Copyright | (c) Ricardo Bonna KTH/ICT/ES ForSyDe-Group |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | ricardobonna@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
Experimental lib. Further test needed
Synopsis
- delayCSDF :: [a] -> Signal a -> Signal a
- actor11CSDF :: [(Int, Int, [a] -> [b])] -> Signal a -> Signal b
- actor12CSDF :: [(Int, (Int, Int), [a] -> ([b], [c]))] -> Signal a -> (Signal b, Signal c)
- actor13CSDF :: [(Int, (Int, Int, Int), [a] -> ([b], [c], [d]))] -> Signal a -> (Signal b, Signal c, Signal d)
- actor14CSDF :: [(Int, (Int, Int, Int, Int), [a] -> ([b], [c], [d], [e]))] -> Signal a -> (Signal b, Signal c, Signal d, Signal e)
- actor21CSDF :: [((Int, Int), Int, [a] -> [b] -> [c])] -> Signal a -> Signal b -> Signal c
- actor22CSDF :: [((Int, Int), (Int, Int), [a] -> [b] -> ([c], [d]))] -> Signal a -> Signal b -> (Signal c, Signal d)
- actor23CSDF :: [((Int, Int), (Int, Int, Int), [a] -> [b] -> ([c], [d], [e]))] -> Signal a -> Signal b -> (Signal c, Signal d, Signal e)
- actor24CSDF :: [((Int, Int), (Int, Int, Int, Int), [a] -> [b] -> ([c], [d], [e], [f]))] -> Signal a -> Signal b -> (Signal c, Signal d, Signal e, Signal f)
- actor31CSDF :: [((Int, Int, Int), Int, [a] -> [b] -> [c] -> [d])] -> Signal a -> Signal b -> Signal c -> Signal d
- actor32CSDF :: [((Int, Int, Int), (Int, Int), [a] -> [b] -> [c] -> ([d], [e]))] -> Signal a -> Signal b -> Signal c -> (Signal d, Signal e)
- actor33CSDF :: [((Int, Int, Int), (Int, Int, Int), [a] -> [b] -> [c] -> ([d], [e], [f]))] -> Signal a -> Signal b -> Signal c -> (Signal d, Signal e, Signal f)
- actor34CSDF :: [((Int, Int, Int), (Int, Int, Int, Int), [a] -> [b] -> [c] -> ([d], [e], [f], [g]))] -> Signal a -> Signal b -> Signal c -> (Signal d, Signal e, Signal f, Signal g)
- actor41CSDF :: [((Int, Int, Int, Int), Int, [a] -> [b] -> [c] -> [d] -> [e])] -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e
- actor42CSDF :: [((Int, Int, Int, Int), (Int, Int), [a] -> [b] -> [c] -> [d] -> ([e], [f]))] -> Signal a -> Signal b -> Signal c -> Signal d -> (Signal e, Signal f)
- actor43CSDF :: [((Int, Int, Int, Int), (Int, Int, Int), [a] -> [b] -> [c] -> [d] -> ([e], [f], [g]))] -> Signal a -> Signal b -> Signal c -> Signal d -> (Signal e, Signal f, Signal g)
- actor44CSDF :: [((Int, Int, Int, Int), (Int, Int, Int, Int), [a] -> [b] -> [c] -> [d] -> ([e], [f], [g], [h]))] -> Signal a -> Signal b -> Signal c -> Signal d -> (Signal e, Signal f, Signal g, Signal h)
Sequential Process Constructors
Sequential process constructors are used for processes that have a state. One of the input parameters is the initial state.
delayCSDF :: [a] -> Signal a -> Signal a Source #
The process constructor delaynCSDF
delays the signal n event
cycles by introducing n initial values at the beginning of the
output signal.
>>>
delayCSDF [3,2,1,0] $ signal [1..5]
{3,2,1,0,1,2,3,4,5}
Actors
Based on the process constructors in the CSDF-MoC, the CSDF-library provides CSDF-actors with single or multiple inputs
actor11CSDF :: [(Int, Int, [a] -> [b])] -> Signal a -> Signal b Source #
The process constructor actor11CSDF
constructs an CSDF actor with
one input and one output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
>>>
let c1 = (2,1,\[a,b] -> [a + b])
>>>
let c2 = (2,2,\[a,b] -> [max a b, min a b])
>>>
let c3 = (2,1,\[a,b] -> [a - b])
>>>
let s = signal [1..20]
>>>
s
{1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20}>>>
actor11CSDF [c1,c2,c3] s
{3,4,3,-1,15,10,9,-1,27,16,15,-1,39}
actor12CSDF :: [(Int, (Int, Int), [a] -> ([b], [c]))] -> Signal a -> (Signal b, Signal c) Source #
The process constructor actor12CSDF
constructs an CSDF actor with
one input and two output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
actor13CSDF :: [(Int, (Int, Int, Int), [a] -> ([b], [c], [d]))] -> Signal a -> (Signal b, Signal c, Signal d) Source #
The process constructor actor13CSDF
constructs an CSDF actor with
one input and three output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
actor14CSDF :: [(Int, (Int, Int, Int, Int), [a] -> ([b], [c], [d], [e]))] -> Signal a -> (Signal b, Signal c, Signal d, Signal e) Source #
The process constructor actor14CSDF
constructs an CSDF actor with
one input and four output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
actor21CSDF :: [((Int, Int), Int, [a] -> [b] -> [c])] -> Signal a -> Signal b -> Signal c Source #
The process constructor actor21CSDF
constructs an CSDF actor with
two input and one output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
>>>
let c1 = ((2,2),1,\[a,b] [c,d] -> [a+b+c+d])
>>>
let c2 = ((1,1),2,\ [a] [b] -> [max a b, min a b])
>>>
let c3 = ((1,3),1,\ [a] [b,c,d] -> [a-b+c-d])
>>>
let s1 = signal [1..10]
>>>
let s2 = signal [10..]
>>>
actor21CSDF [c1,c2,c3] s1 s2
{24,12,3,-10,44,18,7,-12,64}
actor22CSDF :: [((Int, Int), (Int, Int), [a] -> [b] -> ([c], [d]))] -> Signal a -> Signal b -> (Signal c, Signal d) Source #
The process constructor actor22CSDF
constructs an CSDF actor with
two input and two output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
>>>
let c1 = ((2,1), (0,1), \[a,b] [c] -> ([], [a+b+c]))
>>>
let c2 = ((1,3), (2,3), \[a] [b,c,d] -> ([a,b], [b, c, d]))
>>>
actor22CSDF [c1,c2] (signal [1..10]) (signal [11..20])
({3,12,6,16},{14,12,13,14,24,16,17,18,34})
actor23CSDF :: [((Int, Int), (Int, Int, Int), [a] -> [b] -> ([c], [d], [e]))] -> Signal a -> Signal b -> (Signal c, Signal d, Signal e) Source #
The process constructor actor23CSDF
constructs an CSDF actor with
two input and three output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
actor24CSDF :: [((Int, Int), (Int, Int, Int, Int), [a] -> [b] -> ([c], [d], [e], [f]))] -> Signal a -> Signal b -> (Signal c, Signal d, Signal e, Signal f) Source #
The process constructor actor24CSDF
constructs an CSDF actor with
two input and four output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
actor31CSDF :: [((Int, Int, Int), Int, [a] -> [b] -> [c] -> [d])] -> Signal a -> Signal b -> Signal c -> Signal d Source #
The process constructor actor31CSDF
constructs an CSDF actor with
three input and one output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
actor32CSDF :: [((Int, Int, Int), (Int, Int), [a] -> [b] -> [c] -> ([d], [e]))] -> Signal a -> Signal b -> Signal c -> (Signal d, Signal e) Source #
The process constructor actor32CSDF
constructs an CSDF actor with
three input and two output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
actor33CSDF :: [((Int, Int, Int), (Int, Int, Int), [a] -> [b] -> [c] -> ([d], [e], [f]))] -> Signal a -> Signal b -> Signal c -> (Signal d, Signal e, Signal f) Source #
The process constructor actor33CSDF
constructs an CSDF actor with
three input and three output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
actor34CSDF :: [((Int, Int, Int), (Int, Int, Int, Int), [a] -> [b] -> [c] -> ([d], [e], [f], [g]))] -> Signal a -> Signal b -> Signal c -> (Signal d, Signal e, Signal f, Signal g) Source #
The process constructor actor34CSDF
constructs an CSDF actor with
three input and four output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
>>>
let c1 = ((1,0,1), (1,1,3,0), \[a] _ [b] -> ([b], [succ b], [a, 2*a, 3*a], []))
>>>
let c2 = ((2,1,1), (0,2,1,1), \[a,b] [c] [d] -> ([], [d, succ d], [a+b], [c]))
>>>
actor34CSDF [c1,c2] (signal [1..10]) (signal [11..20]) (signal ['a'..'k'])
({'a','c','e','g'},{'b','b','c','d','d','e','f','f','g','h'},{1,2,3,5,4,8,12,11,7,14,21,17,10,20,30},{11,12,13})
actor41CSDF :: [((Int, Int, Int, Int), Int, [a] -> [b] -> [c] -> [d] -> [e])] -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e Source #
The process constructor actor41CSDF
constructs an CSDF actor with
four input and one output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
actor42CSDF :: [((Int, Int, Int, Int), (Int, Int), [a] -> [b] -> [c] -> [d] -> ([e], [f]))] -> Signal a -> Signal b -> Signal c -> Signal d -> (Signal e, Signal f) Source #
The process constructor actor42CSDF
constructs an CSDF actor with
four input and two output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
actor43CSDF :: [((Int, Int, Int, Int), (Int, Int, Int), [a] -> [b] -> [c] -> [d] -> ([e], [f], [g]))] -> Signal a -> Signal b -> Signal c -> Signal d -> (Signal e, Signal f, Signal g) Source #
The process constructor actor43CSDF
constructs an CSDF actor with
four input and three output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.
actor44CSDF :: [((Int, Int, Int, Int), (Int, Int, Int, Int), [a] -> [b] -> [c] -> [d] -> ([e], [f], [g], [h]))] -> Signal a -> Signal b -> Signal c -> Signal d -> (Signal e, Signal f, Signal g, Signal h) Source #
The process constructor actor44CSDF
constructs an CSDF actor with
four input and four output signals. For each firing, the actor behaves
accordingly to the scenario (a tuple with the number of consumed tokens,
produced tokens and the function) defined in the list of tuples, given as
argument, in a cyclic fashion. The length of the list of scenarios gives the
actor's cycle period.