dynamic-pipeline-0.3.1.3: Library Type Safe implementation of Dynamic Pipeline Paradigm (DPP).
Copyright(c) 2021 Juan Pablo Royo Sales
LicenseBSD3
Maintainerjuanpablo.royo@gmail.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

DynamicPipeline.Stage

Description

 
Synopsis
  • data DynamicPipeline dpDefinition filterState filterParam st
  • data Filter dpDefinition filterState filterParam st
  • data Actor dpDefinition filterState filterParam monadicAction
  • data GeneratorStage dpDefinition filterState filterParam st
  • data Stage a
  • type family ValidDP (a :: Bool) :: Constraint where ...
  • type family IsDP (dpDefinition :: k) :: Bool where ...
  • data DP st a
  • data UnFoldFilter dpDefinition readElem st filterState filterParam l
  • withDP :: IO a -> DP s a
  • mkGenerator :: Stage (WithGenerator dpDefinition (Filter dpDefinition filterState filterParam st) (DP st)) -> Filter dpDefinition filterState filterParam st -> GeneratorStage dpDefinition filterState filterParam st
  • mkFilter :: forall dpDefinition filterState filterParam st. WithFilter dpDefinition filterParam (StateT filterState (DP st)) -> Filter dpDefinition filterState filterParam st
  • single :: forall dpDefinition filterState filterParam st. WithFilter dpDefinition filterParam (StateT filterState (DP st)) -> NonEmpty (Actor dpDefinition filterState filterParam (StateT filterState (DP st)))
  • actor :: forall dpDefinition filterState filterParam st. WithFilter dpDefinition filterParam (StateT filterState (DP st)) -> Actor dpDefinition filterState filterParam (StateT filterState (DP st))
  • (|>>>) :: forall dpDefinition filterState filterParam st. Actor dpDefinition filterState filterParam (StateT filterState (DP st)) -> Filter dpDefinition filterState filterParam st -> Filter dpDefinition filterState filterParam st
  • (|>>) :: forall dpDefinition filterState filterParam st. Actor dpDefinition filterState filterParam (StateT filterState (DP st)) -> Actor dpDefinition filterState filterParam (StateT filterState (DP st)) -> Filter dpDefinition filterState filterParam st
  • withSource :: forall (dpDefinition :: Type) st. WithSource dpDefinition (DP st) -> Stage (WithSource dpDefinition (DP st))
  • withGenerator :: forall (dpDefinition :: Type) (filter :: Type) st. WithGenerator dpDefinition filter (DP st) -> Stage (WithGenerator dpDefinition filter (DP st))
  • withSink :: forall (dpDefinition :: Type) st. WithSink dpDefinition (DP st) -> Stage (WithSink dpDefinition (DP st))
  • mkDP :: forall dpDefinition filterState st filterParam filter gparams slr slw glr glw silr silw iparams oparams ls lsi. DPConstraint dpDefinition filterState st filterParam filter gparams slr slw glr glw silr silw iparams oparams ls lsi => Stage (WithSource dpDefinition (DP st)) -> GeneratorStage dpDefinition filterState filterParam st -> Stage (WithSink dpDefinition (DP st)) -> DP st ()
  • runDP :: (forall st. DP st a) -> IO a
  • unfoldF :: forall dpDefinition readElem st filterState filterParam l l1 l2 l3 b2 b3 l4. SpawnFilterConstraint dpDefinition readElem st filterState filterParam l l1 l2 l3 b2 b3 l4 => UnFoldFilter dpDefinition readElem st filterState filterParam l -> DP st (HList l)
  • mkUnfoldFilter :: (readElem -> Bool) -> (readElem -> DP st ()) -> Filter dpDefinition filterState filterParam st -> (readElem -> filterState) -> ReadChannel readElem -> HList l -> UnFoldFilter dpDefinition readElem st filterState filterParam l
  • mkUnfoldFilter' :: (readElem -> Bool) -> Filter dpDefinition filterState filterParam st -> (readElem -> filterState) -> ReadChannel readElem -> HList l -> UnFoldFilter dpDefinition readElem st filterState filterParam l
  • mkUnfoldFilterForAll :: Filter dpDefinition filterState filterParam st -> (readElem -> filterState) -> ReadChannel readElem -> HList l -> UnFoldFilter dpDefinition readElem st filterState filterParam l
  • mkUnfoldFilterForAll' :: (readElem -> DP st ()) -> Filter dpDefinition filterState filterParam st -> (readElem -> filterState) -> ReadChannel readElem -> HList l -> UnFoldFilter dpDefinition readElem st filterState filterParam l

