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