Etage-0.1.8: A general data-flow framework

Control.Etage

Contents

Description

This data-flow framework consists mainly of Neurons which are data processing units in data-flow network, receiving and sending Impulses over bidirectional Nerves attached to each other. Neurons and Nerves are best grown in Incubation monad, which takes care of proper growing and dissolve-ing of Neurons. It comes with some example Neurons but you should probably define your own.

Synopsis

Incubation

Incubation is a Monad helping growing a network of Neurons and Nerves while taking care of all the details and cleanup. It is the recommended and preferred way for growing your networks.

A basic example of using Incubation and of this data-flow framework would be a program where one Neuron is generating Impulses with random values (Control.Etage.Sequence) and another Neuron printing them out (Control.Etage.Dump):

 main = do
   prepareEnvironment
   
   incubate $ do
     nerveRandom <- (growNeuron :: NerveOnlyFrom (SequenceNeuron Int)) defaultOptions
     nerveDump <- (growNeuron :: NerveOnlyFor DumpNeuron) defaultOptions
     
     nerveRandom `attachTo` [TranslatableFor nerveDump]

incubate :: Incubation () -> IO ()Source

Runs an Incubation, growing Neurons and attaching Nerves and after that waiting for them to finish and cleanup. It rethrows any exception which might have been thrown.

growNeuron :: (Neuron n, GrowAxon (Axon (NeuronFromImpulse n) fromConductivity), GrowAxon (Axon (NeuronForImpulse n) forConductivity)) => (NeuronOptions n -> NeuronOptions n) -> Incubation (Nerve (NeuronFromImpulse n) fromConductivity (NeuronForImpulse n) forConductivity)Source

Grows a Neuron, taking a function which changes default options and returning a Nerve attached to the Neuron.

Internally it combines growNerve and attach.

attachTo :: forall from for forConductivity. (Impulse from, Impulse for) => Nerve from AxonConductive for forConductivity -> [TranslatableFor from] -> Incubation ()Source

Attaches a Nerve to other Nerves so that Impulses send from the Neuron over the first Nerve are received by Neurons of other Nerves. Impulses are propagated only in this direction, not in the other. If you want also the other direction use attachTo again for that direction. attachTo takes care of all the details (like branching Nerves as necessary).

Be careful if you are attaching the same Nerve multiple times as some Impulses might already been propagated and thus are not available anymore to later attached Nerves. Just list all destination Nerves the first time.

Internally it uses propagate.

fuseWith :: forall i j. (Impulse i, Impulse j) => [TranslatableFrom i] -> (ImpulseTime -> [i] -> [j]) -> Incubation (Nerve (FuseFromImpulse i j) AxonConductive (FuseForImpulse i j) AxonNonConductive)Source

Fuses Impulses received from given Nerves using the given function, sending them over the resulting grown Nerve. fuseWith takes care of all the details (like branching Nerves as necessary).

The important aspect of fuse-ing is its synchronization behavior, as it requires exactly one Impulse from each given Nerve at a time to fuse them together. So it is important that all given Nerves have more or less the equal density of Impulses, otherwise queues of some Nerves will grow unproportionally because of the stalled Impulses, causing at least a memory leak.

impulseFuser helper function can maybe help you with defining fusing function. fuseWith uses type of the given function to construct type of the resulting Nerve so probably too polymorphic type will give you problems.

For example, fuse-ing by suming two Impulses together can be achived like this:

 incubate $ do
   nerveRandom1 <- (growNeuron :: NerveOnlyFrom (SequenceNeuron Int)) defaultOptions
   nerveRandom2 <- (growNeuron :: NerveOnlyFrom (SequenceNeuron Int)) defaultOptions
   nerveDump <- (growNeuron :: NerveOnlyFor DumpNeuron) defaultOptions
   
   nerveFused <- [TranslatableFrom nerveRandom1, TranslatableFrom nerveRandom2] `fuseWith` (impulseFuser ((: []) . sum . concat))
   
   nerveFused `attachTo` [TranslatableFor nerveDump]

Internally it uses fuse.

