[Haskell-cafe] What are Kind errors and how do you fix them?
MR K P SCHUPKE
k.schupke at imperial.ac.uk
Wed Mar 24 09:13:49 EST 2004
Erm... okay my mistake thats not the problem... although it is to
with state...
When decaring a monad the return type is included in the class
definition (it is a constructor class) This means the return value
MUST be the last parameter to the type, so you need:
type ReverseType a string = (string ->(string,a))
data Reverse string a = Reverse (ReverseType a string)
instance Monad (Reverse s) where
return x = Reverse (\text -> (text,x))
(Reverse p) >>= k = Reverse p3 where
p3 s0 = p2 s1 where
(Reverse p2) = k a
(s1,a)=p s0
I was confused by the unusual format for bind... I would wtite
this:
instance Monad (Reverse s) where
return x = Reverse $ \s -> (s,x)
(Reverse p) >>= k = Reverse $ \s -> case p s of
(s',a) -> (\(Reverse r) -> r) (k a) s'
or even better define the data type as:
data Reverse string a = Reverse { runReverse :: ReverseType a string }
instance Monad (Reverse s) where
return x = Reverse $ \s -> (s,x)
(Reverse p) >>= k = Reverse $ \s -> case p s of
(s',a) -> runReverse (k a) s'
Regards,
Keean.
More information about the Haskell-Cafe
mailing list