[Haskell-cafe] Name for the following combinators?

Tom Ellis tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk
Sat Dec 28 16:13:52 UTC 2013


On Sat, Dec 28, 2013 at 03:58:10PM +0000, Tom Ellis wrote:
> On Sat, Dec 28, 2013 at 04:47:40PM +0100, Hans Höglund wrote:
> > Recently I have found myself using these two combinators a lot: http://lpaste.net/97643
> 
> FYI it looks a lot like these give rise to a monad transformer.

Specifically, the following.  Careful though: I haven't made any effort to
check this satisfies the monad or transformer laws.

If 'Wrap m n' genuinely satisfies the monad laws then you don't need new
combinators.  Just Wrap the type constructors and get a real monad.  (If
'Wrap m' is genuinely a monad transformer, so much the better!)

Tom



import Control.Monad.Trans (MonadTrans, lift)
import Control.Monad (join)
import qualified Data.Traversable as T
import Data.Traversable (Traversable)

data Wrap m n a = Wrap (m (n a))

unwrap :: Wrap m n a -> m (n a)
unwrap (Wrap m) = m

mbind :: (Monad m, Monad n, Functor m, Traversable n)
         => (a -> m (n b)) -> m (n a) -> m (n b)
mbind = (join .) . fmap . (fmap join .) . T.mapM

instance (Functor m, Traversable n, Monad m, Monad n) => Monad (Wrap m n)
where
  return = Wrap . return . return
  m >>= f = Wrap (mbind (unwrap . f) (unwrap m))
  
instance Monad m => MonadTrans (Wrap m) where
  lift = Wrap . return


More information about the Haskell-Cafe mailing list