package bap-std
Install
dune-project
Dependency
Authors
Maintainers
Sources
sha256=63ada71fa4f602bd679174dc6bf780d54aeded40ad4ec20d256df15886e3d2d5
md5=b8b1aff8c6846f2213eafc54de07b304
doc/bap/Bap/Std/Bil/index.html
Module Std.Bil
Main BIL module.
The module specifies Binary Instruction Language (BIL). A language to define a semantics of instructions. The semantics of the BIL language is defined at [1].
The language is defined using algebraic types. For each BIL constructor a smart constructor is defined with the same (if syntax allows) name. This allows to use BIL as a DSL embedded into OCaml:
Bil.([
v := src lsr i32 1;
r := src;
s := i32 31;
while_ (var v <> i32 0) [
r := var r lsl i32 1;
r := var r lor (var v land i32 1);
v := var v lsr i32 1;
s := var s - i32 1;
];
dst := var r lsl var s;
])where i32 is defined as let i32 x = Bil.int (Word.of_int ~width:32 x) and v,r,s are some variables of type var; and src, dst are expressions of type exp.
@see <https://github.com/BinaryAnalysisPlatform/bil/releases/download/v0.1/bil.pdf> [1]: BIL Semantics.
module Types : sig ... endinclude all constructors into Bil namespace
include module type of Types
with type cast = Types.cast
and type binop = Types.binop
and type unop = Types.unop
and type typ = Types.typ
and type var = Types.var
and type exp = Types.exp
and type stmt = Types.stmt
type var = Types.vartype cast = Types.cast = Different forms of casting
val bin_size_cast : cast Core_kernel.Bin_prot.Size.sizerval bin_write_cast : cast Core_kernel.Bin_prot.Write.writerval bin_writer_cast : cast Core_kernel.Bin_prot.Type_class.writerval bin_read_cast : cast Core_kernel.Bin_prot.Read.readerval __bin_read_cast__ : (int -> cast) Core_kernel.Bin_prot.Read.readerval bin_reader_cast : cast Core_kernel.Bin_prot.Type_class.readerval bin_cast : cast Core_kernel.Bin_prot.Type_class.tval sexp_of_cast : cast -> Ppx_sexp_conv_lib.Sexp.tval cast_of_sexp : Ppx_sexp_conv_lib.Sexp.t -> casttype binop = Types.binop = | PLUS(*Integer addition. (commutative, associative)
*)| MINUS(*Subtract second integer from first.
*)| TIMES(*Integer multiplication. (commutative, associative)
*)| DIVIDE(*Unsigned integer division.
*)| SDIVIDE(*Signed integer division.
*)| MOD(*Unsigned modulus.
*)| SMOD(*Signed modulus.
*)| LSHIFT(*Left shift.
*)| RSHIFT(*Right shift, zero padding.
*)| ARSHIFT(*Right shift, sign extend.
*)| AND(*Bitwise and. (commutative, associative)
*)| OR(*Bitwise or. (commutative, associative)
*)| XOR(*Bitwise xor. (commutative, associative)
*)| EQ(*Equals. (commutative) (associative on booleans)
*)| NEQ(*Not equals. (commutative) (associative on booleans)
*)| LT(*Unsigned less than.
*)| LE(*Unsigned less than or equal to.
*)| SLT(*Signed less than.
*)| SLE(*Signed less than or equal to.
*)
Binary operations implemented in the BIL
val bin_size_binop : binop Core_kernel.Bin_prot.Size.sizerval bin_write_binop : binop Core_kernel.Bin_prot.Write.writerval bin_writer_binop : binop Core_kernel.Bin_prot.Type_class.writerval bin_read_binop : binop Core_kernel.Bin_prot.Read.readerval __bin_read_binop__ : (int -> binop) Core_kernel.Bin_prot.Read.readerval bin_reader_binop : binop Core_kernel.Bin_prot.Type_class.readerval bin_binop : binop Core_kernel.Bin_prot.Type_class.tval sexp_of_binop : binop -> Ppx_sexp_conv_lib.Sexp.tval binop_of_sexp : Ppx_sexp_conv_lib.Sexp.t -> binopUnary operations implemented in the IR
val bin_size_unop : unop Core_kernel.Bin_prot.Size.sizerval bin_write_unop : unop Core_kernel.Bin_prot.Write.writerval bin_writer_unop : unop Core_kernel.Bin_prot.Type_class.writerval bin_read_unop : unop Core_kernel.Bin_prot.Read.readerval __bin_read_unop__ : (int -> unop) Core_kernel.Bin_prot.Read.readerval bin_reader_unop : unop Core_kernel.Bin_prot.Type_class.readerval bin_unop : unop Core_kernel.Bin_prot.Type_class.tval sexp_of_unop : unop -> Ppx_sexp_conv_lib.Sexp.tval unop_of_sexp : Ppx_sexp_conv_lib.Sexp.t -> unoptype exp = Types.exp = | Load of exp * exp * endian * size(*load from memory
*)| Store of exp * exp * exp * endian * size(*store to memory
*)| BinOp of binop * exp * exp(*binary operation
*)| UnOp of unop * exp(*unary operation
*)| Var of var(*variable
*)| Int of word(*immediate value
*)| Cast of cast * int * exp(*casting
*)| Let of var * exp * exp(*let-binding
*)| Unknown of string * typ(*unknown or undefined value
*)| Ite of exp * exp * exp(*if-then-else expression
*)| Extract of int * int * exp(*extract portion of word
*)| Concat of exp * exp(*concatenate two words
*)
BIL expression variants
val bin_size_exp : exp Core_kernel.Bin_prot.Size.sizerval bin_write_exp : exp Core_kernel.Bin_prot.Write.writerval bin_writer_exp : exp Core_kernel.Bin_prot.Type_class.writerval bin_size_typ : typ Core_kernel.Bin_prot.Size.sizerval bin_write_typ : typ Core_kernel.Bin_prot.Write.writerval bin_writer_typ : typ Core_kernel.Bin_prot.Type_class.writerval bin_read_exp : exp Core_kernel.Bin_prot.Read.readerval __bin_read_exp__ : (int -> exp) Core_kernel.Bin_prot.Read.readerval bin_reader_exp : exp Core_kernel.Bin_prot.Type_class.readerval bin_read_typ : typ Core_kernel.Bin_prot.Read.readerval __bin_read_typ__ : (int -> typ) Core_kernel.Bin_prot.Read.readerval bin_reader_typ : typ Core_kernel.Bin_prot.Type_class.readerval bin_exp : exp Core_kernel.Bin_prot.Type_class.tval bin_typ : typ Core_kernel.Bin_prot.Type_class.tval sexp_of_exp : exp -> Ppx_sexp_conv_lib.Sexp.tval sexp_of_typ : typ -> Ppx_sexp_conv_lib.Sexp.tval exp_of_sexp : Ppx_sexp_conv_lib.Sexp.t -> expval typ_of_sexp : Ppx_sexp_conv_lib.Sexp.t -> typtype stmt = Types.stmt = | Move of var * exp(*assign value of expression to variable
*)| Jmp of exp(*jump to absolute address
*)| Special of string(*Statement with semantics not expressible in BIL
*)| While of exp * stmt list(*while loops
*)| If of exp * stmt list * stmt list(*if/then/else statement
*)| CpuExn of int(*CPU exception
*)
val bin_size_stmt : stmt Core_kernel.Bin_prot.Size.sizerval bin_write_stmt : stmt Core_kernel.Bin_prot.Write.writerval bin_writer_stmt : stmt Core_kernel.Bin_prot.Type_class.writerval bin_read_stmt : stmt Core_kernel.Bin_prot.Read.readerval __bin_read_stmt__ : (int -> stmt) Core_kernel.Bin_prot.Read.readerval bin_reader_stmt : stmt Core_kernel.Bin_prot.Type_class.readerval bin_stmt : stmt Core_kernel.Bin_prot.Type_class.tval sexp_of_stmt : stmt -> Ppx_sexp_conv_lib.Sexp.tval stmt_of_sexp : Ppx_sexp_conv_lib.Sexp.t -> stmttype t = stmt listinclude Core_kernel.Bin_prot.Binable.S with type t := t
val bin_size_t : t Bin_prot.Size.sizerval bin_write_t : t Bin_prot.Write.writerval bin_read_t : t Bin_prot.Read.readerval __bin_read_t__ : (int -> t) Bin_prot.Read.readerval bin_writer_t : t Bin_prot.Type_class.writerval bin_reader_t : t Bin_prot.Type_class.readerval bin_t : t Bin_prot.Type_class.ttype vars = (var, var_compare) Core_kernel.Set.tinclude Regular.Std.Printable.S with type t := t
val to_string : t -> stringto_string x returns a human-readable representation of x
val str : unit -> t -> stringstr () t is formatted output function that matches "%a" conversion format specifier in functions, that prints to string, e.g., sprintf, failwithf, errorf and, surprisingly all Lwt printing function, including Lwt_io.printf and logging (or any other function with type ('a,unit,string,...) formatN`. Example:
Or_error.errorf "type %a is not valid for %a"
Type.str ty Exp.str expval pps : unit -> t -> stringsynonym for str
val ppo : Core_kernel.Out_channel.t -> t -> unitwill print to a standard output_channel, useful for using in printf, fprintf, etc.
val pp_seq : Format.formatter -> t Core_kernel.Sequence.t -> unitprints a sequence of values of type t
this will include pp function from Core that has type t printer, and can be used in Format.printf family of functions
include Core_kernel.Pretty_printer.S with type t := t
val pp : Base__.Formatter.t -> t -> unitinclude Regular.Std.Data.S with type t := t
name,Ver v,desc information attached to a particular reader or writer.
Data representation version. After any change in data representation the version should be increased.
Serializers that are derived from a data representation must have the same version as a version of the data structure, from which it is derived. This kind of serializers can only read and write data of the same version.
Other serializers can actually read and write data independent on its representation version. A serializer, that can't store data of current version simply shouldn't be added to a set of serializers.
It is assumed, that if a reader and a writer has the same name and version, then whatever was written by the writer should be readable by the reader. The round-trip equality is not required, thus it is acceptable if some information is lost.
It is also possible, that a reader and a writer that has the same name are compatible. In that case it is recommended to use semantic versioning.
val size_in_bytes : ?ver:string -> ?fmt:string -> t -> intsize_in_bytes ?ver ?fmt datum returns the amount of bytes that is needed to represent datum in the given format and version
val of_bytes : ?ver:string -> ?fmt:string -> Regular.Std.bytes -> tof_bytes ?ver ?fmt bytes deserializes a value from bytes.
val to_bytes : ?ver:string -> ?fmt:string -> t -> Regular.Std.bytesto_bytes ?ver ?fmt datum serializes a datum to a sequence of bytes.
val blit_to_bytes :
?ver:string ->
?fmt:string ->
Regular.Std.bytes ->
t ->
int ->
unitblit_to_bytes ?ver ?fmt buffer datum offset copies a serialized representation of datum into a buffer, starting from the offset.
val of_bigstring : ?ver:string -> ?fmt:string -> Core_kernel.bigstring -> tof_bigstring ?ver ?fmt buf deserializes a datum from bigstring
val to_bigstring : ?ver:string -> ?fmt:string -> t -> Core_kernel.bigstringof_bigstring ?ver ?fmt datum serializes a datum to a sequence of bytes represented as bigstring
val blit_to_bigstring :
?ver:string ->
?fmt:string ->
Core_kernel.bigstring ->
t ->
int ->
unitblit_to_bigstring ?ver ?fmt buffer datum offset copies a serialized representation of datum into a buffer, starting from offset.
module Io : sig ... endInput/Output functions for the given datum.
module Cache : sig ... endData cache.
val add_reader :
?desc:string ->
ver:string ->
string ->
t Regular.Std.reader ->
unitadd_reader ?desc ~ver name reader registers a new reader with a provided name, version ver and optional description desc
val add_writer :
?desc:string ->
ver:string ->
string ->
t Regular.Std.writer ->
unitadd_writer ?desc ~ver name writer registers a new writer with a provided name, version ver and optional description desc
val available_readers : unit -> info listavailable_reader () lists available readers for the data type
val default_reader : unit -> infodefault_reader returns information about default reader
set_default_reader ?ver name sets new default reader. If version is not specified then the latest available version is used. Raises an exception if a reader with a given name doesn't exist.
with_reader ?ver name operation temporary sets a default reader to a reader with a specified name and version. The default reader is restored after operation is finished.
val available_writers : unit -> info listavailable_writer () lists available writers for the data type
val default_writer : unit -> infodefault_writer returns information about the default writer
set_default_writer ?ver name sets new default writer. If version is not specified then the latest available version is used. Raises an exception if a writer with a given name doesn't exist.
with_writer ?ver name operation temporary sets a default writer to a writer with a specified name and version. The default writer is restored after operation is finished.
val default_printer : unit -> info optiondefault_writer optionally returns an information about default printer
set_default_printer ?ver name sets new default printer. If version is not specified then the latest available version is used. Raises an exception if a printer with a given name doesn't exist.
with_printer ?ver name operation temporary sets a default printer to a printer with a specified name and version. The default printer is restored after operation is finished.
Low level access to serializers
val find_reader : ?ver:string -> string -> t Regular.Std.reader optionfind_reader ?ver name lookups a reader with a given name. If version is not specified, then a reader with maximum version is returned.
val find_writer : ?ver:string -> string -> t Regular.Std.writer optionfind_writer ?ver name lookups a writer with a given name. If version is not specified, then a writer with maximum version is returned.
val domain : stmt list Bap_knowledge.Knowledge.domainBil is an instance of Domain.
A flat domain with the empty Bil program being the empty element.
val persistent : stmt list Bap_knowledge.Knowledge.persistentInstance of the persistence class
val slot :
(Bap_core_theory.Theory.Program.Semantics.cls, stmt list)
Bap_knowledge.Knowledge.slotThe denotation of the program semantics as a BIL program.
val code : (Bap_core_theory.Theory.program, stmt list) Bap_core_theory.KB.slotThe representation of the program as a BIL program.
val pp_binop : Format.formatter -> binop -> unitprintf "%a" pp_binop op prints a binary operation op.
val pp_unop : Format.formatter -> unop -> unitprintf "%a" pp_unop op prints an unary operation op
val pp_cast : Format.formatter -> cast -> unitprintf "%a" pp_cast t prints a cast type t
val string_of_binop : binop -> stringstring_of_binop op is a textual representation of op.
val string_of_unop : unop -> stringstring_of_unop op is a textual representation of op.
val string_of_cast : cast -> stringstring_of_cast t is a textual representation of a cast type
module Infix : sig ... endInfix operators
Brings infix operations into scope of the Bil module.
include module type of Infix
Arithmetic operations
Bit operations
Equality tests
Signed comparison
Misc operations
Functional constructors
val special : string -> stmtspecial msg -> Special msg
val cpuexn : int -> stmtcpuexn number -> CpuExn number
val unsigned : castunsigned -> UNSIGNED
val signed : castsigned -> SIGNED
val high : casthigh -> HIGH
val low : castlow -> LOW
val plus : binopplus -> PLUS
val minus : binopminus -> MINUS
val times : binoptimes -> TIMES
val divide : binopdivide -> DIVIDE
val sdivide : binopsdivide -> SDIVIDE
val modulo : binopmodulo -> MOD
val smodulo : binopsmodulo -> SMOD
val lshift : binoplshift -> LSHIFT
val rshift : binoprshift -> RSHIFT
val arshift : binoparshift -> ARSHIFT
val bit_and : binopbit_and -> AND
val bit_or : binopbit_or -> OR
val bit_xor : binopbit_xor -> XOR
val eq : binopeq -> EQ
val neq : binopneq -> NEQ
val lt : binoplt -> LT
val le : binople -> LE
val slt : binopslt -> SLT
val sle : binopsle -> SLE
val neg : unopneg -> NEG
val not : unopnot -> NOT
load ~mem ~addr endian size -> Load (mem,addr,endian,size)
store ~mem ~addr exp endian size -> Store(mem,addr,endian,size)
ite ~if_:cond ~then_:e1 ~else_:e2 -> Ite (cond,e1,e2)
BIL Helper functions
is_referenced x p is true if x is referenced in some expression or statement in program p, before it is assigned.
is_assigned x p is true if there exists such Move statement, that x occurs on the left side of it. If strict is true, then only unconditional assignments are accounted. By default, strict is false
val prune_unreferenced :
?such_that:(var -> bool) ->
?physicals:bool ->
?virtuals:bool ->
stmt list ->
stmt listprune_unreferenced ?physicals ?virtuals ?such_that p remove all assignments to variables that are not used in the program p. This is a local optimization. The variable is unreferenced if it is not referenced in its lexical scope, or if it is referenced after the assignment. A variable is pruned only if it matches to one of the user specified kind, described below (no variable matches the default values, so by default nothing is pruned):
such_that matches a variable v for which such_that v is true;
physicals matches all physical variables (i.e., registers and memory locations). See Var.is_physical for more information. Note: passing true to this option is in general unsound, unless you're absolutely sure, that physical variables will not live out program p;
virtuals matches all virtual variables (i.e., such variables that were added to a program artificially and are not represented physically in a program). See Var.is_virtual for more information on virtual variables.
normalize_negatives p transform x + y to x - abs(y) if y < 0
substitute x y p substitutes each occurrence of expression x by expression y in program p. The mnemonic to remember the order is to recall the sed's s/in/out syntax.
substitute_var x y p substitutes all free occurrences of variable x in program p by expression y. A variable is free if it is not bounded in a preceding statement or not bound with let expression.
free_vars bil returns a set of free variables in program bil. Variable is considered free if it is not bound in a preceding statement or is not bound with let expression
fixpoint f applies transformation f until fixpoint is reached. If the transformation orbit contains non-trivial cycles, then the transformation will stop at an arbitrary point of a cycle.
propagate_consts bil propagates consts from their reaching definitions. The implementation computes reaching definition using inference style analysis, overapproximates while cycles (doesn't compute the meet-over-paths solution), and ignores memory locations.
prune_dead_virtuals bil removes definitions of virtual variables that are not live in the provided bil program. We assume that virtual variables are used to represent temporaries, thus their removal is safe. The analysis over-approximates the while loops, and won't remove any definition that occurs in a while loop body, or which depends on it. The analysis doesn't track memory locations.
BIL Special values
The Special statement enables encoding of arbitrary semantics using encode attr values and decode attr to get the values back. The meaning of the attr and values is specific to the user domain.
Example, encode call "malloc", where call is the BIL attribute that denotes a call to a function. See call for more information.
module Attribute : sig ... endBIL attributes.
val encode : 'a Attribute.t -> 'a -> stmtencode attr value encodes value as a special statement.
val decode : 'a Attribute.t -> stmt -> 'a optiondecode attr s is Some v if s is encode attr v.
val call : string Attribute.tcall is the attribute name for encoding calls.
val intrinsic : string Attribute.tintrinsic is the attribute for intrinsic calls.
An intrinsic is a low-level, usually microarchitectural operation.
val label : string Attribute.tlabel a named code location.
val goto : string Attribute.tgoto represents a control-flow transfer to a named label.
module Theory : sig ... endCore Theory specification of BIL.
module Apply : sig ... endMaps BIL operators to bitvectors.
class type storage = object ... endAn interface to a memory storage.
module Storage : sig ... endPredefined storage classes
Value of a result. We slightly diverge from an operational semantics by allowing a user to provide its own storage implementation.
In operational semantics a storage is represented syntactically as
v1 with [v2,ed] : nat <- v3,
where v1 may be either a Bot value, representing an empty memory (or an absence of knowledge), or another storage. So a well typed memory object is defined inductively as:
Inductive memory := | bot : memory | store : (mem : memory) (addr : value) (data : value).
That is equivalent to an assoc list. Although we provide an assoc list as storage variant (see Storage.linear), the default storage is implemented slightly more effective, and uses linear space and provides $log(N)$ lookup and update methods. Users are encouraged to provide more efficient storage implementations, for interpreters that rely heave on memory throughput.
module Result : sig ... endResult of computation.
module Trie : sig ... endTries on BIL.
register_pass ~desc name pass provides a pass to the BIL transformation pipeline. The BIL transformation pipeline is applied after the lifting procedure, i.e., it is embedded into each lift function of all Target modules. (You can selectively register passes based on architecture by subscribing to the Project.Info.arch variable). All passes that were in the selection provided to the select_passes are applied in the order of the selection until the fixed point is reached or a loop is detected. By default, no passes are selected. The bil plugin provides a user interface for passes selection, as well as some useful passes.
val select_passes : pass list -> unitselect_passes passes select the passes for the BIL transformation pipeline. See register_pass for more information about the BIL transformation pipeline.
val passes : unit -> pass listpasses () returns all currently registered passes.
module Pass : sig ... endA BIL analysis pass