what4-1.3: Solver-agnostic symbolic values support for issuing queries
Copyright(c) Galois Inc 2019-2020
LicenseBSD3
Maintainerhuffman@galois.com
Safe HaskellNone
LanguageHaskell2010

What4.Utils.BVDomain.Arith

Description

Provides an interval-based implementation of bitvector abstract domains.

Synopsis

Documentation

data Domain (w :: Nat) Source #

A value of type BVDomain w represents a set of bitvectors of width w. Each BVDomain can represent a single contiguous interval of bitvectors that may wrap around from -1 to 0.

Constructors

BVDAny !Integer

The set of all bitvectors of width w. Argument caches 2^w-1.

BVDInterval !Integer !Integer !Integer

Intervals are represented by a starting value and a size. BVDInterval mask l d represents the set of values of the form x mod 2^w for x such that l <= x <= l + d. It should satisfy the invariants 0 <= l < 2^w and 0 <= d < 2^w. The first argument caches the value 2^w-1.

Instances

Instances details
Show (Domain w) Source # 
Instance details

Defined in What4.Utils.BVDomain.Arith

Methods

showsPrec :: Int -> Domain w -> ShowS #

show :: Domain w -> String #

showList :: [Domain w] -> ShowS #

proper :: NatRepr w -> Domain w -> Bool Source #

Check if the domain satisfies its invariants

bvdMask :: Domain w -> Integer Source #

Return the bitvector mask value from this domain

member :: Domain w -> Integer -> Bool Source #

Test if the given integer value is a member of the abstract domain

pmember :: NatRepr n -> Domain n -> Integer -> Bool Source #

Check that a domain is proper, and that the given value is a member

interval :: Integer -> Integer -> Integer -> Domain w Source #

Unsafe constructor for internal use only. Caller must ensure that mask = maxUnsigned w, and that aw is non-negative.

size :: Domain w -> Integer Source #

Compute how many concrete elements are in the abstract domain

Projection functions

asSingleton :: Domain w -> Maybe Integer Source #

Return value if this is a singleton.

ubounds :: Domain w -> (Integer, Integer) Source #

Return unsigned bounds for domain.

sbounds :: 1 <= w => NatRepr w -> Domain w -> (Integer, Integer) Source #

Return signed bounds for domain.

slt :: 1 <= w => NatRepr w -> Domain w -> Domain w -> Maybe Bool Source #

Check if all elements in one domain are less than all elements in other.

ult :: 1 <= w => Domain w -> Domain w -> Maybe Bool Source #

Check if all elements in one domain are less than all elements in other.

domainsOverlap :: Domain w -> Domain w -> Bool Source #

Return true if domains contain a common element.

arithDomainData :: Domain w -> Maybe (Integer, Integer) Source #

Return the (lo,sz), the low bound and size of the given arithmetic interval. A value x is in the set defined by this domain iff (x - lo) mod w <= sz holds. Returns Nothing if the domain contains all values.

bitbounds :: Domain w -> (Integer, Integer) Source #

Return bitwise bounds for domain (i.e. logical AND of all possible values, paired with logical OR of all possible values).

unknowns :: Domain w -> Integer Source #

unknowns lo hi returns a bitmask representing the set of bit positions whose values are not constant throughout the range lo..hi.

fillright :: Integer -> Integer Source #

fillright x rounds up x to the nearest 2^n-1.

Operations

any :: 1 <= w => NatRepr w -> Domain w Source #

Represents all values

singleton :: (HasCallStack, 1 <= w) => NatRepr w -> Integer -> Domain w Source #

Create a bitvector domain representing the integer.

range :: NatRepr w -> Integer -> Integer -> Domain w Source #

range w l u returns domain containing all bitvectors formed from the w low order bits of some i in [l,u]. Note that per testBit, the least significant bit has index 0.

fromAscEltList :: 1 <= w => NatRepr w -> [Integer] -> Domain w Source #

Create an abstract domain from an ascending list of elements. The elements are assumed to be distinct.

union :: 1 <= w => Domain w -> Domain w -> Domain w Source #

Return union of two domains.

concat :: NatRepr u -> Domain u -> NatRepr v -> Domain v -> Domain (u + v) Source #

concat a y returns domain where each element in a has been concatenated with an element in y. The most-significant bits are a, and the least significant bits are y.

select :: (1 <= n, (i + n) <= w) => NatRepr i -> NatRepr n -> Domain w -> Domain n Source #

select i n a selects n bits starting from index i from a.

zext :: (1 <= w, (w + 1) <= u) => Domain w -> NatRepr u -> Domain u Source #

sext :: forall w u. (1 <= w, (w + 1) <= u) => NatRepr w -> Domain w -> NatRepr u -> Domain u Source #

Shifts

shl :: 1 <= w => NatRepr w -> Domain w -> Domain w -> Domain w Source #

lshr :: 1 <= w => NatRepr w -> Domain w -> Domain w -> Domain w Source #

ashr :: 1 <= w => NatRepr w -> Domain w -> Domain w -> Domain w Source #

Arithmetic

add :: 1 <= w => Domain w -> Domain w -> Domain w Source #

negate :: 1 <= w => Domain w -> Domain w Source #

scale :: 1 <= w => Integer -> Domain w -> Domain w Source #

mul :: 1 <= w => Domain w -> Domain w -> Domain w Source #

udiv :: 1 <= w => Domain w -> Domain w -> Domain w Source #

urem :: 1 <= w => Domain w -> Domain w -> Domain w Source #

sdiv :: 1 <= w => NatRepr w -> Domain w -> Domain w -> Domain w Source #

srem :: 1 <= w => NatRepr w -> Domain w -> Domain w -> Domain w Source #

Bitwise

not :: Domain w -> Domain w Source #

Complement bits in range.

Correctness properties

genDomain :: NatRepr w -> Gen (Domain w) Source #

Random generator for domain values

genElement :: Domain w -> Gen Integer Source #

Generate a random element from a domain

genPair :: NatRepr w -> Gen (Domain w, Integer) Source #

Generate a random domain and an element contained in that domain.

correct_zero_ext :: (1 <= w, (w + 1) <= u) => NatRepr w -> Domain w -> NatRepr u -> Integer -> Property Source #

correct_sign_ext :: (1 <= w, (w + 1) <= u) => NatRepr w -> Domain w -> NatRepr u -> Integer -> Property Source #

correct_select :: (1 <= n, (i + n) <= w) => NatRepr i -> NatRepr n -> (Domain w, Integer) -> Property Source #

correct_eq :: 1 <= n => NatRepr n -> (Domain n, Integer) -> (Domain n, Integer) -> Property Source #