Documentation

data DynamicPipeline dpDefinition filterState filterParam st Source #

DynamicPipeline data type which contains all the three Stages definitions that have been generated by other combinators like withSource, withGenerator and withSink.

dpDefinition ~ Source (Channel ..) :=> Generator (Channel ..) :=> Sink
DP Type level Flow Definition
filterState
State of the StateT Monad that is the local State of the Filter execution
filterParam
Type of the First Parameter that is pass to the Filter when it is created by the Generator Anamorphism. Generator can change the type received from the Reader Channels.
st
Existential Scope of DP Monad.

data Filter dpDefinition filterState filterParam st Source #

Filter Is the template definition of the Filter that may be spawned when reading elements on the Stream.

  • Filter is a NonEmpty List of Actors.
  • Each Actor is executed sequentially on the that List when an Element arrive to that Filter instance.
  • All the Filter execution (a.k.a. forM_ actors runStage) executes in a StateT Monad to share an internal state among Actors.
dpDefinition ~ Source (Channel ..) :=> Generator (Channel ..) :=> Sink
DP Type level Flow Definition
filterState
State of the StateT Monad that is the local State of the Filter execution
filterParam
Type of the First Parameter that is pass to the Filter when it is created by the Generator Anamorphism. Generator can change the type received from the Reader Channels.
st
Existential Scope of DP Monad.

Instances

Instances details
Generic (Filter dpDefinition filterState filterParam st) Source # 
Instance details

Defined in DynamicPipeline.Stage

Associated Types

type Rep (Filter dpDefinition filterState filterParam st) :: Type -> Type #

Methods

from :: Filter dpDefinition filterState filterParam st -> Rep (Filter dpDefinition filterState filterParam st) x #

to :: Rep (Filter dpDefinition filterState filterParam st) x -> Filter dpDefinition filterState filterParam st #

