Existential type question

Hi all, I've come across some code I just can't figure out how to write appropriately. Below is a silly example that demonstrates what I'm trying to do. I don't really have the appropriate vocabulary to describe the issue, so I'll let the code speak for itself. In particular, I'm trying to understand what the correct type signatures for unwrapMyData and bin should be. Thanks, Michael --- {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} class Monad m => MonadFoo x m where foo :: x -> m a data MyData a = forall i. Integral i => MyLeft i | MyRight a instance Monad MyData where return = MyRight (MyLeft i) >>= _ = MyLeft i (MyRight x) >>= f = f x instance Integral i => MonadFoo i MyData where foo = MyLeft bar :: MonadFoo Int m => Int -> m String bar 0 = return "zero" bar i = foo i baz :: String -> MyData String baz "zero" = MyRight "Zero" baz _ = MyLeft (-1 :: Integer) --This works: unwrapMyData (MyLeft i) = foo (fromIntegral i :: Integer) unwrapMyData (MyLeft i) = foo i -- This is what I'd like to work unwrapMyData (MyRight a) = return a bin i = do a <- bar i b <- unwrapMyData $ baz a return $ b ++ "!!!" instance Show a => MonadFoo a IO where foo = fail . show -- I know, it's horrible... main = do res <- bin 0 putStrLn res

Am Sonntag 22 November 2009 19:24:48 schrieb Michael Snoyman:
Hi all,
I've come across some code I just can't figure out how to write appropriately. Below is a silly example that demonstrates what I'm trying to do. I don't really have the appropriate vocabulary to describe the issue, so I'll let the code speak for itself. In particular, I'm trying to understand what the correct type signatures for unwrapMyData and bin should be.
Thanks, Michael
---
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} class Monad m => MonadFoo x m where foo :: x -> m a
data MyData a = forall i. Integral i => MyLeft i
| MyRight a
instance Monad MyData where return = MyRight (MyLeft i) >>= _ = MyLeft i (MyRight x) >>= f = f x instance Integral i => MonadFoo i MyData where foo = MyLeft
bar :: MonadFoo Int m => Int -> m String bar 0 = return "zero" bar i = foo i
baz :: String -> MyData String baz "zero" = MyRight "Zero" baz _ = MyLeft (-1 :: Integer)
--This works: unwrapMyData (MyLeft i) = foo (fromIntegral i :: Integer) unwrapMyData (MyLeft i) = foo i -- This is what I'd like to work
I don't see how it could (except perhaps...). The type would be unwrapMyData ::(forall i. (Integral i => MonadFoo i m)) => MyData a -> m a - the MyData a -> m a part is obviously necessary, but MyLeft can wrap *any* integral type, so you indeed need instances MonadFoo i m for *every* integral type. You can't specify that condition in Haskell. You could try instance MonadFoo a [] where foo _ = [] instance MonadFoo a Maybe where foo _ = Nothing (more general, instance (MonadPlus m) => MonadFoo a m where foo _ = mzero ) unwrapMyData :: (MonadPlus m) => MyData a -> m a that might be got to work, but it's very likely not even remotely what you want (unwrapMyData :: MyData a -> [a] would work with the above instance, I think, but it would be rather pointless).
unwrapMyData (MyRight a) = return a
bin i = do a <- bar i
You must specify which instance of MonadFoo to use here, otherwise it is impossible to determine which instance of bar to use, and the type of bin is irredeemably ambiguous (show . read).
b <- unwrapMyData $ baz a return $ b ++ "!!!"
instance Show a => MonadFoo a IO where foo = fail . show -- I know, it's horrible...
main = do res <- bin 0 putStrLn res
participants (2)
-
Daniel Fischer
-
Michael Snoyman