I confused myself with generics, and now I confused ghc too

I want to implement generic comparison on top of syb-with-class, and based on looking at syb, it seems I could base it on something like gzipWithQ from syb's Data.Generics.Twins. However, there's no Data.Generics.SYB.WithClass.Twins. So I set out to see if I can write one myself (well, one with just enough stuff to support gzipWithQ anyway) Here's what I've got so far: http://hpaste.org/49168 The problem is that GHCi seems to be somewhat confused, or at least confusing, about the type of gzipWithQ here. When I ask with :t, it reports the type as: gzipWithQ :: (Data ctx a2, Data ctx a3, Data ctx a) => Proxy ctx -> (forall a0. Data ctx a0 => a0 -> forall a1. Data ctx a1 => a1 -> r) -> a2 -> a3 -> [r] If I actually replace gzipWithQ's annotated type with this, GHCi will reject the program. And in any case with GenericQ being defined as "type GenericQ ctx r = Data ctx a => a -> r", isn't this closer to gzipWithQ's type with the type synonyms expanded? gzipWithQ :: forall ctx a r. Data ctx a => Proxy ctx -> (Data ctx a0 => a0 -> (Data ctx a1 => a1 -> r)) -> (Data ctx a2 => a2 -> (Data ctx a3 => a3 -> [r])) (GHCi accepts this as gzipWithQ's type so I assume it's the same one. I assume those class constraints after the => come with implicit foralls? Because it seems to mean the same thing if I put foralls in there) I have no idea how to even start figuring out how to make gzipWithQ and its type work. I only got this far by copying code from Data.Generics.Twins and passing down the proxy parameter and/or context type parameter (is it even possible for this approach to work?). What I can tell is that GHCi will still change the type like that even if gzipWithQ = undefined, so I'll have to change the type and not just the body of the function. Is this the kind of thing that all those newtypes in Data.Generics.Twins are for? Should I read up on type theory?

Hi Ari, I won't really try to answer your question, but I'll give you the code for gzipWithQ written by Alexey Rodriguez Yakushev some years ago for his comparison on generic programming libraries. The original darcs repo no longer exists, but here is the file which I think is relevant for you:
{-# OPTIONS_GHC -fglasgow-exts #-}
{-# OPTIONS_GHC -fallow-undecidable-instances #-} {-# OPTIONS_GHC -fallow-overlapping-instances #-}
module Traversals where
import Data.Generics.SYB.WithClass.Basics import BinTreeDatatype import BinTreeReps
These traversals were copied (and adapted) from CtxSchemes.hs. That file is distributed in
< http://homepages.cwi.nl/~ralf/syb3/code.html
The adaptations are necessary so that it works with SYB3 distributed in:
< darcs get http://happs.org/HAppS/syb-with-class
-- | A type constructor for accumulation newtype A a c d = A { unA :: a -> (a, c d) }
gfoldlAccum :: Data ctx d => Proxy ctx -> (forall d r. Data ctx d => a -> c (d -> r) -> d -> (a, c r)) -> (forall g. a -> g -> (a, c g)) -> a -> d -> (a, c d)
gfoldlAccum ctx k z a d = unA (gfoldl ctx k' z' d) a where k' c y = A (\a -> let (a', c') = unA c a in k a' c' y) z' f = A (\a -> z a f)
-- | gmapQr with accumulation gmapAccumQr :: Data ctx d => Proxy ctx -> (r' -> r -> r) -> r -> (forall d. Data ctx d => a -> d -> (a,r')) -> a -> d -> (a, r) gmapAccumQr ctx o r f a d = let (a',l) = gfoldlAccum ctx k z a d in (a',unQr l r) where k a (Qr c) d = let (a',r') = f a d in (a', Qr (\r -> c (r' `o` r))) z a _ = (a, Qr id)
-- | gmapQ with accumulation gmapAccumQ :: Data ctx d => Proxy ctx -> (forall d. Data ctx d => a -> d -> (a,q)) -> a -> d -> (a, [q]) gmapAccumQ ctx f = gmapAccumQr ctx (:) [] f
Adapted from the source code of SYB 1&2 to work with syb3
gzipWithQ :: forall ctx r . Proxy ctx -> GenericQ ctx (GenericQ ctx r) -> GenericQ ctx (GenericQ ctx [r]) gzipWithQ ctx f x y = case gmapAccumQ ctx perkid funs y of ([], r) -> r _ -> error "gzipWithQ" where perkid a d = (tail a, unGQ (head a) d) funs :: [GenericQ' ctx r] funs = gmapQ ctx (\k -> GQ (f k)) x newtype GenericQ' ctx r = GQ { unGQ :: GenericQ ctx r }
Adapted from CtxSchemes.hs
everything :: Proxy ctx -> (r -> r -> r) -> GenericQ ctx r -> GenericQ ctx r everything ctx k f x = foldl k (f x) (gmapQ ctx (everything ctx k f) x)
everywhere :: Proxy ctx -> GenericT ctx -> GenericT ctx everywhere ctx f = f . gmapT ctx (everywhere ctx f)
Let me know if this doesn't work, or if you need something else.
Cheers,
Pedro
On Mon, Jul 18, 2011 at 15:42, Ari Rahikkala
I want to implement generic comparison on top of syb-with-class, and based on looking at syb, it seems I could base it on something like gzipWithQ from syb's Data.Generics.Twins. However, there's no Data.Generics.SYB.WithClass.Twins. So I set out to see if I can write one myself (well, one with just enough stuff to support gzipWithQ anyway) Here's what I've got so far: http://hpaste.org/49168
The problem is that GHCi seems to be somewhat confused, or at least confusing, about the type of gzipWithQ here. When I ask with :t, it reports the type as:
gzipWithQ :: (Data ctx a2, Data ctx a3, Data ctx a) => Proxy ctx -> (forall a0. Data ctx a0 => a0 -> forall a1. Data ctx a1 => a1 -> r) -> a2 -> a3 -> [r]
If I actually replace gzipWithQ's annotated type with this, GHCi will reject the program. And in any case with GenericQ being defined as "type GenericQ ctx r = Data ctx a => a -> r", isn't this closer to gzipWithQ's type with the type synonyms expanded?
gzipWithQ :: forall ctx a r. Data ctx a => Proxy ctx -> (Data ctx a0 => a0 -> (Data ctx a1 => a1 -> r)) -> (Data ctx a2 => a2 -> (Data ctx a3 => a3 -> [r]))
(GHCi accepts this as gzipWithQ's type so I assume it's the same one. I assume those class constraints after the => come with implicit foralls? Because it seems to mean the same thing if I put foralls in there)
I have no idea how to even start figuring out how to make gzipWithQ and its type work. I only got this far by copying code from Data.Generics.Twins and passing down the proxy parameter and/or context type parameter (is it even possible for this approach to work?). What I can tell is that GHCi will still change the type like that even if gzipWithQ = undefined, so I'll have to change the type and not just the body of the function. Is this the kind of thing that all those newtypes in Data.Generics.Twins are for? Should I read up on type theory?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
Ari Rahikkala
-
José Pedro Magalhães