I have created an entry in the syb-with-class issue database here:http://code.google.com/p/syb-with-class/issues/detail?id=3
I attached a version of the code with the necessary bits of Happstack.Data.Default included in-line. On Thu, Dec 3, 2009 at 2:50 PM, Jeremy Shaw <jer...@n-heptane.com> wrote: > I have the following program which loops under GHC 6.10.4: > > http://www.hpaste.org/fastcgi/hpaste.fcgi/view?id=13561#a13561 > > {-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, > UndecidableInstances #-} > module Main where > > import qualified Data.Data as Data > import Data.Typeable (Typeable) > import Happstack.Data.Default > import Data.Generics.SYB.WithClass.Basics > import Data.Generics.SYB.WithClass.Instances () > > data Proposition = Proposition Expression deriving (Show, Data.Data, > Typeable) > data Expression = Conjunction (Maybe Expression) deriving (Show, Data.Data, > Typeable) > > -- instance (Sat (ctx [Expression]), Sat (ctx Expression), Sat (ctx > Proposition)) => Data ctx Proposition where > instance Data DefaultD Proposition where > gunfold _ k z c = > case constrIndex c of > 1 -> k (z Proposition) > instance Default Proposition > > constrExpr :: Constr > constrExpr = mkConstr dataTypeExpr "Conjuction" [] Prefix > > dataTypeExpr :: DataType > dataTypeExpr = mkDataType "Expression" [constrExpr] > > instance ( Data ctx [Expression] > , Sat (ctx Expression) > , Sat (ctx (Maybe Expression))) => Data ctx Expression where > {- > instance Data DefaultD Expression where > -} > gunfold _ k z c = > case constrIndex c of > 1 -> k (z Conjunction) > dataTypeOf _ _ = dataTypeExpr > > instance Default Expression > > e :: Expression > e = defaultValueD dict > > main = print e > > I wish to explain the *many* ways in which it is mysterious. If you load the > program into GHCi and evaluate 'e' it will hang. If you compile the program > and run it, it will output <<loop>>. This behavior seems annoying, but not > very weird. But, here is where it gets fun: > > 1. if you load the program into GHCi and eval 'e' it will hang. But, if you > load the program and type, '(defaultValueD dict) :: Expression' at the > prompt, it works fine! > > 2. if you remove the (Data DefaultD Proposition) instance, it works fine. > (Even though Expression does not refer to Proposition in any way) > > 3. if you simply change the definition of 'gunfold' in the 'Data ctx > Proposition' instance to, error "foo". The application works fine. That's > right, if you change the body of a function that isn't even being called, > evaluating 'e' starts working. (Even though Expression does not refer to > Proposition in any way. And even though that gunfold instance is never > actually called). > > 4. if you change the constraint on, Data ctx Expression, from (Data ctx > [Expression]) to (Data ctx Expression) it works fine. (Or remove it all > together). > > 5. if you change 'instance (Data DefaultD Proposition) where' to the line > above it which is commented out, it works fine. > > 6. if you change the type of Proposition to, data Proposition = Proposition > (Expression, Expression), then it works fine. > > So far I have only tested this in GHC 6.10.4. > > Any idea what is going on here? I can't imagine how changing the body of > functions that aren't being called would fix things... > > - jeremy > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe