Don't rely on implicit promotion of float to double in printf args.
[libguestfs.git] / generator / generator_fish.ml
index 930ef15..3d52421 100644 (file)
@@ -30,6 +30,13 @@ open Generator_structs
 open Generator_prepopts
 open Generator_c
 
+let doc_opttype_of = function
+  | Bool n -> "true|false"
+  | Int n
+  | Int64 n -> "N"
+  | String n -> ".."
+  | _ -> assert false
+
 (* Generate a lot of different functions for guestfish. *)
 let generate_fish_cmds () =
   generate_header CStyle GPLv2plus;
@@ -48,43 +55,39 @@ let generate_fish_cmds () =
 
   pr "#include <config.h>\n";
   pr "\n";
+  pr "/* It is safe to call deprecated functions from this file. */\n";
+  pr "#undef GUESTFS_WARN_DEPRECATED\n";
+  pr "\n";
   pr "#include <stdio.h>\n";
   pr "#include <stdlib.h>\n";
   pr "#include <string.h>\n";
   pr "#include <inttypes.h>\n";
   pr "\n";
-  pr "#include <guestfs.h>\n";
   pr "#include \"c-ctype.h\"\n";
   pr "#include \"full-write.h\"\n";
   pr "#include \"xstrtol.h\"\n";
+  pr "\n";
+  pr "#include <guestfs.h>\n";
   pr "#include \"fish.h\"\n";
+  pr "#include \"fish-cmds.h\"\n";
+  pr "#include \"options.h\"\n";
+  pr "#include \"cmds_gperf.h\"\n";
   pr "\n";
   pr "/* Valid suffixes allowed for numbers.  See Gnulib xstrtol function. */\n";
   pr "static const char *xstrtol_suffixes = \"0kKMGTPEZY\";\n";
   pr "\n";
 
-  (* list_commands function, which implements guestfish -h *)
-  pr "void list_commands (void)\n";
-  pr "{\n";
-  pr "  printf (\"    %%-16s     %%s\\n\", _(\"Command\"), _(\"Description\"));\n";
-  pr "  list_builtin_commands ();\n";
   List.iter (
-    fun (name, _, _, flags, _, shortdesc, _) ->
-      let name = replace_char name '_' '-' in
-      pr "  printf (\"%%-20s %%s\\n\", \"%s\", _(\"%s\"));\n"
-        name shortdesc
-  ) all_functions_and_fish_commands_sorted;
-  pr "  printf (\"    %%s\\n\",";
-  pr "          _(\"Use -h <cmd> / help <cmd> to show detailed help for a command.\"));\n";
-  pr "}\n";
-  pr "\n";
+    fun (name, _, _, _, _, _, _) ->
+      pr "static int run_%s (const char *cmd, size_t argc, char *argv[]);\n"
+        name
+  ) all_functions;
 
-  (* display_command function, which implements guestfish -h cmd *)
-  pr "int display_command (const char *cmd)\n";
-  pr "{\n";
+  pr "\n";
 
