{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances,
FlexibleContexts, OverlappingInstances, TypeFamilies #-}
class Monad m => Ret a m b where
returnN :: a -> m b
instance (Monad m, a ~ b) => Ret a m b where
returnN = return
instance (Monad m, Monad n, Ret a m b) => Ret a n (m b) where
returnN = return . returnN
boo :: [[[Maybe [Either () [Int]]]]]
boo = returnN 0
Dmitry Bogatov
Hi, list!
I want to write function, that will stack `return` as much times, as necessery. In code, I want <$> magicLift 2 :: IO Int <$> magicLift 2 :: Maybe [Int] both be valid.
My best approach is following (not work)
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-}
class Monad m => MonadS m where liftS :: a -> m a
instance (Monad m) => MonadS m where liftS = return
but <$> :t liftS 2 liftS 2 :: (Monad m, Num a) => m a
What would you suggest?
-- Best regards, Dmitry Bogatov
, Free Software supporter and netiquette guardian. git clone git://kaction.name/rc-files.git --depth 1 GPG: 54B7F00D Html mail and proprietary format attachments are forwarded to /dev/null. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe