gunfoldl

Simon Peyton-Jones simonpj at microsoft.com
Tue Mar 1 00:51:11 EST 2005


Regardless of the programming, this should not have crashed GHC.  I've
fixed it, and added a regression test.

Thanks for bringing it up.

Simon


| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org
[mailto:glasgow-haskell-users-
| bounces at haskell.org] On Behalf Of Akos Korosmezey
| Sent: 18 February 2005 20:05
| To: GHC-users list
| Subject: gunfoldl
| 
| 
| 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
| --
| ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
| ~~~~~~
| Akos Korosmezey                             Tel:    +36-1-439-5936
| Ericsson Telecom Ltd. ETH/GSCD/RUNB         Fax:    +36-1-437-7576
| P.O.B. 107, H-1300 Budapest, Hungary        Home:   +36-26-342-687
| mailto:Akos.Korosmezey at ericsson.com         Mobile: +36-30-740-7732
| ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
| ~~~~~~
| 
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


More information about the Glasgow-haskell-users mailing list