monad-skeleton-0.1.5: Monads of program skeleta

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Skeleton

Synopsis

Documentation

data MonadView t m x where Source #

A deconstructed action

Constructors

Return :: a -> MonadView t m a 
(:>>=) :: !(t a) -> (a -> m b) -> MonadView t m b infixl 1 

Instances

Functor m => Functor (MonadView t m) Source # 

Methods

fmap :: (a -> b) -> MonadView t m a -> MonadView t m b #

(<$) :: a -> MonadView t m b -> MonadView t m a #

hoistMV :: (forall x. s x -> t x) -> (m a -> n a) -> MonadView s m a -> MonadView t n a Source #

Transform the action and the continuation.

iterMV :: Monad m => (t a -> MonadView m t a) -> t a -> m a Source #

Join MonadView recursively.

data Skeleton t a where Source #

Skeleton t is a monadic skeleton (operational monad) made out of t. Skeletons can be fleshed out by getting transformed to other monads. It provides O(1) (>>=) and debone, the monadic reflection.

Constructors

ReturnS :: a -> Skeleton t a 
BindS :: t a -> Cat (Kleisli (Skeleton t)) a b -> Skeleton t b 

Instances

Monad (Skeleton t) Source # 

Methods

(>>=) :: Skeleton t a -> (a -> Skeleton t b) -> Skeleton t b #

(>>) :: Skeleton t a -> Skeleton t b -> Skeleton t b #

return :: a -> Skeleton t a #

fail :: String -> Skeleton t a #

Functor (Skeleton t) Source # 

Methods

fmap :: (a -> b) -> Skeleton t a -> Skeleton t b #

(<$) :: a -> Skeleton t b -> Skeleton t a #

Applicative (Skeleton t) Source # 

Methods

pure :: a -> Skeleton t a #

(<*>) :: Skeleton t (a -> b) -> Skeleton t a -> Skeleton t b #

(*>) :: Skeleton t a -> Skeleton t b -> Skeleton t b #

(<*) :: Skeleton t a -> Skeleton t b -> Skeleton t a #

bone :: t a -> Skeleton t a Source #

A skeleton that has only one bone.

debone :: Skeleton t a -> MonadView t (Skeleton t) a Source #

Pick a bone from a Skeleton.

deboneBy :: (MonadView t (Skeleton t) a -> r) -> Skeleton t a -> r Source #

Pick a bone from a Skeleton by a function. It's useful when used with LambdaCase.

Usecase:

 interpretM :: Monad m => Skeleton m a -> m a
 interpretM = deboneBy $ \case
   Return a -> return a
   x :>>= f -> x >>= interpretM . f

unbone :: Skeleton t a -> MonadView t (Skeleton t) a Source #

Deprecated: Use debone instead

Uncommon synonym for debone.

boned :: MonadView t (Skeleton t) a -> Skeleton t a Source #

Re-add a bone.

hoistSkeleton :: forall s t a. (forall x. s x -> t x) -> Skeleton s a -> Skeleton t a Source #

Lift a transformation between bones into transformation between skeletons.