box-0.8.1: boxes
Safe HaskellSafe-Inferred
LanguageHaskell2010

Box.Box

Description

A box is something that commits and emits

Synopsis

Documentation

data Box m c e Source #

A Box is a product of a Committer and an Emitter.

Think of a box with an incoming arrow an outgoing arrow. And then make your pov ambiguous: are you looking at two wires from "inside a box"; or are you looking from "outside the box"; interacting with a black box object. Either way, it looks the same: it's a box.

And either way, one of the arrows, the Committer, is contravariant and the other, the Emitter is covariant. The combination is a profunctor.

Constructors

Box 

Fields

Instances

Instances details
Functor m => Profunctor (Box m) Source # 
Instance details

Defined in Box.Box

Methods

dimap :: (a -> b) -> (c -> d) -> Box m b c -> Box m a d #

lmap :: (a -> b) -> Box m b c -> Box m a c #

rmap :: (b -> c) -> Box m a b -> Box m a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Box m a b -> Box m a c #

(.#) :: forall a b c q. Coercible b a => Box m b c -> q a b -> Box m a c #

(Monad m, Alternative m) => DecAlt (Box m) Source # 
Instance details

Defined in Box.Box

Methods

choice :: (a -> Either b c) -> (Either d e -> f) -> Box m b d -> Box m c e -> Box m a f Source #

loss :: Box m Void b Source #

Applicative m => Divap (Box m) Source # 
Instance details

Defined in Box.Box

Methods

divap :: (a -> (b, c)) -> ((d, e) -> f) -> Box m b d -> Box m c e -> Box m a f Source #

conpur :: a -> Box m b a Source #

(Alternative m, Monad m) => Semigroup (Box m c e) Source # 
Instance details

Defined in Box.Box

Methods

(<>) :: Box m c e -> Box m c e -> Box m c e #

sconcat :: NonEmpty (Box m c e) -> Box m c e #

stimes :: Integral b => b -> Box m c e -> Box m c e #

(Alternative m, Monad m) => Monoid (Box m c e) Source # 
Instance details

Defined in Box.Box

Methods

mempty :: Box m c e #

mappend :: Box m c e -> Box m c e -> Box m c e #

mconcat :: [Box m c e] -> Box m c e #

type CoBox m a b = Codensity m (Box m a b) Source #

A box continuation

newtype CoBoxM m a b Source #

Wrapper for the semigroupoid instance of a box continuation.

Constructors

CoBoxM 

Fields

Instances

Instances details
Monad m => Semigroupoid (CoBoxM m :: Type -> Type -> Type) Source # 
Instance details

Defined in Box.Box

Methods

o :: forall (j :: k) (k1 :: k) (i :: k). CoBoxM m j k1 -> CoBoxM m i j -> CoBoxM m i k1 #

bmap :: Monad m => (a' -> m (Maybe a)) -> (b -> m (Maybe b')) -> Box m a b -> Box m a' b' Source #

A profunctor dimapMaybe

foistb :: (forall a. m a -> n a) -> Box m c e -> Box n c e Source #

Wrong kind signature for the FFunctor class

glue :: Monad m => Committer m a -> Emitter m a -> m () Source #

Connect an emitter directly to a committer of the same type.

>>> glue showStdout <$|> qList [1..3]
1
2
3

glueN :: Monad m => Int -> Committer m a -> Emitter m a -> m () Source #

Glues a committer and emitter, and takes n emits

>>> glueN 3 <$> pure showStdout <*|> qList [1..]
1
2
3

Note that glueN counts the number of events passing across the connection and doesn't take into account post-transmission activity in the Committer, eg

>>> glueN 4 (witherC (\x -> bool (pure Nothing) (pure (Just x)) (even x)) showStdout) <$|> qList [0..9]
0
2

fuse :: Monad m => (a -> m (Maybe b)) -> Box m b a -> m () Source #

Glue a Committer to an Emitter within a box.

fuse (pure . pure) == \(Box c e) -> glue c e

A command-line echoer

fuse (pure . Just . ("echo " <>)) (Box toStdout fromStdin)

class Divap p where Source #

combines divide conquer and liftA2 pure

Methods

divap :: (a -> (b, c)) -> ((d, e) -> f) -> p b d -> p c e -> p a f Source #

conpur :: a -> p b a Source #

Instances

Instances details
Applicative m => Divap (Box m) Source # 
Instance details

Defined in Box.Box

Methods

divap :: (a -> (b, c)) -> ((d, e) -> f) -> Box m b d -> Box m c e -> Box m a f Source #

conpur :: a -> Box m b a Source #

class Profunctor p => DecAlt p where Source #

combines Decidable and Alternative

Methods

choice :: (a -> Either b c) -> (Either d e -> f) -> p b d -> p c e -> p a f Source #

loss :: p Void b Source #

Instances

Instances details
(Monad m, Alternative m) => DecAlt (Box m) Source # 
Instance details

Defined in Box.Box

Methods

choice :: (a -> Either b c) -> (Either d e -> f) -> Box m b d -> Box m c e -> Box m a f Source #

loss :: Box m Void b Source #

cobox :: CoCommitter m a -> CoEmitter m b -> CoBox m a b Source #

Construct a CoBox

cobox = Box <$> c <*> e
>>> fuse (pure . Just . ("show: " <>) . pack . show) <$|> (cobox (pure toStdout) (qList [1..3]))
show: 1
show: 2
show: 3

seqBox :: Monad m => Box (StateT (Seq a) m) a a Source #

State monad queue.