z3-0.3.0: Bindings for the Z3 Theorem Prover

Copyright(c) Iago Abal, 2012-2013 (c) David Castro, 2012-2013
LicenseBSD3
MaintainerIago Abal <iago.abal@gmail.com>, David Castro <david.castro.dcp@gmail.com>
Safe HaskellNone
LanguageHaskell98

Z3.Base

Contents

Description

Low-level bindings to Z3 API.

Synopsis

Types

data Config Source

A Z3 configuration object.

Instances

data Context Source

A Z3 logical context.

Instances

data Symbol Source

A Z3 Lisp-link symbol.

data AST Source

A Z3 AST node.

data Sort Source

Kind of Z3 AST representing types.

data FuncDecl Source

Kind of AST used to represent function symbols.

data App Source

A kind of Z3 AST used to represent constant and function declarations.

Instances

data Pattern Source

A kind of AST used to represent pattern and multi-patterns used to guide quantifier instantiation.

data Model Source

A model for the constraints asserted into the logical context.

Instances

data Params Source

A Z3 parameter set. Starting at Z3 4.0, parameter sets are used to configure many components such as: simplifiers, tactics, solvers, etc.

Instances

data Solver Source

A Z3 solver engine

Instances

Satisfiability result

data Result Source

Result of a satisfiability check.

Constructors

Sat 
Unsat 
Undef 

Configuration

withConfig :: (Config -> IO a) -> IO a Source

Run a computation using a temporally created configuration.

Context

withContext :: Config -> (Context -> IO a) -> IO a Source

Run a computation using a temporally created context.

Symbols

Sorts

mkBvSort :: Context -> Int -> IO Sort Source

Create a bit-vector type of the given size.

This type can also be seen as a machine integer.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#gaeed000a1bbb84b6ca6fdaac6cf0c1688

Constants and Applications

mkFuncDecl :: Context -> Symbol -> [Sort] -> Sort -> IO FuncDecl Source

A Z3 function

mkIte :: Context -> AST -> AST -> AST -> IO AST Source

Create an AST node representing an if-then-else: ite(t1, t2, t3).

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#ga94417eed5c36e1ad48bcfc8ad6e83547

mkAnd :: Context -> [AST] -> IO AST Source

Create an AST node representing args[0] and ... and args[num_args-1].

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#gacde98ce4a8ed1dde50b9669db4838c61

mkOr :: Context -> [AST] -> IO AST Source

Create an AST node representing args[0] or ... or args[num_args-1].

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#ga00866d16331d505620a6c515302021f9

mkDistinct :: Context -> [AST] -> IO AST Source

The distinct construct is used for declaring the arguments pairwise distinct.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#gaa076d3a668e0ec97d61744403153ecf7

mkAdd :: Context -> [AST] -> IO AST Source

Create an AST node representing args[0] + ... + args[num_args-1].

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#ga4e4ac0a4e53eee0b4b0ef159ed7d0cd5

mkMul :: Context -> [AST] -> IO AST Source

Create an AST node representing args[0] * ... * args[num_args-1].

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#gab9affbf8401a18eea474b59ad4adc890

mkSub :: Context -> [AST] -> IO AST Source

Create an AST node representing args[0] - ... - args[num_args - 1].

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#ga4f5fea9b683f9e674fd8f14d676cc9a9

Bit-vectors

mkExtract :: Context -> Int -> Int -> AST -> IO AST Source

Extract the bits high down to low from a bitvector of size m to yield a new bitvector of size n, where n = high - low + 1.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#ga32d2fe7563f3e6b114c1b97b205d4317

mkSignExt :: Context -> Int -> AST -> IO AST Source

Sign-extend of the given bit-vector to the (signed) equivalent bitvector of size m+i, where m is the size of the given bit-vector.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#gad29099270b36d0680bb54b560353c10e

mkZeroExt :: Context -> Int -> AST -> IO AST Source

Extend the given bit-vector with zeros to the (unsigned) equivalent bitvector of size m+i, where m is the size of the given bit-vector.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#gac9322fae11365a78640baf9078c428b3

mkBv2int :: Context -> AST -> Bool -> IO AST Source

Create an integer from the bit-vector argument t1. If is_signed is false, then the bit-vector t1 is treated as unsigned. So the result is non-negative and in the range [0..2^N-1], where N are the number of bits in t1. If is_signed is true, t1 is treated as a signed bit-vector.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#gac87b227dc3821d57258d7f53a28323d4

mkBvnegNoOverflow :: Context -> AST -> IO AST Source

