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