Copyright | (c) Sirui Lu 2021-2023 |
---|---|
License | BSD-3-Clause (see the LICENSE file) |
Maintainer | siruilu@cs.washington.edu |
Stability | Experimental |
Portability | GHC only |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- mrgSuspend :: forall m s x. (Functor s, MonadUnion m, Mergeable x, Mergeable1 s) => s (Coroutine s m x) -> Coroutine s m x
- mrgMapMonad :: forall s m m' x. (Functor s, Mergeable1 s, Mergeable x, Monad m, MonadUnion m') => (forall y. m y -> m' y) -> Coroutine s m x -> Coroutine s m' x
- mrgMapSuspension :: forall s m x s'. (Functor s, MonadUnion m, Mergeable x, Mergeable1 s') => (forall y. s y -> s' y) -> Coroutine s m x -> Coroutine s' m x
- mrgMapFirstSuspension :: forall s m x. (Functor s, Mergeable1 s, MonadUnion m, Mergeable x) => (forall y. s y -> s y) -> Coroutine s m x -> Coroutine s m x
- mrgRunCoroutine :: (MonadUnion m, Mergeable x) => Coroutine Naught m x -> m x
- mrgBounce :: (Functor s, Mergeable1 s, MonadUnion m, Mergeable x) => (s (Coroutine s m x) -> Coroutine s m x) -> Coroutine s m x -> Coroutine s m x
- mrgPogoStick :: (MonadUnion m, Mergeable x) => (s (Coroutine s m x) -> Coroutine s m x) -> Coroutine s m x -> m x
- mrgPogoStickM :: (MonadUnion m, Mergeable x) => (s (Coroutine s m x) -> m (Coroutine s m x)) -> Coroutine s m x -> m x
- mrgFoldRun :: (MonadUnion m, Mergeable x, Mergeable a) => (a -> s (Coroutine s m x) -> (a, Coroutine s m x)) -> a -> Coroutine s m x -> m (a, x)
- type MrgPairBinder bool m = forall x y r. Mergeable r => (x -> y -> m r) -> m x -> m y -> m r
- mrgSequentialBinder :: MonadUnion m => MrgPairBinder bool m
Documentation
mrgSuspend :: forall m s x. (Functor s, MonadUnion m, Mergeable x, Mergeable1 s) => s (Coroutine s m x) -> Coroutine s m x Source #
Symbolic version of suspend
,
the result would be merged and propagate the mergeable knowledge.
mrgMapMonad :: forall s m m' x. (Functor s, Mergeable1 s, Mergeable x, Monad m, MonadUnion m') => (forall y. m y -> m' y) -> Coroutine s m x -> Coroutine s m' x Source #
Symbolic version of mapMonad
,
the result would be merged and propagate the mergeable knowledge.
mrgMapSuspension :: forall s m x s'. (Functor s, MonadUnion m, Mergeable x, Mergeable1 s') => (forall y. s y -> s' y) -> Coroutine s m x -> Coroutine s' m x Source #
Symbolic version of mapSuspension
,
the result would be merged and propagate the mergeable knowledge.
mrgMapFirstSuspension :: forall s m x. (Functor s, Mergeable1 s, MonadUnion m, Mergeable x) => (forall y. s y -> s y) -> Coroutine s m x -> Coroutine s m x Source #
Symbolic version of mapFirstSuspension
,
the result would be merged and propagate the mergeable knowledge.
mrgRunCoroutine :: (MonadUnion m, Mergeable x) => Coroutine Naught m x -> m x Source #
Symbolic version of mapFirstSuspension
,
the result would be merged and propagate the mergeable knowledge.
mrgBounce :: (Functor s, Mergeable1 s, MonadUnion m, Mergeable x) => (s (Coroutine s m x) -> Coroutine s m x) -> Coroutine s m x -> Coroutine s m x Source #
Symbolic version of bounce
,
the result would be merged and propagate the mergeable knowledge.
mrgPogoStick :: (MonadUnion m, Mergeable x) => (s (Coroutine s m x) -> Coroutine s m x) -> Coroutine s m x -> m x Source #
Symbolic version of pogoStick
,
the result would be merged and propagate the mergeable knowledge.
mrgPogoStickM :: (MonadUnion m, Mergeable x) => (s (Coroutine s m x) -> m (Coroutine s m x)) -> Coroutine s m x -> m x Source #
Symbolic version of pogoStickM
,
the result would be merged and propagate the mergeable knowledge.
mrgFoldRun :: (MonadUnion m, Mergeable x, Mergeable a) => (a -> s (Coroutine s m x) -> (a, Coroutine s m x)) -> a -> Coroutine s m x -> m (a, x) Source #
Symbolic version of foldRun
,
the result would be merged and propagate the mergeable knowledge.
type MrgPairBinder bool m = forall x y r. Mergeable r => (x -> y -> m r) -> m x -> m y -> m r Source #
Type of functions that can bind two monadic values together, used to combine two coroutines' step results. The result type needs to be mergeable.
mrgSequentialBinder :: MonadUnion m => MrgPairBinder bool m Source #
Symbolic version of sequentialBinder
,
the result would be merged and propagate the mergeable knowledge.