type NerveBoth n = (NeuronOptions n -> NeuronOptions n) -> Incubation (Nerve (NeuronFromImpulse n) AxonConductive (NeuronForImpulse n) AxonConductive)Source

Type which helps you define (fix) a type of the growNeuron function so that compiler knows whith Neuron instance to choose. It takes type of the Neuron you want to grow as an argument and specifies a Nerve which is conductive in both directions.

type NerveNone n = (NeuronOptions n -> NeuronOptions n) -> Incubation (Nerve (NeuronFromImpulse n) AxonNonConductive (NeuronForImpulse n) AxonNonConductive)Source

Type which helps you define (fix) a type of the growNeuron function so that compiler knows whith Neuron instance to choose. It takes type of the Neuron you want to grow as an argument and specifies a Nerve which is not conductive in any directions.

type NerveOnlyFrom n = (NeuronOptions n -> NeuronOptions n) -> Incubation (Nerve (NeuronFromImpulse n) AxonConductive (NeuronForImpulse n) AxonNonConductive)Source

Type which helps you define (fix) a type of the growNeuron function so that compiler knows whith Neuron instance to choose. It takes type of the Neuron you want to grow as an argument and specifies a Nerve which is conductive only in the direction from the Neuron.

type NerveOnlyFor n = (NeuronOptions n -> NeuronOptions n) -> Incubation (Nerve (NeuronFromImpulse n) AxonNonConductive (NeuronForImpulse n) AxonConductive)Source

Type which helps you define (fix) a type of the growNeuron function so that compiler knows whith Neuron instance to choose. It takes type of the Neuron you want to grow as an argument and specifies a Nerve which is conductive only in the direction to the Neuron.

data Incubation a Source

An Incubation monad type. It makes sure network is grown properly and that everything is cleaned up as necessary.

Internals

Be careful when using those functions as you have to assure your network is well-behaved:

  • You should assure that for all Nerves you defined as conductive from Neurons and attached them to Neurons you really receive sent impulses, otherwise there will be a memory leak. You should probably just define those Nerves you are not interested in Impulses from as NerveOnlyFor or NerveNone.
  • If you attach multiple Neurons to the same Nerve you should probably take care of branching Nerves correctly. For example, if multiple Neurons are receiving from the same Nerve you should first branch Nerve with branchNerveFor, otherwise Neurons will not receive all Impulses as some other Neuron will receive it first (but this can be also intentional). On the other hand, if you are receiving from the same Neuron at multiple parts of the network you should branch Nerve with branchNerveFrom for each such part (or not, if intentional).
  • This also holds for propagate: if you are using it multiple times with the same Nerve as from argument you should first branch it with branchNerveFrom. (But it is probably easier to just use it once and list all for Nerves together.)
  • And for fuse: all Nerves you are fuse-ing from should probably be first branched with branchNerveFrom if you are also receiving from them somewhere else.
  • Of course in a case of an exception or in general when your are doing cleanup you should assure that detach (or detachAndWait) is called for each LiveNeuron (or detachMany or detachManyAndWait).

They are exposed so that you can decouple growing and dissolve-ing handling and that you can attach Nerves in some special ways. If you do not need that use Incubation.

For example, your Neuron can grow and use another Neuron (in this example Control.Etage.Worker) like this:

 data YourNeuron = YourNeuron ... LiveNeuron (Nerve WorkerFromImpulse AxonNonConductive WorkerForImpulse AxonConductive) deriving (Typeable)

 grow options = do
   ...
   nerve <- growNerve
   bracketOnError (attach defaultOptions nerve) detachAndWait $ \neuron -> do
     ...
     return $ YourNeuron ... neuron nerve

 dissolve (YourNeuron ... neuron _) = do
   detachAndWait neuron
   ...

We use bracketOnError there to be sure that Neuron is properly dissolved even if there is an exception later on in growing the parent Neuron. And we use detachAndWait so that we give time for child Neuron to dissolve properly. Which Neuron you want is in this case inferred from the type of the Nerve you defined.

growNerve :: (Impulse from, Impulse for, GrowAxon (Axon from fromConductivity), GrowAxon (Axon for forConductivity)) => IO (Nerve from fromConductivity for forConductivity)Source

