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 :: (KnownDomain dom, NFDataX s) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> (s, o)) -> s -> Signal dom i -> Signal dom o
- mealyS :: (KnownDomain dom, NFDataX s) => Clock dom -> Reset dom -> Enable dom -> (i -> State s o) -> s -> Signal dom i -> Signal dom o
- mealyB :: (KnownDomain dom, NFDataX s, Bundle i, Bundle o) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> (s, o)) -> s -> Unbundled dom i -> Unbundled dom o
- mealySB :: (KnownDomain dom, NFDataX s, Bundle i, Bundle o) => Clock dom -> Reset dom -> Enable dom -> (i -> State s o) -> s -> Unbundled dom i -> Unbundled dom o
Mealy machines with explicit clock and reset ports
:: (KnownDomain dom, NFDataX s) | |
=> Clock dom |
|
-> Reset dom | |
-> Enable dom | Global enable |
-> (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
import qualified Data.List as L macT :: Int -- Current state -> (Int,Int) -- Input -> (Int,Int) -- (Updated state, output) macT s (x,y) = (s',s) where s' = x * y + s mac ::KnownDomain
dom =>Clock
dom ->Reset
dom ->Enable
dom ->Signal
dom (Int, Int) ->Signal
dom Int mac clk rst en =mealy
clk rst en macT 0
>>>
simulate (mac systemClockGen systemResetGen enableGen) [(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 ::KnownDomain
dom =>Clock
dom ->Reset
dom ->Enable
dom -> (Signal
dom Int,Signal
dom Int) -> (Signal
dom Int,Signal
dom Int) ->Signal
dom Int dualMac clk rst en (a,b) (x,y) = s1 + s2 where s1 =mealy
clk rst en macT 0 (bundle
(a,x)) s2 =mealy
clk rst en macT 0 (bundle
(b,y))
:: (KnownDomain dom, NFDataX s) | |
=> Clock dom |
|
-> Reset dom | |
-> Enable dom | Global enable |
-> (i -> State s o) | Transfer function in mealy machine handling inputs using |
-> 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 ::KnownDomain
dom =>Clock
dom ->Reset
dom ->Enable
dom -> (Signal
dom Int ->Signal
dom (Maybe Int)) delayTop clk rst en =mealyS
clk rst en delayS initialDelayState
>>>
L.take 7 $ simulate (delayTop systemClockGen systemResetGen enableGen) [-100,1,2,3,4,5,6,7,8]
[Nothing,Nothing,Nothing,Nothing,Just 1,Just 2,Just 3]
:: (KnownDomain dom, NFDataX s, Bundle i, Bundle o) | |
=> Clock dom | |
-> Reset dom | |
-> Enable dom | |
-> (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 clk rst en a b c = (b1,b2,i2) where (i1,b1) =unbundle
(mealy clk rst en f 0 (bundle
(a,b))) (i2,b2) =unbundle
(mealy clk rst en f 3 (bundle
(c,i1)))
Using mealyB
however we can write:
g clk rst en a b c = (b1,b2,i2) where (i1,b1) =mealyB
clk rst en f 0 (a,b) (i2,b2) =mealyB
clk rst en f 3 (c,i1)
:: (KnownDomain dom, NFDataX s, Bundle i, Bundle o) | |
=> Clock dom | |
-> Reset dom | |
-> Enable dom | |
-> (i -> State s o) | Transfer function in mealy machine handling inputs using |
-> s | Initial state |
-> Unbundled dom i -> Unbundled dom o | Synchronous sequential function with input and output matching that of the mealy machine |