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

What4.Utils.BVDomain.Bitwise

Description

Provides a bitwise implementation of bitvector abstract domains.

Synopsis

Documentation

data Domain (w :: Nat) Source #

A bitwise interval domain, defined via a bitwise upper and lower bound. The ordering used here to construct the interval is the pointwise ordering on bits. In particular x [= y iff x .|. y == y, and a value x is in the set defined by the pair (lo,hi) just when lo [= x && x [= hi.

Constructors

BVBitInterval !Integer !Integer !Integer

BVDBitInterval mask lo hi. mask caches the value of 2^w - 1

Instances

Instances details
Show (Domain w) Source # 
Instance details

Defined in What4.Utils.BVDomain.Bitwise

Methods

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

show :: Domain w -> String #

showList :: [Domain w] -> ShowS #

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

Test 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

size :: Domain w -> Integer Source #

Compute how many concrete elements are in the abstract domain

asSingleton :: Domain w -> Maybe Integer Source #

Test if this domain contains a single value, and return it if so

nonempty :: Domain w -> Bool Source #

Returns true iff there is at least on element in this bitwise domain.

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

Returns true iff the domains have some value in common

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

Bitwise lower and upper bounds

Operations

any :: NatRepr w -> Domain w Source #

Bitwise domain containing every bitvector value

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

Return a domain containing just the given value

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

Construct a domain from bitwise lower and upper bounds

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

Unsafe constructor for internal use.

union :: Domain w -> Domain w -> Domain w Source #

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 :: (1 <= w, (w + 1) <= u) => NatRepr w -> Domain w -> NatRepr u -> Domain u Source #

shifts and rotates

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

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

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

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

bitwise logical

and :: Domain w -> Domain w -> Domain w Source #

or :: Domain w -> Domain w -> Domain w Source #

xor :: Domain w -> Domain w -> Domain w Source #

Correctness properties

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

Random generator for domain values. We always generate nonempty domain values.

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

Generate a random nonempty 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 #

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