churros-0.1.4.0: Channel/Arrow based streaming computation library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Churro.Types

Description

Datatypes and definitions used by Churro library.

Expand instances for additional documentation!

Synopsis

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.

Constructors

Churro 

Fields

Instances

Instances details
(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 id method creates a passthrough arrow. There isn't usually a reason to use id directly as it has no effect:

>>> runWaitChan $ pure 1 >>> id >>> id >>> id >>> sinkPrint
1
Instance details

Defined in Control.Churro.Types

Methods

id :: forall (a0 :: k). Churro a t a0 a0 #

(.) :: forall (b :: k) (c :: k) (a0 :: k). Churro a t b c -> Churro a t a0 b -> Churro a t a0 c #

(Transport t, Monoid a) => Arrow (Churro a t) Source #

The Arrow instance allows for building non-cyclic directed graphs of churros.

The arr method allows for the creation of a that maps items with a pure function. This is equivalent to `fmap f id`. This is more general and exposed via arr`.

>>> :set -XArrows
>>> :{
let sect  = process $ \x@(_x,_y,z) -> print x >> return z
    graph =
      proc i -> do
        j <- arr succ  -< i
        k <- arr show  -< j
        l <- arr succ  -< j
        m <- arr (> 5) -< j
        n <- sect      -< (k,l,m)
        o <- arr not   -< n
        p <- delay 0.1 -< o
        sinkPrint      -< p
in
runWaitChan $ sourceList [1,5,30] >>> graph
:}
("2",3,False)
("6",7,True)
("31",32,True)
True
False
False

The other Arrow methods are also usable:

>>> runWaitChan $ pure 1 >>> (arr show &&& arr succ) >>> sinkPrint
("1",2)

TODO: Write tests to check if the monoid return type is implemented correctly.

Instance details

Defined in Control.Churro.Types

Methods

arr :: (b -> c) -> Churro a t b c #

first :: Churro a t b c -> Churro a t (b, d) (c, d) #

second :: Churro a t b c -> Churro a t (d, b) (d, c) #

(***) :: Churro a t b c -> Churro a t b' c' -> Churro a t (b, b') (c, c') #

(&&&) :: Churro a t b c -> Churro a t b c' -> Churro a t b (c, c') #

Transport t => Functor (Churro a t i) Source #

Covariant functor instance for Churro - Maps over the output.

>>> let s = sourceList [1,2]
>>> runWaitChan $ s >>> sinkPrint
1
2
>>> runWaitChan $ fmap succ s >>> sinkPrint
2
3
Instance details

Defined in Control.Churro.Types

Methods

fmap :: (a0 -> b) -> Churro a t i a0 -> Churro a t i b #

(<$) :: a0 -> Churro a t i b -> Churro a t i a0 #

(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 pure method allows for the creation of a Churro yielding a single item.

TODO: Write test to check Monoid return type.

Instance details

Defined in Control.Churro.Types

Methods

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 #

type Source a t o = Churro a t Void o Source #

type Sink a t i = Churro a t i Void Source #

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.

Associated Types

data In t :: * -> * Source #

data Out t :: * -> * Source #

Methods

flex Source #

Arguments

:: IO (In t a, Out t a)

Create a new pair of transports.

yank Source #

Arguments

:: Out t a 
-> IO a

Yank an item of the Transport

yeet Source #

Arguments

:: In t a 
-> a 
-> IO ()

Yeet an item onto the Transport

Instances

Instances details
Transport Chan Source # 
Instance details

Defined in Control.Churro.Transport.Chan

Associated Types

data In Chan :: Type -> Type Source #

data Out Chan :: Type -> Type Source #

Methods

flex :: IO (In Chan a, Out Chan a) Source #

yank :: Out Chan a -> IO a Source #

yeet :: In Chan a -> a -> IO () Source #

Transport Unagi Source # 
Instance details

Defined in Control.Churro.Transport.Unagi

Associated Types

data In Unagi :: Type -> Type Source #

data Out Unagi :: Type -> Type Source #

Methods

flex :: IO (In Unagi a, Out Unagi a) Source #

yank :: Out Unagi a -> IO a Source #

yeet :: In Unagi a -> a -> IO () Source #

KnownNat n => Transport (UnagiBounded n :: Type -> Type) Source # 
Instance details

Defined in Control.Churro.Transport.Unagi.Bounded

Associated Types

data In (UnagiBounded n) :: Type -> Type Source #

data Out (UnagiBounded n) :: Type -> Type Source #

Methods

flex :: IO (In (UnagiBounded n) a, Out (UnagiBounded n) a) Source #

yank :: Out (UnagiBounded n) a -> IO a Source #

yeet :: In (UnagiBounded n) a -> a -> IO () Source #

(>>>>) :: (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.

c2c :: Transport t => (a -> b) -> Out t (Maybe a) -> In t (Maybe b) -> IO () Source #

Yank then Yeet each item from one Transport into another.

Raw items are used so Nothing should be Yeeted once the transport is depleted.

finally' :: IO b -> IO a -> IO a Source #

Flipped finally.