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