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