[Haskell-cafe] Stacked return

Dmitry Bogatov KAction at gnu.org
Sat Nov 23 16:44:43 UTC 2013


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 <KAction at gnu.org>,
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.
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 835 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20131123/228eaa7f/attachment.sig>


More information about the Haskell-Cafe mailing list