clash-prelude-0.99: 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
ExtensionsMagicHash

Clash.Sized.BitVector

Contents

Description

 

Synopsis

Bit

data Bit Source #

Bit

Instances

Bounded Bit Source # 

Methods

minBound :: Bit #

maxBound :: Bit #

Enum Bit Source # 

Methods

succ :: Bit -> Bit #

pred :: Bit -> Bit #

toEnum :: Int -> Bit #

fromEnum :: Bit -> Int #

enumFrom :: Bit -> [Bit] #

enumFromThen :: Bit -> Bit -> [Bit] #

enumFromTo :: Bit -> Bit -> [Bit] #

enumFromThenTo :: Bit -> Bit -> Bit -> [Bit] #

Eq Bit Source # 

Methods

(==) :: Bit -> Bit -> Bool #

(/=) :: Bit -> Bit -> Bool #

Integral Bit Source # 

Methods

quot :: Bit -> Bit -> Bit #

rem :: Bit -> Bit -> Bit #

div :: Bit -> Bit -> Bit #

mod :: Bit -> Bit -> Bit #

quotRem :: Bit -> Bit -> (Bit, Bit) #

divMod :: Bit -> Bit -> (Bit, Bit) #

toInteger :: Bit -> Integer #

Data Bit Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bit -> c Bit #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bit #

toConstr :: Bit -> Constr #

dataTypeOf :: Bit -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Bit) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bit) #

gmapT :: (forall b. Data b => b -> b) -> Bit -> Bit #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bit -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bit -> r #

gmapQ :: (forall d. Data d => d -> u) -> Bit -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bit -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bit -> m Bit #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bit -> m Bit #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bit -> m Bit #

Num Bit Source # 

Methods

(+) :: Bit -> Bit -> Bit #

(-) :: Bit -> Bit -> Bit #

(*) :: Bit -> Bit -> Bit #

negate :: Bit -> Bit #

abs :: Bit -> Bit #

signum :: Bit -> Bit #

fromInteger :: Integer -> Bit #

Ord Bit Source # 

Methods

compare :: Bit -> Bit -> Ordering #

(<) :: Bit -> Bit -> Bool #

(<=) :: Bit -> Bit -> Bool #

(>) :: Bit -> Bit -> Bool #

(>=) :: Bit -> Bit -> Bool #

max :: Bit -> Bit -> Bit #

min :: Bit -> Bit -> Bit #

Real Bit Source # 

Methods

toRational :: Bit -> Rational #

Show Bit Source # 

Methods

showsPrec :: Int -> Bit -> ShowS #

show :: Bit -> String #

showList :: [Bit] -> ShowS #

Lift Bit Source # 

Methods

lift :: Bit -> Q Exp #

Bits Bit Source # 

Methods

(.&.) :: Bit -> Bit -> Bit #

(.|.) :: Bit -> Bit -> Bit #

xor :: Bit -> Bit -> Bit #

complement :: Bit -> Bit #

shift :: Bit -> Int -> Bit #

rotate :: Bit -> Int -> Bit #

zeroBits :: Bit #

bit :: Int -> Bit #

setBit :: Bit -> Int -> Bit #

clearBit :: Bit -> Int -> Bit #

complementBit :: Bit -> Int -> Bit #

testBit :: Bit -> Int -> Bool #

bitSizeMaybe :: Bit -> Maybe Int #

bitSize :: Bit -> Int #

isSigned :: Bit -> Bool #

shiftL :: Bit -> Int -> Bit #

unsafeShiftL :: Bit -> Int -> Bit #

shiftR :: Bit -> Int -> Bit #

unsafeShiftR :: Bit -> Int -> Bit #

rotateL :: Bit -> Int -> Bit #

rotateR :: Bit -> Int -> Bit #

popCount :: Bit -> Int #

FiniteBits Bit Source # 
Default Bit Source # 

Methods

def :: Bit #

NFData Bit Source # 

Methods

rnf :: Bit -> () #

ShowX Bit Source # 
BitPack Bit Source # 

Associated Types

type BitSize Bit :: Nat Source #

Bundle Bit Source # 

Associated Types

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

Methods

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

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

