bv-sized-0.1.0.0: a BitVector datatype that is parameterized by the vector width

Copyright(c) Benjamin Selfridge 2018
Galois Inc.
LicenseBSD3
Maintainerbenselfridge@galois.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.BitVector.Sized

Contents

Description

This module defines a width-parameterized BitVector type and various associated operations that assume a 2's complement representation.

For more fine-grained access to the internals (including explicit NatReprs), see Internal.

Synopsis

BitVector type

data BitVector (w :: Nat) :: * Source #

BitVector datatype, parameterized by width.

Instances

TestEquality Nat BitVector Source # 

Methods

testEquality :: f a -> f b -> Maybe ((BitVector :~: a) b) #

EqF Nat BitVector Source # 

Methods

eqF :: f a -> f a -> Bool #

ShowF Nat BitVector Source # 

Methods

withShow :: p f -> q tp -> (Show (f tp) -> a) -> a #

showF :: f tp -> String #

showsF :: f tp -> String -> String #

KnownNat w => Bounded (BitVector w) Source # 
KnownNat w => Enum (BitVector w) Source # 
Eq (BitVector w) Source # 

Methods

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

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

KnownNat w => Num (BitVector w) Source # 
Show (BitVector w) Source # 
KnownNat w => Bits (BitVector w) Source # 
KnownNat w => FiniteBits (BitVector w) Source # 

bv :: KnownNat w => Integer -> BitVector w Source #

Construct a bit vector in a context where the width is inferrable from the type context. The Integer input (an unbounded data type, hence with an infinite-width bit representation), whether positive or negative is silently truncated to fit into the number of bits demanded by the return type.

>>> bv 0xA :: BitVector 4
0xa<4>
>>> bv 0xA :: BitVector 3
0x2<3>
>>> bv (-1) :: BitVector 8
0xff<8>
>>> bv (-1) :: BitVector 32
0xffffffff<32>

Bitwise operations (variable width)

These are functions that involve bit vectors of different lengths.

bvConcat :: BitVector v -> BitVector w -> BitVector (v + w) Source #

Concatenate two bit vectors.

>>> (bv 0xAA :: BitVector 8) `bvConcat` (bv 0xBCDEF0 :: BitVector 24)
0xaabcdef0<32>

Note that the first argument gets placed in the higher-order bits. The above example should be illustrative enough.

(<:>) :: BitVector v -> BitVector w -> BitVector (v + w) infixl 6 Source #

Infix bvConcat.

bvExtract :: forall w w'. KnownNat w' => Int -> BitVector w -> BitVector w' Source #

Slice out a smaller bit vector from a larger one. The lowest significant bit is given explicitly as an argument of type Int, and the length of the slice is inferred from a type-level context.

>>> bvExtract 12 (bv 0xAABCDEF0 :: BitVector 32) :: BitVector 8
0xcd<8>

Note that bvExtract does not do any bounds checking whatsoever; if you try and extract bits that aren't present in the input, you will get 0's.

bvZext :: forall w w'. KnownNat w' => BitVector w -> BitVector w' Source #

Zero-extend a vector to one of greater length. If given an input of greater length than the output type, this performs a truncation.

bvSext :: forall w w'. KnownNat w' => BitVector w -> BitVector w' Source #

Sign-extend a vector to one of greater length. If given an input of greater length than the output type, this performs a truncation.

Conversions to Integer

bvIntegerU :: BitVector w -> Integer Source #

Unsigned interpretation of a bit vector as a (positive) Integer.

bvIntegerS :: BitVector w -> Integer Source #

Signed interpretation of a bit vector as an Integer.