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

Copyright(c) Galois Inc. 2018
LicenseBSD-3
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.

Synopsis

BitVector type

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

BitVector datatype, parameterized by width.

Constructors

BV :: NatRepr w -> Integer -> BitVector w 
Instances
TestEquality BitVector Source # 
Instance details

Defined in Data.BitVector.Sized

Methods

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

EqF BitVector Source # 
Instance details

Defined in Data.BitVector.Sized

Methods

eqF :: BitVector a -> BitVector a -> Bool #

OrdF BitVector Source # 
Instance details

Defined in Data.BitVector.Sized

Methods

compareF :: BitVector x -> BitVector y -> OrderingF x y #

leqF :: BitVector x -> BitVector y -> Bool #

ltF :: BitVector x -> BitVector y -> Bool #

geqF :: BitVector x -> BitVector y -> Bool #

gtF :: BitVector x -> BitVector y -> Bool #

ShowF BitVector Source # 
Instance details

Defined in Data.BitVector.Sized

Methods

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

showF :: BitVector tp -> String #

showsPrecF :: Int -> BitVector tp -> String -> String #

KnownNat w => Bounded (BitVector w) Source # 
Instance details

Defined in Data.BitVector.Sized

KnownNat w => Enum (BitVector w) Source # 
Instance details

Defined in Data.BitVector.Sized

Eq (BitVector w) Source # 
Instance details

Defined in Data.BitVector.Sized

Methods

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

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

KnownNat w => Num (BitVector w) Source # 
Instance details

Defined in Data.BitVector.Sized

Ord (BitVector w) Source # 
Instance details

Defined in Data.BitVector.Sized

KnownNat w => Read (BitVector w) Source # 
Instance details

Defined in Data.BitVector.Sized

Show (BitVector w) Source # 
Instance details

Defined in Data.BitVector.Sized

KnownNat w => Ix (BitVector w) Source # 
Instance details

Defined in Data.BitVector.Sized

KnownNat w => Arbitrary (BitVector w) Source # 
Instance details

Defined in Data.BitVector.Sized

Methods

arbitrary :: Gen (BitVector w) #

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

KnownNat w => Bits (BitVector w) Source # 
Instance details

Defined in Data.BitVector.Sized

KnownNat w => FiniteBits (BitVector w) Source # 
Instance details

Defined in Data.BitVector.Sized

Pretty (BitVector w) Source # 
Instance details

Defined in Data.BitVector.Sized

KnownNat w => Random (BitVector w) Source # 
Instance details

Defined in Data.BitVector.Sized

Methods

randomR :: RandomGen g => (BitVector w, BitVector w) -> g -> (BitVector w, g) #

random :: RandomGen g => g -> (BitVector w, g) #

randomRs :: RandomGen g => (BitVector w, BitVector w) -> g -> [BitVector w] #

randoms :: RandomGen g => g -> [BitVector w] #

randomRIO :: (BitVector w, BitVector w) -> IO (BitVector w) #

randomIO :: IO (BitVector w) #

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

Construct a bit vector with a particular width, 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.

>>> bitVector 0xA :: BitVector 4
0xa
>>> bitVector 0xA :: BitVector 2
0x2

bv0 :: BitVector 0 Source #

The zero bitvector with width 0.

Bitwise operations (width-preserving)

These are alternative versions of some of the Bits functions where we do not need to know the width at compile time. They are all width-preserving.

bvAnd :: BitVector w -> BitVector w -> BitVector w Source #

Bitwise and.

bvOr :: BitVector w -> BitVector w -> BitVector w Source #

Bitwise or.

bvXor :: BitVector w -> BitVector w -> BitVector w Source #

Bitwise xor.

bvComplement :: BitVector w -> BitVector w Source #

Bitwise complement (flip every bit).

bvShift :: BitVector w -> Int -> BitVector w Source #

Bitwise shift. Uses an arithmetic right shift.

bvShiftL :: BitVector w -> Int -> BitVector w Source #

Left shift.

bvShiftRA :: BitVector w -> Int -> BitVector w Source #

Right arithmetic shift.

bvShiftRL :: BitVector w -> Int -> BitVector w Source #

Right logical shift.

bvRotate :: BitVector w -> Int -> BitVector w Source #

Bitwise rotate.

bvWidth :: BitVector w -> Int Source #

Get the width of a BitVector.

bvTestBit :: BitVector w -> Int -> Bool Source #

Test if a particular bit is set.

bvPopCount :: BitVector w -> Int Source #

Get the number of 1 bits in a BitVector.

bvTruncBits :: BitVector w -> Int -> BitVector w Source #

Truncate a bit vector to a particular width given at runtime, while keeping the type-level width constant.

Arithmetic operations (width-preserving)

bvAdd :: BitVector w -> BitVector w -> BitVector w Source #

Bitwise add.

bvMul :: BitVector w -> BitVector w -> BitVector w Source #

Bitwise multiply.

bvQuotU :: BitVector w -> BitVector w -> BitVector w Source #

Bitwise division (unsigned). Rounds to zero.

bvQuotS :: BitVector w -> BitVector w -> BitVector w Source #

Bitwise division (signed). Rounds to zero (not negative infinity).

bvRemU :: BitVector w -> BitVector w -> BitVector w Source #

Bitwise remainder after division (unsigned), when rounded to zero.

bvRemS :: BitVector w -> BitVector w -> BitVector w Source #

Bitwise remainder after division (signed), when rounded to zero (not negative infinity).

bvAbs :: BitVector w -> BitVector w Source #

Bitwise absolute value.

bvNegate :: BitVector w -> BitVector w Source #

Bitwise negation.

bvSignum :: BitVector w -> BitVector w Source #

Get the sign bit as a BitVector.

bvLTS :: BitVector w -> BitVector w -> Bool Source #

Signed less than.

bvLTU :: BitVector w -> BitVector w -> Bool Source #

Unsigned less than.

Variable-width operations

These are functions that involve bit vectors of different lengths.

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

Concatenate two bit vectors.

>>> (0xAA :: BitVector 8) `bvConcat` (0xBCDEF0 :: BitVector 24)
0xaabcdef0
>>> :type it
it :: BitVector 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.

bvConcatMany :: KnownNat w' => [BitVector w] -> BitVector w' Source #

Concatenate a list of BitVectors into a BitVector of arbitrary width. The ordering is little endian:

>>> bvConcatMany [0xAA :: BitVector 8, 0xBB] :: BitVector 16
0xbbaa
>>> bvConcatMany [0xAA :: BitVector 8, 0xBB, 0xCC] :: BitVector 16
0xbbaa

If the sum of the widths of the input BitVectors exceeds the output width, we ignore the tail end of the list.

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 (0xAABCDEF0 :: BitVector 32) :: BitVector 8
0xcd

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.

bvExtractWithRepr :: NatRepr w' -> Int -> BitVector w -> BitVector w' Source #

Unconstrained variant of bvExtract with an explicit NatRepr argument.

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.

bvZextWithRepr :: NatRepr w' -> BitVector w -> BitVector w' Source #

Unconstrained variant of bvZext with an explicit NatRepr argument.

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.

bvSextWithRepr :: NatRepr w' -> BitVector w -> BitVector w' Source #

Unconstrained variant of bvSext with an explicit NatRepr argument.

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.

Byte decomposition

bvGetBytesU :: Int -> BitVector w -> [BitVector 8] Source #

Given a BitVector of arbitrary length, decompose it into a list of bytes. Uses an unsigned interpretation of the input vector, so if you ask for more bytes that the BitVector contains, you get zeros. The result is little-endian, so the first element of the list will be the least significant byte of the input vector.