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

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

Clash.Class.BitPack

Description

 
Synopsis

Documentation

class BitPack a where Source #

Convert to and from a BitVector

Associated Types

type BitSize a :: Nat Source #

Number of Bits needed to represents elements of type a

Can be derived using Generics:

{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}

import Clash.Prelude
import GHC.Generics

data MyProductType = MyProductType { a :: Int, b :: Bool }
  deriving (Generic, BitPack)

Methods

pack :: a -> BitVector (BitSize a) Source #

Convert element of type a to a BitVector

>>> pack (-5 :: Signed 6)
11_1011

pack :: (Generic a, GBitPack (Rep a), GBitSize (Rep a) ~ BitSize a) => a -> BitVector (BitSize a) Source #

Convert element of type a to a BitVector

>>> pack (-5 :: Signed 6)
11_1011

unpack :: BitVector (BitSize a) -> a Source #

Convert a BitVector to an element of type a

>>> pack (-5 :: Signed 6)
11_1011
>>> let x = pack (-5 :: Signed 6)
>>> unpack x :: Unsigned 6
59
>>> pack (59 :: Unsigned 6)
11_1011

unpack :: (Generic a, GBitPack (Rep a), GBitSize (Rep a) ~ BitSize a) => BitVector (BitSize a) -> a Source #

Convert a BitVector to an element of type a

>>> pack (-5 :: Signed 6)
11_1011
>>> let x = pack (-5 :: Signed 6)
>>> unpack x :: Unsigned 6
59
>>> pack (59 :: Unsigned 6)
11_1011
Instances
BitPack Bool Source # 
Instance details

Associated Types

type BitSize Bool :: Nat Source #

BitPack Double Source # 
Instance details

Associated Types

type BitSize Double :: Nat Source #

BitPack Float Source # 
Instance details

Associated Types

type BitSize Float :: Nat Source #

BitPack Int Source # 
Instance details

Associated Types

type BitSize Int :: Nat Source #

BitPack Int8 Source # 
Instance details

Associated Types

type BitSize Int8 :: Nat Source #

BitPack Int16 Source # 
Instance details

Associated Types

type BitSize Int16 :: Nat Source #

BitPack Int32 Source # 
Instance details

Associated Types

type BitSize Int32 :: Nat Source #

BitPack Int64 Source # 
Instance details

Associated Types

type BitSize Int64 :: Nat Source #

BitPack Word Source # 
Instance details

Associated Types

type BitSize Word :: Nat Source #

BitPack Word8 Source # 
Instance details

Associated Types

type BitSize Word8 :: Nat Source #

BitPack Word16 Source # 
Instance details

Associated Types

type BitSize Word16 :: Nat Source #

BitPack Word32 Source # 
Instance details

Associated Types

type BitSize Word32 :: Nat Source #

BitPack Word64 Source # 
Instance details

Associated Types

type BitSize Word64 :: Nat Source #

BitPack () Source # 
Instance details

Associated Types

type BitSize () :: Nat Source #

Methods

pack :: () -> BitVector (BitSize ()) Source #

unpack :: BitVector (BitSize ()) -> () Source #

BitPack CUShort Source # 
Instance details

Associated Types

type BitSize CUShort :: Nat Source #

BitPack Bit Source # 
Instance details

Associated Types

type BitSize Bit :: Nat Source #

BitPack Half Source # 
Instance details

Associated Types

type BitSize Half :: Nat Source #

Methods

pack :: Half -> BitVector (BitSize Half) Source #

unpack :: BitVector (BitSize Half) -> Half Source #

(BitPack a, KnownNat (BitSize a)) => BitPack (Maybe a) Source # 
Instance details

Associated Types

type BitSize (Maybe a) :: Nat Source #

BitPack (BitVector n) Source # 
Instance details

Associated Types

type BitSize (BitVector n) :: Nat Source #

KnownNat n => BitPack (Index n) Source # 
Instance details

Associated Types

type BitSize (Index n) :: Nat Source #

BitPack (Unsigned n) Source # 
Instance details

Associated Types

type BitSize (Unsigned n) :: Nat Source #

KnownNat n => BitPack (Signed n) Source # 
Instance details

Associated Types

type BitSize (Signed n) :: Nat Source #

(KnownNat (BitSize b), BitPack a, BitPack b) => BitPack (a, b) Source # 
Instance details

Associated Types

type BitSize (a, b) :: Nat Source #

Methods

pack :: (a, b) -> BitVector (BitSize (a, b)) Source #

unpack :: BitVector (BitSize (a, b)) -> (a, b) Source #

(KnownNat n, KnownNat (BitSize a), BitPack a) => BitPack (Vec n a) Source # 
Instance details

