Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Datatypes and definitions used by Churro library.
Expand instances for additional documentation!
Synopsis
- data Churro t i o = Churro {}
- type Source t o = Churro t Void o
- type Sink t i = Churro t i Void
- type DoubleDipped t = Churro t Void Void
- class Transport t where
- buildChurro :: Transport t => (t (Maybe i) -> t (Maybe o) -> IO ()) -> Churro t i o
- yeetList :: (Foldable t1, Transport t2) => t2 a -> t1 a -> IO ()
- yankList :: Transport t => t (Maybe a) -> IO [a]
- yankAll :: Transport t => t (Maybe i) -> (i -> IO a) -> IO ()
- yankAll' :: Transport t => t (Maybe a) -> (Maybe a -> IO b) -> IO b
- c2c :: Transport t => (a1 -> a2) -> t (Maybe a1) -> t (Maybe a2) -> 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
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.
Convenience types of Source
, Sink
, and DoubleDipped
are also defined, although use is not required.
Instances
Transport t => Arrow (Churro t) Source # | The Arrow instance allows for building non-cyclic directed graphs of churros. The
The other Arrow methods are also usable:
|
Transport t => Category (Churro 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 => Functor (Churro t i) Source # | Covariant functor instance for Churro - Maps over the output.
|
Transport t => Applicative (Churro 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 |
Defined in Control.Churro.Types pure :: a -> Churro t Void a # (<*>) :: Churro t Void (a -> b) -> Churro t Void a -> Churro t Void b # liftA2 :: (a -> b -> c) -> Churro t Void a -> Churro t Void b -> Churro t Void c # (*>) :: Churro t Void a -> Churro t Void b -> Churro t Void b # (<*) :: Churro t Void a -> Churro t Void b -> Churro t Void a # |
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
- 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.
Helpers
buildChurro :: Transport t => (t (Maybe i) -> t (Maybe o) -> IO ()) -> Churro 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
yeetList :: (Foldable t1, Transport t2) => t2 a -> t1 a -> IO () Source #
Yeet all items from a list into a transport.
yankList :: Transport t => 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 => t (Maybe i) -> (i -> IO a) -> IO () Source #
Yank each item from a transport into a callback.
yankAll' :: Transport t => 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.