Grows an unattached Nerve. By specifying type of the Nerve you can specify conductivity of both directions (which is then type checked for consistency around the program) and thus specify which Impulses you are interested in (and thus limit possible memory leak). With type of Impulses this Nerve is capable of conducting you can also specify which Neuron you are interested in growing on the one end of the Nerve.

For example, you could grow a Nerve for Control.Etage.Sequence Neuron and Neuron itself like this:

 nerve <- growNerve :: IO (Nerve (SequenceFromImpulse Int) AxonConductive (SequenceForImpulse Int) AxonNonConductive)
 neuron <- attach defaultOptions nerve

and for example print all Impulses as they are coming in:

 print =<< getContentsFromNeuron nerve

Check growNeuron for a more high-level function (of Incubation) which both grows a Neuron and corresponding Nerve taking care of all the details. Use this function only if you need decoupled growing.

propagate :: forall from for forConductivity. (Impulse from, Impulse for) => Nerve from AxonConductive for forConductivity -> [TranslatableFor from] -> IO ()Source

It grows an internal Neuron which propagates Impulses from a given Nerve to other Nerves, translate-ing as necessary.

Be careful if you are propagate-ing the same Nerve multiple times as some Impulses might already been propagated and thus are not available anymore to later propagated Nerves. Just list all destination Nerves the first time.

Check attachTo for a more high-level function (of Incubation) taking care of all the details (like branching Nerves as necessary). Use this function only if you are dealing with growing and attaching of Nerves directly.

fuse :: forall i j. (Impulse i, Impulse j) => [TranslatableFrom i] -> (ImpulseTime -> [i] -> [j]) -> IO (Nerve (FuseFromImpulse i j) AxonConductive (FuseForImpulse i j) AxonNonConductive)Source

It grows an internal Neuron which fuses Impulses received from given Nerves using the given function, sending them over the resulting grown Nerve, translate-ing received Impulses as necessary.

The important aspect of fuse-ing is its synchronization behavior, as it requires exactly one Impulse from each given Nerve at a time to fuse them together. So it is important that all given Nerves have more or less the equal density of Impulses, otherwise queues of some Nerves will grow unproportionally because of the stalled Impulses, causing at least a memory leak.

impulseFuser helper function can maybe help you with defining fusing function. fuseWith uses type of the given function to construct type of the resulting Nerve so probably too polymorphic type will give you problems.

Check fuseWith for a more high-level function (of Incubation) taking care of all the details (like branching Nerves as necessary). Use this function only if you are dealing with growing and attaching of Nerves directly.

branchNerveFor :: Nerve from fromConductivity for AxonConductive -> IO (Nerve from fromConductivity for AxonConductive)Source

Branches Nerve on the Neuron side. This allows multiple Neurons to be attached to it and still receive all Impulses (otherwise just the first Neuron which would read from a Nerve would receive a given Impulse). Only new Impulses from a moment of branching on are conducted over new the branch, old Impulses are not reconducted. Branching can be applied multiple times.

branchNerveFrom :: Nerve from AxonConductive for forConductivity -> IO (Nerve from AxonConductive for forConductivity)Source

Branches Nerve on the other (non-Neuron) side. This allows using the same Nerve at multiple parts of the network (program) and still receive all Impulses from Neuron at all parts of the network (otherwise just the first read from a Nerve would receive a given Impulse). Only new Impulses from a moment of branching on are conducted over the new branch, old Impulses are not reconducted. Branching can be applied multiple times.

cross :: Nerve from fromConductivity for forConductivity -> Nerve for forConductivity from fromConductivitySource

Crosses axons around in a Nerve. Useful probably only when you want to attachTo Nerve so that it looks as Impulses are comming from a Neuron and are not send to a Neuron. So in this case you are attaching Nerve in a direction away from a Neuron and not towards it, what is a default.