Check that bit-wise negation does not overflow when t1 is interpreted as a signed bit-vector.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#gae9c5d72605ddcd0e76657341eaccb6c7

mkBvaddNoOverflow :: Context -> AST -> AST -> Bool -> IO AST Source

Create a predicate that checks that the bit-wise addition of t1 and t2 does not overflow.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#ga88f6b5ec876f05e0d7ba51e96c4b077f

mkBvaddNoUnderflow :: Context -> AST -> AST -> IO AST Source

Create a predicate that checks that the bit-wise signed addition of t1 and t2 does not underflow.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#ga1e2b1927cf4e50000c1600d47a152947

mkBvsubNoOverflow :: Context -> AST -> AST -> IO AST Source

Create a predicate that checks that the bit-wise signed subtraction of t1 and t2 does not overflow.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#ga785f8127b87e0b42130e6d8f52167d7c

mkBvsubNoUnderflow :: Context -> AST -> AST -> IO AST Source

Create a predicate that checks that the bit-wise subtraction of t1 and t2 does not underflow.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#ga6480850f9fa01e14aea936c88ff184c4

mkBvmulNoOverflow :: Context -> AST -> AST -> Bool -> IO AST Source

Create a predicate that checks that the bit-wise multiplication of t1 and t2 does not overflow.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#ga86f4415719d295a2f6845c70b3aaa1df

mkBvmulNoUnderflow :: Context -> AST -> AST -> IO AST Source

Create a predicate that checks that the bit-wise signed multiplication of t1 and t2 does not underflow.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#ga501ccc01d737aad3ede5699741717fda

mkBvsdivNoOverflow :: Context -> AST -> AST -> IO AST Source

Create a predicate that checks that the bit-wise signed division of t1 and t2 does not overflow.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#gaa17e7b2c33dfe2abbd74d390927ae83e

Arrays

mkSelect :: Context -> AST -> AST -> IO AST Source

Array read. The argument a is the array and i is the index of the array that gets read.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#ga38f423f3683379e7f597a7fe59eccb67

mkArrayDefault :: Context -> AST -> IO AST Source

Access the array default value. Produces the default range value, for arrays that can be represented as finite maps with a default range value.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#ga78e89cca82f0ab4d5f4e662e5e5fba7d

Numerals

mkInt :: Integral a => Context -> a -> IO AST Source

Create a numeral of sort int.

mkReal :: Real r => Context -> r -> IO AST Source

Create a numeral of sort real.

Quantifiers

mkForall :: Context -> [Pattern] -> [Symbol] -> [Sort] -> AST -> IO AST Source

mkExists :: Context -> [Pattern] -> [Symbol] -> [Sort] -> AST -> IO AST Source

Accessors

getBool :: Context -> AST -> IO (Maybe Bool) Source

Return Z3_L_TRUE if a is true, Z3_L_FALSE if it is false, and Z3_L_UNDEF otherwise.

Reference: http://research.microsoft.com/en-us/um/redmond/projects/z3/group__capi.html#ga133aaa1ec31af9b570ed7627a3c8c5a4

getInt :: Context -> AST -> IO Integer Source

Return Z3Int value

getReal :: Context -> AST -> IO Rational Source

Return Z3Real value

Models

eval :: Context -> Model -> AST -> IO (Maybe AST) Source

Evaluate an AST node in the given model.

evalT :: Traversable t => Context -> Model -> t AST -> IO (Maybe (t AST)) Source

Evaluate a collection of AST nodes in the given model.

Constraints

Parameters

Solvers

data Logic Source

Warning: New Z3 API support is still incomplete and fragile: you may experience segmentation faults!

Solvers available in Z3.

These are described at http://smtlib.cs.uiowa.edu/logics.html

WARNING: Support for solvers is fragile, you may experience segmentation faults!

Constructors

AUFLIA

Closed formulas over the theory of linear integer arithmetic and arrays extended with free sort and function symbols but restricted to arrays with integer indices and values.

AUFLIRA

Closed linear formulas with free sort and function symbols over one- and two-dimentional arrays of integer index and real value.

AUFNIRA

Closed formulas with free function and predicate symbols over a theory of arrays of arrays of integer index and real value.

LRA

Closed linear formulas in linear real arithmetic.

QF_ABV

Closed quantifier-free formulas over the theory of bitvectors and bitvector arrays.

QF_AUFBV

Closed quantifier-free formulas over the theory of bitvectors and bitvector arrays extended with free sort and function symbols.

QF_AUFLIA

Closed quantifier-free linear formulas over the theory of integer arrays extended with free sort and function symbols.

QF_AX

