Copyright | (C) 2013-2016 University of Twente 2017-2019 Myrtle Software Ltd Google Inc. 2019 QBayLogic B.V. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Extensions |
|
The Product/Signal isomorphism
Synopsis
- class Bundle a where
- data EmptyTuple = EmptyTuple
- data TaggedEmptyTuple (dom :: Domain) = TaggedEmptyTuple
- vecBundle# :: Vec n (Signal t a) -> Signal t (Vec n a)
Documentation
Isomorphism between a Signal
of a product type (e.g. a tuple) and a
product type of Signal
s.
Instances of Bundle
must satisfy the following laws:
bundle
.unbundle
=id
unbundle
.bundle
=id
By default, bundle
and unbundle
, are defined as the identity, that is,
writing:
data D = A | B instance Bundle D
is the same as:
data D = A | B instance Bundle D where typeUnbundled
clk D =Signal
clk Dbundle
s = sunbundle
s = s
For custom product types you'll have to write the instance manually: @ data Pair a b = MkPair { getA :: a, getB :: b }
instance Bundle (Pair a b) where type Unbundled dom (Pair a b) = Pair (Signal dom a) (Signal dom b)
Nothing
bundle :: Unbundled dom a -> Signal dom a Source #
Example:
bundle :: (Signal
dom a,Signal
dom b) ->Signal
dom (a,b)
However:
bundle ::Signal
domBit
->Signal
domBit
Instances
Bundle Bool Source # | |
Bundle Double Source # | |
Bundle Float Source # | |
Bundle Int Source # | |
Bundle Integer Source # | |
Bundle () Source # | |
Bundle Bit Source # | |
Bundle EmptyTuple Source # | See https://github.com/clash-lang/clash-compiler/pull/539/commits/94b0bff5770aa4961e04ddce2515130df3fc7863 and documentation for TaggedEmptyTuple. |
Defined in Clash.Signal.Bundle type Unbundled dom EmptyTuple = (res :: Type) Source # bundle :: forall (dom :: Domain). Unbundled dom EmptyTuple -> Signal dom EmptyTuple Source # unbundle :: forall (dom :: Domain). Signal dom EmptyTuple -> Unbundled dom EmptyTuple Source # | |
Bundle (Maybe a) Source # | |
Bundle (BitVector n) Source # | |
Bundle (Index n) Source # | |
Bundle (Unsigned n) Source # | |
Bundle (Signed n) Source # | |
Bundle (Either a b) Source # | |
Bundle (a1, a2) Source # | |
KnownNat n => Bundle (Vec n a) Source # | |
KnownNat d => Bundle (RTree d a) Source # | |
Bundle (a1, a2, a3) Source # | |
Bundle (Fixed rep int frac) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle ((f :*: g) a) Source # | |
Bundle (a1, a2, a3, a4) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle (a1, a2, a3, a4, a5) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle (a1, a2, a3, a4, a5, a6) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle (a1, a2, a3, a4, a5, a6, a7) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source # | |
Defined in Clash.Signal.Bundle | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source # | |
Defined in Clash.Signal.Bundle bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source # | |
Defined in Clash.Signal.Bundle bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source # | |
Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source # | |
Defined in Clash.Signal.Bundle bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source # unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source # |
Tools to emulate pre Clash 1.0 Bundle ()
instance
data EmptyTuple Source #
See TaggedEmptyTuple
Instances
data TaggedEmptyTuple (dom :: Domain) Source #
Helper type to emulate the "old" behavior of Bundle's unit instance. I.e.,
the instance for Bundle ()
used to be defined as:
class Bundle () where bundle :: () -> Signal domain () unbundle :: Signal domain () -> ()
In order to have sensible type inference, the Bundle class specifies that
the argument type of bundle
should uniquely identify the result type, and
vice versa for unbundle
. The type signatures in the snippet above don't
though, as ()
doesn't uniquely map to a specific domain. In other words,
domain
should occur in both the argument and result of both functions.
TaggedEmptyTuple tackles this by carrying the domain in its type. The
bundle
and unbundle
instance now looks like:
class Bundle EmptyTuple where bundle :: TaggedEmptyTuple domain -> Signal domain EmptyTuple unbundle :: Signal domain EmptyTuple -> TaggedEmptyTuple domain
domain
is now mentioned both the argument and result for both bundle
and
unbundle
.