Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- 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
- unbone :: Skeleton t a -> MonadView t (Skeleton t) a
- 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
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.
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
.
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.