[Hs-Generics] Regular problem

lists at snowlion.nl lists at snowlion.nl
Mon Jan 17 19:22:44 CET 2011


Hi Pedro,

On 01/17/2011 05:14 PM, José Pedro Magalhães wrote:
> This looks like a bug to me, thanks for reporting. I will fix it soon.
Great, I'm not very fluent in template haskell...
Thanks,

Maarten

>
>
> Cheers,
> Pedro
>
> On Mon, Jan 17, 2011 at 17:08, lists at snowlion.nl 
> <mailto:lists at snowlion.nl> <lists at snowlion.nl 
> <mailto:lists at snowlion.nl>> wrote:
>
>
>     Hi all,
>
>     /(I think something went wrong with my previous email, so if this
>     is sent twice, I apologize)
>     /
>     Why do self referential structure omit the selector in record
>     entries referencing themselves when converting to the regular data
>     structure?
>
>     For instance, when splicing the following data structure:
>
>     data P = V {v::String} | II {i::Integer} | P { p::P }
>       deriving Show
>
>     $(deriveAll ''P "PFP")
>     type instance PF P = PFP
>
>     It generates the following code:
>
>             ...generics at haskell.org <mailto:generics at haskell.org>
>             data P_P_ =
>             ...
>             instance Constructor P_P_ where
>                 { conName _ = "P"
>                   conIsRecord _ = True }
>             ...
>             data P_P_p_ =
>             instance Selector P_V_v_ where
>                 { selName _ = "v" }
>             ...
>             instance Selector P_P_p_ where
>                 { selName _ = "p" }
>             type PFP = :+: (C P_V_ (S P_V_v_ (K String))) (:+: (C
>     P_II_ (S P_II_i_ (K Integer))) (C P_P_ I))
>             instance Regular P where
>                 {         ...generics at haskell.org
>     <mailto:generics at haskell.org>
>                     from II f0 = R (L (C (S (K f0))))
>                     from P f0 = R (R (C (I f0)))
>                     ...
>                     to R L C S K f0 = II f0
>                     to R R C I f0 = P f0 }
>
>     Why is the selector name in case of a self referencing record
>     omitted? I would have expected something like this:
>
>             type PFP = :+: (C P_V_ (S P_V_v_ (K String))) (:+: (C
>     P_II_ (S P_II_i_ (K Integer))) (C P_P_ (S P_P_p_ I)))
>
>     and likewise:
>
>                     from II f0 = R (L (C (S (K f0))))
>                     from P f0 = R (R (C (S (I f0))))
>                     ...
>                     to R L C S K f0 = II f0
>                     to R R C S I f0 = P f0 }
>
>     This gives problems when parsing these kind of structure, or am I
>     missing something?
>
>     kind regards,
>
>     Maarten
>
>
>
>
>
>     _______________________________________________
>     Generics mailing list
>     Generics at haskell.org <mailto: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/20110117/12b0e553/attachment.htm>


More information about the Generics mailing list