Wrapped (Filter s' s a param) Source # 
Instance details

Defined in DynamicPipeline.Stage

Associated Types

type Unwrapped (Filter s' s a param)

Methods

_Wrapped' :: Iso' (Filter s' s a param) (Unwrapped (Filter s' s a param))

type Rep (Filter dpDefinition filterState filterParam st) Source # 
Instance details

Defined in DynamicPipeline.Stage

type Rep (Filter dpDefinition filterState filterParam st) = D1 ('MetaData "Filter" "DynamicPipeline.Stage" "dynamic-pipeline-0.3.1.3-inplace" 'True) (C1 ('MetaCons "Filter" 'PrefixI 'True) (S1 ('MetaSel ('Just "unFilter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (Actor dpDefinition filterState filterParam (StateT filterState (DP st)))))))
type Unwrapped (Filter s' s a param) Source # 
Instance details

Defined in DynamicPipeline.Stage

type Unwrapped (Filter s' s a param) = GUnwrapped (Rep (Filter s' s a param))

data Actor dpDefinition filterState filterParam monadicAction Source #

Actor Is a particular Stage computation inside a Filter.

dpDefinition ~ Source (Channel ..) :=> Generator (Channel ..) :=> Sink
DP Type level Flow Definition
filterState
State of the StateT Monad that is the local State of the Filter execution
filterParam
Type of the First Parameter that is pass to the Filter when it is created by the Generator Anamorphism. Generator can change the type received from the Reader Channels.
monadicAction
Monad Wrapped in StateT.

data GeneratorStage dpDefinition filterState filterParam st Source #

GeneartorStage is a special Stage data type according to DPP Definition which contains a Filter template definition, in orther to know how to spawn a new Filter if it is needed, and the Stage of the Generator to allow the user to perform some computation in that case.

dpDefinition ~ Source (Channel ..) :=> Generator (Channel ..) :=> Sink
DP Type level Flow Definition
filterState
State of the StateT Monad that is the local State of the Filter execution
filterParam
Type of the First Parameter that is pass to the Filter when it is created by the Generator Anamorphism. Generator can change the type received from the Reader Channels.
st
Existential Scope of DP Monad.

data Stage a Source #

type family ValidDP (a :: Bool) :: Constraint where ... Source #

FCF - Type Level Defunctionalization ValidDP Check if IsDP is True

a
IsDP dpDefinition ~ 'True

Throw a TypeError if Grammar is not correct

Equations

ValidDP 'True = () 
ValidDP 'False = TypeError ((((((('Text "Invalid Semantic for Building DP Program" :$$: 'Text "Language Grammar:") :$$: 'Text "DP -> Source CHANS :=> Generator CHANS :=> Sink") :$$: 'Text "DP -> Source CHANS :=> Generator CHANS :=> FEEDBACK :=> Sink") :$$: 'Text "CHANS -> Channel CH") :$$: 'Text "FEEDBACK -> FeedbackChannel CH") :$$: 'Text "CH -> Type :<+> CH | Eof") :$$: 'Text "Example: 'Source (Channel (Int :<+> Int)) :=> Generator (Channel (Int :<+> Int)) :=> Sink'") 

type family IsDP (dpDefinition :: k) :: Bool where ... Source #

FCF - Type Level Defunctionalization IsDP Validates if DP Flow Type Level Definition is Correct according to the Grammar

dpDefinition ~ Source (Channel ..) :=> Generator (Channel ..) :=> Sink
DP Type level Flow Definition

Equations

IsDP (Source (Channel inToGen) :=> (Generator (Channel genToOut) :=> Sink)) = And (IsDP (Source (Channel inToGen))) (IsDP (Generator (Channel genToOut))) 
IsDP (Source (Channel inToGen) :=> (Generator (Channel genToOut) :=> (FeedbackChannel toSource :=> Sink))) = And (IsDP (Source (Channel inToGen))) (IsDP (Generator (Channel genToOut))) 
IsDP (Source (Channel (a :<+> more))) = IsDP (Source (Channel more)) 
IsDP (Source (Channel Eof)) = 'True 
IsDP (Generator (Channel (a :<+> more))) = IsDP (Generator (Channel more)) 
IsDP (Generator (Channel a)) = 'True 
IsDP x = 'False 

data DP st a Source #

DP is the only Monadic Action allowed to run a DP Defined Flow. It is restricted on Scope by its Existential Type st in order to not escape out from this Monadic Context.

st
Existential Type to Ensure context of Monadic DP
a
Any Type that carries the Monadic Context DP

Instances

Instances details
Monad (DP st) Source # 
Instance details

Defined in DynamicPipeline.Stage

Methods

(>>=) :: DP st a -> (a -> DP st b) -> DP st b #

(>>) :: DP st a -> DP st b -> DP st b #

return :: a -> DP st a #

Functor (DP st) Source # 
Instance details

Defined in DynamicPipeline.Stage

Methods

fmap :: (a -> b) -> DP st a -> DP st b #

(<$) :: a -> DP st b -> DP st a #

Applicative (DP st) Source # 
Instance details

Defined in DynamicPipeline.Stage

Methods

pure :: a -> DP st a #

(<*>) :: DP st (a -> b) -> DP st a -> DP st b #

liftA2 :: (a -> b -> c) -> DP st a -> DP st b -> DP st c #

(*>) :: DP st a -> DP st b -> DP st b #

(<*) :: DP st a -> DP st b -> DP st a #

MonadIO (DP st) Source # 
Instance details

Defined in DynamicPipeline.Stage

Methods

liftIO :: IO a -> DP st a #

data UnFoldFilter dpDefinition readElem st filterState filterParam l Source #

UnFoldFilter is a wrapper Data Type that contains all the information needed to spawn Filter instances according to DPP. The user will have the capability to select how those filters are going to be spawned, for example on each read element, how to setup initial states of StateT Monad on Actor computations in filters, among others.

dpDefinition ~ Source (Channel ..) :=> Generator (Channel ..) :=> Sink
DP Type level Flow Definition
readElem
Type of the element that is being read from the Selected Channel in the Generator Stage
st
Existential Scope of DP Monad.
filterState
State of the StateT Monad that is the local State of the Filter execution
filterParam
Type of the First Parameter that is pass to the Filter when it is created by the Generator Anamorphism. Generator can change the type received from the Reader Channels.

withDP :: IO a -> DP s a Source #

Smart Constructor of DP from IO action

mkGenerator Source #

Arguments

:: Stage (WithGenerator dpDefinition (Filter dpDefinition filterState filterParam st) (DP st))

Generator Stage

-> Filter dpDefinition filterState filterParam st

Filter template

-> GeneratorStage dpDefinition filterState filterParam st 

Smart Constructor of GeneratorStage.

mkFilter Source #

Arguments

:: forall dpDefinition filterState filterParam st. WithFilter dpDefinition filterParam (StateT filterState (DP st))

Associated type family to Generate Function Signature

-> Filter dpDefinition filterState filterParam st 

Smart Constructor of Filter.

single Source #

Arguments

:: forall dpDefinition filterState filterParam st. WithFilter dpDefinition filterParam (StateT filterState (DP st))

Associated type family to Generate Function Signature

-> NonEmpty (Actor dpDefinition filterState filterParam (StateT filterState (DP st))) 

Smart Constructor of Single Actor Wrapped in NonEmpty List.

actor Source #

Arguments

:: forall dpDefinition filterState filterParam st. WithFilter dpDefinition filterParam (StateT filterState (DP st))

Associated type family to Generate Function Signature

-> Actor dpDefinition filterState filterParam (StateT filterState (DP st)) 

Smart Constructor of Actor.

(|>>>) infixr 5 Source #

Arguments

:: forall dpDefinition filterState filterParam st. Actor dpDefinition filterState filterParam (StateT filterState (DP st))

New Actor to put on front

-> Filter dpDefinition filterState filterParam st

Existing Filter

-> Filter dpDefinition filterState filterParam st 

Combinator to build Filter in a DSL approach. Add a new Actor to an already existing Filter.

(|>>) infixr 5 Source #

Arguments

:: forall dpDefinition filterState filterParam st. Actor dpDefinition filterState filterParam (StateT filterState (DP st))

Actor 1

-> Actor dpDefinition filterState filterParam (StateT filterState (DP st))

Actor 2

-> Filter dpDefinition filterState filterParam st 

Combinator to build Filter in a DSL approach . Given 2 Actors build a Filter.

withSource Source #

Arguments

:: forall (dpDefinition :: Type) st. WithSource dpDefinition (DP st)

Associated type family to Generate Function Signature

-> Stage (WithSource dpDefinition (DP st)) 

Combinator for Building a Source Stage. It uses an Associated Type Class to deduce the Function Signature required to the user taken from DP Type Level Flow Definition [dpDefinition ~ Source (Channel ..) :=> Generator (Channel ..) :=> Sink]: DP Type level Flow Definition

st
Existential Scope of DP Monad.

withGenerator Source #

Arguments

:: forall (dpDefinition :: Type) (filter :: Type) st. WithGenerator dpDefinition filter (DP st)

Associated type family to Generate Function Signature

-> Stage (WithGenerator dpDefinition filter (DP st)) 

Combinator for Building a Generator Stage. It uses an Associated Type Class to deduce the Function Signature required to the user taken from DP Type Level Flow Definition [dpDefinition ~ Source (Channel ..) :=> Generator (Channel ..) :=> Sink]: DP Type level Flow Definition

filter
Filter template type
st
Existential Scope of DP Monad.

withSink Source #

Arguments

:: forall (dpDefinition :: Type) st. WithSink dpDefinition (DP st)

Associated type family to Generate Function Signature

-> Stage (WithSink dpDefinition (DP st)) 

Combinator for Building a Sink Stage. It uses an Associated Type Class to deduce the Function Signature required to the user taken from DP Type Level Flow Definition [dpDefinition ~ Source (Channel ..) :=> Generator (Channel ..) :=> Sink]: DP Type level Flow Definition

st
Existential Scope of DP Monad.

mkDP Source #

Arguments

:: forall dpDefinition filterState st filterParam filter gparams slr slw glr glw silr silw iparams oparams ls lsi. DPConstraint dpDefinition filterState st filterParam filter gparams slr slw glr glw silr silw iparams oparams ls lsi 
=> Stage (WithSource dpDefinition (DP st))

Source Stage generated by withSource combinator

-> GeneratorStage dpDefinition filterState filterParam st

Generator Stage generated by withGenerator combinator

-> Stage (WithSink dpDefinition (DP st))

Sink Stage generated by withSink combinator

-> DP st () 

Smart constructor for DynamicPipeline Definition

runDP :: (forall st. DP st a) -> IO a Source #

Run DP Monad to final IO result

unfoldF Source #

Arguments

:: forall dpDefinition readElem st filterState filterParam l l1 l2 l3 b2 b3 l4. SpawnFilterConstraint dpDefinition readElem st filterState filterParam l l1 l2 l3 b2 b3 l4 
=> UnFoldFilter dpDefinition readElem st filterState filterParam l

UnFoldFilter

-> DP st (HList l)

Return the list of ReadChannels with the results to be read for the Generator at the end. You can use this to pass the results to Sink

mkUnfoldFilter Source #

Arguments

:: (readElem -> Bool)

Given a new Element determine if we need to interpose a new Filter or not

-> (readElem -> DP st ())

For each element that the Filter is consuming allow to do something outside the filter with that element. For example trace or debug

-> Filter dpDefinition filterState filterParam st

Filter Template

-> (readElem -> filterState)

Given the First element in this Filter Instance how to Initiate Internal Filter StateT (Memory)

-> ReadChannel readElem

Main ReadChannel to feed filter

-> HList l

HList with the rest of the ReadChannels if There are needed or HNil if it only contians 1 read channel

-> UnFoldFilter dpDefinition readElem st filterState filterParam l 

Smart Constructor for UnFoldFilter

mkUnfoldFilter' Source #

Arguments

:: (readElem -> Bool) 
-> Filter dpDefinition filterState filterParam st 
-> (readElem -> filterState) 
-> ReadChannel readElem 
-> HList l 
-> UnFoldFilter dpDefinition readElem st filterState filterParam l 

Smart Constructor for UnFoldFilter which bypass to do something externally on each read element

mkUnfoldFilterForAll Source #

Arguments

:: Filter dpDefinition filterState filterParam st 
-> (readElem -> filterState) 
-> ReadChannel readElem 
-> HList l 
-> UnFoldFilter dpDefinition readElem st filterState filterParam l 

Smart Constructor for UnFoldFilter That creates a Filter for each element on the Read Channel and interpose on Front of Generator Stage and Last Filter

 Source ---> Filter1 ---> Filter2 ... ---> FilterN ---> Generator ---> Sink

mkUnfoldFilterForAll' Source #

Arguments

:: (readElem -> DP st ()) 
-> Filter dpDefinition filterState filterParam st 
-> (readElem -> filterState) 
-> ReadChannel readElem 
-> HList l 
-> UnFoldFilter dpDefinition readElem st filterState filterParam l 

Idem for mkUnfoldFilterForAll but do something on each Element externally