{-| Copyright : (C) 2013-2016, University of Twente, 2017 , Google Inc. 2019 , Myrtle Software Ltd License : BSD2 (see the file LICENSE) Maintainer : Christiaan Baaij <christiaan.baaij@gmail.com> 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. -} {-# LANGUAGE Safe #-} module Clash.Explicit.Mealy ( -- * Mealy machines with explicit clock and reset ports mealy , mealyB ) where import Clash.Explicit.Signal (KnownDomain, Bundle (..), Clock, Reset, Signal, Enable, register) import Clash.XException (NFDataX) {- $setup >>> :set -XDataKinds -XTypeApplications >>> import Clash.Explicit.Prelude >>> import qualified Data.List as L >>> :{ let macT s (x,y) = (s',s) where s' = x * y + s :} >>> let mac clk rst en = mealy clk rst en macT 0 -} -- | 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)) -- @ mealy :: ( KnownDomain dom , NFDataX s ) => Clock dom -- ^ 'Clock' to synchronize to -> Reset dom -> Enable dom -- ^ Global enable -> (s -> i -> (s,o)) -- ^ Transfer function in mealy machine form: @state -> input -> (newstate,output)@ -> s -- ^ Initial state -> (Signal dom i -> Signal dom o) -- ^ Synchronous sequential function with input and output matching that -- of the mealy machine mealy :: Clock dom -> Reset dom -> Enable dom -> (s -> i -> (s, o)) -> s -> Signal dom i -> Signal dom o mealy Clock dom clk Reset dom rst Enable dom en s -> i -> (s, o) f s iS = \Signal dom i i -> let (Signal dom s s',Signal dom o o) = Signal dom (s, o) -> Unbundled dom (s, o) forall a (dom :: Domain). Bundle a => Signal dom a -> Unbundled dom a unbundle (Signal dom (s, o) -> Unbundled dom (s, o)) -> Signal dom (s, o) -> Unbundled dom (s, o) forall a b. (a -> b) -> a -> b $ s -> i -> (s, o) f (s -> i -> (s, o)) -> Signal dom s -> Signal dom (i -> (s, o)) forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b <$> Signal dom s s Signal dom (i -> (s, o)) -> Signal dom i -> Signal dom (s, o) forall (f :: Type -> Type) a b. Applicative f => f (a -> b) -> f a -> f b <*> Signal dom i i s :: Signal dom s s = Clock dom -> Reset dom -> Enable dom -> s -> Signal dom s -> Signal dom s forall (dom :: Domain) a. (KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> Signal dom a -> Signal dom a register Clock dom clk Reset dom rst Enable dom en s iS Signal dom s s' in Signal dom o o {-# INLINABLE mealy #-} -- | 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) -- @ mealyB :: ( KnownDomain dom , NFDataX s , Bundle i , Bundle o ) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> (s,o)) -- ^ Transfer function in mealy machine form: @state -> input -> (newstate,output)@ -> s -- ^ Initial state -> (Unbundled dom i -> Unbundled dom o) -- ^ Synchronous sequential function with input and output matching that -- of the mealy machine mealyB :: Clock dom -> Reset dom -> Enable dom -> (s -> i -> (s, o)) -> s -> Unbundled dom i -> Unbundled dom o mealyB Clock dom clk Reset dom rst Enable dom en s -> i -> (s, o) f s iS Unbundled dom i i = Signal dom o -> Unbundled dom o forall a (dom :: Domain). Bundle a => Signal dom a -> Unbundled dom a unbundle (Clock dom -> Reset dom -> Enable dom -> (s -> i -> (s, o)) -> s -> Signal dom i -> Signal dom o forall (dom :: Domain) s i o. (KnownDomain dom, NFDataX s) => Clock dom -> Reset dom -> Enable dom -> (s -> i -> (s, o)) -> s -> Signal dom i -> Signal dom o mealy Clock dom clk Reset dom rst Enable dom en s -> i -> (s, o) f s iS (Unbundled dom i -> Signal dom i forall a (dom :: Domain). Bundle a => Unbundled dom a -> Signal dom a bundle Unbundled dom i i)) {-# INLINE mealyB #-}