Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Datatypes and definitions used by Churro library.
Expand instances for additional documentation!
Synopsis
- newtype Churro a t i o = Churro {}
- type Source a t o = Churro a t Void o
- type Sink a t i = Churro a t i Void
- type DoubleDipped a t = Churro a t Void Void
- class Transport (t :: * -> *) where
- (>>>>) :: (Transport t, fo ~ gi) => Churro a1 t fi fo -> Churro a2 t gi go -> Churro a2 t fi go
- pure' :: (Transport t, Monoid a) => o -> Churro a t i o
- arr' :: (Functor (cat a), Category cat) => (a -> b) -> cat a b
- buildChurro :: Transport t => (Out t (Maybe i) -> In t (Maybe o) -> IO a) -> Churro a t i o
- buildChurro' :: Transport t => (In t (Maybe i) -> Out t (Maybe i) -> In t (Maybe o) -> IO a) -> Churro a t i o
- yeetList :: (Foldable f, Transport t) => In t a -> f a -> IO ()
- yankList :: Transport t => Out t (Maybe a) -> IO [a]
- yankAll :: (Transport t, Monoid a) => Out t (Maybe i) -> (i -> IO a) -> IO a
- yankAll' :: (Transport t, Monoid b) => Out t (Maybe a) -> (Maybe a -> IO b) -> IO b
- c2c :: Transport t => (a -> b) -> Out t (Maybe a) -> In t (Maybe b) -> IO ()
- finally' :: IO b -> IO a -> IO a
Documentation
We import the library for testing, although this would be a circular import in the module itself.
>>>
import Control.Churro
Data, Classes and Instances
newtype Churro a t i o Source #
The core datatype for the library.
Parameters t
, i
and o
represent the transport, input, and output types respectively.
The items on transports are wrapped in Maybe
to allow signalling of completion of a source.
When building a program by composing Churros, the output Transport of one Churro is fed into the input Transports of other Churros.
Type families are used to allow the in/out channels to have different types and prevent accidentally reading/writing from the wrong transport.
Convenience types of Source
, Sink
, and DoubleDipped
are also defined,
although use is not required.
Instances
(Transport t, Monoid a) => Category (Churro a t :: Type -> Type -> Type) Source # | The Category instance allows for the creation of Churro pipelines. All other examples of the form `a >>> b` use this instance. The
|
(Transport t, Monoid a) => Arrow (Churro a t) Source # | The Arrow instance allows for building non-cyclic directed graphs of churros. The
The other Arrow methods are also usable:
TODO: Write tests to check if the monoid return type is implemented correctly. |
Defined in Control.Churro.Types | |
Transport t => Functor (Churro a t i) Source # | Covariant functor instance for Churro - Maps over the output.
|
(Transport t, Monoid a) => Applicative (Churro a t Void) Source # | The Applicative instance allows for pairwise composition of Churro pipelines. Once again this is covariat and the composition occurs on the output transports of the Churros. The TODO: Write test to check Monoid return type. |
Defined in Control.Churro.Types pure :: a0 -> Churro a t Void a0 # (<*>) :: Churro a t Void (a0 -> b) -> Churro a t Void a0 -> Churro a t Void b # liftA2 :: (a0 -> b -> c) -> Churro a t Void a0 -> Churro a t Void b -> Churro a t Void c # (*>) :: Churro a t Void a0 -> Churro a t Void b -> Churro a t Void b # (<*) :: Churro a t Void a0 -> Churro a t Void b -> Churro a t Void a0 # |
class Transport (t :: * -> *) where Source #
The transport method is abstracted via the Transport class
This allows use of pure or impure channels, such as:
- Chan (Included in
Chan
) - TChan
- Seq
- Unagi
- Various buffered options
Transports used in conjunction with Churros wrap items in Maybe so that once a source has been depleted it can signal completion with a Nothing item.
The flex method returns two transports, so that channels such as unagi that create an in/outs pair can have a Transport instance.
Channels like Chan that have a single channel act as in/out simply reuse the same channel in the pair returned.
(>>>>) :: (Transport t, fo ~ gi) => Churro a1 t fi fo -> Churro a2 t gi go -> Churro a2 t fi go Source #
Category style composition that allows for return type to change downstream.
pure' :: (Transport t, Monoid a) => o -> Churro a t i o Source #
More general variant of pure
with Monoid constraint.
arr' :: (Functor (cat a), Category cat) => (a -> b) -> cat a b Source #
More general version of arr
.
Useful when building pipelines that need to work with return types.
Helpers
buildChurro :: Transport t => (Out t (Maybe i) -> In t (Maybe o) -> IO a) -> Churro a t i o Source #
A helper to facilitate constructing a Churro that makes new input and output transports available for manipulation.
The manipulations performed are carried out in the async action associated with the Churro
buildChurro' :: Transport t => (In t (Maybe i) -> Out t (Maybe i) -> In t (Maybe o) -> IO a) -> Churro a t i o Source #
A version of buildChurro
that also passes the original input to the callback so that you can reschedule items.
Used by "retry" style functions.
yeetList :: (Foldable f, Transport t) => In t a -> f a -> IO () Source #
Yeet all items from a list into a raw transport.
WARNING: If you are using this to build a churro by hand make sure you yeet Nothing once you're finished.
yankList :: Transport t => Out t (Maybe a) -> IO [a] Source #
Yank all items from a Raw transport into a list.
Won't terminate until the transport has been consumed.
yankAll :: (Transport t, Monoid a) => Out t (Maybe i) -> (i -> IO a) -> IO a Source #
Yank each item from a transport into a callback.
yankAll' :: (Transport t, Monoid b) => Out t (Maybe a) -> (Maybe a -> IO b) -> IO b Source #
Yank each raw item from a transport into a callback.
The items are wrapped in Maybes and when all items are yanked, Nothing is fed to the callback.