Portability | non-portable (Template Haskell) |
---|---|
Stability | experimental |
Maintainer | [email protected] |
ForSyDe.Process.SynchProc
Description
This module provides the synchronous process constructors of ForSyDe and some useful synchronous processes.
- constSY :: ProcType a => ProcId -> a -> Signal a
- mapSY :: forall a b. (ProcType a, ProcType b) => ProcId -> ProcFun (a -> b) -> Signal a -> Signal b
- zipWithSY :: forall a b c. (ProcType a, ProcType b, ProcType c) => ProcId -> ProcFun (a -> b -> c) -> Signal a -> Signal b -> Signal c
- zipWith3SY :: forall a b c d. (ProcType a, ProcType b, ProcType c, ProcType d) => ProcId -> ProcFun (a -> b -> c -> d) -> Signal a -> Signal b -> Signal c -> Signal d
- zipWith4SY :: forall a b c d e. (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e) => ProcId -> ProcFun (a -> b -> c -> d -> e) -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e
- zipWith5SY :: forall a b c d e f. (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e, ProcType f) => ProcId -> ProcFun (a -> b -> c -> d -> e -> f) -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e -> Signal f
- zipWith6SY :: forall a b c d e f g. (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e, ProcType f, ProcType g) => ProcId -> ProcFun (a -> b -> c -> d -> e -> f -> g) -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e -> Signal f -> Signal g
- zipWithxSY :: forall s a b. (Nat s, Typeable s, ProcType a, ProcType b) => ProcId -> ProcFun (FSVec s a -> b) -> FSVec s (Signal a) -> Signal b
- delaySY :: ProcType a => ProcId -> a -> Signal a -> Signal a
- delaynSY :: ProcType a => ProcId -> a -> Int -> Signal a -> Signal a
- scanlSY :: (ProcType a, ProcType b) => ProcId -> ProcFun (a -> b -> a) -> a -> Signal b -> Signal a
- scanl2SY :: (ProcType a, ProcType b, ProcType c) => ProcId -> ProcFun (a -> b -> c -> a) -> a -> Signal b -> Signal c -> Signal a
- scanl3SY :: (ProcType a, ProcType b, ProcType c, ProcType d) => ProcId -> ProcFun (a -> b -> c -> d -> a) -> a -> Signal b -> Signal c -> Signal d -> Signal a
- scanldSY :: (ProcType a, ProcType b) => ProcId -> ProcFun (a -> b -> a) -> a -> Signal b -> Signal a
- scanld2SY :: (ProcType a, ProcType b, ProcType c) => ProcId -> ProcFun (a -> b -> c -> a) -> a -> Signal b -> Signal c -> Signal a
- scanld3SY :: (ProcType a, ProcType b, ProcType c, ProcType d) => ProcId -> ProcFun (a -> b -> c -> d -> a) -> a -> Signal b -> Signal c -> Signal d -> Signal a
- mooreSY :: (ProcType a, ProcType b, ProcType c) => ProcId -> ProcFun (a -> b -> a) -> ProcFun (a -> c) -> a -> Signal b -> Signal c
- moore2SY :: (ProcType a, ProcType b, ProcType c, ProcType d) => ProcId -> ProcFun (a -> b -> c -> a) -> ProcFun (a -> d) -> a -> Signal b -> Signal c -> Signal d
- moore3SY :: (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e) => ProcId -> ProcFun (a -> b -> c -> d -> a) -> ProcFun (a -> e) -> a -> Signal b -> Signal c -> Signal d -> Signal e
- mealySY :: (ProcType a, ProcType b, ProcType c) => ProcId -> ProcFun (a -> b -> a) -> ProcFun (a -> b -> c) -> a -> Signal b -> Signal c
- mealy2SY :: (ProcType a, ProcType b, ProcType c, ProcType d) => ProcId -> ProcFun (a -> b -> c -> a) -> ProcFun (a -> b -> c -> d) -> a -> Signal b -> Signal c -> Signal d
- mealy3SY :: (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e) => ProcId -> ProcFun (a -> b -> c -> d -> a) -> ProcFun (a -> b -> c -> d -> e) -> a -> Signal b -> Signal c -> Signal d -> Signal e
- sourceSY :: ProcType a => ProcId -> ProcFun (a -> a) -> a -> Signal a
- filterSY :: ProcType a => ProcId -> ProcFun (a -> Bool) -> Signal a -> Signal (AbstExt a)
- fillSY :: ProcType a => ProcId -> a -> Signal (AbstExt a) -> Signal a
- holdSY :: ProcType a => ProcId -> a -> Signal (AbstExt a) -> Signal a
- whenSY :: (ProcType a, ProcType b) => ProcId -> Signal (AbstExt a) -> Signal (AbstExt b) -> Signal (AbstExt a)
- zipSY :: (ProcType a, ProcType b) => ProcId -> Signal a -> Signal b -> Signal (a, b)
- zip3SY :: (ProcType a, ProcType b, ProcType c) => ProcId -> Signal a -> Signal b -> Signal c -> Signal (a, b, c)
- zip4SY :: (ProcType a, ProcType b, ProcType c, ProcType d) => ProcId -> Signal a -> Signal b -> Signal c -> Signal d -> Signal (a, b, c, d)
- zip5SY :: (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e) => ProcId -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e -> Signal (a, b, c, d, e)
- zip6SY :: (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e, ProcType f) => ProcId -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e -> Signal f -> Signal (a, b, c, d, e, f)
- unzipSY :: forall a b. (ProcType a, ProcType b) => ProcId -> Signal (a, b) -> (Signal a, Signal b)
- unzip3SY :: forall a b c. (ProcType a, ProcType b, ProcType c) => ProcId -> Signal (a, b, c) -> (Signal a, Signal b, Signal c)
- unzip4SY :: forall a b c d. (ProcType a, ProcType b, ProcType c, ProcType d) => ProcId -> Signal (a, b, c, d) -> (Signal a, Signal b, Signal c, Signal d)
- unzip5SY :: forall a b c d e. (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e) => ProcId -> Signal (a, b, c, d, e) -> (Signal a, Signal b, Signal c, Signal d, Signal e)
- unzip6SY :: forall a b c d e f. (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e, ProcType f) => ProcId -> Signal (a, b, c, d, e, f) -> (Signal a, Signal b, Signal c, Signal d, Signal e, Signal f)
- zipxSY :: (Nat s, Typeable s, ProcType a) => ProcId -> FSVec s (Signal a) -> Signal (FSVec s a)
- unzipxSY :: forall s a. (Typeable s, Nat s, ProcType a) => ProcId -> Signal (FSVec s a) -> FSVec s (Signal a)
- mapxSY :: (Nat s, ProcType a, ProcType b) => ProcId -> ProcFun (a -> b) -> FSVec s (Signal a) -> FSVec s (Signal b)
- fstSY :: (ProcType a, ProcType b) => ProcId -> Signal (a, b) -> Signal a
- sndSY :: (ProcType a, ProcType b) => ProcId -> Signal (a, b) -> Signal b
- groupSY :: forall k a. (Nat k, Typeable k, ProcType a) => ProcId -> k -> Signal a -> Signal (AbstExt (FSVec k a))
Combinational process constructors
Combinational process constructors are used for processes that do not have a state.
Arguments
:: ProcType a | |
=> ProcId | Identifier of the process |
-> a | Value to output |
-> Signal a | Resulting output signal |
Creates a constant process. A process which outputs the same signal value in every clock cycle.
Arguments
:: forall a b . (ProcType a, ProcType b) | |
=> ProcId | Identifier of the process |
-> ProcFun (a -> b) | Function applied to the input signal in every cycle |
-> Signal a | Input |
-> Signal b | Output |
The process constructor mapSY
takes an identifier and a
combinational function as arguments and returns a process with one
input signal and one output signal.
Arguments
:: forall a b c . (ProcType a, ProcType b, ProcType c) | |
=> ProcId | Identifier of the process |
-> ProcFun (a -> b -> c) | Function applied to the input signals in every cycle |
-> Signal a | First input |
-> Signal b | Second input |
-> Signal c | Output Signal |
The process constructor zipWithSY
takes an identifier and a
combinational function as arguments and returns a process with
two input signals and one output signal.
Arguments
:: forall a b c d . (ProcType a, ProcType b, ProcType c, ProcType d) | |
=> ProcId | Identifier of the process |
-> ProcFun (a -> b -> c -> d) | Function applied to the input signals in every cycle |
-> Signal a | First input |
-> Signal b | Second input |
-> Signal c | Third input |
-> Signal d | Output Signal |
The process constructor zipWith3SY
takes an identifier and a
combinational function as arguments and returns a process with
three input signals and one output signal.
Arguments
:: forall a b c d e . (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e) | |
=> ProcId | Identifier of the process |
-> ProcFun (a -> b -> c -> d -> e) | Function applied to the input signals in every cycle |
-> Signal a | First input |
-> Signal b | Second input |
-> Signal c | Third input |
-> Signal d | Fourth input |
-> Signal e | Output Signal |
The process constructor zipWith4SY
takes an identifier and a
combinational function as arguments and returns a process with
four input signals and one output signal.
Arguments
:: forall a b c d e f . (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e, ProcType f) | |
=> ProcId | Identifier of the process |
-> ProcFun (a -> b -> c -> d -> e -> f) | Function applied to the input signals in every cycle |
-> Signal a | First input |
-> Signal b | Second input |
-> Signal c | Third input |
-> Signal d | Fourth input |
-> Signal e | Fifth input |
-> Signal f | Output Signal |
The process constructor zipWith5SY
takes an identifier and a
combinational function as arguments and returns a process with
five input signals and one output signal.
Arguments
:: forall a b c d e f g . (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e, ProcType f, ProcType g) | |
=> ProcId | Identifier of the process |
-> ProcFun (a -> b -> c -> d -> e -> f -> g) | Function applied to the input signals in every cycle |
-> Signal a | First input |
-> Signal b | Second input |
-> Signal c | Third input |
-> Signal d | Fourth input |
-> Signal e | Fifth input |
-> Signal f | Sixth input |
-> Signal g | Output Signal |
The process constructor zipWith6SY
takes an identifier and a
combinational function as arguments and returns a process with
five input signals and one output signal.
zipWithxSY :: forall s a b. (Nat s, Typeable s, ProcType a, ProcType b) => ProcId -> ProcFun (FSVec s a -> b) -> FSVec s (Signal a) -> Signal bSource
The process constructor zipWithxSY
works as zipWithSY
, but takes a
vector of signals as input.
Sequential process constructors
Sequential process constructors are used for processes that have a state. One of the input parameters is the initial state.
Arguments
:: ProcType a | |
=> ProcId | Identifier of the process |
-> a | Initial value |
-> Signal a |
|
-> Signal a | Resulting delayed |
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.
Arguments
:: (ProcType a, ProcType b) | |
=> ProcId | Process Identifier |
-> ProcFun (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.
This is in contrast to the function scanldSY
, which has its current
state as its output value.
Arguments
:: (ProcType a, ProcType b, ProcType c, ProcType d) | |
=> ProcId | Process Identifier |
-> ProcFun (a -> b -> c -> d -> a) | Combinational function for next state decoder |
-> a | Initial state |
-> Signal b | First Input signal |
-> Signal c | Second Input signal |
-> Signal d | Third Input signal |
-> Signal a | Output signal |
Arguments
:: (ProcType a, ProcType b) | |
=> ProcId | |
-> ProcFun (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
similarly 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.
Arguments
:: (ProcType a, ProcType b, ProcType c) | |
=> ProcId | |
-> ProcFun (a -> b -> a) | Combinational function for next state decoder |
-> ProcFun (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.
Arguments
:: (ProcType a, ProcType b, ProcType c, ProcType d) | |
=> ProcId | |
-> ProcFun (a -> b -> c -> a) | Combinational function for next state decoder |
-> ProcFun (a -> d) | Combinational function for output decoder |
-> a | Initial state |
-> Signal b | First Input signal |
-> Signal c | Second Input signal |
-> Signal d | Output signal |
Arguments
:: (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e) | |
=> ProcId | |
-> ProcFun (a -> b -> c -> d -> a) | Combinational function for next state decoder |
-> ProcFun (a -> e) | Combinational function for output decoder |
-> a | Initial state |
-> Signal b | First Input signal |
-> Signal c | Second Input signal |
-> Signal d | Third Input signal |
-> Signal e | Output signal |
Arguments
:: (ProcType a, ProcType b, ProcType c) | |
=> ProcId | |
-> ProcFun (a -> b -> a) | Combinational function for next state decoder |
-> ProcFun (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.
Arguments
:: (ProcType a, ProcType b, ProcType c, ProcType d) | |
=> ProcId | |
-> ProcFun (a -> b -> c -> a) | Combinational function for next state decoder |
-> ProcFun (a -> b -> c -> d) | Combinational function for output decoder |
-> a | Initial state |
-> Signal b | First Input signal |
-> Signal c | Second Input signal |
-> Signal d | Output signal |
Arguments
:: (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e) | |
=> ProcId | |
-> ProcFun (a -> b -> c -> d -> a) | Combinational function for next state decoder |
-> ProcFun (a -> b -> c -> d -> e) | Combinational function for output decoder |
-> a | Initial state |
-> Signal b | First Input signal |
-> Signal c | Second Input signal |
-> Signal d | Third Input signal |
-> Signal e | Output signal |
sourceSY :: ProcType a => ProcId -> ProcFun (a -> a) -> a -> Signal aSource
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 con structed by
sourceSY "naturals" (+1) 0
Arguments
:: ProcType a | |
=> ProcId | |
-> ProcFun (a -> Bool) | Predicate function |
-> Signal a | Input signal |
-> Signal (AbstExt a) | Output signal |
The process constructor filterSY
discards the values who do not fulfill a predicate given by a predicate function and replaces them with absent events.
Synchronous Processes
The library contains a few simple processes that are applicable to many cases.
whenSY :: (ProcType a, ProcType b) => ProcId -> Signal (AbstExt a) -> Signal (AbstExt b) -> Signal (AbstExt a)Source
zipSY :: (ProcType a, ProcType b) => ProcId -> Signal a -> Signal b -> Signal (a, b)Source
The process zipSY
"zips" two incoming signals into one signal of
tuples.
zip3SY :: (ProcType a, ProcType b, ProcType c) => ProcId -> Signal a -> Signal b -> Signal c -> Signal (a, b, c)Source
zip4SY :: (ProcType a, ProcType b, ProcType c, ProcType d) => ProcId -> Signal a -> Signal b -> Signal c -> Signal d -> Signal (a, b, c, d)Source
zip5SY :: (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e) => ProcId -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e -> Signal (a, b, c, d, e)Source
zip6SY :: (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e, ProcType f) => ProcId -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e -> Signal f -> Signal (a, b, c, d, e, f)Source
unzipSY :: forall a b. (ProcType a, ProcType b) => ProcId -> Signal (a, b) -> (Signal a, Signal b)Source
The process unzipSY
"unzips" a signal of tuples into two signals.
unzip3SY :: forall a b c. (ProcType a, ProcType b, ProcType c) => ProcId -> Signal (a, b, c) -> (Signal a, Signal b, Signal c)Source
The process unzip3SY
"unzips" a signal of tuples into three signals.
unzip4SY :: forall a b c d. (ProcType a, ProcType b, ProcType c, ProcType d) => ProcId -> Signal (a, b, c, d) -> (Signal a, Signal b, Signal c, Signal d)Source
The process unzip4SY
"unzips" a signal of tuples into four signals.
unzip5SY :: forall a b c d e. (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e) => ProcId -> Signal (a, b, c, d, e) -> (Signal a, Signal b, Signal c, Signal d, Signal e)Source
The process unzip5SY
"unzips" a signal of tuples into five signals.
unzip6SY :: forall a b c d e f. (ProcType a, ProcType b, ProcType c, ProcType d, ProcType e, ProcType f) => ProcId -> Signal (a, b, c, d, e, f) -> (Signal a, Signal b, Signal c, Signal d, Signal e, Signal f)Source
The process unzip6SY
"unzips" a signal of tuples into six signals.
zipxSY :: (Nat s, Typeable s, ProcType a) => ProcId -> FSVec s (Signal a) -> Signal (FSVec s a)Source
The process zipxSY
"zips" a signal of vectors into a vector of signals.
unzipxSY :: forall s a. (Typeable s, Nat s, ProcType a) => ProcId -> Signal (FSVec s a) -> FSVec s (Signal a)Source
The process unzipxSY
"unzips" a vector of n signals into a signal of
vectors.
mapxSY :: (Nat s, ProcType a, ProcType b) => ProcId -> ProcFun (a -> b) -> FSVec s (Signal a) -> FSVec s (Signal b)Source
The process constructor mapxSY
creates a process network that maps a
function onto all signals in a vector of signals. The identifier is used
as the identifier prefix of the processes created (a number starting with 1
will be appended to each identifier)
fstSY :: (ProcType a, ProcType b) => ProcId -> Signal (a, b) -> Signal aSource
The process fstSY
selects always the first value from a signal of pairs