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
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to