Copyright | (C) 2013-2016 University of Twente 2017 Google Inc. 2019 Myrtle Software Ltd 2023 Alex Mason |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | Safe |
Language | Haskell2010 |
Whereas the output of a Moore machine depends on the previous state, the output of a Mealy machine depends on current transition.
Mealy machines are strictly more expressive, but may impose stricter timing requirements.
Synopsis
- mealy :: (HiddenClockResetEnable dom, NFDataX s) => (s -> i -> (s, o)) -> s -> Signal dom i -> Signal dom o
- mealyS :: (HiddenClockResetEnable dom, NFDataX s) => (i -> State s o) -> s -> Signal dom i -> Signal dom o
- mealyB :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (s -> i -> (s, o)) -> s -> Unbundled dom i -> Unbundled dom o
- mealySB :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (i -> State s o) -> s -> Unbundled dom i -> Unbundled dom o
- (<^>) :: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) => (s -> i -> (s, o)) -> s -> Unbundled dom i -> Unbundled dom o
Mealy machine synchronized to the system clock
:: (HiddenClockResetEnable dom, NFDataX s) | |
=> (s -> i -> (s, o)) | Transfer function in mealy machine form: |
-> s | Initial state |
-> Signal dom i -> Signal dom o | Synchronous sequential function with input and output matching that of the mealy machine |
Create a synchronous function from a combinational function describing a mealy machine
macT :: Int -- Current state -> (Int,Int) -- Input -> (Int,Int) -- (Updated state, output) macT s (x,y) = (s',s) where s' = x * y + s mac :: HiddenClockResetEnable dom =>Signal
dom (Int, Int) ->Signal
dom Int mac =mealy
macT 0
>>>
simulate @System mac [(0,0),(1,1),(2,2),(3,3),(4,4)]
[0,0,1,5,14... ...
Synchronous sequential functions can be composed just like their combinational counterpart:
dualMac :: HiddenClockResetEnable dom => (Signal
dom Int,Signal
dom Int) -> (Signal
dom Int,Signal
dom Int) ->Signal
dom Int dualMac (a,b) (x,y) = s1 + s2 where s1 =mealy
macT 0 (bundle
(a,x)) s2 =mealy
macT 0 (bundle
(b,y))
:: (HiddenClockResetEnable dom, NFDataX s) | |
=> (i -> State s o) | |
-> s | Initial state |
-> Signal dom i -> Signal dom o | Synchronous sequential function with input and output matching that of the mealy machine |
Create a synchronous function from a combinational function describing a mealy machine using the state monad. This can be particularly useful when combined with lenses or optics to replicate imperative algorithms.
data DelayState = DelayState { _history :: Vec 4 Int , _untilValid :: Index 4 } deriving (Generic, NFDataX) makeLenses ''DelayState initialDelayState = DelayState (repeat 0) maxBound delayS :: Int -> State DelayState (Maybe Int) delayS n = do history %= (n +>>) remaining <- use untilValid if remaining > 0 then do untilValid -= 1 return Nothing else do out <- uses history last return (Just out) delayTop :: HiddenClockResetEnable dom =>Signal
dom Int ->Signal
dom (Maybe Int) delayTop =mealyS
delayS initialDelayState
>>>
L.take 7 $ simulate @System delayTop [1,2,3,4,5,6,7,8]
[Nothing,Nothing,Nothing,Just 1,Just 2,Just 3,Just 4] ...
:: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) | |
=> (s -> i -> (s, o)) | Transfer function in mealy machine form: |
-> s | Initial state |
-> Unbundled dom i -> Unbundled dom o | Synchronous sequential function with input and output matching that of the mealy machine |
A version of mealy
that does automatic Bundle
ing
Given a function f
of type:
f :: Int -> (Bool, Int) -> (Int, (Int, Bool))
When we want to make compositions of f
in g
using mealy
, we have to
write:
g a b c = (b1,b2,i2) where (i1,b1) =unbundle
(mealy
f 0 (bundle
(a,b))) (i2,b2) =unbundle
(mealy
f 3 (bundle
(c,i1)))
Using mealyB
however we can write:
g a b c = (b1,b2,i2) where (i1,b1) =mealyB
f 0 (a,b) (i2,b2) =mealyB
f 3 (c,i1)
:: (HiddenClockResetEnable dom, NFDataX s, Bundle i, Bundle o) | |
=> (s -> i -> (s, o)) | Transfer function in mealy machine form: |
-> s | Initial state |
-> Unbundled dom i -> Unbundled dom o | Synchronous sequential function with input and output matching that of the mealy machine |
Infix version of mealyB