+  (* List of command_entry structs. *)
   List.iter (
-    fun (name, style, _, flags, _, shortdesc, longdesc) ->
+    fun (name, _, _, flags, _, shortdesc, longdesc) ->
       let name2 = replace_char name '_' '-' in
       let aliases =
         filter_map (function FishAlias n -> Some n | _ -> None) flags in
@@ -94,40 +97,44 @@ let generate_fish_cmds () =
             (String.concat " or " (List.map (fun s -> "'" ^ s ^ "'") aliases))
         else "" in
 
-      pr "  if (";
-      pr "STRCASEEQ (cmd, \"%s\")" name;
-      if name <> name2 then
-        pr " || STRCASEEQ (cmd, \"%s\")" name2;
-      List.iter (
-        fun alias ->
-          pr " || STRCASEEQ (cmd, \"%s\")" alias
-      ) aliases;
-      pr ") {\n";
-      pr "    pod2text (\"%s\", _(\"%s\"), %S);\n"
-        name2 shortdesc
-        ("=head1 DESCRIPTION\n\n" ^
-         longdesc ^ describe_alias);
-      pr "    return 0;\n";
-      pr "  }\n";
-      pr "  else\n"
+      let pod =
+        sprintf "%s - %s\n\n=head1 DESCRIPTION\n\n%s\n\n%s"
+          name2 shortdesc longdesc describe_alias in
+      let text =
+        String.concat "\n" (pod2text ~trim:false ~discard:false "NAME" pod)
+        ^ "\n" in
+
+      pr "struct command_entry %s_cmd_entry = {\n" name;
+      pr "  .name = \"%s\",\n" name2;
+      pr "  .help = \"%s\",\n" (c_quote text);
+      pr "  .run = run_%s\n" name;
+      pr "};\n";
+      pr "\n";
   ) fish_commands;
 
   List.iter (
-    fun (name, style, _, flags, _, shortdesc, longdesc) ->
+    fun (name, (_, args, optargs), _, flags, _, shortdesc, longdesc) ->
       let name2 = replace_char name '_' '-' in
       let aliases =
         filter_map (function FishAlias n -> Some n | _ -> None) flags in
+
       let longdesc = replace_str longdesc "C<guestfs_" "C<" in
       let synopsis =
-        match snd style with
+        match args with
         | [] -> name2
         | args ->
             let args = List.filter (function Key _ -> false | _ -> true) args in
-            sprintf "%s %s"
-              name2 (String.concat " " (List.map name_of_argt args)) in
+            sprintf "%s%s%s"
+              name2
+              (String.concat ""
+                 (List.map (fun arg -> " " ^ name_of_argt arg) args))
+              (String.concat ""
+                 (List.map (fun arg ->
+                   sprintf " [%s:%s]" (name_of_argt arg) (doc_opttype_of arg)
+                  ) optargs)) in
 
       let warnings =
-        if List.exists (function Key _ -> true | _ -> false) (snd style) then
+        if List.exists (function Key _ -> true | _ -> false) args then
           "\n\nThis command has one or more key or passphrase parameters.
 Guestfish will prompt for these separately."
         else "" in
@@ -138,16 +145,6 @@ Guestfish will prompt for these separately."
             ("\n\n" ^ protocol_limit_warning)
           else "" in
 
-      (* For DangerWillRobinson commands, we should probably have
-       * guestfish prompt before allowing you to use them (especially
-       * in interactive mode). XXX
-       *)
-      let warnings =
-        warnings ^
-          if List.mem DangerWillRobinson flags then
-            ("\n\n" ^ danger_will_robinson)
-          else "" in
-
       let warnings =
         warnings ^
           match deprecation_notice flags with
@@ -160,31 +157,57 @@ Guestfish will prompt for these separately."
             (String.concat " or " (List.map (fun s -> "'" ^ s ^ "'") aliases))
         else "" in
 
-      pr "  if (";
-      pr "STRCASEEQ (cmd, \"%s\")" name;
-      if name <> name2 then
-        pr " || STRCASEEQ (cmd, \"%s\")" name2;
-      List.iter (
-        fun alias ->
-          pr " || STRCASEEQ (cmd, \"%s\")" alias
-      ) aliases;
-      pr ") {\n";
-      pr "    pod2text (\"%s\", _(\"%s\"), %S);\n"
-        name2 shortdesc
-        ("=head1 SYNOPSIS\n\n " ^ synopsis ^ "\n\n" ^
-         "=head1 DESCRIPTION\n\n" ^
-         longdesc ^ warnings ^ describe_alias);
-      pr "    return 0;\n";
-      pr "  }\n";
-      pr "  else\n"
+      let pod =
+        sprintf "%s - %s\n\n=head1 SYNOPSIS\n\n %s\n\n=head1 DESCRIPTION\n\n%s%s%s"
+          name2 shortdesc synopsis longdesc warnings describe_alias in
+      let text =
+        String.concat "\n" (pod2text ~trim:false ~discard:false "NAME" pod)
+        ^ "\n" in
+
+      pr "struct command_entry %s_cmd_entry = {\n" name;
+      pr "  .name = \"%s\",\n" name2;
+      pr "  .help = \"%s\",\n" (c_quote text);
+      pr "  .run = run_%s\n" name;
+      pr "};\n";
+      pr "\n";
   ) all_functions;
 
