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

  1. Overview
  2. Docs

This files implements the parsing of custom subsection, especially the `name` custom section (see https://webassembly.github.io/spec/core/appendix/custom.html#name-section).

The `name` section has the following format: h len vec_len:n (index name_len name)^n where

  • h is a tag encoded in a single byte (`1` for the functions subsection)
  • len is a variable-length unsigned 32bits integer (`vu32`), which is the length of the subsection
  • vec_len (`vu32`) encoding the number of values in the vector then for each value of the vector:
  • index (`vu32`) encoding the function representation
  • name_len (`vu32`) encoding the length in bytes of the name
  • name (`utf8`) bytes of length `name_len` encoding an utf8 representation of the symbol
val vuN : int -> string -> int -> int64 * int
val vu32 : string -> int -> int32 * int
val parse_subsection_header : string -> int -> (char * int32 * int) option

parse_subsection_header bytes index reads the tag for the subsection and its length, and returns the next index to continue reading. Returns `None` if there are not at least 2 bytes to read.

val u32_to_int : int32 -> int
val get_function_name_section_indexes : string -> (int * int32) option

get_function_name_section_indexes bytes returns the starting index of the `functions` subsection and its length.

val parse_nameassoc : Tezos_base.TzPervasives.String.t -> int -> (int32 * string) * int

parse_nameassoc bytes index parses a `(index, name)` encoded value and returns the index to continue the reading.

module FuncMap : sig ... end
val parse_vec : string -> int -> (string -> int -> 'a * int) -> 'b Tezos_base.TzPervasives.Seq.t

parse_vec bytes start parse_value parses an encoded vector and its values with parse_value.

val parse_function_subsection : Tezos_base.TzPervasives.String.t -> string FuncMap.t

parse_function_subsection bytes parse and returns the `functions` subsection, as described by the reference documentation.

val pp_function_subsection : Stdlib.Format.formatter -> string FuncMap.t -> unit

pp_function_subsection ppf map pretty-prints the parsed functions subsection.

val parse_custom_sections : string -> string -> string FuncMap.t Lwt.t
OCaml

Innovation. Community. Security.