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