+  (* list_commands function, which implements guestfish -h *)
+  pr "void\n";
+  pr "list_commands (void)\n";
+  pr "{\n";
+  pr "  printf (\"    %%-16s     %%s\\n\", _(\"Command\"), _(\"Description\"));\n";
+  pr "  list_builtin_commands ();\n";
+  List.iter (
+    fun (name, _, _, flags, _, shortdesc, _) ->
+      let name = replace_char name '_' '-' in
+      pr "  printf (\"%%-20s %%s\\n\", \"%s\", _(\"%s\"));\n"
+        name shortdesc
+  ) all_functions_and_fish_commands_sorted;
+  pr "  printf (\"    %%s\\n\",";
+  pr "          _(\"Use -h <cmd> / help <cmd> to show detailed help for a command.\"));\n";
+  pr "}\n";
+  pr "\n";
+
+  (* display_command function, which implements guestfish -h cmd *)
+  pr "int\n";
+  pr "display_command (const char *cmd)\n";
+  pr "{\n";
+  pr "  const struct command_table *ct;\n";
+  pr "\n";
+  pr "  ct = lookup_fish_command (cmd, strlen (cmd));\n";
+  pr "  if (ct) {\n";
+  pr "    fputs (ct->entry->help, stdout);\n";
+  pr "    return 0;\n";
+  pr "  }\n";
+  pr "  else\n";
   pr "    return display_builtin_command (cmd);\n";
   pr "}\n";
   pr "\n";
 
   let emit_print_list_function typ =
-    pr "static void print_%s_list (struct guestfs_%s_list *%ss)\n"
+    pr "static void\n";
+    pr "print_%s_list (struct guestfs_%s_list *%ss)\n"
       typ typ typ;
     pr "{\n";
     pr "  unsigned int i;\n";
@@ -204,7 +227,8 @@ Guestfish will prompt for these separately."
       let needs_i =
         List.exists (function (_, (FUUID|FBuffer)) -> true | _ -> false) cols in
 
-      pr "static void print_%s_indent (struct guestfs_%s *%s, const char *indent)\n" typ typ typ;
+      pr "static void\n";
+      pr "print_%s_indent (struct guestfs_%s *%s, const char *indent)\n" typ typ typ;
       pr "{\n";
       if needs_i then (
         pr "  unsigned int i;\n";
@@ -243,9 +267,11 @@ Guestfish will prompt for these separately."
             pr "  printf (\"%%s%s: %%c\\n\", indent, %s->%s);\n"
               name typ name
         | name, FOptPercent ->
-            pr "  if (%s->%s >= 0) printf (\"%%s%s: %%g %%%%\\n\", indent, %s->%s);\n"
-              typ name name typ name;
-            pr "  else printf (\"%%s%s: \\n\", indent);\n" name
+            pr "  if (%s->%s >= 0)\n" typ name;
+            pr "    printf (\"%%s%s: %%g %%%%\\n\", indent, (double) %s->%s);\n"
+              name typ name;
+            pr "  else\n";
+            pr "    printf (\"%%s%s: \\n\", indent);\n" name
       ) cols;
       pr "}\n";
       pr "\n";
