gunfoldl

Ralf Laemmel Ralf.Laemmel at cwi.nl
Fri Feb 18 16:24:41 EST 2005


It is called "gunfold" rather than "gunfoldl"
as you will see when you browse the Data.Generics.Basics.

Also, your gunfold code looks like it will not work.

Here is a simple example for Maybe:
    gunfold k z con   =
      case constrIndex con of
        1 -> z Nothing  -- no children
        2 -> k (z Just) -- one child, hence one k

Bottom line:
- apply z to the Constructor
- apply k as many times as the number of children.

No warranty that this is easy for your type Item.

Good luck,
Ralf

Akos Korosmezey wrote:

>
> I wrote a little data structure with quantified constructors:
>
> module MyModule where
>   import Data.Generics
>   import Data.HashTable
>
>   data Item = forall a. (Data a) => Leaf Bool a
>             | forall a. (Data a) => Branch Bool a Int Int
>                                                                                      
> deriving (Typeable)
>
> I want it to make an instance of Data:
>
>   instance Data Item where
>       gfoldl k z (Leaf b v) = z (Leaf b) `k` v
>       gfoldl k z (Branch b v a1 a2) = z (\x -> Branch b x a1 a2) `k` v
>       --gunfoldl k z c = case constrIndex c of
>       --                                    1 -> k z (Leaf undefined 
> undefined)
>       toConstr (Leaf _ _) = leafConstr
>       toConstr (Branch _ _ _ _) = branchConstr
>       dataTypeOf _ = itemDataType
>
>   itemDataType = mkDataType "Subliminal.Item" [leafConstr, branchConstr]
>   leafConstr = mkConstr itemDataType "Leaf" [] Prefix
>   branchConstr = mkConstr itemDataType "Branch" [] Prefix
>
> But, when I try to compile it with ghc-6.4-20050217:
>
> ghc -fglasgow-exts -i. -c kicsi.hs
>
> kicsi.hs:13:4:
>   Warning: No explicit method nor default method for `gunfold'
>        In the instance declaration for `Data Item'
> ghc-6.4.20050217: panic! (the `impossible' happened, GHC version 
> 6.4.20050217):
>   cgPanic
>   k{v a1vu}
>   static binds for:
>   local binds for:
>   gunfold{v r22q}
>   SRT labelghc-6.4.20050217: panic! (the `impossible' happened, GHC 
> version 6.4.20050217):
>   initC: srt
>
> Please report it as a compiler bug to glasgow-haskell-bugs at haskell.org,
> or http://sourceforge.net/projects/ghc/.
>
> If I uncomment the gunfoldl lines:
>
> ghc -fglasgow-exts -i. -c kicsi.hs
>
> kicsi.hs:12:8: `gunfoldl' is not a (visible) method of class `Data'
>
> Compilation exited abnormally with code 1 at Fri Feb 18 20:55:32
>
> Could you please help me?
>
> Thanks
> Akos



-- 
Ralf Lammel
ralfla at microsoft.com
Microsoft Corp., Redmond, Webdata/XML
http://www.cs.vu.nl/~ralf/




More information about the Glasgow-haskell-users mailing list