| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Control.Monad.Skeleton
Synopsis
- data MonadView t m x where
- hoistMV :: (forall x. s x -> t x) -> (m a -> n a) -> MonadView s m a -> MonadView t n a
- iterMV :: Monad m => (t a -> MonadView m t a) -> t a -> m a
- data Skeleton t a where
- bone :: t a -> Skeleton t a
- debone :: Skeleton t a -> MonadView t (Skeleton t) a
- deboneBy :: (MonadView t (Skeleton t) a -> r) -> Skeleton t a -> r
- boned :: MonadView t (Skeleton t) a -> Skeleton t a
- hoistSkeleton :: forall s t a. (forall x. s x -> t x) -> Skeleton s a -> Skeleton t a
Documentation
data MonadView t m x where Source #
A deconstructed action
hoistMV :: (forall x. s x -> t x) -> (m a -> n a) -> MonadView s m a -> MonadView t n a Source #
Transform the instruction as well as the continuation.
data Skeleton t a where Source #
Skeleton tt.
 Skeletons can be fleshed out by interpreting the instructions.
 It provides O(1) (>>=) and debone.
Constructors
| ReturnS :: a -> Skeleton t a | |
| BindS :: t a -> Cat (Kleisli (Skeleton t)) a b -> Skeleton t b | 
debone :: Skeleton t a -> MonadView t (Skeleton t) a Source #
Extract the first instruction in Skeleton.
deboneBy :: (MonadView t (Skeleton t) a -> r) -> Skeleton t a -> r Source #
Continuation-passing variant of debone
 which allows nicer expression using LambdaCase.
Usecase:
interpretM :: Monad m => Skeleton m a -> m a interpretM = deboneBy $ \case Return a -> return a x :>>= f -> x >>= interpretM . f
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.