@@ -264,7 +290,8 @@ Guestfish will prompt for these separately."
   List.iter (
     function
     | typ, (RStructOnly | RStructAndList) ->
-        pr "static void print_%s (struct guestfs_%s *%s)\n" typ typ typ;
+        pr "static void\n";
+        pr "print_%s (struct guestfs_%s *%s)\n" typ typ typ;
         pr "{\n";
         pr "  print_%s_indent (%s, \"\");\n" typ typ;
         pr "}\n";
@@ -274,10 +301,11 @@ Guestfish will prompt for these separately."
 
   (* run_<action> actions *)
   List.iter (
-    fun (name, style, _, flags, _, _, _) ->
-      pr "static int run_%s (const char *cmd, int argc, char *argv[])\n" name;
+    fun (name, (ret, args, optargs as style), _, flags, _, _, _) ->
+      pr "static int\n";
+      pr "run_%s (const char *cmd, size_t argc, char *argv[])\n" name;
       pr "{\n";
-      (match fst style with
+      (match ret with
        | RErr
        | RInt _
        | RBool _ -> pr "  int r;\n"
@@ -308,26 +336,46 @@ Guestfish will prompt for these separately."
         | Bool n -> pr "  int %s;\n" n
         | Int n -> pr "  int %s;\n" n
         | Int64 n -> pr "  int64_t %s;\n" n
-      ) (snd style);
+        | Pointer _ -> assert false
+      ) args;
+
+      if optargs <> [] then (
+        pr "  struct guestfs_%s_argv optargs_s = { .bitmask = 0 };\n" name;
+        pr "  struct guestfs_%s_argv *optargs = &optargs_s;\n" name
+      );
+
+      if args <> [] || optargs <> [] then
+        pr "  size_t i = 0;\n";
+
+      pr "\n";
 
       (* Check and convert parameters. *)
-      let argc_expected =
+      let argc_minimum, argc_maximum =
         let args_no_keys =
-          List.filter (function Key _ -> false | _ -> true) (snd style) in
-        List.length args_no_keys in
-      pr "  if (argc != %d) {\n" argc_expected;
-      pr "    fprintf (stderr, _(\"%%s should have %%d parameter(s)\\n\"), cmd, %d);\n"
-        argc_expected;
+          List.filter (function Key _ -> false | _ -> true) args in
+        let argc_minimum = List.length args_no_keys in
+        let argc_maximum = argc_minimum + List.length optargs in
+        argc_minimum, argc_maximum in
+
+      if argc_minimum = argc_maximum then (
+        pr "  if (argc != %d) {\n" argc_minimum;
+        pr "    fprintf (stderr, _(\"%%s should have %%d parameter(s)\\n\"), cmd, %d);\n"
+          argc_minimum;
+      ) else (
+        pr "  if (argc < %d || argc > %d) {\n" argc_minimum argc_maximum;
+        pr "    fprintf (stderr, _(\"%%s should have %%d-%%d parameter(s)\\n\"), cmd, %d, %d);\n"
+          argc_minimum argc_maximum;
+      );
       pr "    fprintf (stderr, _(\"type 'help %%s' for help on %%s\\n\"), cmd, cmd);\n";
       pr "    return -1;\n";
       pr "  }\n";
 
-      let parse_integer fn fntyp rtyp range name =
+      let parse_integer expr fn fntyp rtyp range name =
         pr "  {\n";
         pr "    strtol_error xerr;\n";
         pr "    %s r;\n" fntyp;
         pr "\n";
-        pr "    xerr = %s (argv[i++], NULL, 0, &r, xstrtol_suffixes);\n" fn;
+        pr "    xerr = %s (%s, NULL, 0, &r, xstrtol_suffixes);\n" fn expr;
         pr "    if (xerr != LONGINT_OK) {\n";
         pr "      fprintf (stderr,\n";
         pr "               _(\"%%s: %%s: invalid integer parameter (%%s returned %%d)\\n\"),\n";
@@ -349,9 +397,6 @@ Guestfish will prompt for these separately."
         pr "  }\n";
       in
 
-      if snd style <> [] then
-        pr "  size_t i = 0;\n";
-
       List.iter (
         function
         | Device name
@@ -359,7 +404,7 @@ Guestfish will prompt for these separately."
             pr "  %s = argv[i++];\n" name
         | Pathname name
         | Dev_or_Path name ->
-            pr "  %s = resolve_win_path (argv[i++]);\n" name;
+            pr "  %s = win_prefix (argv[i++]); /* process \"win:\" prefix */\n" name;
             pr "  if (%s == NULL) return -1;\n" name
         | OptString name ->
             pr "  %s = STRNEQ (argv[i], \"\") ? argv[i] : NULL;\n" name;
@@ -379,6 +424,8 @@ Guestfish will prompt for these separately."
             pr "  if (%s == NULL) return -1;\n" name
         | Key name ->
             pr "  %s = read_key (\"%s\");\n" name name;
+            pr "  if (keys_from_stdin)\n";
+            pr "    input_lineno++;\n";
             pr "  if (%s == NULL) return -1;\n" name
         | Bool name ->
             pr "  %s = is_true (argv[i++]) ? 1 : 0;\n" name
@@ -389,13 +436,79 @@ Guestfish will prompt for these separately."
               and comment =
                 "The Int type in the generator is a signed 31 bit int." in
               Some (min, max, comment) in
-            parse_integer "xstrtoll" "long long" "int" range name
+            parse_integer "argv[i++]" "xstrtoll" "long long" "int" range name
         | Int64 name ->
-            parse_integer "xstrtoll" "long long" "int64_t" None name
-      ) (snd style);
+            parse_integer "argv[i++]" "xstrtoll" "long long" "int64_t" None name
+        | Pointer _ -> assert false
+      ) args;
+
+      (* Optional arguments are prefixed with <argname>:<value> and
+       * may be missing, so we need to parse those until the end of
+       * the argument list.
+       *)
+      if optargs <> [] then (
+        let uc_name = String.uppercase name in
+        pr "\n";
+        pr "  for (; i < argc; ++i) {\n";
+        pr "    uint64_t this_mask;\n";
+        pr "    const char *this_arg;\n";
+        pr "\n";
+        pr "    ";
+        List.iter (
+          fun argt ->
+            let n = name_of_argt argt in
+            let uc_n = String.uppercase n in
+            let len = String.length n in
+            pr "if (STRPREFIX (argv[i], \"%s:\")) {\n" n;
+            (match argt with
+             | Bool n ->
+                 pr "      optargs_s.%s = is_true (&argv[i][%d]) ? 1 : 0;\n"
+                   n (len+1);
+             | Int n ->
+                 let range =
+                   let min = "(-(2LL<<30))"
+                   and max = "((2LL<<30)-1)"
+                   and comment =
+                     "The Int type in the generator is a signed 31 bit int." in
+                   Some (min, max, comment) in
+                 let expr = sprintf "&argv[i][%d]" (len+1) in
+                 parse_integer expr "xstrtoll" "long long" "int" range
+                   (sprintf "optargs_s.%s" n)
+             | Int64 n ->
+                 let expr = sprintf "&argv[i][%d]" (len+1) in
+                 parse_integer expr "xstrtoll" "long long" "int64_t" None
+                   (sprintf "optargs_s.%s" n)
+             | String n ->
+                 pr "      optargs_s.%s = &argv[i][%d];\n" n (len+1);
+             | _ -> assert false
+            );
+            pr "      this_mask = GUESTFS_%s_%s_BITMASK;\n" uc_name uc_n;
+            pr "      this_arg = \"%s\";\n" n;
+            pr "    }\n";
+            pr "    else ";
+        ) optargs;
+
+        pr "{\n";
+        pr "      fprintf (stderr, _(\"%%s: unknown optional argument \\\"%%s\\\"\\n\"),\n";
+        pr "               cmd, argv[i]);\n";
+        pr "      return -1;\n";
+        pr "    }\n";
+        pr "\n";
+        pr "    if (optargs_s.bitmask & this_mask) {\n";
+        pr "      fprintf (stderr, _(\"%%s: optional argument \\\"%%s\\\" given twice\\n\"),\n";
+        pr "               cmd, this_arg);\n";
+        pr "      return -1;\n";
+        pr "    }\n";
+        pr "    optargs_s.bitmask |= this_mask;\n";
+        pr "  }\n";
+        pr "\n";
+      );
 
       (* Call C API function. *)
-      pr "  r = guestfs_%s " name;
+      if optargs = [] then
+        pr "  r = guestfs_%s " name
+      else
+        pr "  r = guestfs_%s_argv " name;
       generate_c_call_args ~handle:"g" style;
       pr ";\n";
 
@@ -412,7 +525,8 @@ Guestfish will prompt for these separately."
             pr "  free_file_in (%s);\n" name
         | StringList name | DeviceList name ->
             pr "  free_strings (%s);\n" name
-      ) (snd style);
+        | Pointer _ -> assert false
+      ) args;
 
       (* Any output flags? *)
       let fish_output =
