open Hashtbl type protovers = X86Linux2012 | X86Win2012 type sctltype = Local of int| Remote of (string*int) type sctl = { ptype : sctltype; ic : in_channel; oc : out_channel; vers : protovers; } type ctlproc = { sctl : sctl; id : int64; (* other stuff like a register cache ? *) } type sctlns = { ns_id : int64; ns_sctl : sctl; } type lockind = L_var | L_param type cbase = Vundef | Vbool | Vchar | Vshort | Vint | Vlong | Vvlong | Vuchar | Vushort | Vuint | Vulong | Vuvlong | Vfloat | Vdouble | Vlongdouble | Vcomplex | Vdoublex | Vlongdoublex | Vptr | Vvoid | Vnallbase type rkind = Rundef | Ru08le | Ru16le | Ru32le | Ru64le | Rs08le | Rs16le | Rs32le | Rs64le | Ru08be | Ru16be | Ru32be | Ru64be | Rs08be | Rs16be | Rs32be | Rs64be | Rf32 | Rf64 | Rf96 | Rf128 | Rx64 | Rx128 | Rx192 | Rnrep type sctlloc = { sl_id : string; sl_type : tname; sl_kind : lockind; sl_lexpr : sctllexpr; } and tname = Tvoid | Tbase of cbase | Tstruct of string | Tunion of string | Tenum of string | Tptr of tname | Tarr of int * tname | Tfun of tname * int * param list | Ttypedef of string | Tbitfield of int * int * tname | Tconst of tname | Txaccess | Tundef of tname and attr = Noattrsyet and field = { f_off : int; f_alist : attr list; f_name : string; f_type : tname; } and sctldecl = { sd_type : tdef; sd_id : string; sd_off : int32; } and sctlenum = { se_id : string; se_off : int64; se_type : tdef; } and param = { (* attrs left out for now *) p_name : string; p_type : tname; } and tdef = { st_tname : tname; st_rep : rkind option; st_id : string option; st_sz : int64 option; st_pos : int option; st_w : int option; st_plist : param list option; st_flist : field list option; st_elist : sctlenum list option; st_link : tname option; } and sctllexpr = Lreg of int | Lderef of sctllexpr | Ladd of sctllexpr * sctllexpr | Lsub of sctllexpr * sctllexpr | Lulit of int64 | Lslit of int64 type srcloc = { src_addr : int64; src_file : string; src_line : int32; src_col : int32; } type launch_flag = | Fstdin | Fstdout | Fstderr type ctx = { r15 : int64; r14 : int64; r13 : int64; r12 : int64; rbp : int64; rbx : int64; r11 : int64; r10 : int64; r9 : int64; r8 : int64; rax : int64; rcx : int64; rdx : int64; rsi : int64; rdi : int64; orig_rax : int64; rip : int64; cs : int64; eflags : int64; rsp : int64; ss : int64; fs_base : int64; gs_base : int64; ds : int64; es : int64; fs : int64; gs : int64; cursig : int64; } type loctab = (int64, (int64 * sctlloc list)) Hashtbl.t type typetab = (string, tdef) Hashtbl.t type trace_flag = | TFsyscall | TFexec | TFfork | TFclone | TFsignal | TFexit | TFtrap | TFsnap | TFstepctx | TFload | TFunload type event_details = | Esyscall of ctx | Eexec of ctx | Efork of (int64*ctx*ctx) | Eclone of (int64*ctx*ctx) | Esignal of ctx | Eexit | Etrap of (int64*ctx) | Esnap of (int64*int64*ctx) | Eload of (string*int64*ctx) | Eunload of (string*int64*ctx) type event = (int64*event_details) type proc = { pid : int64; cmd : string; tids : int64 list; } type rflag = PROT_READ | PROT_WRITE | PROT_EXEC type region = { r_file : string; r_addr: int64; r_len : int64; r_flags : rflag list; } type binary = { b_nsid : int64; b_base : int64; b_isexe : bool; b_path : string; } type stat = (int64*region array*binary array) type sctlstring = { len : int; s : string; } type sflag = SUNDEF | SDATA | STEXT | SRO |SENUM | SINLINE type sym = { s_name : string; s_flags : sflag list; s_val : int64; s_size : int64; s_type : tname; } type symtab = (string, sym) Hashtbl.t type trapmode = Trap | Snap val empty_ctx:ctx val format_rflags: rflag list -> string val ns: string -> sctlns val looksym: sctlns -> string -> sym val enumsym: sctlns -> symtab val enumloc: sctlns -> int64 -> loctab val looktype: sctlns -> tname -> tdef val enumtype: sctlns -> typetab val lookaddr: sctlns -> int64 -> sym val enumseg: sctlns -> sym array val looksrc: sctlns -> int64 -> srcloc val lookpc: sctlns -> string -> int -> int64 val create_local: unit -> sctl val launch: sctl -> launch_flag list -> string list -> (ctlproc*ctx) val step: ctlproc -> ctx val cont: ctlproc -> unit val cont_to_exit: ctlproc -> unit val stop: ctlproc -> ctx val close: sctl -> unit val ping: sctl -> string -> unit val ps: sctl -> proc array val attach: sctl -> int64 -> (ctlproc*ctx) val readmem: ctlproc -> int64 -> int64 -> string val writemem: ctlproc -> int64 -> string -> int64 val detach:ctlproc -> unit val stat: ctlproc -> stat val snap: ctlproc -> ctlproc val kill: ctlproc -> unit val trace: ctlproc -> trace_flag list -> unit val settrap: ctlproc -> trapmode -> int64 -> int64 val formattype: tname -> string val format_lexpr: sctllexpr -> string val formatsym: sym -> string val formatsymsize: sym -> string val skip_prologue: sctlns -> string -> (int64 * int64) option