Copyright | (c) SAM/KTH 2007 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | forsyde-dev@ict.kth.se |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
The synchronuous library defines process constructors and processes for the synchronous computational model. A process constructor is a higher order function which together with combinational function(s) and values as arguments constructs a process.
Synopsis
- mapSY :: (a -> b) -> Signal a -> Signal b
- zipWithSY :: (a -> b -> c) -> Signal a -> Signal b -> Signal c
- zipWith3SY :: (a -> b -> c -> d) -> Signal a -> Signal b -> Signal c -> Signal d
- zipWith4SY :: (a -> b -> c -> d -> e) -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e
- mapxSY :: (a -> b) -> Vector (Signal a) -> Vector (Signal b)
- zipWithxSY :: (Vector a -> b) -> Vector (Signal a) -> Signal b
- combSY :: (a -> b) -> Signal a -> Signal b
- comb2SY :: (a -> b -> c) -> Signal a -> Signal b -> Signal c
- comb3SY :: (a -> b -> c -> d) -> Signal a -> Signal b -> Signal c -> Signal d
- comb4SY :: (a -> b -> c -> d -> e) -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e
- delaySY :: a -> Signal a -> Signal a
- delaynSY :: a -> Int -> Signal a -> Signal a
- scanlSY :: (a -> b -> a) -> a -> Signal b -> Signal a
- scanl2SY :: (a -> b -> c -> a) -> a -> Signal b -> Signal c -> Signal a
- scanl3SY :: (a -> b -> c -> d -> a) -> a -> Signal b -> Signal c -> Signal d -> Signal a
- scanldSY :: (a -> b -> a) -> a -> Signal b -> Signal a
- scanld2SY :: (a -> b -> c -> a) -> a -> Signal b -> Signal c -> Signal a
- scanld3SY :: (a -> b -> c -> d -> a) -> a -> Signal b -> Signal c -> Signal d -> Signal a
- mooreSY :: (a -> b -> a) -> (a -> c) -> a -> Signal b -> Signal c
- moore2SY :: (a -> b -> c -> a) -> (a -> d) -> a -> Signal b -> Signal c -> Signal d
- moore3SY :: (a -> b -> c -> d -> a) -> (a -> e) -> a -> Signal b -> Signal c -> Signal d -> Signal e
- mealySY :: (a -> b -> a) -> (a -> b -> c) -> a -> Signal b -> Signal c
- mealy2SY :: (a -> b -> c -> a) -> (a -> b -> c -> d) -> a -> Signal b -> Signal c -> Signal d
- mealy3SY :: (a -> b -> c -> d -> a) -> (a -> b -> c -> d -> e) -> a -> Signal b -> Signal c -> Signal d -> Signal e
- sourceSY :: (a -> a) -> a -> Signal a
- filterSY :: (a -> Bool) -> Signal a -> Signal (AbstExt a)
- fillSY :: a -> Signal (AbstExt a) -> Signal a
- holdSY :: a -> Signal (AbstExt a) -> Signal a
- whenSY :: Signal (AbstExt a) -> Signal (AbstExt b) -> Signal (AbstExt a)
- zipSY :: Signal a -> Signal b -> Signal (a, b)
- zip3SY :: Signal a -> Signal b -> Signal c -> Signal (a, b, c)
- zip4SY :: Signal a -> Signal b -> Signal c -> Signal d -> Signal (a, b, c, d)
- zip5SY :: Signal a -> Signal b -> Signal c -> Signal d -> Signal e -> Signal (a, b, c, d, e)
- zip6SY :: Signal a -> Signal b -> Signal c -> Signal d -> Signal e -> Signal f -> Signal (a, b, c, d, e, f)
- unzipSY :: Signal (a, b) -> (Signal a, Signal b)
- unzip3SY :: Signal (a, b, c) -> (Signal a, Signal b, Signal c)
- unzip4SY :: Signal (a, b, c, d) -> (Signal a, Signal b, Signal c, Signal d)
- unzip5SY :: Signal (a, b, c, d, e) -> (Signal a, Signal b, Signal c, Signal d, Signal e)
- unzip6SY :: Signal (a, b, c, d, e, f) -> (Signal a, Signal b, Signal c, Signal d, Signal e, Signal f)
- zipxSY :: Vector (Signal a) -> Signal (Vector a)
- unzipxSY :: Signal (Vector a) -> Vector (Signal a)
- fstSY :: Signal (a, b) -> Signal a
- sndSY :: Signal (a, b) -> Signal b
- module ForSyDe.Shallow.MoC.Synchronous.Process
- module ForSyDe.Shallow.MoC.Synchronous.Stochastic
The Core Library
Combinational process constructors
Combinational process constructors are used for processes that do not have a state.
mapSY :: (a -> b) -> Signal a -> Signal b Source #
The process constructor mapSY
takes a combinational function as
argument and returns a process with one input signal and one output
signal.
>>>
mapSY (+1) $ signal [1,2,3,4]
{2,3,4,5}
zipWithSY :: (a -> b -> c) -> Signal a -> Signal b -> Signal c Source #
The process constructor zipWithSY
takes a combinational
function as argument and returns a process with two input signals
and one output signal.
>>>
zipWithSY (+) (signal [1,2,3,4]) (signal [11,12,13,14,15,16,17])
{12,14,16,18}
zipWith3SY :: (a -> b -> c -> d) -> Signal a -> Signal b -> Signal c -> Signal d Source #
The process constructor zipWith3SY
takes a combinational
function as argument and returns a process with three input signals
and one output signal.
zipWith4SY :: (a -> b -> c -> d -> e) -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e Source #
The process constructor zipWith4SY
takes a combinational
function as argument and returns a process with four input signals
and one output signal.
mapxSY :: (a -> b) -> Vector (Signal a) -> Vector (Signal b) Source #
The process constructor mapxSY
creates a process network that
maps a function onto all signals in a vector of signals. See mapV
.
>>>
let s1 = signal [1,2,3,4]
>>>
let s2 = signal [10,20,30,40]
>>>
let s3 = signal [100,200,300]
>>>
mapxSY (+1) $ vector [s1,s2,s3]
<{2,3,4,5},{11,21,31,41},{101,201,301}>
zipWithxSY :: (Vector a -> b) -> Vector (Signal a) -> Signal b Source #
The process constructor zipWithxSY
works as zipWithSY
, but
takes a vector of signals as input.
>>>
let s1 = signal [1,2,3,4]
>>>
let s2 = signal [10,20,30,40]
>>>
let s3 = signal [100,200,300]
>>>
zipWithxSY (reduceV (+)) $ vector [s1,s2,s3]
{111,222,333}
comb3SY :: (a -> b -> c -> d) -> Signal a -> Signal b -> Signal c -> Signal d Source #
The process constructor comb3SY
is an alias to zipWith3SY
and
behaves exactly in the same way.
comb4SY :: (a -> b -> c -> d -> e) -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e Source #
The process constructor comb4SY
is an alias to zipWith4SY
and
behaves exactly in the same way.
Sequential process constructors
Sequential process constructors are used for processes that have a state. One of the input parameters is the initial state.
The process constructor delaySY
delays the signal one event
cycle by introducing an initial value at the beginning of the
output signal. Note, that this implies that there is one event
(the first) at the output signal that has no corresponding event at
the input signal. One could argue that input and output signals
are not fully synchronized, even though all input events are
synchronous with a corresponding output event. However, this is
necessary to initialize feed-back loops.
>>>
delaySY 1 $ signal [1,2,3,4]
{1,1,2,3,4}
The process constructor delaynSY
delays the signal n events by
introducing n identical default values.
>>>
delaynSY 0 3 $ signal [1,2,3,4]
{0,0,0,1,2,3,4}
:: (a -> b -> a) | Combinational function for next state decoder |
-> a | Initial state |
-> Signal b | Input signal |
-> Signal a | Output signal |
The process constructor scanlSY
is used to construct a finite
state machine process without output decoder. It takes an initial
value and a function for the next state decoder. The process
constructor behaves similar to the Haskell prelude function
scanlSY
and has the value of the new state as its output value as
illustrated by the following example.
>>>
scanlSY (+) 0 (signal [1,2,3,4])
{1,3,6,10}
This is in contrast to the function scanldSY
, which has its
current state as its output value.
:: (a -> b -> a) | Combinational function for next state decoder |
-> a | Initial state |
-> Signal b | Input signal |
-> Signal a | Output signal |
The process constructor scanldSY
is used to construct a finite
state machine process without output decoder. It takes an initial
value and a function for the next state decoder. The process
constructor behaves similar to the Haskell prelude function
scanlSY
. In contrast to the process constructor scanlSY
here
the output value is the current state and not the one of the next
state.
>>>
scanldSY (+) 0 (signal [1,2,3,4])
{0,1,3,6,10}
:: (a -> b -> a) | Combinational function for next state decoder |
-> (a -> c) | Combinational function for output decoder |
-> a | Initial state |
-> Signal b | Input signal |
-> Signal c | Output signal |
The process constructor mooreSY
is used to model state machines
of "Moore" type, where the output only depends on the current
state. The process constructor is based on the process constructor
scanldSY
, since it is natural for state machines in hardware,
that the output operates on the current state and not on the next
state. The process constructors takes a function to calculate the
next state, another function to calculate the output and a value
for the initial state.
In contrast the output of a process created by the process constructor mealySY
depends not only on the state, but also on the input values.
>>>
mooreSY (+) (*2) 0 $ signal [1,2,3,4,5]
{0,2,6,12,20,30}
moore3SY :: (a -> b -> c -> d -> a) -> (a -> e) -> a -> Signal b -> Signal c -> Signal d -> Signal e Source #
:: (a -> b -> a) | Combinational function for next state decoder |
-> (a -> b -> c) | Combinational function for output decoder |
-> a | Initial state |
-> Signal b | Input signal |
-> Signal c | Output signal |
The process constructor melaySY
is used to model state machines
of "Mealy" type, where the output only depends on the current
state and the input values. The process constructor is based on the
process constructor scanldSY
, since it is natural for state
machines in hardware, that the output operates on the current state
and not on the next state. The process constructors takes a
function to calculate the next state, another function to calculate
the output and a value for the initial state.
In contrast the output of a process created by the process
constructor mooreSY
depends only on the state, but not on the
input values.
>>>
mealySY (+) (+) 0 $ signal [1,2,3,4,5]
{1,3,6,10,15}
mealy2SY :: (a -> b -> c -> a) -> (a -> b -> c -> d) -> a -> Signal b -> Signal c -> Signal d Source #
mealy3SY :: (a -> b -> c -> d -> a) -> (a -> b -> c -> d -> e) -> a -> Signal b -> Signal c -> Signal d -> Signal e Source #
sourceSY :: (a -> a) -> a -> Signal a Source #
The process sourceSY
takes a function and an initial state and
generates an infinite signal starting with the initial state as
first output followed by the recursive application of the function
on the current state. The state also serves as output value.
The process that has the infinite signal of natural numbers as output is constructed by
>>>
takeS 5 $ sourceSY (+1) 0
{0,1,2,3,4}
The process constructor filterSY
discards the values who do not
fulfill a predicate given by a predicate function and replaces them
with absent events.
The process constructor holdSY
creates a process that fills
a signal with values by replacing absent values by the preceding present value. Only in cases, where no preceding value exists, the absent value is replaced by a default value. The output signal is not any more of the type AbstExt
.
>>>
let s = signal [Abst, Prst 1, Prst 2, Abst, Abst, Prst 4, Abst]
>>>
holdSY 3 s
{3,1,2,2,2,4,4}
Synchronous Processes
The library contains a few simple processes that are applicable to many cases.
whenSY :: Signal (AbstExt a) -> Signal (AbstExt b) -> Signal (AbstExt a) Source #
The process constructor whenSY
creates a process that
synchronizes a signal of absent extended values with another signal
of absent extended values. The output signal has the value of the
first signal whenever an event has a present value and Abst
when
the event has an absent value.
>>>
let clk = signal [Abst, Prst (), Prst (), Abst, Abst, Prst (), Abst]
>>>
let sig = signal [Prst 10, Prst 11, Prst 12, Prst 13, Prst 14, Prst 15]
>>>
sig `whenSY` clk
{_,11,12,_,_,15}
zipSY :: Signal a -> Signal b -> Signal (a, b) Source #
The process zipSY
"zips" two incoming signals into one signal
of tuples.
>>>
zipSY (signal [1,2,3,4]) (signal [10,11,12,13,14])
{(1,10),(2,11),(3,12),(4,13)}
zip5SY :: Signal a -> Signal b -> Signal c -> Signal d -> Signal e -> Signal (a, b, c, d, e) Source #
zip6SY :: Signal a -> Signal b -> Signal c -> Signal d -> Signal e -> Signal f -> Signal (a, b, c, d, e, f) Source #
unzipSY :: Signal (a, b) -> (Signal a, Signal b) Source #
The process unzipSY
"unzips" a signal of tuples into two
signals.
unzip6SY :: Signal (a, b, c, d, e, f) -> (Signal a, Signal b, Signal c, Signal d, Signal e, Signal f) Source #
zipxSY :: Vector (Signal a) -> Signal (Vector a) Source #
The process zipxSY
transposes a signal of vectors into a vector
of signals. All the events carried by the output signal are synchronized values from all input signals.
>>>
let s1 = signal [1,2,3,4]
>>>
let s2 = signal [10,20,30,40]
>>>
let s3 = signal [100,200,300]
>>>
zipxSY $ vector [s1,s2,s3]
{<1,10,100>,<2,20,200>,<3,30,300>}
unzipxSY :: Signal (Vector a) -> Vector (Signal a) Source #
The process unzipxSY
"unzips" a vector of signals into a
signal of vectors.
fstSY :: Signal (a, b) -> Signal a Source #
The process fstSY
selects always the first value from a signal
of pairs.
sndSY :: Signal (a, b) -> Signal b Source #
The process sndSY
selects always the second value from a signal
of pairs.
Add-ons
Utility Processes
Collection of process constructors commonly used in designs.
Stochastic Processes
Library of stochastic process constructors