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