[Hs-Generics] pervasiveness of Rec in TH-derived instant-generics representation types

José Pedro Magalhães jpm at cs.uu.nl
Thu Feb 17 14:00:19 CET 2011


Hi,

2011/2/16 Nicolas Frisby <nicolas.frisby at gmail.com>

> Thanks for the quick response!
>
> The Mappable class from Section 4.2 of the Fast and Easy! paper left
> me with the feeling that Rec and Var were useful. Has something else
> replaced that use in those examples or am I overestimating their
> usefulness?
>

There the Var is applied to a single type variable (let's assume it is the
last type variable of kind *). Then you can use this to write an fmap, which
is quite cool. Let me paste here the code adapted to work with the released
version:

import Generics.Instant
> import Generics.Instant.Instances
>
> class Mappable t a b where
>   type Rebind t a b
>   mapit :: (a -> b) -> t -> Rebind t a b
>
> instance Mappable U a b where
>   type Rebind U a b = U
>   mapit f U = U
>
> instance (Mappable t a b) => Mappable (C c t) a b where
>   type Rebind (C c t) a b = C c (Rebind t a b)
>   mapit f (C a) = C (mapit f a)
>
> instance (Mappable t a b, Mappable u a b) => Mappable (t :*: u) a b where
>   type Rebind (t :*: u) a b = Rebind t a b :*: Rebind u a b
>   mapit f (t :*: u) = mapit f t :*: mapit f u
>
> instance (Mappable t a b, Mappable u a b) => Mappable (t :+: u) a b where
>   type Rebind (t :+: u) a b = Rebind t a b :+: Rebind u a b
>   mapit f (L t) = L (mapit f t)
>   mapit f (R u) = R (mapit f u)
>
> instance Mappable (Var a) a b where
>   type Rebind (Var a) a b = Var b
>   mapit f (Var a) = Var (f a)
>
> class Fun f where
>   mapp :: (a -> b) -> f a -> f b
>
> instance Fun f => Mappable (Rec (f a)) a b where
>   type Rebind (Rec (f a)) a b = Rec (f b)
>   mapit f (Rec t) = Rec (mapp f t)
>
> generic_map :: (Representable (f a), Representable (f b),
>                 Mappable (Rep (f a)) a b,
>                 Rebind (Rep (f a)) a b ~ Rep (f b))
>             => (a -> b) -> f a -> f b
> generic_map f x = to (mapit f (from x))
>
> instance Fun [] where mapp = generic_map
> instance Fun Maybe where mapp = generic_map
>

If you want to support datatypes with more type variables (like Either, for
instance), I think you need to add another representation type, e.g. Other,
which tags things that are not to be mapped over:

data Oth a = Oth a
>
> instance Representable (Either a b) where
>   type Rep (Either a b) = (Oth a :+: Var b)
>   from (Left  a) = L (Oth a)
>   from (Right a) = R (Var a)
>   to (L (Oth a)) = Left a
>   to (R (Var a)) = Right a
>
> instance Mappable (Oth a) b c where
>   type Rebind (Oth a) b c = Oth a
>   mapit f (Oth a) = Oth a
>
> instance Fun (Either a) where mapp = generic_map
>

What I haven't yet tried is an example with mutually recursive datatypes.
This relates to your next question...


>
> Would there be any harm in determining the mutually recursive
> datatypes and Rec-tagging exactly those fields that are part of the
> mutually recursive group? We might have some bitrotted TH code lying
> around that identifies the strongly connected types in a mutual
> recursive group of declarations. Please let me know if that's an
> attractive way forward for determining whether or not to insert the
> Rec.
>

So, for the code that is currently on Hackage, I don't think there would be
any harm in doing this; it would be great, actually. But I don't know how it
would affect the generic_map above... but, anyway, the generic_map above
wouldn't work with the current TH code, so something will have to change if
we want to incorporate generic_map.


Cheers,
Pedro


>
> 2011/2/16 José Pedro Magalhães <jpm at cs.uu.nl>:
> > Hi,
> >
> > On Wed, Feb 16, 2011 at 23:03, Nicolas Frisby <nicolas.frisby at gmail.com>
> > wrote:
> >>
> >> In instant-generics-0.2.1, the TH functions for deriving the Rep type
> >> instances insert the "Rec" type at every field. Is there a consequence
> >> to this?
> >>
> >> This behavior seems at odds with the paper; isn't Rec only meant as an
> >> indicator of recursive occurrences within the original data type?
> >
> > I think that is the current behavior, yes. I've given some thought to
> this
> > in the generic deriving paper [1]; in fact, tagging a recursive
> occurrence
> > with Var or Rec doesn't make much difference, since in the end it is just
> a
> > tag. You can't, for instance, define an fmap function by mapping over the
> > things tagged with Var, because you know nothing about the types of those
> > things.
> >
> > This doesn't mean they are entirely useless, though. In fact,
> > instant-generics makes use of this in the empty function [2]: on a sum,
> it
> > looks ahead to see if there are Rec's on the left or right, and proceeds
> to
> > the side that has no Rec's. This guarantees that a finite element will be
> > generated (if there is one). So, tagging only the occurrences of the
> > original type with Rec wouldn't be very helpful, since datatypes can be
> > mutually recursive.
> >
> > I think the best approach is to tag everything as Rec, except for
> parameters
> > and base types. That is what we do in UHC [1], if I recall correctly.
> >
> > And, as the comment says, the TH code for instant-generics should be
> updated
> > to generate Var tags too. I haven't gotten around to do that yet, but if
> > it's important for you I can have a look. Of course, patches are welcome
> too
> > [3].
> >
> >
> > Cheers,
> > Pedro
> >
> > [1] http://www.dreixel.net/research/pdf/gdmh.pdf
> > [2]
> >
> http://hackage.haskell.org/packages/archive/instant-generics/0.2.1/doc/html/Generics-Instant-Functions-Empty.html
> > [3]
> https://subversion.cs.uu.nl/repos/project.dgp-haskell.libraries/Instant/
> >
> >>
> >> Thanks.
> >>
> >> ---
> >>
> >> snippet from http://j.mp/gK8MOk ; repField is invoked for every field
> >> of every constructor by all of the relevant TH entry-points.
> >>
> >>  repField :: (Name, [Name]) -> Type -> Q Type
> >>  --repField d t | t == dataDeclToType d = conT ''I
> >>  repField d t = conT ''Rec `appT` return t
> >>
> >>  repField' :: (Name, [Name]) -> Name -> (Name, Strict, Type) -> Q Type
> >>  --repField' d ns (_, _, t) | t == dataDeclToType d = conT ''I
> >>  repField' (dt, vs) ns (f, _, t) = conT ''Rec `appT` return t
> >>  -- Note: we should generate Var too, at some point
> >>
> >> _______________________________________________
> >> Generics mailing list
> >> Generics at haskell.org
> >> http://www.haskell.org/mailman/listinfo/generics
> >
> >
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/generics/attachments/20110217/382b8dc0/attachment.htm>


More information about the Generics mailing list