6414ce4acbb04ea92a3339d634764d963f8b2779
[virt-mem.git] / extract / codegen / kerneldb_to_parser.ml
1 (* Memory info for virtual domains.
2    (C) Copyright 2008 Richard W.M. Jones, Red Hat Inc.
3    http://libvirt.org/
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., 675 Mass Ave, Cambridge, MA 02139, USA.
18 *)
19
20 (* This program takes the kernel database (in kernels/ in toplevel
21    directory) and generates parsing code for the various structures
22    in the kernel that we are interested in.
23
24    The output programs -- *.ml, *.mli files of generated code -- go
25    into lib/ at the toplevel, eg. lib/kernel_task_struct.ml
26
27    The stuff at the top of this file determine what structures
28    and fields we try to parse.
29 *)
30
31 let what = [
32   "task_struct", (
33     "struct task_struct {", "};", true,
34     [ "state"; "prio"; "normal_prio"; "static_prio";
35       "tasks'prev"; "tasks'next"; "mm"; "active_mm"; "comm"; "pid" ]
36   );
37 (*
38   "mm_struct", (
39     "struct mm_struct {", "};", true,
40     [ ]
41   );
42 *)
43   "net_device", (
44     "struct net_device {", "};", true,
45     [ "name"; "dev_addr" ]
46   );
47 ]
48
49 let debug = false
50
51 open Camlp4.PreCast
52 open Syntax
53 (*open Ast*)
54
55 open ExtList
56 open ExtString
57 open Printf
58
59 let (//) = Filename.concat
60
61 let () =
62   let args = Array.to_list Sys.argv in
63
64   let kernelsdir, outputdir =
65     match args with
66     | [_;kd;od] -> kd,od
67     | _ ->
68         let arg0 = Filename.basename Sys.executable_name in
69         eprintf "%s - Turn kernels database into code modules.
70
71 Usage:
72   %s <kernelsdir> <outputdir>
73
74 Example (from toplevel of virt-mem source tree):
75   %s kernels/ lib/
76 " arg0 arg0 arg0;
77         exit 2 in
78
79   (* Get the *.info files from the kernels database. *)
80   let infos = Sys.readdir kernelsdir in
81   let infos = Array.to_list infos in
82   let infos = List.filter (fun name -> String.ends_with name ".info") infos in
83   let infos = List.map ((//) kernelsdir) infos in
84
85   (* Regular expressions.  We really really should use ocaml-mikmatch ... *)
86   let re_oldformat = Pcre.regexp "^RPM: \\d+: \\(build \\d+\\) ([-\\w]+) ([\\w.]+) ([\\w.]+) \\(.*?\\) (\\w+)" in
87   let re_keyvalue = Pcre.regexp "^(\\w+): (.*)" in
88
89   (* Parse in the *.info files.  These have historically had a few different
90    * formats that we need to support.
91    *)
92   let infos = List.map (
93     fun filename ->
94       (* Get the basename (for getting the .data file later on). *)
95       let basename = Filename.chop_suffix filename ".info" in
96
97       let chan = open_in filename in
98       let line = input_line chan in
99
100       (* Kernel version string. *)
101       let version, arch =
102         if Pcre.pmatch ~rex:re_oldformat line then (
103           (* If the file starts with "RPM: \d+: ..." then it's the
104            * original Fedora format.  Everything in one line.
105            *)
106           let subs = Pcre.exec ~rex:re_oldformat line in
107           (* let name = Pcre.get_substring subs 1 in *)
108           let version = Pcre.get_substring subs 2 in
109           let release = Pcre.get_substring subs 3 in
110           let arch = Pcre.get_substring subs 4 in
111           close_in chan;
112           (* XXX Map name -> PAE, hugemem etc. *)
113           (* name, *) sprintf "%s-%s.%s" version release arch, arch
114         ) else (
115           (* New-style "key: value" entries, up to end of file or the first
116            * blank line.
117            *)
118           let (*name,*) version, release, arch =
119             (*ref "",*) ref "", ref "", ref "" in
120           let rec loop line =
121             try
122               let subs = Pcre.exec ~rex:re_keyvalue line in
123               let key = Pcre.get_substring subs 1 in
124               let value = Pcre.get_substring subs 2 in
125               (*if key = "Name" then name := value
126               else*) if key = "Version" then version := value
127               else if key = "Release" then release := value
128               else if key = "Architecture" then arch := value;
129               let line = input_line chan in
130               loop line
131             with
132               Not_found | End_of_file ->
133                 close_in chan
134           in
135           loop line;
136           let (*name,*) version, release, arch =
137             (*!name,*) !version, !release, !arch in
138           if (*name = "" ||*) version = "" || release = "" || arch = "" then
139             failwith (sprintf "%s: missing Name, Version, Release or Architecture key" filename);
140           (* XXX Map name -> PAE, hugemem etc. *)
141           (* name, *) sprintf "%s-%s.%s" version release arch, arch
142         ) in
143
144       (*printf "%s -> %s %s\n%!" basename version arch;*)
145
146       (basename, version, arch)
147   ) infos in
148
149   (* For quick access to the opener strings, build a hash. *)
150   let openers = Hashtbl.create 13 in
151   List.iter (
152     fun (name, (opener, closer, _, _)) ->
153       Hashtbl.add openers opener (closer, name)
154   ) what;
155
156   (* Now read the data files and parse out the structures of interest. *)
157   let datas = List.map (
158     fun (basename, version, arch) ->
159       let file_exists name =
160         try Unix.access name [Unix.F_OK]; true
161         with Unix.Unix_error _ -> false
162       in
163       let close_process_in cmd chan =
164         match Unix.close_process_in chan with
165         | Unix.WEXITED 0 -> ()
166         | Unix.WEXITED i ->
167             eprintf "%s: command exited with code %d\n" cmd i; exit i
168         | Unix.WSIGNALED i ->
169             eprintf "%s: command exited with signal %d\n" cmd i; exit 1
170         | Unix.WSTOPPED i ->
171             eprintf "%s: command stopped by signal %d\n" cmd i; exit 1
172       in
173
174       (* Open the data file, uncompressing it on the fly if necessary. *)
175       let chan, close =
176         if file_exists (basename ^ ".data") then
177           open_in (basename ^ ".data"), close_in
178         else if file_exists (basename ^ ".data.gz") then (
179           let cmd =
180             sprintf "gzip -cd %s" (Filename.quote (basename ^ ".data.gz")) in
181           Unix.open_process_in cmd, close_process_in cmd
182         )
183         else if file_exists (basename ^ ".data.bz2") then (
184           let cmd =
185             sprintf "bzip2 -cd %s" (Filename.quote (basename ^ ".data.bz2")) in
186           Unix.open_process_in cmd, close_process_in cmd
187         ) else
188           failwith
189             (sprintf "%s: cannot find corresponding data file" basename) in
190
191       (* Read the data file in, looking for structures of interest to us. *)
192       let bodies = Hashtbl.create 13 in
193       let rec loop () =
194         let line = input_line chan in
195
196         (* If the line is an opener for one of the structures we
197          * are looking for, then for now just save all the text until
198          * we get to the closer line.
199          *)
200         (try
201            let closer, name = Hashtbl.find openers line in
202            let rec loop2 lines =
203              let line = input_line chan in
204              let lines = line :: lines in
205              if String.starts_with line closer then List.rev lines
206              else loop2 lines
207            in
208
209            let body =
210              try loop2 [line]
211              with End_of_file ->
212                failwith (sprintf "%s: %s: %S not matched by closing %S" basename name line closer) in
213
214            Hashtbl.replace bodies name body
215          with Not_found -> ());
216
217         loop ()
218       in
219       (try loop () with End_of_file -> ());
220
221       close chan;
222
223       (* Make sure we got all the mandatory structures. *)
224       List.iter (
225          fun (name, (_, _, mandatory, _)) ->
226            if mandatory && not (Hashtbl.mem bodies name) then
227              failwith (sprintf "%s: structure %s not found in this kernel" basename name)
228       ) what;
229
230       (basename, version, arch, bodies)
231   ) infos in
232
233   (* Now parse each structure body.
234    * XXX This would be better as a proper lex/yacc parser.
235    * XXX Even better would be to have a proper interface to libdwarves.
236    *)
237   let re_offsetsize = Pcre.regexp "/\\*\\s+(\\d+)\\s+(\\d+)\\s+\\*/" in
238   let re_intfield = Pcre.regexp "int\\s+(\\w+);" in
239   let re_ptrfield = Pcre.regexp "struct\\s+(\\w+)\\s*\\*\\s*(\\w+);" in
240   let re_strfield = Pcre.regexp "char\\s+(\\w+)\\[(\\d+)\\];" in
241   let re_structopener = Pcre.regexp "(struct|union)\\s+.*{$" in
242   let re_structcloser = Pcre.regexp "}\\s*(\\w+)?(\\[\\d+\\])?;" in
243
244   (* 'basename' is the source file, and second parameter ('body') is
245    * the list of text lines which covers this structure (minus the
246    * opener line).  Result is the list of parsed fields from this
247    * structure.
248    *)
249   let rec parse basename = function
250     | [] -> assert false
251     | [_] -> []                  (* Just the closer line, finished. *)
252     | line :: lines when Pcre.pmatch ~rex:re_structopener line ->
253       (* Recursively parse a sub-structure.  First search for the
254        * corresponding closer line.
255        *)
256       let rec loop depth acc = function
257         | [] ->
258             eprintf "%s: %S has no matching close structure line\n%!"
259               basename line;
260             assert false
261         | line :: lines when Pcre.pmatch ~rex:re_structopener line ->
262           loop (depth+1) (line :: acc) lines
263         | line :: lines
264             when depth = 0 && Pcre.pmatch ~rex:re_structcloser line ->
265           (line :: acc), lines
266         | line :: lines
267             when depth > 0 && Pcre.pmatch ~rex:re_structcloser line ->
268           loop (depth-1) (line :: acc) lines
269         | line :: lines -> loop depth (line :: acc) lines
270       in
271       let nested_body, rest = loop 0 [] lines in
272
273       (* Then parse the sub-structure. *)
274       let struct_name, nested_body =
275         match nested_body with
276         | [] -> assert false
277         | closer :: _ ->
278             let subs = Pcre.exec ~rex:re_structcloser closer in
279             let struct_name =
280               try Some (Pcre.get_substring subs 1) with Not_found -> None in
281             struct_name, List.rev nested_body in
282       let nested_fields = parse basename nested_body in
283
284       (* Prefix the sub-fields with the name of the structure. *)
285       let nested_fields =
286         match struct_name with
287         | None -> nested_fields
288         | Some prefix ->
289             List.map (
290               fun (name, details) -> (prefix ^ "'" ^ name, details)
291             ) nested_fields in
292
293       (* Parse the rest. *)
294       nested_fields @ parse basename rest
295
296     | line :: lines when Pcre.pmatch ~rex:re_intfield line ->
297       (* An int field. *)
298       let subs = Pcre.exec ~rex:re_intfield line in
299       let name = Pcre.get_substring subs 1 in
300       (try
301          let subs = Pcre.exec ~rex:re_offsetsize line in
302          let offset = int_of_string (Pcre.get_substring subs 1) in
303          let size = int_of_string (Pcre.get_substring subs 2) in
304          (name, (`Int, offset, size)) :: parse basename lines
305        with
306          Not_found -> parse basename lines
307       );
308
309     | line :: lines when Pcre.pmatch ~rex:re_ptrfield line ->
310       (* A pointer-to-struct field. *)
311       let subs = Pcre.exec ~rex:re_ptrfield line in
312       let struct_name = Pcre.get_substring subs 1 in
313       let name = Pcre.get_substring subs 2 in
314       (try
315          let subs = Pcre.exec ~rex:re_offsetsize line in
316          let offset = int_of_string (Pcre.get_substring subs 1) in
317          let size = int_of_string (Pcre.get_substring subs 2) in
318          (name, (`Ptr struct_name, offset, size))
319            :: parse basename lines
320        with
321          Not_found -> parse basename lines
322       );
323
324     | line :: lines when Pcre.pmatch ~rex:re_strfield line ->
325       (* A string (char array) field. *)
326       let subs = Pcre.exec ~rex:re_strfield line in
327       let name = Pcre.get_substring subs 1 in
328       let width = int_of_string (Pcre.get_substring subs 2) in
329       (try
330          let subs = Pcre.exec ~rex:re_offsetsize line in
331          let offset = int_of_string (Pcre.get_substring subs 1) in
332          let size = int_of_string (Pcre.get_substring subs 2) in
333          (name, (`Str width, offset, size))
334            :: parse basename lines
335        with
336          Not_found -> parse basename lines
337       );
338
339     | _ :: lines ->
340         (* Just ignore any other field we can't parse. *)
341         parse basename lines
342
343   in
344
345   let datas = List.map (
346     fun (basename, version, arch, bodies) ->
347       let structures = List.filter_map (
348         fun (struct_name, (_, _, _, wanted_fields)) ->
349           let body =
350             try Some (Hashtbl.find bodies struct_name)
351             with Not_found -> None in
352           match body with
353           | None -> None
354           | Some body ->
355               let body = List.tl body in (* Don't care about opener line. *)
356               let fields = parse basename body in
357
358               (* Compute total size of the structure. *)
359               let total_size =
360                 let fields = List.map (
361                   fun (_, (_, offset, size)) -> offset + size
362                 ) fields in
363                 List.fold_left max 0 fields in
364
365               (* That got us all the fields, but we only care about
366                * the wanted_fields.
367                *)
368               let fields = List.filter (
369                 fun (name, _) -> List.mem name wanted_fields
370               ) fields in
371
372               (* Also check we have all the wanted fields. *)
373               List.iter (
374                 fun wanted_field ->
375                   if not (List.mem_assoc wanted_field fields) then
376                     failwith (sprintf "%s: structure %s is missing required field %s" basename struct_name wanted_field)
377               ) wanted_fields;
378
379               (* Prefix all the field names with the structure name. *)
380               let fields =
381                 List.map (fun (name, details) ->
382                             struct_name ^ "_" ^ name, details) fields in
383
384               Some (struct_name, (fields, total_size))
385       ) what in
386
387       (basename, version, arch, structures)
388   ) datas in
389
390   if debug then
391     List.iter (
392       fun (basename, version, arch, structures) ->
393         printf "%s (version: %s, arch: %s):\n" basename version arch;
394         List.iter (
395           fun (struct_name, (fields, total_size)) ->
396             printf "  struct %s {\n" struct_name;
397             List.iter (
398               fun (field_name, (typ, offset, size)) ->
399                 (match typ with
400                  | `Int ->
401                      printf "    int %s; " field_name
402                  | `Ptr struct_name ->
403                      printf "    struct %s *%s; " struct_name field_name
404                  | `Str width ->
405                      printf "    char %s[%d]; " field_name width
406                 );
407                 printf " /* offset = %d, size = %d */\n" offset size
408             ) fields;
409             printf "  } /* %d bytes */\n\n" total_size;
410         ) structures;
411     ) datas;
412
413   (* We'll generate a code file for each structure type (eg. task_struct
414    * across all kernel versions), so rearrange 'datas' for that purpose.
415    *
416    * XXX This loop is O(n^3), luckily n is small!
417    *)
418   let files =
419     List.map (
420       fun (name, _) ->
421         name,
422         List.filter_map (
423           fun (basename, version, arch, structures) ->
424             try Some (basename, version, arch, List.assoc name structures)
425             with Not_found -> None
426         ) datas
427     ) what in
428
429   let datas = () in ignore datas; (* garbage collect *)
430
431   (* Get just the field types.  It's plausible that a field with the
432    * same name has a different type between kernel versions, so we must
433    * check that didn't happen.
434    *)
435   let files = List.map (
436     fun (struct_name, kernels) ->
437       let field_types =
438         match kernels with
439         | [] -> []
440         | (_, _, _, (fields, _)) :: kernels ->
441             let field_types_of_fields fields =
442               List.sort (
443                 List.map (
444                   fun (field_name, (typ, _, _)) -> field_name, typ
445                 ) fields
446               )
447             in
448             let field_types = field_types_of_fields fields in
449             List.iter (
450               fun (_, _, _, (fields, _)) ->
451                 if field_types <> field_types_of_fields fields then
452                   failwith (sprintf "%s: one of the structure fields changed type between kernel versions" struct_name)
453             ) kernels;
454             field_types in
455       (struct_name, kernels, field_types)
456   ) files in
457
458   (* To minimize generated code size, we want to fold together all
459    * structures where the particulars (eg. offsets, sizes, endianness)
460    * of the fields we care about are the same -- eg. between kernel
461    * versions which are very similar.
462    *)
463   let endian_of_architecture arch =
464     if String.starts_with arch "i386" ||
465       String.starts_with arch "i486" ||
466       String.starts_with arch "i586" ||
467       String.starts_with arch "i686" ||
468       String.starts_with arch "x86_64" ||
469       String.starts_with arch "x86-64" then
470         Bitstring.LittleEndian
471     else if String.starts_with arch "ia64" then
472       Bitstring.LittleEndian (* XXX usually? *)
473     else if String.starts_with arch "ppc" then
474       Bitstring.BigEndian
475     else if String.starts_with arch "sparc" then
476       Bitstring.BigEndian
477     else
478       failwith (sprintf "endian_of_architecture: cannot parse %S" arch)
479   in
480
481   let files =
482     List.map (
483       fun (struct_name, kernels, field_types) ->
484         let hash = Hashtbl.create 13 in
485         let i = ref 0 in
486         let xs = ref [] in
487         let kernels =
488           List.map (
489             fun (basename, version, arch, (fields, total_size)) ->
490               let key = endian_of_architecture arch, fields in
491               let j =
492                 try Hashtbl.find hash key
493                 with Not_found ->
494                   incr i;
495                   xs := (!i, key) :: !xs; Hashtbl.add hash key !i;
496                   !i in
497               (basename, version, arch, total_size, j)
498           ) kernels in
499         struct_name, kernels, field_types, List.rev !xs
500     ) files in
501
502   (* How much did we save by sharing? *)
503   if debug then
504     List.iter (
505       fun (struct_name, kernels, _, parsers) ->
506         printf "struct %s:\n" struct_name;
507         printf "  number of kernel versions: %d\n" (List.length kernels);
508         printf "  number of parser functions needed after sharing: %d\n"
509           (List.length parsers)
510     ) files;
511
512   (* Let's generate some code! *)
513   let files =
514     List.map (
515       fun (struct_name, kernels, field_types, parsers) ->
516         (* Dummy location required - there are no real locations for
517          * output files.
518          *)
519         let _loc = Loc.ghost in
520
521         (* The structure type. *)
522         let struct_type, struct_sig =
523           let fields = List.map (
524             function
525             | (name, `Int) ->
526                 <:ctyp< $lid:name$ : int64 >>
527             | (name, `Ptr _) ->
528                 <:ctyp< $lid:name$ : Virt_mem_mmap.addr >>
529             | (name, `Str _) ->
530                 <:ctyp< $lid:name$ : string >>
531           ) field_types in
532           let f, fs = match fields with
533             | [] -> failwith (sprintf "%s: structure has no fields" struct_name)
534             | f :: fs -> f, fs in
535           let fields = List.fold_left (
536             fun fs f -> <:ctyp< $fs$ ; $f$ >>
537           ) f fs in
538
539           let struct_type = <:str_item< type t = { $fields$ } >> in
540           let struct_sig = <:sig_item< type t = { $fields$ } >> in
541           struct_type, struct_sig in
542
543         (* The shared parser functions.
544          * 
545          * We could include bitmatch statements directly in here, but
546          * what happens is that the macros get expanded here, resulting
547          * in (even more) unreadable generated code.  So instead just
548          * do a textual substitution later by post-processing the
549          * generated files.  Not type-safe, but we can't have
550          * everything.
551          *)
552         let parser_stmts, parser_subs =
553           let parser_stmts = List.map (
554             fun (i, _) ->
555               let fnname = sprintf "parser_%d" i in
556               <:str_item<
557                 let $lid:fnname$ bits = $str:fnname$
558                   >>
559           ) parsers in
560
561           let parser_stmts =
562             match parser_stmts with
563             | [] -> <:str_item< >>
564             | p :: ps ->
565                 List.fold_left (fun ps p -> <:str_item< $ps$ $p$ >>) p ps in
566
567           (* What gets substituted for "parser_NN" ... *)
568           let parser_subs = List.map (
569             fun (i, (endian, fields)) ->
570               let fnname = sprintf "parser_%d" i in
571               let endian =
572                 match endian with
573                 | Bitstring.LittleEndian -> "littleendian"
574                 | Bitstring.BigEndian -> "bigendian"
575                 | _ -> assert false in
576               let patterns =
577                 (* Fields must be sorted by offset, otherwise bitmatch
578                  * will complain.
579                  *)
580                 let cmp (_, (_, o1, _)) (_, (_, o2, _)) = compare o1 o2 in
581                 let fields = List.sort ~cmp fields in
582                 String.concat ";\n    " (
583                   List.map (
584                     function
585                     | (field_name, (`Int, offset, size))
586                     | (field_name, (`Ptr _, offset, size)) ->
587                         (* 'zero+' is a hack to force the type to int64. *)
588                         sprintf "%s : zero+%d : offset(%d), %s"
589                           field_name (size*8) (offset*8) endian
590                     | (field_name, (`Str width, offset, size)) ->
591                         sprintf "%s : %d : offset(%d), string"
592                           field_name (width*8) (offset*8)
593                   ) fields
594                 ) in
595               let assignments =
596                 String.concat ";\n    " (
597                   List.map (
598                     function
599                     | (field_name, (`Ptr "list_head", offset, size)) ->
600                         sprintf "%s = Int64.sub %s %dL" field_name field_name offset
601                     | (field_name, _) ->
602                         sprintf "%s = %s" field_name field_name
603                   ) fields
604                 ) in
605
606               let sub =
607                 sprintf "\
608   bitmatch bits with
609   | { %s } -> { %s }
610   | { _ } -> raise (ParseError (%S, %S, \"failed to match kernel structure\"))"
611                   patterns assignments struct_name fnname in
612
613               fnname, sub
614           ) parsers in
615
616           parser_stmts, parser_subs in
617
618         (* Define a map from kernel versions to parsing functions. *)
619         let version_map =
620           let stmts = List.fold_left (
621             fun stmts (_, version, arch, total_size, i) ->
622               let parserfn = sprintf "parser_%d" i in
623               <:str_item<
624                 $stmts$
625                 let v = ($lid:parserfn$, $`int:total_size$)
626                 let map = StringMap.add $str:version$ v map
627               >>
628           ) <:str_item< let map = StringMap.empty >> kernels in
629
630           <:str_item<
631             module StringMap = Map.Make (String)
632             $stmts$
633           >> in
634
635         (* Code (.ml file). *)
636         let code = <:str_item<
637           let warning = "This code is automatically generated from the kernel database by kerneldb-to-parser program.  Any edits you make will be lost."
638           let zero = 0
639           exception ParseError of string * string * string;;
640           $struct_type$
641           $parser_stmts$
642           $version_map$
643
644           type kernel_version = string
645           let $lid:struct_name^"_known"$ version = StringMap.mem version map
646           let $lid:struct_name^"_size"$ version =
647             let _, size = StringMap.find version map in
648             size
649           let $lid:struct_name^"_of_bits"$ version bits =
650             let parsefn, _ = StringMap.find version map in
651             parsefn bits
652           let $lid:"get_"^struct_name$ version mem addr =
653             let parsefn, size = StringMap.find version map in
654             let bytes = Virt_mem_mmap.get_bytes mem addr size in
655             let bits = Bitstring.bitstring_of_string bytes in
656             parsefn bits
657         >> in
658
659         (* Interface (.mli file). *)
660         let interface = <:sig_item<
661           exception ParseError of string * string * string;;
662           $struct_sig$
663
664           type kernel_version = string
665           val $lid:struct_name^"_known"$ : kernel_version -> bool
666           val $lid:struct_name^"_size"$ : kernel_version -> int
667           val $lid:struct_name^"_of_bits"$ :
668             kernel_version -> Bitstring.bitstring -> t
669           val $lid:"get_"^struct_name$ : kernel_version ->
670             ('a, 'b, [`HasMapping]) Virt_mem_mmap.t -> Virt_mem_mmap.addr -> t
671         >> in
672
673         (struct_name, code, interface, parser_subs)
674     ) files in
675
676   (* Finally generate the output files. *)
677   let re_subst = Pcre.regexp "^(.*)\"(parser_\\d+)\"(.*)$" in
678
679   List.iter (
680     fun (struct_name, code, interface, parser_subs) ->
681       (* Interface (.mli file). *)
682       let output_file = outputdir // "kernel_" ^ struct_name ^ ".mli" in
683       printf "Writing %s interface to %s ...\n%!" struct_name output_file;
684       Printers.OCaml.print_interf ~output_file interface;
685
686       (* Implementation (.ml file). *)
687       let output_file = outputdir // "kernel_" ^ struct_name ^ ".ml" in
688       printf "Writing %s implementation to %s ...\n%!" struct_name output_file;
689
690       let new_output_file = output_file ^ ".new" in
691       Printers.OCaml.print_implem ~output_file:new_output_file code;
692
693       (* Substitute the parser bodies in the output file. *)
694       let ichan = open_in new_output_file in
695       let ochan = open_out output_file in
696
697       let rec loop () =
698         let line = input_line ichan in
699         let line =
700           if Pcre.pmatch ~rex:re_subst line then (
701             let subs = Pcre.exec ~rex:re_subst line in
702             let start = Pcre.get_substring subs 1 in
703             let template = Pcre.get_substring subs 2 in
704             let rest = Pcre.get_substring subs 3 in
705             let sub = List.assoc template parser_subs in
706             start ^ sub ^ rest
707           ) else line in
708         output_string ochan line; output_char ochan '\n';
709         loop ()
710       in
711       (try loop () with End_of_file -> ());
712
713       close_out ochan;
714       close_in ichan;
715
716       Unix.unlink new_output_file
717   ) files