clash-prelude-0.10.9: 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
  • DataKinds
  • DefaultSignatures
  • MagicHash
  • KindSignatures
  • 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 Source #

Methods

bundle' :: SClock clk -> 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' :: SClock clk -> 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' :: SClock clk -> 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' :: SClock clk -> 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 :: * Source #

Methods

bundle' :: SClock clk -> Unbundled' clk Bool -> Signal' clk Bool Source #

unbundle' :: SClock clk -> Signal' clk Bool -> Unbundled' clk Bool Source #

Bundle Double Source # 

Associated Types

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

Bundle Float Source # 

Associated Types

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

Bundle Int Source # 

Associated Types

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

Methods

bundle' :: SClock clk -> Unbundled' clk Int -> Signal' clk Int Source #

unbundle' :: SClock clk -> Signal' clk Int -> Unbundled' clk Int Source #

Bundle Integer Source # 

Associated Types

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

Bundle () Source # 

Associated Types

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

Methods

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

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

Bundle (Maybe a) Source # 

Associated Types

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

Methods

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

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

Bundle (Index n) Source # 

Associated Types

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

Methods

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

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

Bundle (BitVector n) Source # 

Associated Types

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

Methods

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

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

Bundle (Signed n) Source # 

Associated Types

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

Methods

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

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

Bundle (Unsigned n) Source # 

Associated Types

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

Methods

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

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

Bundle (Either a b) Source # 

Associated Types

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

Methods

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

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

Bundle (a, b) Source # 

Associated Types

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

Methods

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

unbundle' :: SClock clk -> 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) :: * Source #

Methods

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

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

Bundle (a, b, c) Source # 

Associated Types

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

Methods

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

unbundle' :: SClock clk -> 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) :: * Source #

Methods

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

unbundle' :: SClock clk -> 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) :: * Source #

Methods

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

unbundle' :: SClock clk -> 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) :: * Source #

Methods

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

unbundle' :: SClock clk -> 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) :: * Source #

Methods

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

unbundle' :: SClock clk -> 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) :: * Source #

Methods

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

unbundle' :: SClock clk -> 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) :: * Source #

Methods

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

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