For example, you can do something like this:

 nerveDump <- (growNeuron :: NerveOnlyFor DumpNeuron) defaultOptions
 nerveOnes <- (growNeuron :: NerveOnlyFrom (SequenceNeuron Int)) (\o -> o { valueSource = repeat 1 })
 nerveTwos <- (growNeuron :: NerveOnlyFrom (SequenceNeuron Int)) (\o -> o { valueSource = repeat 2 })
 
 nerveOnes `attachTo` [TranslatableFor (cross nerveTwos)]
 nerveTwos `attachTo` [TranslatableFor nerveDump]

Of course in this example you could simply attachTo both Nerves to Control.Etage.Dump Neuron. So cross is probably useful only when using Nerves unattached to its Neuron (made by growNerve, for example) and/or when using such Nerves with Neurons which operate on how Impulses are propagated (or fused).

Neurons and Impulses

Using only built-in Neurons is not much fun. Main idea of this data-flow framework is to ease development of your own Neurons (data processing units).

class (Typeable n, Impulse (NeuronFromImpulse n), Impulse (NeuronForImpulse n), Typeable (NeuronFromImpulse n), Typeable (NeuronForImpulse n)) => Neuron n whereSource

A type class which defines common methods and data types of Neurons.

Associated Types

type NeuronFromImpulse n Source

A type for Impulses send from a Neuron. If not used, define it simply as NoImpulse.

type NeuronForImpulse n Source

A type for Impulses send for a Neuron. If not used, define it simply as NoImpulse.

data NeuronOptions n Source

A data type for options. Neuron does not really need to use them.

Methods

mkDefaultOptions :: IO (NeuronOptions n)Source

Method which returns default values for options. By default returns undefined.

getNeuronMapCapability :: NeuronOptions n -> NeuronMapCapabilitySource

Method which returns how should Neuron be mapped on capabilities (OS threads). By default returns NeuronFreelyMapOnCapability.

grow :: NeuronOptions n -> IO nSource

The first phase in a life-cycle of a Neuron is to grow. In this phase everything should be prepared and initialized. It returns a Neuron value which is then passed to next phases. If you want to use NeuronOptions also in those phases you should store them in the Neuron value. By default returns undefined.

live :: Nerve (NeuronFromImpulse n) fromConductivity (NeuronForImpulse n) forConductivity -> n -> IO ()Source

After growing Neuron lives. This is a phase in which it should read Impulses from its Nerve and send them back, as defined by its logic/purpose. Some Neurons only read, some only send, some do both or none.

Most Neurons do never finish this phase on its own (only by exception), but if your Neuron does, consider using dissolving at the end which initiates dissolving also elsewhere in the network (or in the parent Neuron, if it has one). Examples of such Neurons are Control.Etage.Timeout and Control.Etage.Sequence (once a given sequence ends).

By default it blocks indefinitely (until an exception).

dissolve :: n -> IO ()Source

In this phase everything should be cleaned up and deinitialized. If you have grown child Neurons you should take care here to dissolve them too. You can use detachAndWait for that (or detachManyAndWait if you have more of them). By default it does nothing.

attach :: (NeuronOptions n -> NeuronOptions n) -> Nerve (NeuronFromImpulse n) fromConductivity (NeuronForImpulse n) forConductivity -> IO LiveNeuronSource

This method should take care of growing a Neuron with a given Nerve attached to it. It takes a function which changes default options and returns a LiveNeuron value which can be used for detaching (and thus dissolve-ing) the Neuron. It should create a thread for a Neuron to live in and it should assure proper cleanup and dissolve-ing.

By default it calls attach' to do all that.

Instances

Neuron DumpNeuron

A Neuron which dumps all Impulses it receives.

Neuron WorkerNeuron

A worker Neuron which evaluates IO actions it receives.

Neuron TimeoutNeuron

A simple Neuron which initiates dissolving after a given delay.

Neuron FailNeuron

A simple Neuron which just fails in growing phase.

(Real v, Random v, Show v, Typeable v) => Neuron (SequenceNeuron v)

A Neuron which generates values based on a given sequence at a given interval.

Impulse i => Neuron (DelayNeuron i)

A Neuron which delays received Impulses before sending them further.

(Impulse from, Impulse for) => Neuron (PropagateNeuron from for)

