Reputation: 13210
Given a datatype
data Foo = IFoo Int | SFoo String deriving (Data, Typeable)
what is a simple definition of
gconstr :: (Typeable a, Data t) => a -> t
such that
gconstr (5 :: Int) :: Foo == IFoo 5
gconstr "asdf" :: Foo == SFoo "asdf"
gconstr True :: Foo == _|_
It would be essentially the opposite of syb's gfindtype
.
Or does such a thing exist already? I've tried hoogle-ing the type and haven't found much, but the syb types are kind of hard to interpret. A function returning Nothing
on error is also acceptable.
Upvotes: 3
Views: 261
Reputation: 29120
This seems to be possible, though it's not completely trivial.
Preliminaries:
{-# LANGUAGE DeriveDataTypeable #-}
import Control.Monad ( msum )
import Data.Data
import Data.Maybe
First a helper function gconstrn
, which tries to do the same thing as required of gconstr
, but for a specific constructor only:
gconstrn :: (Typeable a, Data t) => Constr -> a -> Maybe t
gconstrn constr arg = gunfold addArg Just constr
where
addArg :: Data b => Maybe (b -> r) -> Maybe r
addArg Nothing = Nothing
addArg (Just f) =
case cast arg of
Just v -> Just (f v)
Nothing -> Nothing
The key part is that the addArg
function will use arg
as an argument to the constructor, if the types match.
Essentially gunfold
starts unfolding with Just IFoo
or Just SFoo
, and then the next step is to try addArg
to provide it with its argument.
For multi-argument constructors this would be called repeatedly, so if you defined an IIFoo
constructor that took two Int
s, it would also get successfully filled in by gconstrn
. Obviously with a bit more work you could do something more sophisticated like providing a list of arguments.
Then it's just a question of trying this with all possible constructors. The recursive definition between result
and dt
is just to get the right type argument for dataTypeOf
, the actual value being passed in doesn't matter at all. ScopedTypeVariables
would be an alternative for achieving this.
gconstr :: (Typeable a, Data t) => a -> Maybe t
gconstr arg = result
where result = msum [gconstrn constr arg | constr <- dataTypeConstrs dt]
dt = dataTypeOf (fromJust result)
As discussed in the comments, both functions can be simplified with <*>
from Control.Applicative
to the following, though it's a bit harder to see what's going on in the gunfold
:
gconstr :: (Typeable a, Data t) => a -> Maybe t
gconstr arg = result
where
result = msum $ map (gunfold (<*> cast arg) Just) (dataTypeConstrs dt)
dt = dataTypeOf (fromJust result)
Upvotes: 2