Remove bogus msgstr from kn.po.
[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   | RErrDispose                         (* Disposes handle, see hivex_close. *)
49   | RHive                               (* Returns a hive_h or NULL. *)
50   | RNode                               (* Returns hive_node_h or 0. *)
51   | RNodeNotFound                       (* See hivex_node_get_child. *)
52   | RNodeList                           (* Returns hive_node_h* or NULL. *)
53   | RValue                              (* Returns hive_value_h or 0. *)
54   | RValueList                          (* Returns hive_value_h* or NULL. *)
55   | RString                             (* Returns char* or NULL. *)
56   | RStringList                         (* Returns char** or NULL. *)
57   | RLenType                            (* See hivex_value_type. *)
58   | RLenTypeVal                         (* See hivex_value_value. *)
59   | RInt32                              (* Returns int32. *)
60   | RInt64                              (* Returns int64. *)
61
62 and args = argt list                    (* List of parameters. *)
63
64 and argt =                              (* Note, cannot be NULL/0 unless it
65                                            says so explicitly below. *)
66   | AHive                               (* hive_h* *)
67   | ANode of string                     (* hive_node_h *)
68   | AValue of string                    (* hive_value_h *)
69   | AString of string                   (* char* *)
70   | AStringNullable of string           (* char* (can be NULL) *)
71   | AOpenFlags                          (* HIVEX_OPEN_* flags list. *)
72   | AUnusedFlags                        (* Flags arg that is always 0 *)
73   | ASetValues                          (* See hivex_node_set_values. *)
74
75 (* Hive types, from:
76  * https://secure.wikimedia.org/wikipedia/en/wiki/Windows_Registry#Keys_and_values
77  * 
78  * It's unfortunate that in our original C binding we strayed away from
79  * the names that Windows uses (eg. REG_SZ for strings).  We include
80  * both our names and the Windows names.
81  *)
82 let hive_types = [
83   0, "none", "NONE",
84     "Just a key without a value";
85   1, "string", "SZ",
86     "A Windows string (encoding is unknown, but often UTF16-LE)";
87   2, "expand_string", "EXPAND_SZ",
88     "A Windows string that contains %env% (environment variable expansion)";
89   3, "binary", "BINARY",
90     "A blob of binary";
91   4, "dword", "DWORD",
92     "DWORD (32 bit integer), little endian";
93   5, "dword_be", "DWORD_BIG_ENDIAN",
94     "DWORD (32 bit integer), big endian";
95   6, "link", "LINK",
96     "Symbolic link to another part of the registry tree";
97   7, "multiple_strings", "MULTI_SZ",
98     "Multiple Windows strings.  See http://blogs.msdn.com/oldnewthing/archive/2009/10/08/9904646.aspx";
99   8, "resource_list", "RESOURCE_LIST",
100     "Resource list";
101   9, "full_resource_description", "FULL_RESOURCE_DESCRIPTOR",
102     "Resource descriptor";
103   10, "resource_requirements_list", "RESOURCE_REQUIREMENTS_LIST",
104     "Resouce requirements list";
105   11, "qword", "QWORD",
106     "QWORD (64 bit integer), unspecified endianness but usually little endian"
107 ]
108 let max_hive_type = 11
109
110 (* Open flags (bitmask passed to AOpenFlags) *)
111 let open_flags = [
112   1, "VERBOSE", "Verbose messages";
113   2, "DEBUG", "Debug messages";
114   4, "WRITE", "Enable writes to the hive";
115 ]
116
117 (* The API calls. *)
118 let functions = [
119   "open", (RHive, [AString "filename"; AOpenFlags]),
120     "open a hive file",
121     "\
122 Opens the hive named C<filename> for reading.
123
124 Flags is an ORed list of the open flags (or C<0> if you don't
125 want to pass any flags).  These flags are defined:
126
127 =over 4
128
129 =item HIVEX_OPEN_VERBOSE
130
131 Verbose messages.
132
133 =item HIVEX_OPEN_DEBUG
134
135 Very verbose messages, suitable for debugging problems in the library
136 itself.
137
138 This is also selected if the C<HIVEX_DEBUG> environment variable
139 is set to 1.
140
141 =item HIVEX_OPEN_WRITE
142
143 Open the hive for writing.  If omitted, the hive is read-only.
144
145 See L<hivex(3)/WRITING TO HIVE FILES>.
146
147 =back";
148
149   "close", (RErrDispose, [AHive]),
150     "close a hive handle",
151     "\
152 Close a hive handle and free all associated resources.
153
154 Note that any uncommitted writes are I<not> committed by this call,
155 but instead are lost.  See L<hivex(3)/WRITING TO HIVE FILES>.";
156
157   "root", (RNode, [AHive]),
158     "return the root node of the hive",
159     "\
160 Return root node of the hive.  All valid registries must contain
161 a root node.";
162
163   "node_name", (RString, [AHive; ANode "node"]),
164     "return the name of the node",
165     "\
166 Return the name of the node.
167
168 Note that the name of the root node is a dummy, such as
169 C<$$$PROTO.HIV> (other names are possible: it seems to depend on the
170 tool or program that created the hive in the first place).  You can
171 only know the \"real\" name of the root node by knowing which registry
172 file this hive originally comes from, which is knowledge that is
173 outside the scope of this library.";
174
175   "node_children", (RNodeList, [AHive; ANode "node"]),
176     "return children of node",
177     "\
178 Return an array of nodes which are the subkeys
179 (children) of C<node>.";
180
181   "node_get_child", (RNodeNotFound, [AHive; ANode "node"; AString "name"]),
182     "return named child of node",
183     "\
184 Return the child of node with the name C<name>, if it exists.
185
186 The name is matched case insensitively.";
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
739   pr "/* Functions. */\n";
740
741   (* Function declarations. *)
742   List.iter (
743     fun (shortname, style, _, _) ->
744       let name = "hivex_" ^ shortname in
745       generate_c_prototype ~extern:true name style
746   ) functions;
747
748   (* The visitor pattern. *)
749   pr "
750 /* Visit all nodes.  This is specific to the C API and is not made
751  * available to other languages.  This is because of the complexity
752  * of binding callbacks in other languages, but also because other
753  * languages make it much simpler to iterate over a tree.
754  */
755 struct hivex_visitor {
756   int (*node_start) (hive_h *, void *opaque, hive_node_h, const char *name);
757   int (*node_end) (hive_h *, void *opaque, hive_node_h, const char *name);
758   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);
759   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);
760   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);
761   int (*value_dword) (hive_h *, void *opaque, hive_node_h, hive_value_h, hive_type t, size_t len, const char *key, int32_t);
762   int (*value_qword) (hive_h *, void *opaque, hive_node_h, hive_value_h, hive_type t, size_t len, const char *key, int64_t);
763   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);
764   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);
765   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);
766   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);
767 };
768
769 #define HIVEX_VISIT_SKIP_BAD 1
770
771 extern int hivex_visit (hive_h *h, const struct hivex_visitor *visitor, size_t len, void *opaque, int flags);
772 extern int hivex_visit_node (hive_h *h, hive_node_h node, const struct hivex_visitor *visitor, size_t len, void *opaque, int flags);
773
774 ";
775
776   (* Finish the header file. *)
777   pr "\
778 #ifdef __cplusplus
779 }
780 #endif
781
782 #endif /* HIVEX_H_ */
783 "
784
785 and generate_c_prototype ?(extern = false) name style =
786   if extern then pr "extern ";
787   (match fst style with
788    | RErr -> pr "int "
789    | RErrDispose -> pr "int "
790    | RHive -> pr "hive_h *"
791    | RNode -> pr "hive_node_h "
792    | RNodeNotFound -> pr "hive_node_h "
793    | RNodeList -> pr "hive_node_h *"
794    | RValue -> pr "hive_value_h "
795    | RValueList -> pr "hive_value_h *"
796    | RString -> pr "char *"
797    | RStringList -> pr "char **"
798    | RLenType -> pr "int "
799    | RLenTypeVal -> pr "char *"
800    | RInt32 -> pr "int32_t "
801    | RInt64 -> pr "int64_t "
802   );
803   pr "%s (" name;
804   let comma = ref false in
805   List.iter (
806     fun arg ->
807       if !comma then pr ", "; comma := true;
808       match arg with
809       | AHive -> pr "hive_h *h"
810       | ANode n -> pr "hive_node_h %s" n
811       | AValue n -> pr "hive_value_h %s" n
812       | AString n | AStringNullable n -> pr "const char *%s" n
813       | AOpenFlags | AUnusedFlags -> pr "int flags"
814       | ASetValues -> pr "size_t nr_values, const hive_set_value *values"
815   ) (snd style);
816   (match fst style with
817    | RLenType | RLenTypeVal -> pr ", hive_type *t, size_t *len"
818    | _ -> ()
819   );
820   pr ");\n"
821
822 and generate_c_pod () =
823   generate_header PODCommentStyle GPLv2;
824
825   pr "\
826   =encoding utf8
827
828 =head1 NAME
829
830 hivex - Windows Registry \"hive\" extraction library
831
832 =head1 SYNOPSIS
833
834  #include <hivex.h>
835  
836 ";
837   List.iter (
838     fun (shortname, style, _, _) ->
839       let name = "hivex_" ^ shortname in
840       pr " ";
841       generate_c_prototype ~extern:false name style;
842   ) functions;
843
844   pr "\
845
846 Link with I<-lhivex>.
847
848 =head1 DESCRIPTION
849
850 libhivex is a library for extracting the contents of Windows Registry
851 \"hive\" files.  It is designed to be secure against buggy or malicious
852 registry files.
853
854 Unlike many other tools in this area, it doesn't use the textual .REG
855 format for output, because parsing that is as much trouble as parsing
856 the original binary format.  Instead it makes the file available
857 through a C API, or there is a separate program to export the hive as
858 XML (see L<hivexml(1)>), or to navigate the file (see L<hivexsh(1)>).
859
860 =head1 TYPES
861
862 =head2 hive_h *
863
864 This handle describes an open hive file.
865
866 =head2 hive_node_h
867
868 This is a node handle, an integer but opaque outside the library.
869 Valid node handles cannot be 0.  The library returns 0 in some
870 situations to indicate an error.
871
872 =head2 hive_type
873
874 The enum below describes the possible types for the value(s)
875 stored at each node.  Note that you should not trust the
876 type field in a Windows Registry, as it very often has no
877 relationship to reality.  Some applications use their own
878 types.  The encoding of strings is not specified.  Some
879 programs store everything (including strings) in binary blobs.
880
881  enum hive_type {
882 ";
883   List.iter (
884     fun (t, _, new_style, description) ->
885       pr "   /* %s */\n" description;
886       pr "   hive_t_REG_%s = %d,\n" new_style t
887   ) hive_types;
888   pr "\
889  };
890
891 =head2 hive_value_h
892
893 This is a value handle, an integer but opaque outside the library.
894 Valid value handles cannot be 0.  The library returns 0 in some
895 situations to indicate an error.
896
897 =head2 hive_set_value
898
899 The typedef C<hive_set_value> is used in conjunction with the
900 C<hivex_node_set_values> call described below.
901
902  struct hive_set_value {
903    char *key;     /* key - a UTF-8 encoded ASCIIZ string */
904    hive_type t;   /* type of value field */
905    size_t len;    /* length of value field in bytes */
906    char *value;   /* value field */
907  };
908  typedef struct hive_set_value hive_set_value;
909
910 To set the default value for a node, you have to pass C<key = \"\">.
911
912 Note that the C<value> field is just treated as a list of bytes, and
913 is stored directly in the hive.  The caller has to ensure correct
914 encoding and endianness, for example converting dwords to little
915 endian.
916
917 The correct type and encoding for values depends on the node and key
918 in the registry, the version of Windows, and sometimes even changes
919 between versions of Windows for the same key.  We don't document it
920 here.  Often it's not documented at all.
921
922 =head1 FUNCTIONS
923
924 ";
925   List.iter (
926     fun (shortname, style, _, longdesc) ->
927       let name = "hivex_" ^ shortname in
928       pr "=head2 %s\n" name;
929       pr "\n";
930       generate_c_prototype ~extern:false name style;
931       pr "\n";
932       pr "%s\n" longdesc;
933       pr "\n";
934       (match fst style with
935        | RErr ->
936            pr "\
937 Returns 0 on success.
938 On error this returns -1 and sets errno.\n\n"
939        | RErrDispose ->
940            pr "\
941 Returns 0 on success.
942 On error this returns -1 and sets errno.
943
944 This function frees the hive handle (even if it returns an error).
945 The hive handle must not be used again after calling this function.\n\n"
946        | RHive ->
947            pr "\
948 Returns a new hive handle.
949 On error this returns NULL and sets errno.\n\n"
950        | RNode ->
951            pr "\
952 Returns a node handle.
953 On error this returns 0 and sets errno.\n\n"
954        | RNodeNotFound ->
955            pr "\
956 Returns a node handle.
957 If the node was not found, this returns 0 without setting errno.
958 On error this returns 0 and sets errno.\n\n"
959        | RNodeList ->
960            pr "\
961 Returns a 0-terminated array of nodes.
962 The array must be freed by the caller when it is no longer needed.
963 On error this returns NULL and sets errno.\n\n"
964        | RValue ->
965            pr "\
966 Returns a value handle.
967 On error this returns 0 and sets errno.\n\n"
968        | RValueList ->
969            pr "\
970 Returns a 0-terminated array of values.
971 The array must be freed by the caller when it is no longer needed.
972 On error this returns NULL and sets errno.\n\n"
973        | RString ->
974            pr "\
975 Returns a string.
976 The string must be freed by the caller when it is no longer needed.
977 On error this returns NULL and sets errno.\n\n"
978        | RStringList ->
979            pr "\
980 Returns a NULL-terminated array of C strings.
981 The strings and the array must all be freed by the caller when
982 they are no longer needed.
983 On error this returns NULL and sets errno.\n\n"
984        | RLenType ->
985            pr "\
986 Returns 0 on success.
987 On error this returns NULL and sets errno.\n\n"
988        | RLenTypeVal ->
989            pr "\
990 The value is returned as an array of bytes (of length C<len>).
991 The value must be freed by the caller when it is no longer needed.
992 On error this returns NULL and sets errno.\n\n"
993        | RInt32 | RInt64 -> ()
994       );
995   ) functions;
996
997   pr "\
998 =head1 WRITING TO HIVE FILES
999
1000 The hivex library supports making limited modifications to hive files.
1001 We have tried to implement this very conservatively in order to reduce
1002 the chance of corrupting your registry.  However you should be careful
1003 and take back-ups, since Microsoft has never documented the hive
1004 format, and so it is possible there are nuances in the
1005 reverse-engineered format that we do not understand.
1006
1007 To be able to modify a hive, you must pass the C<HIVEX_OPEN_WRITE>
1008 flag to C<hivex_open>, otherwise any write operation will return with
1009 errno C<EROFS>.
1010
1011 The write operations shown below do not modify the on-disk file
1012 immediately.  You must call C<hivex_commit> in order to write the
1013 changes to disk.  If you call C<hivex_close> without committing then
1014 any writes are discarded.
1015
1016 Hive files internally consist of a \"memory dump\" of binary blocks
1017 (like the C heap), and some of these blocks can be unused.  The hivex
1018 library never reuses these unused blocks.  Instead, to ensure
1019 robustness in the face of the partially understood on-disk format,
1020 hivex only allocates new blocks after the end of the file, and makes
1021 minimal modifications to existing structures in the file to point to
1022 these new blocks.  This makes hivex slightly less disk-efficient than
1023 it could be, but disk is cheap, and registry modifications tend to be
1024 very small.
1025
1026 When deleting nodes, it is possible that this library may leave
1027 unreachable live blocks in the hive.  This is because certain parts of
1028 the hive disk format such as security (sk) records and big data (db)
1029 records and classname fields are not well understood (and not
1030 documented at all) and we play it safe by not attempting to modify
1031 them.  Apart from wasting a little bit of disk space, it is not
1032 thought that unreachable blocks are a problem.
1033
1034 =head2 WRITE OPERATIONS WHICH ARE NOT SUPPORTED
1035
1036 =over 4
1037
1038 =item *
1039
1040 Changing the root node.
1041
1042 =item *
1043
1044 Creating a new hive file from scratch.  This is impossible at present
1045 because not all fields in the header are understood.
1046
1047 =item *
1048
1049 Modifying or deleting single values at a node.
1050
1051 =item *
1052
1053 Modifying security key (sk) records or classnames.
1054 Previously we did not understand these records.  However now they
1055 are well-understood and we could add support if it was required
1056 (but nothing much really uses them).
1057
1058 =back
1059
1060 =head1 VISITING ALL NODES
1061
1062 The visitor pattern is useful if you want to visit all nodes
1063 in the tree or all nodes below a certain point in the tree.
1064
1065 First you set up your own C<struct hivex_visitor> with your
1066 callback functions.
1067
1068 Each of these callback functions should return 0 on success or -1
1069 on error.  If any callback returns -1, then the entire visit
1070 terminates immediately.  If you don't need a callback function at
1071 all, set the function pointer to NULL.
1072
1073  struct hivex_visitor {
1074    int (*node_start) (hive_h *, void *opaque, hive_node_h, const char *name);
1075    int (*node_end) (hive_h *, void *opaque, hive_node_h, const char *name);
1076    int (*value_string) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1077          hive_type t, size_t len, const char *key, const char *str);
1078    int (*value_multiple_strings) (hive_h *, void *opaque, hive_node_h,
1079          hive_value_h, hive_type t, size_t len, const char *key, char **argv);
1080    int (*value_string_invalid_utf16) (hive_h *, void *opaque, hive_node_h,
1081          hive_value_h, hive_type t, size_t len, const char *key,
1082          const char *str);
1083    int (*value_dword) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1084          hive_type t, size_t len, const char *key, int32_t);
1085    int (*value_qword) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1086          hive_type t, size_t len, const char *key, int64_t);
1087    int (*value_binary) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1088          hive_type t, size_t len, const char *key, const char *value);
1089    int (*value_none) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1090          hive_type t, size_t len, const char *key, const char *value);
1091    int (*value_other) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1092          hive_type t, size_t len, const char *key, const char *value);
1093    /* If value_any callback is not NULL, then the other value_*
1094     * callbacks are not used, and value_any is called on all values.
1095     */
1096    int (*value_any) (hive_h *, void *opaque, hive_node_h, hive_value_h,
1097          hive_type t, size_t len, const char *key, const char *value);
1098  };
1099
1100 =over 4
1101
1102 =item hivex_visit
1103
1104  int hivex_visit (hive_h *h, const struct hivex_visitor *visitor, size_t len, void *opaque, int flags);
1105
1106 Visit all the nodes recursively in the hive C<h>.
1107
1108 C<visitor> should be a C<hivex_visitor> structure with callback
1109 fields filled in as required (unwanted callbacks can be set to
1110 NULL).  C<len> must be the length of the 'visitor' struct (you
1111 should pass C<sizeof (struct hivex_visitor)> for this).
1112
1113 This returns 0 if the whole recursive visit was completed
1114 successfully.  On error this returns -1.  If one of the callback
1115 functions returned an error than we don't touch errno.  If the
1116 error was generated internally then we set errno.
1117
1118 You can skip bad registry entries by setting C<flag> to
1119 C<HIVEX_VISIT_SKIP_BAD>.  If this flag is not set, then a bad registry
1120 causes the function to return an error immediately.
1121
1122 This function is robust if the registry contains cycles or
1123 pointers which are invalid or outside the registry.  It detects
1124 these cases and returns an error.
1125
1126 =item hivex_visit_node
1127
1128  int hivex_visit_node (hive_h *h, hive_node_h node, const struct hivex_visitor *visitor, size_t len, void *opaque);
1129
1130 Same as C<hivex_visit> but instead of starting out at the root, this
1131 starts at C<node>.
1132
1133 =back
1134
1135 =head1 THE STRUCTURE OF THE WINDOWS REGISTRY
1136
1137 Note: To understand the relationship between hives and the common
1138 Windows Registry keys (like C<HKEY_LOCAL_MACHINE>) please see the
1139 Wikipedia page on the Windows Registry.
1140
1141 The Windows Registry is split across various binary files, each
1142 file being known as a \"hive\".  This library only handles a single
1143 hive file at a time.
1144
1145 Hives are n-ary trees with a single root.  Each node in the tree
1146 has a name.
1147
1148 Each node in the tree (including non-leaf nodes) may have an
1149 arbitrary list of (key, value) pairs attached to it.  It may
1150 be the case that one of these pairs has an empty key.  This
1151 is referred to as the default key for the node.
1152
1153 The (key, value) pairs are the place where the useful data is
1154 stored in the registry.  The key is always a string (possibly the
1155 empty string for the default key).  The value is a typed object
1156 (eg. string, int32, binary, etc.).
1157
1158 =head2 RELATIONSHIP TO .REG FILES
1159
1160 Although this library does not care about or deal with Windows reg
1161 files, it's useful to look at the relationship between the registry
1162 itself and reg files because they are so common.
1163
1164 A reg file is a text representation of the registry, or part of the
1165 registry.  The actual registry hives that Windows uses are binary
1166 files.  There are a number of Windows and Linux tools that let you
1167 generate reg files, or merge reg files back into the registry hives.
1168 Notable amongst them is Microsoft's REGEDIT program (formerly known as
1169 REGEDT32).
1170
1171 A typical reg file will contain many sections looking like this:
1172
1173  [HKEY_LOCAL_MACHINE\\SOFTWARE\\Classes\\Stack]
1174  \"@\"=\"Generic Stack\"
1175  \"TileInfo\"=\"prop:System.FileCount\"
1176  \"TilePath\"=str(2):\"%%systemroot%%\\\\system32\"
1177  \"ThumbnailCutoff\"=dword:00000000
1178  \"FriendlyTypeName\"=hex(2):40,00,25,00,53,00,79,00,73,00,74,00,65,00,6d,00,52,00,6f,00,\\
1179   6f,00,74,00,25,00,5c,00,53,00,79,00,73,00,74,00,65,00,6d,00,\\
1180   33,00,32,00,5c,00,73,00,65,00,61,00,72,00,63,00,68,00,66,00,\\
1181   6f,00,6c,00,64,00,65,00,72,00,2e,00,64,00,6c,00,6c,00,2c,00,\\
1182   2d,00,39,00,30,00,32,00,38,00,00,00,d8
1183
1184 Taking this one piece at a time:
1185
1186  [HKEY_LOCAL_MACHINE\\SOFTWARE\\Classes\\Stack]
1187
1188 This is the path to this node in the registry tree.  The first part,
1189 C<HKEY_LOCAL_MACHINE\\SOFTWARE> means that this comes from a hive
1190 (file) called C<SOFTWARE>.  C<\\Classes\\Stack> is the real path part,
1191 starting at the root node of the C<SOFTWARE> hive.
1192
1193 Below the node name is a list of zero or more key-value pairs.  Any
1194 interior or leaf node in the registry may have key-value pairs
1195 attached.
1196
1197  \"@\"=\"Generic Stack\"
1198
1199 This is the \"default key\".  In reality (ie. inside the binary hive)
1200 the key string is the empty string.  In reg files this is written as
1201 C<@> but this has no meaning either in the hives themselves or in this
1202 library.  The value is a string (type 1 - see C<enum hive_type>
1203 above).
1204
1205  \"TileInfo\"=\"prop:System.FileCount\"
1206
1207 This is a regular (key, value) pair, with the value being a type 1
1208 string.  Note that inside the binary file the string is likely to be
1209 UTF-16 encoded.  This library converts to and from UTF-8 strings
1210 transparently.
1211
1212  \"TilePath\"=str(2):\"%%systemroot%%\\\\system32\"
1213
1214 The value in this case has type 2 (expanded string) meaning that some
1215 %%...%% variables get expanded by Windows.  (This library doesn't know
1216 or care about variable expansion).
1217
1218  \"ThumbnailCutoff\"=dword:00000000
1219
1220 The value in this case is a dword (type 4).
1221
1222  \"FriendlyTypeName\"=hex(2):40,00,....
1223
1224 This value is an expanded string (type 2) represented in the reg file
1225 as a series of hex bytes.  In this case the string appears to be a
1226 UTF-16 string.
1227
1228 =head1 NOTE ON THE USE OF ERRNO
1229
1230 Many functions in this library set errno to indicate errors.  These
1231 are the values of errno you may encounter (this list is not
1232 exhaustive):
1233
1234 =over 4
1235
1236 =item ENOTSUP
1237
1238 Corrupt or unsupported Registry file format.
1239
1240 =item ENOKEY
1241
1242 Missing root key.
1243
1244 =item EINVAL
1245
1246 Passed an invalid argument to the function.
1247
1248 =item EFAULT
1249
1250 Followed a Registry pointer which goes outside
1251 the registry or outside a registry block.
1252
1253 =item ELOOP
1254
1255 Registry contains cycles.
1256
1257 =item ERANGE
1258
1259 Field in the registry out of range.
1260
1261 =item EEXIST
1262
1263 Registry key already exists.
1264
1265 =item EROFS
1266
1267 Tried to write to a registry which is not opened for writing.
1268
1269 =back
1270
1271 =head1 ENVIRONMENT VARIABLES
1272
1273 =over 4
1274
1275 =item HIVEX_DEBUG
1276
1277 Setting HIVEX_DEBUG=1 will enable very verbose messages.  This is
1278 useful for debugging problems with the library itself.
1279
1280 =back
1281
1282 =head1 SEE ALSO
1283
1284 L<hivexml(1)>,
1285 L<hivexsh(1)>,
1286 L<virt-win-reg(1)>,
1287 L<guestfs(3)>,
1288 L<http://libguestfs.org/>,
1289 L<virt-cat(1)>,
1290 L<virt-edit(1)>,
1291 L<http://en.wikipedia.org/wiki/Windows_Registry>.
1292
1293 =head1 AUTHORS
1294
1295 Richard W.M. Jones (C<rjones at redhat dot com>)
1296
1297 =head1 COPYRIGHT
1298
1299 Copyright (C) 2009-2010 Red Hat Inc.
1300
1301 Derived from code by Petter Nordahl-Hagen under a compatible license:
1302 Copyright (C) 1997-2007 Petter Nordahl-Hagen.
1303
1304 Derived from code by Markus Stephany under a compatible license:
1305 Copyright (C) 2000-2004 Markus Stephany.
1306
1307 This library is free software; you can redistribute it and/or
1308 modify it under the terms of the GNU Lesser General Public
1309 License as published by the Free Software Foundation;
1310 version 2.1 of the License only.
1311
1312 This library is distributed in the hope that it will be useful,
1313 but WITHOUT ANY WARRANTY; without even the implied warranty of
1314 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
1315 Lesser General Public License for more details.
1316 "
1317
1318 and generate_ocaml_interface () =
1319   generate_header OCamlStyle LGPLv2plus;
1320
1321   pr "\
1322 type t
1323 (** A [hive_h] hive file handle. *)
1324
1325 type node
1326 type value
1327 (** Nodes and values. *)
1328
1329 exception Error of string * Unix.error * string
1330 (** Error raised by a function.
1331
1332     The first parameter is the name of the function which raised the error.
1333     The second parameter is the errno (see the [Unix] module).  The third
1334     parameter is a human-readable string corresponding to the errno.
1335
1336     See hivex(3) for a partial list of interesting errno values that
1337     can be generated by the library. *)
1338 exception Handle_closed of string
1339 (** This exception is raised if you call a function on a closed handle. *)
1340
1341 type hive_type =
1342 ";
1343   iteri (
1344     fun i ->
1345       fun (t, _, new_style, description) ->
1346         assert (i = t);
1347         pr "  | REG_%s (** %s *)\n" new_style description
1348   ) hive_types;
1349
1350   pr "\
1351   | REG_UNKNOWN of int32 (** unknown type *)
1352 (** Hive type field. *)
1353
1354 type open_flag =
1355 ";
1356   iteri (
1357     fun i ->
1358       fun (v, flag, description) ->
1359         assert (1 lsl i = v);
1360         pr "  | OPEN_%s (** %s *)\n" flag description
1361   ) open_flags;
1362
1363   pr "\
1364 (** Open flags for {!open_file} call. *)
1365
1366 type set_value = {
1367   key : string;
1368   t : hive_type;
1369   value : string;
1370 }
1371 (** (key, value) pair passed (as an array) to {!node_set_values}. *)
1372 ";
1373
1374   List.iter (
1375     fun (name, style, shortdesc, _) ->
1376       pr "\n";
1377       generate_ocaml_prototype name style;
1378       pr "(** %s *)\n" shortdesc
1379   ) functions
1380
1381 and generate_ocaml_implementation () =
1382   generate_header OCamlStyle LGPLv2plus;
1383
1384   pr "\
1385 type t
1386 type node = int
1387 type value = int
1388
1389 exception Error of string * Unix.error * string
1390 exception Handle_closed of string
1391
1392 (* Give the exceptions names, so they can be raised from the C code. *)
1393 let () =
1394   Callback.register_exception \"ocaml_hivex_error\"
1395     (Error (\"\", Unix.EUNKNOWNERR 0, \"\"));
1396   Callback.register_exception \"ocaml_hivex_closed\" (Handle_closed \"\")
1397
1398 type hive_type =
1399 ";
1400   iteri (
1401     fun i ->
1402       fun (t, _, new_style, _) ->
1403         assert (i = t);
1404         pr "  | REG_%s\n" new_style
1405   ) hive_types;
1406
1407   pr "\
1408   | REG_UNKNOWN of int32
1409
1410 type open_flag =
1411 ";
1412   iteri (
1413     fun i ->
1414       fun (v, flag, description) ->
1415         assert (1 lsl i = v);
1416         pr "  | OPEN_%s (** %s *)\n" flag description
1417   ) open_flags;
1418
1419   pr "\
1420
1421 type set_value = {
1422   key : string;
1423   t : hive_type;
1424   value : string;
1425 }
1426
1427 ";
1428
1429   List.iter (
1430     fun (name, style, _, _) ->
1431       generate_ocaml_prototype ~is_external:true name style
1432   ) functions
1433
1434 and generate_ocaml_prototype ?(is_external = false) name style =
1435   let ocaml_name = if name = "open" then "open_file" else name in
1436
1437   if is_external then pr "external " else pr "val ";
1438   pr "%s : " ocaml_name;
1439   List.iter (
1440     function
1441     | AHive -> pr "t -> "
1442     | ANode _ -> pr "node -> "
1443     | AValue _ -> pr "value -> "
1444     | AString _ -> pr "string -> "
1445     | AStringNullable _ -> pr "string option -> "
1446     | AOpenFlags -> pr "open_flag list -> "
1447     | AUnusedFlags -> ()
1448     | ASetValues -> pr "set_value array -> "
1449   ) (snd style);
1450   (match fst style with
1451    | RErr -> pr "unit" (* all errors are turned into exceptions *)
1452    | RErrDispose -> pr "unit"
1453    | RHive -> pr "t"
1454    | RNode -> pr "node"
1455    | RNodeNotFound -> pr "node"
1456    | RNodeList -> pr "node array"
1457    | RValue -> pr "value"
1458    | RValueList -> pr "value array"
1459    | RString -> pr "string"
1460    | RStringList -> pr "string array"
1461    | RLenType -> pr "hive_type * int"
1462    | RLenTypeVal -> pr "hive_type * string"
1463    | RInt32 -> pr "int32"
1464    | RInt64 -> pr "int64"
1465   );
1466   if is_external then
1467     pr " = \"ocaml_hivex_%s\"" name;
1468   pr "\n"
1469
1470 and generate_ocaml_c () =
1471   generate_header CStyle LGPLv2plus;
1472
1473   pr "\
1474 #include <config.h>
1475
1476 #include <stdio.h>
1477 #include <stdlib.h>
1478 #include <string.h>
1479 #include <stdint.h>
1480 #include <errno.h>
1481
1482 #include <caml/config.h>
1483 #include <caml/alloc.h>
1484 #include <caml/callback.h>
1485 #include <caml/custom.h>
1486 #include <caml/fail.h>
1487 #include <caml/memory.h>
1488 #include <caml/mlvalues.h>
1489 #include <caml/signals.h>
1490 #include <caml/unixsupport.h>
1491
1492 #include <hivex.h>
1493
1494 #define Hiveh_val(v) (*((hive_h **)Data_custom_val(v)))
1495 static value Val_hiveh (hive_h *);
1496 static int HiveOpenFlags_val (value);
1497 static hive_set_value *HiveSetValues_val (value);
1498 static hive_type HiveType_val (value);
1499 static value Val_hive_type (hive_type);
1500 static value copy_int_array (size_t *);
1501 static value copy_type_len (size_t, hive_type);
1502 static value copy_type_value (const char *, size_t, hive_type);
1503 static void raise_error (const char *) Noreturn;
1504 static void raise_closed (const char *) Noreturn;
1505
1506 ";
1507
1508   (* The wrappers. *)
1509   List.iter (
1510     fun (name, style, _, _) ->
1511       pr "/* Automatically generated wrapper for function\n";
1512       pr " * "; generate_ocaml_prototype name style;
1513       pr " */\n";
1514       pr "\n";
1515
1516       let c_params =
1517         List.map (function
1518                   | ASetValues -> ["nrvalues"; "values"]
1519                   | AUnusedFlags -> ["0"]
1520                   | arg -> [name_of_argt arg]) (snd style) in
1521       let c_params =
1522         match fst style with
1523         | RLenType | RLenTypeVal -> c_params @ [["&t"; "&len"]]
1524         | _ -> c_params in
1525       let c_params = List.concat c_params in
1526
1527       let params =
1528         filter_map (function
1529                     | AUnusedFlags -> None
1530                     | arg -> Some (name_of_argt arg ^ "v")) (snd style) in
1531
1532       pr "/* Emit prototype to appease gcc's -Wmissing-prototypes. */\n";
1533       pr "CAMLprim value ocaml_hivex_%s (value %s" name (List.hd params);
1534       List.iter (pr ", value %s") (List.tl params); pr ");\n";
1535       pr "\n";
1536
1537       pr "CAMLprim value\n";
1538       pr "ocaml_hivex_%s (value %s" name (List.hd params);
1539       List.iter (pr ", value %s") (List.tl params);
1540       pr ")\n";
1541       pr "{\n";
1542
1543       pr "  CAMLparam%d (%s);\n"
1544         (List.length params) (String.concat ", " params);
1545       pr "  CAMLlocal1 (rv);\n";
1546       pr "\n";
1547
1548       List.iter (
1549         function
1550         | AHive ->
1551             pr "  hive_h *h = Hiveh_val (hv);\n";
1552             pr "  if (h == NULL)\n";
1553             pr "    raise_closed (\"%s\");\n" name
1554         | ANode n ->
1555             pr "  hive_node_h %s = Int_val (%sv);\n" n n
1556         | AValue n ->
1557             pr "  hive_value_h %s = Int_val (%sv);\n" n n
1558         | AString n ->
1559             pr "  const char *%s = String_val (%sv);\n" n n
1560         | AStringNullable n ->
1561             pr "  const char *%s =\n" n;
1562             pr "    %sv != Val_int (0) ? String_val (Field (%sv, 0)) : NULL;\n"
1563               n n
1564         | AOpenFlags ->
1565             pr "  int flags = HiveOpenFlags_val (flagsv);\n"
1566         | AUnusedFlags -> ()
1567         | ASetValues ->
1568             pr "  int nrvalues = Wosize_val (valuesv);\n";
1569             pr "  hive_set_value *values = HiveSetValues_val (valuesv);\n"
1570       ) (snd style);
1571       pr "\n";
1572
1573       let error_code =
1574         match fst style with
1575         | RErr -> pr "  int r;\n"; "-1"
1576         | RErrDispose -> pr "  int r;\n"; "-1"
1577         | RHive -> pr "  hive_h *r;\n"; "NULL"
1578         | RNode -> pr "  hive_node_h r;\n"; "0"
1579         | RNodeNotFound ->
1580             pr "  errno = 0;\n";
1581             pr "  hive_node_h r;\n";
1582             "0 && errno != 0"
1583         | RNodeList -> pr "  hive_node_h *r;\n"; "NULL"
1584         | RValue -> pr "  hive_value_h r;\n"; "0"
1585         | RValueList -> pr "  hive_value_h *r;\n"; "NULL"
1586         | RString -> pr "  char *r;\n"; "NULL"
1587         | RStringList -> pr "  char **r;\n"; "NULL"
1588         | RLenType ->
1589             pr "  int r;\n";
1590             pr "  size_t len;\n";
1591             pr "  hive_type t;\n";
1592             "-1"
1593         | RLenTypeVal ->
1594             pr "  char *r;\n";
1595             pr "  size_t len;\n";
1596             pr "  hive_type t;\n";
1597             "NULL"
1598         | RInt32 ->
1599             pr "  errno = 0;\n";
1600             pr "  int32_t r;\n";
1601             "-1 && errno != 0"
1602         | RInt64 ->
1603             pr "  errno = 0;\n";
1604             pr "  int64_t r;\n";
1605             "-1 && errno != 0" in
1606
1607       (* The libguestfs OCaml bindings call enter_blocking_section
1608        * here.  However I don't think that is safe, because we are
1609        * holding pointers to caml strings during the call, and these
1610        * could be moved or freed by other threads.  In any case, there
1611        * is very little reason to enter_blocking_section for any hivex
1612        * call, so don't do it.  XXX
1613        *)
1614       (*pr "  caml_enter_blocking_section ();\n";*)
1615       pr "  r = hivex_%s (%s" name (List.hd c_params);
1616       List.iter (pr ", %s") (List.tl c_params);
1617       pr ");\n";
1618       (*pr "  caml_leave_blocking_section ();\n";*)
1619       pr "\n";
1620
1621       (* Dispose of the hive handle (even if hivex_close returns error). *)
1622       (match fst style with
1623        | RErrDispose ->
1624            pr "  /* So we don't double-free in the finalizer. */\n";
1625            pr "  Hiveh_val (hv) = NULL;\n";
1626            pr "\n";
1627        | _ -> ()
1628       );
1629
1630       List.iter (
1631         function
1632         | AHive | ANode _ | AValue _ | AString _ | AStringNullable _
1633         | AOpenFlags | AUnusedFlags -> ()
1634         | ASetValues ->
1635             pr "  free (values);\n";
1636             pr "\n";
1637       ) (snd style);
1638
1639       (* Check for errors. *)
1640       pr "  if (r == %s)\n" error_code;
1641       pr "    raise_error (\"%s\");\n" name;
1642       pr "\n";
1643
1644       (match fst style with
1645        | RErr -> pr "  rv = Val_unit;\n"
1646        | RErrDispose -> pr "  rv = Val_unit;\n"
1647        | RHive -> pr "  rv = Val_hiveh (r);\n"
1648        | RNode -> pr "  rv = Val_int (r);\n"
1649        | RNodeNotFound ->
1650            pr "  if (r == 0)\n";
1651            pr "    caml_raise_not_found ();\n";
1652            pr "\n";
1653            pr "  rv = Val_int (r);\n"
1654        | RNodeList ->
1655            pr "  rv = copy_int_array (r);\n";
1656            pr "  free (r);\n"
1657        | RValue -> pr "  rv = Val_int (r);\n"
1658        | RValueList ->
1659            pr "  rv = copy_int_array (r);\n";
1660            pr "  free (r);\n"
1661        | RString ->
1662            pr "  rv = caml_copy_string (r);\n";
1663            pr "  free (r);\n"
1664        | RStringList ->
1665            pr "  rv = caml_copy_string_array ((const char **) r);\n";
1666            pr "  for (int i = 0; r[i] != NULL; ++i) free (r[i]);\n";
1667            pr "  free (r);\n"
1668        | RLenType -> pr "  rv = copy_type_len (len, t);\n"
1669        | RLenTypeVal ->
1670            pr "  rv = copy_type_value (r, len, t);\n";
1671            pr "  free (r);\n"
1672        | RInt32 -> pr "  rv = caml_copy_int32 (r);\n"
1673        | RInt64 -> pr "  rv = caml_copy_int32 (r);\n"
1674       );
1675
1676       pr "  CAMLreturn (rv);\n";
1677       pr "}\n";
1678       pr "\n";
1679
1680   ) functions;
1681
1682   pr "\
1683 static int
1684 HiveOpenFlags_val (value v)
1685 {
1686   int flags = 0;
1687   value v2;
1688
1689   while (v != Val_int (0)) {
1690     v2 = Field (v, 0);
1691     flags |= 1 << Int_val (v2);
1692     v = Field (v, 1);
1693   }
1694
1695   return flags;
1696 }
1697
1698 static hive_set_value *
1699 HiveSetValues_val (value v)
1700 {
1701   size_t nr_values = Wosize_val (v);
1702   hive_set_value *values = malloc (nr_values * sizeof (hive_set_value));
1703   size_t i;
1704   value v2;
1705
1706   for (i = 0; i < nr_values; ++i) {
1707     v2 = Field (v, i);
1708     values[i].key = String_val (Field (v2, 0));
1709     values[i].t = HiveType_val (Field (v2, 1));
1710     values[i].len = caml_string_length (Field (v2, 2));
1711     values[i].value = String_val (Field (v2, 2));
1712   }
1713
1714   return values;
1715 }
1716
1717 static hive_type
1718 HiveType_val (value v)
1719 {
1720   if (Is_long (v))
1721     return Int_val (v); /* REG_NONE etc. */
1722   else
1723     return Int32_val (Field (v, 0)); /* REG_UNKNOWN of int32 */
1724 }
1725
1726 static value
1727 Val_hive_type (hive_type t)
1728 {
1729   CAMLparam0 ();
1730   CAMLlocal2 (rv, v);
1731
1732   if (t <= %d)
1733     CAMLreturn (Val_int (t));
1734   else {
1735     rv = caml_alloc (1, 0); /* REG_UNKNOWN of int32 */
1736     v = caml_copy_int32 (t);
1737     caml_modify (&Field (rv, 0), v);
1738     CAMLreturn (rv);
1739   }
1740 }
1741
1742 static value
1743 copy_int_array (size_t *xs)
1744 {
1745   CAMLparam0 ();
1746   CAMLlocal2 (v, rv);
1747   size_t nr, i;
1748
1749   for (nr = 0; xs[nr] != 0; ++nr)
1750     ;
1751   if (nr == 0)
1752     CAMLreturn (Atom (0));
1753   else {
1754     rv = caml_alloc (nr, 0);
1755     for (i = 0; i < nr; ++i) {
1756       v = Val_int (xs[i]);
1757       Store_field (rv, i, v); /* Safe because v is not a block. */
1758     }
1759     CAMLreturn (rv);
1760   }
1761 }
1762
1763 static value
1764 copy_type_len (size_t len, hive_type t)
1765 {
1766   CAMLparam0 ();
1767   CAMLlocal2 (v, rv);
1768
1769   rv = caml_alloc (2, 0);
1770   v = Val_hive_type (t);
1771   Store_field (rv, 0, v);
1772   v = Val_int (len);
1773   Store_field (rv, 1, len);
1774   CAMLreturn (rv);
1775 }
1776
1777 static value
1778 copy_type_value (const char *r, size_t len, hive_type t)
1779 {
1780   CAMLparam0 ();
1781   CAMLlocal2 (v, rv);
1782
1783   rv = caml_alloc (2, 0);
1784   v = Val_hive_type (t);
1785   Store_field (rv, 0, v);
1786   v = caml_alloc_string (len);
1787   memcpy (String_val (v), r, len);
1788   caml_modify (&Field (rv, 1), len);
1789   CAMLreturn (rv);
1790 }
1791
1792 /* Raise exceptions. */
1793 static void
1794 raise_error (const char *function)
1795 {
1796   /* Save errno early in case it gets trashed. */
1797   int err = errno;
1798
1799   CAMLparam0 ();
1800   CAMLlocal3 (v1, v2, v3);
1801
1802   v1 = caml_copy_string (function);
1803   v2 = unix_error_of_code (err);
1804   v3 = caml_copy_string (strerror (err));
1805   value vvv[] = { v1, v2, v3 };
1806   caml_raise_with_args (*caml_named_value (\"ocaml_hivex_error\"), 3, vvv);
1807
1808   CAMLnoreturn;
1809 }
1810
1811 static void
1812 raise_closed (const char *function)
1813 {
1814   CAMLparam0 ();
1815   CAMLlocal1 (v);
1816
1817   v = caml_copy_string (function);
1818   caml_raise_with_arg (*caml_named_value (\"ocaml_hivex_closed\"), v);
1819
1820   CAMLnoreturn;
1821 }
1822
1823 /* Allocate handles and deal with finalization. */
1824 static void
1825 hivex_finalize (value hv)
1826 {
1827   hive_h *h = Hiveh_val (hv);
1828   if (h) hivex_close (h);
1829 }
1830
1831 static struct custom_operations hivex_custom_operations = {
1832   (char *) \"hivex_custom_operations\",
1833   hivex_finalize,
1834   custom_compare_default,
1835   custom_hash_default,
1836   custom_serialize_default,
1837   custom_deserialize_default
1838 };
1839
1840 static value
1841 Val_hiveh (hive_h *h)
1842 {
1843   CAMLparam0 ();
1844   CAMLlocal1 (rv);
1845
1846   rv = caml_alloc_custom (&hivex_custom_operations,
1847                           sizeof (hive_h *), 0, 1);
1848   Hiveh_val (rv) = h;
1849
1850   CAMLreturn (rv);
1851 }
1852 " max_hive_type
1853
1854 and generate_perl_pm () =
1855   generate_header HashStyle LGPLv2plus
1856
1857 and generate_perl_xs () =
1858   generate_header CStyle LGPLv2plus
1859
1860 and generate_python_py () =
1861   generate_header HashStyle LGPLv2plus
1862
1863 and generate_python_c () =
1864   generate_header CStyle LGPLv2plus
1865
1866 let output_to filename k =
1867   let filename_new = filename ^ ".new" in
1868   chan := open_out filename_new;
1869   k ();
1870   close_out !chan;
1871   chan := Pervasives.stdout;
1872
1873   (* Is the new file different from the current file? *)
1874   if Sys.file_exists filename && files_equal filename filename_new then
1875     unlink filename_new                 (* same, so skip it *)
1876   else (
1877     (* different, overwrite old one *)
1878     (try chmod filename 0o644 with Unix_error _ -> ());
1879     rename filename_new filename;
1880     chmod filename 0o444;
1881     printf "written %s\n%!" filename;
1882   )
1883
1884 let perror msg = function
1885   | Unix_error (err, _, _) ->
1886       eprintf "%s: %s\n" msg (error_message err)
1887   | exn ->
1888       eprintf "%s: %s\n" msg (Printexc.to_string exn)
1889
1890 (* Main program. *)
1891 let () =
1892   let lock_fd =
1893     try openfile "configure.ac" [O_RDWR] 0
1894     with
1895     | Unix_error (ENOENT, _, _) ->
1896         eprintf "\
1897 You are probably running this from the wrong directory.
1898 Run it from the top source directory using the command
1899   generator/generator.ml
1900 ";
1901         exit 1
1902     | exn ->
1903         perror "open: configure.ac" exn;
1904         exit 1 in
1905
1906   (* Acquire a lock so parallel builds won't try to run the generator
1907    * twice at the same time.  Subsequent builds will wait for the first
1908    * one to finish.  Note the lock is released implicitly when the
1909    * program exits.
1910    *)
1911   (try lockf lock_fd F_LOCK 1
1912    with exn ->
1913      perror "lock: configure.ac" exn;
1914      exit 1);
1915
1916   check_functions ();
1917
1918   output_to "lib/hivex.h" generate_c_header;
1919   output_to "lib/hivex.pod" generate_c_pod;
1920
1921   output_to "ocaml/hivex.mli" generate_ocaml_interface;
1922   output_to "ocaml/hivex.ml" generate_ocaml_implementation;
1923   output_to "ocaml/hivex_c.c" generate_ocaml_c;
1924
1925   output_to "perl/lib/Win/Hivex.pm" generate_perl_pm;
1926   output_to "perl/Hivex.xs" generate_perl_xs;
1927
1928   output_to "python/hivex.py" generate_python_py;
1929   output_to "python/hivex-py.c" generate_python_c;
1930
1931   (* Always generate this file last, and unconditionally.  It's used
1932    * by the Makefile to know when we must re-run the generator.
1933    *)
1934   let chan = open_out "generator/stamp-generator" in
1935   fprintf chan "1\n";
1936   close_out chan;
1937
1938   printf "generated %d lines of code\n" !lines