Sorry, I meant to send this to the whole list.
Brock Peabody wrote:
Please excuse my newbiness, but in this snippet:
data (Monad m) => DataType m = DataType { f :: Char -> m () }
test_function :: (Monad m) => DataType m -> m ()
^^^^^^^^^^^^
test_function d = f d 'C'
Why is "(Monad m) =>" required, when the definition of DataType already
implies it? Is there an easier way to do this or will I have to have it
in all signatures containing DataType?
Because class constraints on data types are a bit silly. It just
restricts the types of the constructors so you can only apply them if m
is a Monad. It doesn't actually package up the evidance that m is a
monad inside the value to make this stuff work.
Existential types do package up the class instance in the value, but
they hide the type.
data Showable = forall a . (Show a) => Showable a
showShowable :: Showable -> String
showShowable (Showable x) = show x
Getting them both is tricky, but you can do it if you use a GADT to
write a type that means "exists a such that a = m and a is a Monad":
{-# OPTIONS -fglasgow-exts #-}
data TyEq (a :: * -> *) (b :: * -> *) where
Refl :: TyEq a a
data DataType m = forall m' . (Monad m') => DataType (TyEq m m') (Char
-> m' ())
buildDataType :: (Monad m) => (Char -> m ()) -> DataType m
buildDataType = DataType Refl
test_function :: DataType m -> m ()
test_function (DataType Refl f) = f 'C'
-- try let x = buildDataType putChar
-- :t x
-- :t test_function
-- test_function x
Brandon
Thanks,
Brock
_______________________________________________
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