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