haskus-utils-0.6.0.0: Haskus utility modules

Safe HaskellNone
LanguageHaskell2010

Haskus.Utils.Flow

Contents

Description

First-class control-flow (based on Variant)

Synopsis

Documentation

type Flow m l = m (Variant l) Source #

Control-flow

type IOV l = Flow IO l Source #

class Monad m => MonadIO m where #

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Minimal complete definition

liftIO

Methods

liftIO :: IO a -> m a #

Lift a computation from the IO monad.

Instances

MonadIO IO 

Methods

liftIO :: IO a -> IO a #

MonadIO m => MonadIO (ListT m) 

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (ListT m) 

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (MaybeT m) 

Methods

liftIO :: IO a -> MaybeT m a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 

Methods

liftIO :: IO a -> ErrorT e m a #

MonadIO m => MonadIO (ExceptT e m) 

Methods

liftIO :: IO a -> ExceptT e m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (IdentityT * m) 

Methods

liftIO :: IO a -> IdentityT * m a #

MonadIO m => MonadIO (ReaderT * r m) 

Methods

liftIO :: IO a -> ReaderT * r m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

Methods

liftIO :: IO a -> RWST r w s m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

Methods

liftIO :: IO a -> RWST r w s m a #

class MonadIO m => MonadInIO m where Source #

Minimal complete definition

liftWith, liftWith2

Methods

liftWith :: (forall c. (a -> IO c) -> IO c) -> (a -> m b) -> m b Source #

Lift with*-like functions into IO (alloca, etc.)

liftWith2 :: (forall c. (a -> b -> IO c) -> IO c) -> (a -> b -> m e) -> m e Source #

Lift with*-like functions into IO (alloca, etc.)

Instances

MonadInIO IO Source # 

Methods

liftWith :: (forall c. (a -> IO c) -> IO c) -> (a -> IO b) -> IO b Source #

liftWith2 :: (forall c. (a -> b -> IO c) -> IO c) -> (a -> b -> IO e) -> IO e Source #

MonadInIO m => MonadInIO (StateT s m) Source # 

Methods

liftWith :: (forall c. (a -> IO c) -> IO c) -> (a -> StateT s m b) -> StateT s m b Source #

liftWith2 :: (forall c. (a -> b -> IO c) -> IO c) -> (a -> b -> StateT s m e) -> StateT s m e Source #

Flow utils

flowRes :: Functor m => Flow m '[x] -> m x Source #

Extract single flow result

flowSingle :: Monad m => x -> Flow m '[x] Source #

Return a single element

flowSetN :: forall n xs m. (Monad m, KnownNat n) => Index n xs -> Flow m xs Source #

Return in the first element

flowSet :: (Member x xs, Monad m) => x -> Flow m xs Source #

Return in the first well-typed element

flowLift :: (Liftable xs ys, Monad m) => Flow m xs -> Flow m ys Source #

Lift a flow into another

flowToCont :: (ContVariant xs, Monad m) => Flow m xs -> ContFlow xs (m r) Source #

Lift a flow into a ContFlow

