| Copyright | (C) 2013-2016 University of Twente 2017-2019 Myrtle Software Ltd Google Inc. 20192022 QBayLogic B.V. |
|---|---|
| License | BSD2 (see the file LICENSE) |
| Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
| Extensions |
|
Clash.Signal.Bundle
Description
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 Signals.
Instances of Bundle must satisfy the following laws:
bundle.unbundle=idunbundle.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 typeUnbundledclk D =Signalclk Dbundles = sunbundles = 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)
-- bundle :: Pair (Signal dom a) (Signal dom b) -> Signal dom (Pair a b)
bundle (MkPair as bs) = MkPair $ as * bs
-- unbundle :: Signal dom (Pair a b) -> Pair (Signal dom a) (Signal dom b)
unbundle pairs = MkPair (getA $ pairs) (getB $ pairs)
Minimal complete definition
Nothing
Methods
bundle :: Unbundled dom a -> Signal dom a Source #
Example:
bundle :: (Signaldom a,Signaldom b) ->Signaldom (a,b)
However:
bundle ::SignaldomBit->SignaldomBit
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 commit 94b0bff5
and documentation for |
Defined in Clash.Signal.Bundle Associated Types type Unbundled dom EmptyTuple = (res :: Type) Source # Methods 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 # | |
Defined in Clash.Signal.Bundle | |
| Bundle (Index n) Source # | |
| Bundle (Unsigned n) Source # | |
Defined in Clash.Signal.Bundle | |
| Bundle (Signed n) Source # | |
| Bundle (Either a b) Source # | |
Defined in Clash.Signal.Bundle | |
| Bundle (a1, a2) Source # | |
| KnownNat n => Bundle (Vec n a) Source # | |
| KnownNat d => Bundle (RTree d a) Source # | |
Defined in Clash.Signal.Bundle | |
| Bundle (a1, a2, a3) Source # | N.B.: The documentation only shows instances up to 3-tuples. By
default, instances up to and including 12-tuples will exist. If the flag
|
Defined in Clash.Signal.Bundle | |
| Bundle (Fixed rep int frac) Source # | |
Defined in Clash.Signal.Bundle | |
| Bundle ((f :*: g) a) Source # | |
Defined in Clash.Signal.Bundle | |
Tools to emulate pre Clash 1.0 Bundle () instance
data EmptyTuple Source #
See TaggedEmptyTuple
Constructors
| EmptyTuple |
Instances
| Bundle EmptyTuple Source # | See commit 94b0bff5
and documentation for |
Defined in Clash.Signal.Bundle Associated Types type Unbundled dom EmptyTuple = (res :: Type) Source # Methods bundle :: forall (dom :: Domain). Unbundled dom EmptyTuple -> Signal dom EmptyTuple Source # unbundle :: forall (dom :: Domain). Signal dom EmptyTuple -> Unbundled dom EmptyTuple Source # | |
| Bundle EmptyTuple Source # | See commit 94b0bff5
and documentation for |
Defined in Clash.Signal.Delayed.Bundle Associated Types type Unbundled dom d EmptyTuple = (res :: Type) Source # Methods bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d EmptyTuple -> DSignal dom d EmptyTuple Source # unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d EmptyTuple -> Unbundled dom d EmptyTuple Source # | |
| type Unbundled dom EmptyTuple Source # | |
Defined in Clash.Signal.Bundle | |
| type Unbundled dom d EmptyTuple Source # | |
Defined in Clash.Signal.Delayed.Bundle | |
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 dom () unbundle :: Signal dom () -> ()
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 dom -> Signal dom EmptyTuple unbundle :: Signal dom EmptyTuple -> TaggedEmptyTuple dom
dom is now mentioned both the argument and result for both bundle and
unbundle.
Constructors
| TaggedEmptyTuple |