[Haskell-cafe] reifying based-on type of a newtype or data

John Lato jwlato at gmail.com
Tue Oct 29 06:12:30 UTC 2013


On Mon, Oct 28, 2013 at 11:07 PM, AntC <anthony_clayden at clear.net.nz> wrote:

> > John Lato <jwlato <at> gmail.com> writes:
> >
> > What about Data.Typeable.typeRepArgs ?
> > typeRepArgs :: TypeRep -> [TypeRep]
> > Prelude Data.Data> typeRepArgs (typeOf Foo)[Int,Foo]
>
> Thanks John, I did look at that,
> and thought it returned only type args,
> not the 'baked in' type.
>
> Your example applies to `(typeOf Foo)` -- that is, the data constr,
> which is indeed a function.
> And `typeOf Foo` is `Int -> Foo`, as I noted in the OP.
>
> I want something that can apply to a value of type Foo.
> (`someFoo`, in my example.)
>

Ah, sorry.  I understand now.  First, let's define:

newtype FooT = FooD Int deriving (Data, Typeable, Generic)

someFoo :: FooT
someFoo = FooD 7

so we can keep all the Foo's straight.

Personally I think it's a little more straightforward to do this with Data,
but Generics have some benefits as well, and are probably simpler to pick
up if you don't have much experience with either.

With Data.Data, we can get the name of the data constructor used to create
a 'FooT' by using 'toConstr'

*Foo> toConstr someFoo
FooD

There's not a whole lot we can do with a Constr.  But we can find out the
types of the inner values by mapping over the data structure with gmapM.
gmapM has a hairy type,

gmapM :: (Monad m, Data a) => (forall d. Data d => d -> m d) -> a -> m a

but it's sufficient for this purpose.  Since Data implies Typeable, all you
need to do is call typeOf on the internal values and write them to the
monad!

*Foo >let (_,types) = runWriter $ gmapM (\d -> tell [typeOf d] >> return d)
someFoo
*Foo>> :t types
types :: [TypeRep]
*Foo> types
[Int]

You can do something similar with Generics.  The types look bigger, but the
functions are probably simpler to grok.  And once you start using generics
the types get much easier to read.

*Foo GHC.Generics> let x = from someFoo
*Foo GHC.Generics> :t x
x :: D1 Foo.D1FooT (C1 Foo.C1_0FooT (S1 NoSelector (Rec0 Int))) x

Deriving a Generic instance generates a bunch of auxiliary types, which
contain the same information you could get out of DataRep/Constr.  The
generated structure is fairly uniform: D1 is for datatype information, C1
is constructor information, and S1 is selector information (for record
syntax).  These are all type synonyms around the M1 constructor, used for
meta-information.  So you can just peel of the M1s to get to the
information you want.

*Foo GHC.Generics> datatypeName x
"FooT"
*Foo GHC.Generics> let (M1 xc) = x
*Foo GHC.Generics> :t xc
xc :: C1 Foo.C1_0FooT (S1 NoSelector (Rec0 Int)) t
*Foo GHC.Generics> conName xc
"FooD"
*Foo GHC.Generics> let (M1 xs) = xc
*Foo GHC.Generics> :t xs
xs :: S1 NoSelector (Rec0 Int) t
*Foo GHC.Generics> let (M1 xr) = xs
*Foo GHC.Generics> :t xr
xr :: Rec0 Int t

Rec0 is not meta-information, rather it encodes recursion, which means it
has the actual value we're interested in.  The constructor is K1.

*Foo GHC.Generics> let (K1 xi) = xr
*Foo GHC.Generics> :t xi
xi :: Int
*Foo GHC.Generics> xi
7

At this point, you can get 'typeOf xi', or you could even use `asTypeOf`
(or various other methods) to expose the type directly.

The usual way to use Generic is to make a class that performs the
operations you want, then make instances of that class for (M1 C a b), (M1
D a b), etc.  Although if you control the type, you could hard-wire
unwrapping M1/K1 as I did above.  Doing so is type-safe, since if either
Foo or the internal deriving structure changes, the generated
representation won't match the unwrapping.  Plus this is the easiest way to
expose the 'Int' type to the type system.

I've created a gist that should get you started with the generic class
creation if you decide to go that route,
https://gist.github.com/JohnLato/7209766.

John
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20131029/3e55d3a9/attachment.html>


More information about the Haskell-Cafe mailing list