File: hivex.ml

package info (click to toggle)
hivex 1.3.24-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 3,924 kB
  • sloc: ansic: 7,385; sh: 5,314; ml: 4,424; makefile: 559; perl: 528; python: 253; ruby: 123; xml: 104; sed: 16
file content (96 lines) | stat: -rw-r--r-- 4,418 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
(* hivex generated file
 * WARNING: THIS FILE IS GENERATED FROM:
 *   generator/generator.ml
 * ANY CHANGES YOU MAKE TO THIS FILE WILL BE LOST.
 *
 * Copyright (C) 2009-2022 Red Hat Inc.
 * Derived from code by Petter Nordahl-Hagen under a compatible license:
 *   Copyright (c) 1997-2007 Petter Nordahl-Hagen.
 * Derived from code by Markus Stephany under a compatible license:
 *   Copyright (c)2000-2004, Markus Stephany.
 *
 * This library is free software; you can redistribute it and/or
 * modify it under the terms of the GNU Lesser General Public
 * License as published by the Free Software Foundation; either
 * version 2 of the License, or (at your option) any later version.
 *
 * This library is distributed in the hope that it will be useful,
 * but WITHOUT ANY WARRANTY; without even the implied warranty of
 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
 * Lesser General Public License for more details.
 *
 * You should have received a copy of the GNU Lesser General Public
 * License along with this library; if not, write to the Free Software
 * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
 *)

type t
type node = int
type value = int

exception Error of string * Unix.error * string
exception Handle_closed of string

(* Give the exceptions names, so they can be raised from the C code. *)
let () =
  Callback.register_exception "ocaml_hivex_error"
    (Error ("", Unix.EUNKNOWNERR 0, ""));
  Callback.register_exception "ocaml_hivex_closed" (Handle_closed "")

type hive_type =
  | REG_NONE
  | REG_SZ
  | REG_EXPAND_SZ
  | REG_BINARY
  | REG_DWORD
  | REG_DWORD_BIG_ENDIAN
  | REG_LINK
  | REG_MULTI_SZ
  | REG_RESOURCE_LIST
  | REG_FULL_RESOURCE_DESCRIPTOR
  | REG_RESOURCE_REQUIREMENTS_LIST
  | REG_QWORD
| REG_UNKNOWN of int32

type open_flag =
  | OPEN_VERBOSE (** Verbose messages *)
  | OPEN_DEBUG (** Debug messages *)
  | OPEN_WRITE (** Enable writes to the hive *)
  | OPEN_UNSAFE (** Enable heuristics to allow read/write of corrupted hives *)

type set_value = {
  key : string;
  t : hive_type;
  value : string;
}

external open_file : string -> open_flag list -> t = "ocaml_hivex_open"
external close : t -> unit = "ocaml_hivex_close"
external root : t -> node = "ocaml_hivex_root"
external last_modified : t -> int64 = "ocaml_hivex_last_modified"
external node_name : t -> node -> string = "ocaml_hivex_node_name"
external node_name_len : t -> node -> int64 = "ocaml_hivex_node_name_len"
external node_timestamp : t -> node -> int64 = "ocaml_hivex_node_timestamp"
external node_children : t -> node -> node array = "ocaml_hivex_node_children"
external node_get_child : t -> node -> string -> node = "ocaml_hivex_node_get_child"
external node_nr_children : t -> node -> int64 = "ocaml_hivex_node_nr_children"
external node_parent : t -> node -> node = "ocaml_hivex_node_parent"
external node_values : t -> node -> value array = "ocaml_hivex_node_values"
external node_get_value : t -> node -> string -> value = "ocaml_hivex_node_get_value"
external node_nr_values : t -> node -> int64 = "ocaml_hivex_node_nr_values"
external value_key_len : t -> value -> int64 = "ocaml_hivex_value_key_len"
external value_key : t -> value -> string = "ocaml_hivex_value_key"
external value_type : t -> value -> hive_type * int = "ocaml_hivex_value_type"
external node_struct_length : t -> node -> int64 = "ocaml_hivex_node_struct_length"
external value_struct_length : t -> value -> int64 = "ocaml_hivex_value_struct_length"
external value_data_cell_offset : t -> value -> int * value = "ocaml_hivex_value_data_cell_offset"
external value_value : t -> value -> hive_type * string = "ocaml_hivex_value_value"
external value_string : t -> value -> string = "ocaml_hivex_value_string"
external value_multiple_strings : t -> value -> string array = "ocaml_hivex_value_multiple_strings"
external value_dword : t -> value -> int32 = "ocaml_hivex_value_dword"
external value_qword : t -> value -> int64 = "ocaml_hivex_value_qword"
external commit : t -> string option -> unit = "ocaml_hivex_commit"
external node_add_child : t -> node -> string -> node = "ocaml_hivex_node_add_child"
external node_delete_child : t -> node -> unit = "ocaml_hivex_node_delete_child"
external node_set_values : t -> node -> set_value array -> unit = "ocaml_hivex_node_set_values"
external node_set_value : t -> node -> set_value -> unit = "ocaml_hivex_node_set_value"