[Haskell-cafe] Stacked return

Dmitry Bogatov KAction at gnu.org
Sun Nov 24 06:03:15 UTC 2013


Antonio <me at lelf.lu> writes:

> {-# 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
Great! Now I know what I do not know. Thanks!


--
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/20131124/b0c47aee/attachment.sig>


More information about the Haskell-Cafe mailing list