{-# LANGUAGE Safe #-}
module Clash.Explicit.Moore
(
moore
, mooreB
, medvedev
, medvedevB
)
where
import Clash.Explicit.Signal
(KnownDomain, Bundle (..), Clock, Reset, Signal, Enable, register)
import Clash.XException (NFDataX)
moore
:: ( KnownDomain dom
, NFDataX s )
=> Clock dom
-> Reset dom
-> Enable dom
-> (s -> i -> s)
-> (s -> o)
-> s
-> (Signal dom i -> Signal dom o)
moore :: Clock dom
-> Reset dom
-> Enable dom
-> (s -> i -> s)
-> (s -> o)
-> s
-> Signal dom i
-> Signal dom o
moore Clock dom
clk Reset dom
rst Enable dom
en s -> i -> s
ft s -> o
fo s
iS =
\Signal dom i
i -> let s' :: Signal dom s
s' = s -> i -> s
ft (s -> i -> s) -> Signal dom s -> Signal dom (i -> s)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom s
s Signal dom (i -> s) -> Signal dom i -> Signal dom s
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 s -> o
fo (s -> o) -> Signal dom s -> Signal dom o
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Signal dom s
s
{-# INLINABLE moore #-}
medvedev
:: ( KnownDomain dom
, NFDataX s )
=> Clock dom
-> Reset dom
-> Enable dom
-> (s -> i -> s)
-> s
-> (Signal dom i -> Signal dom s)
medvedev :: Clock dom
-> Reset dom
-> Enable dom
-> (s -> i -> s)
-> s
-> Signal dom i
-> Signal dom s
medvedev Clock dom
clk Reset dom
rst Enable dom
en s -> i -> s
tr s
st = Clock dom
-> Reset dom
-> Enable dom
-> (s -> i -> s)
-> (s -> s)
-> s
-> Signal dom i
-> Signal dom s
forall (dom :: Domain) s i o.
(KnownDomain dom, NFDataX s) =>
Clock dom
-> Reset dom
-> Enable dom
-> (s -> i -> s)
-> (s -> o)
-> s
-> Signal dom i
-> Signal dom o
moore Clock dom
clk Reset dom
rst Enable dom
en s -> i -> s
tr s -> s
forall a. a -> a
id s
st
{-# INLINE medvedev #-}
mooreB
:: ( KnownDomain dom
, NFDataX s
, Bundle i
, Bundle o )
=> Clock dom
-> Reset dom
-> Enable dom
-> (s -> i -> s)
-> (s -> o)
-> s
-> (Unbundled dom i -> Unbundled dom o)
mooreB :: Clock dom
-> Reset dom
-> Enable dom
-> (s -> i -> s)
-> (s -> o)
-> s
-> Unbundled dom i
-> Unbundled dom o
mooreB Clock dom
clk Reset dom
rst Enable dom
en s -> i -> s
ft s -> o
fo 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)
-> (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)
-> (s -> o)
-> s
-> Signal dom i
-> Signal dom o
moore Clock dom
clk Reset dom
rst Enable dom
en s -> i -> s
ft s -> o
fo 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 mooreB #-}
medvedevB
:: ( KnownDomain dom
, NFDataX s
, Bundle i
, Bundle s )
=> Clock dom
-> Reset dom
-> Enable dom
-> (s -> i -> s)
-> s
-> (Unbundled dom i -> Unbundled dom s)
medvedevB :: Clock dom
-> Reset dom
-> Enable dom
-> (s -> i -> s)
-> s
-> Unbundled dom i
-> Unbundled dom s
medvedevB Clock dom
clk Reset dom
rst Enable dom
en s -> i -> s
tr s
st = Clock dom
-> Reset dom
-> Enable dom
-> (s -> i -> s)
-> (s -> s)
-> s
-> Unbundled dom i
-> Unbundled dom s
forall (dom :: Domain) s i o.
(KnownDomain dom, NFDataX s, Bundle i, Bundle o) =>
Clock dom
-> Reset dom
-> Enable dom
-> (s -> i -> s)
-> (s -> o)
-> s
-> Unbundled dom i
-> Unbundled dom o
mooreB Clock dom
clk Reset dom
rst Enable dom
en s -> i -> s
tr s -> s
forall a. a -> a
id s
st
{-# INLINE medvedevB #-}