package octez-smart-rollup-wasm-debugger-lib

  1. Overview
  2. Docs
module Prof : sig ... end
val compute_step : Config.config -> Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> (Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree * int64) Tezos_base.TzPervasives.tzresult Lwt.t
val eval_to_result : Config.config -> Tezos_scoru_wasm_helpers.Wasm_utils.tree -> (Tezos_scoru_wasm_helpers.Wasm_utils.tree * int64) Tezos_base.TzPervasives.tzresult Lwt.t
val eval_kernel_run : Config.config -> Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> (Tezos_scoru_wasm_helpers.Wasm_utils.Wasm_fast.tree * int64) Tezos_base.TzPervasives.tzresult Lwt.t
val eval_until_input_requested : Config.config -> Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> (Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree * int64) Tezos_base.TzPervasives.tzresult Lwt.t
val produce_flamegraph : collapse:bool -> max_depth:int -> Profiling.function_call Profiling.call_stack option list -> unit
val profiling_results : Profiling.function_call Profiling.call_stack option -> unit
val eval_and_profile : collapse:bool -> with_time:bool -> no_reboot:bool -> Config.config -> string Custom_section.FuncMap.t -> Tezos_scoru_wasm_helpers.Wasm_utils.Tree_encoding_runner.tree -> Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree Tezos_base.TzPervasives.tzresult Lwt.t
val set_raw_message_input_step : int32 -> Z.t -> string -> Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree Lwt.t
val check_input_request : Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> (unit, string) Stdlib.result Lwt.t
val load_inputs_gen : string list Tezos_base.TzPervasives.Seq.t -> int32 -> Tezos_scoru_wasm_helpers.Wasm_utils.tree -> (Tezos_scoru_wasm_helpers.Wasm_utils.tree * string list Tezos_base.TzPervasives.Seq.t * int32, Tezos_base.TzPervasives.tztrace) Stdlib.result Lwt.t
val load_inputs : string list Tezos_base.TzPervasives.Seq.t -> int32 -> Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> (Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree * string list Tezos_base.TzPervasives.Seq.t * int32, Tezos_base.TzPervasives.tztrace) Stdlib.result Lwt.t
val eval : int32 -> string list Tezos_base.TzPervasives.Seq.t -> Config.config -> Octez_smart_rollup_wasm_debugger_lib__Commands.eval_step -> Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> (Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree * int64 * string list Tezos_base.TzPervasives.Seq.t * int32, Tezos_base.TzPervasives.tztrace) Stdlib.result Lwt.t
val profile : collapse:bool -> with_time:bool -> no_reboot:bool -> int32 -> string list Tezos_base.TzPervasives.Seq.t -> Config.config -> string Custom_section.FuncMap.t -> Tezos_scoru_wasm_helpers.Wasm_utils.Tree_encoding_runner.tree -> (Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree * string list Tezos_base.TzPervasives.Seq.t * int32, Tezos_base.TzPervasives.tztrace) Stdlib.result Lwt.t
val pp_input_request : Stdlib.Format.formatter -> Tezos_scoru_wasm.Wasm_pvm_state.input_request -> unit
val show_status : Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> unit Lwt.t
val step : int32 -> string list Tezos_base.TzPervasives.Seq.t -> Config.config -> Octez_smart_rollup_wasm_debugger_lib__Commands.eval_step -> Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> ((Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree * string list Tezos_base.TzPervasives.Seq.t * int32) option, Tezos_base.TzPervasives.tztrace) Stdlib.result Lwt.t
val show_inbox : Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> unit Lwt.t
val show_outbox_gen : Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> int32 -> unit Lwt.t
val show_outbox : Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> int32 -> unit Lwt.t
val find_key_in_durable : Tezos_scoru_wasm_helpers.Wasm_utils.tree -> Tezos_scoru_wasm.Durable.key -> Tezos_lazy_containers.Chunked_byte_vector.t option Lwt.t
val print_durable : ?depth:int -> ?show_values:bool -> ?path:string list -> Tezos_scoru_wasm_helpers.Wasm_utils.Ctx.Tree.tree -> unit Lwt.t
val show_durable : Tezos_scoru_wasm_helpers.Wasm_utils.Ctx.Tree.tree -> unit Lwt.t
val show_subkeys : Tezos_scoru_wasm_helpers.Wasm_utils.Ctx.Tree.tree -> string -> unit Lwt.t
val show_value : Repl_helpers.printable_value_kind -> string -> string
val show_key_gen : Tezos_scoru_wasm_helpers.Wasm_utils.tree -> Tezos_scoru_wasm.Durable.key -> Repl_helpers.printable_value_kind -> unit Lwt.t
val show_key : Tezos_scoru_wasm_helpers.Wasm_utils.tree -> string -> Repl_helpers.printable_value_kind -> unit Lwt.t
exception Cannot_inspect_memory of string
val load_memory : Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> Tezos_webassembly_interpreter.Instance.memory_inst Lwt.t
val show_memory : Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> Tezos_webassembly_interpreter.Memory.address -> int -> Repl_helpers.printable_value_kind -> unit Lwt.t
val dump_function_symbols : string Custom_section.FuncMap.t -> unit Lwt.t
val reveal_preimage : Config.config -> string option -> Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree Lwt.t
val reveal_metadata : Config.config -> Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree Lwt.t
val get_function_symbols : Tezos_scoru_wasm_helpers.Wasm_utils.tree -> (string Custom_section.FuncMap.t, Tezos_base.TzPervasives.tztrace) Stdlib.result Lwt.t
val handle_command : string -> Config.config -> Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree -> string list Tezos_base.TzPervasives.Seq.t -> int32 -> ((Tezos_scoru_wasm_helpers.Wasm_utils.Wasm.tree * string list Tezos_base.TzPervasives.Seq.t * int32) option, Tezos_base.TzPervasives.tztrace) Stdlib.result Lwt.t
OCaml

Innovation. Community. Security.