bv-0.1.0: Bit-vectors library

MaintainerIago Abal <iago.abal@gmail.com>
Safe HaskellSafe-Inferred

Data.BitVector

Contents

Description

Implementation of bit-vectors as wrappers over Integer.

  • Bit-vectors are interpreted as unsigned integers (i.e. natural numbers) except for some very specific cases.
  • Bit-vectors are size-polymorphic insofar as most operations treat a bit-vector of size k as of size n for n >= k if required.

For documentation purposes we will write [n]k to denote a bit-vector of size n representing the natural number k.

Synopsis

Bit-vectors

type BitVector = BVSource

An alias for BV.

data BV Source

Big-endian pseudo size-polymorphic bit-vectors.

Instances

size :: BV -> IntSource

The size of a bit-vector.

width :: BV -> IntSource

An alias for size.

nat :: BV -> IntegerSource

The value of a bit-vector, as a natural number.

uint :: BV -> IntegerSource

An alias for nat.

int :: BV -> IntegerSource

2's complement value of a bit-vector.

Creation

bitVec :: Integral a => Int -> a -> BVSource

Create a bit-vector given a size and an integer value.

>>> bitVec 4 3
[4]3

This function also handles negative values.

>>> bitVec 4 (-1)
[4]15

ones :: Int -> BVSource

Create a mask of ones.

zeros :: Int -> BVSource

Create a mask of zeros.

Comparison

(==.) :: BV -> BV -> BoolSource

Fixed-size equality.

In contrast with ==, which is size-polymorphic, this equality requires both bit-vectors to be of equal size.

>>> [n]k ==. [m]k
False
>>> [n]k == [n]k
True

(/=.) :: BV -> BV -> BoolSource

Fixed-size inequality.

The negated version of ==..

Indexing

(@.) :: BV -> Int -> BoolSource

Bit indexing.

u @. i stands for the i-th bit of u.

>>> [4]2 @. 0
False
>>> [4]2 @. 1
True

(@@) :: BV -> (Int, Int) -> BVSource

Bit-string extraction.

u @@ (j,i) == fromBits (map (u @.) [j,j-1..i])
>>> [4]7 @@ (3,1)
[3]3

(!.) :: BV -> Int -> BoolSource

Reverse bit-indexing.

Index from the end of the sequenc

u !. i == u @. (size u - i - 1)
>>> [3]3 !. 0
False

least :: Int -> BV -> BVSource

Take least significant bits.

least m u == u @@ (m-1,0)

most :: Int -> BV -> BVSource

Take most significant bits.

most m u == u @@ (n-1,n-m)

msb :: BV -> BoolSource

Most significant bit.

msb u == u !. 0

lsb :: BV -> BoolSource

Least significant bit.

lsb u == u @. 0

msb1 :: BV -> IntSource

Most significant 1-bit.

Pre: input must be non-zero.

>>> msb1 [4]2
1
>>> msb1 [4]4
2

Arithmetic

sdiv :: BV -> BV -> BVSource

2's complement signed division.

srem :: BV -> BV -> BVSource

2's complement signed remainder (sign follows dividend).

smod :: BV -> BV -> BVSource

2's complement signed remainder (sign follows divisor).

lg2 :: BV -> BVSource

Ceiling logarithm base 2.

Pre: input bit-vector must be non-zero.

List-like operations

(#) :: BV -> BV -> BVSource

Concatenation of two bit-vectors.

zeroExtend :: Int -> BV -> BVSource

Logical extension.

>>> zeroExtend 3 [1]1
[4]1

signExtend :: Int -> BV -> BVSource

Arithmetic extension.

>>> signExtend 2 [2]1
[4]1
>>> signExtend 2 [2]3
[4]15

foldl_ :: (a -> Bool -> a) -> a -> BV -> aSource

foldl_ f z (fromBits [un, ..., u1, u0]) == ((((z `f` un) `f` ...) `f` u1) `f` u0)
foldl_ f e = fromBits . foldl f e . toBits

foldr_ :: (Bool -> a -> a) -> a -> BV -> aSource

foldr_ f z (fromBits [un, ..., u1, u0]) == un f (... f (u1 `f` (u0 `f` z)))
foldr_ f e = fromBits . foldr f e . toBits

reverse_ :: BV -> BVSource

reverse_ == fromBits . reverse . toBits

replicate_ :: Int -> BV -> BVSource

Pre: if replicate_ n u then n > 0 must hold.

replicate_ n == fromBits . concat . replicate n . toBits

Bitwise operations

module Data.Bits

not_ :: BV -> BVSource

An alias for complement.

nand :: BV -> BV -> BVSource

Negated .&..

nor :: BV -> BV -> BVSource

Negated .|..

xnor :: BV -> BV -> BVSource

Negated xor.

(<<.) :: BV -> BV -> BVSource

Left shift.

(>>.) :: BV -> BV -> BVSource

Logical right shift.

ashr :: BV -> BV -> BVSource

Arithmetic right shift

(<<<.) :: BV -> BV -> BVSource

Rotate left.

(>>>.) :: BV -> BV -> BVSource

Rotate right.

Conversion

fromBits :: [Bool] -> BVSource

Create a bit-vector from a big-endian list of bits.

>>> fromBits [False, False, True]
[3]1

toBits :: BV -> [Bool]Source

Create a big-endian list of bits from a bit-vector.

>>> toBits [4]11
[True, False, True, True]

Utilities

maxNat :: Integral a => Int -> aSource

Greatest natural number representable with n bits.

integerWidth :: Integer -> IntSource

Minimum width of a bit-vector to represent a given integer number.

>>> integerWith 4
3
>>> integerWith (-4)
4