box-0.6.3: boxes
Safe HaskellNone
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 m and an Emitter. Think of a box with an incoming wire and an outgoing wire. Now notice that the abstraction is reversable: are you looking at two wires from "inside a box"; a blind erlang grunt communicating with the outside world via the two thin wires, or are you looking from "outside the box"; interacting with a black box object. Either way, it's a box. And either way, the committer is contravariant and the emitter covariant so it forms a profunctor.

a Box can also be seen as having an input tape and output tape, thus available for turing and finite-state machine metaphorics.

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 #

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

a profunctor dimapMaybe

hoistb :: Monad m => (forall a. m a -> n a) -> Box m c e -> Box n c e Source #

Wrong signature for the MFunctor class

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

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

The monadic action returns when the committer finishes.

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

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

The monadic action returns if the committer returns False.

glueb :: Monad m => Box m a a -> m () Source #

Short-circuit a homophonuos box.

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

fuse a box

fuse (pure . pure) == glueb

dotb :: Monad m => Box m a b -> Box m b c -> m (Box m a c) Source #

composition of monadic boxes

class Divap p where Source #

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 #