53e4fd5639c3cc30481a5d42af9d7c81d7e198e1
[libguestfs.git] / generator / generator_fish.ml
1 (* libguestfs
2  * Copyright (C) 2009-2010 Red Hat Inc.
3  *
4  * This program is free software; you can redistribute it and/or modify
5  * it under the terms of the GNU General Public License as published by
6  * the Free Software Foundation; either version 2 of the License, or
7  * (at your option) any later version.
8  *
9  * This program is distributed in the hope that it will be useful,
10  * but WITHOUT ANY WARRANTY; without even the implied warranty of
11  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
12  * GNU General Public License for more details.
13  *
14  * You should have received a copy of the GNU General Public License
15  * along with this program; if not, write to the Free Software
16  * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
17  *)
18
19 (* Please read generator/README first. *)
20
21 open Printf
22
23 open Generator_types
24 open Generator_utils
25 open Generator_pr
26 open Generator_docstrings
27 open Generator_optgroups
28 open Generator_actions
29 open Generator_structs
30 open Generator_prepopts
31 open Generator_c
32 open Generator_events
33
34 let doc_opttype_of = function
35   | Bool n -> "true|false"
36   | Int n
37   | Int64 n -> "N"
38   | String n -> ".."
39   | _ -> assert false
40
41 (* Generate a lot of different functions for guestfish. *)
42 let generate_fish_cmds () =
43   generate_header CStyle GPLv2plus;
44
45   let all_functions =
46     List.filter (
47       fun (_, _, _, flags, _, _, _) -> not (List.mem NotInFish flags)
48     ) all_functions in
49   let all_functions_sorted =
50     List.filter (
51       fun (_, _, _, flags, _, _, _) -> not (List.mem NotInFish flags)
52     ) all_functions_sorted in
53
54   let all_functions_and_fish_commands_sorted =
55     List.sort action_compare (all_functions_sorted @ fish_commands) in
56
57   pr "#include <config.h>\n";
58   pr "\n";
59   pr "/* It is safe to call deprecated functions from this file. */\n";
60   pr "#undef GUESTFS_WARN_DEPRECATED\n";
61   pr "\n";
62   pr "#include <stdio.h>\n";
63   pr "#include <stdlib.h>\n";
64   pr "#include <string.h>\n";
65   pr "#include <inttypes.h>\n";
66   pr "\n";
67   pr "#include \"c-ctype.h\"\n";
68   pr "#include \"full-write.h\"\n";
69   pr "#include \"xstrtol.h\"\n";
70   pr "\n";
71   pr "#include <guestfs.h>\n";
72   pr "#include \"fish.h\"\n";
73   pr "#include \"fish-cmds.h\"\n";
74   pr "#include \"options.h\"\n";
75   pr "#include \"cmds_gperf.h\"\n";
76   pr "\n";
77   pr "/* Valid suffixes allowed for numbers.  See Gnulib xstrtol function. */\n";
78   pr "static const char *xstrtol_suffixes = \"0kKMGTPEZY\";\n";
79   pr "\n";
80
81   List.iter (
82     fun (name, _, _, _, _, _, _) ->
83       pr "static int run_%s (const char *cmd, size_t argc, char *argv[]);\n"
84         name
85   ) all_functions;
86
87   pr "\n";
88
89   (* List of command_entry structs. *)
90   List.iter (
91     fun (name, _, _, flags, _, shortdesc, longdesc) ->
92       let name2 = replace_char name '_' '-' in
93       let aliases =
94         filter_map (function FishAlias n -> Some n | _ -> None) flags in
95       let describe_alias =
96         if aliases <> [] then
97           sprintf "\n\nYou can use %s as an alias for this command."
98             (String.concat " or " (List.map (fun s -> "'" ^ s ^ "'") aliases))
99         else "" in
100
101       let pod =
102         sprintf "%s - %s\n\n=head1 DESCRIPTION\n\n%s\n\n%s"
103           name2 shortdesc longdesc describe_alias in
104       let text =
105         String.concat "\n" (pod2text ~trim:false ~discard:false "NAME" pod)
106         ^ "\n" in
107
108       pr "struct command_entry %s_cmd_entry = {\n" name;
109       pr "  .name = \"%s\",\n" name2;
110       pr "  .help = \"%s\",\n" (c_quote text);
111       pr "  .run = run_%s\n" name;
112       pr "};\n";
113       pr "\n";
114   ) fish_commands;
115
116   List.iter (
117     fun (name, (_, args, optargs), _, flags, _, shortdesc, longdesc) ->
118       let name2 = replace_char name '_' '-' in
119       let aliases =
120         filter_map (function FishAlias n -> Some n | _ -> None) flags in
121
122       let longdesc = replace_str longdesc "C<guestfs_" "C<" in
123       let synopsis =
124         match args with
125         | [] -> name2
126         | args ->
127             let args = List.filter (function Key _ -> false | _ -> true) args in
128             sprintf "%s%s%s"
129               name2
130               (String.concat ""
131                  (List.map (fun arg -> " " ^ name_of_argt arg) args))
132               (String.concat ""
133                  (List.map (fun arg ->
134                    sprintf " [%s:%s]" (name_of_argt arg) (doc_opttype_of arg)
135                   ) optargs)) in
136
137       let warnings =
138         if List.exists (function Key _ -> true | _ -> false) args then
139           "\n\nThis command has one or more key or passphrase parameters.
140 Guestfish will prompt for these separately."
141         else "" in
142
143       let warnings =
144         warnings ^
145           if List.mem ProtocolLimitWarning flags then
146             ("\n\n" ^ protocol_limit_warning)
147           else "" in
148
149       let warnings =
150         warnings ^
151           match deprecation_notice flags with
152           | None -> ""
153           | Some txt -> "\n\n" ^ txt in
154
155       let describe_alias =
156         if aliases <> [] then
157           sprintf "\n\nYou can use %s as an alias for this command."
158             (String.concat " or " (List.map (fun s -> "'" ^ s ^ "'") aliases))
159         else "" in
160
161       let pod =
162         sprintf "%s - %s\n\n=head1 SYNOPSIS\n\n %s\n\n=head1 DESCRIPTION\n\n%s%s%s"
163           name2 shortdesc synopsis longdesc warnings describe_alias in
164       let text =
165         String.concat "\n" (pod2text ~trim:false ~discard:false "NAME" pod)
166         ^ "\n" in
167
168       pr "struct command_entry %s_cmd_entry = {\n" name;
169       pr "  .name = \"%s\",\n" name2;
170       pr "  .help = \"%s\",\n" (c_quote text);
171       pr "  .run = run_%s\n" name;
172       pr "};\n";
173       pr "\n";
174   ) all_functions;
175
176   (* list_commands function, which implements guestfish -h *)
177   pr "void\n";
178   pr "list_commands (void)\n";
179   pr "{\n";
180   pr "  printf (\"    %%-16s     %%s\\n\", _(\"Command\"), _(\"Description\"));\n";
181   pr "  list_builtin_commands ();\n";
182   List.iter (
183     fun (name, _, _, flags, _, shortdesc, _) ->
184       let name = replace_char name '_' '-' in
185       pr "  printf (\"%%-20s %%s\\n\", \"%s\", _(\"%s\"));\n"
186         name shortdesc
187   ) all_functions_and_fish_commands_sorted;
188   pr "  printf (\"    %%s\\n\",";
189   pr "          _(\"Use -h <cmd> / help <cmd> to show detailed help for a command.\"));\n";
190   pr "}\n";
191   pr "\n";
192
193   (* display_command function, which implements guestfish -h cmd *)
194   pr "int\n";
195   pr "display_command (const char *cmd)\n";
196   pr "{\n";
197   pr "  const struct command_table *ct;\n";
198   pr "\n";
199   pr "  ct = lookup_fish_command (cmd, strlen (cmd));\n";
200   pr "  if (ct) {\n";
201   pr "    fputs (ct->entry->help, stdout);\n";
202   pr "    return 0;\n";
203   pr "  }\n";
204   pr "  else\n";
205   pr "    return display_builtin_command (cmd);\n";
206   pr "}\n";
207   pr "\n";
208
209   let emit_print_list_function typ =
210     pr "static void\n";
211     pr "print_%s_list (struct guestfs_%s_list *%ss)\n"
212       typ typ typ;
213     pr "{\n";
214     pr "  unsigned int i;\n";
215     pr "\n";
216     pr "  for (i = 0; i < %ss->len; ++i) {\n" typ;
217     pr "    printf (\"[%%d] = {\\n\", i);\n";
218     pr "    print_%s_indent (&%ss->val[i], \"  \");\n" typ typ;
219     pr "    printf (\"}\\n\");\n";
220     pr "  }\n";
221     pr "}\n";
222     pr "\n";
223   in
224
225   (* print_* functions *)
226   List.iter (
227     fun (typ, cols) ->
228       let needs_i =
229         List.exists (function (_, (FUUID|FBuffer)) -> true | _ -> false) cols in
230
231       pr "static void\n";
232       pr "print_%s_indent (struct guestfs_%s *%s, const char *indent)\n" typ typ typ;
233       pr "{\n";
234       if needs_i then (
235         pr "  unsigned int i;\n";
236         pr "\n"
237       );
238       List.iter (
239         function
240         | name, FString ->
241             pr "  printf (\"%%s%s: %%s\\n\", indent, %s->%s);\n" name typ name
242         | name, FUUID ->
243             pr "  printf (\"%%s%s: \", indent);\n" name;
244             pr "  for (i = 0; i < 32; ++i)\n";
245             pr "    printf (\"%%c\", %s->%s[i]);\n" typ name;
246             pr "  printf (\"\\n\");\n"
247         | name, FBuffer ->
248             pr "  printf (\"%%s%s: \", indent);\n" name;
249             pr "  for (i = 0; i < %s->%s_len; ++i)\n" typ name;
250             pr "    if (c_isprint (%s->%s[i]))\n" typ name;
251             pr "      printf (\"%%c\", %s->%s[i]);\n" typ name;
252             pr "    else\n";
253             pr "      printf (\"\\\\x%%02x\", %s->%s[i]);\n" typ name;
254             pr "  printf (\"\\n\");\n"
255         | name, (FUInt64|FBytes) ->
256             pr "  printf (\"%%s%s: %%\" PRIu64 \"\\n\", indent, %s->%s);\n"
257               name typ name
258         | name, FInt64 ->
259             pr "  printf (\"%%s%s: %%\" PRIi64 \"\\n\", indent, %s->%s);\n"
260               name typ name
261         | name, FUInt32 ->
262             pr "  printf (\"%%s%s: %%\" PRIu32 \"\\n\", indent, %s->%s);\n"
263               name typ name
264         | name, FInt32 ->
265             pr "  printf (\"%%s%s: %%\" PRIi32 \"\\n\", indent, %s->%s);\n"
266               name typ name
267         | name, FChar ->
268             pr "  printf (\"%%s%s: %%c\\n\", indent, %s->%s);\n"
269               name typ name
270         | name, FOptPercent ->
271             pr "  if (%s->%s >= 0)\n" typ name;
272             pr "    printf (\"%%s%s: %%g %%%%\\n\", indent, (double) %s->%s);\n"
273               name typ name;
274             pr "  else\n";
275             pr "    printf (\"%%s%s: \\n\", indent);\n" name
276       ) cols;
277       pr "}\n";
278       pr "\n";
279   ) structs;
280
281   (* Emit a print_TYPE_list function definition only if that function is used. *)
282   List.iter (
283     function
284     | typ, (RStructListOnly | RStructAndList) ->
285         (* generate the function for typ *)
286         emit_print_list_function typ
287     | typ, _ -> () (* empty *)
288   ) (rstructs_used_by all_functions);
289
290   (* Emit a print_TYPE function definition only if that function is used. *)
291   List.iter (
292     function
293     | typ, (RStructOnly | RStructAndList) ->
294         pr "static void\n";
295         pr "print_%s (struct guestfs_%s *%s)\n" typ typ typ;
296         pr "{\n";
297         pr "  print_%s_indent (%s, \"\");\n" typ typ;
298         pr "}\n";
299         pr "\n";
300     | typ, _ -> () (* empty *)
301   ) (rstructs_used_by all_functions);
302
303   (* run_<action> actions *)
304   List.iter (
305     fun (name, (ret, args, optargs as style), _, flags, _, _, _) ->
306       pr "static int\n";
307       pr "run_%s (const char *cmd, size_t argc, char *argv[])\n" name;
308       pr "{\n";
309       (match ret with
310        | RErr
311        | RInt _
312        | RBool _ -> pr "  int r;\n"
313        | RInt64 _ -> pr "  int64_t r;\n"
314        | RConstString _ | RConstOptString _ -> pr "  const char *r;\n"
315        | RString _ -> pr "  char *r;\n"
316        | RStringList _ | RHashtable _ -> pr "  char **r;\n"
317        | RStruct (_, typ) -> pr "  struct guestfs_%s *r;\n" typ
318        | RStructList (_, typ) -> pr "  struct guestfs_%s_list *r;\n" typ
319        | RBufferOut _ ->
320            pr "  char *r;\n";
321            pr "  size_t size;\n";
322       );
323       List.iter (
324         function
325         | Device n
326         | String n
327         | OptString n -> pr "  const char *%s;\n" n
328         | Pathname n
329         | Dev_or_Path n
330         | FileIn n
331         | FileOut n
332         | Key n -> pr "  char *%s;\n" n
333         | BufferIn n ->
334             pr "  const char *%s;\n" n;
335             pr "  size_t %s_size;\n" n
336         | StringList n | DeviceList n -> pr "  char **%s;\n" n
337         | Bool n -> pr "  int %s;\n" n
338         | Int n -> pr "  int %s;\n" n
339         | Int64 n -> pr "  int64_t %s;\n" n
340         | Pointer _ -> assert false
341       ) args;
342
343       if optargs <> [] then (
344         pr "  struct guestfs_%s_argv optargs_s = { .bitmask = 0 };\n" name;
345         pr "  struct guestfs_%s_argv *optargs = &optargs_s;\n" name
346       );
347
348       if args <> [] || optargs <> [] then
349         pr "  size_t i = 0;\n";
350
351       pr "\n";
352
353       (* Check and convert parameters. *)
354       let argc_minimum, argc_maximum =
355         let args_no_keys =
356           List.filter (function Key _ -> false | _ -> true) args in
357         let argc_minimum = List.length args_no_keys in
358         let argc_maximum = argc_minimum + List.length optargs in
359         argc_minimum, argc_maximum in
360
361       if argc_minimum = argc_maximum then (
362         pr "  if (argc != %d) {\n" argc_minimum;
363         pr "    fprintf (stderr, _(\"%%s should have %%d parameter(s)\\n\"), cmd, %d);\n"
364           argc_minimum;
365       ) else (
366         pr "  if (argc < %d || argc > %d) {\n" argc_minimum argc_maximum;
367         pr "    fprintf (stderr, _(\"%%s should have %%d-%%d parameter(s)\\n\"), cmd, %d, %d);\n"
368           argc_minimum argc_maximum;
369       );
370       pr "    fprintf (stderr, _(\"type 'help %%s' for help on %%s\\n\"), cmd, cmd);\n";
371       pr "    return -1;\n";
372       pr "  }\n";
373
374       let parse_integer expr fn fntyp rtyp range name =
375         pr "  {\n";
376         pr "    strtol_error xerr;\n";
377         pr "    %s r;\n" fntyp;
378         pr "\n";
379         pr "    xerr = %s (%s, NULL, 0, &r, xstrtol_suffixes);\n" fn expr;
380         pr "    if (xerr != LONGINT_OK) {\n";
381         pr "      fprintf (stderr,\n";
382         pr "               _(\"%%s: %%s: invalid integer parameter (%%s returned %%d)\\n\"),\n";
383         pr "               cmd, \"%s\", \"%s\", xerr);\n" name fn;
384         pr "      return -1;\n";
385         pr "    }\n";
386         (match range with
387          | None -> ()
388          | Some (min, max, comment) ->
389              pr "    /* %s */\n" comment;
390              pr "    if (r < %s || r > %s) {\n" min max;
391              pr "      fprintf (stderr, _(\"%%s: %%s: integer out of range\\n\"), cmd, \"%s\");\n"
392                name;
393              pr "      return -1;\n";
394              pr "    }\n";
395              pr "    /* The check above should ensure this assignment does not overflow. */\n";
396         );
397         pr "    %s = r;\n" name;
398         pr "  }\n";
399       in
400
401       List.iter (
402         function
403         | Device name
404         | String name ->
405             pr "  %s = argv[i++];\n" name
406         | Pathname name
407         | Dev_or_Path name ->
408             pr "  %s = win_prefix (argv[i++]); /* process \"win:\" prefix */\n" name;
409             pr "  if (%s == NULL) return -1;\n" name
410         | OptString name ->
411             pr "  %s = STRNEQ (argv[i], \"\") ? argv[i] : NULL;\n" name;
412             pr "  i++;\n"
413         | BufferIn name ->
414             pr "  %s = argv[i];\n" name;
415             pr "  %s_size = strlen (argv[i]);\n" name;
416             pr "  i++;\n"
417         | FileIn name ->
418             pr "  %s = file_in (argv[i++]);\n" name;
419             pr "  if (%s == NULL) return -1;\n" name
420         | FileOut name ->
421             pr "  %s = file_out (argv[i++]);\n" name;
422             pr "  if (%s == NULL) return -1;\n" name
423         | StringList name | DeviceList name ->
424             pr "  %s = parse_string_list (argv[i++]);\n" name;
425             pr "  if (%s == NULL) return -1;\n" name
426         | Key name ->
427             pr "  %s = read_key (\"%s\");\n" name name;
428             pr "  if (keys_from_stdin)\n";
429             pr "    input_lineno++;\n";
430             pr "  if (%s == NULL) return -1;\n" name
431         | Bool name ->
432             pr "  %s = is_true (argv[i++]) ? 1 : 0;\n" name
433         | Int name ->
434             let range =
435               let min = "(-(2LL<<30))"
436               and max = "((2LL<<30)-1)"
437               and comment =
438                 "The Int type in the generator is a signed 31 bit int." in
439               Some (min, max, comment) in
440             parse_integer "argv[i++]" "xstrtoll" "long long" "int" range name
441         | Int64 name ->
442             parse_integer "argv[i++]" "xstrtoll" "long long" "int64_t" None name
443         | Pointer _ -> assert false
444       ) args;
445
446       (* Optional arguments are prefixed with <argname>:<value> and
447        * may be missing, so we need to parse those until the end of
448        * the argument list.
449        *)
450       if optargs <> [] then (
451         let uc_name = String.uppercase name in
452         pr "\n";
453         pr "  for (; i < argc; ++i) {\n";
454         pr "    uint64_t this_mask;\n";
455         pr "    const char *this_arg;\n";
456         pr "\n";
457         pr "    ";
458         List.iter (
459           fun argt ->
460             let n = name_of_argt argt in
461             let uc_n = String.uppercase n in
462             let len = String.length n in
463             pr "if (STRPREFIX (argv[i], \"%s:\")) {\n" n;
464             (match argt with
465              | Bool n ->
466                  pr "      optargs_s.%s = is_true (&argv[i][%d]) ? 1 : 0;\n"
467                    n (len+1);
468              | Int n ->
469                  let range =
470                    let min = "(-(2LL<<30))"
471                    and max = "((2LL<<30)-1)"
472                    and comment =
473                      "The Int type in the generator is a signed 31 bit int." in
474                    Some (min, max, comment) in
475                  let expr = sprintf "&argv[i][%d]" (len+1) in
476                  parse_integer expr "xstrtoll" "long long" "int" range
477                    (sprintf "optargs_s.%s" n)
478              | Int64 n ->
479                  let expr = sprintf "&argv[i][%d]" (len+1) in
480                  parse_integer expr "xstrtoll" "long long" "int64_t" None
481                    (sprintf "optargs_s.%s" n)
482              | String n ->
483                  pr "      optargs_s.%s = &argv[i][%d];\n" n (len+1);
484              | _ -> assert false
485             );
486             pr "      this_mask = GUESTFS_%s_%s_BITMASK;\n" uc_name uc_n;
487             pr "      this_arg = \"%s\";\n" n;
488             pr "    }\n";
489             pr "    else ";
490         ) optargs;
491
492         pr "{\n";
493         pr "      fprintf (stderr, _(\"%%s: unknown optional argument \\\"%%s\\\"\\n\"),\n";
494         pr "               cmd, argv[i]);\n";
495         pr "      return -1;\n";
496         pr "    }\n";
497         pr "\n";
498         pr "    if (optargs_s.bitmask & this_mask) {\n";
499         pr "      fprintf (stderr, _(\"%%s: optional argument \\\"%%s\\\" given twice\\n\"),\n";
500         pr "               cmd, this_arg);\n";
501         pr "      return -1;\n";
502         pr "    }\n";
503         pr "    optargs_s.bitmask |= this_mask;\n";
504         pr "  }\n";
505         pr "\n";
506       );
507
508       (* Call C API function. *)
509       if optargs = [] then
510         pr "  r = guestfs_%s " name
511       else
512         pr "  r = guestfs_%s_argv " name;
513       generate_c_call_args ~handle:"g" style;
514       pr ";\n";
515
516       List.iter (
517         function
518         | Device _ | String _
519         | OptString _ | Bool _
520         | Int _ | Int64 _
521         | BufferIn _ -> ()
522         | Pathname name | Dev_or_Path name | FileOut name
523         | Key name ->
524             pr "  free (%s);\n" name
525         | FileIn name ->
526             pr "  free_file_in (%s);\n" name
527         | StringList name | DeviceList name ->
528             pr "  free_strings (%s);\n" name
529         | Pointer _ -> assert false
530       ) args;
531
532       (* Any output flags? *)
533       let fish_output =
534         let flags = filter_map (
535           function FishOutput flag -> Some flag | _ -> None
536         ) flags in
537         match flags with
538         | [] -> None
539         | [f] -> Some f
540         | _ ->
541             failwithf "%s: more than one FishOutput flag is not allowed" name in
542
543       (* Check return value for errors and display command results. *)
544       (match ret with
545        | RErr -> pr "  return r;\n"
546        | RInt _ ->
547            pr "  if (r == -1) return -1;\n";
548            (match fish_output with
549             | None ->
550                 pr "  printf (\"%%d\\n\", r);\n";
551             | Some FishOutputOctal ->
552                 pr "  printf (\"%%s%%o\\n\", r != 0 ? \"0\" : \"\", r);\n";
553             | Some FishOutputHexadecimal ->
554                 pr "  printf (\"%%s%%x\\n\", r != 0 ? \"0x\" : \"\", r);\n");
555            pr "  return 0;\n"
556        | RInt64 _ ->
557            pr "  if (r == -1) return -1;\n";
558            (match fish_output with
559             | None ->
560                 pr "  printf (\"%%\" PRIi64 \"\\n\", r);\n";
561             | Some FishOutputOctal ->
562                 pr "  printf (\"%%s%%\" PRIo64 \"\\n\", r != 0 ? \"0\" : \"\", r);\n";
563             | Some FishOutputHexadecimal ->
564                 pr "  printf (\"%%s%%\" PRIx64 \"\\n\", r != 0 ? \"0x\" : \"\", r);\n");
565            pr "  return 0;\n"
566        | RBool _ ->
567            pr "  if (r == -1) return -1;\n";
568            pr "  if (r) printf (\"true\\n\"); else printf (\"false\\n\");\n";
569            pr "  return 0;\n"
570        | RConstString _ ->
571            pr "  if (r == NULL) return -1;\n";
572            pr "  printf (\"%%s\\n\", r);\n";
573            pr "  return 0;\n"
574        | RConstOptString _ ->
575            pr "  printf (\"%%s\\n\", r ? : \"(null)\");\n";
576            pr "  return 0;\n"
577        | RString _ ->
578            pr "  if (r == NULL) return -1;\n";
579            pr "  printf (\"%%s\\n\", r);\n";
580            pr "  free (r);\n";
581            pr "  return 0;\n"
582        | RStringList _ ->
583            pr "  if (r == NULL) return -1;\n";
584            pr "  print_strings (r);\n";
585            pr "  free_strings (r);\n";
586            pr "  return 0;\n"
587        | RStruct (_, typ) ->
588            pr "  if (r == NULL) return -1;\n";
589            pr "  print_%s (r);\n" typ;
590            pr "  guestfs_free_%s (r);\n" typ;
591            pr "  return 0;\n"
592        | RStructList (_, typ) ->
593            pr "  if (r == NULL) return -1;\n";
594            pr "  print_%s_list (r);\n" typ;
595            pr "  guestfs_free_%s_list (r);\n" typ;
596            pr "  return 0;\n"
597        | RHashtable _ ->
598            pr "  if (r == NULL) return -1;\n";
599            pr "  print_table (r);\n";
600            pr "  free_strings (r);\n";
601            pr "  return 0;\n"
602        | RBufferOut _ ->
603            pr "  if (r == NULL) return -1;\n";
604            pr "  if (full_write (1, r, size) != size) {\n";
605            pr "    perror (\"write\");\n";
606            pr "    free (r);\n";
607            pr "    return -1;\n";
608            pr "  }\n";
609            pr "  free (r);\n";
610            pr "  return 0;\n"
611       );
612       pr "}\n";
613       pr "\n"
614   ) all_functions;
615
616   (* run_action function *)
617   pr "int\n";
618   pr "run_action (const char *cmd, size_t argc, char *argv[])\n";
619   pr "{\n";
620   pr "  const struct command_table *ct;\n";
621   pr "\n";
622   pr "  ct = lookup_fish_command (cmd, strlen (cmd));\n";
623   pr "  if (ct)\n";
624   pr "    return ct->entry->run (cmd, argc, argv);\n";
625   pr "  else {\n";
626   pr "    fprintf (stderr, _(\"%%s: unknown command\\n\"), cmd);\n";
627   pr "    if (command_num == 1)\n";
628   pr "      extended_help_message ();\n";
629   pr "    return -1;\n";
630   pr "  }\n";
631   pr "}\n"
632
633 and generate_fish_cmds_h () =
634   generate_header CStyle GPLv2plus;
635
636   pr "#ifndef FISH_CMDS_H\n";
637   pr "#define FISH_CMDS_H\n";
638   pr "\n";
639
640   List.iter (
641     fun (shortname, _, _, _, _, _, _) ->
642       pr "extern int run_%s (const char *cmd, size_t argc, char *argv[]);\n"
643         shortname
644   ) fish_commands;
645
646   pr "\n";
647   pr "#endif /* FISH_CMDS_H */\n"
648
649 (* gperf code to do fast lookups of commands. *)
650 and generate_fish_cmds_gperf () =
651   generate_header CStyle GPLv2plus;
652
653   let all_functions_sorted =
654     List.filter (
655       fun (_, _, _, flags, _, _, _) -> not (List.mem NotInFish flags)
656     ) all_functions_sorted in
657
658   let all_functions_and_fish_commands_sorted =
659     List.sort action_compare (all_functions_sorted @ fish_commands) in
660
661   pr "\
662 %%language=ANSI-C
663 %%define lookup-function-name lookup_fish_command
664 %%ignore-case
665 %%readonly-tables
666 %%null-strings
667
668 %%{
669
670 #include <config.h>
671
672 #include <stdlib.h>
673 #include <string.h>
674
675 #include \"cmds_gperf.h\"
676
677 ";
678
679   List.iter (
680     fun (name, _, _, _, _, _, _) ->
681       pr "extern struct command_entry %s_cmd_entry;\n" name
682   ) all_functions_and_fish_commands_sorted;
683
684   pr "\
685 %%}
686
687 struct command_table;
688
689 %%%%
690 ";
691
692   List.iter (
693     fun (name, _, _, flags, _, _, _) ->
694       let name2 = replace_char name '_' '-' in
695       let aliases =
696         filter_map (function FishAlias n -> Some n | _ -> None) flags in
697
698       (* The basic command. *)
699       pr "%s, &%s_cmd_entry\n" name name;
700
701       (* Command with dashes instead of underscores. *)
702       if name <> name2 then
703         pr "%s, &%s_cmd_entry\n" name2 name;
704
705       (* Aliases for the command. *)
706       List.iter (
707         fun alias ->
708           pr "%s, &%s_cmd_entry\n" alias name;
709       ) aliases;
710   ) all_functions_and_fish_commands_sorted
711
712 (* Readline completion for guestfish. *)
713 and generate_fish_completion () =
714   generate_header CStyle GPLv2plus;
715
716   let all_functions =
717     List.filter (
718       fun (_, _, _, flags, _, _, _) -> not (List.mem NotInFish flags)
719     ) all_functions in
720
721   pr "\
722 #include <config.h>
723
724 #include <stdio.h>
725 #include <stdlib.h>
726 #include <string.h>
727
728 #ifdef HAVE_LIBREADLINE
729 #include <readline/readline.h>
730 #endif
731
732 #include \"fish.h\"
733
734 #ifdef HAVE_LIBREADLINE
735
736 static const char *const commands[] = {
737   BUILTIN_COMMANDS_FOR_COMPLETION,
738 ";
739
740   (* Get the commands, including the aliases.  They don't need to be
741    * sorted - the generator() function just does a dumb linear search.
742    *)
743   let commands =
744     List.map (
745       fun (name, _, _, flags, _, _, _) ->
746         let name2 = replace_char name '_' '-' in
747         let aliases =
748           filter_map (function FishAlias n -> Some n | _ -> None) flags in
749         name2 :: aliases
750     ) (all_functions @ fish_commands) in
751   let commands = List.flatten commands in
752
753   List.iter (pr "  \"%s\",\n") commands;
754
755   pr "  NULL
756 };
757
758 static char *
759 generator (const char *text, int state)
760 {
761   static size_t index, len;
762   const char *name;
763
764   if (!state) {
765     index = 0;
766     len = strlen (text);
767   }
768
769   rl_attempted_completion_over = 1;
770
771   while ((name = commands[index]) != NULL) {
772     index++;
773     if (STRCASEEQLEN (name, text, len))
774       return strdup (name);
775   }
776
777   return NULL;
778 }
779
780 #endif /* HAVE_LIBREADLINE */
781
782 #ifdef HAVE_RL_COMPLETION_MATCHES
783 #define RL_COMPLETION_MATCHES rl_completion_matches
784 #else
785 #ifdef HAVE_COMPLETION_MATCHES
786 #define RL_COMPLETION_MATCHES completion_matches
787 #endif
788 #endif /* else just fail if we don't have either symbol */
789
790 char **
791 do_completion (const char *text, int start, int end)
792 {
793   char **matches = NULL;
794
795 #ifdef HAVE_LIBREADLINE
796   rl_completion_append_character = ' ';
797
798   if (start == 0)
799     matches = RL_COMPLETION_MATCHES (text, generator);
800   else if (complete_dest_paths)
801     matches = RL_COMPLETION_MATCHES (text, complete_dest_paths_generator);
802 #endif
803
804   return matches;
805 }
806 ";
807
808 (* Generate the POD documentation for guestfish. *)
809 and generate_fish_actions_pod () =
810   let all_functions_sorted =
811     List.filter (
812       fun (_, _, _, flags, _, _, _) ->
813         not (List.mem NotInFish flags || List.mem NotInDocs flags)
814     ) all_functions_sorted in
815
816   let rex = Str.regexp "C<guestfs_\\([^>]+\\)>" in
817
818   List.iter (
819     fun (name, (_, args, optargs), _, flags, _, _, longdesc) ->
820       let longdesc =
821         Str.global_substitute rex (
822           fun s ->
823             let sub =
824               try Str.matched_group 1 s
825               with Not_found ->
826                 failwithf "error substituting C<guestfs_...> in longdesc of function %s" name in
827             "L</" ^ replace_char sub '_' '-' ^ ">"
828         ) longdesc in
829       let name = replace_char name '_' '-' in
830       let aliases =
831         filter_map (function FishAlias n -> Some n | _ -> None) flags in
832
833       List.iter (
834         fun name ->
835           pr "=head2 %s\n\n" name
836       ) (name :: aliases);
837       pr " %s" name;
838       List.iter (
839         function
840         | Pathname n | Device n | Dev_or_Path n | String n ->
841             pr " %s" n
842         | OptString n -> pr " %s" n
843         | StringList n | DeviceList n -> pr " '%s ...'" n
844         | Bool _ -> pr " true|false"
845         | Int n -> pr " %s" n
846         | Int64 n -> pr " %s" n
847         | FileIn n | FileOut n -> pr " (%s|-)" n
848         | BufferIn n -> pr " %s" n
849         | Key _ -> () (* keys are entered at a prompt *)
850         | Pointer _ -> assert false
851       ) args;
852       List.iter (
853         function
854         | (Bool n | Int n | Int64 n | String n) as arg ->
855           pr " [%s:%s]" n (doc_opttype_of arg)
856         | _ -> assert false
857       ) optargs;
858       pr "\n";
859       pr "\n";
860       pr "%s\n\n" longdesc;
861
862       if List.exists (function FileIn _ | FileOut _ -> true
863                       | _ -> false) args then
864         pr "Use C<-> instead of a filename to read/write from stdin/stdout.\n\n";
865
866       if List.exists (function Key _ -> true | _ -> false) args then
867         pr "This command has one or more key or passphrase parameters.
868 Guestfish will prompt for these separately.\n\n";
869
870       if optargs <> [] then
871         pr "This command has one or more optional arguments.  See L</OPTIONAL ARGUMENTS>.\n\n";
872
873       if List.mem ProtocolLimitWarning flags then
874         pr "%s\n\n" protocol_limit_warning;
875
876       match deprecation_notice flags with
877       | None -> ()
878       | Some txt -> pr "%s\n\n" txt
879   ) all_functions_sorted
880
881 (* Generate documentation for guestfish-only commands. *)
882 and generate_fish_commands_pod () =
883   List.iter (
884     fun (name, _, _, flags, _, _, longdesc) ->
885       let name = replace_char name '_' '-' in
886       let aliases =
887         filter_map (function FishAlias n -> Some n | _ -> None) flags in
888
889       List.iter (
890         fun name ->
891           pr "=head2 %s\n\n" name
892       ) (name :: aliases);
893       pr "%s\n\n" longdesc;
894   ) fish_commands
895
896 and generate_fish_prep_options_h () =
897   generate_header CStyle GPLv2plus;
898
899   pr "#ifndef PREPOPTS_H\n";
900   pr "\n";
901
902   pr "\
903 struct prep {
904   const char *name;             /* eg. \"fs\" */
905
906   size_t nr_params;             /* optional parameters */
907   struct prep_param *params;
908
909   const char *shortdesc;        /* short description */
910   const char *longdesc;         /* long description */
911
912                                 /* functions to implement it */
913   void (*prelaunch) (const char *filename, prep_data *);
914   void (*postlaunch) (const char *filename, prep_data *, const char *device);
915 };
916
917 struct prep_param {
918   const char *pname;            /* parameter name */
919   const char *pdefault;         /* parameter default */
920   const char *pdesc;            /* parameter description */
921 };
922
923 extern const struct prep preps[];
924 #define NR_PREPS %d
925
926 " (List.length prepopts);
927
928   List.iter (
929     fun (name, shortdesc, args, longdesc) ->
930       pr "\
931 extern void prep_prelaunch_%s (const char *filename, prep_data *data);
932 extern void prep_postlaunch_%s (const char *filename, prep_data *data, const char *device);
933
934 " name name;
935   ) prepopts;
936
937   pr "\n";
938   pr "#endif /* PREPOPTS_H */\n"
939
940 and generate_fish_prep_options_c () =
941   generate_header CStyle GPLv2plus;
942
943   pr "\
944 #include <stdio.h>
945
946 #include \"fish.h\"
947 #include \"prepopts.h\"
948
949 ";
950
951   List.iter (
952     fun (name, shortdesc, args, longdesc) ->
953       pr "static struct prep_param %s_args[] = {\n" name;
954       List.iter (
955         fun (n, default, desc) ->
956           pr "  { \"%s\", \"%s\", \"%s\" },\n" n default desc
957       ) args;
958       pr "};\n";
959       pr "\n";
960   ) prepopts;
961
962   pr "const struct prep preps[] = {\n";
963   List.iter (
964     fun (name, shortdesc, args, longdesc) ->
965       pr "  { \"%s\", %d, %s_args,
966     \"%s\",
967     \"%s\",
968     prep_prelaunch_%s, prep_postlaunch_%s },
969 "
970         name (List.length args) name
971         (c_quote shortdesc) (c_quote longdesc)
972         name name;
973   ) prepopts;
974   pr "};\n"
975
976 and generate_fish_event_names () =
977   generate_header CStyle GPLv2plus;
978
979   pr "\
980 #include <stdio.h>
981 #include <stdlib.h>
982 #include <string.h>
983
984 #include \"fish.h\"
985
986 const char *
987 event_name_of_event_bitmask (uint64_t ev)
988 {
989   switch (ev) {
990 ";
991
992   List.iter (
993     fun (name, _) ->
994       pr "  case GUESTFS_EVENT_%s:\n" (String.uppercase name);
995       pr "    return \"%s\";\n" name
996   ) events;
997
998   pr "  default:
999     abort (); /* should not happen */
1000   }
1001 }
1002
1003 void
1004 print_event_set (uint64_t event_bitmask, FILE *fp)
1005 {
1006   int comma = 0;
1007
1008   if (event_bitmask == GUESTFS_EVENT_ALL) {
1009     fputs (\"*\", fp);
1010     return;
1011   }
1012
1013 ";
1014
1015   List.iter (
1016     fun (name, _) ->
1017       pr "  if (event_bitmask & GUESTFS_EVENT_%s) {\n" (String.uppercase name);
1018       pr "    if (comma) fputc (',', fp);\n";
1019       pr "    comma = 1;\n";
1020       pr "    fputs (\"%s\", fp);\n" name;
1021       pr "  }\n"
1022   ) events;
1023
1024   pr "\
1025 }
1026
1027 int
1028 event_bitmask_of_event_set (const char *arg, uint64_t *eventset_r)
1029 {
1030   size_t n;
1031
1032   if (STREQ (arg, \"*\")) {
1033     *eventset_r = GUESTFS_EVENT_ALL;
1034     return 0;
1035   }
1036
1037   *eventset_r = 0;
1038
1039   while (*arg) {
1040     n = strcspn (arg, \",\");
1041
1042     ";
1043
1044   List.iter (
1045     fun (name, _) ->
1046       pr "if (STREQLEN (arg, \"%s\", n))\n" name;
1047       pr "      *eventset_r |= GUESTFS_EVENT_%s;\n" (String.uppercase name);
1048       pr "    else ";
1049   ) events;
1050
1051   pr "\
1052 {
1053       fprintf (stderr, _(\"unknown event name: %%s\\n\"), arg);
1054       return -1;
1055     }
1056
1057     arg += n;
1058     if (*arg == ',')
1059       arg++;
1060   }
1061
1062   return 0;
1063 }
1064 "