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