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