SYB <<looping>> very, very mysteriously

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

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
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

I have stripped things down to the bare minimum, and test under GHC 6.10, GHC 6.12, Linux, and Mac OS X. Results are consistent. In the following code, 1. if you load the code into ghci and evaluate e it will hang, but (defaultValueD dict) :: Expression returns fine 2. if you change the gunfold instance for Proposition to, error "gunfold" it stops hanging -- even though this code is never called. 3. if you change, ( Data ctx [Expression], Sat (ctx Expression) => Data ctx Expression, to (Data ctx Expression, ....) => ... it stops hanging. If someone could explain why each of these cases perform as they do, that would be awesome! Right now it is a big mystery to me.. e calls dict .. and there is only one instance of dict available, which should call error right away. I can't see how something could get in the way there... - jeremy {-# LANGUAGE DeriveDataTypeable, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, UndecidableInstances, RankNTypes, ScopedTypeVariables, KindSignatures, EmptyDataDecls, NoMonomorphismRestriction #-} module Main where import qualified Data.Data as Data import Data.Typeable --- syb-with-class data Constr = Constr deriving (Eq, Show) data Proxy (a :: * -> *) class Sat a where dict :: a class (Typeable a, Sat (ctx a)) => Data ctx a where gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a instance (Sat (ctx [a]),Data ctx a) => Data ctx [a] --- Default class (Data DefaultD a) => Default a where defaultValue :: a data DefaultD a = DefaultD { defaultValueD :: a } instance Default t => Sat (DefaultD t) where dict = error "Sat (DefaultD t) not implemented" instance Default a => Default [a] where defaultValue = error "Default [a] not implemented" --- Trouble data Proposition = Proposition Expression deriving (Show, Data.Data, Typeable) data Expression = Conjunction 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 = k (z Proposition) -- gunfold _ k z c = error "gunfold" instance Default Proposition -- Change Data ctx [Expression] to Data ctx Expression and main works. instance ( Data ctx [Expression] , Sat (ctx Expression) ) => Data ctx Expression instance Default Expression e :: Expression e = defaultValueD (dict :: DefaultD Expression) main = print e

On Fri, Dec 4, 2009 at 8:51 PM, Jeremy Shaw
I have stripped things down to the bare minimum, and test under GHC 6.10, GHC 6.12, Linux, and Mac OS X. Results are consistent.
In the following code,
1. if you load the code into ghci and evaluate e it will hang, but (defaultValueD dict) :: Expression returns fine 2. if you change the gunfold instance for Proposition to, error "gunfold" it stops hanging -- even though this code is never called. 3. if you change, ( Data ctx [Expression], Sat (ctx Expression) => Data ctx Expression, to (Data ctx Expression, ....) => ... it stops hanging.
If someone could explain why each of these cases perform as they do, that would be awesome! Right now it is a big mystery to me.. e calls dict .. and there is only one instance of dict available, which should call error right away. I can't see how something could get in the way there...
It's less of a mystery if you think about the actual dictionaries ghc uses to implement typeclasses. The instance for Data ctx [a] depends on Data ctx a, so by requiring Data ctx [Expression] in the Data ctx Expression instance you're indeed making a loop there, though typeclasses do allow this, and the implementation has to be lazy enough to permit it. Strange that with a direct Data ctx Expression => Data ctx Expression loop we don't get the same problem. The reason the implementation of Proposition's gunfold matters is probably that k gets passed the dictionary for Data DefaultD Expression at the site of its call and some optimization is making it stricter than necessary. Looks like we need a ghc dev here to fully unravel the mystery, in the meantime i'll try to reduce the test case even further.
- jeremy
{-# LANGUAGE DeriveDataTypeable, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, UndecidableInstances, RankNTypes, ScopedTypeVariables, KindSignatures, EmptyDataDecls, NoMonomorphismRestriction #-} module Main where
import qualified Data.Data as Data import Data.Typeable
--- syb-with-class
data Constr = Constr deriving (Eq, Show)
data Proxy (a :: * -> *)
class Sat a where dict :: a
class (Typeable a, Sat (ctx a)) => Data ctx a where gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a
instance (Sat (ctx [a]),Data ctx a) => Data ctx [a]
--- Default
class (Data DefaultD a) => Default a where defaultValue :: a
data DefaultD a = DefaultD { defaultValueD :: a }
instance Default t => Sat (DefaultD t) where dict = error "Sat (DefaultD t) not implemented"
instance Default a => Default [a] where defaultValue = error "Default [a] not implemented"
--- Trouble
data Proposition = Proposition Expression deriving (Show, Data.Data, Typeable) data Expression = Conjunction 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 = k (z Proposition) -- gunfold _ k z c = error "gunfold"
instance Default Proposition
-- Change Data ctx [Expression] to Data ctx Expression and main works. instance ( Data ctx [Expression] , Sat (ctx Expression) ) => Data ctx Expression
instance Default Expression
e :: Expression e = defaultValueD (dict :: DefaultD Expression)
main = print e
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, Dec 5, 2009 at 2:38 AM, Andrea Vezzosi
On Fri, Dec 4, 2009 at 8:51 PM, Jeremy Shaw
wrote: I have stripped things down to the bare minimum, and test under GHC 6.10, GHC 6.12, Linux, and Mac OS X. Results are consistent.
In the following code,
1. if you load the code into ghci and evaluate e it will hang, but (defaultValueD dict) :: Expression returns fine 2. if you change the gunfold instance for Proposition to, error "gunfold" it stops hanging -- even though this code is never called. 3. if you change, ( Data ctx [Expression], Sat (ctx Expression) => Data ctx Expression, to (Data ctx Expression, ....) => ... it stops hanging.
If someone could explain why each of these cases perform as they do, that would be awesome! Right now it is a big mystery to me.. e calls dict .. and there is only one instance of dict available, which should call error right away. I can't see how something could get in the way there...
It's less of a mystery if you think about the actual dictionaries ghc uses to implement typeclasses. The instance for Data ctx [a] depends on Data ctx a, so by requiring Data ctx [Expression] in the Data ctx Expression instance you're indeed making a loop there, though typeclasses do allow this, and the implementation has to be lazy enough to permit it. Strange that with a direct Data ctx Expression => Data ctx Expression loop we don't get the same problem. The reason the implementation of Proposition's gunfold matters is probably that k gets passed the dictionary for Data DefaultD Expression at the site of its call and some optimization is making it stricter than necessary.
Looks like we need a ghc dev here to fully unravel the mystery, in the meantime i'll try to reduce the test case even further.
I have posted a ghc bug for this: http://hackage.haskell.org/trac/ghc/ticket/3731 and an syb-with-class bug, in case it is not a ghc bug (perhaps due to undecidable instances?):http://code.google.com/p/syb-with-class/issues/detail?id=3

On Mon, Dec 7, 2009 at 3:38 PM, David Fox
On Sat, Dec 5, 2009 at 2:38 AM, Andrea Vezzosi
wrote: On Fri, Dec 4, 2009 at 8:51 PM, Jeremy Shaw
wrote: I have stripped things down to the bare minimum, and test under GHC 6.10, GHC 6.12, Linux, and Mac OS X. Results are consistent.
In the following code,
1. if you load the code into ghci and evaluate e it will hang, but (defaultValueD dict) :: Expression returns fine 2. if you change the gunfold instance for Proposition to, error "gunfold" it stops hanging -- even though this code is never called. 3. if you change, ( Data ctx [Expression], Sat (ctx Expression) => Data ctx Expression, to (Data ctx Expression, ....) => ... it stops hanging.
If someone could explain why each of these cases perform as they do, that would be awesome! Right now it is a big mystery to me.. e calls dict .. and there is only one instance of dict available, which should call error right away. I can't see how something could get in the way there...
It's less of a mystery if you think about the actual dictionaries ghc uses to implement typeclasses. The instance for Data ctx [a] depends on Data ctx a, so by requiring Data ctx [Expression] in the Data ctx Expression instance you're indeed making a loop there, though typeclasses do allow this, and the implementation has to be lazy enough to permit it. Strange that with a direct Data ctx Expression => Data ctx Expression loop we don't get the same problem. The reason the implementation of Proposition's gunfold matters is probably that k gets passed the dictionary for Data DefaultD Expression at the site of its call and some optimization is making it stricter than necessary.
Looks like we need a ghc dev here to fully unravel the mystery, in the meantime i'll try to reduce the test case even further.
I have posted a ghc bug for this: http://hackage.haskell.org/trac/ghc/ticket/3731 and an syb-with-class bug, in case it is not a ghc bug (perhaps due to undecidable instances?):http://code.google.com/p/syb-with-class/issues/detail?id=3
While trying to make the test case on the ghc trac self-contained I've found a workaround which involves changing the Default [a] instance in happstack-data. I've attached the patch. I don't know why it works with certainity, so it'd be nice if you could test it in a large codebase at least. The problem is that one should work out how all these dictionaries get constructed, and that means staring at a lot of Core.
participants (3)
-
Andrea Vezzosi
-
David Fox
-
Jeremy Shaw