[Haskell-cafe] SYB <<looping>> very, very mysteriously

Jeremy Shaw jeremy at n-heptane.com
Fri Dec 4 14:51:14 EST 2009


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



More information about the Haskell-Cafe mailing list