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