{-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE ForeignFunctionInterface #-} -- | -- Module : Z3.Base.C -- Copyright : (c) Iago Abal, 2012 -- (c) David Castro, 2012 -- License : BSD3 -- Maintainer: Iago Abal , -- David Castro -- -- Low-level bindings, highly inspired by yices-painless. -- module Z3.Base.C where import Foreign import Foreign.C.Types import Foreign.C.String #include --------------------------------------------------------------------- -- * Types -- | A configuration object used to initialize logical contexts. data Z3_config -- | Logical context. This is the main Z3 data-structure. data Z3_context -- | A Lisp-link symbol. It is used to name types, constants, and functions. -- A symbol can be created using string or integers. data Z3_symbol -- | Abstract syntax tree node. That is, the data-structure used in Z3 to -- represent terms, formulas and types. data Z3_ast -- | A kind of AST used to represent types. data Z3_sort -- | A kind of AST used to represent constant and function declarations. data Z3_app -- | A kind of AST used to represent pattern and multi-patterns used to -- guide quantifier instantiation. data Z3_pattern -- | A model for the constraints asserted into the logical context. data Z3_model -- | Lifted Boolean type: false, undefined, true. type Z3_lbool = CInt -- | Values of lifted boolean type z3_l_true, z3_l_false, z3_l_undef :: Z3_lbool z3_l_true = #const Z3_L_TRUE z3_l_false = #const Z3_L_FALSE z3_l_undef = #const Z3_L_UNDEF -- | Boolean type. It is just an alias for int. type Z3_bool = CInt -- | Z3_bool values z3_true, z3_false :: Z3_lbool z3_true = #const Z3_TRUE z3_false = #const Z3_FALSE -- | Z3 String type type Z3_string = CString --------------------------------------------------------------------- -- * Create configuration -- | Create a configuration. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_config" z3_mk_config :: IO (Ptr Z3_config) -- | Delete the given configuration object. -- -- Reference: -- foreign import ccall unsafe "Z3_del_config" z3_del_config :: Ptr Z3_config -> IO () -- | Set a configuration parameter. -- -- Reference: -- foreign import ccall unsafe "Z3_set_param_value" z3_set_param_value :: Ptr Z3_config -> Z3_string -> Z3_string -> IO () --------------------------------------------------------------------- -- * Create context -- | Create a context using the given configuration. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_context" z3_mk_context :: Ptr Z3_config -> IO (Ptr Z3_context) -- | Delete the given logical context. -- -- Reference: -- foreign import ccall unsafe "Z3_del_context" z3_del_context :: Ptr Z3_context -> IO () --------------------------------------------------------------------- -- * Symbols -- | Create a Z3 symbol using a C string. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_string_symbol" z3_mk_string_symbol :: Ptr Z3_context -> Z3_string -> IO (Ptr Z3_symbol) --------------------------------------------------------------------- -- * Sorts -- TODO Sorts: Z3_is_eq_sort -- TODO Sorts: Z3_mk_uninterpreted_sort -- | Create the Boolean type. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_bool_sort" z3_mk_bool_sort :: Ptr Z3_context -> IO (Ptr Z3_sort) -- | Create an integer type. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_int_sort" z3_mk_int_sort :: Ptr Z3_context -> IO (Ptr Z3_sort) -- | Create a real type. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_real_sort" z3_mk_real_sort :: Ptr Z3_context -> IO (Ptr Z3_sort) -- TODO Sorts: from Z3_mk_real_sort on --------------------------------------------------------------------- -- * Constants and Applications -- TODO Constants and Applications: Z3_mk_func_decl -- TODO Constants and Applications: Z3_mk_app -- | Declare and create a constant. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_const" z3_mk_const :: Ptr Z3_context -> Ptr Z3_symbol -> Ptr Z3_sort -> IO (Ptr Z3_ast) -- TODO Constants and Applications: Z3_mk_fresh_func_decl -- TODO Constants and Applications: Z3_mk_fresh_const --------------------------------------------------------------------- -- * Propositional Logic and Equality -- | Create an AST node representing /true/. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_true" z3_mk_true :: Ptr Z3_context -> IO (Ptr Z3_ast) -- | Create an AST node representing /false/. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_false" z3_mk_false :: Ptr Z3_context -> IO (Ptr Z3_ast) -- | Create an AST node representing l = r. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_eq" z3_mk_eq :: Ptr Z3_context -> Ptr Z3_ast -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- TODO: Z3_mk_distinct -- | Create an AST node representing not(a). -- -- Reference: -- foreign import ccall unsafe "Z3_mk_not" z3_mk_not :: Ptr Z3_context -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Create an AST node representing an if-then-else: ite(t1, t2, t3). -- -- Reference: -- foreign import ccall unsafe "Z3_mk_ite" z3_mk_ite :: Ptr Z3_context -> Ptr Z3_ast -> Ptr Z3_ast -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Create an AST node representing t1 iff t2. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_iff" z3_mk_iff :: Ptr Z3_context -> Ptr Z3_ast -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Create an AST node representing t1 implies t2. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_implies" z3_mk_implies :: Ptr Z3_context -> Ptr Z3_ast -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Create an AST node representing t1 xor t2. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_xor" z3_mk_xor :: Ptr Z3_context -> Ptr Z3_ast -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Create an AST node representing args[0] and ... and args[num_args-1]. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_and" z3_mk_and :: Ptr Z3_context -> CUInt -> Ptr (Ptr Z3_ast) -> IO (Ptr Z3_ast) -- | Create an AST node representing args[0] or ... or args[num_args-1]. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_or" z3_mk_or :: Ptr Z3_context -> CUInt -> Ptr (Ptr Z3_ast) -> IO (Ptr Z3_ast) --------------------------------------------------------------------- -- * Arithmetic: Integers and Reals -- | Create an AST node representing args[0] + ... + args[num_args-1]. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_add" z3_mk_add :: Ptr Z3_context -> CUInt -> Ptr (Ptr Z3_ast) -> IO (Ptr Z3_ast) -- | Create an AST node representing args[0] * ... * args[num_args-1]. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_mul" z3_mk_mul :: Ptr Z3_context -> CUInt -> Ptr (Ptr Z3_ast) -> IO (Ptr Z3_ast) -- | Create an AST node representing args[0] - ... - args[num_args - 1]. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_sub" z3_mk_sub :: Ptr Z3_context -> CUInt -> Ptr (Ptr Z3_ast) -> IO (Ptr Z3_ast) -- | Create an AST node representing -arg. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_unary_minus" z3_mk_unary_minus :: Ptr Z3_context -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Create an AST node representing arg1 div arg2. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_div" z3_mk_div :: Ptr Z3_context -> Ptr Z3_ast -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Create an AST node representing arg1 mod arg2. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_mod" z3_mk_mod :: Ptr Z3_context -> Ptr Z3_ast -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Create an AST node representing arg1 rem arg2. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_rem" z3_mk_rem :: Ptr Z3_context -> Ptr Z3_ast -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Create less than. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_lt" z3_mk_lt :: Ptr Z3_context -> Ptr Z3_ast -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Create less than or equal to. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_le" z3_mk_le :: Ptr Z3_context -> Ptr Z3_ast -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Create greater than. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_gt" z3_mk_gt :: Ptr Z3_context -> Ptr Z3_ast -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Create greater than or equal to. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_ge" z3_mk_ge :: Ptr Z3_context -> Ptr Z3_ast -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Coerce an integer to a real. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_int2real" z3_mk_int2real :: Ptr Z3_context -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Coerce a real to an integer. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_real2int" z3_mk_real2int :: Ptr Z3_context -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Check if a real number is an integer. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_is_int" z3_mk_is_int :: Ptr Z3_context -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- TODO Bit-vectors, Arrays, Sets --------------------------------------------------------------------- -- * Numerals -- | Create a numeral of a given sort. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_numeral" z3_mk_numeral :: Ptr Z3_context -> Z3_string -> Ptr Z3_sort -> IO (Ptr Z3_ast) -- | Create a real from a fraction. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_real" z3_mk_real :: Ptr Z3_context -> CInt -> CInt -> IO (Ptr Z3_ast) -- | Create a numeral of a given sort. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_int" z3_mk_int :: Ptr Z3_context -> CInt -> Ptr Z3_sort -> IO (Ptr Z3_ast) -- | Create a numeral of a given sort. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_unsigned_int" z3_mk_unsigned_int :: Ptr Z3_context -> CUInt -> Ptr Z3_sort -> IO (Ptr Z3_ast) -- | Create a numeral of a given sort. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_int64" z3_mk_int64 :: Ptr Z3_context -> CLLong -> Ptr Z3_sort -> IO (Ptr Z3_ast) -- | Create a numeral of a given sort. -- -- Reference: -- foreign import ccall unsafe "Z3_mk_unsigned_int64" z3_mk_unsigned_int64 :: Ptr Z3_context -> CULLong -> Ptr Z3_sort -> IO (Ptr Z3_ast) -- TODO Quantifiers --------------------------------------------------------------------- -- * Accessors -- | Return Z3_L_TRUE if a is true, Z3_L_FALSE if it is false, and Z3_L_UNDEF -- otherwise. -- -- Reference: -- foreign import ccall unsafe "Z3_get_bool_value" z3_get_bool_value :: Ptr Z3_context -> Ptr Z3_ast -> IO Z3_lbool -- | Return numeral value, as a string of a numeric constant term. -- -- Reference: -- foreign import ccall unsafe "Z3_get_numeral_string" z3_get_numeral_string :: Ptr Z3_context -> Ptr Z3_ast -> IO Z3_string -- | Return the numerator (as a numeral AST) of a numeral AST of sort Int. -- -- Reference: -- foreign import ccall unsafe "Z3_get_numerator" z3_get_numerator :: Ptr Z3_context -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- | Return the denominator (as a numeral AST) of a numeral AST of sort Real. -- -- Reference: -- foreign import ccall unsafe "Z3_get_denominator" z3_get_denominator :: Ptr Z3_context -> Ptr Z3_ast -> IO (Ptr Z3_ast) -- TODO Modifiers --------------------------------------------------------------------- -- * Models -- | Evaluate the AST node t in the given model. Return Z3_TRUE if succeeded, -- and store the result in v. -- -- Reference: -- foreign import ccall unsafe "Z3_eval" z3_eval :: Ptr Z3_context -> Ptr Z3_model -> Ptr Z3_ast -> Ptr (Ptr Z3_ast) -> IO Z3_bool --------------------------------------------------------------------- -- * Constraints -- TODO Constraints: Z3_push -- TODO Constraints: Z3_pop -- TODO Constraints: Z3_get_num_scopes -- TODO Constraints: Z3_persist_ast -- | Assert a constraing into the logical context. -- -- Reference: -- foreign import ccall unsafe "Z3_assert_cnstr" z3_assert_cnstr :: Ptr Z3_context -> Ptr Z3_ast -> IO () -- | Check whether the given logical context is consistent or not. -- -- Reference : -- foreign import ccall unsafe "Z3_check_and_get_model" z3_check_and_get_model :: Ptr Z3_context -> Ptr (Ptr Z3_model) -> IO Z3_lbool -- | Check whether the given logical context is consistent or not. -- -- Reference: -- foreign import ccall unsafe "Z3_check" z3_check :: Ptr Z3_context -> IO Z3_lbool -- TODO Constraints: Z3_check_assumptions -- TODO Constraints: Z3_get_implied_equalities -- | Delete a model object. -- -- Reference: -- foreign import ccall unsafe "Z3_del_model" z3_del_model :: Ptr Z3_context -> Ptr Z3_model -> IO () -- TODO From section 'Constraints' on.