[Haskell-cafe] Parameterisations of Monads
Matthew Sackman
matthew at wellquite.org
Tue Feb 5 09:48:14 EST 2008
So I was thinking how dull and uninspiring the current definiton of
Monad really is and came up with some more interesting
parameterisations. The only problem with this one is I'm a) not sure if
it still is a Monad and b) very unsure if it's of any use. There's the
possibility that chucking Cont in there or using newtype to simultate
multiple arrows / type lambdas may lead to more interesting instances,
but can anyone think of exciting use cases for this stuff?
Feel free to fill in the instances! It's also not a parameterisation
I've seen before.
Matthew
> class SuperMonad (m1 :: * -> * -> *) (m2 :: * -> *) where
> (>>~) :: m1 (m2 a) (m1 (m2 b) (m2 b))
> (>>=~) :: m1 (m2 a) (m1 (m1 a (m2 b)) (m2 b))
> returns :: m1 a (m2 a)
>
> instance (Monad m) => SuperMonad ((->)) m where
> (>>~) :: m a -> m b -> m b
> (>>~) = (>>)
> (>>=~) :: m a -> (a -> m b) -> m b
> (>>=~) = (>>=)
> returns :: a -> m a
> returns = return
>
> instance (Monad m) => SuperMonad ((,)) m where
> (>>~) :: (m a, (m b, m b))
> (>>=~) :: (m a, ((a, m b), m b))
> returns :: (a, m a)
>
> instance (Monad m) => SuperMonad Either m where
> (>>~) :: Either (m a) (Either (m a) (m b))
> (>>=~) :: Either (m a) (Either (Either a (m b)) (m b))
> returns :: Either a (m a)
>
> instance (Monad m) => SuperMonad State m where
> (>>~) :: State (m a) (State (m a) (m b))
> (>>=~) :: State (m a) (State (State a (m b)) (m b))
> returns :: State a (m a)
More information about the Haskell-Cafe
mailing list