flowTraverse :: forall m a b xs. Monad m => (a -> Flow m (b ': xs)) -> [a] -> Flow m ([b] ': xs) Source #

Traverse a list and stop on first error

flowFor :: forall m a b xs. Monad m => [a] -> (a -> Flow m (b ': xs)) -> Flow m ([b] ': xs) Source #

Traverse a list and stop on first error

flowTraverseFilter :: forall m a b xs. Monad m => (a -> Flow m (b ': xs)) -> [a] -> m [b] Source #

Traverse a list and return only valid values

flowForFilter :: forall m a b xs. Monad m => [a] -> (a -> Flow m (b ': xs)) -> m [b] Source #

Traverse a list and return only valid values

type Liftable xs ys = (IsSubset xs ys ~ True, VariantLift xs ys) Source #

xs is liftable in ys

type Catchable a xs = (IsMember a xs ~ True, VariantRemoveType a xs) Source #

a is catchable in xs

type MaybeCatchable a xs = VariantRemoveType a xs Source #

a may be catchable in xs

Non-variant single operations

(|>) :: a -> (a -> b) -> b infixl 0 Source #

Apply a function

(<|) :: (a -> b) -> a -> b infixr 0 Source #

Apply a function

(||>) :: Functor f => f a -> (a -> b) -> f b infixl 0 Source #

Apply a function in a Functor

(<||) :: Functor f => (a -> b) -> f a -> f b infixr 0 Source #

Apply a function in a Functor

Monadic/applicative operators

when :: Applicative f => Bool -> f () -> f () #

Conditional execution of Applicative expressions. For example,

when debug (putStrLn "Debugging")

will output the string Debugging if the Boolean value debug is True, and otherwise do nothing.

unless :: Applicative f => Bool -> f () -> f () #

The reverse of when.

guard :: Alternative f => Bool -> f () #

guard b is pure () if b is True, and empty if b is False.

void :: Functor f => f a -> f () #

void value discards or ignores the result of evaluation, such as the return value of an IO action.

Examples

Replace the contents of a Maybe Int with unit:

>>> void Nothing
Nothing
>>> void (Just 3)
Just ()

Replace the contents of an Either Int Int with unit, resulting in an Either Int '()':

>>> void (Left 8675309)
Left 8675309
>>> void (Right 8675309)
Right ()

Replace every element of a list with unit:

>>> void [1,2,3]
[(),(),()]

Replace the second element of a pair with unit:

>>> void (1,2)
(1,())

Discard the result of an IO action:

>>> mapM print [1,2]
1
2
[(),()]
>>> void $ mapM print [1,2]
1
2

forever :: Applicative f => f a -> f b #

forever act repeats the action infinitely.

foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b #

The foldM function is analogous to foldl, except that its result is encapsulated in a monad. Note that foldM works from left-to-right over the list arguments. This could be an issue where (>>) and the `folded function' are not commutative.

      foldM f a1 [x1, x2, ..., xm]

==

      do
        a2 <- f a1 x1
        a3 <- f a2 x2
        ...
        f am xm

If right-to-left evaluation is required, the input list should be reversed.

Note: foldM is the same as foldlM

foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m () #

Like foldM, but discards the result.

forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) #

forM is mapM with its arguments flipped. For a version that ignores the results see forM_.

forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m () #

forM_ is mapM_ with its arguments flipped. For a version that doesn't ignore the results see forM.

As of base 4.8.0.0, forM_ is just for_, specialized to Monad.

mapM :: Traversable t => forall m a b. Monad m => (a -> m b) -> t a -> m (t b) #

Map each element of a structure to a monadic action, evaluate these actions from left to right, and collect the results. For a version that ignores the results see mapM_.

mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () #

Map each element of a structure to a monadic action, evaluate these actions from left to right, and ignore the results. For a version that doesn't ignore the results see mapM.

As of base 4.8.0.0, mapM_ is just traverse_, specialized to Monad.

sequence :: Traversable t => forall m a. Monad m => t (m a) -> m (t a) #

Evaluate each monadic action in the structure from left to right, and collect the results. For a version that ignores the results see sequence_.

replicateM :: Applicative m => Int -> m a -> m [a] #

replicateM n act performs the action n times, gathering the results.

replicateM_ :: Applicative m => Int -> m a -> m () #

Like replicateM, but discards the result.

filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a] #

This generalizes the list-based filter function.

join :: Monad m => m (m a) -> m a #

The join function is the conventional monad join operator. It is used to remove one level of monadic structure, projecting its bound argument into the outer level.

(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c infixr 1 #

Right-to-left Kleisli composition of monads. (>=>), with the arguments flipped.

Note how this operator resembles function composition (.):

(.)   ::            (b ->   c) -> (a ->   b) -> a ->   c
(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c

(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #

Left-to-right Kleisli composition of monads.

Named operators

flowMap :: Monad m => Flow m (x ': xs) -> (x -> y) -> Flow m (y ': xs) Source #

Map a pure function onto the correct value in the flow

flowBind :: forall xs ys zs m x. (Liftable xs zs, Liftable ys zs, zs ~ Union xs ys, Monad m) => Flow m (x ': ys) -> (x -> Flow m xs) -> Flow m zs Source #

Bind two flows in a monadish way (error types union)

flowBind' :: Monad m => Flow m (x ': xs) -> (x -> Flow m (y ': xs)) -> Flow m (y ': xs) Source #

Bind two flows in a monadic way (constant error types)

flowMatch :: forall x xs zs m. (Monad m, Catchable x xs, Liftable (Filter x xs) zs) => Flow m xs -> (x -> Flow m zs) -> Flow m zs Source #

Match a value in a flow

flowMatchFail :: forall x xs m. (Monad m, Catchable x xs) => Flow m xs -> (x -> m ()) -> Flow m (Filter x xs) Source #

Match a value in a flow and use a non-returning failure in this case

First element operations

(.~.>) :: forall m l x a. Monad m => Variant (a ': l) -> (a -> m x) -> Flow m (x ': l) infixl 0 Source #

Extract the first value, set the first value

(>.~.>) :: forall m l x a. Monad m => Flow m (a ': l) -> (a -> m x) -> Flow m (x ': l) infixl 0 Source #

Extract the first value, set the first value

(.~+>) :: forall k m l l2 a. (KnownNat k, k ~ Length l2, Monad m) => Variant (a ': l) -> (a -> Flow m l2) -> Flow m (Concat l2 l) infixl 0 Source #

Extract the first value, concat the result

(>.~+>) :: forall k m l l2 a. (KnownNat k, k ~ Length l2, Monad m) => Flow m (a ': l) -> (a -> Flow m l2) -> Flow m (Concat l2 l) infixl 0 Source #

Extract the first value, concat the results

(.~^^>) :: forall m a xs ys zs. (Monad m, Liftable xs zs, Liftable ys zs) => Variant (a ': ys) -> (a -> Flow m xs) -> Flow m zs infixl 0 Source #

Extract the first value, lift both

(>.~^^>) :: forall m a xs ys zs. (Monad m, Liftable xs zs, Liftable ys zs) => Flow m (a ': ys) -> (a -> Flow m xs) -> Flow m zs infixl 0 Source #

Extract the first value, lift both

(.~^>) :: forall m a ys zs. (Monad m, Liftable ys zs) => Variant (a ': ys) -> (a -> Flow m zs) -> Flow m zs infixl 0 Source #

Extract the first value, lift unselected

(>.~^>) :: forall m a ys zs. (Monad m, Liftable ys zs) => Flow m (a ': ys) -> (a -> Flow m zs) -> Flow m zs infixl 0 Source #

Extract the first value, lift unselected

(.~$>) :: forall m x xs a. Monad m => Variant (a ': xs) -> (a -> Flow m (x ': xs)) -> Flow m (x ': xs) infixl 0 Source #

Extract the first value, use the same tail

(>.~$>) :: forall m x xs a. Monad m => Flow m (a ': xs) -> (a -> Flow m (x ': xs)) -> Flow m (x ': xs) infixl 0 Source #

Extract the first value, use the same tail

(.~|>) :: (Liftable xs zs, Liftable ys zs, zs ~ Union xs ys, Monad m) => Variant (a ': ys) -> (a -> Flow m xs) -> Flow m zs infixl 0 Source #

Take the first output, union the result

(>.~|>) :: (Liftable xs zs, Liftable ys zs, zs ~ Union xs ys, Monad m) => Flow m (a ': ys) -> (a -> Flow m xs) -> Flow m zs infixl 0 Source #

Take the first output, fusion the result

(.~=>) :: Monad m => Variant (a ': l) -> (a -> m ()) -> Flow m (a ': l) infixl 0 Source #

Extract the first value and perform effect. Passthrough the input value

(>.~=>) :: Monad m => Flow m (a ': l) -> (a -> m ()) -> Flow m (a ': l) infixl 0 Source #

Extract the first value and perform effect. Passthrough the input value

(.~!>) :: Monad m => Variant (a ': l) -> (a -> m ()) -> m () infixl 0 Source #

Extract the first value and perform effect.

(>.~!>) :: Monad m => Flow m (a ': l) -> (a -> m ()) -> m () infixl 0 Source #

Extract the first value and perform effect.

(.~!!>) :: Monad m => Variant (a ': l) -> (a -> m ()) -> m (Variant l) infixl 0 Source #

Extract the first value and perform effect.

(>.~!!>) :: Monad m => Flow m (a ': l) -> (a -> m ()) -> m (Variant l) infixl 0 Source #

Extract the first value and perform effect.

First element, pure variant

(.-.>) :: forall m l x a. Monad m => Variant (a ': l) -> (a -> x) -> Flow m (x ': l) infixl 0 Source #

Extract the first value, set the first value

(>.-.>) :: forall m l x a. Monad m => Flow m (a ': l) -> (a -> x) -> Flow m (x ': l) infixl 0 Source #

Extract the first value, set the first value

(<.-.) :: forall m l x a. Monad m => (a -> x) -> Variant (a ': l) -> Flow m (x ': l) infixr 0 Source #

Extract the first value, set the first value

(<.-.<) :: forall m l x a. Monad m => (a -> x) -> Flow m (a ': l) -> Flow m (x ': l) infixr 0 Source #

Extract the first value, set the first value

Functor, applicative equivalents

(<$<) :: forall m l a b. Monad m => (a -> b) -> Flow m (a ': l) -> Flow m (b ': l) infixl 4 Source #

Functor $ equivalent

(<*<) :: forall m l a b. Monad m => Flow m ((a -> b) ': l) -> Flow m (a ': l) -> Flow m (b ': l) infixl 4 Source #

Applicative * equivalent

(<|<) :: forall m xs ys zs y z. (Monad m, Liftable xs zs, Liftable ys zs, zs ~ Union xs ys) => Flow m ((y -> z) ': xs) -> Flow m (y ': ys) -> Flow m (z ': zs) infixl 4 Source #

Applicative * equivalent, with error union

First element, const variant

(.~~.>) :: forall m l x a. Monad m => Variant (a ': l) -> m x -> Flow m (x ': l) infixl 0 Source #

Extract the first value, set the first value

(>.~~.>) :: forall m l x a. Monad m => Flow m (a ': l) -> m x -> Flow m (x ': l) infixl 0 Source #

Extract the first value, set the first value

(.~~+>) :: forall k m l l2 a. (KnownNat k, k ~ Length l2, Monad m) => Variant (a ': l) -> Flow m l2 -> Flow m (Concat l2 l) infixl 0 Source #

Extract the first value, concat the result

(>.~~+>) :: forall k m l l2 a. (KnownNat k, k ~ Length l2, Monad m) => Flow m (a ': l) -> Flow m l2 -> Flow m (Concat l2 l) infixl 0 Source #

Extract the first value, concat the results

(.~~^^>) :: forall m a xs ys zs. (Monad m, Liftable xs zs, Liftable ys zs) => Variant (a ': ys) -> Flow m xs -> Flow m zs infixl 0 Source #

Extract the first value, lift the result

(>.~~^^>) :: forall m a xs ys zs. (Monad m, Liftable xs zs, Liftable ys zs) => Flow m (a ': ys) -> Flow m xs -> Flow m zs infixl 0 Source #

Extract the first value, lift the result

(.~~^>) :: forall m a ys zs. (Monad m, Liftable ys zs) => Variant (a ': ys) -> Flow m zs -> Flow m zs infixl 0 Source #

Extract the first value, connect to the expected output

(>.~~^>) :: forall m a ys zs. (Monad m, Liftable ys zs) => Flow m (a ': ys) -> Flow m zs -> Flow m zs infixl 0 Source #

Extract the first value, connect to the expected output

(.~~$>) :: forall m x xs a. Monad m => Variant (a ': xs) -> Flow m (x ': xs) -> Flow m (x ': xs) infixl 0 Source #

Extract the first value, use the same output type

(>.~~$>) :: forall m x xs a. Monad m => Flow m (a ': xs) -> Flow m (x ': xs) -> Flow m (x ': xs) infixl 0 Source #

Extract the first value, use the same output type

(.~~|>) :: (Liftable xs zs, Liftable ys zs, zs ~ Union xs ys, Monad m) => Variant (a ': ys) -> Flow m xs -> Flow m zs infixl 0 Source #

Take the first output, fusion the result

(>.~~|>) :: (Liftable xs zs, Liftable ys zs, zs ~ Union xs ys, Monad m) => Flow m (a ': ys) -> Flow m xs -> Flow m zs infixl 0 Source #

Take the first output, fusion the result

(.~~=>) :: Monad m => Variant (a ': l) -> m () -> Flow m (a ': l) infixl 0 Source #

Extract the first value and perform effect. Passthrough the input value

(>.~~=>) :: Monad m => Flow m (a ': l) -> m () -> Flow m (a ': l) infixl 0 Source #

Extract the first value and perform effect. Passthrough the input value

(.~~!>) :: Monad m => Variant (a ': l) -> m () -> m () infixl 0 Source #

Extract the first value and perform effect.

(>.~~!>) :: Monad m => Flow m (a ': l) -> m () -> m () infixl 0 Source #

Extract the first value and perform effect.

Tail operations

(..~.>) :: Monad m => Variant (a ': l) -> (Variant l -> m a) -> m a infixl 0 Source #

Extract the tail, set the first value

(>..~.>) :: Monad m => Flow m (a ': l) -> (Variant l -> m a) -> m a infixl 0 Source #

Extract the tail, set the first value

(..-.>) :: Monad m => Variant (a ': l) -> (Variant l -> a) -> m a infixl 0 Source #

Extract the tail, set the first value (pure function)

(>..-.>) :: Monad m => Flow m (a ': l) -> (Variant l -> a) -> m a infixl 0 Source #

Extract the tail, set the first value (pure function)

(..-..>) :: forall a l xs m. Monad m => Variant (a ': l) -> (Variant l -> Variant xs) -> Flow m (a ': xs) infixl 0 Source #

Extract the tail, set the tail

(>..-..>) :: Monad m => Flow m (a ': l) -> (Variant l -> Variant xs) -> Flow m (a ': xs) infixl 0 Source #

Extract the tail, set the tail

(..~..>) :: forall a l xs m. Monad m => Variant (a ': l) -> (Variant l -> Flow m xs) -> Flow m (a ': xs) infixl 0 Source #

Extract the tail, set the tail

(>..~..>) :: Monad m => Flow m (a ': l) -> (Variant l -> Flow m xs) -> Flow m (a ': xs) infixl 0 Source #

Extract the tail, set the tail

(..~^^>) :: (Monad m, Liftable xs (a ': zs)) => Variant (a ': l) -> (Variant l -> Flow m xs) -> Flow m (a ': zs) infixl 0 Source #

Extract the tail, lift the result

(>..~^^>) :: (Monad m, Liftable xs (a ': zs)) => Flow m (a ': l) -> (Variant l -> Flow m xs) -> Flow m (a ': zs) infixl 0 Source #

Extract the tail, lift the result

(..~^>) :: (Monad m, Member a zs) => Variant (a ': l) -> (Variant l -> Flow m zs) -> Flow m zs infixl 0 Source #

Extract the tail, connect the result

(>..~^>) :: (Monad m, Member a zs) => Flow m (a ': l) -> (Variant l -> Flow m zs) -> Flow m zs infixl 0 Source #

Extract the tail, connect the result

(..~=>) :: Monad m => Variant (x ': xs) -> (Variant xs -> m ()) -> Flow m (x ': xs) infixl 0 Source #

Extract the tail and perform an effect. Passthrough the input value

(>..~=>) :: Monad m => Flow m (x ': xs) -> (Variant xs -> m ()) -> Flow m (x ': xs) infixl 0 Source #

Extract the tail and perform an effect. Passthrough the input value

(..~!>) :: Monad m => Variant (x ': xs) -> (Variant xs -> m ()) -> m () infixl 0 Source #

Extract the tail and perform an effect

(>..~!>) :: Monad m => Flow m (x ': xs) -> (Variant xs -> m ()) -> m () infixl 0 Source #

Extract the tail and perform an effect

(..~!!>) :: Monad m => Variant (x ': xs) -> (Variant xs -> m ()) -> m x infixl 0 Source #

Extract the tail and perform an effect

(>..~!!>) :: Monad m => Flow m (x ': xs) -> (Variant xs -> m ()) -> m x infixl 0 Source #

Extract the tail and perform an effect

Tail catch operations

(..%~^>) :: (Monad m, Catchable a xs, Liftable (Filter a xs) ys) => Variant (x ': xs) -> (a -> Flow m ys) -> Flow m (x ': ys) infixl 0 Source #

Match in the tail, connect to the expected result

(>..%~^>) :: (Monad m, Catchable a xs, Liftable (Filter a xs) ys) => Flow m (x ': xs) -> (a -> Flow m ys) -> Flow m (x ': ys) infixl 0 Source #

Match in the tail, connect to the expected result

(..%~^^>) :: (Monad m, Catchable a xs, Liftable (Filter a xs) zs, Liftable ys zs) => Variant (x ': xs) -> (a -> Flow m ys) -> Flow m (x ': zs) infixl 0 Source #

Match in the tail, lift to the expected result

(>..%~^^>) :: (Monad m, Catchable a xs, Liftable (Filter a xs) zs, Liftable ys zs) => Flow m (x ': xs) -> (a -> Flow m ys) -> Flow m (x ': zs) infixl 0 Source #

Match in the tail, lift to the expected result

(..%~$>) :: (Monad m, Catchable a xs, Liftable (Filter a xs) (x ': xs)) => Variant (x ': xs) -> (a -> Flow m (x ': xs)) -> Flow m (x ': xs) infixl 0 Source #

Match in the tail, keep the same types

(>..%~$>) :: (Monad m, Catchable a xs, Liftable (Filter a xs) (x ': xs)) => Flow m (x ': xs) -> (a -> Flow m (x ': xs)) -> Flow m (x ': xs) infixl 0 Source #

Match in the tail, keep the same types

(..%~!!>) :: (Monad m, Catchable y xs) => Variant (x ': xs) -> (y -> m ()) -> Flow m (x ': Filter y xs) infixl 0 Source #

Match in the tail and perform an effect

(>..%~!!>) :: (Monad m, Catchable y xs) => Flow m (x ': xs) -> (y -> m ()) -> Flow m (x ': Filter y xs) infixl 0 Source #

Match in the tail and perform an effect

(..%~!>) :: (Monad m, Catchable y xs) => Variant (x ': xs) -> (y -> m ()) -> m () infixl 0 Source #

Match in the tail and perform an effect

(>..%~!>) :: (Monad m, Catchable y xs) => Flow m (x ': xs) -> (y -> m ()) -> m () infixl 0 Source #

Match in the tail and perform an effect

(..?~^>) :: (Monad m, MaybeCatchable a xs, Liftable (Filter a xs) ys) => Variant (x ': xs) -> (a -> Flow m ys) -> Flow m (x ': ys) infixl 0 Source #

Match in the tail, connect to the expected result

(>..?~^>) :: (Monad m, MaybeCatchable a xs, Liftable (Filter a xs) ys) => Flow m (x ': xs) -> (a -> Flow m ys) -> Flow m (x ': ys) infixl 0 Source #

Match in the tail, connect to the expected result

(..?~^^>) :: (Monad m, MaybeCatchable a xs, Liftable (Filter a xs) zs, Liftable ys zs) => Variant (x ': xs) -> (a -> Flow m ys) -> Flow m (x ': zs) infixl 0 Source #

Match in the tail, lift to the expected result

(>..?~^^>) :: (Monad m, MaybeCatchable a xs, Liftable (Filter a xs) zs, Liftable ys zs) => Flow m (x ': xs) -> (a -> Flow m ys) -> Flow m (x ': zs) infixl 0 Source #

Match in the tail, lift to the expected result

(..?~$>) :: (Monad m, MaybeCatchable a xs, Liftable (Filter a xs) (x ': xs)) => Variant (x ': xs) -> (a -> Flow m (x ': xs)) -> Flow m (x ': xs) infixl 0 Source #

Match in the tail, keep the same types

(>..?~$>) :: (Monad m, MaybeCatchable a xs, Liftable (Filter a xs) (x ': xs)) => Flow m (x ': xs) -> (a -> Flow m (x ': xs)) -> Flow m (x ': xs) infixl 0 Source #

Match in the tail, keep the same types

(..?~!!>) :: (Monad m, MaybeCatchable y xs) => Variant (x ': xs) -> (y -> m ()) -> Flow m (x ': Filter y xs) infixl 0 Source #

Match in the tail and perform an effect

(>..?~!!>) :: (Monad m, MaybeCatchable y xs) => Flow m (x ': xs) -> (y -> m ()) -> Flow m (x ': Filter y xs) infixl 0 Source #

Match in the tail and perform an effect

(..?~!>) :: (Monad m, MaybeCatchable y xs) => Variant (x ': xs) -> (y -> m ()) -> m () infixl 0 Source #

Match in the tail and perform an effect

(>..?~!>) :: (Monad m, MaybeCatchable y xs) => Flow m (x ': xs) -> (y -> m ()) -> m () infixl 0 Source #

Match in the tail and perform an effect

Caught element operations

(%~.>) :: forall x xs y ys m. (ys ~ Filter x xs, Monad m, Catchable x xs) => Variant xs -> (x -> m y) -> Flow m (y ': ys) infixl 0 Source #

Catch element, set the first value

(>%~.>) :: (ys ~ Filter x xs, Monad m, Catchable x xs) => Flow m xs -> (x -> m y) -> Flow m (y ': ys) infixl 0 Source #

Catch element, set the first value

(%~+>) :: forall x xs ys m. (Monad m, Catchable x xs, KnownNat (Length ys)) => Variant xs -> (x -> Flow m ys) -> Flow m (Concat ys (Filter x xs)) infixl 0 Source #

Catch element, concat the result

(>%~+>) :: forall x xs ys m. (Monad m, Catchable x xs, KnownNat (Length ys)) => Flow m xs -> (x -> Flow m ys) -> Flow m (Concat ys (Filter x xs)) infixl 0 Source #

Catch element, concat the result

(%~^^>) :: forall x xs ys zs m. (Monad m, Catchable x xs, Liftable (Filter x xs) zs, Liftable ys zs) => Variant xs -> (x -> Flow m ys) -> Flow m zs infixl 0 Source #

Catch element, lift the result

(>%~^^>) :: forall x xs ys zs m. (Monad m, Catchable x xs, Liftable (Filter x xs) zs, Liftable ys zs) => Flow m xs -> (x -> Flow m ys) -> Flow m zs infixl 0 Source #

Catch element, lift the result

(%~^>) :: forall x xs zs m. (Monad m, Catchable x xs, Liftable (Filter x xs) zs) => Variant xs -> (x -> Flow m zs) -> Flow m zs infixl 0 Source #

Catch element, connect to the expected output

(>%~^>) :: forall x xs zs m. (Monad m, Catchable x xs, Liftable (Filter x xs) zs) => Flow m xs -> (x -> Flow m zs) -> Flow m zs infixl 0 Source #

Catch element, connect to the expected output

(%~$>) :: forall x xs m. (Monad m, Catchable x xs) => Variant xs -> (x -> Flow m xs) -> Flow m xs infixl 0 Source #

Catch element, use the same output type

(>%~$>) :: forall x xs m. (Monad m, Catchable x xs) => Flow m xs -> (x -> Flow m xs) -> Flow m xs infixl 0 Source #

Catch element, use the same output type

(%~|>) :: forall x xs ys zs m. (Monad m, Catchable x xs, Liftable (Filter x xs) zs, Liftable ys zs, zs ~ Union (Filter x xs) ys) => Variant xs -> (x -> Flow m ys) -> Flow m zs infixl 0 Source #

Catch element, fusion the result

(>%~|>) :: forall x xs ys zs m. (Monad m, Catchable x xs, Liftable (Filter x xs) zs, Liftable ys zs, zs ~ Union (Filter x xs) ys) => Flow m xs -> (x -> Flow m ys) -> Flow m zs infixl 0 Source #

Catch element, fusion the result

(%~=>) :: forall x xs m. (Monad m, Catchable x xs) => Variant xs -> (x -> m ()) -> Flow m xs infixl 0 Source #

Catch element and perform effect. Passthrough the input value.

(>%~=>) :: forall x xs m. (Monad m, Catchable x xs) => Flow m xs -> (x -> m ()) -> Flow m xs infixl 0 Source #

Catch element and perform effect. Passthrough the input value.

(%~!>) :: forall x xs m. (Monad m, Catchable x xs) => Variant xs -> (x -> m ()) -> m () infixl 0 Source #

Catch element and perform effect.

(>%~!>) :: forall x xs m. (Monad m, Catchable x xs) => Flow m xs -> (x -> m ()) -> m () infixl 0 Source #

Catch element and perform effect.

(%~!!>) :: forall x xs m. (Monad m, Catchable x xs) => Variant xs -> (x -> m ()) -> Flow m (Filter x xs) infixl 0 Source #

Catch element and perform effect.

(>%~!!>) :: forall x xs m. (Monad m, Catchable x xs) => Flow m xs -> (x -> m ()) -> Flow m (Filter x xs) infixl 0 Source #

Catch element and perform effect.

(?~.>) :: forall x xs y ys m. (ys ~ Filter x xs, Monad m, MaybeCatchable x xs) => Variant xs -> (x -> m y) -> Flow m (y ': ys) infixl 0 Source #

Catch element, set the first value

(>?~.>) :: (ys ~ Filter x xs, Monad m, MaybeCatchable x xs) => Flow m xs -> (x -> m y) -> Flow m (y ': ys) infixl 0 Source #

Catch element, set the first value

(?~+>) :: forall x xs ys m. (Monad m, MaybeCatchable x xs, KnownNat (Length ys)) => Variant xs -> (x -> Flow m ys) -> Flow m (Concat ys (Filter x xs)) infixl 0 Source #

Catch element, concat the result

(>?~+>) :: forall x xs ys m. (Monad m, MaybeCatchable x xs, KnownNat (Length ys)) => Flow m xs -> (x -> Flow m ys) -> Flow m (Concat ys (Filter x xs)) infixl 0 Source #

Catch element, concat the result

(?~^^>) :: forall x xs ys zs m. (Monad m, MaybeCatchable x xs, Liftable (Filter x xs) zs, Liftable ys zs) => Variant xs -> (x -> Flow m ys) -> Flow m zs infixl 0 Source #

Catch element, lift the result

(>?~^^>) :: forall x xs ys zs m. (Monad m, MaybeCatchable x xs, Liftable (Filter x xs) zs, Liftable ys zs) => Flow m xs -> (x -> Flow m ys) -> Flow m zs infixl 0 Source #

Catch element, lift the result

(?~^>) :: forall x xs zs m. (Monad m, MaybeCatchable x xs, Liftable (Filter x xs) zs) => Variant xs -> (x -> Flow m zs) -> Flow m zs infixl 0 Source #

Catch element, connect to the expected output

(>?~^>) :: forall x xs zs m. (Monad m, MaybeCatchable x xs, Liftable (Filter x xs) zs) => Flow m xs -> (x -> Flow m zs) -> Flow m zs infixl 0 Source #

Catch element, connect to the expected output

(?~$>) :: forall x xs m. (Monad m, MaybeCatchable x xs) => Variant xs -> (x -> Flow m xs) -> Flow m xs infixl 0 Source #

Catch element, use the same output type

(>?~$>) :: forall x xs m. (Monad m, MaybeCatchable x xs) => Flow m xs -> (x -> Flow m xs) -> Flow m xs infixl 0 Source #

Catch element, use the same output type

(?~|>) :: forall x xs ys zs m. (Monad m, MaybeCatchable x xs, Liftable (Filter x xs) zs, Liftable ys zs, zs ~ Union (Filter x xs) ys) => Variant xs -> (x -> Flow m ys) -> Flow m zs infixl 0 Source #

Catch element, fusion the result

(>?~|>) :: forall x xs ys zs m. (Monad m, MaybeCatchable x xs, Liftable (Filter x xs) zs, Liftable ys zs, zs ~ Union (Filter x xs) ys) => Flow m xs -> (x -> Flow m ys) -> Flow m zs infixl 0 Source #

Catch element, fusion the result

(?~=>) :: forall x xs m. (Monad m, MaybeCatchable x xs) => Variant xs -> (x -> m ()) -> Flow m xs infixl 0 Source #

Catch element and perform effect. Passthrough the input value.

(>?~=>) :: forall x xs m. (Monad m, MaybeCatchable x xs) => Flow m xs -> (x -> m ()) -> Flow m xs infixl 0 Source #

Catch element and perform effect. Passthrough the input value.

(?~!>) :: forall x xs m. (Monad m, MaybeCatchable x xs) => Variant xs -> (x -> m ()) -> m () infixl 0 Source #

Catch element and perform effect.

(>?~!>) :: forall x xs m. (Monad m, MaybeCatchable x xs) => Flow m xs -> (x -> m ()) -> m () infixl 0 Source #

Catch element and perform effect.

(?~!!>) :: forall x xs m. (Monad m, MaybeCatchable x xs) => Variant xs -> (x -> m ()) -> Flow m (Filter x xs) infixl 0 Source #

Catch element and perform effect.

(>?~!!>) :: forall x xs m. (Monad m, MaybeCatchable x xs) => Flow m xs -> (x -> m ()) -> Flow m (Filter x xs) infixl 0 Source #

Catch element and perform effect.

Helpers

makeFlowOp :: Monad m => (Variant as -> Either (Variant bs) (Variant cs)) -> (Variant cs -> Flow m ds) -> (Either (Variant bs) (Variant ds) -> es) -> Variant as -> m es Source #

Make a flow operator

makeFlowOpM :: Monad m => (Variant as -> Either (Variant bs) (Variant cs)) -> (Variant cs -> Flow m ds) -> (Either (Variant bs) (Variant ds) -> es) -> Flow m as -> m es Source #

Make a flow operator

selectTail :: Variant (x ': xs) -> Either (Variant '[x]) (Variant xs) Source #

Select the tail

selectFirst :: Variant (x ': xs) -> Either (Variant xs) (Variant '[x]) Source #

Select the first value

selectType :: Catchable x xs => Variant xs -> Either (Variant (Filter x xs)) (Variant '[x]) Source #

Select by type

applyConst :: Flow m ys -> Variant xs -> Flow m ys Source #

Const application

applyPure :: Monad m => (Variant xs -> Variant ys) -> Variant xs -> Flow m ys Source #

Pure application

applyM :: Monad m => (a -> m b) -> Variant '[a] -> Flow m '[b] Source #

Lift a monadic function

applyF :: (a -> Flow m b) -> Variant '[a] -> Flow m b Source #

Lift a monadic function

combineFirst :: forall x xs. Either (Variant xs) (Variant '[x]) -> Variant (x ': xs) Source #

Set the first value (the "correct" one)

combineSameTail :: forall x xs. Either (Variant xs) (Variant (x ': xs)) -> Variant (x ': xs) Source #

Set the first value, keep the same tail type

combineEither :: Either (Variant xs) (Variant xs) -> Variant xs Source #

Return the valid variant unmodified

combineConcat :: forall xs ys. KnownNat (Length xs) => Either (Variant ys) (Variant xs) -> Variant (Concat xs ys) Source #

Concatenate unselected values

combineUnion :: (Liftable xs (Union xs ys), Liftable ys (Union xs ys)) => Either (Variant ys) (Variant xs) -> Variant (Union xs ys) Source #

Union

combineLiftUnselected :: Liftable ys xs => Either (Variant ys) (Variant xs) -> Variant xs Source #

Lift unselected

combineLiftBoth :: (Liftable ys zs, Liftable xs zs) => Either (Variant ys) (Variant xs) -> Variant zs Source #

Lift both

combineSingle :: Either (Variant '[x]) (Variant '[x]) -> x Source #

Single value

liftV :: (a -> b) -> Variant '[a] -> Variant '[b] Source #

Lift a pure function into a Variant to Variant function

liftF :: Monad m => (a -> m b) -> Variant '[a] -> Flow m '[b] Source #

Lift a function into a Flow