fe12c0b8f808b4af5765ad3076ed17e8a92508df
[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 #directory "+xml-light";;
40 #load "xml-light.cma";;
41
42 open Unix
43 open Printf
44
45 type style = ret * args
46 and ret =
47   | RErr                                (* 0 = ok, -1 = error *)
48   | RHive                               (* Returns a hive_h or NULL. *)
49   | RNode                               (* Returns hive_node_h or 0. *)
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
73 (* Hive types, from:
74  * https://secure.wikimedia.org/wikipedia/en/wiki/Windows_Registry#Keys_and_values
75  * 
76  * It's unfortunate that in our original C binding we strayed away from
77  * the names that Windows uses (eg. REG_SZ for strings).  We include
78  * both our names and the Windows names.
79  *)
80 let hive_types = [
81   0, "none", "NONE",
82     "Just a key without a value";
83   1, "string", "SZ",
84     "A Windows string (encoding is unknown, but often UTF16-LE)";
85   2, "expand_string", "EXPAND_SZ",
86     "A Windows string that contains %env% (environment variable expansion)";
87   3, "binary", "BINARY",
88     "A blob of binary";
89   4, "dword", "DWORD",
90     "DWORD (32 bit integer), little endian";
91   5, "dword_be", "DWORD_BIG_ENDIAN",
92     "DWORD (32 bit integer), big endian";
93   6, "link", "LINK",
94     "Symbolic link to another part of the registry tree";
95   7, "multiple_strings", "MULTI_SZ",
96     "Multiple Windows strings.  See http://blogs.msdn.com/oldnewthing/archive/2009/10/08/9904646.aspx";
97   8, "resource_list", "RESOURCE_LIST",
98     "Resource list";
99   9, "full_resource_description", "FULL_RESOURCE_DESCRIPTOR",
100     "Resource descriptor";
101   10, "resource_requirements_list", "RESOURCE_REQUIREMENTS_LIST",
102     "Resouce requirements list";
103   11, "qword", "QWORD",
104     "QWORD (64 bit integer), unspecified endianness but usually little endian"
105 ]
106
107 (* Open flags (bitmask passed to AOpenFlags) *)
108 let open_flags = [
109   1, "VERBOSE", "Verbose messages";
110   2, "DEBUG", "Debug messages";
111   4, "WRITE", "Enable writes to the hive";
112 ]
113
114 (* The API calls. *)
115 let functions = [
116   "open", (RHive, [AString "filename"; AOpenFlags]),
117     "open a hive file",
118     "\
119 Opens the hive named C<filename> for reading.
120
121 Flags is an ORed list of the open flags (or C<0> if you don't
122 want to pass any flags).  These flags are defined:
123
124 =over 4
125
126 =item HIVEX_OPEN_VERBOSE
127
128 Verbose messages.
129
130 =item HIVEX_OPEN_DEBUG
131
132 Very verbose messages, suitable for debugging problems in the library
133 itself.
134
135 This is also selected if the C<HIVEX_DEBUG> environment variable
136 is set to 1.
137
138 =item HIVEX_OPEN_WRITE
139
140 Open the hive for writing.  If omitted, the hive is read-only.
141
142 See L<hivex(3)/WRITING TO HIVE FILES>.
143
144 =back";
145
146   "close", (RErr, [AHive]),
147     "close a hive handle",
148     "\
149 Close a hive handle and free all associated resources.
150
151 Note that any uncommitted writes are I<not> committed by this call,
152 but instead are lost.  See L<hivex(3)/WRITING TO HIVE FILES>.";
153
154   "root", (RNode, [AHive]),
155     "return the root node of the hive",
156     "\
157 Return root node of the hive.  All valid registries must contain
158 a root node.";
159
160   "node_name", (RString, [AHive; ANode "node"]),
161     "return the name of the node",
162     "\
163 Return the name of the node.
164
165 Note that the name of the root node is a dummy, such as
166 C<$$$PROTO.HIV> (other names are possible: it seems to depend on the
167 tool or program that created the hive in the first place).  You can
168 only know the \"real\" name of the root node by knowing which registry
169 file this hive originally comes from, which is knowledge that is
170 outside the scope of this library.";
171
172   "node_children", (RNodeList, [AHive; ANode "node"]),
173     "return children of node",
174     "\
175 Return an array of nodes which are the subkeys
176 (children) of C<node>.";
177
178   "node_get_child", (RNode, [AHive; ANode "node"; AString "name"]),
179     "return named child of node",
180     "\
181 Return the child of node with the name C<name>, if it exists.
182
183 The name is matched case insensitively.
184
185 If the child node does not exist, this returns 0 without
186 setting errno.";
187
188   "node_parent", (RNode, [AHive; ANode "node"]),
189     "return the parent of node",
190     "\
191 Return the parent of C<node>.
192
193 The parent pointer of the root node in registry files that we
194 have examined seems to be invalid, and so this function will
195 return an error if called on the root node.";
196
197   "node_values", (RValueList, [AHive; ANode "node"]),
198     "return (key, value) pairs attached to a node",
199     "\
200 Return the array of (key, value) pairs attached to this node.";
201
202   "node_get_value", (RValue, [AHive; ANode "node"; AString "key"]),
203     "return named key at node",
204     "\
205 Return the value attached to this node which has the name C<key>,
206 if it exists.
207
208 The key name is matched case insensitively.
209
210 Note that to get the default key, you should pass the empty
211 string C<\"\"> here.  The default key is often written C<\"@\">, but
212 inside hives that has no meaning and won't give you the
213 default key.";
214
215   "value_key", (RString, [AHive; AValue "val"]),
216     "return the key of a (key, value) pair",
217     "\
218 Return the key (name) of a (key, value) pair.  The name
219 is reencoded as UTF-8 and returned as a string.
220
221 The string should be freed by the caller when it is no longer needed.
222
223 Note that this function can return a zero-length string.  In the
224 context of Windows Registries, this means that this value is the
225 default key for this node in the tree.  This is usually written
226 as C<\"@\">.";
227
228   "value_type", (RLenType, [AHive; AValue "val"]),
229     "return data length and data type of a value",
230     "\
231 Return the data length and data type of the value in this (key, value)
232 pair.  See also C<hivex_value_value> which returns all this
233 information, and the value itself.  Also, C<hivex_value_*> functions
234 below which can be used to return the value in a more useful form when
235 you know the type in advance.";
236
237   "value_value", (RLenTypeVal, [AHive; AValue "val"]),
238     "return data length, data type and data of a value",
239     "\
240 Return the value of this (key, value) pair.  The value should
241 be interpreted according to its type (see C<hive_type>).";
242
243   "value_string", (RString, [AHive; AValue "val"]),
244     "return value as a string",
245     "\
246 If this value is a string, return the string reencoded as UTF-8
247 (as a C string).  This only works for values which have type
248 C<hive_t_string>, C<hive_t_expand_string> or C<hive_t_link>.";
249
250   "value_multiple_strings", (RStringList, [AHive; AValue "val"]),
251     "return value as multiple strings",
252     "\
253 If this value is a multiple-string, return the strings reencoded
254 as UTF-8 (as a NULL-terminated array of C 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 then we
275 overwrite the original file (ie. the file name that was passed to
276 C<hivex_open>).  C<flags> is not used, always pass 0.
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, call
281 C<hivex_close> after this.";
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 stored in C<node>.
306
307 C<node> is the node to modify.  C<values> is an array of (key, value)
308 pairs.  There should be C<nr_values> elements in this array.  C<flags>
309 is not used, always pass 0.
310
311 Any existing values stored at the node are discarded, and their
312 C<hive_value_h> handles become invalid.  Thus you can remove all
313 values stored at C<node> by passing C<nr_values = 0>.
314
315 Note that this library does not offer a way to modify just a single
316 key at a node.  We don't implement a way to do this efficiently.";
317 ]
318
319 (* Used to memoize the result of pod2text. *)
320 let pod2text_memo_filename = "generator/.pod2text.data"
321 let pod2text_memo : ((int * string * string), string list) Hashtbl.t =
322   try
323     let chan = open_in pod2text_memo_filename in
324     let v = input_value chan in
325     close_in chan;
326     v
327   with
328     _ -> Hashtbl.create 13
329 let pod2text_memo_updated () =
330   let chan = open_out pod2text_memo_filename in
331   output_value chan pod2text_memo;
332   close_out chan
333
334 (* Useful functions.
335  * Note we don't want to use any external OCaml libraries which
336  * makes this a bit harder than it should be.
337  *)
338 module StringMap = Map.Make (String)
339
340 let failwithf fs = ksprintf failwith fs
341
342 let unique = let i = ref 0 in fun () -> incr i; !i
343
344 let replace_char s c1 c2 =
345   let s2 = String.copy s in
346   let r = ref false in
347   for i = 0 to String.length s2 - 1 do
348     if String.unsafe_get s2 i = c1 then (
349       String.unsafe_set s2 i c2;
350       r := true
351     )
352   done;
353   if not !r then s else s2
354
355 let isspace c =
356   c = ' '
357   (* || c = '\f' *) || c = '\n' || c = '\r' || c = '\t' (* || c = '\v' *)
358
359 let triml ?(test = isspace) str =
360   let i = ref 0 in
361   let n = ref (String.length str) in
362   while !n > 0 && test str.[!i]; do
363     decr n;
364     incr i
365   done;
366   if !i = 0 then str
367   else String.sub str !i !n
368
369 let trimr ?(test = isspace) str =
370   let n = ref (String.length str) in
371   while !n > 0 && test str.[!n-1]; do
372     decr n
373   done;
374   if !n = String.length str then str
375   else String.sub str 0 !n
376
377 let trim ?(test = isspace) str =
378   trimr ~test (triml ~test str)
379
380 let rec find s sub =
381   let len = String.length s in
382   let sublen = String.length sub in
383   let rec loop i =
384     if i <= len-sublen then (
385       let rec loop2 j =
386         if j < sublen then (
387           if s.[i+j] = sub.[j] then loop2 (j+1)
388           else -1
389         ) else
390           i (* found *)
391       in
392       let r = loop2 0 in
393       if r = -1 then loop (i+1) else r
394     ) else
395       -1 (* not found *)
396   in
397   loop 0
398
399 let rec replace_str s s1 s2 =
400   let len = String.length s in
401   let sublen = String.length s1 in
402   let i = find s s1 in
403   if i = -1 then s
404   else (
405     let s' = String.sub s 0 i in
406     let s'' = String.sub s (i+sublen) (len-i-sublen) in
407     s' ^ s2 ^ replace_str s'' s1 s2
408   )
409
410 let rec string_split sep str =
411   let len = String.length str in
412   let seplen = String.length sep in
413   let i = find str sep in
414   if i = -1 then [str]
415   else (
416     let s' = String.sub str 0 i in
417     let s'' = String.sub str (i+seplen) (len-i-seplen) in
418     s' :: string_split sep s''
419   )
420
421 let files_equal n1 n2 =
422   let cmd = sprintf "cmp -s %s %s" (Filename.quote n1) (Filename.quote n2) in
423   match Sys.command cmd with
424   | 0 -> true
425   | 1 -> false
426   | i -> failwithf "%s: failed with error code %d" cmd i
427
428 let rec filter_map f = function
429   | [] -> []
430   | x :: xs ->
431       match f x with
432       | Some y -> y :: filter_map f xs
433       | None -> filter_map f xs
434
435 let rec find_map f = function
436   | [] -> raise Not_found
437   | x :: xs ->
438       match f x with
439       | Some y -> y
440       | None -> find_map f xs
441
442 let iteri f xs =
443   let rec loop i = function
444     | [] -> ()
445     | x :: xs -> f i x; loop (i+1) xs
446   in
447   loop 0 xs
448
449 let mapi f xs =
450   let rec loop i = function
451     | [] -> []
452     | x :: xs -> let r = f i x in r :: loop (i+1) xs
453   in
454   loop 0 xs
455
456 let count_chars c str =
457   let count = ref 0 in
458   for i = 0 to String.length str - 1 do
459     if c = String.unsafe_get str i then incr count
460   done;
461   !count
462
463 let name_of_argt = function
464   | AHive -> "h"
465   | ANode n | AValue n | AString n | AStringNullable n -> n
466   | AOpenFlags | AUnusedFlags -> "flags"
467   | ASetValues -> "values"
468
469 (* Check function names etc. for consistency. *)
470 let check_functions () =
471   let contains_uppercase str =
472     let len = String.length str in
473     let rec loop i =
474       if i >= len then false
475       else (
476         let c = str.[i] in
477         if c >= 'A' && c <= 'Z' then true
478         else loop (i+1)
479       )
480     in
481     loop 0
482   in
483
484   (* Check function names. *)
485   List.iter (
486     fun (name, _, _, _) ->
487       if String.length name >= 7 && String.sub name 0 7 = "hivex" then
488         failwithf "function name %s does not need 'hivex' prefix" name;
489       if name = "" then
490         failwithf "function name is empty";
491       if name.[0] < 'a' || name.[0] > 'z' then
492         failwithf "function name %s must start with lowercase a-z" name;
493       if String.contains name '-' then
494         failwithf "function name %s should not contain '-', use '_' instead."
495           name
496   ) functions;
497
498   (* Check function parameter/return names. *)
499   List.iter (
500     fun (name, style, _, _) ->
501       let check_arg_ret_name n =
502         if contains_uppercase n then
503           failwithf "%s param/ret %s should not contain uppercase chars"
504             name n;
505         if String.contains n '-' || String.contains n '_' then
506           failwithf "%s param/ret %s should not contain '-' or '_'"
507             name n;
508         if n = "value" then
509           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;
510         if n = "int" || n = "char" || n = "short" || n = "long" then
511           failwithf "%s has a param/ret which conflicts with a C type (eg. 'int', 'char' etc.)" name;
512         if n = "i" || n = "n" then
513           failwithf "%s has a param/ret called 'i' or 'n', which will cause some conflicts in the generated code" name;
514         if n = "argv" || n = "args" then
515           failwithf "%s has a param/ret called 'argv' or 'args', which will cause some conflicts in the generated code" name;
516
517         (* List Haskell, OCaml and C keywords here.
518          * http://www.haskell.org/haskellwiki/Keywords
519          * http://caml.inria.fr/pub/docs/manual-ocaml/lex.html#operator-char
520          * http://en.wikipedia.org/wiki/C_syntax#Reserved_keywords
521          * Formatted via: cat c haskell ocaml|sort -u|grep -vE '_|^val$' \
522          *   |perl -pe 's/(.+)/"$1";/'|fmt -70
523          * Omitting _-containing words, since they're handled above.
524          * Omitting the OCaml reserved word, "val", is ok,
525          * and saves us from renaming several parameters.
526          *)
527         let reserved = [
528           "and"; "as"; "asr"; "assert"; "auto"; "begin"; "break"; "case";
529           "char"; "class"; "const"; "constraint"; "continue"; "data";
530           "default"; "deriving"; "do"; "done"; "double"; "downto"; "else";
531           "end"; "enum"; "exception"; "extern"; "external"; "false"; "float";
532           "for"; "forall"; "foreign"; "fun"; "function"; "functor"; "goto";
533           "hiding"; "if"; "import"; "in"; "include"; "infix"; "infixl";
534           "infixr"; "inherit"; "initializer"; "inline"; "instance"; "int";
535           "interface";
536           "land"; "lazy"; "let"; "long"; "lor"; "lsl"; "lsr"; "lxor";
537           "match"; "mdo"; "method"; "mod"; "module"; "mutable"; "new";
538           "newtype"; "object"; "of"; "open"; "or"; "private"; "qualified";
539           "rec"; "register"; "restrict"; "return"; "short"; "sig"; "signed";
540           "sizeof"; "static"; "struct"; "switch"; "then"; "to"; "true"; "try";
541           "type"; "typedef"; "union"; "unsigned"; "virtual"; "void";
542           "volatile"; "when"; "where"; "while";
543           ] in
544         if List.mem n reserved then
545           failwithf "%s has param/ret using reserved word %s" name n;
546       in
547
548       List.iter (fun arg -> check_arg_ret_name (name_of_argt arg)) (snd style)
549   ) functions;
550
551   (* Check short descriptions. *)
552   List.iter (
553     fun (name, _, shortdesc, _) ->
554       if shortdesc.[0] <> Char.lowercase shortdesc.[0] then
555         failwithf "short description of %s should begin with lowercase." name;
556       let c = shortdesc.[String.length shortdesc-1] in
557       if c = '\n' || c = '.' then
558         failwithf "short description of %s should not end with . or \\n." name
559   ) functions;
560
561   (* Check long dscriptions. *)
562   List.iter (
563     fun (name, _, _, longdesc) ->
564       if longdesc.[String.length longdesc-1] = '\n' then
565         failwithf "long description of %s should not end with \\n." name
566   ) functions
567
568 (* 'pr' prints to the current output file. *)
569 let chan = ref Pervasives.stdout
570 let lines = ref 0
571 let pr fs =
572   ksprintf
573     (fun str ->
574        let i = count_chars '\n' str in
575        lines := !lines + i;
576        output_string !chan str
577     ) fs
578
579 let copyright_years =
580   let this_year = 1900 + (localtime (time ())).tm_year in
581   if this_year > 2009 then sprintf "2009-%04d" this_year else "2009"
582
583 (* Generate a header block in a number of standard styles. *)
584 type comment_style =
585   | CStyle | CPlusPlusStyle | HashStyle | OCamlStyle | HaskellStyle
586   | PODCommentStyle
587 type license = GPLv2plus | LGPLv2plus | GPLv2 | LGPLv2
588
589 let generate_header ?(extra_inputs = []) comment license =
590   let inputs = "generator/generator.ml" :: extra_inputs in
591   let c = match comment with
592     | CStyle ->         pr "/* "; " *"
593     | CPlusPlusStyle -> pr "// "; "//"
594     | HashStyle ->      pr "# ";  "#"
595     | OCamlStyle ->     pr "(* "; " *"
596     | HaskellStyle ->   pr "{- "; "  "
597     | PODCommentStyle -> pr "=begin comment\n\n "; "" in
598   pr "hivex generated file\n";
599   pr "%s WARNING: THIS FILE IS GENERATED FROM:\n" c;
600   List.iter (pr "%s   %s\n" c) inputs;
601   pr "%s ANY CHANGES YOU MAKE TO THIS FILE WILL BE LOST.\n" c;
602   pr "%s\n" c;
603   pr "%s Copyright (C) %s Red Hat Inc.\n" c copyright_years;
604   pr "%s Derived from code by Petter Nordahl-Hagen under a compatible license:\n" c;
605   pr "%s   Copyright (c) 1997-2007 Petter Nordahl-Hagen.\n" c;
606   pr "%s Derived from code by Markus Stephany under a compatible license:\n" c;
607   pr "%s   Copyright (c)2000-2004, Markus Stephany.\n" c;
608   pr "%s\n" c;
609   (match license with
610    | GPLv2plus ->
611        pr "%s This program is free software; you can redistribute it and/or modify\n" c;
612        pr "%s it under the terms of the GNU General Public License as published by\n" c;
613        pr "%s the Free Software Foundation; either version 2 of the License, or\n" c;
614        pr "%s (at your option) any later version.\n" c;
615        pr "%s\n" c;
616        pr "%s This program is distributed in the hope that it will be useful,\n" c;
617        pr "%s but WITHOUT ANY WARRANTY; without even the implied warranty of\n" c;
618        pr "%s MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the\n" c;
619        pr "%s GNU General Public License for more details.\n" c;
620        pr "%s\n" c;
621        pr "%s You should have received a copy of the GNU General Public License along\n" c;
622        pr "%s with this program; if not, write to the Free Software Foundation, Inc.,\n" c;
623        pr "%s 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.\n" c;
624
625    | LGPLv2plus ->
626        pr "%s This library is free software; you can redistribute it and/or\n" c;
627        pr "%s modify it under the terms of the GNU Lesser General Public\n" c;
628        pr "%s License as published by the Free Software Foundation; either\n" c;
629        pr "%s version 2 of the License, or (at your option) any later version.\n" c;
630        pr "%s\n" c;
631        pr "%s This library is distributed in the hope that it will be useful,\n" c;
632        pr "%s but WITHOUT ANY WARRANTY; without even the implied warranty of\n" c;
633        pr "%s MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU\n" c;
634        pr "%s Lesser General Public License for more details.\n" c;
635        pr "%s\n" c;
636        pr "%s You should have received a copy of the GNU Lesser General Public\n" c;
637        pr "%s License along with this library; if not, write to the Free Software\n" c;
638        pr "%s Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA\n" c;
639
640    | GPLv2 ->
641        pr "%s This program is free software; you can redistribute it and/or modify\n" c;
642        pr "%s it under the terms of the GNU General Public License as published by\n" c;
643        pr "%s the Free Software Foundation; version 2 of the License only.\n" c;
644        pr "%s\n" c;
645        pr "%s This program is distributed in the hope that it will be useful,\n" c;
646        pr "%s but WITHOUT ANY WARRANTY; without even the implied warranty of\n" c;
647        pr "%s MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the\n" c;
648        pr "%s GNU General Public License for more details.\n" c;
649        pr "%s\n" c;
650        pr "%s You should have received a copy of the GNU General Public License along\n" c;
651        pr "%s with this program; if not, write to the Free Software Foundation, Inc.,\n" c;
652        pr "%s 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.\n" c;
653
654    | LGPLv2 ->
655        pr "%s This library is free software; you can redistribute it and/or\n" c;
656        pr "%s modify it under the terms of the GNU Lesser General Public\n" c;
657        pr "%s License as published by the Free Software Foundation; either\n" c;
658        pr "%s version 2.1 of the License only.\n" c;
659        pr "%s\n" c;
660        pr "%s This library is distributed in the hope that it will be useful,\n" c;
661        pr "%s but WITHOUT ANY WARRANTY; without even the implied warranty of\n" c;
662        pr "%s MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU\n" c;
663        pr "%s Lesser General Public License for more details.\n" c;
664        pr "%s\n" c;
665        pr "%s You should have received a copy of the GNU Lesser General Public\n" c;
666        pr "%s License along with this library; if not, write to the Free Software\n" c;
667        pr "%s Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA\n" c;
668   );
669   (match comment with
670    | CStyle -> pr " */\n"
671    | CPlusPlusStyle
672    | HashStyle -> ()
673    | OCamlStyle -> pr " *)\n"
674    | HaskellStyle -> pr "-}\n"
675    | PODCommentStyle -> pr "\n=end comment\n"
676   );
677   pr "\n"
678
679 (* Start of main code generation functions below this line. *)
680
681 let rec generate_c_header () =
682   generate_header CStyle LGPLv2;
683
684   pr "\
685 #ifndef HIVEX_H_
686 #define HIVEX_H_
687
688 #include <stdint.h>
689
690 #ifdef __cplusplus
691 extern \"C\" {
692 #endif
693
694 /* NOTE: This API is documented in the man page hivex(3). */
695
696 /* Hive handle. */
697 typedef struct hive_h hive_h;
698
699 /* Nodes and values. */
700 typedef size_t hive_node_h;
701 typedef size_t hive_value_h;
702
703 /* Pre-defined types. */
704 enum hive_type {
705 ";
706   List.iter (
707     fun (t, old_style, new_style, description) ->
708       pr "  /* %s */\n" description;
709       pr "  hive_t_REG_%s,\n" new_style;
710       pr "#define hive_t_%s hive_t_REG_%s\n" old_style new_style;
711       pr "\n"
712   ) hive_types;
713   pr "\
714 };
715
716 typedef enum hive_type hive_type;
717
718 /* Bitmask of flags passed to hivex_open. */
719 ";
720   List.iter (
721     fun (v, flag, description) ->
722       pr "  /* %s */\n" description;
723       pr "#define HIVEX_OPEN_%-10s %d\n" flag v;
724   ) open_flags;
725   pr "\n";
726
727   pr "\
728 /* Array of (key, value) pairs passed to hivex_node_set_values. */
729 struct hive_set_value {
730   char *key;
731   hive_type t;
732   size_t len;
733   char *value;
734 };
735 typedef struct hive_set_value hive_set_value;
736 ";
737
738   (* Function declarations. *)
739   List.iter (
740     fun (shortname, style, _, _) ->
741       let name = "hivex_" ^ shortname in
742       generate_c_prototype ~extern:true name style
743   ) functions;
744
745   (* The visitor pattern. *)
746   pr "
747 /* Visit all nodes.  This is specific to the C API and is not made
748  * available to other languages.  This is because of the complexity
749  * of binding callbacks in other languages, but also because other
750  * languages make it much simpler to iterate over a tree.
751  */
752 struct hivex_visitor {
753   int (*node_start) (hive_h *, void *opaque, hive_node_h, const char *name);
754   int (*node_end) (hive_h *, void *opaque, hive_node_h, const char *name);
755   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);
756   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);
757   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);
758   int (*value_dword) (hive_h *, void *opaque, hive_node_h, hive_value_h, hive_type t, size_t len, const char *key, int32_t);
759   int (*value_qword) (hive_h *, void *opaque, hive_node_h, hive_value_h, hive_type t, size_t len, const char *key, int64_t);
760   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);
761   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);
762   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);
763   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);
764 };
765
766 #define HIVEX_VISIT_SKIP_BAD 1
767
768 extern int hivex_visit (hive_h *h, const struct hivex_visitor *visitor, size_t len, void *opaque, int flags);
769 extern int hivex_visit_node (hive_h *h, hive_node_h node, const struct hivex_visitor *visitor, size_t len, void *opaque, int flags);
770
771 ";
772
773   (* Finish the header file. *)
774   pr "\
775 #ifdef __cplusplus
776 }
777 #endif
778
779 #endif /* HIVEX_H_ */
780 "
781
782 and generate_c_prototype ?(extern = false) name style =
783   if extern then pr "extern ";
784   (match fst style with
785    | RErr -> pr "int "
786    | RHive -> pr "hive_h *"
787    | RNode -> pr "hive_node_h "
788    | RNodeList -> pr "hive_node_h *"
789    | RValue -> pr "hive_value_h "
790    | RValueList -> pr "hive_value_h *"
791    | RString -> pr "char *"
792    | RStringList -> pr "char **"
793    | RLenType -> pr "int "
794    | RLenTypeVal -> pr "char *"
795    | RInt32 -> pr "int32_t "
796    | RInt64 -> pr "int64_t "
797   );
798   pr "%s (" name;
799   let comma = ref false in
800   List.iter (
801     fun arg ->
802       if !comma then pr ", "; comma := true;
803       match arg with
804       | AHive -> pr "hive_h *h"
805       | ANode n -> pr "hive_node_h %s" n
806       | AValue n -> pr "hive_value_h %s" n
807       | AString n | AStringNullable n -> pr "const char *%s" n
808       | AOpenFlags | AUnusedFlags -> pr "int flags"
809       | ASetValues -> pr "size_t nr_values, const hive_set_value *values"
810   ) (snd style);
811   (match fst style with
812    | RLenType | RLenTypeVal -> pr ", hive_type *t, size_t *len"
813    | _ -> ()
814   );
815   pr ");\n"
816
817 and generate_c_pod () =
818   generate_header PODCommentStyle GPLv2;
819
820   pr "\
821   =encoding utf8
822
823 =head1 NAME
824
825 hivex - Windows Registry \"hive\" extraction library
826
827 =head1 SYNOPSIS
828
829  #include <hivex.h>
830  
831 ";
832   List.iter (
833     fun (shortname, style, _, _) ->
834       let name = "hivex_" ^ shortname in
835       pr " ";
836       generate_c_prototype ~extern:false name style;
837   ) functions;
838
839   pr "\
840
841 Link with I<-lhivex>.
842
843 =head1 DESCRIPTION
844
845 libhivex is a library for extracting the contents of Windows Registry
846 \"hive\" files.  It is designed to be secure against buggy or malicious
847 registry files.
848
849 Unlike many other tools in this area, it doesn't use the textual .REG
850 format for output, because parsing that is as much trouble as parsing
851 the original binary format.  Instead it makes the file available
852 through a C API, or there is a separate program to export the hive as
853 XML (see L<hivexml(1)>), or to navigate the file (see L<hivexsh(1)>).
854
855 =head1 TYPES
856
857 =head2 hive_h *
858
859 This handle describes an open hive file.
860
861 =head2 hive_node_h
862
863 This is a node handle, an integer but opaque outside the library.
864 Valid node handles cannot be 0.  The library returns 0 in some
865 situations to indicate an error.
866
867 =head2 hive_type
868
869 The enum below describes the possible types for the value(s)
870 stored at each node.  Note that you should not trust the
871 type field in a Windows Registry, as it very often has no
872 relationship to reality.  Some applications use their own
873 types.  The encoding of strings is not specified.  Some
874 programs store everything (including strings) in binary blobs.
875
876  enum hive_type {
877 ";
878   List.iter (
879     fun (t, _, new_style, description) ->
880       pr "   /* %s */\n" description;
881       pr "   hive_t_REG_%s = %d,\n" new_style t
882   ) hive_types;
883   pr "\
884  };
885
886 =head2 hive_value_h
887
888 This is a value handle, an integer but opaque outside the library.
889 Valid value handles cannot be 0.  The library returns 0 in some
890 situations to indicate an error.
891
892 =head2 hive_set_value
893
894 The typedef C<hive_set_value> is used in conjunction with the
895 C<hivex_node_set_values> call described below.
896
897  struct hive_set_value {
898    char *key;     /* key - a UTF-8 encoded ASCIIZ string */
899    hive_type t;   /* type of value field */
900    size_t len;    /* length of value field in bytes */
901    char *value;   /* value field */
902  };
903  typedef struct hive_set_value hive_set_value;
904
905 To set the default value for a node, you have to pass C<key = \"\">.
906
907 Note that the C<value> field is just treated as a list of bytes, and
908 is stored directly in the hive.  The caller has to ensure correct
909 encoding and endianness, for example converting dwords to little
910 endian.
911
912 The correct type and encoding for values depends on the node and key
913 in the registry, the version of Windows, and sometimes even changes
914 between versions of Windows for the same key.  We don't document it
915 here.  Often it's not documented at all.
916
917 =head1 FUNCTIONS
918
919 ";
920   List.iter (
921     fun (shortname, style, _, longdesc) ->
922       let name = "hivex_" ^ shortname in
923       pr "=head2 %s\n" name;
924       pr "\n";
925       generate_c_prototype ~extern:false name style;
926       pr "\n";
927       pr "%s\n" longdesc;
928       pr "\n";
929       (match fst style with
930        | RErr ->
931            pr "\
932 Returns 0 on success.
933 On error this returns -1 and sets errno.\n\n"
934        | RHive ->
935            pr "\
936 Returns a new hive handle.
937 On error this returns NULL and sets errno.\n\n"
938        | RNode ->
939            pr "\
940 Returns a node handle.
941 On error this returns 0 and sets errno.\n\n"
942        | RNodeList ->
943            pr "\
944 Returns a 0-terminated array of nodes.
945 The array must be freed by the caller when it is no longer needed.
946 On error this returns NULL and sets errno.\n\n"
947        | RValue ->
948            pr "\
949 Returns a value handle.
950 On error this returns 0 and sets errno.\n\n"
951        | RValueList ->
952            pr "\
953 Returns a 0-terminated array of values.
954 The array must be freed by the caller when it is no longer needed.
955 On error this returns NULL and sets errno.\n\n"
956        | RString ->
957            pr "\
958 Returns a string.
959 The string must be freed by the caller when it is no longer needed.
960 On error this returns NULL and sets errno.\n\n"
961        | RStringList ->
962            pr "\
963 Returns a NULL-terminated array of C strings.
964 The strings and the array must all be freed by the caller when
965 they are no longer needed.
966 On error this returns NULL and sets errno.\n\n"
967        | RLenType ->
968            pr "\
969 Returns 0 on success.
970 On error this returns NULL and sets errno.\n\n"
971        | RLenTypeVal ->
972            pr "\
973 The value is returned as an array of bytes (of length C<len>).
974 The value must be freed by the caller when it is no longer needed.
975 On error this returns NULL and sets errno.\n\n"
976        | RInt32 | RInt64 -> ()
977       );
978   ) functions;
979
980   pr "\
981 =head1 WRITING TO HIVE FILES
982
983 The hivex library supports making limited modifications to hive files.
984 We have tried to implement this very conservatively in order to reduce
985 the chance of corrupting your registry.  However you should be careful
986 and take back-ups, since Microsoft has never documented the hive
987 format, and so it is possible there are nuances in the
988 reverse-engineered format that we do not understand.
989
990 To be able to modify a hive, you must pass the C<HIVEX_OPEN_WRITE>
991 flag to C<hivex_open>, otherwise any write operation will return with
992 errno C<EROFS>.
993
994 The write operations shown below do not modify the on-disk file
995 immediately.  You must call C<hivex_commit> in order to write the
996 changes to disk.  If you call C<hivex_close> without committing then
997 any writes are discarded.
998
999 Hive files internally consist of a \"memory dump\" of binary blocks
1000 (like the C heap), and some of these blocks can be unused.  The hivex
1001 library never reuses these unused blocks.  Instead, to ensure
1002 robustness in the face of the partially understood on-disk format,
1003 hivex only allocates new blocks after the end of the file, and makes
1004 minimal modifications to existing structures in the file to point to
1005 these new blocks.  This makes hivex slightly less disk-efficient than
1006 it could be, but disk is cheap, and registry modifications tend to be
1007 very small.
1008
1009 When deleting nodes, it is possible that this library may leave
1010 unreachable live blocks in the hive.  This is because certain parts of
1011 the hive disk format such as security (sk) records and big data (db)
1012 records and classname fields are not well understood (and not
1013 documented at all) and we play it safe by not attempting to modify
1014 them.  Apart from wasting a little bit of disk space, it is not
1015 thought that unreachable blocks are a problem.
1016
1017 =head2 WRITE OPERATIONS WHICH ARE NOT SUPPORTED
1018
1019 =over 4
1020
1021 =item *
1022
1023 Changing the root node.
1024
1025 =item *
1026
1027 Creating a new hive file from scratch.  This is impossible at present
1028 because not all fields in the header are understood.
1029
1030 =item *
1031
1032 Modifying or deleting single values at a node.
1033
1034 =item *
1035
1036 Modifying security key (sk) records or classnames.
1037 Previously we did not understand these records.  However now they
1038 are well-understood and we could add support if it was required
1039 (but nothing much really uses them).
1040
1041 =back
1042
1043 =head1 VISITING ALL NODES
1044
1045 The visitor pattern is useful if you want to visit all nodes
1046 in the tree or all nodes below a certain point in the tree.
1047
1048 First you set up your own C<struct hivex_visitor> with your
1049 callback functions.
1050
1051 Each of these callback functions should return 0 on success or -1
1052 on error.  If any callback returns -1, then the entire visit
1053 terminates immediately.  If you don't need a callback function at
1054 all, set the function pointer to NULL.
1055
1056  struct hivex_visitor {
1057    int (*node_start) (hive_h *, void *opaque, hive_node_h, const char *name);
1058    int (*node_end) (hive_h *, void *opaque, hive_node_h, const char *name);
1059    int (*value_string) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1060          hive_type t, size_t len, const char *key, const char *str);
1061    int (*value_multiple_strings) (hive_h *, void *opaque, hive_node_h,
1062          hive_value_h, hive_type t, size_t len, const char *key, char **argv);
1063    int (*value_string_invalid_utf16) (hive_h *, void *opaque, hive_node_h,
1064          hive_value_h, hive_type t, size_t len, const char *key,
1065          const char *str);
1066    int (*value_dword) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1067          hive_type t, size_t len, const char *key, int32_t);
1068    int (*value_qword) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1069          hive_type t, size_t len, const char *key, int64_t);
1070    int (*value_binary) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1071          hive_type t, size_t len, const char *key, const char *value);
1072    int (*value_none) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1073          hive_type t, size_t len, const char *key, const char *value);
1074    int (*value_other) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1075          hive_type t, size_t len, const char *key, const char *value);
1076    /* If value_any callback is not NULL, then the other value_*
1077     * callbacks are not used, and value_any is called on all values.
1078     */
1079    int (*value_any) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1080          hive_type t, size_t len, const char *key, const char *value);
1081  };
1082
1083 =over 4
1084
1085 =item hivex_visit
1086
1087  int hivex_visit (hive_h *h, const struct hivex_visitor *visitor, size_t len, void *opaque, int flags);
1088
1089 Visit all the nodes recursively in the hive C<h>.
1090
1091 C<visitor> should be a C<hivex_visitor> structure with callback
1092 fields filled in as required (unwanted callbacks can be set to
1093 NULL).  C<len> must be the length of the 'visitor' struct (you
1094 should pass C<sizeof (struct hivex_visitor)> for this).
1095
1096 This returns 0 if the whole recursive visit was completed
1097 successfully.  On error this returns -1.  If one of the callback
1098 functions returned an error than we don't touch errno.  If the
1099 error was generated internally then we set errno.
1100
1101 You can skip bad registry entries by setting C<flag> to
1102 C<HIVEX_VISIT_SKIP_BAD>.  If this flag is not set, then a bad registry
1103 causes the function to return an error immediately.
1104
1105 This function is robust if the registry contains cycles or
1106 pointers which are invalid or outside the registry.  It detects
1107 these cases and returns an error.
1108
1109 =item hivex_visit_node
1110
1111  int hivex_visit_node (hive_h *h, hive_node_h node, const struct hivex_visitor *visitor, size_t len, void *opaque);
1112
1113 Same as C<hivex_visit> but instead of starting out at the root, this
1114 starts at C<node>.
1115
1116 =back
1117
1118 =head1 THE STRUCTURE OF THE WINDOWS REGISTRY
1119
1120 Note: To understand the relationship between hives and the common
1121 Windows Registry keys (like C<HKEY_LOCAL_MACHINE>) please see the
1122 Wikipedia page on the Windows Registry.
1123
1124 The Windows Registry is split across various binary files, each
1125 file being known as a \"hive\".  This library only handles a single
1126 hive file at a time.
1127
1128 Hives are n-ary trees with a single root.  Each node in the tree
1129 has a name.
1130
1131 Each node in the tree (including non-leaf nodes) may have an
1132 arbitrary list of (key, value) pairs attached to it.  It may
1133 be the case that one of these pairs has an empty key.  This
1134 is referred to as the default key for the node.
1135
1136 The (key, value) pairs are the place where the useful data is
1137 stored in the registry.  The key is always a string (possibly the
1138 empty string for the default key).  The value is a typed object
1139 (eg. string, int32, binary, etc.).
1140
1141 =head2 RELATIONSHIP TO .REG FILES
1142
1143 Although this library does not care about or deal with Windows reg
1144 files, it's useful to look at the relationship between the registry
1145 itself and reg files because they are so common.
1146
1147 A reg file is a text representation of the registry, or part of the
1148 registry.  The actual registry hives that Windows uses are binary
1149 files.  There are a number of Windows and Linux tools that let you
1150 generate reg files, or merge reg files back into the registry hives.
1151 Notable amongst them is Microsoft's REGEDIT program (formerly known as
1152 REGEDT32).
1153
1154 A typical reg file will contain many sections looking like this:
1155
1156  [HKEY_LOCAL_MACHINE\\SOFTWARE\\Classes\\Stack]
1157  \"@\"=\"Generic Stack\"
1158  \"TileInfo\"=\"prop:System.FileCount\"
1159  \"TilePath\"=str(2):\"%%systemroot%%\\\\system32\"
1160  \"ThumbnailCutoff\"=dword:00000000
1161  \"FriendlyTypeName\"=hex(2):40,00,25,00,53,00,79,00,73,00,74,00,65,00,6d,00,52,00,6f,00,\\
1162   6f,00,74,00,25,00,5c,00,53,00,79,00,73,00,74,00,65,00,6d,00,\\
1163   33,00,32,00,5c,00,73,00,65,00,61,00,72,00,63,00,68,00,66,00,\\
1164   6f,00,6c,00,64,00,65,00,72,00,2e,00,64,00,6c,00,6c,00,2c,00,\\
1165   2d,00,39,00,30,00,32,00,38,00,00,00,d8
1166
1167 Taking this one piece at a time:
1168
1169  [HKEY_LOCAL_MACHINE\\SOFTWARE\\Classes\\Stack]
1170
1171 This is the path to this node in the registry tree.  The first part,
1172 C<HKEY_LOCAL_MACHINE\\SOFTWARE> means that this comes from a hive
1173 (file) called C<SOFTWARE>.  C<\\Classes\\Stack> is the real path part,
1174 starting at the root node of the C<SOFTWARE> hive.
1175
1176 Below the node name is a list of zero or more key-value pairs.  Any
1177 interior or leaf node in the registry may have key-value pairs
1178 attached.
1179
1180  \"@\"=\"Generic Stack\"
1181
1182 This is the \"default key\".  In reality (ie. inside the binary hive)
1183 the key string is the empty string.  In reg files this is written as
1184 C<@> but this has no meaning either in the hives themselves or in this
1185 library.  The value is a string (type 1 - see C<enum hive_type>
1186 above).
1187
1188  \"TileInfo\"=\"prop:System.FileCount\"
1189
1190 This is a regular (key, value) pair, with the value being a type 1
1191 string.  Note that inside the binary file the string is likely to be
1192 UTF-16 encoded.  This library converts to and from UTF-8 strings
1193 transparently.
1194
1195  \"TilePath\"=str(2):\"%%systemroot%%\\\\system32\"
1196
1197 The value in this case has type 2 (expanded string) meaning that some
1198 %%...%% variables get expanded by Windows.  (This library doesn't know
1199 or care about variable expansion).
1200
1201  \"ThumbnailCutoff\"=dword:00000000
1202
1203 The value in this case is a dword (type 4).
1204
1205  \"FriendlyTypeName\"=hex(2):40,00,....
1206
1207 This value is an expanded string (type 2) represented in the reg file
1208 as a series of hex bytes.  In this case the string appears to be a
1209 UTF-16 string.
1210
1211 =head1 NOTE ON THE USE OF ERRNO
1212
1213 Many functions in this library set errno to indicate errors.  These
1214 are the values of errno you may encounter (this list is not
1215 exhaustive):
1216
1217 =over 4
1218
1219 =item ENOTSUP
1220
1221 Corrupt or unsupported Registry file format.
1222
1223 =item ENOKEY
1224
1225 Missing root key.
1226
1227 =item EINVAL
1228
1229 Passed an invalid argument to the function.
1230
1231 =item EFAULT
1232
1233 Followed a Registry pointer which goes outside
1234 the registry or outside a registry block.
1235
1236 =item ELOOP
1237
1238 Registry contains cycles.
1239
1240 =item ERANGE
1241
1242 Field in the registry out of range.
1243
1244 =item EEXIST
1245
1246 Registry key already exists.
1247
1248 =item EROFS
1249
1250 Tried to write to a registry which is not opened for writing.
1251
1252 =back
1253
1254 =head1 ENVIRONMENT VARIABLES
1255
1256 =over 4
1257
1258 =item HIVEX_DEBUG
1259
1260 Setting HIVEX_DEBUG=1 will enable very verbose messages.  This is
1261 useful for debugging problems with the library itself.
1262
1263 =back
1264
1265 =head1 SEE ALSO
1266
1267 L<hivexml(1)>,
1268 L<hivexsh(1)>,
1269 L<virt-win-reg(1)>,
1270 L<guestfs(3)>,
1271 L<http://libguestfs.org/>,
1272 L<virt-cat(1)>,
1273 L<virt-edit(1)>,
1274 L<http://en.wikipedia.org/wiki/Windows_Registry>.
1275
1276 =head1 AUTHORS
1277
1278 Richard W.M. Jones (C<rjones at redhat dot com>)
1279
1280 =head1 COPYRIGHT
1281
1282 Copyright (C) 2009-2010 Red Hat Inc.
1283
1284 Derived from code by Petter Nordahl-Hagen under a compatible license:
1285 Copyright (C) 1997-2007 Petter Nordahl-Hagen.
1286
1287 Derived from code by Markus Stephany under a compatible license:
1288 Copyright (C) 2000-2004 Markus Stephany.
1289
1290 This library is free software; you can redistribute it and/or
1291 modify it under the terms of the GNU Lesser General Public
1292 License as published by the Free Software Foundation;
1293 version 2.1 of the License only.
1294
1295 This library is distributed in the hope that it will be useful,
1296 but WITHOUT ANY WARRANTY; without even the implied warranty of
1297 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
1298 Lesser General Public License for more details.
1299 "
1300
1301 let output_to filename k =
1302   let filename_new = filename ^ ".new" in
1303   chan := open_out filename_new;
1304   k ();
1305   close_out !chan;
1306   chan := Pervasives.stdout;
1307
1308   (* Is the new file different from the current file? *)
1309   if Sys.file_exists filename && files_equal filename filename_new then
1310     unlink filename_new                 (* same, so skip it *)
1311   else (
1312     (* different, overwrite old one *)
1313     (try chmod filename 0o644 with Unix_error _ -> ());
1314     rename filename_new filename;
1315     chmod filename 0o444;
1316     printf "written %s\n%!" filename;
1317   )
1318
1319 let perror msg = function
1320   | Unix_error (err, _, _) ->
1321       eprintf "%s: %s\n" msg (error_message err)
1322   | exn ->
1323       eprintf "%s: %s\n" msg (Printexc.to_string exn)
1324
1325 (* Main program. *)
1326 let () =
1327   let lock_fd =
1328     try openfile "configure.ac" [O_RDWR] 0
1329     with
1330     | Unix_error (ENOENT, _, _) ->
1331         eprintf "\
1332 You are probably running this from the wrong directory.
1333 Run it from the top source directory using the command
1334   generator/generator.ml
1335 ";
1336         exit 1
1337     | exn ->
1338         perror "open: configure.ac" exn;
1339         exit 1 in
1340
1341   (* Acquire a lock so parallel builds won't try to run the generator
1342    * twice at the same time.  Subsequent builds will wait for the first
1343    * one to finish.  Note the lock is released implicitly when the
1344    * program exits.
1345    *)
1346   (try lockf lock_fd F_LOCK 1
1347    with exn ->
1348      perror "lock: configure.ac" exn;
1349      exit 1);
1350
1351   check_functions ();
1352
1353   output_to "hivex/hivex.h" generate_c_header;
1354   output_to "hivex/hivex.pod" generate_c_pod;
1355
1356   (* Always generate this file last, and unconditionally.  It's used
1357    * by the Makefile to know when we must re-run the generator.
1358    *)
1359   let chan = open_out "generator/stamp-generator" in
1360   fprintf chan "1\n";
1361   close_out chan;
1362
1363   printf "generated %d lines of code\n" !lines