clash-prelude-0.99.1: CAES Language for Synchronous Hardware - Prelude library

Copyright(C) 2013-2016 University of Twente
2017 Myrtle Software Ltd Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellTrustworthy
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • TypeFamilies
  • TypeFamilyDependencies
  • DataKinds
  • DefaultSignatures
  • MagicHash
  • KindSignatures
  • TypeOperators
  • ExplicitNamespaces

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

Associated Types

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

Methods

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

Example:

bundle :: (Signal domain a, Signal domain b) -> Signal clk (a,b)

However:

bundle :: Signal domain Bit -> Signal domain Bit

bundle :: Signal domain a ~ Unbundled domain a => Unbundled domain a -> Signal domain a Source #

Example:

bundle :: (Signal domain a, Signal domain b) -> Signal clk (a,b)

However:

bundle :: Signal domain Bit -> Signal domain Bit

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

Example:

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

However:

unbundle :: Signal domain Bit -> Signal domain Bit

unbundle :: Unbundled domain a ~ Signal domain a => Signal domain a -> Unbundled domain a Source #

Example:

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

However:

unbundle :: Signal domain Bit -> Signal domain Bit
Instances
Bundle Bool Source # 
Instance details

Associated Types

type Unbundled domain Bool = (res :: *) Source #

Methods

bundle :: Unbundled domain Bool -> Signal domain Bool Source #

unbundle :: Signal domain Bool -> Unbundled domain Bool Source #

Bundle Double Source # 
Instance details

Associated Types

type Unbundled domain Double = (res :: *) Source #

Methods

bundle :: Unbundled domain Double -> Signal domain Double Source #

unbundle :: Signal domain Double -> Unbundled domain Double Source #

Bundle Float Source # 
Instance details

Associated Types

type Unbundled domain Float = (res :: *) Source #

Methods

bundle :: Unbundled domain Float -> Signal domain Float Source #

unbundle :: Signal domain Float -> Unbundled domain Float Source #

Bundle Int Source # 
Instance details

Associated Types

type Unbundled domain Int = (res :: *) Source #

Methods

bundle :: Unbundled domain Int -> Signal domain Int Source #

unbundle :: Signal domain Int -> Unbundled domain Int Source #

Bundle Integer Source # 
Instance details

Associated Types

type Unbundled domain Integer = (res :: *) Source #

Methods

bundle :: Unbundled domain Integer -> Signal domain Integer Source #

unbundle :: Signal domain Integer -> Unbundled domain Integer Source #

Bundle () Source #

Note that:

bundle   :: () -> Signal domain ()
unbundle :: Signal domain () -> ()
Instance details

Associated Types

type Unbundled domain () = (res :: *) Source #

Methods

bundle :: Unbundled domain () -> Signal domain () Source #

unbundle :: Signal domain () -> Unbundled domain () Source #

Bundle Bit Source # 
Instance details

Associated Types

type Unbundled domain Bit = (res :: *) Source #

Methods

bundle :: Unbundled domain Bit -> Signal domain Bit Source #

unbundle :: Signal domain Bit -> Unbundled domain Bit Source #

Bundle (Maybe a) Source # 
Instance details

Associated Types

type Unbundled domain (Maybe a) = (res :: *) Source #

Methods

bundle :: Unbundled domain (Maybe a) -> Signal domain (Maybe a) Source #

unbundle :: Signal domain (Maybe a) -> Unbundled domain (Maybe a) Source #

Bundle (BitVector n) Source # 
Instance details

Associated Types

type Unbundled domain (BitVector n) = (res :: *) Source #

Methods

bundle :: Unbundled domain (BitVector n) -> Signal domain (BitVector n) Source #

unbundle :: Signal domain (BitVector n) -> Unbundled domain (BitVector n) Source #

Bundle (Index n) Source # 
Instance details

Associated Types

type Unbundled domain (Index n) = (res :: *) Source #

Methods

bundle :: Unbundled domain (Index n) -> Signal domain (Index n) Source #

unbundle :: Signal domain (Index n) -> Unbundled domain (Index n) Source #

