clash-prelude-1.3.0: CAES Language for Synchronous Hardware - Prelude library
Copyright(C) 2013-2016 University of Twente
2017-2019 Myrtle Software Ltd Google Inc.
2019 QBayLogic B.V.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellTrustworthy
LanguageHaskell2010
Extensions
  • Cpp
  • MonoLocalBinds
  • TemplateHaskell
  • TemplateHaskellQuotes
  • ScopedTypeVariables
  • BangPatterns
  • TypeFamilies
  • TypeFamilyDependencies
  • ViewPatterns
  • DataKinds
  • InstanceSigs
  • StandaloneDeriving
  • DeriveDataTypeable
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • DeriveGeneric
  • DefaultSignatures
  • DeriveLift
  • DerivingStrategies
  • MagicHash
  • KindSignatures
  • TupleSections
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • BinaryLiterals
  • TypeApplications

Clash.Signal.Bundle

Description

The Product/Signal isomorphism

Synopsis

Documentation

class Bundle a where Source #

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 = 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
  type Unbundled clk D = Signal clk D
  bundle   s = s
  unbundle 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)

  -- 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

Associated Types

type Unbundled (dom :: Domain) a = res | res -> dom a Source #

type Unbundled dom a = Signal dom a

Methods

bundle :: Unbundled dom a -> Signal dom a Source #

Example:

bundle :: (Signal dom a, Signal dom b) -> Signal dom (a,b)

However:

bundle :: Signal dom Bit -> Signal dom Bit

default bundle :: Signal dom a ~ Unbundled dom a => Unbundled dom a -> Signal dom a Source #

unbundle :: Signal dom a -> Unbundled dom a Source #

Example:

unbundle :: Signal dom (a,b) -> (Signal dom a, Signal dom b)

However:

unbundle :: Signal dom Bit -> Signal dom Bit

default unbundle :: Unbundled dom a ~ Signal dom a => Signal dom a -> Unbundled dom a Source #

Instances

Instances details
Bundle Bool Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom Bool = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom Bool -> Signal dom Bool Source #

unbundle :: forall (dom :: Domain). Signal dom Bool -> Unbundled dom Bool Source #

Bundle Double Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom Double = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom Double -> Signal dom Double Source #

unbundle :: forall (dom :: Domain). Signal dom Double -> Unbundled dom Double Source #

Bundle Float Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom Float = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom Float -> Signal dom Float Source #

unbundle :: forall (dom :: Domain). Signal dom Float -> Unbundled dom Float Source #

Bundle Int Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom Int = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom Int -> Signal dom Int Source #

unbundle :: forall (dom :: Domain). Signal dom Int -> Unbundled dom Int Source #

Bundle Integer Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom Integer = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom Integer -> Signal dom Integer Source #

unbundle :: forall (dom :: Domain). Signal dom Integer -> Unbundled dom Integer Source #

Bundle () Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom () = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom () -> Signal dom () Source #

unbundle :: forall (dom :: Domain). Signal dom () -> Unbundled dom () Source #

Bundle Bit Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom Bit = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom Bit -> Signal dom Bit Source #

unbundle :: forall (dom :: Domain). Signal dom Bit -> Unbundled dom Bit Source #

Bundle EmptyTuple Source #

See commit 94b0bff5 and documentation for TaggedEmptyTuple.

Instance details

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 # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Maybe a) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Maybe a) -> Signal dom (Maybe a) Source #

unbundle :: forall (dom :: Domain). Signal dom (Maybe a) -> Unbundled dom (Maybe a) Source #

Bundle (BitVector n) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (BitVector n) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (BitVector n) -> Signal dom (BitVector n) Source #

unbundle :: forall (dom :: Domain). Signal dom (BitVector n) -> Unbundled dom (BitVector n) Source #

Bundle (Index n) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Index n) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Index n) -> Signal dom (Index n) Source #

unbundle :: forall (dom :: Domain). Signal dom (Index n) -> Unbundled dom (Index n) Source #

Bundle (Unsigned n) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Unsigned n) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Unsigned n) -> Signal dom (Unsigned n) Source #

unbundle :: forall (dom :: Domain). Signal dom (Unsigned n) -> Unbundled dom (Unsigned n) Source #

Bundle (Signed n) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Signed n) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Signed n) -> Signal dom (Signed n) Source #

unbundle :: forall (dom :: Domain). Signal dom (Signed n) -> Unbundled dom (Signed n) Source #

Bundle (Either a b) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Either a b) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Either a b) -> Signal dom (Either a b) Source #

unbundle :: forall (dom :: Domain). Signal dom (Either a b) -> Unbundled dom (Either a b) Source #

Bundle (a1, a2) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2) -> Signal dom (a1, a2) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2) -> Unbundled dom (a1, a2) Source #

KnownNat n => Bundle (Vec n a) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Vec n a) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Vec n a) -> Signal dom (Vec n a) Source #

unbundle :: forall (dom :: Domain). Signal dom (Vec n a) -> Unbundled dom (Vec n a) Source #

KnownNat d => Bundle (RTree d a) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (RTree d a) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (RTree d a) -> Signal dom (RTree d a) Source #

unbundle :: forall (dom :: Domain). Signal dom (RTree d a) -> Unbundled dom (RTree d a) Source #

Bundle (a1, a2, a3) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3) -> Signal dom (a1, a2, a3) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3) -> Unbundled dom (a1, a2, a3) Source #

Bundle (Fixed rep int frac) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (Fixed rep int frac) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (Fixed rep int frac) -> Signal dom (Fixed rep int frac) Source #

unbundle :: forall (dom :: Domain). Signal dom (Fixed rep int frac) -> Unbundled dom (Fixed rep int frac) Source #

Bundle ((f :*: g) a) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom ((f :*: g) a) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom ((f :*: g) a) -> Signal dom ((f :*: g) a) Source #

unbundle :: forall (dom :: Domain). Signal dom ((f :*: g) a) -> Unbundled dom ((f :*: g) a) Source #

Bundle (a1, a2, a3, a4) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4) -> Signal dom (a1, a2, a3, a4) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4) -> Unbundled dom (a1, a2, a3, a4) Source #

Bundle (a1, a2, a3, a4, a5) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5) -> Signal dom (a1, a2, a3, a4, a5) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5) -> Unbundled dom (a1, a2, a3, a4, a5) Source #

Bundle (a1, a2, a3, a4, a5, a6) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5, a6) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6) -> Signal dom (a1, a2, a3, a4, a5, a6) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6) -> Unbundled dom (a1, a2, a3, a4, a5, a6) Source #

Bundle (a1, a2, a3, a4, a5, a6, a7) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5, a6, a7) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7) -> Signal dom (a1, a2, a3, a4, a5, a6, a7) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7) Source #

Bundle (a1, a2, a3, a4, a5, a6, a7, a8) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8) Source #

Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain). Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source #

unbundle :: forall (dom :: Domain). Signal dom (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source #

Bundle (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) = (res :: Type) Source #

Methods

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 # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) = (res :: Type) Source #

Methods

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 # 
Instance details

Defined in Clash.Signal.Bundle

Associated Types

type Unbundled dom (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) = (res :: Type) Source #

Methods

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 #

Constructors

EmptyTuple 

Instances

Instances details
Bundle EmptyTuple Source #

See commit 94b0bff5 and documentation for TaggedEmptyTuple.

Instance details

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 TaggedEmptyTuple.

Instance details

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 # 
Instance details

Defined in Clash.Signal.Bundle

type Unbundled dom d EmptyTuple Source # 
Instance details

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 

Internal

vecBundle# :: Vec n (Signal t a) -> Signal t (Vec n a) Source #