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