clash-prelude-1.2.4: CAES Language for Synchronous Hardware - Prelude library
Copyright(C) 2018 Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Annotations.BitRepresentation.Deriving

Description

This module contains:

  • Template Haskell functions for deriving BitPack instances given a custom bit representation as those defined in Clash.Annotations.BitRepresentation.
  • Template Haskell functions for deriving custom bit representations, e.g. one-hot, for a data type.
Synopsis

Derivation functions

deriveBitPack :: Q Type -> Q [Dec] Source #

Derives BitPack instances for given type. Will account for custom bit representation annotations in the module where the splice is ran. Note that the generated instance might conflict with existing implementations (for example, an instance for Maybe a exists, yielding conflicts for any alternative implementations).

Usage:

data Color = R | G | B
{-# ANN module (DataReprAnn
                  $(liftQ [t|Color|])
                  2
                  [ ConstrRepr 'R 0b11 0b00 []
                  , ConstrRepr 'G 0b11 0b01 []
                  , ConstrRepr 'B 0b11 0b10 []
                  ]) #-}
deriveBitPack [t| Color |]

data MaybeColor = JustColor Color
                | NothingColor deriving (Generic,BitPack)

NB: Because of the way template haskell works the order here matters, if you try to derive MaybeColor before deriveBitPack Color it will complain about missing an instance BitSize Color.

deriveDefaultAnnotation :: Q Type -> Q [Dec] Source #

Derives bit representation corresponding to the default manner in which Clash stores types.

derivePackedMaybeAnnotation :: DataReprAnn -> Q [Dec] Source #

Derive a compactly represented version of Maybe a.

deriveBlueSpecAnnotation :: Q Type -> Q [Dec] Source #

Derives bit representation corresponding to the default manner in which BlueSpec stores types.

Derivators

defaultDerivator :: Derivator Source #

Derives bit representation corresponding to the default manner in which Clash stores types.

blueSpecDerivator :: Derivator Source #

Derives bit representation corresponding to the default manner in which BlueSpec stores types.

packedDerivator :: Derivator Source #

This derivator tries to distribute its constructor bits over space left by the difference in constructor sizes. Example:

type SmallInt = Unsigned 2

data Train
   = Passenger SmallInt
   | Freight SmallInt SmallInt
   | Maintenance
   | Toy

The packed representation of this data type needs only a single constructor bit. The first bit discriminates between Freight and non-Freight constructors. All other constructors do not use their last two bits; the packed representation will store the rest of the constructor bits there.

simpleDerivator :: ConstructorType -> FieldsType -> Derivator Source #

Simple derivators change the (default) way Clash stores data types. It assumes no overlap between constructors and fields.

Util functions

dontApplyInHDL :: (a -> b) -> a -> b Source #

In Haskell apply the first argument to the second argument, in HDL just return the second argument.

This is used in the generated pack/unpack to not do anything in HDL.

Types associated with various functions

data ConstructorType Source #

Indicates how to pack constructor for simpleDerivator

Constructors

Binary

First constructor will be encoded as 0b0, the second as 0b1, the third as 0b10, etc.

OneHot

Reserve a single bit for each constructor marker.

data FieldsType Source #

Indicates how to pack (constructor) fields for simpleDerivator

Constructors

OverlapL

Store fields of different constructors at (possibly) overlapping bit positions. That is, a data type with two constructors with each two fields of each one bit will take two bits for its whole representation (plus constructor bits). Overlap is left-biased, i.e. don't care bits are padded to the right.

This is the default behavior of Clash.

OverlapR

Store fields of different constructors at (possibly) overlapping bit positions. That is, a data type with two constructors with each two fields of each one bit will take two bits for its whole representation (plus constructor bits). Overlap is right biased, i.e. don't care bits are padded between between the constructor bits and the field bits.

Wide

Store fields of different constructs at non-overlapping positions. That is, a data type with two constructors with each two fields of each one bit will take four bits for its whole representation (plus constructor bits).

Convenience type synonyms

type Derivator = Type -> Q DataReprAnnExp Source #

A derivator derives a bit representation given a type

type DataReprAnnExp = Exp Source #

DataReprAnn as template haskell expression