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

Copyright(C) 2013-2016 University of Twente
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' (clk :: Clock) a = res | res -> clk Source #

Methods

bundle :: Unbundled' clk a -> Signal' clk a Source #

Example:

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

However:

bundle :: Signal' clk Bit -> Signal' clk Bit

bundle :: Signal' clk a -> Signal' clk a Source #

Example:

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

However:

bundle :: Signal' clk Bit -> Signal' clk Bit

unbundle :: Signal' clk a -> Unbundled' clk a Source #

Example:

unbundle :: Signal' clk (a,b) -> (Signal' clk a, Signal' clk b)

However:

unbundle :: Signal' clk Bit -> Signal' clk Bit

unbundle :: Signal' clk a -> Signal' clk a Source #

Example:

unbundle :: Signal' clk (a,b) -> (Signal' clk a, Signal' clk b)

However:

unbundle :: Signal' clk Bit -> Signal' clk Bit

Instances

Bundle Bool Source # 

Associated Types

type Unbundled' (clk :: Clock) Bool = (res :: *) Source #

Bundle Double Source # 

Associated Types

type Unbundled' (clk :: Clock) Double = (res :: *) Source #

Bundle Float Source # 

Associated Types

type Unbundled' (clk :: Clock) Float = (res :: *) Source #

Bundle Int Source # 

Associated Types

type Unbundled' (clk :: Clock) Int = (res :: *) Source #

Bundle Integer Source # 

Associated Types

type Unbundled' (clk :: Clock) Integer = (res :: *) Source #

Bundle () Source #

Note that:

bundle   :: () -> Signal' clk ()
unbundle :: Signal' clk () -> ()

Associated Types

type Unbundled' (clk :: Clock) () = (res :: *) Source #

Methods

bundle :: Unbundled' clk () -> Signal' clk () Source #

unbundle :: Signal' clk () -> Unbundled' clk () Source #

Bundle (Maybe a) Source # 

Associated Types

type Unbundled' (clk :: Clock) (Maybe a) = (res :: *) Source #

Methods

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

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

Bundle (Index n) Source # 

Associated Types

type Unbundled' (clk :: Clock) (Index n) = (res :: *) Source #

Methods

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

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

Bundle (BitVector n) Source # 

Associated Types

type Unbundled' (clk :: Clock) (BitVector n) = (res :: *) Source #

Bundle (Signed n) Source # 

Associated Types

type Unbundled' (clk :: Clock) (Signed n) = (res :: *) Source #

Methods

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

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

Bundle (Unsigned n) Source # 

Associated Types

type Unbundled' (clk :: Clock) (Unsigned n) = (res :: *) Source #

Methods

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

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

Bundle (Either a b) Source # 

Associated Types

type Unbundled' (clk :: Clock) (Either a b) = (res :: *) Source #

Methods

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

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

Bundle (a, b) Source # 

Associated Types

type Unbundled' (clk :: Clock) (a, b) = (res :: *) Source #

Methods

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

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

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

Associated Types

type Unbundled' (clk :: Clock) (Vec n a) = (res :: *) Source #

Methods

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

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

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

Associated Types

type Unbundled' (clk :: Clock) (RTree d a) = (res :: *) Source #

Methods

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

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

Bundle (a, b, c) Source # 

Associated Types

type Unbundled' (clk :: Clock) (a, b, c) = (res :: *) Source #

Methods

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

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

Bundle (Fixed rep int frac) Source # 

Associated Types

type Unbundled' (clk :: Clock) (Fixed rep int frac) = (res :: *) Source #

Methods

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

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

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

Associated Types

type Unbundled' (clk :: Clock) (a, b, c, d) = (res :: *) Source #

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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