Here is something else that I don't quite understand...

Original version compiles:

push :: Show b => State b -> Dispatcher b a -> (ScriptState a b) ()
push state dispatcher =
    do w <- get
       trace 95 $ "push: Pushing " ++ show state ++ " onto the stack"
       let s = stack w
       putStrict $ w { stack = (state, dispatcher):s }

data State a
    = Start
    | Stop
    | (Show a, Eq a) => State a

instance Eq a => Eq (State a) where
    (State a) == (State b) = a == b
    Start == Start = True
    Stop == Stop = True
    _ == _ = False

instance Show a => Show (State a) where
    show (State a) = show a
    show Start = "Start"
    show Stop = "Stop"

This version does not. Why does it require Eq in the ++ context? And why doesn't the other version?

data (Show a, Eq a) => State a
    = Start
    | Stop
    | State a
    deriving (Eq, Show)

Could not deduce (Eq b) from the context (Show b)
   arising from use of `show' at ./Script/Engine.hs:86:38-41
Probable fix: add (Eq b) to the type signature(s) for `push'
In the first argument of `(++)', namely `show state'
In the second argument of `(++)', namely `(show state) ++ " onto the stack"'

--
http://wagerlabs.com/





_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to