Recently (I think) I found the following Monad
. Is this known somewhere? Is there any usage of it for programming? (Or I’m totally wrong, and it’s not a lawful Monad
at all?)
-- | It /looks/ like it is the product monad of 'Control.Monad.Trans.Select.Select' and
-- 'Control.Monad.Trans.Cont.Cont' ...
-- but it isn't! The two components are not independent.
data SC s a = SC {
runSelect :: (a -> s) -> a,
runCont :: (a -> s) -> s
}
deriving Functor
instance Applicative (SC s) where
pure = pureSC
(<*>) = ap
instance Monad (SC s) where
ma >>= k = joinSC (fmap k ma)
pureSC :: a -> SC s a
pureSC x = SC { runSelect = const x, runCont = ($ x) }
joinSC :: SC s (SC s a) -> SC s a
joinSC mmx = SC { runSelect = selPart, runCont = contPart }
where
contPart = \f -> runCont mmx (\mx -> runCont mx f)
selPart = \f -> runSelect (runSelect mmx (\mx -> runCont mx f)) f
Compare it with Selection monad and Continuation monad:
-- | Continuation monad
newtype C s a = C { runC :: (a -> s) -> s }
deriving Functor
pureC :: a -> C s a
pureC x = C ($ x)
joinC :: C s (C s a) -> C s a
joinC mmx = C $ \f -> runC mmx (\mx -> runC mx f)
-- | Selection monad
newtype S s a = S { runS :: (a -> s) -> a }
deriving Functor
pureS :: a -> S s a
pureS x = S $ const x
joinS :: S s (S s a) -> S s a
joinS mmx = S $ \f -> runS (runS mmx (\mx -> f (runS mx f))) f
Note that the Cont
part of the new monad SC s
is exactly the continuation monad C s
, but the Select
part is not just a translation of S s
. joinSC
of the Select
part depends on the Cont
part.
The following links are the code (and how I’ve derived this Monad
)
- The implementation of SC monad
- Background of (R w) monad
- X posts I’ve made about it