Copyright | (C) 2019 Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class NFDataX a => AutoReg a where
- autoReg :: (HasCallStack, KnownDomain dom) => Clock dom -> Reset dom -> Enable dom -> a -> Signal dom a -> Signal dom a
- deriveAutoReg :: Name -> DecsQ
Documentation
class NFDataX a => AutoReg a where Source #
autoReg
is a "smart" version of register
. It does two things:
- It splits product types over their fields. For example, given a 3-tuple, the corresponding HDL will end up with three instances of a register (or more if the three fields can be split up similarly).
- Given a data type where a constructor indicates (parts) of the data will (not) be updated a given cycle, it will split the data in two parts. The first part will contain the "always interesting" parts (the constructor bits). The second holds the "potentially uninteresting" data (the rest). Both parts will be stored in separate registers. The register holding the "potentially uninteresting" part will only be enabled if the constructor bits indicate they're interesting.
The most important example of this is Maybe
. Consider Maybe (Signed 16)
;
when viewed as bits, a Nothing
would look like:
>>>
pack @(Maybe (Signed 16)) Nothing
0_...._...._...._....
and Just
>>>
pack @(Maybe (Signed 16)) (Just 3)
1_0000_0000_0000_0011
In the first case, Nothing, we don't particularly care about updating the
register holding the Signed 16
field, as they'll be unknown anyway. We
can therefore deassert its enable line.
Making Clash lay it out like this increases the chances of synthesis tools clock gating the registers, saving energy.
This version of autoReg
will split the given data type up recursively. For
example, given a :: Maybe (Maybe Int, Maybe Int)
, a total of five registers
will be rendered. Both the "interesting" and "uninteresting" enable lines of
the inner Maybe types will be controlled by the outer one, in addition to
the inner parts controlling their "uninteresting" parts as described in (2).
The default implementation is just register
. If you don't need or want
the special features of AutoReg, you can use that by writing an empty instance.
data MyDataType = ... instance AutoReg MyDataType
If you have a product type you can use deriveAutoReg
to derive an instance.
Nothing
:: (HasCallStack, KnownDomain dom) | |
=> Clock dom | |
-> Reset dom | |
-> Enable dom | |
-> a | Reset value |
-> Signal dom a | |
-> Signal dom a |
For documentation see class AutoReg
.
This is version with explicit clockresetenable,
Clash.Prelude exports an implicit version of this: autoReg
Instances
deriveAutoReg :: Name -> DecsQ Source #
Automatically derives an AutoReg
instance for a product type
Usage:
data Pair a b = MkPair { getA :: a, getB :: b } deriving (Generic, NFDataX) data Tup3 a b c = MkTup3 { getAB :: Pair a b, getC :: c } deriving (Generic, NFDataX) deriveAutoReg ''Pair deriveAutoReg ''Tup3
NB: Because of the way template haskell works the order here matters,
if you try to deriveAutoReg ''Tup3
before Pair
it will complain
about missing an instance AutoReg (Pair a b)
.