An internal Neuron which implements propagate.

(Impulse i, Impulse j) => Neuron (FuseNeuron i j)

An internal Neuron which implements fuse.

(Impulse i, Impulse j) => Neuron (FunctionNeuron i j)

A Neuron which applies a given function to received Impulses.

attach' :: Neuron n => (NeuronOptions n -> NeuronOptions n) -> Nerve (NeuronFromImpulse n) fromConductivity (NeuronForImpulse n) forConductivity -> IO LiveNeuronSource

Default implementation for attach method. It takes a function which changes default options and returns a LiveNeuron value which can be used for detaching (and thus dissolve-ing) the Neuron.

It changes default options according to a given function, creates thread for a Neuron to live in based on getNeuronMapCapability, grows a Neuron, runs live and prepares everything for cleanup with dissolve, whether because live finished or because of an exception. In the later case it rethrows an exception in the parent Neuron (or in Incubation). It also signals the Neuron has dissolved for detachAndWait and detachManyAndWait.

detach :: LiveNeuron -> IO ()Source

Initiates dissolve-ing of a Neuron by throwing a DissolveException. To be used outside of a Neuron.

detachAndWait :: LiveNeuron -> IO ()Source

Similar to detachAndWait but it also waits Neuron to finish dissolve-ing.

detachMany :: [LiveNeuron] -> IO ()Source

Similar to detach but for many Neurons at the same time. It initiates dissolve-ing in the list order.

detachManyAndWait :: [LiveNeuron] -> IO ()Source

Similar to detachAndWait but for many Neurons at the same time. It first initiates dissolve-ing in the list order and then wait for all Neurons to finish dissolve-ing.

data LiveNeuron Source

Type representing a live Neuron.

data DissolveException Source

An exception which initiates dissolve-ing of a Neuron. Should be thrown outside the Neuron to the Neuron. For throwing inside the Neuron use DissolvingException (or simply dissolving).

dissolving :: Show n => n -> IO aSource

Initiates dissolve-ing of a Neuron by throwing a DissolvingException. To be used inside a Neuron to maybe prematurely finish its life but more importantly to initiate dissolve-ing in the parent Neuron (or in Incubation). As an argument it is accustomed to pass a Neuron value as passed to live method.

data DissolvingException Source

An exception which initiates dissolve-ing of a Neuron. Should be thrown inside the Neuron with passing its Neuron value as argument (as passed to live method). For throwing outside the Neuron use DissolveException (or simply detach and others).

mkNeuronMapOnRandomCapability :: IO NeuronMapCapabilitySource

Creates a NeuronMapOnCapability value with a chosen capability picked by random. Useful when you have to map few Neurons to the same capability (because of an eternal (FFI) library limitations) but it does not matter to which one. So you create this value and pass it as an option to all those Neurons, making sure that they will return it with their getNeuronMapCapability method. For example, sometimes you have to assure that both your Neuron and Control.Etage.Worker Neuron are running on the same capability so that you can correctly offload lengthly IO actions to it. This makes both Neurons in fact still running in one thread (which is often a limitation of external libraries), Haskell taking care of interleaving Neurons IO actions.

data NeuronMapCapability Source

Neurons can be mapped to capabilities (OS threads) in different ways. The best is to let Haskell decide the best capability (and also move Neurons among them as necessary) by using NeuronFreelyMapOnCapability value, but sometimes because of an external (FFI) library limitations you have to map Neuron to a fixed capability, you can use NeuronMapOnCapability for that.

Sometimes it is not important to which capability you map a Neuron, just that few Neurons are mapped to the same. You can use mkNeuronMapOnRandomCapability to create such NeuronMapCapability value.

Constructors

NeuronMapOnCapability Int

Map a Neuron to fixed capability.

NeuronFreelyMapOnCapability

Let Haskell decide on which capability is best to map a Neuron at a given time.

defaultOptions :: Neuron n => NeuronOptions n -> NeuronOptions nSource

Function which can be used as an argument to growNeuron or attach which leaves default options as they are.

In fact it is just an identity function.

