clash-prelude-1.2.3: CAES Language for Synchronous Hardware - Prelude library
Copyright(C) 2019 Myrtle Software Ltd.
2018 @blaxill
2018 QBayLogic B.V.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Signal.Delayed.Bundle

Description

 
Synopsis

Documentation

class Bundle a where Source #

Isomorphism between a DSignal of a product type (e.g. a tuple) and a product type of DSignals.

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 dom delay D = DSignal dom delay D
  bundle   s = s
  unbundle s = s

Minimal complete definition

Nothing

Associated Types

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

type Unbundled dom d a = DSignal dom d a

Methods

bundle :: Unbundled dom d a -> DSignal dom d a Source #

Example:

bundle :: (DSignal dom d a, DSignal dom d b) -> DSignal clk d (a,b)

However:

bundle :: DSignal dom Bit -> DSignal dom Bit

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

unbundle :: DSignal dom d a -> Unbundled dom d a Source #

Example:

unbundle :: DSignal dom d (a,b) -> (DSignal dom d a, DSignal dom d b)

However:

unbundle :: DSignal dom Bit -> DSignal dom Bit

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

Instances

Instances details
Bundle Bool Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d Bool -> DSignal dom d Bool Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d Bool -> Unbundled dom d Bool Source #

Bundle Double Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d Double -> DSignal dom d Double Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d Double -> Unbundled dom d Double Source #

Bundle Float Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d Float -> DSignal dom d Float Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d Float -> Unbundled dom d Float Source #

Bundle Int Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d Int -> DSignal dom d Int Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d Int -> Unbundled dom d Int Source #

Bundle Integer Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d Integer -> DSignal dom d Integer Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d Integer -> Unbundled dom d Integer Source #

Bundle () Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d () -> DSignal dom d () Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d () -> Unbundled dom d () Source #

Bundle Bit Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d Bit -> DSignal dom d Bit Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d Bit -> Unbundled dom d Bit Source #

Bundle EmptyTuple Source #

See https://github.com/clash-lang/clash-compiler/pull/539/commits/94b0bff5770aa4961e04ddce2515130df3fc7863 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 #

Bundle (Maybe a) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d (Maybe a) -> DSignal dom d (Maybe a) Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d (Maybe a) -> Unbundled dom d (Maybe a) Source #

Bundle (BitVector n) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d (BitVector n) -> DSignal dom d (BitVector n) Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d (BitVector n) -> Unbundled dom d (BitVector n) Source #

Bundle (Index n) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d (Index n) -> DSignal dom d (Index n) Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d (Index n) -> Unbundled dom d (Index n) Source #

Bundle (Unsigned n) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d (Unsigned n) -> DSignal dom d (Unsigned n) Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d (Unsigned n) -> Unbundled dom d (Unsigned n) Source #

Bundle (Signed n) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d (Signed n) -> DSignal dom d (Signed n) Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d (Signed n) -> Unbundled dom d (Signed n) Source #

Bundle (Either a b) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

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

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

Bundle (a, b) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d (a, b) -> DSignal dom d (a, b) Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d (a, b) -> Unbundled dom d (a, b) Source #

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

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

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

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

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

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

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

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

Bundle (a, b, c) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

type Unbundled dom d (a, b, c) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain) (d :: Nat). Unbundled dom d (a, b, c) -> DSignal dom d (a, b, c) Source #

unbundle :: forall (dom :: Domain) (d :: Nat). DSignal dom d (a, b, c) -> Unbundled dom d (a, b, c) Source #

Bundle (Fixed rep int frac) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

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

Methods

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

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

Bundle (a, b, c, d) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

type Unbundled dom d (a, b, c, d) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain) (d0 :: Nat). Unbundled dom d0 (a, b, c, d) -> DSignal dom d0 (a, b, c, d) Source #

unbundle :: forall (dom :: Domain) (d0 :: Nat). DSignal dom d0 (a, b, c, d) -> Unbundled dom d0 (a, b, c, d) Source #

Bundle (a, b, c, d, e) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

type Unbundled dom d (a, b, c, d, e) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain) (d0 :: Nat). Unbundled dom d0 (a, b, c, d, e) -> DSignal dom d0 (a, b, c, d, e) Source #

unbundle :: forall (dom :: Domain) (d0 :: Nat). DSignal dom d0 (a, b, c, d, e) -> Unbundled dom d0 (a, b, c, d, e) Source #

Bundle (a, b, c, d, e, f) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

type Unbundled dom d (a, b, c, d, e, f) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain) (d0 :: Nat). Unbundled dom d0 (a, b, c, d, e, f) -> DSignal dom d0 (a, b, c, d, e, f) Source #

unbundle :: forall (dom :: Domain) (d0 :: Nat). DSignal dom d0 (a, b, c, d, e, f) -> Unbundled dom d0 (a, b, c, d, e, f) Source #

Bundle (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

type Unbundled dom d (a, b, c, d, e, f, g) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain) (d0 :: Nat). Unbundled dom d0 (a, b, c, d, e, f, g) -> DSignal dom d0 (a, b, c, d, e, f, g) Source #

unbundle :: forall (dom :: Domain) (d0 :: Nat). DSignal dom d0 (a, b, c, d, e, f, g) -> Unbundled dom d0 (a, b, c, d, e, f, g) Source #

Bundle (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Clash.Signal.Delayed.Bundle

Associated Types

type Unbundled dom d (a, b, c, d, e, f, g, h) = (res :: Type) Source #

Methods

bundle :: forall (dom :: Domain) (d0 :: Nat). Unbundled dom d0 (a, b, c, d, e, f, g, h) -> DSignal dom d0 (a, b, c, d, e, f, g, h) Source #

unbundle :: forall (dom :: Domain) (d0 :: Nat). DSignal dom d0 (a, b, c, d, e, f, g, h) -> Unbundled dom d0 (a, b, c, d, e, f, g, h) Source #

Tools to emulate pre Clash 1.0 Bundle () instance

data EmptyTuple Source #

Constructors

EmptyTuple 

Instances

Instances details
Bundle EmptyTuple Source #

See https://github.com/clash-lang/clash-compiler/pull/539/commits/94b0bff5770aa4961e04ddce2515130df3fc7863 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 https://github.com/clash-lang/clash-compiler/pull/539/commits/94b0bff5770aa4961e04ddce2515130df3fc7863 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) (d :: Nat) Source #

Constructors

TaggedEmptyTuple