@@ -426,7 +540,7 @@ Guestfish will prompt for these separately."
             failwithf "%s: more than one FishOutput flag is not allowed" name in
 
       (* Check return value for errors and display command results. *)
-      (match fst style with
+      (match ret with
        | RErr -> pr "  return r;\n"
        | RInt _ ->
            pr "  if (r == -1) return -1;\n";
@@ -499,36 +613,100 @@ Guestfish will prompt for these separately."
   ) all_functions;
 
   (* run_action function *)
-  pr "int run_action (const char *cmd, int argc, char *argv[])\n";
+  pr "int\n";
+  pr "run_action (const char *cmd, size_t argc, char *argv[])\n";
   pr "{\n";
+  pr "  const struct command_table *ct;\n";
+  pr "\n";
+  pr "  ct = lookup_fish_command (cmd, strlen (cmd));\n";
+  pr "  if (ct)\n";
+  pr "    return ct->entry->run (cmd, argc, argv);\n";
+  pr "  else {\n";
+  pr "    fprintf (stderr, _(\"%%s: unknown command\\n\"), cmd);\n";
+  pr "    if (command_num == 1)\n";
+  pr "      extended_help_message ();\n";
+  pr "    return -1;\n";
+  pr "  }\n";
+  pr "}\n"
+
+and generate_fish_cmds_h () =
+  generate_header CStyle GPLv2plus;
+
+  pr "#ifndef FISH_CMDS_H\n";
+  pr "#define FISH_CMDS_H\n";
+  pr "\n";
+
+  List.iter (
+    fun (shortname, _, _, _, _, _, _) ->
+      pr "extern int run_%s (const char *cmd, size_t argc, char *argv[]);\n"
+        shortname
+  ) fish_commands;
+
+  pr "\n";
+  pr "#endif /* FISH_CMDS_H */\n"
+
+(* gperf code to do fast lookups of commands. *)
+and generate_fish_cmds_gperf () =
+  generate_header CStyle GPLv2plus;
+
+  let all_functions_sorted =
+    List.filter (
+      fun (_, _, _, flags, _, _, _) -> not (List.mem NotInFish flags)
+    ) all_functions_sorted in
+
+  let all_functions_and_fish_commands_sorted =
+    List.sort action_compare (all_functions_sorted @ fish_commands) in
+
+  pr "\
+%%language=ANSI-C
+%%define lookup-function-name lookup_fish_command
+%%ignore-case
+%%readonly-tables
+%%null-strings
+
+%%{
+
+#include <config.h>
+
+#include <stdlib.h>
+#include <string.h>
+
+#include \"cmds_gperf.h\"
+
+";
+
+  List.iter (
+    fun (name, _, _, _, _, _, _) ->
+      pr "extern struct command_entry %s_cmd_entry;\n" name
+  ) all_functions_and_fish_commands_sorted;
+
+  pr "\
+%%}
+
+struct command_table;
+
+%%%%
+";
 
   List.iter (
     fun (name, _, _, flags, _, _, _) ->
       let name2 = replace_char name '_' '-' in
       let aliases =
         filter_map (function FishAlias n -> Some n | _ -> None) flags in
-      pr "  if (";
-      pr "STRCASEEQ (cmd, \"%s\")" name;
+
+      (* The basic command. *)
+      pr "%s, &%s_cmd_entry\n" name name;
+
+      (* Command with dashes instead of underscores. *)
       if name <> name2 then
-        pr " || STRCASEEQ (cmd, \"%s\")" name2;
+        pr "%s, &%s_cmd_entry\n" name2 name;
+
+      (* Aliases for the command. *)
       List.iter (
         fun alias ->
-          pr " || STRCASEEQ (cmd, \"%s\")" alias;
+          pr "%s, &%s_cmd_entry\n" alias name;
       ) aliases;
-      pr ")\n";
-      pr "    return run_%s (cmd, argc, argv);\n" name;
-      pr "  else\n";
-  ) all_functions_and_fish_commands_sorted;
-
-  pr "    {\n";
-  pr "      fprintf (stderr, _(\"%%s: unknown command\\n\"), cmd);\n";
-  pr "      if (command_num == 1)\n";
-  pr "        extended_help_message ();\n";
-  pr "      return -1;\n";
-  pr "    }\n";
-  pr "  return 0;\n";
-  pr "}\n";
-  pr "\n"
+  ) all_functions_and_fish_commands_sorted
 
 (* Readline completion for guestfish. *)
 and generate_fish_completion () =
@@ -637,7 +815,7 @@ and generate_fish_actions_pod () =
   let rex = Str.regexp "C<guestfs_\\([^>]+\\)>" in
 
   List.iter (
-    fun (name, style, _, flags, _, _, longdesc) ->
+    fun (name, (_, args, optargs), _, flags, _, _, longdesc) ->
       let longdesc =
         Str.global_substitute rex (
           fun s ->
@@ -668,25 +846,32 @@ and generate_fish_actions_pod () =
         | FileIn n | FileOut n -> pr " (%s|-)" n
         | BufferIn n -> pr " %s" n
         | Key _ -> () (* keys are entered at a prompt *)
-      ) (snd style);
+        | Pointer _ -> assert false
+      ) args;
+      List.iter (
+        function
+        | (Bool n | Int n | Int64 n | String n) as arg ->
+          pr " [%s:%s]" n (doc_opttype_of arg)
+        | _ -> assert false
+      ) optargs;
       pr "\n";
       pr "\n";
       pr "%s\n\n" longdesc;
 
       if List.exists (function FileIn _ | FileOut _ -> true
-                      | _ -> false) (snd style) then
+                      | _ -> false) args then
         pr "Use C<-> instead of a filename to read/write from stdin/stdout.\n\n";
 