class (Show i, Typeable i) => Impulse i whereSource

Type class with common methods for impulses send over Nerves and processed in Neurons so that it is possible to define Neurons which operate on any Impulse type by using AnyImpulse type as their receiving Impulses type. An example of such Neuron is Control.Etage.Dump.

Methods

impulseTime :: i -> ImpulseTimeSource

This method should return a timestamp when the Impulse was created/finalized what should be the moment just before it is send over the Nerve, the moment it formed into its final form and started leaving the Neuron. As Haskell is a lazy language this does not mean that at that moment all values the Impulse defines are really already evaluated (they are evaluated when they are needed, probably in some other Neuron).

You can do something like:

 time <- getCurrentImpulseTime
 sendFromNeuron nerve YourImpulse { impulseTimestamp = time, ... }

impulseValue :: i -> ImpulseValueSource

This method should return all values (data payload) the Impulse defines. Currently order and format is not yet finalized so it is just a list of Rational values in some order (for now it probably should be the order in which the values are defined in the Impulse constructor).

It is meant to allow general Neurons which can work on any Impulse type to be developed. For example Neurons which implement some machine learning or data mining algorithms. It is on purpose that values are cleared of any semantic meaning so algorithms have better chance not to get in touch with some unintended domain specific knowledge.

type ImpulseTime = POSIXTimeSource

Type of Impulse timestamp. You can use getCurrentImpulseTime for timestamp representing current time.

type ImpulseValue = [Rational]Source

Type of a general representation of Impulse values (data payload). Currently it is just a list of Rational values.

data AnyImpulse whereSource

An existentially quantified type encompassing all Impulses. Useful when Neuron should send or receive any Impulse type.

Constructors

AnyImpulse :: Impulse i => i -> AnyImpulse 

data NoImpulse Source

Empty Impulse data type. Useful when Neuron does not send or receive Impulses.

data (Real r, Show r, Typeable r) => IValue r Source

Basic Impulse data type holding a value.

Ordered first by impulseValueTimestamp and then by value. Equal only if both impulseValueTimestamp and value are equal.

Constructors

IValue 

Fields

impulseValueTimestamp :: ImpulseTime

Time when the Impulse was created/finalized.

value :: r

value of the Impulse.

Instances

Typeable1 IValue 
(Real r, Typeable r) => Eq (IValue r) 
(Data r, Real r) => Data (IValue r) 
(Real r, Typeable r) => Ord (IValue r) 
(Read r, Real r, Typeable r) => Read (IValue r) 
(Real r, Typeable r) => Show (IValue r) 
(Real r, Show r, Typeable r) => Impulse (IValue r) 

type IInteger = IValue IntegerSource

IValue type with value as Integer type.

data (Real r, Show r, Typeable r) => IList r Source

Basic Impulse data type holding a list of values.

Ordered first by impulseListTimestamp and then by list. Equal only if both impulseListTimestamp and list are equal.

Constructors

IList 

Fields

impulseListTimestamp :: ImpulseTime

Time when the Impulse was created/finalized.

list :: [r]

list of values of the Impulse.

Instances

Typeable1 IList 
(Real r, Typeable r) => Eq (IList r) 
(Data r, Real r) => Data (IList r) 
(Real r, Typeable r) => Ord (IList r) 
(Read r, Real r, Typeable r) => Read (IList r) 
(Real r, Typeable r) => Show (IList r) 
(Real r, Show r, Typeable r) => Impulse (IList r) 

type IIntegerList = IList IntegerSource

IList type with list having Integer type values.

type IRationalList = IList RationalSource

IList type with list having Rational type values.

class (Impulse i, Impulse j) => ImpulseTranslator i j whereSource

This type class defines a method for translating between Impulse types.

Methods

translate :: i -> [j]Source

translate gets an Impulse of one type and returns a list of Impulses of another type.

