6f318ac36f8be1eda20cb440d24695892f21c1a9
[hivex.git] / generator / generator.ml
1 #!/usr/bin/env ocaml
2 (* hivex
3  * Copyright (C) 2009-2011 Red Hat Inc.
4  *
5  * This program is free software; you can redistribute it and/or modify
6  * it under the terms of the GNU General Public License as published by
7  * the Free Software Foundation; either version 2 of the License, or
8  * (at your option) any later version.
9  *
10  * This program is distributed in the hope that it will be useful,
11  * but WITHOUT ANY WARRANTY; without even the implied warranty of
12  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
13  * GNU General Public License for more details.
14  *
15  * You should have received a copy of the GNU General Public License
16  * along with this program; if not, write to the Free Software
17  * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
18  *)
19
20 (* This script generates language bindings and some documentation for
21  * hivex.
22  *
23  * After editing this file, run it (./generator/generator.ml) to
24  * regenerate all the output files.  'make' will rerun this
25  * automatically when necessary.  Note that if you are using a separate
26  * build directory you must run generator.ml from the _source_
27  * directory.
28  *
29  * IMPORTANT: This script should NOT print any warnings.  If it prints
30  * warnings, you should treat them as errors.
31  *
32  * OCaml tips: (1) In emacs, install tuareg-mode to display and format
33  * OCaml code correctly.  'vim' comes with a good OCaml editing mode by
34  * default.  (2) Read the resources at http://ocaml-tutorial.org/
35  *)
36
37 #load "unix.cma";;
38 #load "str.cma";;
39
40 open Unix
41 open Printf
42
43 type style = ret * args
44 and ret =
45   | RErr                                (* 0 = ok, -1 = error *)
46   | RErrDispose                         (* Disposes handle, see hivex_close. *)
47   | RHive                               (* Returns a hive_h or NULL. *)
48   | RSize                               (* Returns size_t or 0. *)
49   | RNode                               (* Returns hive_node_h or 0. *)
50   | RNodeNotFound                       (* See hivex_node_get_child. *)
51   | RNodeList                           (* Returns hive_node_h* or NULL. *)
52   | RValue                              (* Returns hive_value_h or 0. *)
53   | RValueList                          (* Returns hive_value_h* or NULL. *)
54   | RString                             (* Returns char* or NULL. *)
55   | RStringList                         (* Returns char** or NULL. *)
56   | RLenType                            (* See hivex_value_type. *)
57   | RLenTypeVal                         (* See hivex_value_value. *)
58   | RInt32                              (* Returns int32. *)
59   | RInt64                              (* Returns int64. *)
60
61 and args = argt list                    (* List of parameters. *)
62
63 and argt =                              (* Note, cannot be NULL/0 unless it
64                                            says so explicitly below. *)
65   | AHive                               (* hive_h* *)
66   | ANode of string                     (* hive_node_h *)
67   | AValue of string                    (* hive_value_h *)
68   | AString of string                   (* char* *)
69   | AStringNullable of string           (* char* (can be NULL) *)
70   | AOpenFlags                          (* HIVEX_OPEN_* flags list. *)
71   | AUnusedFlags                        (* Flags arg that is always 0 *)
72   | ASetValues                          (* See hivex_node_set_values. *)
73   | ASetValue                           (* See hivex_node_set_value. *)
74
75 (* Hive types, from:
76  * https://secure.wikimedia.org/wikipedia/en/wiki/Windows_Registry#Keys_and_values
77  *
78  * It's unfortunate that in our original C binding we strayed away from
79  * the names that Windows uses (eg. REG_SZ for strings).  We include
80  * both our names and the Windows names.
81  *)
82 let hive_types = [
83   0, "none", "NONE",
84     "Just a key without a value";
85   1, "string", "SZ",
86     "A Windows string (encoding is unknown, but often UTF16-LE)";
87   2, "expand_string", "EXPAND_SZ",
88     "A Windows string that contains %env% (environment variable expansion)";
89   3, "binary", "BINARY",
90     "A blob of binary";
91   4, "dword", "DWORD",
92     "DWORD (32 bit integer), little endian";
93   5, "dword_be", "DWORD_BIG_ENDIAN",
94     "DWORD (32 bit integer), big endian";
95   6, "link", "LINK",
96     "Symbolic link to another part of the registry tree";
97   7, "multiple_strings", "MULTI_SZ",
98     "Multiple Windows strings.  See http://blogs.msdn.com/oldnewthing/archive/2009/10/08/9904646.aspx";
99   8, "resource_list", "RESOURCE_LIST",
100     "Resource list";
101   9, "full_resource_description", "FULL_RESOURCE_DESCRIPTOR",
102     "Resource descriptor";
103   10, "resource_requirements_list", "RESOURCE_REQUIREMENTS_LIST",
104     "Resouce requirements list";
105   11, "qword", "QWORD",
106     "QWORD (64 bit integer), unspecified endianness but usually little endian"
107 ]
108 let max_hive_type = 11
109
110 (* Open flags (bitmask passed to AOpenFlags) *)
111 let open_flags = [
112   1, "VERBOSE", "Verbose messages";
113   2, "DEBUG", "Debug messages";
114   4, "WRITE", "Enable writes to the hive";
115 ]
116
117 (* The API calls. *)
118 let functions = [
119   "open", (RHive, [AString "filename"; AOpenFlags]),
120     "open a hive file",
121     "\
122 Opens the hive named C<filename> for reading.
123
124 Flags is an ORed list of the open flags (or C<0> if you don't
125 want to pass any flags).  These flags are defined:
126
127 =over 4
128
129 =item HIVEX_OPEN_VERBOSE
130
131 Verbose messages.
132
133 =item HIVEX_OPEN_DEBUG
134
135 Very verbose messages, suitable for debugging problems in the library
136 itself.
137
138 This is also selected if the C<HIVEX_DEBUG> environment variable
139 is set to 1.
140
141 =item HIVEX_OPEN_WRITE
142
143 Open the hive for writing.  If omitted, the hive is read-only.
144
145 See L<hivex(3)/WRITING TO HIVE FILES>.
146
147 =back";
148
149   "close", (RErrDispose, [AHive]),
150     "close a hive handle",
151     "\
152 Close a hive handle and free all associated resources.
153
154 Note that any uncommitted writes are I<not> committed by this call,
155 but instead are lost.  See L<hivex(3)/WRITING TO HIVE FILES>.";
156
157   "root", (RNode, [AHive]),
158     "return the root node of the hive",
159     "\
160 Return root node of the hive.  All valid hives must contain a root node.";
161
162   "last_modified", (RInt64, [AHive]),
163     "return the modification time from the header of the hive",
164     "\
165 Return the modification time from the header of the hive.
166
167 The returned value is a Windows filetime.
168 To convert this to a Unix C<time_t> see:
169 L<http://stackoverflow.com/questions/6161776/convert-windows-filetime-to-second-in-unix-linux/6161842#6161842>";
170
171   "node_name", (RString, [AHive; ANode "node"]),
172     "return the name of the node",
173     "\
174 Return the name of the node.
175
176 Note that the name of the root node is a dummy, such as
177 C<$$$PROTO.HIV> (other names are possible: it seems to depend on the
178 tool or program that created the hive in the first place).  You can
179 only know the \"real\" name of the root node by knowing which registry
180 file this hive originally comes from, which is knowledge that is
181 outside the scope of this library.";
182
183   "node_timestamp", (RInt64, [AHive; ANode "node"]),
184     "return the modification time of the node",
185     "\
186 Return the modification time of the node.
187
188 The returned value is a Windows filetime.
189 To convert this to a Unix C<time_t> see:
190 L<http://stackoverflow.com/questions/6161776/convert-windows-filetime-to-second-in-unix-linux/6161842#6161842>";
191
192   "node_children", (RNodeList, [AHive; ANode "node"]),
193     "return children of node",
194     "\
195 Return an array of nodes which are the subkeys
196 (children) of C<node>.";
197
198   "node_get_child", (RNodeNotFound, [AHive; ANode "node"; AString "name"]),
199     "return named child of node",
200     "\
201 Return the child of node with the name C<name>, if it exists.
202
203 The name is matched case insensitively.";
204
205   "node_parent", (RNode, [AHive; ANode "node"]),
206     "return the parent of node",
207     "\
208 Return the parent of C<node>.
209
210 The parent pointer of the root node in registry files that we
211 have examined seems to be invalid, and so this function will
212 return an error if called on the root node.";
213
214   "node_values", (RValueList, [AHive; ANode "node"]),
215     "return (key, value) pairs attached to a node",
216     "\
217 Return the array of (key, value) pairs attached to this node.";
218
219   "node_get_value", (RValue, [AHive; ANode "node"; AString "key"]),
220     "return named key at node",
221     "\
222 Return the value attached to this node which has the name C<key>,
223 if it exists.
224
225 The key name is matched case insensitively.
226
227 Note that to get the default key, you should pass the empty
228 string C<\"\"> here.  The default key is often written C<\"@\">, but
229 inside hives that has no meaning and won't give you the
230 default key.";
231
232   "value_key_len", (RSize, [AHive; AValue "val"]),
233     "return the length of a value's key",
234     "\
235 Return the length of the key (name) of a (key, value) pair.  The
236 length can legitimately be 0, so errno is the necesary mechanism
237 to check for errors.
238
239 In the context of Windows Registries, a zero-length name means
240 that this value is the default key for this node in the tree.
241 This is usually written as C<\"@\">.";
242
243   "value_key", (RString, [AHive; AValue "val"]),
244     "return the key of a (key, value) pair",
245     "\
246 Return the key (name) of a (key, value) pair.  The name
247 is reencoded as UTF-8 and returned as a string.
248
249 The string should be freed by the caller when it is no longer needed.
250
251 Note that this function can return a zero-length string.  In the
252 context of Windows Registries, this means that this value is the
253 default key for this node in the tree.  This is usually written
254 as C<\"@\">.";
255
256   "value_type", (RLenType, [AHive; AValue "val"]),
257     "return data length and data type of a value",
258     "\
259 Return the data length and data type of the value in this (key, value)
260 pair.  See also C<hivex_value_value> which returns all this
261 information, and the value itself.  Also, C<hivex_value_*> functions
262 below which can be used to return the value in a more useful form when
263 you know the type in advance.";
264
265   "value_value", (RLenTypeVal, [AHive; AValue "val"]),
266     "return data length, data type and data of a value",
267     "\
268 Return the value of this (key, value) pair.  The value should
269 be interpreted according to its type (see C<hive_type>).";
270
271   "value_string", (RString, [AHive; AValue "val"]),
272     "return value as a string",
273     "\
274 If this value is a string, return the string reencoded as UTF-8
275 (as a C string).  This only works for values which have type
276 C<hive_t_string>, C<hive_t_expand_string> or C<hive_t_link>.";
277
278   "value_multiple_strings", (RStringList, [AHive; AValue "val"]),
279     "return value as multiple strings",
280     "\
281 If this value is a multiple-string, return the strings reencoded
282 as UTF-8 (in C, as a NULL-terminated array of C strings, in other
283 language bindings, as a list of strings).  This only
284 works for values which have type C<hive_t_multiple_strings>.";
285
286   "value_dword", (RInt32, [AHive; AValue "val"]),
287     "return value as a DWORD",
288     "\
289 If this value is a DWORD (Windows int32), return it.  This only works
290 for values which have type C<hive_t_dword> or C<hive_t_dword_be>.";
291
292   "value_qword", (RInt64, [AHive; AValue "val"]),
293     "return value as a QWORD",
294     "\
295 If this value is a QWORD (Windows int64), return it.  This only
296 works for values which have type C<hive_t_qword>.";
297
298   "commit", (RErr, [AHive; AStringNullable "filename"; AUnusedFlags]),
299     "commit (write) changes to file",
300     "\
301 Commit (write) any changes which have been made.
302
303 C<filename> is the new file to write.  If C<filename> is null/undefined
304 then we overwrite the original file (ie. the file name that was passed to
305 C<hivex_open>).
306
307 Note this does not close the hive handle.  You can perform further
308 operations on the hive after committing, including making more
309 modifications.  If you no longer wish to use the hive, then you
310 should close the handle after committing.";
311
312   "node_add_child", (RNode, [AHive; ANode "parent"; AString "name"]),
313     "add child node",
314     "\
315 Add a new child node named C<name> to the existing node C<parent>.
316 The new child initially has no subnodes and contains no keys or
317 values.  The sk-record (security descriptor) is inherited from
318 the parent.
319
320 The parent must not have an existing child called C<name>, so if you
321 want to overwrite an existing child, call C<hivex_node_delete_child>
322 first.";
323
324   "node_delete_child", (RErr, [AHive; ANode "node"]),
325     "delete child node",
326     "\
327 Delete the node C<node>.  All values at the node and all subnodes are
328 deleted (recursively).  The C<node> handle and the handles of all
329 subnodes become invalid.  You cannot delete the root node.";
330
331   "node_set_values", (RErr, [AHive; ANode "node"; ASetValues; AUnusedFlags]),
332     "set (key, value) pairs at a node",
333     "\
334 This call can be used to set all the (key, value) pairs
335 stored in C<node>.
336
337 C<node> is the node to modify.";
338
339   "node_set_value", (RErr, [AHive; ANode "node"; ASetValue; AUnusedFlags]),
340     "set a single (key, value) pair at a given node",
341     "\
342 This call can be used to replace a single C<(key, value)> pair
343 stored in C<node>.  If the key does not already exist, then a
344 new key is added.  Key matching is case insensitive.
345
346 C<node> is the node to modify.";
347 ]
348
349 (* Useful functions.
350  * Note we don't want to use any external OCaml libraries which
351  * makes this a bit harder than it should be.
352  *)
353 module StringMap = Map.Make (String)
354
355 let failwithf fs = ksprintf failwith fs
356
357 let unique = let i = ref 0 in fun () -> incr i; !i
358
359 let replace_char s c1 c2 =
360   let s2 = String.copy s in
361   let r = ref false in
362   for i = 0 to String.length s2 - 1 do
363     if String.unsafe_get s2 i = c1 then (
364       String.unsafe_set s2 i c2;
365       r := true
366     )
367   done;
368   if not !r then s else s2
369
370 let isspace c =
371   c = ' '
372   (* || c = '\f' *) || c = '\n' || c = '\r' || c = '\t' (* || c = '\v' *)
373
374 let triml ?(test = isspace) str =
375   let i = ref 0 in
376   let n = ref (String.length str) in
377   while !n > 0 && test str.[!i]; do
378     decr n;
379     incr i
380   done;
381   if !i = 0 then str
382   else String.sub str !i !n
383
384 let trimr ?(test = isspace) str =
385   let n = ref (String.length str) in
386   while !n > 0 && test str.[!n-1]; do
387     decr n
388   done;
389   if !n = String.length str then str
390   else String.sub str 0 !n
391
392 let trim ?(test = isspace) str =
393   trimr ~test (triml ~test str)
394
395 (* Used to memoize the result of pod2text. *)
396 let pod2text_memo_filename = "generator/.pod2text.data.version.2"
397 let pod2text_memo : ((int option * bool * bool * string * string), string list) Hashtbl.t =
398   try
399     let chan = open_in pod2text_memo_filename in
400     let v = input_value chan in
401     close_in chan;
402     v
403   with
404     _ -> Hashtbl.create 13
405 let pod2text_memo_updated () =
406   let chan = open_out pod2text_memo_filename in
407   output_value chan pod2text_memo;
408   close_out chan
409
410 (* Useful if you need the longdesc POD text as plain text.  Returns a
411  * list of lines.
412  *
413  * Because this is very slow (the slowest part of autogeneration),
414  * we memoize the results.
415  *)
416 let pod2text ?width ?(trim = true) ?(discard = true) name longdesc =
417   let key = width, trim, discard, name, longdesc in
418   try Hashtbl.find pod2text_memo key
419   with Not_found ->
420     let filename, chan = Filename.open_temp_file "gen" ".tmp" in
421     fprintf chan "=head1 %s\n\n%s\n" name longdesc;
422     close_out chan;
423     let cmd =
424       match width with
425       | Some width ->
426           sprintf "pod2text -w %d %s" width (Filename.quote filename)
427       | None ->
428           sprintf "pod2text %s" (Filename.quote filename) in
429     let chan = open_process_in cmd in
430     let lines = ref [] in
431     let rec loop i =
432       let line = input_line chan in
433       if i = 1 && discard then  (* discard the first line of output *)
434         loop (i+1)
435       else (
436         let line = if trim then triml line else line in
437         lines := line :: !lines;
438         loop (i+1)
439       ) in
440     let lines = try loop 1 with End_of_file -> List.rev !lines in
441     unlink filename;
442     (match close_process_in chan with
443      | WEXITED 0 -> ()
444      | WEXITED i ->
445          failwithf "pod2text: process exited with non-zero status (%d)" i
446      | WSIGNALED i | WSTOPPED i ->
447          failwithf "pod2text: process signalled or stopped by signal %d" i
448     );
449     Hashtbl.add pod2text_memo key lines;
450     pod2text_memo_updated ();
451     lines
452
453 let rec find s sub =
454   let len = String.length s in
455   let sublen = String.length sub in
456   let rec loop i =
457     if i <= len-sublen then (
458       let rec loop2 j =
459         if j < sublen then (
460           if s.[i+j] = sub.[j] then loop2 (j+1)
461           else -1
462         ) else
463           i (* found *)
464       in
465       let r = loop2 0 in
466       if r = -1 then loop (i+1) else r
467     ) else
468       -1 (* not found *)
469   in
470   loop 0
471
472 let rec replace_str s s1 s2 =
473   let len = String.length s in
474   let sublen = String.length s1 in
475   let i = find s s1 in
476   if i = -1 then s
477   else (
478     let s' = String.sub s 0 i in
479     let s'' = String.sub s (i+sublen) (len-i-sublen) in
480     s' ^ s2 ^ replace_str s'' s1 s2
481   )
482
483 let rec string_split sep str =
484   let len = String.length str in
485   let seplen = String.length sep in
486   let i = find str sep in
487   if i = -1 then [str]
488   else (
489     let s' = String.sub str 0 i in
490     let s'' = String.sub str (i+seplen) (len-i-seplen) in
491     s' :: string_split sep s''
492   )
493
494 let files_equal n1 n2 =
495   let cmd = sprintf "cmp -s %s %s" (Filename.quote n1) (Filename.quote n2) in
496   match Sys.command cmd with
497   | 0 -> true
498   | 1 -> false
499   | i -> failwithf "%s: failed with error code %d" cmd i
500
501 let rec filter_map f = function
502   | [] -> []
503   | x :: xs ->
504       match f x with
505       | Some y -> y :: filter_map f xs
506       | None -> filter_map f xs
507
508 let rec find_map f = function
509   | [] -> raise Not_found
510   | x :: xs ->
511       match f x with
512       | Some y -> y
513       | None -> find_map f xs
514
515 let iteri f xs =
516   let rec loop i = function
517     | [] -> ()
518     | x :: xs -> f i x; loop (i+1) xs
519   in
520   loop 0 xs
521
522 let mapi f xs =
523   let rec loop i = function
524     | [] -> []
525     | x :: xs -> let r = f i x in r :: loop (i+1) xs
526   in
527   loop 0 xs
528
529 let count_chars c str =
530   let count = ref 0 in
531   for i = 0 to String.length str - 1 do
532     if c = String.unsafe_get str i then incr count
533   done;
534   !count
535
536 let name_of_argt = function
537   | AHive -> "h"
538   | ANode n | AValue n | AString n | AStringNullable n -> n
539   | AOpenFlags | AUnusedFlags -> "flags"
540   | ASetValues -> "values"
541   | ASetValue -> "val"
542
543 (* Check function names etc. for consistency. *)
544 let check_functions () =
545   let contains_uppercase str =
546     let len = String.length str in
547     let rec loop i =
548       if i >= len then false
549       else (
550         let c = str.[i] in
551         if c >= 'A' && c <= 'Z' then true
552         else loop (i+1)
553       )
554     in
555     loop 0
556   in
557
558   (* Check function names. *)
559   List.iter (
560     fun (name, _, _, _) ->
561       if String.length name >= 7 && String.sub name 0 7 = "hivex" then
562         failwithf "function name %s does not need 'hivex' prefix" name;
563       if name = "" then
564         failwithf "function name is empty";
565       if name.[0] < 'a' || name.[0] > 'z' then
566         failwithf "function name %s must start with lowercase a-z" name;
567       if String.contains name '-' then
568         failwithf "function name %s should not contain '-', use '_' instead."
569           name
570   ) functions;
571
572   (* Check function parameter/return names. *)
573   List.iter (
574     fun (name, style, _, _) ->
575       let check_arg_ret_name n =
576         if contains_uppercase n then
577           failwithf "%s param/ret %s should not contain uppercase chars"
578             name n;
579         if String.contains n '-' || String.contains n '_' then
580           failwithf "%s param/ret %s should not contain '-' or '_'"
581             name n;
582         if n = "value" then
583           failwithf "%s has a param/ret called 'value', which causes conflicts in the OCaml bindings, use something like 'val' or a more descriptive name" name;
584         if n = "int" || n = "char" || n = "short" || n = "long" then
585           failwithf "%s has a param/ret which conflicts with a C type (eg. 'int', 'char' etc.)" name;
586         if n = "i" || n = "n" then
587           failwithf "%s has a param/ret called 'i' or 'n', which will cause some conflicts in the generated code" name;
588         if n = "argv" || n = "args" then
589           failwithf "%s has a param/ret called 'argv' or 'args', which will cause some conflicts in the generated code" name;
590
591         (* List Haskell, OCaml and C keywords here.
592          * http://www.haskell.org/haskellwiki/Keywords
593          * http://caml.inria.fr/pub/docs/manual-ocaml/lex.html#operator-char
594          * http://en.wikipedia.org/wiki/C_syntax#Reserved_keywords
595          * Formatted via: cat c haskell ocaml|sort -u|grep -vE '_|^val$' \
596          *   |perl -pe 's/(.+)/"$1";/'|fmt -70
597          * Omitting _-containing words, since they're handled above.
598          * Omitting the OCaml reserved word, "val", is ok,
599          * and saves us from renaming several parameters.
600          *)
601         let reserved = [
602           "and"; "as"; "asr"; "assert"; "auto"; "begin"; "break"; "case";
603           "char"; "class"; "const"; "constraint"; "continue"; "data";
604           "default"; "deriving"; "do"; "done"; "double"; "downto"; "else";
605           "end"; "enum"; "exception"; "extern"; "external"; "false"; "float";
606           "for"; "forall"; "foreign"; "fun"; "function"; "functor"; "goto";
607           "hiding"; "if"; "import"; "in"; "include"; "infix"; "infixl";
608           "infixr"; "inherit"; "initializer"; "inline"; "instance"; "int";
609           "interface";
610           "land"; "lazy"; "let"; "long"; "lor"; "lsl"; "lsr"; "lxor";
611           "match"; "mdo"; "method"; "mod"; "module"; "mutable"; "new";
612           "newtype"; "object"; "of"; "open"; "or"; "private"; "qualified";
613           "rec"; "register"; "restrict"; "return"; "short"; "sig"; "signed";
614           "sizeof"; "static"; "struct"; "switch"; "then"; "to"; "true"; "try";
615           "type"; "typedef"; "union"; "unsigned"; "virtual"; "void";
616           "volatile"; "when"; "where"; "while";
617           ] in
618         if List.mem n reserved then
619           failwithf "%s has param/ret using reserved word %s" name n;
620       in
621
622       List.iter (fun arg -> check_arg_ret_name (name_of_argt arg)) (snd style)
623   ) functions;
624
625   (* Check short descriptions. *)
626   List.iter (
627     fun (name, _, shortdesc, _) ->
628       if shortdesc.[0] <> Char.lowercase shortdesc.[0] then
629         failwithf "short description of %s should begin with lowercase." name;
630       let c = shortdesc.[String.length shortdesc-1] in
631       if c = '\n' || c = '.' then
632         failwithf "short description of %s should not end with . or \\n." name
633   ) functions;
634
635   (* Check long dscriptions. *)
636   List.iter (
637     fun (name, _, _, longdesc) ->
638       if longdesc.[String.length longdesc-1] = '\n' then
639         failwithf "long description of %s should not end with \\n." name
640   ) functions
641
642 (* 'pr' prints to the current output file. *)
643 let chan = ref Pervasives.stdout
644 let lines = ref 0
645 let pr fs =
646   ksprintf
647     (fun str ->
648        let i = count_chars '\n' str in
649        lines := !lines + i;
650        output_string !chan str
651     ) fs
652
653 let copyright_years =
654   let this_year = 1900 + (localtime (time ())).tm_year in
655   if this_year > 2009 then sprintf "2009-%04d" this_year else "2009"
656
657 (* Generate a header block in a number of standard styles. *)
658 type comment_style =
659   | CStyle | CPlusPlusStyle | HashStyle | OCamlStyle | HaskellStyle
660   | PODCommentStyle
661 type license = GPLv2plus | LGPLv2plus | GPLv2 | LGPLv2
662
663 let generate_header ?(extra_inputs = []) comment license =
664   let inputs = "generator/generator.ml" :: extra_inputs in
665   let c = match comment with
666     | CStyle ->         pr "/* "; " *"
667     | CPlusPlusStyle -> pr "// "; "//"
668     | HashStyle ->      pr "# ";  "#"
669     | OCamlStyle ->     pr "(* "; " *"
670     | HaskellStyle ->   pr "{- "; "  "
671     | PODCommentStyle -> pr "=begin comment\n\n "; "" in
672   pr "hivex generated file\n";
673   pr "%s WARNING: THIS FILE IS GENERATED FROM:\n" c;
674   List.iter (pr "%s   %s\n" c) inputs;
675   pr "%s ANY CHANGES YOU MAKE TO THIS FILE WILL BE LOST.\n" c;
676   pr "%s\n" c;
677   pr "%s Copyright (C) %s Red Hat Inc.\n" c copyright_years;
678   pr "%s Derived from code by Petter Nordahl-Hagen under a compatible license:\n" c;
679   pr "%s   Copyright (c) 1997-2007 Petter Nordahl-Hagen.\n" c;
680   pr "%s Derived from code by Markus Stephany under a compatible license:\n" c;
681   pr "%s   Copyright (c)2000-2004, Markus Stephany.\n" c;
682   pr "%s\n" c;
683   (match license with
684    | GPLv2plus ->
685        pr "%s This program is free software; you can redistribute it and/or modify\n" c;
686        pr "%s it under the terms of the GNU General Public License as published by\n" c;
687        pr "%s the Free Software Foundation; either version 2 of the License, or\n" c;
688        pr "%s (at your option) any later version.\n" c;
689        pr "%s\n" c;
690        pr "%s This program is distributed in the hope that it will be useful,\n" c;
691        pr "%s but WITHOUT ANY WARRANTY; without even the implied warranty of\n" c;
692        pr "%s MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the\n" c;
693        pr "%s GNU General Public License for more details.\n" c;
694        pr "%s\n" c;
695        pr "%s You should have received a copy of the GNU General Public License along\n" c;
696        pr "%s with this program; if not, write to the Free Software Foundation, Inc.,\n" c;
697        pr "%s 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.\n" c;
698
699    | LGPLv2plus ->
700        pr "%s This library is free software; you can redistribute it and/or\n" c;
701        pr "%s modify it under the terms of the GNU Lesser General Public\n" c;
702        pr "%s License as published by the Free Software Foundation; either\n" c;
703        pr "%s version 2 of the License, or (at your option) any later version.\n" c;
704        pr "%s\n" c;
705        pr "%s This library is distributed in the hope that it will be useful,\n" c;
706        pr "%s but WITHOUT ANY WARRANTY; without even the implied warranty of\n" c;
707        pr "%s MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU\n" c;
708        pr "%s Lesser General Public License for more details.\n" c;
709        pr "%s\n" c;
710        pr "%s You should have received a copy of the GNU Lesser General Public\n" c;
711        pr "%s License along with this library; if not, write to the Free Software\n" c;
712        pr "%s Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA\n" c;
713
714    | GPLv2 ->
715        pr "%s This program is free software; you can redistribute it and/or modify\n" c;
716        pr "%s it under the terms of the GNU General Public License as published by\n" c;
717        pr "%s the Free Software Foundation; version 2 of the License only.\n" c;
718        pr "%s\n" c;
719        pr "%s This program is distributed in the hope that it will be useful,\n" c;
720        pr "%s but WITHOUT ANY WARRANTY; without even the implied warranty of\n" c;
721        pr "%s MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the\n" c;
722        pr "%s GNU General Public License for more details.\n" c;
723        pr "%s\n" c;
724        pr "%s You should have received a copy of the GNU General Public License along\n" c;
725        pr "%s with this program; if not, write to the Free Software Foundation, Inc.,\n" c;
726        pr "%s 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.\n" c;
727
728    | LGPLv2 ->
729        pr "%s This library is free software; you can redistribute it and/or\n" c;
730        pr "%s modify it under the terms of the GNU Lesser General Public\n" c;
731        pr "%s License as published by the Free Software Foundation;\n" c;
732        pr "%s version 2.1 of the License only.\n" c;
733        pr "%s\n" c;
734        pr "%s This library is distributed in the hope that it will be useful,\n" c;
735        pr "%s but WITHOUT ANY WARRANTY; without even the implied warranty of\n" c;
736        pr "%s MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU\n" c;
737        pr "%s Lesser General Public License for more details.\n" c;
738        pr "%s\n" c;
739        pr "%s You should have received a copy of the GNU Lesser General Public\n" c;
740        pr "%s License along with this library; if not, write to the Free Software\n" c;
741        pr "%s Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA\n" c;
742   );
743   (match comment with
744    | CStyle -> pr " */\n"
745    | CPlusPlusStyle
746    | HashStyle -> ()
747    | OCamlStyle -> pr " *)\n"
748    | HaskellStyle -> pr "-}\n"
749    | PODCommentStyle -> pr "\n=end comment\n"
750   );
751   pr "\n"
752
753 (* Start of main code generation functions below this line. *)
754
755 let rec generate_c_header () =
756   generate_header CStyle LGPLv2;
757
758   pr "\
759 #ifndef HIVEX_H_
760 #define HIVEX_H_
761
762 #include <stdlib.h>
763 #include <stdint.h>
764
765 #ifdef __cplusplus
766 extern \"C\" {
767 #endif
768
769 /* NOTE: This API is documented in the man page hivex(3). */
770
771 /* Hive handle. */
772 typedef struct hive_h hive_h;
773
774 /* Nodes and values. */
775 typedef size_t hive_node_h;
776 typedef size_t hive_value_h;
777
778 #include <errno.h>
779 #ifdef ENOKEY
780 # define HIVEX_NO_KEY ENOKEY
781 #else
782 # define HIVEX_NO_KEY ENOENT
783 #endif
784
785 /* Pre-defined types. */
786 enum hive_type {
787 ";
788   List.iter (
789     fun (t, old_style, new_style, description) ->
790       pr "  /* %s */\n" description;
791       pr "  hive_t_REG_%s,\n" new_style;
792       pr "#define hive_t_%s hive_t_REG_%s\n" old_style new_style;
793       pr "\n"
794   ) hive_types;
795   pr "\
796 };
797
798 typedef enum hive_type hive_type;
799
800 /* Bitmask of flags passed to hivex_open. */
801 ";
802   List.iter (
803     fun (v, flag, description) ->
804       pr "  /* %s */\n" description;
805       pr "#define HIVEX_OPEN_%-10s %d\n" flag v;
806   ) open_flags;
807   pr "\n";
808
809   pr "\
810 /* Array of (key, value) pairs passed to hivex_node_set_values. */
811 struct hive_set_value {
812   char *key;
813   hive_type t;
814   size_t len;
815   char *value;
816 };
817 typedef struct hive_set_value hive_set_value;
818
819 ";
820
821   pr "/* Functions. */\n";
822
823   (* Function declarations. *)
824   List.iter (
825     fun (shortname, style, _, _) ->
826       let name = "hivex_" ^ shortname in
827       generate_c_prototype ~extern:true name style
828   ) functions;
829
830   (* The visitor pattern. *)
831   pr "
832 /* Visit all nodes.  This is specific to the C API and is not made
833  * available to other languages.  This is because of the complexity
834  * of binding callbacks in other languages, but also because other
835  * languages make it much simpler to iterate over a tree.
836  */
837 struct hivex_visitor {
838   int (*node_start) (hive_h *, void *opaque, hive_node_h, const char *name);
839   int (*node_end) (hive_h *, void *opaque, hive_node_h, const char *name);
840   int (*value_string) (hive_h *, void *opaque, hive_node_h, hive_value_h, hive_type t, size_t len, const char *key, const char *str);
841   int (*value_multiple_strings) (hive_h *, void *opaque, hive_node_h, hive_value_h, hive_type t, size_t len, const char *key, char **argv);
842   int (*value_string_invalid_utf16) (hive_h *, void *opaque, hive_node_h, hive_value_h, hive_type t, size_t len, const char *key, const char *str);
843   int (*value_dword) (hive_h *, void *opaque, hive_node_h, hive_value_h, hive_type t, size_t len, const char *key, int32_t);
844   int (*value_qword) (hive_h *, void *opaque, hive_node_h, hive_value_h, hive_type t, size_t len, const char *key, int64_t);
845   int (*value_binary) (hive_h *, void *opaque, hive_node_h, hive_value_h, hive_type t, size_t len, const char *key, const char *value);
846   int (*value_none) (hive_h *, void *opaque, hive_node_h, hive_value_h, hive_type t, size_t len, const char *key, const char *value);
847   int (*value_other) (hive_h *, void *opaque, hive_node_h, hive_value_h, hive_type t, size_t len, const char *key, const char *value);
848   int (*value_any) (hive_h *, void *opaque, hive_node_h, hive_value_h, hive_type t, size_t len, const char *key, const char *value);
849 };
850
851 #define HIVEX_VISIT_SKIP_BAD 1
852
853 extern int hivex_visit (hive_h *h, const struct hivex_visitor *visitor, size_t len, void *opaque, int flags);
854 extern int hivex_visit_node (hive_h *h, hive_node_h node, const struct hivex_visitor *visitor, size_t len, void *opaque, int flags);
855
856 ";
857
858   (* Finish the header file. *)
859   pr "\
860 #ifdef __cplusplus
861 }
862 #endif
863
864 #endif /* HIVEX_H_ */
865 "
866
867 and generate_c_prototype ?(extern = false) name style =
868   if extern then pr "extern ";
869   (match fst style with
870    | RErr -> pr "int "
871    | RErrDispose -> pr "int "
872    | RHive -> pr "hive_h *"
873    | RSize -> pr "size_t "
874    | RNode -> pr "hive_node_h "
875    | RNodeNotFound -> pr "hive_node_h "
876    | RNodeList -> pr "hive_node_h *"
877    | RValue -> pr "hive_value_h "
878    | RValueList -> pr "hive_value_h *"
879    | RString -> pr "char *"
880    | RStringList -> pr "char **"
881    | RLenType -> pr "int "
882    | RLenTypeVal -> pr "char *"
883    | RInt32 -> pr "int32_t "
884    | RInt64 -> pr "int64_t "
885   );
886   pr "%s (" name;
887   let comma = ref false in
888   List.iter (
889     fun arg ->
890       if !comma then pr ", "; comma := true;
891       match arg with
892       | AHive -> pr "hive_h *h"
893       | ANode n -> pr "hive_node_h %s" n
894       | AValue n -> pr "hive_value_h %s" n
895       | AString n | AStringNullable n -> pr "const char *%s" n
896       | AOpenFlags | AUnusedFlags -> pr "int flags"
897       | ASetValues -> pr "size_t nr_values, const hive_set_value *values"
898       | ASetValue -> pr "const hive_set_value *val"
899   ) (snd style);
900   (match fst style with
901    | RLenType | RLenTypeVal -> pr ", hive_type *t, size_t *len"
902    | _ -> ()
903   );
904   pr ");\n"
905
906 and generate_c_pod () =
907   generate_header PODCommentStyle GPLv2;
908
909   pr "\
910   =encoding utf8
911
912 =head1 NAME
913
914 hivex - Windows Registry \"hive\" extraction library
915
916 =head1 SYNOPSIS
917
918  #include <hivex.h>
919
920 ";
921   List.iter (
922     fun (shortname, style, _, _) ->
923       let name = "hivex_" ^ shortname in
924       pr " ";
925       generate_c_prototype ~extern:false name style;
926   ) functions;
927
928   pr "\
929
930 Link with I<-lhivex>.
931
932 =head1 DESCRIPTION
933
934 Hivex is a library for extracting the contents of Windows Registry
935 \"hive\" files.  It is designed to be secure against buggy or malicious
936 registry files.
937
938 Unlike other tools in this area, it doesn't use the textual .REG
939 format, because parsing that is as much trouble as parsing the
940 original binary format.  Instead it makes the file available
941 through a C API, and then wraps this API in higher level scripting
942 and GUI tools.
943
944 There is a separate program to export the hive as XML
945 (see L<hivexml(1)>), or to navigate the file (see L<hivexsh(1)>).
946 There is also a Perl script to export and merge the
947 file as a textual .REG (regedit) file, see L<hivexregedit(1)>.
948
949 If you just want to export or modify the Registry of a Windows
950 virtual machine, you should look at L<virt-win-reg(1)>.
951
952 Hivex is also comes with language bindings for
953 OCaml, Perl, Python and Ruby.
954
955 =head1 TYPES
956
957 =head2 C<hive_h *>
958
959 This handle describes an open hive file.
960
961 =head2 C<hive_node_h>
962
963 This is a node handle, an integer but opaque outside the library.
964 Valid node handles cannot be 0.  The library returns 0 in some
965 situations to indicate an error.
966
967 =head2 C<hive_type>
968
969 The enum below describes the possible types for the value(s)
970 stored at each node.  Note that you should not trust the
971 type field in a Windows Registry, as it very often has no
972 relationship to reality.  Some applications use their own
973 types.  The encoding of strings is not specified.  Some
974 programs store everything (including strings) in binary blobs.
975
976  enum hive_type {
977 ";
978   List.iter (
979     fun (t, _, new_style, description) ->
980       pr "   /* %s */\n" description;
981       pr "   hive_t_REG_%s = %d,\n" new_style t
982   ) hive_types;
983   pr "\
984  };
985
986 =head2 C<hive_value_h>
987
988 This is a value handle, an integer but opaque outside the library.
989 Valid value handles cannot be 0.  The library returns 0 in some
990 situations to indicate an error.
991
992 =head2 C<hive_set_value>
993
994 The typedef C<hive_set_value> is used in conjunction with the
995 C<hivex_node_set_values> call described below.
996
997  struct hive_set_value {
998    char *key;     /* key - a UTF-8 encoded ASCIIZ string */
999    hive_type t;   /* type of value field */
1000    size_t len;    /* length of value field in bytes */
1001    char *value;   /* value field */
1002  };
1003  typedef struct hive_set_value hive_set_value;
1004
1005 To set the default value for a node, you have to pass C<key = \"\">.
1006
1007 Note that the C<value> field is just treated as a list of bytes, and
1008 is stored directly in the hive.  The caller has to ensure correct
1009 encoding and endianness, for example converting dwords to little
1010 endian.
1011
1012 The correct type and encoding for values depends on the node and key
1013 in the registry, the version of Windows, and sometimes even changes
1014 between versions of Windows for the same key.  We don't document it
1015 here.  Often it's not documented at all.
1016
1017 =head1 FUNCTIONS
1018
1019 ";
1020   List.iter (
1021     fun (shortname, style, _, longdesc) ->
1022       let name = "hivex_" ^ shortname in
1023       pr "=head2 %s\n" name;
1024       pr "\n ";
1025       generate_c_prototype ~extern:false name style;
1026       pr "\n";
1027       pr "%s\n" longdesc;
1028       pr "\n";
1029
1030       if List.mem AUnusedFlags (snd style) then
1031         pr "The flags parameter is unused.  Always pass 0.\n\n";
1032
1033       if List.mem ASetValues (snd style) then
1034         pr "C<values> is an array of (key, value) pairs.  There
1035 should be C<nr_values> elements in this array.
1036
1037 Any existing values stored at the node are discarded, and their
1038 C<hive_value_h> handles become invalid.  Thus you can remove all
1039 values stored at C<node> by passing C<nr_values = 0>.\n\n";
1040
1041       if List.mem ASetValue (snd style) then
1042         pr "C<value> is a single (key, value) pair.
1043
1044 Existing C<hive_value_h> handles become invalid.\n\n";
1045
1046       (match fst style with
1047        | RErr ->
1048            pr "\
1049 Returns 0 on success.
1050 On error this returns -1 and sets errno.\n\n"
1051        | RErrDispose ->
1052            pr "\
1053 Returns 0 on success.
1054 On error this returns -1 and sets errno.
1055
1056 This function frees the hive handle (even if it returns an error).
1057 The hive handle must not be used again after calling this function.\n\n"
1058        | RHive ->
1059            pr "\
1060 Returns a new hive handle.
1061 On error this returns NULL and sets errno.\n\n"
1062        | RSize ->
1063            pr "\
1064 Returns a size.
1065 On error this returns 0 and sets errno.\n\n"
1066        | RNode ->
1067            pr "\
1068 Returns a node handle.
1069 On error this returns 0 and sets errno.\n\n"
1070        | RNodeNotFound ->
1071            pr "\
1072 Returns a node handle.
1073 If the node was not found, this returns 0 without setting errno.
1074 On error this returns 0 and sets errno.\n\n"
1075        | RNodeList ->
1076            pr "\
1077 Returns a 0-terminated array of nodes.
1078 The array must be freed by the caller when it is no longer needed.
1079 On error this returns NULL and sets errno.\n\n"
1080        | RValue ->
1081            pr "\
1082 Returns a value handle.
1083 On error this returns 0 and sets errno.\n\n"
1084        | RValueList ->
1085            pr "\
1086 Returns a 0-terminated array of values.
1087 The array must be freed by the caller when it is no longer needed.
1088 On error this returns NULL and sets errno.\n\n"
1089        | RString ->
1090            pr "\
1091 Returns a string.
1092 The string must be freed by the caller when it is no longer needed.
1093 On error this returns NULL and sets errno.\n\n"
1094        | RStringList ->
1095            pr "\
1096 Returns a NULL-terminated array of C strings.
1097 The strings and the array must all be freed by the caller when
1098 they are no longer needed.
1099 On error this returns NULL and sets errno.\n\n"
1100        | RLenType ->
1101            pr "\
1102 Returns 0 on success.
1103 On error this returns -1 and sets errno.\n\n"
1104        | RLenTypeVal ->
1105            pr "\
1106 The value is returned as an array of bytes (of length C<len>).
1107 The value must be freed by the caller when it is no longer needed.
1108 On error this returns NULL and sets errno.\n\n"
1109        | RInt32 | RInt64 -> ()
1110       );
1111   ) functions;
1112
1113   pr "\
1114 =head1 WRITING TO HIVE FILES
1115
1116 The hivex library supports making limited modifications to hive files.
1117 We have tried to implement this very conservatively in order to reduce
1118 the chance of corrupting your registry.  However you should be careful
1119 and take back-ups, since Microsoft has never documented the hive
1120 format, and so it is possible there are nuances in the
1121 reverse-engineered format that we do not understand.
1122
1123 To be able to modify a hive, you must pass the C<HIVEX_OPEN_WRITE>
1124 flag to C<hivex_open>, otherwise any write operation will return with
1125 errno C<EROFS>.
1126
1127 The write operations shown below do not modify the on-disk file
1128 immediately.  You must call C<hivex_commit> in order to write the
1129 changes to disk.  If you call C<hivex_close> without committing then
1130 any writes are discarded.
1131
1132 Hive files internally consist of a \"memory dump\" of binary blocks
1133 (like the C heap), and some of these blocks can be unused.  The hivex
1134 library never reuses these unused blocks.  Instead, to ensure
1135 robustness in the face of the partially understood on-disk format,
1136 hivex only allocates new blocks after the end of the file, and makes
1137 minimal modifications to existing structures in the file to point to
1138 these new blocks.  This makes hivex slightly less disk-efficient than
1139 it could be, but disk is cheap, and registry modifications tend to be
1140 very small.
1141
1142 When deleting nodes, it is possible that this library may leave
1143 unreachable live blocks in the hive.  This is because certain parts of
1144 the hive disk format such as security (sk) records and big data (db)
1145 records and classname fields are not well understood (and not
1146 documented at all) and we play it safe by not attempting to modify
1147 them.  Apart from wasting a little bit of disk space, it is not
1148 thought that unreachable blocks are a problem.
1149
1150 =head2 WRITE OPERATIONS WHICH ARE NOT SUPPORTED
1151
1152 =over 4
1153
1154 =item *
1155
1156 Changing the root node.
1157
1158 =item *
1159
1160 Creating a new hive file from scratch.  This is impossible at present
1161 because not all fields in the header are understood.  In the hivex
1162 source tree is a file called C<images/minimal> which could be used as
1163 the basis for a new hive (but I<caveat emptor>).
1164
1165 =item *
1166
1167 Modifying or deleting single values at a node.
1168
1169 =item *
1170
1171 Modifying security key (sk) records or classnames.
1172 Previously we did not understand these records.  However now they
1173 are well-understood and we could add support if it was required
1174 (but nothing much really uses them).
1175
1176 =back
1177
1178 =head1 VISITING ALL NODES
1179
1180 The visitor pattern is useful if you want to visit all nodes
1181 in the tree or all nodes below a certain point in the tree.
1182
1183 First you set up your own C<struct hivex_visitor> with your
1184 callback functions.
1185
1186 Each of these callback functions should return 0 on success or -1
1187 on error.  If any callback returns -1, then the entire visit
1188 terminates immediately.  If you don't need a callback function at
1189 all, set the function pointer to NULL.
1190
1191  struct hivex_visitor {
1192    int (*node_start) (hive_h *, void *opaque, hive_node_h, const char *name);
1193    int (*node_end) (hive_h *, void *opaque, hive_node_h, const char *name);
1194    int (*value_string) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1195          hive_type t, size_t len, const char *key, const char *str);
1196    int (*value_multiple_strings) (hive_h *, void *opaque, hive_node_h,
1197          hive_value_h, hive_type t, size_t len, const char *key, char **argv);
1198    int (*value_string_invalid_utf16) (hive_h *, void *opaque, hive_node_h,
1199          hive_value_h, hive_type t, size_t len, const char *key,
1200          const char *str);
1201    int (*value_dword) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1202          hive_type t, size_t len, const char *key, int32_t);
1203    int (*value_qword) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1204          hive_type t, size_t len, const char *key, int64_t);
1205    int (*value_binary) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1206          hive_type t, size_t len, const char *key, const char *value);
1207    int (*value_none) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1208          hive_type t, size_t len, const char *key, const char *value);
1209    int (*value_other) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1210          hive_type t, size_t len, const char *key, const char *value);
1211    /* If value_any callback is not NULL, then the other value_*
1212     * callbacks are not used, and value_any is called on all values.
1213     */
1214    int (*value_any) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1215          hive_type t, size_t len, const char *key, const char *value);
1216  };
1217
1218 =over 4
1219
1220 =item hivex_visit
1221
1222  int hivex_visit (hive_h *h, const struct hivex_visitor *visitor, size_t len, void *opaque, int flags);
1223
1224 Visit all the nodes recursively in the hive C<h>.
1225
1226 C<visitor> should be a C<hivex_visitor> structure with callback
1227 fields filled in as required (unwanted callbacks can be set to
1228 NULL).  C<len> must be the length of the 'visitor' struct (you
1229 should pass C<sizeof (struct hivex_visitor)> for this).
1230
1231 This returns 0 if the whole recursive visit was completed
1232 successfully.  On error this returns -1.  If one of the callback
1233 functions returned an error than we don't touch errno.  If the
1234 error was generated internally then we set errno.
1235
1236 You can skip bad registry entries by setting C<flag> to
1237 C<HIVEX_VISIT_SKIP_BAD>.  If this flag is not set, then a bad registry
1238 causes the function to return an error immediately.
1239
1240 This function is robust if the registry contains cycles or
1241 pointers which are invalid or outside the registry.  It detects
1242 these cases and returns an error.
1243
1244 =item hivex_visit_node
1245
1246  int hivex_visit_node (hive_h *h, hive_node_h node, const struct hivex_visitor *visitor, size_t len, void *opaque);
1247
1248 Same as C<hivex_visit> but instead of starting out at the root, this
1249 starts at C<node>.
1250
1251 =back
1252
1253 =head1 THE STRUCTURE OF THE WINDOWS REGISTRY
1254
1255 Note: To understand the relationship between hives and the common
1256 Windows Registry keys (like C<HKEY_LOCAL_MACHINE>) please see the
1257 Wikipedia page on the Windows Registry.
1258
1259 The Windows Registry is split across various binary files, each
1260 file being known as a \"hive\".  This library only handles a single
1261 hive file at a time.
1262
1263 Hives are n-ary trees with a single root.  Each node in the tree
1264 has a name.
1265
1266 Each node in the tree (including non-leaf nodes) may have an
1267 arbitrary list of (key, value) pairs attached to it.  It may
1268 be the case that one of these pairs has an empty key.  This
1269 is referred to as the default key for the node.
1270
1271 The (key, value) pairs are the place where the useful data is
1272 stored in the registry.  The key is always a string (possibly the
1273 empty string for the default key).  The value is a typed object
1274 (eg. string, int32, binary, etc.).
1275
1276 =head2 RELATIONSHIP TO .REG FILES
1277
1278 The hivex C library does not care about or deal with Windows .REG
1279 files.  Instead we push this complexity up to the Perl
1280 L<Win::Hivex(3)> library and the Perl programs
1281 L<hivexregedit(1)> and L<virt-win-reg(1)>.
1282 Nevertheless it is useful to look at the relationship between the
1283 Registry and .REG files because they are so common.
1284
1285 A .REG file is a textual representation of the registry, or part of the
1286 registry.  The actual registry hives that Windows uses are binary
1287 files.  There are a number of Windows and Linux tools that let you
1288 generate .REG files, or merge .REG files back into the registry hives.
1289 Notable amongst them is Microsoft's REGEDIT program (formerly known as
1290 REGEDT32).
1291
1292 A typical .REG file will contain many sections looking like this:
1293
1294  [HKEY_LOCAL_MACHINE\\SOFTWARE\\Classes\\Stack]
1295  \"@\"=\"Generic Stack\"
1296  \"TileInfo\"=\"prop:System.FileCount\"
1297  \"TilePath\"=str(2):\"%%systemroot%%\\\\system32\"
1298  \"ThumbnailCutoff\"=dword:00000000
1299  \"FriendlyTypeName\"=hex(2):40,00,25,00,53,00,79,00,73,00,74,00,65,00,6d,00,52,00,6f,00,\\
1300   6f,00,74,00,25,00,5c,00,53,00,79,00,73,00,74,00,65,00,6d,00,\\
1301   33,00,32,00,5c,00,73,00,65,00,61,00,72,00,63,00,68,00,66,00,\\
1302   6f,00,6c,00,64,00,65,00,72,00,2e,00,64,00,6c,00,6c,00,2c,00,\\
1303   2d,00,39,00,30,00,32,00,38,00,00,00,d8
1304
1305 Taking this one piece at a time:
1306
1307  [HKEY_LOCAL_MACHINE\\SOFTWARE\\Classes\\Stack]
1308
1309 This is the path to this node in the registry tree.  The first part,
1310 C<HKEY_LOCAL_MACHINE\\SOFTWARE> means that this comes from a hive
1311 file called C<C:\\WINDOWS\\SYSTEM32\\CONFIG\\SOFTWARE>.
1312 C<\\Classes\\Stack> is the real path part,
1313 starting at the root node of the C<SOFTWARE> hive.
1314
1315 Below the node name is a list of zero or more key-value pairs.  Any
1316 interior or leaf node in the registry may have key-value pairs
1317 attached.
1318
1319  \"@\"=\"Generic Stack\"
1320
1321 This is the \"default key\".  In reality (ie. inside the binary hive)
1322 the key string is the empty string.  In .REG files this is written as
1323 C<@> but this has no meaning either in the hives themselves or in this
1324 library.  The value is a string (type 1 - see C<enum hive_type>
1325 above).
1326
1327  \"TileInfo\"=\"prop:System.FileCount\"
1328
1329 This is a regular (key, value) pair, with the value being a type 1
1330 string.  Note that inside the binary file the string is likely to be
1331 UTF-16LE encoded.  This library converts to and from UTF-8 strings
1332 transparently in some cases.
1333
1334  \"TilePath\"=str(2):\"%%systemroot%%\\\\system32\"
1335
1336 The value in this case has type 2 (expanded string) meaning that some
1337 %%...%% variables get expanded by Windows.  (This library doesn't know
1338 or care about variable expansion).
1339
1340  \"ThumbnailCutoff\"=dword:00000000
1341
1342 The value in this case is a dword (type 4).
1343
1344  \"FriendlyTypeName\"=hex(2):40,00,....
1345
1346 This value is an expanded string (type 2) represented in the .REG file
1347 as a series of hex bytes.  In this case the string appears to be a
1348 UTF-16LE string.
1349
1350 =head1 NOTE ON THE USE OF ERRNO
1351
1352 Many functions in this library set errno to indicate errors.  These
1353 are the values of errno you may encounter (this list is not
1354 exhaustive):
1355
1356 =over 4
1357
1358 =item ENOTSUP
1359
1360 Corrupt or unsupported Registry file format.
1361
1362 =item HIVEX_NO_KEY
1363
1364 Missing root key.
1365
1366 =item EINVAL
1367
1368 Passed an invalid argument to the function.
1369
1370 =item EFAULT
1371
1372 Followed a Registry pointer which goes outside
1373 the registry or outside a registry block.
1374
1375 =item ELOOP
1376
1377 Registry contains cycles.
1378
1379 =item ERANGE
1380
1381 Field in the registry out of range.
1382
1383 =item EEXIST
1384
1385 Registry key already exists.
1386
1387 =item EROFS
1388
1389 Tried to write to a registry which is not opened for writing.
1390
1391 =back
1392
1393 =head1 ENVIRONMENT VARIABLES
1394
1395 =over 4
1396
1397 =item HIVEX_DEBUG
1398
1399 Setting HIVEX_DEBUG=1 will enable very verbose messages.  This is
1400 useful for debugging problems with the library itself.
1401
1402 =back
1403
1404 =head1 SEE ALSO
1405
1406 L<hivexget(1)>,
1407 L<hivexml(1)>,
1408 L<hivexsh(1)>,
1409 L<hivexregedit(1)>,
1410 L<virt-win-reg(1)>,
1411 L<Win::Hivex(3)>,
1412 L<guestfs(3)>,
1413 L<http://libguestfs.org/>,
1414 L<virt-cat(1)>,
1415 L<virt-edit(1)>,
1416 L<http://en.wikipedia.org/wiki/Windows_Registry>.
1417
1418 =head1 AUTHORS
1419
1420 Richard W.M. Jones (C<rjones at redhat dot com>)
1421
1422 =head1 COPYRIGHT
1423
1424 Copyright (C) 2009-2010 Red Hat Inc.
1425
1426 Derived from code by Petter Nordahl-Hagen under a compatible license:
1427 Copyright (C) 1997-2007 Petter Nordahl-Hagen.
1428
1429 Derived from code by Markus Stephany under a compatible license:
1430 Copyright (C) 2000-2004 Markus Stephany.
1431
1432 This library is free software; you can redistribute it and/or
1433 modify it under the terms of the GNU Lesser General Public
1434 License as published by the Free Software Foundation;
1435 version 2.1 of the License only.
1436
1437 This library is distributed in the hope that it will be useful,
1438 but WITHOUT ANY WARRANTY; without even the implied warranty of
1439 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
1440 Lesser General Public License for more details.
1441 "
1442
1443 (* Generate the linker script which controls the visibility of
1444  * symbols in the public ABI and ensures no other symbols get
1445  * exported accidentally.
1446  *)
1447 and generate_linker_script () =
1448   generate_header HashStyle GPLv2plus;
1449
1450   let globals = [
1451     "hivex_visit";
1452     "hivex_visit_node"
1453   ] in
1454
1455   let functions =
1456     List.map (fun (name, _, _, _) -> "hivex_" ^ name)
1457       functions in
1458   let globals = List.sort compare (globals @ functions) in
1459
1460   pr "{\n";
1461   pr "    global:\n";
1462   List.iter (pr "        %s;\n") globals;
1463   pr "\n";
1464
1465   pr "    local:\n";
1466   pr "        *;\n";
1467   pr "};\n"
1468
1469 and generate_ocaml_interface () =
1470   generate_header OCamlStyle LGPLv2plus;
1471
1472   pr "\
1473 type t
1474 (** A [hive_h] hive file handle. *)
1475
1476 type node
1477 type value
1478 (** Nodes and values. *)
1479
1480 exception Error of string * Unix.error * string
1481 (** Error raised by a function.
1482
1483     The first parameter is the name of the function which raised the error.
1484     The second parameter is the errno (see the [Unix] module).  The third
1485     parameter is a human-readable string corresponding to the errno.
1486
1487     See hivex(3) for a partial list of interesting errno values that
1488     can be generated by the library. *)
1489 exception Handle_closed of string
1490 (** This exception is raised if you call a function on a closed handle. *)
1491
1492 type hive_type =
1493 ";
1494   iteri (
1495     fun i ->
1496       fun (t, _, new_style, description) ->
1497         assert (i = t);
1498         pr "  | REG_%s (** %s *)\n" new_style description
1499   ) hive_types;
1500
1501   pr "\
1502   | REG_UNKNOWN of int32 (** unknown type *)
1503 (** Hive type field. *)
1504
1505 type open_flag =
1506 ";
1507   iteri (
1508     fun i ->
1509       fun (v, flag, description) ->
1510         assert (1 lsl i = v);
1511         pr "  | OPEN_%s (** %s *)\n" flag description
1512   ) open_flags;
1513
1514   pr "\
1515 (** Open flags for {!open_file} call. *)
1516
1517 type set_value = {
1518   key : string;
1519   t : hive_type;
1520   value : string;
1521 }
1522 (** (key, value) pair passed (as an array) to {!node_set_values}. *)
1523 ";
1524
1525   List.iter (
1526     fun (name, style, shortdesc, _) ->
1527       pr "\n";
1528       generate_ocaml_prototype name style;
1529       pr "(** %s *)\n" shortdesc
1530   ) functions
1531
1532 and generate_ocaml_implementation () =
1533   generate_header OCamlStyle LGPLv2plus;
1534
1535   pr "\
1536 type t
1537 type node = int
1538 type value = int
1539
1540 exception Error of string * Unix.error * string
1541 exception Handle_closed of string
1542
1543 (* Give the exceptions names, so they can be raised from the C code. *)
1544 let () =
1545   Callback.register_exception \"ocaml_hivex_error\"
1546     (Error (\"\", Unix.EUNKNOWNERR 0, \"\"));
1547   Callback.register_exception \"ocaml_hivex_closed\" (Handle_closed \"\")
1548
1549 type hive_type =
1550 ";
1551   iteri (
1552     fun i ->
1553       fun (t, _, new_style, _) ->
1554         assert (i = t);
1555         pr "  | REG_%s\n" new_style
1556   ) hive_types;
1557
1558   pr "\
1559   | REG_UNKNOWN of int32
1560
1561 type open_flag =
1562 ";
1563   iteri (
1564     fun i ->
1565       fun (v, flag, description) ->
1566         assert (1 lsl i = v);
1567         pr "  | OPEN_%s (** %s *)\n" flag description
1568   ) open_flags;
1569
1570   pr "\
1571
1572 type set_value = {
1573   key : string;
1574   t : hive_type;
1575   value : string;
1576 }
1577
1578 ";
1579
1580   List.iter (
1581     fun (name, style, _, _) ->
1582       generate_ocaml_prototype ~is_external:true name style
1583   ) functions
1584
1585 and generate_ocaml_prototype ?(is_external = false) name style =
1586   let ocaml_name = if name = "open" then "open_file" else name in
1587
1588   if is_external then pr "external " else pr "val ";
1589   pr "%s : " ocaml_name;
1590   List.iter (
1591     function
1592     | AHive -> pr "t -> "
1593     | ANode _ -> pr "node -> "
1594     | AValue _ -> pr "value -> "
1595     | AString _ -> pr "string -> "
1596     | AStringNullable _ -> pr "string option -> "
1597     | AOpenFlags -> pr "open_flag list -> "
1598     | AUnusedFlags -> ()
1599     | ASetValues -> pr "set_value array -> "
1600     | ASetValue -> pr "set_value -> "
1601   ) (snd style);
1602   (match fst style with
1603    | RErr -> pr "unit" (* all errors are turned into exceptions *)
1604    | RErrDispose -> pr "unit"
1605    | RHive -> pr "t"
1606    | RSize -> pr "int64"
1607    | RNode -> pr "node"
1608    | RNodeNotFound -> pr "node"
1609    | RNodeList -> pr "node array"
1610    | RValue -> pr "value"
1611    | RValueList -> pr "value array"
1612    | RString -> pr "string"
1613    | RStringList -> pr "string array"
1614    | RLenType -> pr "hive_type * int"
1615    | RLenTypeVal -> pr "hive_type * string"
1616    | RInt32 -> pr "int32"
1617    | RInt64 -> pr "int64"
1618   );
1619   if is_external then
1620     pr " = \"ocaml_hivex_%s\"" name;
1621   pr "\n"
1622
1623 and generate_ocaml_c () =
1624   generate_header CStyle LGPLv2plus;
1625
1626   pr "\
1627 #include <config.h>
1628
1629 #include <stdio.h>
1630 #include <stdlib.h>
1631 #include <string.h>
1632 #include <stdint.h>
1633 #include <errno.h>
1634
1635 #include <caml/config.h>
1636 #include <caml/alloc.h>
1637 #include <caml/callback.h>
1638 #include <caml/custom.h>
1639 #include <caml/fail.h>
1640 #include <caml/memory.h>
1641 #include <caml/mlvalues.h>
1642 #include <caml/signals.h>
1643
1644 #ifdef HAVE_CAML_UNIXSUPPORT_H
1645 #include <caml/unixsupport.h>
1646 #else
1647 extern value unix_error_of_code (int errcode);
1648 #endif
1649
1650 #ifndef HAVE_CAML_RAISE_WITH_ARGS
1651 static void
1652 caml_raise_with_args (value tag, int nargs, value args[])
1653 {
1654   CAMLparam1 (tag);
1655   CAMLxparamN (args, nargs);
1656   value bucket;
1657   int i;
1658
1659   bucket = caml_alloc_small (1 + nargs, 0);
1660   Field(bucket, 0) = tag;
1661   for (i = 0; i < nargs; i++) Field(bucket, 1 + i) = args[i];
1662   caml_raise(bucket);
1663   CAMLnoreturn;
1664 }
1665 #endif
1666
1667 #include <hivex.h>
1668
1669 #define Hiveh_val(v) (*((hive_h **)Data_custom_val(v)))
1670 static value Val_hiveh (hive_h *);
1671 static int HiveOpenFlags_val (value);
1672 static hive_set_value *HiveSetValue_val (value);
1673 static hive_set_value *HiveSetValues_val (value);
1674 static hive_type HiveType_val (value);
1675 static value Val_hive_type (hive_type);
1676 static value copy_int_array (size_t *);
1677 static value copy_type_len (size_t, hive_type);
1678 static value copy_type_value (const char *, size_t, hive_type);
1679 static void raise_error (const char *) Noreturn;
1680 static void raise_closed (const char *) Noreturn;
1681
1682 ";
1683
1684   (* The wrappers. *)
1685   List.iter (
1686     fun (name, style, _, _) ->
1687       pr "/* Automatically generated wrapper for function\n";
1688       pr " * "; generate_ocaml_prototype name style;
1689       pr " */\n";
1690       pr "\n";
1691
1692       let c_params =
1693         List.map (function
1694                   | ASetValues -> ["nrvalues"; "values"]
1695                   | AUnusedFlags -> ["0"]
1696                   | arg -> [name_of_argt arg]) (snd style) in
1697       let c_params =
1698         match fst style with
1699         | RLenType | RLenTypeVal -> c_params @ [["&t"; "&len"]]
1700         | _ -> c_params in
1701       let c_params = List.concat c_params in
1702
1703       let params =
1704         filter_map (function
1705                     | AUnusedFlags -> None
1706                     | arg -> Some (name_of_argt arg ^ "v")) (snd style) in
1707
1708       pr "/* Emit prototype to appease gcc's -Wmissing-prototypes. */\n";
1709       pr "CAMLprim value ocaml_hivex_%s (value %s" name (List.hd params);
1710       List.iter (pr ", value %s") (List.tl params); pr ");\n";
1711       pr "\n";
1712
1713       pr "CAMLprim value\n";
1714       pr "ocaml_hivex_%s (value %s" name (List.hd params);
1715       List.iter (pr ", value %s") (List.tl params);
1716       pr ")\n";
1717       pr "{\n";
1718
1719       pr "  CAMLparam%d (%s);\n"
1720         (List.length params) (String.concat ", " params);
1721       pr "  CAMLlocal1 (rv);\n";
1722       pr "\n";
1723
1724       List.iter (
1725         function
1726         | AHive ->
1727             pr "  hive_h *h = Hiveh_val (hv);\n";
1728             pr "  if (h == NULL)\n";
1729             pr "    raise_closed (\"%s\");\n" name
1730         | ANode n ->
1731             pr "  hive_node_h %s = Int_val (%sv);\n" n n
1732         | AValue n ->
1733             pr "  hive_value_h %s = Int_val (%sv);\n" n n
1734         | AString n ->
1735             pr "  const char *%s = String_val (%sv);\n" n n
1736         | AStringNullable n ->
1737             pr "  const char *%s =\n" n;
1738             pr "    %sv != Val_int (0) ? String_val (Field (%sv, 0)) : NULL;\n"
1739               n n
1740         | AOpenFlags ->
1741             pr "  int flags = HiveOpenFlags_val (flagsv);\n"
1742         | AUnusedFlags -> ()
1743         | ASetValues ->
1744             pr "  int nrvalues = Wosize_val (valuesv);\n";
1745             pr "  hive_set_value *values = HiveSetValues_val (valuesv);\n"
1746         | ASetValue ->
1747             pr "  hive_set_value *val = HiveSetValue_val (valv);\n"
1748       ) (snd style);
1749       pr "\n";
1750
1751       let error_code =
1752         match fst style with
1753         | RErr -> pr "  int r;\n"; "-1"
1754         | RErrDispose -> pr "  int r;\n"; "-1"
1755         | RHive -> pr "  hive_h *r;\n"; "NULL"
1756         | RSize -> pr "  size_t r;\n"; "0"
1757         | RNode -> pr "  hive_node_h r;\n"; "0"
1758         | RNodeNotFound ->
1759             pr "  errno = 0;\n";
1760             pr "  hive_node_h r;\n";
1761             "0 && errno != 0"
1762         | RNodeList -> pr "  hive_node_h *r;\n"; "NULL"
1763         | RValue -> pr "  hive_value_h r;\n"; "0"
1764         | RValueList -> pr "  hive_value_h *r;\n"; "NULL"
1765         | RString -> pr "  char *r;\n"; "NULL"
1766         | RStringList -> pr "  char **r;\n"; "NULL"
1767         | RLenType ->
1768             pr "  int r;\n";
1769             pr "  size_t len;\n";
1770             pr "  hive_type t;\n";
1771             "-1"
1772         | RLenTypeVal ->
1773             pr "  char *r;\n";
1774             pr "  size_t len;\n";
1775             pr "  hive_type t;\n";
1776             "NULL"
1777         | RInt32 ->
1778             pr "  errno = 0;\n";
1779             pr "  int32_t r;\n";
1780             "-1 && errno != 0"
1781         | RInt64 ->
1782             pr "  errno = 0;\n";
1783             pr "  int64_t r;\n";
1784             "-1 && errno != 0" in
1785
1786       (* The libguestfs OCaml bindings call enter_blocking_section
1787        * here.  However I don't think that is safe, because we are
1788        * holding pointers to caml strings during the call, and these
1789        * could be moved or freed by other threads.  In any case, there
1790        * is very little reason to enter_blocking_section for any hivex
1791        * call, so don't do it.  XXX
1792        *)
1793       (*pr "  caml_enter_blocking_section ();\n";*)
1794       pr "  r = hivex_%s (%s" name (List.hd c_params);
1795       List.iter (pr ", %s") (List.tl c_params);
1796       pr ");\n";
1797       (*pr "  caml_leave_blocking_section ();\n";*)
1798       pr "\n";
1799
1800       (* Dispose of the hive handle (even if hivex_close returns error). *)
1801       (match fst style with
1802        | RErrDispose ->
1803            pr "  /* So we don't double-free in the finalizer. */\n";
1804            pr "  Hiveh_val (hv) = NULL;\n";
1805            pr "\n";
1806        | _ -> ()
1807       );
1808
1809       List.iter (
1810         function
1811         | AHive | ANode _ | AValue _ | AString _ | AStringNullable _
1812         | AOpenFlags | AUnusedFlags -> ()
1813         | ASetValues ->
1814             pr "  free (values);\n";
1815             pr "\n";
1816         | ASetValue ->
1817             pr "  free (val);\n";
1818             pr "\n";
1819       ) (snd style);
1820
1821       (* Check for errors. *)
1822       pr "  if (r == %s)\n" error_code;
1823       pr "    raise_error (\"%s\");\n" name;
1824       pr "\n";
1825
1826       (match fst style with
1827        | RErr -> pr "  rv = Val_unit;\n"
1828        | RErrDispose -> pr "  rv = Val_unit;\n"
1829        | RHive -> pr "  rv = Val_hiveh (r);\n"
1830        | RSize -> pr "  rv = caml_copy_int64 (r);\n"
1831        | RNode -> pr "  rv = Val_int (r);\n"
1832        | RNodeNotFound ->
1833            pr "  if (r == 0)\n";
1834            pr "    caml_raise_not_found ();\n";
1835            pr "\n";
1836            pr "  rv = Val_int (r);\n"
1837        | RNodeList ->
1838            pr "  rv = copy_int_array (r);\n";
1839            pr "  free (r);\n"
1840        | RValue -> pr "  rv = Val_int (r);\n"
1841        | RValueList ->
1842            pr "  rv = copy_int_array (r);\n";
1843            pr "  free (r);\n"
1844        | RString ->
1845            pr "  rv = caml_copy_string (r);\n";
1846            pr "  free (r);\n"
1847        | RStringList ->
1848            pr "  rv = caml_copy_string_array ((const char **) r);\n";
1849            pr "  for (int i = 0; r[i] != NULL; ++i) free (r[i]);\n";
1850            pr "  free (r);\n"
1851        | RLenType -> pr "  rv = copy_type_len (len, t);\n"
1852        | RLenTypeVal ->
1853            pr "  rv = copy_type_value (r, len, t);\n";
1854            pr "  free (r);\n"
1855        | RInt32 -> pr "  rv = caml_copy_int32 (r);\n"
1856        | RInt64 -> pr "  rv = caml_copy_int64 (r);\n"
1857       );
1858
1859       pr "  CAMLreturn (rv);\n";
1860       pr "}\n";
1861       pr "\n";
1862
1863   ) functions;
1864
1865   pr "\
1866 static int
1867 HiveOpenFlags_val (value v)
1868 {
1869   int flags = 0;
1870   value v2;
1871
1872   while (v != Val_int (0)) {
1873     v2 = Field (v, 0);
1874     flags |= 1 << Int_val (v2);
1875     v = Field (v, 1);
1876   }
1877
1878   return flags;
1879 }
1880
1881 static hive_set_value *
1882 HiveSetValue_val (value v)
1883 {
1884   hive_set_value *val = malloc (sizeof (hive_set_value));
1885
1886   val->key = String_val (Field (v, 0));
1887   val->t = HiveType_val (Field (v, 1));
1888   val->len = caml_string_length (Field (v, 2));
1889   val->value = String_val (Field (v, 2));
1890
1891   return val;
1892 }
1893
1894 static hive_set_value *
1895 HiveSetValues_val (value v)
1896 {
1897   size_t nr_values = Wosize_val (v);
1898   hive_set_value *values = malloc (nr_values * sizeof (hive_set_value));
1899   size_t i;
1900   value v2;
1901
1902   for (i = 0; i < nr_values; ++i) {
1903     v2 = Field (v, i);
1904     values[i].key = String_val (Field (v2, 0));
1905     values[i].t = HiveType_val (Field (v2, 1));
1906     values[i].len = caml_string_length (Field (v2, 2));
1907     values[i].value = String_val (Field (v2, 2));
1908   }
1909
1910   return values;
1911 }
1912
1913 static hive_type
1914 HiveType_val (value v)
1915 {
1916   if (Is_long (v))
1917     return Int_val (v); /* REG_NONE etc. */
1918   else
1919     return Int32_val (Field (v, 0)); /* REG_UNKNOWN of int32 */
1920 }
1921
1922 static value
1923 Val_hive_type (hive_type t)
1924 {
1925   CAMLparam0 ();
1926   CAMLlocal2 (rv, v);
1927
1928   if (t <= %d)
1929     CAMLreturn (Val_int (t));
1930   else {
1931     rv = caml_alloc (1, 0); /* REG_UNKNOWN of int32 */
1932     v = caml_copy_int32 (t);
1933     caml_modify (&Field (rv, 0), v);
1934     CAMLreturn (rv);
1935   }
1936 }
1937
1938 static value
1939 copy_int_array (size_t *xs)
1940 {
1941   CAMLparam0 ();
1942   CAMLlocal2 (v, rv);
1943   size_t nr, i;
1944
1945   for (nr = 0; xs[nr] != 0; ++nr)
1946     ;
1947   if (nr == 0)
1948     CAMLreturn (Atom (0));
1949   else {
1950     rv = caml_alloc (nr, 0);
1951     for (i = 0; i < nr; ++i) {
1952       v = Val_int (xs[i]);
1953       Store_field (rv, i, v); /* Safe because v is not a block. */
1954     }
1955     CAMLreturn (rv);
1956   }
1957 }
1958
1959 static value
1960 copy_type_len (size_t len, hive_type t)
1961 {
1962   CAMLparam0 ();
1963   CAMLlocal2 (v, rv);
1964
1965   rv = caml_alloc (2, 0);
1966   v = Val_hive_type (t);
1967   Store_field (rv, 0, v);
1968   v = Val_int (len);
1969   Store_field (rv, 1, v);
1970   CAMLreturn (rv);
1971 }
1972
1973 static value
1974 copy_type_value (const char *r, size_t len, hive_type t)
1975 {
1976   CAMLparam0 ();
1977   CAMLlocal2 (v, rv);
1978
1979   rv = caml_alloc (2, 0);
1980   v = Val_hive_type (t);
1981   Store_field (rv, 0, v);
1982   v = caml_alloc_string (len);
1983   memcpy (String_val (v), r, len);
1984   caml_modify (&Field (rv, 1), v);
1985   CAMLreturn (rv);
1986 }
1987
1988 /* Raise exceptions. */
1989 static void
1990 raise_error (const char *function)
1991 {
1992   /* Save errno early in case it gets trashed. */
1993   int err = errno;
1994
1995   CAMLparam0 ();
1996   CAMLlocal3 (v1, v2, v3);
1997
1998   v1 = caml_copy_string (function);
1999   v2 = unix_error_of_code (err);
2000   v3 = caml_copy_string (strerror (err));
2001   value vvv[] = { v1, v2, v3 };
2002   caml_raise_with_args (*caml_named_value (\"ocaml_hivex_error\"), 3, vvv);
2003
2004   CAMLnoreturn;
2005 }
2006
2007 static void
2008 raise_closed (const char *function)
2009 {
2010   CAMLparam0 ();
2011   CAMLlocal1 (v);
2012
2013   v = caml_copy_string (function);
2014   caml_raise_with_arg (*caml_named_value (\"ocaml_hivex_closed\"), v);
2015
2016   CAMLnoreturn;
2017 }
2018
2019 /* Allocate handles and deal with finalization. */
2020 static void
2021 hivex_finalize (value hv)
2022 {
2023   hive_h *h = Hiveh_val (hv);
2024   if (h) hivex_close (h);
2025 }
2026
2027 static struct custom_operations hivex_custom_operations = {
2028   (char *) \"hivex_custom_operations\",
2029   hivex_finalize,
2030   custom_compare_default,
2031   custom_hash_default,
2032   custom_serialize_default,
2033   custom_deserialize_default
2034 };
2035
2036 static value
2037 Val_hiveh (hive_h *h)
2038 {
2039   CAMLparam0 ();
2040   CAMLlocal1 (rv);
2041
2042   rv = caml_alloc_custom (&hivex_custom_operations,
2043                           sizeof (hive_h *), 0, 1);
2044   Hiveh_val (rv) = h;
2045
2046   CAMLreturn (rv);
2047 }
2048 " max_hive_type
2049
2050 and generate_perl_pm () =
2051   generate_header HashStyle LGPLv2plus;
2052
2053   pr "\
2054 =pod
2055
2056 =head1 NAME
2057
2058 Win::Hivex - Perl bindings for reading and writing Windows Registry hive files
2059
2060 =head1 SYNOPSIS
2061
2062  use Win::Hivex;
2063
2064  $h = Win::Hivex->open ('SOFTWARE');
2065  $root_node = $h->root ();
2066  print $h->node_name ($root_node);
2067
2068 =head1 DESCRIPTION
2069
2070 The C<Win::Hivex> module provides a Perl XS binding to the
2071 L<hivex(3)> API for reading and writing Windows Registry binary
2072 hive files.
2073
2074 =head1 ERRORS
2075
2076 All errors turn into calls to C<croak> (see L<Carp(3)>).
2077
2078 =head1 METHODS
2079
2080 =over 4
2081
2082 =cut
2083
2084 package Win::Hivex;
2085
2086 use strict;
2087 use warnings;
2088
2089 require XSLoader;
2090 XSLoader::load ('Win::Hivex');
2091
2092 =item open
2093
2094  $h = Win::Hivex->open ($filename,";
2095
2096   List.iter (
2097     fun (_, flag, _) ->
2098       pr "\n                        [%s => 1,]" (String.lowercase flag)
2099   ) open_flags;
2100
2101   pr ")
2102
2103 Open a Windows Registry binary hive file.
2104
2105 The C<verbose> and C<debug> flags enable different levels of
2106 debugging messages.
2107
2108 The C<write> flag is required if you will be modifying the
2109 hive file (see L<hivex(3)/WRITING TO HIVE FILES>).
2110
2111 This function returns a hive handle.  The hive handle is
2112 closed automatically when its reference count drops to 0.
2113
2114 =cut
2115
2116 sub open {
2117   my $proto = shift;
2118   my $class = ref ($proto) || $proto;
2119   my $filename = shift;
2120   my %%flags = @_;
2121   my $flags = 0;
2122
2123 ";
2124
2125   List.iter (
2126     fun (n, flag, description) ->
2127       pr "  # %s\n" description;
2128       pr "  $flags += %d if $flags{%s};\n" n (String.lowercase flag)
2129   ) open_flags;
2130
2131   pr "\
2132
2133   my $self = Win::Hivex::_open ($filename, $flags);
2134   bless $self, $class;
2135   return $self;
2136 }
2137
2138 ";
2139
2140   List.iter (
2141     fun (name, style, _, longdesc) ->
2142       (* The close call isn't explicit in Perl: handles are closed
2143        * when their reference count drops to 0.
2144        *
2145        * The open call is coded specially in Perl.
2146        *
2147        * Therefore we don't generate prototypes for these two calls:
2148        *)
2149       if fst style <> RErrDispose && List.hd (snd style) = AHive then (
2150         let longdesc = replace_str longdesc "C<hivex_" "C<" in
2151         pr "=item %s\n\n " name;
2152         generate_perl_prototype name style;
2153         pr "\n\n";
2154         pr "%s\n\n" longdesc;
2155
2156         (match fst style with
2157          | RErr
2158          | RErrDispose
2159          | RHive
2160          | RString
2161          | RStringList
2162          | RLenType
2163          | RLenTypeVal
2164          | RInt32
2165          | RInt64 -> ()
2166          | RSize ->
2167              pr "\
2168 This returns a size.\n\n"
2169          | RNode ->
2170              pr "\
2171 This returns a node handle.\n\n"
2172          | RNodeNotFound ->
2173              pr "\
2174 This returns a node handle, or C<undef> if the node was not found.\n\n"
2175          | RNodeList ->
2176              pr "\
2177 This returns a list of node handles.\n\n"
2178          | RValue ->
2179              pr "\
2180 This returns a value handle.\n\n"
2181          | RValueList ->
2182              pr "\
2183 This returns a list of value handles.\n\n"
2184         );
2185
2186         if List.mem ASetValues (snd style) then
2187           pr "C<@values> is an array of (keys, value) pairs.
2188 Each element should be a hashref containing C<key>, C<t> (type)
2189 and C<data>.
2190
2191 Any existing values stored at the node are discarded, and their
2192 C<value> handles become invalid.  Thus you can remove all
2193 values stored at C<node> by passing C<@values = []>.\n\n"
2194       )
2195   ) functions;
2196
2197   pr "\
2198 =cut
2199
2200 1;
2201
2202 =back
2203
2204 =head1 COPYRIGHT
2205
2206 Copyright (C) %s Red Hat Inc.
2207
2208 =head1 LICENSE
2209
2210 Please see the file COPYING.LIB for the full license.
2211
2212 =head1 SEE ALSO
2213
2214 L<hivex(3)>,
2215 L<hivexsh(1)>,
2216 L<http://libguestfs.org>,
2217 L<Sys::Guestfs(3)>.
2218
2219 =cut
2220 " copyright_years
2221
2222 and generate_perl_prototype name style =
2223   (* Return type. *)
2224   (match fst style with
2225    | RErr
2226    | RErrDispose -> ()
2227    | RHive -> pr "$h = "
2228    | RSize -> pr "$size = "
2229    | RNode
2230    | RNodeNotFound -> pr "$node = "
2231    | RNodeList -> pr "@nodes = "
2232    | RValue -> pr "$value = "
2233    | RValueList -> pr "@values = "
2234    | RString -> pr "$string = "
2235    | RStringList -> pr "@strings = "
2236    | RLenType -> pr "($type, $len) = "
2237    | RLenTypeVal -> pr "($type, $data) = "
2238    | RInt32 -> pr "$int32 = "
2239    | RInt64 -> pr "$int64 = "
2240   );
2241
2242   let args = List.tl (snd style) in
2243
2244   (* AUnusedFlags is dropped in the bindings. *)
2245   let args = List.filter ((<>) AUnusedFlags) args in
2246
2247   pr "$h->%s (" name;
2248
2249   let comma = ref false in
2250   List.iter (
2251     fun arg ->
2252       if !comma then pr ", "; comma := true;
2253       match arg with
2254       | AHive -> pr "$h"
2255       | ANode n
2256       | AValue n
2257       | AString n -> pr "$%s" n
2258       | AStringNullable n -> pr "[$%s|undef]" n
2259       | AOpenFlags -> pr "[flags]"
2260       | AUnusedFlags -> assert false
2261       | ASetValues -> pr "\\@values"
2262       | ASetValue -> pr "$val"
2263   ) args;
2264
2265   pr ")"
2266
2267 and generate_perl_xs () =
2268   generate_header CStyle LGPLv2plus;
2269
2270   pr "\
2271 #include \"EXTERN.h\"
2272 #include \"perl.h\"
2273 #include \"XSUB.h\"
2274
2275 #include <string.h>
2276 #include <hivex.h>
2277 #include <inttypes.h>
2278
2279 static SV *
2280 my_newSVll(long long val) {
2281 #ifdef USE_64_BIT_ALL
2282   return newSViv(val);
2283 #else
2284   char buf[100];
2285   int len;
2286   len = snprintf(buf, 100, \"%%\" PRId64, val);
2287   return newSVpv(buf, len);
2288 #endif
2289 }
2290
2291 #if 0
2292 static SV *
2293 my_newSVull(unsigned long long val) {
2294 #ifdef USE_64_BIT_ALL
2295   return newSVuv(val);
2296 #else
2297   char buf[100];
2298   int len;
2299   len = snprintf(buf, 100, \"%%\" PRIu64, val);
2300   return newSVpv(buf, len);
2301 #endif
2302 }
2303 #endif
2304
2305 #if 0
2306 /* http://www.perlmonks.org/?node_id=680842 */
2307 static char **
2308 XS_unpack_charPtrPtr (SV *arg) {
2309   char **ret;
2310   AV *av;
2311   I32 i;
2312
2313   if (!arg || !SvOK (arg) || !SvROK (arg) || SvTYPE (SvRV (arg)) != SVt_PVAV)
2314     croak (\"array reference expected\");
2315
2316   av = (AV *)SvRV (arg);
2317   ret = malloc ((av_len (av) + 1 + 1) * sizeof (char *));
2318   if (!ret)
2319     croak (\"malloc failed\");
2320
2321   for (i = 0; i <= av_len (av); i++) {
2322     SV **elem = av_fetch (av, i, 0);
2323
2324     if (!elem || !*elem)
2325       croak (\"missing element in list\");
2326
2327     ret[i] = SvPV_nolen (*elem);
2328   }
2329
2330   ret[i] = NULL;
2331
2332   return ret;
2333 }
2334 #endif
2335
2336 /* Handle set_values parameter. */
2337 typedef struct pl_set_values {
2338   size_t nr_values;
2339   hive_set_value *values;
2340 } pl_set_values;
2341
2342 static pl_set_values
2343 unpack_pl_set_values (SV *sv)
2344 {
2345   pl_set_values ret;
2346   AV *av;
2347   I32 i;
2348
2349   if (!sv || !SvOK (sv) || !SvROK (sv) || SvTYPE (SvRV (sv)) != SVt_PVAV)
2350     croak (\"array reference expected\");
2351
2352   av = (AV *)SvRV(sv);
2353   ret.nr_values = av_len (av) + 1;
2354   ret.values = malloc (ret.nr_values * sizeof (hive_set_value));
2355   if (!ret.values)
2356     croak (\"malloc failed\");
2357
2358   for (i = 0; i <= av_len (av); i++) {
2359     SV **hvp = av_fetch (av, i, 0);
2360
2361     if (!hvp || !*hvp || !SvROK (*hvp) || SvTYPE (SvRV (*hvp)) != SVt_PVHV)
2362       croak (\"missing element in list or not a hash ref\");
2363
2364     HV *hv = (HV *)SvRV(*hvp);
2365
2366     SV **svp;
2367     svp = hv_fetch (hv, \"key\", 3, 0);
2368     if (!svp || !*svp)
2369       croak (\"missing 'key' in hash\");
2370     ret.values[i].key = SvPV_nolen (*svp);
2371
2372     svp = hv_fetch (hv, \"t\", 1, 0);
2373     if (!svp || !*svp)
2374       croak (\"missing 't' in hash\");
2375     ret.values[i].t = SvIV (*svp);
2376
2377     svp = hv_fetch (hv, \"value\", 5, 0);
2378     if (!svp || !*svp)
2379       croak (\"missing 'value' in hash\");
2380     ret.values[i].value = SvPV (*svp, ret.values[i].len);
2381   }
2382
2383   return ret;
2384 }
2385
2386 static hive_set_value *
2387 unpack_set_value (SV *sv)
2388 {
2389   hive_set_value *ret;
2390
2391   if (!sv || !SvROK (sv) || SvTYPE (SvRV (sv)) != SVt_PVHV)
2392     croak (\"not a hash ref\");
2393
2394   ret = malloc (sizeof (hive_set_value));
2395   if (ret == NULL)
2396     croak (\"malloc failed\");
2397
2398   HV *hv = (HV *)SvRV(sv);
2399
2400   SV **svp;
2401   svp = hv_fetch (hv, \"key\", 3, 0);
2402   if (!svp || !*svp)
2403     croak (\"missing 'key' in hash\");
2404   ret->key = SvPV_nolen (*svp);
2405
2406   svp = hv_fetch (hv, \"t\", 1, 0);
2407   if (!svp || !*svp)
2408     croak (\"missing 't' in hash\");
2409   ret->t = SvIV (*svp);
2410
2411   svp = hv_fetch (hv, \"value\", 5, 0);
2412   if (!svp || !*svp)
2413     croak (\"missing 'value' in hash\");
2414   ret->value = SvPV (*svp, ret->len);
2415
2416   return ret;
2417 }
2418
2419 MODULE = Win::Hivex  PACKAGE = Win::Hivex
2420
2421 PROTOTYPES: ENABLE
2422
2423 hive_h *
2424 _open (filename, flags)
2425       char *filename;
2426       int flags;
2427    CODE:
2428       RETVAL = hivex_open (filename, flags);
2429       if (!RETVAL)
2430         croak (\"hivex_open: %%s: %%s\", filename, strerror (errno));
2431  OUTPUT:
2432       RETVAL
2433
2434 void
2435 DESTROY (h)
2436       hive_h *h;
2437  PPCODE:
2438       if (hivex_close (h) == -1)
2439         croak (\"hivex_close: %%s\", strerror (errno));
2440
2441 ";
2442
2443   List.iter (
2444     fun (name, style, _, longdesc) ->
2445       (* The close and open calls are handled specially above. *)
2446       if fst style <> RErrDispose && List.hd (snd style) = AHive then (
2447         (match fst style with
2448          | RErr -> pr "void\n"
2449          | RErrDispose -> failwith "perl bindings cannot handle a call which disposes of the handle"
2450          | RHive -> failwith "perl bindings cannot handle a call which returns a handle"
2451          | RSize
2452          | RNode
2453          | RNodeNotFound
2454          | RValue
2455          | RString -> pr "SV *\n"
2456          | RNodeList
2457          | RValueList
2458          | RStringList
2459          | RLenType
2460          | RLenTypeVal -> pr "void\n"
2461          | RInt32 -> pr "SV *\n"
2462          | RInt64 -> pr "SV *\n"
2463         );
2464
2465         (* Call and arguments. *)
2466         let perl_params =
2467           filter_map (function
2468                       | AUnusedFlags -> None
2469                       | arg -> Some (name_of_argt arg)) (snd style) in
2470
2471         let c_params =
2472           List.map (function
2473                     | AUnusedFlags -> "0"
2474                     | ASetValues -> "values.nr_values, values.values"
2475                     | arg -> name_of_argt arg) (snd style) in
2476
2477         pr "%s (%s)\n" name (String.concat ", " perl_params);
2478         iteri (
2479           fun i ->
2480             function
2481             | AHive ->
2482                 pr "      hive_h *h;\n"
2483             | ANode n
2484             | AValue n ->
2485                 pr "      int %s;\n" n
2486             | AString n ->
2487                 pr "      char *%s;\n" n
2488             | AStringNullable n ->
2489                 (* http://www.perlmonks.org/?node_id=554277 *)
2490                 pr "      char *%s = SvOK(ST(%d)) ? SvPV_nolen(ST(%d)) : NULL;\n" n i i
2491             | AOpenFlags ->
2492                 pr "      int flags;\n"
2493             | AUnusedFlags -> ()
2494             | ASetValues ->
2495                 pr "      pl_set_values values = unpack_pl_set_values (ST(%d));\n" i
2496             | ASetValue ->
2497                 pr "      hive_set_value *val = unpack_set_value (ST(%d));\n" i
2498         ) (snd style);
2499
2500         let free_args () =
2501           List.iter (
2502             function
2503             | ASetValues ->
2504                 pr "      free (values.values);\n"
2505             | ASetValue ->
2506                 pr "      free (val);\n"
2507             | AHive | ANode _ | AValue _ | AString _ | AStringNullable _
2508             | AOpenFlags | AUnusedFlags -> ()
2509           ) (snd style)
2510         in
2511
2512         (* Code. *)
2513         (match fst style with
2514          | RErr ->
2515              pr "PREINIT:\n";
2516              pr "      int r;\n";
2517              pr " PPCODE:\n";
2518              pr "      r = hivex_%s (%s);\n"
2519                name (String.concat ", " c_params);
2520              free_args ();
2521              pr "      if (r == -1)\n";
2522              pr "        croak (\"%%s: %%s\", \"%s\", strerror (errno));\n"
2523                name;
2524
2525          | RErrDispose -> assert false
2526          | RHive -> assert false
2527
2528          | RSize
2529          | RNode
2530          | RValue ->
2531              pr "PREINIT:\n";
2532              pr "      /* hive_node_h = hive_value_h = size_t so we cheat\n";
2533              pr "         here to simplify the generator */\n";
2534              pr "      size_t r;\n";
2535              pr "   CODE:\n";
2536              pr "      r = hivex_%s (%s);\n"
2537                name (String.concat ", " c_params);
2538              free_args ();
2539              pr "      if (r == 0)\n";
2540              pr "        croak (\"%%s: %%s\", \"%s\", strerror (errno));\n"
2541                name;
2542              pr "      RETVAL = newSViv (r);\n";
2543              pr " OUTPUT:\n";
2544              pr "      RETVAL\n"
2545
2546          | RNodeNotFound ->
2547              pr "PREINIT:\n";
2548              pr "      hive_node_h r;\n";
2549              pr "   CODE:\n";
2550              pr "      errno = 0;\n";
2551              pr "      r = hivex_%s (%s);\n"
2552                name (String.concat ", " c_params);
2553              free_args ();
2554              pr "      if (r == 0 && errno != 0)\n";
2555              pr "        croak (\"%%s: %%s\", \"%s\", strerror (errno));\n"
2556                name;
2557              pr "      if (r == 0)\n";
2558              pr "        RETVAL = &PL_sv_undef;\n";
2559              pr "      else\n";
2560              pr "        RETVAL = newSViv (r);\n";
2561              pr " OUTPUT:\n";
2562              pr "      RETVAL\n"
2563
2564          | RString ->
2565              pr "PREINIT:\n";
2566              pr "      char *r;\n";
2567              pr "   CODE:\n";
2568              pr "      r = hivex_%s (%s);\n"
2569                name (String.concat ", " c_params);
2570              free_args ();
2571              pr "      if (r == NULL)\n";
2572              pr "        croak (\"%%s: %%s\", \"%s\", strerror (errno));\n"
2573                name;
2574              pr "      RETVAL = newSVpv (r, 0);\n";
2575              pr "      free (r);\n";
2576              pr " OUTPUT:\n";
2577              pr "      RETVAL\n"
2578
2579          | RNodeList
2580          | RValueList ->
2581              pr "PREINIT:\n";
2582              pr "      size_t *r;\n";
2583              pr "      int i, n;\n";
2584              pr " PPCODE:\n";
2585              pr "      r = hivex_%s (%s);\n"
2586                name (String.concat ", " c_params);
2587              free_args ();
2588              pr "      if (r == NULL)\n";
2589              pr "        croak (\"%%s: %%s\", \"%s\", strerror (errno));\n"
2590                name;
2591              pr "      for (n = 0; r[n] != 0; ++n) /**/;\n";
2592              pr "      EXTEND (SP, n);\n";
2593              pr "      for (i = 0; i < n; ++i)\n";
2594              pr "        PUSHs (sv_2mortal (newSViv (r[i])));\n";
2595              pr "      free (r);\n";
2596
2597          | RStringList ->
2598              pr "PREINIT:\n";
2599              pr "      char **r;\n";
2600              pr "      int i, n;\n";
2601              pr " PPCODE:\n";
2602              pr "      r = hivex_%s (%s);\n"
2603                name (String.concat ", " c_params);
2604              free_args ();
2605              pr "      if (r == NULL)\n";
2606              pr "        croak (\"%%s: %%s\", \"%s\", strerror (errno));\n"
2607                name;
2608              pr "      for (n = 0; r[n] != NULL; ++n) /**/;\n";
2609              pr "      EXTEND (SP, n);\n";
2610              pr "      for (i = 0; i < n; ++i) {\n";
2611              pr "        PUSHs (sv_2mortal (newSVpv (r[i], 0)));\n";
2612              pr "        free (r[i]);\n";
2613              pr "      }\n";
2614              pr "      free (r);\n";
2615
2616          | RLenType ->
2617              pr "PREINIT:\n";
2618              pr "      int r;\n";
2619              pr "      size_t len;\n";
2620              pr "      hive_type type;\n";
2621              pr " PPCODE:\n";
2622              pr "      r = hivex_%s (%s, &type, &len);\n"
2623                name (String.concat ", " c_params);
2624              free_args ();
2625              pr "      if (r == -1)\n";
2626              pr "        croak (\"%%s: %%s\", \"%s\", strerror (errno));\n"
2627                name;
2628              pr "      EXTEND (SP, 2);\n";
2629              pr "      PUSHs (sv_2mortal (newSViv (type)));\n";
2630              pr "      PUSHs (sv_2mortal (newSViv (len)));\n";
2631
2632          | RLenTypeVal ->
2633              pr "PREINIT:\n";
2634              pr "      char *r;\n";
2635              pr "      size_t len;\n";
2636              pr "      hive_type type;\n";
2637              pr " PPCODE:\n";
2638              pr "      r = hivex_%s (%s, &type, &len);\n"
2639                name (String.concat ", " c_params);
2640              free_args ();
2641              pr "      if (r == NULL)\n";
2642              pr "        croak (\"%%s: %%s\", \"%s\", strerror (errno));\n"
2643                name;
2644              pr "      EXTEND (SP, 2);\n";
2645              pr "      PUSHs (sv_2mortal (newSViv (type)));\n";
2646              pr "      PUSHs (sv_2mortal (newSVpvn (r, len)));\n";
2647              pr "      free (r);\n";
2648
2649          | RInt32 ->
2650              pr "PREINIT:\n";
2651              pr "      int32_t r;\n";
2652              pr "   CODE:\n";
2653              pr "      errno = 0;\n";
2654              pr "      r = hivex_%s (%s);\n"
2655                name (String.concat ", " c_params);
2656              free_args ();
2657              pr "      if (r == -1 && errno != 0)\n";
2658              pr "        croak (\"%%s: %%s\", \"%s\", strerror (errno));\n"
2659                name;
2660              pr "      RETVAL = newSViv (r);\n";
2661              pr " OUTPUT:\n";
2662              pr "      RETVAL\n"
2663
2664          | RInt64 ->
2665              pr "PREINIT:\n";
2666              pr "      int64_t r;\n";
2667              pr "   CODE:\n";
2668              pr "      errno = 0;\n";
2669              pr "      r = hivex_%s (%s);\n"
2670                name (String.concat ", " c_params);
2671              free_args ();
2672              pr "      if (r == -1 && errno != 0)\n";
2673              pr "        croak (\"%%s: %%s\", \"%s\", strerror (errno));\n"
2674                name;
2675              pr "      RETVAL = my_newSVll (r);\n";
2676              pr " OUTPUT:\n";
2677              pr "      RETVAL\n"
2678         );
2679         pr "\n"
2680       )
2681   ) functions
2682
2683 and generate_python_c () =
2684   generate_header CStyle LGPLv2plus;
2685
2686   pr "\
2687 #define PY_SSIZE_T_CLEAN 1
2688 #include <Python.h>
2689
2690 #if PY_VERSION_HEX < 0x02050000
2691 typedef int Py_ssize_t;
2692 #define PY_SSIZE_T_MAX INT_MAX
2693 #define PY_SSIZE_T_MIN INT_MIN
2694 #endif
2695
2696 #include <stdio.h>
2697 #include <stdlib.h>
2698 #include <assert.h>
2699
2700 #include \"hivex.h\"
2701
2702 #ifndef HAVE_PYCAPSULE_NEW
2703 typedef struct {
2704   PyObject_HEAD
2705   hive_h *h;
2706 } Pyhivex_Object;
2707 #endif
2708
2709 static hive_h *
2710 get_handle (PyObject *obj)
2711 {
2712   assert (obj);
2713   assert (obj != Py_None);
2714 #ifndef HAVE_PYCAPSULE_NEW
2715   return ((Pyhivex_Object *) obj)->h;
2716 #else
2717   return (hive_h *) PyCapsule_GetPointer(obj, \"hive_h\");
2718 #endif
2719 }
2720
2721 static PyObject *
2722 put_handle (hive_h *h)
2723 {
2724   assert (h);
2725 #ifndef HAVE_PYCAPSULE_NEW
2726   return
2727     PyCObject_FromVoidPtrAndDesc ((void *) h, (char *) \"hive_h\", NULL);
2728 #else
2729   return PyCapsule_New ((void *) h, \"hive_h\", NULL);
2730 #endif
2731 }
2732
2733 /* This returns pointers into the Python objects, which should
2734  * not be freed.
2735  */
2736 static int
2737 get_value (PyObject *v, hive_set_value *ret)
2738 {
2739   PyObject *obj;
2740
2741   obj = PyDict_GetItemString (v, \"key\");
2742   if (!obj) {
2743     PyErr_SetString (PyExc_RuntimeError, \"no 'key' element in dictionary\");
2744     return -1;
2745   }
2746   if (!PyString_Check (obj)) {
2747     PyErr_SetString (PyExc_RuntimeError, \"'key' element is not a string\");
2748     return -1;
2749   }
2750   ret->key = PyString_AsString (obj);
2751
2752   obj = PyDict_GetItemString (v, \"t\");
2753   if (!obj) {
2754     PyErr_SetString (PyExc_RuntimeError, \"no 't' element in dictionary\");
2755     return -1;
2756   }
2757   if (!PyInt_Check (obj)) {
2758     PyErr_SetString (PyExc_RuntimeError, \"'t' element is not an integer\");
2759     return -1;
2760   }
2761   ret->t = PyInt_AsLong (obj);
2762
2763   obj = PyDict_GetItemString (v, \"value\");
2764   if (!obj) {
2765     PyErr_SetString (PyExc_RuntimeError, \"no 'value' element in dictionary\");
2766     return -1;
2767   }
2768   if (!PyString_Check (obj)) {
2769     PyErr_SetString (PyExc_RuntimeError, \"'value' element is not a string\");
2770     return -1;
2771   }
2772   ret->value = PyString_AsString (obj);
2773   ret->len = PyString_Size (obj);
2774
2775   return 0;
2776 }
2777
2778 typedef struct py_set_values {
2779   size_t nr_values;
2780   hive_set_value *values;
2781 } py_set_values;
2782
2783 static int
2784 get_values (PyObject *v, py_set_values *ret)
2785 {
2786   Py_ssize_t slen;
2787   size_t len, i;
2788
2789   if (!PyList_Check (v)) {
2790     PyErr_SetString (PyExc_RuntimeError, \"expecting a list parameter\");
2791     return -1;
2792   }
2793
2794   slen = PyList_Size (v);
2795   if (slen < 0) {
2796     PyErr_SetString (PyExc_RuntimeError, \"get_string_list: PyList_Size failure\");
2797     return -1;
2798   }
2799   len = (size_t) slen;
2800   ret->nr_values = len;
2801   ret->values = malloc (len * sizeof (hive_set_value));
2802   if (!ret->values) {
2803     PyErr_SetString (PyExc_RuntimeError, strerror (errno));
2804     return -1;
2805   }
2806
2807   for (i = 0; i < len; ++i) {
2808     if (get_value (PyList_GetItem (v, i), &(ret->values[i])) == -1) {
2809       free (ret->values);
2810       return -1;
2811     }
2812   }
2813
2814   return 0;
2815 }
2816
2817 static PyObject *
2818 put_string_list (char * const * const argv)
2819 {
2820   PyObject *list;
2821   size_t argc, i;
2822
2823   for (argc = 0; argv[argc] != NULL; ++argc)
2824     ;
2825
2826   list = PyList_New (argc);
2827   for (i = 0; i < argc; ++i)
2828     PyList_SetItem (list, i, PyString_FromString (argv[i]));
2829
2830   return list;
2831 }
2832
2833 static void
2834 free_strings (char **argv)
2835 {
2836   size_t argc;
2837
2838   for (argc = 0; argv[argc] != NULL; ++argc)
2839     free (argv[argc]);
2840   free (argv);
2841 }
2842
2843 /* Since hive_node_t is the same as hive_value_t this also works for values. */
2844 static PyObject *
2845 put_node_list (hive_node_h *nodes)
2846 {
2847   PyObject *list;
2848   size_t argc, i;
2849
2850   for (argc = 0; nodes[argc] != 0; ++argc)
2851     ;
2852
2853   list = PyList_New (argc);
2854   for (i = 0; i < argc; ++i)
2855     PyList_SetItem (list, i, PyLong_FromLongLong ((long) nodes[i]));
2856
2857   return list;
2858 }
2859
2860 static PyObject *
2861 put_len_type (size_t len, hive_type t)
2862 {
2863   PyObject *r = PyTuple_New (2);
2864   PyTuple_SetItem (r, 0, PyInt_FromLong ((long) t));
2865   PyTuple_SetItem (r, 1, PyLong_FromLongLong ((long) len));
2866   return r;
2867 }
2868
2869 static PyObject *
2870 put_val_type (char *val, size_t len, hive_type t)
2871 {
2872   PyObject *r = PyTuple_New (2);
2873   PyTuple_SetItem (r, 0, PyInt_FromLong ((long) t));
2874   PyTuple_SetItem (r, 1, PyString_FromStringAndSize (val, len));
2875   return r;
2876 }
2877
2878 ";
2879
2880   (* Generate functions. *)
2881   List.iter (
2882     fun (name, style, _, longdesc) ->
2883       pr "static PyObject *\n";
2884       pr "py_hivex_%s (PyObject *self, PyObject *args)\n" name;
2885       pr "{\n";
2886       pr "  PyObject *py_r;\n";
2887
2888       let error_code =
2889         match fst style with
2890         | RErr -> pr "  int r;\n"; "-1"
2891         | RErrDispose -> pr "  int r;\n"; "-1"
2892         | RHive -> pr "  hive_h *r;\n"; "NULL"
2893         | RSize -> pr "  size_t r;\n"; "0"
2894         | RNode -> pr "  hive_node_h r;\n"; "0"
2895         | RNodeNotFound ->
2896             pr "  errno = 0;\n";
2897             pr "  hive_node_h r;\n";
2898             "0 && errno != 0"
2899         | RNodeList -> pr "  hive_node_h *r;\n"; "NULL"
2900         | RValue -> pr "  hive_value_h r;\n"; "0"
2901         | RValueList -> pr "  hive_value_h *r;\n"; "NULL"
2902         | RString -> pr "  char *r;\n"; "NULL"
2903         | RStringList -> pr "  char **r;\n"; "NULL"
2904         | RLenType ->
2905             pr "  int r;\n";
2906             pr "  size_t len;\n";
2907             pr "  hive_type t;\n";
2908             "-1"
2909         | RLenTypeVal ->
2910             pr "  char *r;\n";
2911             pr "  size_t len;\n";
2912             pr "  hive_type t;\n";
2913             "NULL"
2914         | RInt32 ->
2915             pr "  errno = 0;\n";
2916             pr "  int32_t r;\n";
2917             "-1 && errno != 0"
2918         | RInt64 ->
2919             pr "  errno = 0;\n";
2920             pr "  int64_t r;\n";
2921             "-1 && errno != 0" in
2922
2923       (* Call and arguments. *)
2924       let c_params =
2925         List.map (function
2926                   | AUnusedFlags -> "0"
2927                   | ASetValues -> "values.nr_values, values.values"
2928                   | ASetValue -> "&val"
2929                   | arg -> name_of_argt arg) (snd style) in
2930       let c_params =
2931         match fst style with
2932         | RLenType | RLenTypeVal -> c_params @ ["&t"; "&len"]
2933         | _ -> c_params in
2934
2935       List.iter (
2936         function
2937         | AHive ->
2938             pr "  hive_h *h;\n";
2939             pr "  PyObject *py_h;\n"
2940         | ANode n
2941         | AValue n ->
2942             pr "  long %s;\n" n
2943         | AString n
2944         | AStringNullable n ->
2945             pr "  char *%s;\n" n
2946         | AOpenFlags ->
2947             pr "  int flags;\n"
2948         | AUnusedFlags -> ()
2949         | ASetValues ->
2950             pr "  py_set_values values;\n";
2951             pr "  PyObject *py_values;\n"
2952         | ASetValue ->
2953             pr "  hive_set_value val;\n";
2954             pr "  PyObject *py_val;\n"
2955       ) (snd style);
2956
2957       pr "\n";
2958
2959       (* Convert the required parameters. *)
2960       pr "  if (!PyArg_ParseTuple (args, (char *) \"";
2961       List.iter (
2962         function
2963         | AHive ->
2964             pr "O"
2965         | ANode n
2966         | AValue n ->
2967             pr "l"
2968         | AString n ->
2969             pr "s"
2970         | AStringNullable n ->
2971             pr "z"
2972         | AOpenFlags ->
2973             pr "i"
2974         | AUnusedFlags -> ()
2975         | ASetValues
2976         | ASetValue ->
2977             pr "O"
2978       ) (snd style);
2979
2980       pr ":hivex_%s\"" name;
2981
2982       List.iter (
2983         function
2984         | AHive ->
2985             pr ", &py_h"
2986         | ANode n
2987         | AValue n ->
2988             pr ", &%s" n
2989         | AString n
2990         | AStringNullable n ->
2991             pr ", &%s" n
2992         | AOpenFlags ->
2993             pr ", &flags"
2994         | AUnusedFlags -> ()
2995         | ASetValues ->
2996             pr ", &py_values"
2997         | ASetValue ->
2998             pr ", &py_val"
2999         ) (snd style);
3000
3001       pr "))\n";
3002       pr "    return NULL;\n";
3003
3004       (* Convert some Python argument types to C. *)
3005       List.iter (
3006         function
3007         | AHive ->
3008             pr "  h = get_handle (py_h);\n"
3009         | ANode _
3010         | AValue _
3011         | AString _
3012         | AStringNullable _
3013         | AOpenFlags
3014         | AUnusedFlags -> ()
3015         | ASetValues ->
3016             pr "  if (get_values (py_values, &values) == -1)\n";
3017             pr "    return NULL;\n"
3018         | ASetValue ->
3019             pr "  if (get_value (py_val, &val) == -1)\n";
3020             pr "    return NULL;\n"
3021       ) (snd style);
3022
3023       (* Call the C function. *)
3024       pr "  r = hivex_%s (%s);\n" name (String.concat ", " c_params);
3025
3026       (* Free up arguments. *)
3027       List.iter (
3028         function
3029         | AHive | ANode _ | AValue _
3030         | AString _ | AStringNullable _
3031         | AOpenFlags | AUnusedFlags -> ()
3032         | ASetValues ->
3033             pr "  free (values.values);\n"
3034         | ASetValue -> ()
3035       ) (snd style);
3036
3037       (* Check for errors from C library. *)
3038       pr "  if (r == %s) {\n" error_code;
3039       pr "    PyErr_SetString (PyExc_RuntimeError,\n";
3040       pr "                     strerror (errno));\n";
3041       pr "    return NULL;\n";
3042       pr "  }\n";
3043       pr "\n";
3044
3045       (* Convert return value to Python. *)
3046       (match fst style with
3047        | RErr
3048        | RErrDispose ->
3049            pr "  Py_INCREF (Py_None);\n";
3050            pr "  py_r = Py_None;\n"
3051        | RHive ->
3052            pr "  py_r = put_handle (r);\n"
3053        | RSize
3054        | RNode ->
3055            pr "  py_r = PyLong_FromLongLong (r);\n"
3056        | RNodeNotFound ->
3057            pr "  if (r)\n";
3058            pr "    py_r = PyLong_FromLongLong (r);\n";
3059            pr "  else {\n";
3060            pr "    Py_INCREF (Py_None);\n";
3061            pr "    py_r = Py_None;\n";
3062            pr "  }\n";
3063        | RNodeList
3064        | RValueList ->
3065            pr "  py_r = put_node_list (r);\n";
3066            pr "  free (r);\n"
3067        | RValue ->
3068            pr "  py_r = PyLong_FromLongLong (r);\n"
3069        | RString ->
3070            pr "  py_r = PyString_FromString (r);\n";
3071            pr "  free (r);"
3072        | RStringList ->
3073            pr "  py_r = put_string_list (r);\n";
3074            pr "  free_strings (r);\n"
3075        | RLenType ->
3076            pr "  py_r = put_len_type (len, t);\n"
3077        | RLenTypeVal ->
3078            pr "  py_r = put_val_type (r, len, t);\n";
3079            pr "  free (r);\n"
3080        | RInt32 ->
3081            pr "  py_r = PyInt_FromLong ((long) r);\n"
3082        | RInt64 ->
3083            pr "  py_r = PyLong_FromLongLong (r);\n"
3084       );
3085       pr "  return py_r;\n";
3086       pr "}\n";
3087       pr "\n"
3088   ) functions;
3089
3090   (* Table of functions. *)
3091   pr "static PyMethodDef methods[] = {\n";
3092   List.iter (
3093     fun (name, _, _, _) ->
3094       pr "  { (char *) \"%s\", py_hivex_%s, METH_VARARGS, NULL },\n"
3095         name name
3096   ) functions;
3097   pr "  { NULL, NULL, 0, NULL }\n";
3098   pr "};\n";
3099   pr "\n";
3100
3101   (* Init function. *)
3102   pr "\
3103 void
3104 initlibhivexmod (void)
3105 {
3106   static int initialized = 0;
3107
3108   if (initialized) return;
3109   Py_InitModule ((char *) \"libhivexmod\", methods);
3110   initialized = 1;
3111 }
3112 "
3113
3114 and generate_python_py () =
3115   generate_header HashStyle LGPLv2plus;
3116
3117   pr "\
3118 u\"\"\"Python bindings for hivex
3119
3120 import hivex
3121 h = hivex.Hivex (filename)
3122
3123 The hivex module provides Python bindings to the hivex API for
3124 examining and modifying Windows Registry 'hive' files.
3125
3126 Read the hivex(3) man page to find out how to use the API.
3127 \"\"\"
3128
3129 import libhivexmod
3130
3131 class Hivex:
3132     \"\"\"Instances of this class are hivex API handles.\"\"\"
3133
3134     def __init__ (self, filename";
3135
3136   List.iter (
3137     fun (_, flag, _) -> pr ", %s = False" (String.lowercase flag)
3138   ) open_flags;
3139
3140   pr "):
3141         \"\"\"Create a new hivex handle.\"\"\"
3142         flags = 0
3143 ";
3144
3145   List.iter (
3146     fun (n, flag, description) ->
3147       pr "        # %s\n" description;
3148       pr "        if %s: flags += %d\n" (String.lowercase flag) n
3149   ) open_flags;
3150
3151   pr "        self._o = libhivexmod.open (filename, flags)
3152
3153     def __del__ (self):
3154         libhivexmod.close (self._o)
3155
3156 ";
3157
3158   List.iter (
3159     fun (name, style, shortdesc, _) ->
3160       (* The close and open calls are handled specially above. *)
3161       if fst style <> RErrDispose && List.hd (snd style) = AHive then (
3162         let args = List.tl (snd style) in
3163         let args = List.filter (
3164           function AOpenFlags | AUnusedFlags -> false
3165           | _ -> true
3166         ) args in
3167
3168         pr "    def %s (self" name;
3169         List.iter (fun arg -> pr ", %s" (name_of_argt arg)) args;
3170         pr "):\n";
3171         pr "        u\"\"\"%s\"\"\"\n" shortdesc;
3172         pr "        return libhivexmod.%s (self._o" name;
3173         List.iter (
3174           fun arg ->
3175             pr ", ";
3176             match arg with
3177             | AHive -> assert false
3178             | ANode n | AValue n
3179             | AString n | AStringNullable n -> pr "%s" n
3180             | AOpenFlags
3181             | AUnusedFlags -> assert false
3182             | ASetValues -> pr "values"
3183             | ASetValue -> pr "val"
3184         ) args;
3185         pr ")\n";
3186         pr "\n"
3187       )
3188   ) functions
3189
3190 and generate_ruby_c () =
3191   generate_header CStyle LGPLv2plus;
3192
3193   pr "\
3194 #include <stdio.h>
3195 #include <stdlib.h>
3196 #include <stdint.h>
3197
3198 #include <ruby.h>
3199
3200 #include \"hivex.h\"
3201
3202 #include \"extconf.h\"
3203
3204 /* For Ruby < 1.9 */
3205 #ifndef RARRAY_LEN
3206 #define RARRAY_LEN(r) (RARRAY((r))->len)
3207 #endif
3208
3209 static VALUE m_hivex;                   /* hivex module */
3210 static VALUE c_hivex;                   /* hive_h handle */
3211 static VALUE e_Error;                   /* used for all errors */
3212
3213 static void
3214 ruby_hivex_free (void *hvp)
3215 {
3216   hive_h *h = hvp;
3217
3218   if (h)
3219     hivex_close (h);
3220 }
3221
3222 static void
3223 get_value (VALUE valv, hive_set_value *val)
3224 {
3225   VALUE key = rb_hash_lookup (valv, ID2SYM (rb_intern (\"key\")));
3226   VALUE type = rb_hash_lookup (valv, ID2SYM (rb_intern (\"type\")));
3227   VALUE value = rb_hash_lookup (valv, ID2SYM (rb_intern (\"value\")));
3228
3229   val->key = StringValueCStr (key);
3230   val->t = NUM2ULL (type);
3231   val->len = RSTRING (value)->len;
3232   val->value = RSTRING (value)->ptr;
3233 }
3234
3235 static hive_set_value *
3236 get_values (VALUE valuesv, size_t *nr_values)
3237 {
3238   size_t i;
3239   hive_set_value *ret;
3240
3241   *nr_values = RARRAY_LEN (valuesv);
3242   ret = malloc (sizeof (*ret) * *nr_values);
3243   if (ret == NULL)
3244     abort ();
3245
3246   for (i = 0; i < *nr_values; ++i) {
3247     VALUE v = rb_ary_entry (valuesv, i);
3248     get_value (v, &ret[i]);
3249   }
3250
3251   return ret;
3252 }
3253
3254 ";
3255
3256   List.iter (
3257     fun (name, (ret, args), shortdesc, longdesc) ->
3258       let () =
3259         (* Generate rdoc. *)
3260         let doc = replace_str longdesc "C<hivex_" "C<h." in
3261         let doc = pod2text ~width:60 name doc in
3262         let doc = String.concat "\n * " doc in
3263         let doc = trim doc in
3264
3265         let call, args =
3266           match args with
3267           | AHive :: args -> "h." ^ name, args
3268           | args -> "Hivex::" ^ name, args in
3269         let args = filter_map (
3270           function
3271           | AUnusedFlags -> None
3272           | args -> Some (name_of_argt args)
3273         ) args in
3274         let args = String.concat ", " args in
3275
3276         let ret =
3277           match ret with
3278           | RErr | RErrDispose -> "nil"
3279           | RHive -> "Hivex::Hivex"
3280           | RSize | RNode | RNodeNotFound -> "integer"
3281           | RNodeList -> "list"
3282           | RValue -> "integer"
3283           | RValueList -> "list"
3284           | RString -> "string"
3285           | RStringList -> "list"
3286           | RLenType -> "hash"
3287           | RLenTypeVal -> "hash"
3288           | RInt32 -> "integer"
3289           | RInt64 -> "integer" in
3290
3291         pr "\
3292 /*
3293  * call-seq:
3294  *   %s(%s) -> %s
3295  *
3296  * %s
3297  *
3298  * %s
3299  *
3300  * (For the C API documentation for this function, see
3301  * +hivex_%s+[http://libguestfs.org/hivex.3.html#hivex_%s]).
3302  */
3303 " call args ret shortdesc doc name name in
3304
3305       (* Generate the function. *)
3306       pr "static VALUE\n";
3307       pr "ruby_hivex_%s (" name;
3308
3309       let () =
3310         (* If the first argument is not AHive, then this is a module-level
3311          * function, and Ruby passes an implicit module argument which we
3312          * must ignore.  Otherwise the first argument is the hive handle.
3313          *)
3314         let args =
3315           match args with
3316           | AHive :: args -> pr "VALUE hv"; args
3317           | args -> pr "VALUE modulev"; args in
3318         List.iter (
3319           function
3320           | AUnusedFlags -> ()
3321           | arg ->
3322             pr ", VALUE %sv" (name_of_argt arg)
3323         ) args;
3324         pr ")\n" in
3325
3326       pr "{\n";
3327
3328       List.iter (
3329         function
3330         | AHive ->
3331           pr "  hive_h *h;\n";
3332           pr "  Data_Get_Struct (hv, hive_h, h);\n";
3333           pr "  if (!h)\n";
3334           pr "    rb_raise (rb_eArgError, \"%%s: used handle after closing it\",\n";
3335           pr "              \"%s\");\n" name;
3336         | ANode n ->
3337           pr "  hive_node_h %s = NUM2ULL (%sv);\n" n n
3338         | AValue n ->
3339           pr "  hive_value_h %s = NUM2ULL (%sv);\n" n n
3340         | AString n ->
3341           pr "  const char *%s = StringValueCStr (%sv);\n" n n;
3342         | AStringNullable n ->
3343           pr "  const char *%s =\n" n;
3344           pr "    !NIL_P (%sv) ? StringValueCStr (%sv) : NULL;\n" n n
3345         | AOpenFlags ->
3346           pr "  int flags = 0;\n";
3347           List.iter (
3348             fun (n, flag, _) ->
3349               pr "  if (RTEST (rb_hash_lookup (flagsv, ID2SYM (rb_intern (\"%s\")))))\n"
3350                 (String.lowercase flag);
3351               pr "    flags += %d;\n" n
3352           ) open_flags
3353         | AUnusedFlags -> ()
3354         | ASetValues ->
3355           pr "  size_t nr_values;\n";
3356           pr "  hive_set_value *values;\n";
3357           pr "  values = get_values (valuesv, &nr_values);\n"
3358         | ASetValue ->
3359           pr "  hive_set_value val;\n";
3360           pr "  get_value (valv, &val);\n"
3361       ) args;
3362       pr "\n";
3363
3364       let error_code =
3365         match ret with
3366         | RErr -> pr "  int r;\n"; "-1"
3367         | RErrDispose -> pr "  int r;\n"; "-1"
3368         | RHive -> pr "  hive_h *r;\n"; "NULL"
3369         | RSize -> pr "  size_t r;\n"; "0"
3370         | RNode -> pr "  hive_node_h r;\n"; "0"
3371         | RNodeNotFound ->
3372             pr "  errno = 0;\n";
3373             pr "  hive_node_h r;\n";
3374             "0 && errno != 0"
3375         | RNodeList -> pr "  hive_node_h *r;\n"; "NULL"
3376         | RValue -> pr "  hive_value_h r;\n"; "0"
3377         | RValueList -> pr "  hive_value_h *r;\n"; "NULL"
3378         | RString -> pr "  char *r;\n"; "NULL"
3379         | RStringList -> pr "  char **r;\n"; "NULL"
3380         | RLenType ->
3381             pr "  int r;\n";
3382             pr "  size_t len;\n";
3383             pr "  hive_type t;\n";
3384             "-1"
3385         | RLenTypeVal ->
3386             pr "  char *r;\n";
3387             pr "  size_t len;\n";
3388             pr "  hive_type t;\n";
3389             "NULL"
3390         | RInt32 ->
3391             pr "  errno = 0;\n";
3392             pr "  int32_t r;\n";
3393             "-1 && errno != 0"
3394         | RInt64 ->
3395             pr "  errno = 0;\n";
3396             pr "  int64_t r;\n";
3397             "-1 && errno != 0" in
3398       pr "\n";
3399
3400       let c_params =
3401         List.map (function
3402                   | ASetValues -> ["nr_values"; "values"]
3403                   | ASetValue -> ["&val"]
3404                   | AUnusedFlags -> ["0"]
3405                   | arg -> [name_of_argt arg]) args in
3406       let c_params =
3407         match ret with
3408         | RLenType | RLenTypeVal -> c_params @ [["&t"; "&len"]]
3409         | _ -> c_params in
3410       let c_params = List.concat c_params in
3411
3412       pr "  r = hivex_%s (%s" name (List.hd c_params);
3413       List.iter (pr ", %s") (List.tl c_params);
3414       pr ");\n";
3415       pr "\n";
3416
3417       (* Dispose of the hive handle (even if hivex_close returns error). *)
3418       (match ret with
3419        | RErrDispose ->
3420            pr "  /* So we don't double-free in the finalizer. */\n";
3421            pr "  DATA_PTR (hv) = NULL;\n";
3422            pr "\n";
3423        | _ -> ()
3424       );
3425
3426       List.iter (
3427         function
3428         | AHive
3429         | ANode _
3430         | AValue _
3431         | AString _
3432         | AStringNullable _
3433         | AOpenFlags
3434         | AUnusedFlags -> ()
3435         | ASetValues ->
3436           pr "  free (values);\n"
3437         | ASetValue -> ()
3438       ) args;
3439
3440       (* Check for errors from C library. *)
3441       pr "  if (r == %s)\n" error_code;
3442       pr "    rb_raise (e_Error, \"%%s\", strerror (errno));\n";
3443       pr "\n";
3444
3445       (match ret with
3446       | RErr | RErrDispose ->
3447         pr "  return Qnil;\n"
3448       | RHive ->
3449         pr "  return Data_Wrap_Struct (c_hivex, NULL, ruby_hivex_free, r);\n"
3450       | RSize
3451       | RNode
3452       | RValue
3453       | RInt64 ->
3454         pr "  return ULL2NUM (r);\n"
3455       | RInt32 ->
3456         pr "  return INT2NUM (r);\n"
3457       | RNodeNotFound ->
3458         pr "  if (r)\n";
3459         pr "    return ULL2NUM (r);\n";
3460         pr "  else\n";
3461         pr "    return Qnil;\n"
3462       | RNodeList
3463       | RValueList ->
3464         pr "  size_t i, len = 0;\n";
3465         pr "  for (i = 0; r[i] != 0; ++i) len++;\n";
3466         pr "  VALUE rv = rb_ary_new2 (len);\n";
3467         pr "  for (i = 0; r[i] != 0; ++i)\n";
3468         pr "    rb_ary_push (rv, ULL2NUM (r[i]));\n";
3469         pr "  free (r);\n";
3470         pr "  return rv;\n"
3471       | RString ->
3472         pr "  VALUE rv = rb_str_new2 (r);\n";
3473         pr "  free (r);\n";
3474         pr "  return rv;\n"
3475       | RStringList ->
3476         pr "  size_t i, len = 0;\n";
3477         pr "  for (i = 0; r[i] != NULL; ++i) len++;\n";
3478         pr "  VALUE rv = rb_ary_new2 (len);\n";
3479         pr "  for (i = 0; r[i] != NULL; ++i) {\n";
3480         pr "    rb_ary_push (rv, rb_str_new2 (r[i]));\n";
3481         pr "    free (r[i]);\n";
3482         pr "  }\n";
3483         pr "  free (r);\n";
3484         pr "  return rv;\n"
3485       | RLenType ->
3486         pr "  VALUE rv = rb_hash_new ();\n";
3487         pr "  rb_hash_aset (rv, ID2SYM (rb_intern (\"len\")), INT2NUM (len));\n";
3488         pr "  rb_hash_aset (rv, ID2SYM (rb_intern (\"type\")), INT2NUM (t));\n";
3489         pr "  return rv;\n"
3490       | RLenTypeVal ->
3491         pr "  VALUE rv = rb_hash_new ();\n";
3492         pr "  rb_hash_aset (rv, ID2SYM (rb_intern (\"len\")), INT2NUM (len));\n";
3493         pr "  rb_hash_aset (rv, ID2SYM (rb_intern (\"type\")), INT2NUM (t));\n";
3494         pr "  rb_hash_aset (rv, ID2SYM (rb_intern (\"value\")), rb_str_new (r, len));\n";
3495         pr "  free (r);\n";
3496         pr "  return rv;\n"
3497       );
3498
3499       pr "}\n";
3500       pr "\n"
3501   ) functions;
3502
3503   pr "\
3504 /* Initialize the module. */
3505 void Init__hivex ()
3506 {
3507   m_hivex = rb_define_module (\"Hivex\");
3508   c_hivex = rb_define_class_under (m_hivex, \"Hivex\", rb_cObject);
3509   e_Error = rb_define_class_under (m_hivex, \"Error\", rb_eStandardError);
3510
3511   /* XXX How to pass arguments? */
3512 #if 0
3513 #ifdef HAVE_RB_DEFINE_ALLOC_FUNC
3514   rb_define_alloc_func (c_hivex, ruby_hivex_open);
3515 #endif
3516 #endif
3517
3518 ";
3519
3520   (* Methods. *)
3521   List.iter (
3522     fun (name, (_, args), _, _) ->
3523       let args = List.filter (
3524         function
3525         | AUnusedFlags -> false
3526         | _ -> true
3527       ) args in
3528       let nr_args = List.length args in
3529       match args with
3530       | AHive :: _ ->
3531         pr "  rb_define_method (c_hivex, \"%s\",\n" name;
3532         pr "                    ruby_hivex_%s, %d);\n" name (nr_args-1)
3533       | args -> (* class function *)
3534         pr "  rb_define_module_function (m_hivex, \"%s\",\n" name;
3535         pr "                             ruby_hivex_%s, %d);\n" name nr_args
3536   ) functions;
3537
3538   pr "}\n"
3539
3540 let output_to filename k =
3541   let filename_new = filename ^ ".new" in
3542   chan := open_out filename_new;
3543   k ();
3544   close_out !chan;
3545   chan := Pervasives.stdout;
3546
3547   (* Is the new file different from the current file? *)
3548   if Sys.file_exists filename && files_equal filename filename_new then
3549     unlink filename_new                 (* same, so skip it *)
3550   else (
3551     (* different, overwrite old one *)
3552     (try chmod filename 0o644 with Unix_error _ -> ());
3553     rename filename_new filename;
3554     chmod filename 0o444;
3555     printf "written %s\n%!" filename;
3556   )
3557
3558 let perror msg = function
3559   | Unix_error (err, _, _) ->
3560       eprintf "%s: %s\n" msg (error_message err)
3561   | exn ->
3562       eprintf "%s: %s\n" msg (Printexc.to_string exn)
3563
3564 (* Main program. *)
3565 let () =
3566   let lock_fd =
3567     try openfile "configure.ac" [O_RDWR] 0
3568     with
3569     | Unix_error (ENOENT, _, _) ->
3570         eprintf "\
3571 You are probably running this from the wrong directory.
3572 Run it from the top source directory using the command
3573   generator/generator.ml
3574 ";
3575         exit 1
3576     | exn ->
3577         perror "open: configure.ac" exn;
3578         exit 1 in
3579
3580   (* Acquire a lock so parallel builds won't try to run the generator
3581    * twice at the same time.  Subsequent builds will wait for the first
3582    * one to finish.  Note the lock is released implicitly when the
3583    * program exits.
3584    *)
3585   (try lockf lock_fd F_LOCK 1
3586    with exn ->
3587      perror "lock: configure.ac" exn;
3588      exit 1);
3589
3590   check_functions ();
3591
3592   output_to "lib/hivex.h" generate_c_header;
3593   output_to "lib/hivex.pod" generate_c_pod;
3594
3595   output_to "lib/hivex.syms" generate_linker_script;
3596
3597   output_to "ocaml/hivex.mli" generate_ocaml_interface;
3598   output_to "ocaml/hivex.ml" generate_ocaml_implementation;
3599   output_to "ocaml/hivex_c.c" generate_ocaml_c;
3600
3601   output_to "perl/lib/Win/Hivex.pm" generate_perl_pm;
3602   output_to "perl/Hivex.xs" generate_perl_xs;
3603
3604   output_to "python/hivex.py" generate_python_py;
3605   output_to "python/hivex-py.c" generate_python_c;
3606
3607   output_to "ruby/ext/hivex/_hivex.c" generate_ruby_c;
3608
3609   (* Always generate this file last, and unconditionally.  It's used
3610    * by the Makefile to know when we must re-run the generator.
3611    *)
3612   let chan = open_out "generator/stamp-generator" in
3613   fprintf chan "1\n";
3614   close_out chan;
3615
3616   printf "generated %d lines of code\n" !lines