Open gnull opened 7 years ago
Well, window
isn't a primitive of the compiler, so you could write windowEn
yourself:
module Windows where
import CLaSH.Prelude
import Data.Maybe
-- | like `mealy`, but with an enable signal
mealyEn
:: (s -> i -> (s,o)) -- transfer function
-> s -- initial state
-> Signal Bool -- enable
-> Signal i
-> Signal o
mealyEn f iS =
\en i -> let s = regEn iS en s'
(s',o) = unbundle (f <$> s <*> i)
in o
-- | window function in mealy machine form
windowT
:: KnownNat n
=> Vec n a
-> a
-> (Vec n a, Vec (n + 1) a)
windowT prev x = (x +>> prev,x :> prev)
windowEn
:: KnownNat n
=> a -- reset values
-> Signal Bool -- enable
-> Signal a
-> Signal (Vec (n + 1) a)
windowEn rval = mealyEn windowT (repeat rval)
windowMaybe
is not straigforward to write, because, the output depends directly on the input. We can however write a windowDMaybe
: a counterpart to the windowD
function:
-- | like `moore`, but with an enable
mooreEn
:: (s -> i -> s) -- state transfer function
-> (s -> o) -- output function
-> s -- initial state
-> Signal Bool
-> Signal i
-> Signal o
mooreEn ft fo iS =
\en i -> let s' = ft <$> s' <*> i
s = regEn iS en s'
in fo <$> s
-- | like `moore`, but the state is only updated when the input is `Just i`
mooreMaybe
:: (s -> i -> s) -- state transfer function
-> (s -> o) -- output function
-> s -- initial state
-> Signal (Maybe i)
-> Signal o
mooreMaybe ft fo iS =
\iM -> mooreEn ft fo iS (isJust <$> iM) (fromJust <$> iM)
windowDMaybe
:: KnownNat n
=> a -- reset values
-> Signal (Maybe a) -- window only updates when input is `Just a`
-> Signal (Vec (n + 1) a)
windowDMaybe rval =
mooreMaybe (\prev x -> x +>> prev) id (repeat rval)
Now, we can write something like windowMaybe
, but its output would be a Maybe
value aswell:
mealyMaybe
:: (s -> i -> (s,o)) -- transfer function
-> s -- initial state
-> Signal (Maybe i)
-> Signal (Maybe o)
mealyMaybe f iS =
\iM -> let en = isJust <$> iM
in mux en (Just <$> mealyEn f iS en (fromJust <$> iM))
(pure Nothing)
windowMaybe
:: KnownNat n
=> a -- reset values
-> Signal (Maybe a) -- window only updates when input is `Just a`
-> Signal (Maybe (Vec (n + 1) a))
windowMaybe rval = mealyMaybe windowT (repeat rval)
In conclusion: I plan to add at least all the variants of mealy
and moore
to a next iteration of the prelude; and perhaps the versions of window
as well.
@christiaanb, thank you for so detailed reply!
But here is something in your mealyEn
function that seems weird to me. Its output is always present and depends on input without checking whether en
is True
. So if en
is False
, i
may contain any kind of garbage that is populated to o
. And somebody who uses the value of o
on the other end of the wire has no means to determine whether o
is valid, unless we pass to him the same en
that we've passed to mealyEn
. This behavior also differs from the one of mealyMaybe
that sends Nothing
in such case.
An alternative approach to implement mealyEn
could be to return a tuple of o
and ready
Bool
:
mealyEn
:: (s -> i -> (s,o)) -- transfer function
-> s -- initial state
-> Signal Bool -- enable
-> Signal i
-> Signal (o, Bool) -- This Bool is always equal to enable input
This one should behave exactly like mealyMaybe
. But why don't we implement mealyEn
like this as a wrapper around mealyMaybe
to make sure that they behave in the same way?
After seeing an example like this, I don't like the whole idea of using en
signal when we can pass a value of Maybe a
instead. en
signal doesn't guarantee at compile time that the value protected by it is used only when valid. This approach will allow many incorrect programs to compile. It scares me.
Maybe such dangerous library functions shouldn't be provided to a programmer? How do you think?
One of my friends who is a hardware designer starting to learn Clash was disappointed with the fact that Prelude's
window
function doesn't allow him to pass an enable signal to it. Such a signal could be used, for example, to get a window over some selected set of clock cycles by making thewindow
pause for unnecessary clock cycles. According to him, such a feature is frequently used in typical designs.I'm a bit familiar with haskell, and could implement for Prelude a function like:
Or maybe a more haskell-ish style function that encodes the enable signal inside
Maybe
:And also corresponding
windowEn'
andwindowEnD
functions.What do you think about all this? Maybe there is already a function in Prelude that solves this task?