Impulses should be translated meaningfully, translating values as possible and filling others with reasonable defaults. Timestamp should be just copied (translation should be seen as an instantaneous operation as it is a byproduct of type constraints and chosen description format of Impulses and not something found otherwise in a network. Time spend in translation should be seen as a part of time spend in sending of an Impulse along a Nerve.

One Impulse can be translated into multiple other Impulses as sometimes some Impulses are higher level than other. (Translating multiple Impulses into one Impulse requires keeping a state and should be done in a Neuron.) The order is important as first Impulses in the list are send first along a Nerve.

translateAndSend :: ImpulseTranslator i for => Nerve from fromConductivity for AxonConductive -> i -> IO ()Source

Translates (if necessary ImpulseTranslator exists) an Impulse and sends translation to Neuron.

data Nerve from fromConductivity for forConductivity Source

Type representing a Nerve between Neurons. It is bi-directional (from and to a Neuron, each direction being one axon) and you can specify type of Impulses traveling along the axon and its conductivity (with AxonConductive or AxonNonConductive).

You mostly do not need to specify this type manually if you are using growNeuron and one of NerveBoth, NerveNone, NerveOnlyFrom and NerveOnlyFor types.

Instances

Typeable4 Nerve 
(Typeable forConductivity, Typeable fromConductivity, Typeable from, Typeable for) => Show (Nerve from fromConductivity for forConductivity) 

data AxonConductive Source

Is axon (one direction of a Nerve) conductive? Yes, it is.

This is type checked and enforced. If you define axon as conductive you have to make make sure that Impulses send along it are really read somewhere, otherwise a memory leak will occur.

Instances

data AxonNonConductive Source

Is axon (one direction of a Nerve) conductive? No, it is not.

This is type checked and enforced. It is useful to specify nonconductive axons when you are not interested in Impulses from a particular axon (direction), making sure there will not be a memory leak because Impulses would pile up.

data FromNerve whereSource

An existentially quantified type encompassing all Nerves which are conductive from a Neuron.

Constructors

FromNerve :: Impulse from => Nerve from AxonConductive for forConductivity -> FromNerve 

data ForNerve whereSource

An existentially quantified type encompassing all Nerves which are conductive to a Neuron.

Constructors

ForNerve :: Impulse for => Nerve from fromConductivity for AxonConductive -> ForNerve 

data BothNerve whereSource

An existentially quantified type encompassing all Nerves which are conductive in both directions.

Constructors

BothNerve :: (Impulse from, Impulse for) => Nerve from AxonConductive for AxonConductive -> BothNerve 

data TranslatableFrom i whereSource

An existentially quantified type encompassing all Nerves which can be translated to the same Impulse type. Used in fuseWith (and fuse) to list all Nerves from which you want to fuse Impulses.

Constructors

TranslatableFrom :: (Impulse for, ImpulseTranslator from i) => Nerve from AxonConductive for forConductivity -> TranslatableFrom i 

data TranslatableFor i whereSource

An existentially quantified type encompassing all Nerves which can be translated from the same Impulse type. Used in attachTo (and propagate) to list all Nerves to which you want a given Nerve to attach to (and Impulses to propagate).

Constructors

TranslatableFor :: (Impulse from, ImpulseTranslator i for) => Nerve from fromConductivity for AxonConductive -> TranslatableFor i 

Sending and receiving outside the Neuron

Those functions are used outside the Neuron when interacting with it.

sendForNeuron :: Nerve from fromConductivity for AxonConductive -> for -> IO ()Source

Sends an Impulse to a Neuron. Nerve has to be conductive.

getFromNeuron :: Nerve from AxonConductive for forConductivity -> IO fromSource

Gets an Impulse from a Neuron. It blocks until an Impulse is available. Nerve has to be conductive.

maybeGetFromNeuron :: Nerve from AxonConductive for forConductivity -> IO (Maybe from)Source

Similar to getFromNeuron just that it does not block if Impulse is not available.

slurpFromNeuron :: Nerve from AxonConductive for forConductivity -> IO [from]Source

Gets all immediately available Impulses from a Neuron. There could be no Impulses available and thus the result is an empty list. Oldest Impulse is the last in the list. Nerve has to be conductive.

waitAndSlurpFromNeuron :: Nerve from AxonConductive for forConductivity -> IO [from]Source

Similar to slurpFromNeuron but it waits for at least one Impulse.

getContentsFromNeuron :: Nerve from AxonConductive for forConductivity -> IO [from]Source

Returns a lazy list of Impulses from a Neuron. Nerve has to be conductive.

sendListForNeuron :: Nerve from fromConductivity for AxonConductive -> [for] -> IO ()Source

Sends all Impulses from a given list to a Neuron. Nerve has to be conductive.

Sending and receiving inside the Neuron

Those functions are used inside the Neuron when implementing it.

sendFromNeuron :: Nerve from fromConductivity for forConductivity -> from -> IO ()Source

Sends an Impulse from a Neuron. Nerve does not need to be conductive, Impulse will be silently dropped in this case.

getForNeuron :: Nerve from fromConductivity for forConductivity -> IO forSource

Gets an Impulse for a Neuron. It blocks until an Impulse is available. Nerve does not need to be conductive, it will block indefinitely (until an exception) in this case.

maybeGetForNeuron :: Nerve from fromConductivity for forConductivity -> IO (Maybe for)Source

Similar to getForNeuron just that it does not block if Impulse is not available. Nerve does not need to be conductive, it will always return Nothing in this case.

slurpForNeuron :: Nerve from fromConductivity for forConductivity -> IO [for]Source

Gets all immediately available Impulses for a Neuron. There could be no Impulses available and thus the result is an empty list. Oldest Impulse is the last in the list. Nerve does not need to be conductive, it will always return an empty list in this case.

waitAndSlurpForNeuron :: Nerve from fromConductivity for forConductivity -> IO [for]Source

Similar to slurpForNeuron but it waits for at least one Impulse. Nerve does not need to be conductive, it will block indefinitely (until an exception) in this case.

getNewestForNeuron :: Data for => Nerve from fromConductivity for forConductivity -> IO [for]Source

Similar to waitAndSlurpForNeuron but it will return only the newest Impulse for every NeuronForImpulse data type constructor. This is the same as head <$> waitAndSlurpForNeuron iff NeuronForImpulse has only one constructor defined. Otherwise it can return multiple Impulses, for each constructor one.

getContentsForNeuron :: Nerve from fromConductivity for forConductivity -> IO [for]Source

Returns a lazy list of Impulses for a Neuron. Nerve does not need to be conductive, it will block indefinitely (until an exception) in this case.

sendListFromNeuron :: Nerve from fromConductivity for forConductivity -> [from] -> IO ()Source

Sends all Impulses from a given list to a Neuron. Nerve does not need to be conductive, Impulses will be silently dropped in this case.

Helper functions

prepareEnvironment :: IO ()Source

Helper function which does some common initialization. Currently it sets stderr buffering to LineBuffering so that when multiple Neurons print to stderr output is not mixed. It also installs handlers for keyboardSignal and softwareTermination signals so that cleanup in Incubation works as expected.

Using it has also an useful side-effect of Haskell not throwing BlockedIndefinitelyOnMVar exceptions when the network runs out.

fuserFun :: (Real r, Show r, Typeable r) => ([ImpulseValue] -> [r]) -> ImpulseTime -> [AnyImpulse] -> [IValue r]Source

Helper function for use with fuseWith (and fuse) which wraps given function with impulseValue before it and IValue after.

For example, you can define a fusing function which makes a product of fusing Impulses (more precisely their data payload):

 impulseFuser ((: []) . product . concat)

listFuser :: (Real r, Show r, Typeable r) => ImpulseTime -> [IValue r] -> [IList r]Source

Helper function for use with fuseWith (and fuse) which converts a list of IValue Impulses to a IList Impulse. If given list is empty no resulting Impulse is made.

getCurrentImpulseTime :: IO ImpulseTimeSource

Returns current time. Useful when creating new Impulses.

impulseEq :: (Impulse i, Impulse j) => i -> j -> BoolSource

This function defines equality between Impulses as equality of impulseTime and impulseValue values.

impulseCompare :: (Impulse i, Impulse j) => i -> j -> OrderingSource

This function defines ordering between Impulses as ordering first by impulseTime values and then by impulseValue values.