Associated Types

type BitSize (Vec n a) :: Nat Source #

Methods

pack :: Vec n a -> BitVector (BitSize (Vec n a)) Source #

unpack :: BitVector (BitSize (Vec n a)) -> Vec n a Source #

(KnownNat d, KnownNat (BitSize a), BitPack a) => BitPack (RTree d a) Source # 
Instance details

Associated Types

type BitSize (RTree d a) :: Nat Source #

Methods

pack :: RTree d a -> BitVector (BitSize (RTree d a)) Source #

unpack :: BitVector (BitSize (RTree d a)) -> RTree d a Source #

(KnownNat (BitSize c), BitPack (a, b), BitPack c) => BitPack (a, b, c) Source # 
Instance details

Associated Types

type BitSize (a, b, c) :: Nat Source #

Methods

pack :: (a, b, c) -> BitVector (BitSize (a, b, c)) Source #

unpack :: BitVector (BitSize (a, b, c)) -> (a, b, c) Source #

BitPack (rep (int + frac)) => BitPack (Fixed rep int frac) Source # 
Instance details

Associated Types

type BitSize (Fixed rep int frac) :: Nat Source #

Methods

pack :: Fixed rep int frac -> BitVector (BitSize (Fixed rep int frac)) Source #

unpack :: BitVector (BitSize (Fixed rep int frac)) -> Fixed rep int frac Source #

(KnownNat (BitSize d), BitPack (a, b, c), BitPack d) => BitPack (a, b, c, d) Source # 
Instance details

Associated Types

type BitSize (a, b, c, d) :: Nat Source #

Methods

pack :: (a, b, c, d) -> BitVector (BitSize (a, b, c, d)) Source #

unpack :: BitVector (BitSize (a, b, c, d)) -> (a, b, c, d) Source #

(KnownNat (BitSize e), BitPack (a, b, c, d), BitPack e) => BitPack (a, b, c, d, e) Source # 
Instance details

Associated Types

type BitSize (a, b, c, d, e) :: Nat Source #

Methods

pack :: (a, b, c, d, e) -> BitVector (BitSize (a, b, c, d, e)) Source #

unpack :: BitVector (BitSize (a, b, c, d, e)) -> (a, b, c, d, e) Source #

(KnownNat (BitSize f), BitPack (a, b, c, d, e), BitPack f) => BitPack (a, b, c, d, e, f) Source # 
Instance details

Associated Types

type BitSize (a, b, c, d, e, f) :: Nat Source #

Methods

pack :: (a, b, c, d, e, f) -> BitVector (BitSize (a, b, c, d, e, f)) Source #

unpack :: BitVector (BitSize (a, b, c, d, e, f)) -> (a, b, c, d, e, f) Source #

(KnownNat (BitSize g), BitPack (a, b, c, d, e, f), BitPack g) => BitPack (a, b, c, d, e, f, g) Source # 
Instance details

Associated Types

type BitSize (a, b, c, d, e, f, g) :: Nat Source #

Methods

pack :: (a, b, c, d, e, f, g) -> BitVector (BitSize (a, b, c, d, e, f, g)) Source #

unpack :: BitVector (BitSize (a, b, c, d, e, f, g)) -> (a, b, c, d, e, f, g) Source #

(KnownNat (BitSize h), BitPack (a, b, c, d, e, f, g), BitPack h) => BitPack (a, b, c, d, e, f, g, h) Source # 
Instance details

Associated Types

type BitSize (a, b, c, d, e, f, g, h) :: Nat Source #

Methods

pack :: (a, b, c, d, e, f, g, h) -> BitVector (BitSize (a, b, c, d, e, f, g, h)) Source #

unpack :: BitVector (BitSize (a, b, c, d, e, f, g, h)) -> (a, b, c, d, e, f, g, h) Source #

bitCoerce :: (BitPack a, BitPack b, BitSize a ~ BitSize b) => a -> b Source #

Coerce a value from one type to another through its bit representation.

>>> pack (-5 :: Signed 6)
11_1011
>>> bitCoerce (-5 :: Signed 6) :: Unsigned 6
59
>>> pack (59 :: Unsigned 6)
11_1011

boolToBV :: KnownNat n => Bool -> BitVector (n + 1) Source #

Zero-extend a Boolean value to a BitVector of the appropriate size.

>>> boolToBV True :: BitVector 6
00_0001
>>> boolToBV False :: BitVector 6
00_0000

boolToBit :: Bool -> Bit Source #

Convert a Bool to a Bit

bitToBool :: Bit -> Bool Source #

Convert a Bool to a Bit