| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Control.Concurrent.Free
- data F f a
- liftF :: f a -> F f a
- hoist :: (forall a. f a -> g a) -> F f a -> F g a
- retractA :: Applicative f => F f a -> Maybe (f a)
- retractM :: Monad f => F f a -> f a
- foldA :: Applicative g => (forall x. f x -> g x) -> F f a -> Maybe (g a)
- foldM :: Monad m => (forall x. f x -> m x) -> F f a -> m a
- foldConcurrentM :: Monad m => (forall x. f x -> m (m x)) -> F f a -> m a
- retractConcurrentIO :: F IO a -> IO a
- foldConcurrentIO :: (forall x. f x -> IO x) -> F f a -> IO a
Documentation
The combination of a free functor, a free applicative functor,
and free monad over f.
The semantics of the Functor, Applicative and Monad instances
are such that it tries to pick the lowest possible abstraction to
perform the operation.
This means that if a computation is constructed using fmap, pure
and <*>, it can be parallelised up until the point where the first
monadic join sits.
hoist :: (forall a. f a -> g a) -> F f a -> F g a Source
Given a natural transformation from f to g this gives a monoidal natural transformation from F f to F g.
retractA :: Applicative f => F f a -> Maybe (f a) Source
Partially interprets the free monad over f using the semantics for pure and <*> given by the Applicative instance for f. If it encounters a monadic join, the result is Nothing.
foldA :: Applicative g => (forall x. f x -> g x) -> F f a -> Maybe (g a) Source
Given a natural transformation from f to g, this gives a partial monoidal natural transformation from F f to g.
foldM :: Monad m => (forall x. f x -> m x) -> F f a -> m a Source
Given a natural transformation from f to m, this gives a canonical monoidal natural transformation from F f to m.
foldConcurrentM :: Monad m => (forall x. f x -> m (m x)) -> F f a -> m a Source
Interprets the free monad over f using the
transformation from f to m m.
The semantics of the concurrency are given by the transformation, which produces a result that is unwrapped in two stages: The first monadic layer should spawn the concurrent action, and reveal the second layer, which should block until the spawned action has returned with a result.