-      if List.exists (function Key _ -> true | _ -> false) (snd style) then
+      if List.exists (function Key _ -> true | _ -> false) args then
         pr "This command has one or more key or passphrase parameters.
 Guestfish will prompt for these separately.\n\n";
 
+      if optargs <> [] then
+        pr "This command has one or more optional arguments.  See L</OPTIONAL ARGUMENTS>.\n\n";
+
       if List.mem ProtocolLimitWarning flags then
         pr "%s\n\n" protocol_limit_warning;
 
-      if List.mem DangerWillRobinson flags then
-        pr "%s\n\n" danger_will_robinson;
-
       match deprecation_notice flags with
       | None -> ()
       | Some txt -> pr "%s\n\n" txt
@@ -695,7 +880,7 @@ Guestfish will prompt for these separately.\n\n";
 (* Generate documentation for guestfish-only commands. *)
 and generate_fish_commands_pod () =
   List.iter (
-    fun (name, style, _, flags, _, _, longdesc) ->
+    fun (name, _, _, flags, _, _, longdesc) ->
       let name = replace_char name '_' '-' in
       let aliases =
         filter_map (function FishAlias n -> Some n | _ -> None) flags in
@@ -755,6 +940,8 @@ and generate_fish_prep_options_c () =
   generate_header CStyle GPLv2plus;
 
   pr "\
+#include <stdio.h>
+
 #include \"fish.h\"
 #include \"prepopts.h\"