Bundle (Unsigned n) Source # 
Instance details

Associated Types

type Unbundled domain (Unsigned n) = (res :: *) Source #

Methods

bundle :: Unbundled domain (Unsigned n) -> Signal domain (Unsigned n) Source #

unbundle :: Signal domain (Unsigned n) -> Unbundled domain (Unsigned n) Source #

Bundle (Signed n) Source # 
Instance details

Associated Types

type Unbundled domain (Signed n) = (res :: *) Source #

Methods

bundle :: Unbundled domain (Signed n) -> Signal domain (Signed n) Source #

unbundle :: Signal domain (Signed n) -> Unbundled domain (Signed n) Source #

Bundle (Either a b) Source # 
Instance details

Associated Types

type Unbundled domain (Either a b) = (res :: *) Source #

Methods

bundle :: Unbundled domain (Either a b) -> Signal domain (Either a b) Source #

unbundle :: Signal domain (Either a b) -> Unbundled domain (Either a b) Source #

Bundle (a, b) Source # 
Instance details

Associated Types

type Unbundled domain (a, b) = (res :: *) Source #

Methods

bundle :: Unbundled domain (a, b) -> Signal domain (a, b) Source #

unbundle :: Signal domain (a, b) -> Unbundled domain (a, b) Source #

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

Associated Types

type Unbundled domain (Vec n a) = (res :: *) Source #

Methods

bundle :: Unbundled domain (Vec n a) -> Signal domain (Vec n a) Source #

unbundle :: Signal domain (Vec n a) -> Unbundled domain (Vec n a) Source #

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

Associated Types

type Unbundled domain (RTree d a) = (res :: *) Source #

Methods

bundle :: Unbundled domain (RTree d a) -> Signal domain (RTree d a) Source #

unbundle :: Signal domain (RTree d a) -> Unbundled domain (RTree d a) Source #

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

Associated Types

type Unbundled domain (a, b, c) = (res :: *) Source #

Methods

bundle :: Unbundled domain (a, b, c) -> Signal domain (a, b, c) Source #

unbundle :: Signal domain (a, b, c) -> Unbundled domain (a, b, c) Source #

Bundle (Fixed rep int frac) Source # 
Instance details

Associated Types

type Unbundled domain (Fixed rep int frac) = (res :: *) Source #

Methods

bundle :: Unbundled domain (Fixed rep int frac) -> Signal domain (Fixed rep int frac) Source #

unbundle :: Signal domain (Fixed rep int frac) -> Unbundled domain (Fixed rep int frac) Source #

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

Associated Types

type Unbundled domain (a, b, c, d) = (res :: *) Source #

Methods

bundle :: Unbundled domain (a, b, c, d) -> Signal domain (a, b, c, d) Source #

unbundle :: Signal domain (a, b, c, d) -> Unbundled domain (a, b, c, d) Source #

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

Associated Types

type Unbundled domain (a, b, c, d, e) = (res :: *) Source #

Methods

bundle :: Unbundled domain (a, b, c, d, e) -> Signal domain (a, b, c, d, e) Source #

unbundle :: Signal domain (a, b, c, d, e) -> Unbundled domain (a, b, c, d, e) Source #

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

Associated Types

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

Methods

bundle :: Unbundled domain (a, b, c, d, e, f) -> Signal domain (a, b, c, d, e, f) Source #

unbundle :: Signal domain (a, b, c, d, e, f) -> Unbundled domain (a, b, c, d, e, f) Source #

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

Associated Types

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

Methods

bundle :: Unbundled domain (a, b, c, d, e, f, g) -> Signal domain (a, b, c, d, e, f, g) Source #

unbundle :: Signal domain (a, b, c, d, e, f, g) -> Unbundled domain (a, b, c, d, e, f, g) Source #

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

Associated Types

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

Methods

bundle :: Unbundled domain (a, b, c, d, e, f, g, h) -> Signal domain (a, b, c, d, e, f, g, h) Source #

unbundle :: Signal domain (a, b, c, d, e, f, g, h) -> Unbundled domain (a, b, c, d, e, f, g, h) Source #