Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data MultiSignal n a = MultiSignal {
- unMultiSignal :: Signal (Vec n a)
- class Prependable f where
- type SignalLike f = (Prependable f, Applicative f)
- mealyP :: SignalLike f => (s -> i -> (s, o)) -> s -> f i -> f o
- mooreP :: SignalLike f => (s -> i -> s) -> (s -> o) -> s -> f i -> f o
- windowP :: (KnownNat n, Default a, Prependable f) => f a -> Vec n (f a)
- fromListP :: NFData a => SNat (n + 1) -> [a] -> MultiSignal (n + 1) a
- fromListPI :: (NFData a, KnownNat n) => [a] -> MultiSignal (n + 1) a
- simulateP :: (NFData a, NFData b, KnownNat n) => (MultiSignal (n + 1) a -> MultiSignal (n + 1) b) -> [a] -> [b]
Documentation
data MultiSignal n a Source #
MultiSignal | |
|
Prependable
class Prependable f where Source #
class that can be prepended
- rule
toList (
prepend
a ax) == a : toList ax
Prependable ZipList Source # | |
Prependable (Signal' SystemClock) Source # | |
(KnownNat n, (~) Nat n ((+) m 1)) => Prependable (MultiSignal n) Source # | |
Utility functions
type SignalLike f = (Prependable f, Applicative f) Source #
Constraints synonym
:: SignalLike f | |
=> (s -> i -> (s, o)) | Transfer function in mealy machine form:
|
-> s | Initial state |
-> f i -> f o | Synchronous sequential function with input and output matching that of the mealy machine |
:: SignalLike f | |
=> (s -> i -> s) | Transfer function in moore machine form:
|
-> (s -> o) | Output function in moore machine form:
|
-> s | Initial state |
-> f i -> f o | Synchronous sequential function with input and output matching that of the moore machine |
:: (KnownNat n, Default a, Prependable f) | |
=> f a |
|
-> Vec n (f a) | Vector of signals |
Simulation functions (not synthesisable)
fromListP :: NFData a => SNat (n + 1) -> [a] -> MultiSignal (n + 1) a Source #
convert list to MultiSignal
fromListPI :: (NFData a, KnownNat n) => [a] -> MultiSignal (n + 1) a Source #
convert list to MultiSignal
simulateP :: (NFData a, NFData b, KnownNat n) => (MultiSignal (n + 1) a -> MultiSignal (n + 1) b) -> [a] -> [b] Source #
Simulate a (
)
function given a list of samples of type aMultiSignal
(n + 1) a -> MultiSignal
(n + 1) b