type BitSize Bit Source # 
type BitSize Bit = 1
type Unbundled domain Bit Source # 
type Unbundled domain Bit = Signal domain Bit

Construction

Initialisation

high :: Bit Source #

logic '1'

low :: Bit Source #

logic '0'

BitVector

data BitVector (n :: Nat) Source #

A vector of bits.

  • Bit indices are descending
  • Num instance performs unsigned arithmetic.

Instances

Resize BitVector Source # 
KnownNat n => Bounded (BitVector n) Source # 
KnownNat n => Enum (BitVector n) Source #

The functions: enumFrom, enumFromThen, enumFromTo, and enumFromThenTo, are not synthesisable.

Eq (BitVector n) Source # 

Methods

(==) :: BitVector n -> BitVector n -> Bool #

(/=) :: BitVector n -> BitVector n -> Bool #

KnownNat n => Integral (BitVector n) Source # 
KnownNat n => Data (BitVector n) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BitVector n -> c (BitVector n) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BitVector n) #

toConstr :: BitVector n -> Constr #

dataTypeOf :: BitVector n -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (BitVector n)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (BitVector n)) #

gmapT :: (forall b. Data b => b -> b) -> BitVector n -> BitVector n #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BitVector n -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BitVector n -> r #

gmapQ :: (forall d. Data d => d -> u) -> BitVector n -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BitVector n -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BitVector n -> m (BitVector n) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BitVector n -> m (BitVector n) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BitVector n -> m (BitVector n) #

KnownNat n => Num (BitVector n) Source # 
Ord (BitVector n) Source # 
KnownNat n => Real (BitVector n) Source # 
KnownNat n => Show (BitVector n) Source # 
KnownNat n => Lift (BitVector n) Source # 

Methods

lift :: BitVector n -> Q Exp #

KnownNat n => Arbitrary (BitVector n) Source # 

Methods

arbitrary :: Gen (BitVector n) #

shrink :: BitVector n -> [BitVector n] #

KnownNat n => CoArbitrary (BitVector n) Source # 

Methods

coarbitrary :: BitVector n -> Gen b -> Gen b #

KnownNat n => Bits (BitVector n) Source # 
KnownNat n => FiniteBits (BitVector n) Source # 
Default (BitVector n) Source # 

Methods

def :: BitVector n #

NFData (BitVector n) Source # 

Methods

rnf :: BitVector n -> () #

KnownNat n => Ixed (BitVector n) Source # 
KnownNat n => SaturatingNum (BitVector n) Source # 
KnownNat n => ShowX (BitVector n) Source # 
BitPack (BitVector n) Source # 

Associated Types

type BitSize (BitVector n) :: Nat Source #

Bundle (BitVector n) Source # 

Associated Types

type Unbundled (domain :: 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 #

(KnownNat m, KnownNat n) => ExtendingNum (BitVector m) (BitVector n) Source # 
type Unbundled domain (BitVector n) Source # 
type Unbundled domain (BitVector n) = Signal domain (BitVector n)
type Index (BitVector n) Source # 
type Index (BitVector n) = Int
type IxValue (BitVector n) Source # 
type IxValue (BitVector n) = Bit
type BitSize (BitVector n) Source # 
type BitSize (BitVector n) = n
type AResult (BitVector m) (BitVector n) Source # 
type AResult (BitVector m) (BitVector n) = BitVector ((+) (Max m n) 1)
type MResult (BitVector m) (BitVector n) Source # 
type MResult (BitVector m) (BitVector n) = BitVector ((+) m n)

Accessors

Length information

Construction

bLit :: KnownNat n => String -> Q (TExp (BitVector n)) Source #

Create a binary literal

>>> $$(bLit "1001") :: BitVector 4
1001
>>> $$(bLit "1001") :: BitVector 3
001

NB: You can also just write:

>>> 0b1001 :: BitVector 4
1001

The advantage of bLit is that you can use computations to create the string literal:

>>> import qualified Data.List as List
>>> $$(bLit (List.replicate 4 '1')) :: BitVector 4
1111

Concatenation

(++#) :: KnownNat m => BitVector n -> BitVector m -> BitVector (n + m) Source #

Concatenate two BitVectors