Closed quantifier-free formulas over the theory of arrays with extensionality.

QF_BV

Closed quantifier-free formulas over the theory of fixed-size bitvectors.

QF_IDL

Difference Logic over the integers. In essence, Boolean combinations of inequations of the form x - y < b where x and y are integer variables and b is an integer constant.

QF_LIA

Unquantified linear integer arithmetic. In essence, Boolean combinations of inequations between linear polynomials over integer variables.

QF_LRA

Unquantified linear real arithmetic. In essence, Boolean combinations of inequations between linear polynomials over real variables.

QF_NIA

Quantifier-free integer arithmetic.

QF_NRA

Quantifier-free real arithmetic.

QF_RDL

Difference Logic over the reals. In essence, Boolean combinations of inequations of the form x - y < b where x and y are real variables and b is a rational constant.

QF_UF

Unquantified formulas built over a signature of uninterpreted (i.e., free) sort and function symbols.

QF_UFBV

Unquantified formulas over bitvectors with uninterpreted sort function and symbols.

QF_UFIDL

Difference Logic over the integers (in essence) but with uninterpreted sort and function symbols.

QF_UFLIA

Unquantified linear integer arithmetic with uninterpreted sort and function symbols.

QF_UFLRA

Unquantified linear real arithmetic with uninterpreted sort and function symbols.

QF_UFNRA

Unquantified non-linear real arithmetic with uninterpreted sort and function symbols.

UFLRA

Linear real arithmetic with uninterpreted sort and function symbols.

UFNIA

Non-linear integer arithmetic with uninterpreted sort and function symbols.

Instances

mkSolver :: Context -> IO Solver Source

Warning: New Z3 API support is still incomplete and fragile: you may experience segmentation faults!

mkSimpleSolver :: Context -> IO Solver Source

Warning: New Z3 API support is still incomplete and fragile: you may experience segmentation faults!

mkSolverForLogic :: Context -> Logic -> IO Solver Source

Warning: New Z3 API support is still incomplete and fragile: you may experience segmentation faults!

solverSetParams :: Context -> Solver -> Params -> IO () Source

Warning: New Z3 API support is still incomplete and fragile: you may experience segmentation faults!

solverPush :: Context -> Solver -> IO () Source

Warning: New Z3 API support is still incomplete and fragile: you may experience segmentation faults!

solverPop :: Context -> Solver -> Int -> IO () Source

Warning: New Z3 API support is still incomplete and fragile: you may experience segmentation faults!

solverReset :: Context -> Solver -> IO () Source

Warning: New Z3 API support is still incomplete and fragile: you may experience segmentation faults!

solverAssertCnstr :: Context -> Solver -> AST -> IO () Source

Warning: New Z3 API support is still incomplete and fragile: you may experience segmentation faults!

solverAssertAndTrack :: Context -> Solver -> AST -> AST -> IO () Source

Warning: New Z3 API support is still incomplete and fragile: you may experience segmentation faults!

solverCheck :: Context -> Solver -> IO Result Source

Warning: New Z3 API support is still incomplete and fragile: you may experience segmentation faults!

solverCheckAndGetModel :: Context -> Solver -> IO (Result, Maybe Model) Source

Warning: New Z3 API support is still incomplete and fragile: you may experience segmentation faults!

solverGetReasonUnknown :: Context -> Solver -> IO String Source

Warning: New Z3 API support is still incomplete and fragile: you may experience segmentation faults!

String Conversion

data ASTPrintMode Source

Pretty-printing mode for converting ASTs to strings. The mode can be one of the following:

  • Z3_PRINT_SMTLIB_FULL: Print AST nodes in SMTLIB verbose format.
  • Z3_PRINT_LOW_LEVEL: Print AST nodes using a low-level format.
  • Z3_PRINT_SMTLIB_COMPLIANT: Print AST nodes in SMTLIB 1.x compliant format.
  • Z3_PRINT_SMTLIB2_COMPLIANT: Print AST nodes in SMTLIB 2.x compliant format.

setASTPrintMode :: Context -> ASTPrintMode -> IO () Source

Set the pretty-printing mode for converting ASTs to strings.

astToString :: Context -> AST -> IO String Source

Convert an AST to a string.

patternToString :: Context -> Pattern -> IO String Source

Convert a pattern to a string.

sortToString :: Context -> Sort -> IO String Source

Convert a sort to a string.

funcDeclToString :: Context -> FuncDecl -> IO String Source

Convert a FuncDecl to a string.

Error Handling

data Z3Error Source

Z3 exceptions.

Constructors

Z3Error