Add 'set-kernel'/'get-kernel'/LIBGUESTFS_KERNEL to override appliance kernel.
[libguestfs.git] / src / generator.ml
index d3040d5..398fd04 100755 (executable)
@@ -25,9 +25,8 @@
  * daemon/<somefile>.c to write the implementation.
  *
  * After editing this file, run it (./src/generator.ml) to regenerate all the
- * output files. Note that if you are using a separate build directory you must
- * run generator.ml from your top level build directory. You must also have run
- * configure before generator.ml will run.
+ * output files.  Note that if you are using a separate build directory you
+ * must run generator.ml from the _source_ directory.
  *
  * IMPORTANT: This script should NOT print any warnings.  If it prints
  * warnings, you should treat them as errors.
@@ -86,16 +85,20 @@ and ret =
      * inefficient.  Keys should be unique.  NULLs are not permitted.
      *)
   | RHashtable of string
-(* Not implemented:
     (* "RBufferOut" is handled almost exactly like RString, but
      * it allows the string to contain arbitrary 8 bit data including
      * ASCII NUL.  In the C API this causes an implicit extra parameter
-     * to be added of type <size_t *size_r>.  Other programming languages
-     * support strings with arbitrary 8 bit data.  At the RPC layer
-     * we have to use the opaque<> type instead of string<>.
+     * to be added of type <size_t *size_r>.  The extra parameter
+     * returns the actual size of the return buffer in bytes.
+     *
+     * Other programming languages support strings with arbitrary 8 bit
+     * data.
+     *
+     * At the RPC layer we have to use the opaque<> type instead of
+     * string<>.  Returned data is still limited to the max message
+     * size (ie. ~ 2 MB).
      *)
   | RBufferOut of string
-*)
 
 and args = argt list   (* Function parameters, guestfs handle is implicit. *)
 
@@ -527,6 +530,31 @@ guest kernel command line.
 
 If C<NULL> then no options are added.");
 
+  ("set_kernel", (RErr, [String "kernel"]), -1, [FishAlias "kernel"],
+   [],
+   "override the normal appliance kernel",
+   "\
+This function lets you override the ordinary selection
+of kernel used in the appliance.
+
+The default is C<NULL> unless overridden by setting
+C<LIBGUESTFS_KERNEL> environment variable.
+
+Setting C<kernel> to C<NULL> means the ordinary appliance
+kernel is selected by the usual means.");
+
+  ("get_kernel", (RConstString "kernel", []), -1, [],
+   (* This cannot be tested with the current framework.  The
+    * function can return NULL in normal operations, which the
+    * test framework interprets as an error.
+    *)
+   [],
+   "get the override appliance kernel",
+   "\
+Return the override appliance kernel (see C<guestfs_set_kernel>).
+
+If C<NULL> then the ordinary appliance kernel is used.");
+
   ("set_autosync", (RErr, [Bool "autosync"]), -1, [FishAlias "autosync"],
    [],
    "set autosync mode",
@@ -773,8 +801,8 @@ Return the contents of the file named C<path>.
 
 Note that this function cannot correctly handle binary files
 (specifically, files containing C<\\0> character which is treated
-as end of string).  For those you need to use the C<guestfs_download>
-function which has a more complex interface.");
+as end of string).  For those you need to use the C<guestfs_read_file>
+or C<guestfs_download> functions which have a more complex interface.");
 
   ("ll", (RString "listing", [String "directory"]), 5, [],
    [], (* XXX Tricky to test because it depends on the exact format
@@ -1371,7 +1399,9 @@ contains the filesystem.");
 This returns the list of currently mounted filesystems.  It returns
 the list of devices (eg. C</dev/sda1>, C</dev/VG/LV>).
 
-Some internal mounts are not shown.");
+Some internal mounts are not shown.
+
+See also: C<guestfs_mountpoints>");
 
   ("umount_all", (RErr, []), 47, [FishAlias "unmount-all"],
    [InitBasicFS, Always, TestOutputList (
@@ -2841,6 +2871,50 @@ All entries in the directory are returned, including C<.> and
 C<..>.  The entries are I<not> sorted, but returned in the same
 order as the underlying filesystem.
 
+Also this call returns basic file type information about each
+file.  The C<ftyp> field will contain one of the following characters:
+
+=over 4
+
+=item 'b'
+
+Block special
+
+=item 'c'
+
+Char special
+
+=item 'd'
+
+Directory
+
+=item 'f'
+
+FIFO (named pipe)
+
+=item 'l'
+
+Symbolic link
+
+=item 'r'
+
+Regular file
+
+=item 's'
+
+Socket
+
+=item 'u'
+
+Unknown file type
+
+=item '?'
+
+The L<readdir(3)> returned a C<d_type> field with an
+unexpected value
+
+=back
+
 This function is primarily intended for use by programs.  To
 get a simple list of names, use C<guestfs_ls>.  To get a printable
 directory for human consumption, use C<guestfs_ll>.");
@@ -2868,6 +2942,123 @@ C<method> must be one of C<gzip>, C<compress> or C<bzip2>.
 
 See also: C<guestfs_file>");
 
+  ("getxattrs", (RStructList ("xattrs", "xattr"), [String "path"]), 141, [],
+   [],
+   "list extended attributes of a file or directory",
+   "\
+This call lists the extended attributes of the file or directory
+C<path>.
+
+At the system call level, this is a combination of the
+L<listxattr(2)> and L<getxattr(2)> calls.
+
+See also: C<guestfs_lgetxattrs>, L<attr(5)>.");
+
+  ("lgetxattrs", (RStructList ("xattrs", "xattr"), [String "path"]), 142, [],
+   [],
+   "list extended attributes of a file or directory",
+   "\
+This is the same as C<guestfs_getxattrs>, but if C<path>
+is a symbolic link, then it returns the extended attributes
+of the link itself.");
+
+  ("setxattr", (RErr, [String "xattr";
+                      String "val"; Int "vallen"; (* will be BufferIn *)
+                      String "path"]), 143, [],
+   [],
+   "set extended attribute of a file or directory",
+   "\
+This call sets the extended attribute named C<xattr>
+of the file C<path> to the value C<val> (of length C<vallen>).
+The value is arbitrary 8 bit data.
+
+See also: C<guestfs_lsetxattr>, L<attr(5)>.");
+
+  ("lsetxattr", (RErr, [String "xattr";
+                       String "val"; Int "vallen"; (* will be BufferIn *)
+                       String "path"]), 144, [],
+   [],
+   "set extended attribute of a file or directory",
+   "\
+This is the same as C<guestfs_setxattr>, but if C<path>
+is a symbolic link, then it sets an extended attribute
+of the link itself.");
+
+  ("removexattr", (RErr, [String "xattr"; String "path"]), 145, [],
+   [],
+   "remove extended attribute of a file or directory",
+   "\
+This call removes the extended attribute named C<xattr>
+of the file C<path>.
+
+See also: C<guestfs_lremovexattr>, L<attr(5)>.");
+
+  ("lremovexattr", (RErr, [String "xattr"; String "path"]), 146, [],
+   [],
+   "remove extended attribute of a file or directory",
+   "\
+This is the same as C<guestfs_removexattr>, but if C<path>
+is a symbolic link, then it removes an extended attribute
+of the link itself.");
+
+  ("mountpoints", (RHashtable "mps", []), 147, [],
+   [],
+   "show mountpoints",
+   "\
+This call is similar to C<guestfs_mounts>.  That call returns
+a list of devices.  This one returns a hash table (map) of
+device name to directory where the device is mounted.");
+
+  ("mkmountpoint", (RErr, [String "path"]), 148, [],
+   [],
+   "create a mountpoint",
+   "\
+C<guestfs_mkmountpoint> and C<guestfs_rmmountpoint> are
+specialized calls that can be used to create extra mountpoints
+before mounting the first filesystem.
+
+These calls are I<only> necessary in some very limited circumstances,
+mainly the case where you want to mount a mix of unrelated and/or
+read-only filesystems together.
+
+For example, live CDs often contain a \"Russian doll\" nest of
+filesystems, an ISO outer layer, with a squashfs image inside, with
+an ext2/3 image inside that.  You can unpack this as follows
+in guestfish:
+
+ add-ro Fedora-11-i686-Live.iso
+ run
+ mkmountpoint /cd
+ mkmountpoint /squash
+ mkmountpoint /ext3
+ mount /dev/sda /cd
+ mount-loop /cd/LiveOS/squashfs.img /squash
+ mount-loop /squash/LiveOS/ext3fs.img /ext3
+
+The inner filesystem is now unpacked under the /ext3 mountpoint.");
+
+  ("rmmountpoint", (RErr, [String "path"]), 149, [],
+   [],
+   "remove a mountpoint",
+   "\
+This calls removes a mountpoint that was previously created
+with C<guestfs_mkmountpoint>.  See C<guestfs_mkmountpoint>
+for full details.");
+
+  ("read_file", (RBufferOut "content", [String "path"]), 150, [ProtocolLimitWarning],
+   [InitBasicFS, Always, TestOutput (
+      [["write_file"; "/new"; "new file contents"; "0"];
+       ["read_file"; "/new"]], "new file contents")],
+   "read a file",
+   "\
+This calls returns the contents of the file C<path> as a
+buffer.
+
+Unlike C<guestfs_cat>, this function can correctly
+handle files that contain embedded ASCII NUL characters.
+However unlike C<guestfs_download>, this function is limited
+in the total size of file that can be handled.");
+
 ]
 
 let all_functions = non_daemon_functions @ daemon_functions
@@ -2883,6 +3074,7 @@ let all_functions_sorted =
 type field =
   | FChar                      (* C 'char' (really, a 7 bit byte). *)
   | FString                    (* nul-terminated ASCII string. *)
+  | FBuffer                    (* opaque buffer of bytes, (char *, int) pair *)
   | FUInt32
   | FInt32
   | FUInt64
@@ -3021,6 +3213,12 @@ let structs = [
     "release", FInt64;
     "extra", FString;
   ];
+
+  (* Extended attribute. *)
+  "xattr", [
+    "attrname", FString;
+    "attrval", FBuffer;
+  ];
 ] (* end of structs *)
 
 (* Ugh, Java has to be different ..
@@ -3035,6 +3233,7 @@ let java_structs = [
   "statvfs", "StatVFS";
   "dirent", "Dirent";
   "version", "Version";
+  "xattr", "XAttr";
 ]
 
 (* Used for testing language bindings. *)
@@ -3243,7 +3442,7 @@ let check_functions () =
        | RErr -> ()
        | RInt n | RInt64 n | RBool n | RConstString n | RString n
        | RStringList n | RStruct (n, _) | RStructList (n, _)
-       | RHashtable n ->
+       | RHashtable n | RBufferOut n ->
           check_arg_ret_name n
       );
       List.iter (fun arg -> check_arg_ret_name (name_of_argt arg)) (snd style)
@@ -3425,6 +3624,10 @@ strings, or NULL if there was an error.
 The array of strings will always have length C<2n+1>, where
 C<n> keys and values alternate, followed by the trailing NULL entry.
 I<The caller must free the strings and the array after use>.\n\n"
+        | RBufferOut _ ->
+            pr "This function returns a buffer, or NULL on error.
+The size of the returned buffer is written to C<*size_r>.
+I<The caller must free the returned buffer after use>.\n\n"
        );
        if List.mem ProtocolLimitWarning flags then
          pr "%s\n\n" protocol_limit_warning;
@@ -3448,6 +3651,10 @@ and generate_structs_pod () =
        | name, (FUInt64|FBytes) -> pr "   uint64_t %s;\n" name
        | name, FInt64 -> pr "   int64_t %s;\n" name
        | name, FString -> pr "   char *%s;\n" name
+       | name, FBuffer ->
+           pr "   /* The next two fields describe a byte array. */\n";
+           pr "   uint32_t %s_len;\n" name;
+           pr "   char *%s;\n" name
        | name, FUUID ->
            pr "   /* The next field is NOT nul-terminated, be careful when printing it: */\n";
            pr "   char %s[32];\n" name
@@ -3491,6 +3698,7 @@ and generate_xdr () =
        List.iter (function
                   | name, FChar -> pr "  char %s;\n" name
                   | name, FString -> pr "  string %s<>;\n" name
+                  | name, FBuffer -> pr "  opaque %s<>;\n" name
                   | name, FUUID -> pr "  opaque %s[32];\n" name
                   | name, (FInt32|FUInt32) -> pr "  int %s;\n" name
                   | name, (FInt64|FUInt64|FBytes) -> pr "  hyper %s;\n" name
@@ -3557,6 +3765,10 @@ and generate_xdr () =
           pr "struct %s_ret {\n" name;
           pr "  str %s<>;\n" n;
           pr "};\n\n"
+       | RBufferOut n ->
+          pr "struct %s_ret {\n" name;
+          pr "  opaque %s<>;\n" n;
+          pr "};\n\n"
       );
   ) daemon_functions;
 
@@ -3652,6 +3864,9 @@ and generate_structs_h () =
        function
        | name, FChar -> pr "  char %s;\n" name
        | name, FString -> pr "  char *%s;\n" name
+       | name, FBuffer ->
+           pr "  uint32_t %s_len;\n" name;
+           pr "  char *%s;\n" name
        | name, FUUID -> pr "  char %s[32]; /* this is NOT nul-terminated, be careful when printing */\n" name
        | name, FUInt32 -> pr "  uint32_t %s;\n" name
        | name, FInt32 -> pr "  int32_t %s;\n" name
@@ -3775,7 +3990,7 @@ check_state (guestfs_h *g, const char *caller)
        | RInt _ | RInt64 _
        | RBool _ | RString _ | RStringList _
        | RStruct _ | RStructList _
-       | RHashtable _ ->
+       | RHashtable _ | RBufferOut _ ->
           pr "  struct %s_ret ret;\n" name
       );
       pr "};\n";
@@ -3816,7 +4031,7 @@ check_state (guestfs_h *g, const char *caller)
        | RInt _ | RInt64 _
        | RBool _ | RString _ | RStringList _
        | RStruct _ | RStructList _
-       | RHashtable _ ->
+       | RHashtable _ | RBufferOut _ ->
           pr "  if (!xdr_%s_ret (xdr, &ctx->ret)) {\n" name;
           pr "    error (g, \"%%s: failed to parse reply\", \"%s\");\n" name;
           pr "    return;\n";
@@ -3838,7 +4053,7 @@ check_state (guestfs_h *g, const char *caller)
            failwithf "RConstString cannot be returned from a daemon function"
        | RString _ | RStringList _
        | RStruct _ | RStructList _
-       | RHashtable _ ->
+       | RHashtable _ | RBufferOut _ ->
            "NULL" in
 
       pr "{\n";
@@ -3976,6 +4191,9 @@ check_state (guestfs_h *g, const char *caller)
        | RStructList (n, _) ->
           pr "  /* caller will free this */\n";
           pr "  return safe_memdup (g, &ctx.ret.%s, sizeof (ctx.ret.%s));\n" n n
+       | RBufferOut n ->
+          pr "  *size_r = ctx.ret.%s.%s_len;\n" n n;
+          pr "  return ctx.ret.%s.%s_val; /* caller will free */\n" n n
       );
 
       pr "}\n\n"
@@ -4056,7 +4274,11 @@ and generate_daemon_actions () =
        | RString _ -> pr "  char *r;\n"; "NULL"
        | RStringList _ | RHashtable _ -> pr "  char **r;\n"; "NULL"
        | RStruct (_, typ) -> pr "  guestfs_int_%s *r;\n" typ; "NULL"
-       | RStructList (_, typ) -> pr "  guestfs_int_%s_list *r;\n" typ; "NULL" in
+       | RStructList (_, typ) -> pr "  guestfs_int_%s_list *r;\n" typ; "NULL"
+       | RBufferOut _ ->
+           pr "  size_t size;\n";
+           pr "  char *r;\n";
+           "NULL" in
 
       (match snd style with
        | [] -> ()
@@ -4110,11 +4332,11 @@ and generate_daemon_actions () =
       (* Don't want to call the impl with any FileIn or FileOut
        * parameters, since these go "outside" the RPC protocol.
        *)
-      let argsnofile =
+      let args' =
        List.filter (function FileIn _ | FileOut _ -> false | _ -> true)
          (snd style) in
       pr "  r = do_%s " name;
-      generate_call_args argsnofile;
+      generate_c_call_args (fst style, args');
       pr ";\n";
 
       pr "  if (r == %s)\n" error_code;
@@ -4166,6 +4388,13 @@ and generate_daemon_actions () =
              name;
            pr "  xdr_free ((xdrproc_t) xdr_guestfs_%s_ret, (char *) &ret);\n"
              name
+       | RBufferOut n ->
+           pr "  struct guestfs_%s_ret ret;\n" name;
+           pr "  ret.%s.%s_val = r;\n" n n;
+           pr "  ret.%s.%s_len = size;\n" n n;
+           pr "  reply ((xdrproc_t) &xdr_guestfs_%s_ret, (char *) &ret);\n"
+             name;
+           pr "  free (r);\n"
       );
 
       (* Free the args. *)
@@ -4269,7 +4498,7 @@ and generate_daemon_actions () =
                 pr "    fprintf (stderr, \"%%s: failed to parse float '%%s' from token %%s\\n\", __func__, tok, \"%s\");\n" name;
                 pr "    return -1;\n";
                 pr "  }\n";
-            | FInt32 | FUInt32 | FUInt64 | FChar ->
+            | FBuffer | FInt32 | FUInt32 | FUInt64 | FChar ->
                 assert false (* can never be an LVM column *)
            );
            pr "  tok = next;\n";
@@ -4974,7 +5203,11 @@ and generate_test_command_call ?(expect_error = false) ?test test_name cmd =
        | RStruct (_, typ) ->
            pr "    struct guestfs_%s *r;\n" typ; "NULL"
        | RStructList (_, typ) ->
-           pr "    struct guestfs_%s_list *r;\n" typ; "NULL" in
+           pr "    struct guestfs_%s_list *r;\n" typ; "NULL"
+       | RBufferOut _ ->
+           pr "    char *r;\n";
+           pr "    size_t size;\n";
+           "NULL" in
 
       pr "    suppress_error = %d;\n" (if expect_error then 1 else 0);
       pr "    r = guestfs_%s (g" name;
@@ -5000,7 +5233,13 @@ and generate_test_command_call ?(expect_error = false) ?test test_name cmd =
            let b = bool_of_string arg in pr ", %d" (if b then 1 else 0)
       ) (List.combine (snd style) args);
 
+      (match fst style with
+       | RBufferOut _ -> pr ", &size"
+       | _ -> ()
+      );
+
       pr ");\n";
+
       if not expect_error then
        pr "    if (r == %s)\n" error_code
       else
@@ -5015,7 +5254,7 @@ and generate_test_command_call ?(expect_error = false) ?test test_name cmd =
 
       (match fst style with
        | RErr | RInt _ | RInt64 _ | RBool _ | RConstString _ -> ()
-       | RString _ -> pr "    free (r);\n"
+       | RString _ | RBufferOut _ -> pr "    free (r);\n"
        | RStringList _ | RHashtable _ ->
           pr "    for (i = 0; r[i] != NULL; ++i)\n";
           pr "      free (r[i]);\n";
@@ -5052,6 +5291,7 @@ and generate_fish_cmds () =
   pr "#include <stdlib.h>\n";
   pr "#include <string.h>\n";
   pr "#include <inttypes.h>\n";
+  pr "#include <ctype.h>\n";
   pr "\n";
   pr "#include <guestfs.h>\n";
   pr "#include \"fish.h\"\n";
@@ -5129,7 +5369,7 @@ and generate_fish_cmds () =
   List.iter (
     fun (typ, cols) ->
       let needs_i =
-        List.exists (function (_, FUUID) -> true | _ -> false) cols in
+        List.exists (function (_, (FUUID|FBuffer)) -> true | _ -> false) cols in
 
       pr "static void print_%s (struct guestfs_%s *%s)\n" typ typ typ;
       pr "{\n";
@@ -5146,6 +5386,14 @@ and generate_fish_cmds () =
            pr "  for (i = 0; i < 32; ++i)\n";
            pr "    printf (\"%%c\", %s->%s[i]);\n" typ name;
            pr "  printf (\"\\n\");\n"
+       | name, FBuffer ->
+           pr "  printf (\"%s: \");\n" name;
+           pr "  for (i = 0; i < %s->%s_len; ++i)\n" typ name;
+           pr "    if (isprint (%s->%s[i]))\n" typ name;
+           pr "      printf (\"%%c\", %s->%s[i]);\n" typ name;
+           pr "    else\n";
+           pr "      printf (\"\\\\x%%02x\", %s->%s[i]);\n" typ name;
+           pr "  printf (\"\\n\");\n"
        | name, (FUInt64|FBytes) ->
            pr "  printf (\"%s: %%\" PRIu64 \"\\n\", %s->%s);\n" name typ name
        | name, FInt64 ->
@@ -5189,6 +5437,9 @@ and generate_fish_cmds () =
        | RStringList _ | RHashtable _ -> pr "  char **r;\n"
        | RStruct (_, typ) -> pr "  struct guestfs_%s *r;\n" typ
        | RStructList (_, typ) -> pr "  struct guestfs_%s_list *r;\n" typ
+       | RBufferOut _ ->
+          pr "  char *r;\n";
+          pr "  size_t size;\n";
       );
       List.iter (
        function
@@ -5235,7 +5486,7 @@ and generate_fish_cmds () =
        try find_map (function FishAction n -> Some n | _ -> None) flags
        with Not_found -> sprintf "guestfs_%s" name in
       pr "  r = %s " fn;
-      generate_call_args ~handle:"g" (snd style);
+      generate_c_call_args ~handle:"g" style;
       pr ";\n";
 
       (* Check return value for errors and display command results. *)
@@ -5282,6 +5533,11 @@ and generate_fish_cmds () =
           pr "  print_table (r);\n";
           pr "  free_strings (r);\n";
           pr "  return 0;\n"
+       | RBufferOut _ ->
+          pr "  if (r == NULL) return -1;\n";
+          pr "  fwrite (r, size, 1, stdout);\n";
+          pr "  free (r);\n";
+          pr "  return 0;\n"
       );
       pr "}\n";
       pr "\n"
@@ -5472,7 +5728,7 @@ and generate_prototype ?(extern = true) ?(static = false) ?(semicolon = true)
    | RInt64 _ -> pr "int64_t "
    | RBool _ -> pr "int "
    | RConstString _ -> pr "const char *"
-   | RString _ -> pr "char *"
+   | RString _ | RBufferOut _ -> pr "char *"
    | RStringList _ | RHashtable _ -> pr "char **"
    | RStruct (_, typ) ->
        if not in_daemon then pr "struct guestfs_%s *" typ
@@ -5481,8 +5737,9 @@ and generate_prototype ?(extern = true) ?(static = false) ?(semicolon = true)
        if not in_daemon then pr "struct guestfs_%s_list *" typ
        else pr "guestfs_int_%s_list *" typ
   );
+  let is_RBufferOut = match fst style with RBufferOut _ -> true | _ -> false in
   pr "%s%s (" prefix name;
-  if handle = None && List.length (snd style) = 0 then
+  if handle = None && List.length (snd style) = 0 && not is_RBufferOut then
     pr "void"
   else (
     let comma = ref false in
@@ -5513,25 +5770,37 @@ and generate_prototype ?(extern = true) ?(static = false) ?(semicolon = true)
       | FileOut n ->
          if not in_daemon then (next (); pr "const char *%s" n)
     ) (snd style);
+    if is_RBufferOut then (next (); pr "size_t *size_r");
   );
   pr ")";
   if semicolon then pr ";";
   if newline then pr "\n"
 
 (* Generate C call arguments, eg "(handle, foo, bar)" *)
-and generate_call_args ?handle args =
+and generate_c_call_args ?handle ?(decl = false) style =
   pr "(";
   let comma = ref false in
+  let next () =
+    if !comma then pr ", ";
+    comma := true
+  in
   (match handle with
    | None -> ()
    | Some handle -> pr "%s" handle; comma := true
   );
   List.iter (
     fun arg ->
-      if !comma then pr ", ";
-      comma := true;
+      next ();
       pr "%s" (name_of_argt arg)
-  ) args;
+  ) (snd style);
+  (* For RBufferOut calls, add implicit &size parameter. *)
+  if not decl then (
+    match fst style with
+    | RBufferOut _ ->
+       next ();
+       pr "&size"
+    | _ -> ()
+  );
   pr ")"
 
 (* Generate the OCaml bindings interface. *)
@@ -5661,6 +5930,10 @@ copy_table (char * const * argv)
          (match col with
           | name, FString ->
               pr "  v = caml_copy_string (%s->%s);\n" typ name
+          | name, FBuffer ->
+              pr "  v = caml_alloc_string (%s->%s_len);\n" typ name;
+              pr "  memcpy (String_val (v), %s->%s, %s->%s_len);\n"
+                typ name typ name
           | name, FUUID ->
               pr "  v = caml_alloc_string (32);\n";
               pr "  memcpy (String_val (v), %s->%s, 32);\n" typ name
@@ -5772,12 +6045,16 @@ copy_table (char * const * argv)
        | RHashtable _ ->
            pr "  int i;\n";
            pr "  char **r;\n";
+           "NULL"
+       | RBufferOut _ ->
+           pr "  char *r;\n";
+           pr "  size_t size;\n";
            "NULL" in
       pr "\n";
 
       pr "  caml_enter_blocking_section ();\n";
       pr "  r = guestfs_%s " name;
-      generate_call_args ~handle:"g" (snd style);
+      generate_c_call_args ~handle:"g" style;
       pr ";\n";
       pr "  caml_leave_blocking_section ();\n";
 
@@ -5816,6 +6093,9 @@ copy_table (char * const * argv)
           pr "  rv = copy_table (r);\n";
           pr "  for (i = 0; r[i] != NULL; ++i) free (r[i]);\n";
           pr "  free (r);\n";
+       | RBufferOut _ ->
+          pr "  rv = caml_alloc_string (size);\n";
+          pr "  memcpy (String_val (rv), r, size);\n";
       );
 
       pr "  CAMLreturn (rv);\n";
@@ -5841,6 +6121,7 @@ and generate_ocaml_structure_decls () =
       List.iter (
        function
        | name, FString -> pr "  %s : string;\n" name
+       | name, FBuffer -> pr "  %s : string;\n" name
        | name, FUUID -> pr "  %s : string;\n" name
        | name, (FBytes|FInt64|FUInt64) -> pr "  %s : int64;\n" name
        | name, (FInt32|FUInt32) -> pr "  %s : int32;\n" name
@@ -5868,7 +6149,7 @@ and generate_ocaml_prototype ?(is_external = false) name style =
    | RInt64 _ -> pr "int64"
    | RBool _ -> pr "bool"
    | RConstString _ -> pr "string"
-   | RString _ -> pr "string"
+   | RString _ | RBufferOut _ -> pr "string"
    | RStringList _ -> pr "string array"
    | RStruct (_, typ) -> pr "%s" typ
    | RStructList (_, typ) -> pr "%s array" typ
@@ -5985,6 +6266,7 @@ DESTROY (g)
        | RBool _ -> pr "SV *\n"
        | RConstString _ -> pr "SV *\n"
        | RString _ -> pr "SV *\n"
+       | RBufferOut _ -> pr "SV *\n"
        | RStringList _
        | RStruct _ | RStructList _
        | RHashtable _ ->
@@ -5992,7 +6274,7 @@ DESTROY (g)
       );
       (* Call and arguments. *)
       pr "%s " name;
-      generate_call_args ~handle:"g" (snd style);
+      generate_c_call_args ~handle:"g" ~decl:true style;
       pr "\n";
       pr "      guestfs_h *g;\n";
       iteri (
@@ -6026,7 +6308,7 @@ DESTROY (g)
           pr "      int r;\n";
           pr " PPCODE:\n";
           pr "      r = guestfs_%s " name;
-          generate_call_args ~handle:"g" (snd style);
+          generate_c_call_args ~handle:"g" style;
           pr ";\n";
           do_cleanups ();
           pr "      if (r == -1)\n";
@@ -6037,7 +6319,7 @@ DESTROY (g)
           pr "      int %s;\n" n;
           pr "   CODE:\n";
           pr "      %s = guestfs_%s " n name;
-          generate_call_args ~handle:"g" (snd style);
+          generate_c_call_args ~handle:"g" style;
           pr ";\n";
           do_cleanups ();
           pr "      if (%s == -1)\n" n;
@@ -6050,7 +6332,7 @@ DESTROY (g)
           pr "      int64_t %s;\n" n;
           pr "   CODE:\n";
           pr "      %s = guestfs_%s " n name;
-          generate_call_args ~handle:"g" (snd style);
+          generate_c_call_args ~handle:"g" style;
           pr ";\n";
           do_cleanups ();
           pr "      if (%s == -1)\n" n;
@@ -6063,7 +6345,7 @@ DESTROY (g)
           pr "      const char *%s;\n" n;
           pr "   CODE:\n";
           pr "      %s = guestfs_%s " n name;
-          generate_call_args ~handle:"g" (snd style);
+          generate_c_call_args ~handle:"g" style;
           pr ";\n";
           do_cleanups ();
           pr "      if (%s == NULL)\n" n;
@@ -6076,7 +6358,7 @@ DESTROY (g)
           pr "      char *%s;\n" n;
           pr "   CODE:\n";
           pr "      %s = guestfs_%s " n name;
-          generate_call_args ~handle:"g" (snd style);
+          generate_c_call_args ~handle:"g" style;
           pr ";\n";
           do_cleanups ();
           pr "      if (%s == NULL)\n" n;
@@ -6091,7 +6373,7 @@ DESTROY (g)
           pr "      int i, n;\n";
           pr " PPCODE:\n";
           pr "      %s = guestfs_%s " n name;
-          generate_call_args ~handle:"g" (snd style);
+          generate_c_call_args ~handle:"g" style;
           pr ";\n";
           do_cleanups ();
           pr "      if (%s == NULL)\n" n;
@@ -6109,6 +6391,21 @@ DESTROY (g)
        | RStructList (n, typ) ->
           let cols = cols_of_struct typ in
           generate_perl_struct_list_code typ cols name style n do_cleanups
+       | RBufferOut n ->
+          pr "PREINIT:\n";
+          pr "      char *%s;\n" n;
+          pr "      size_t size;\n";
+          pr "   CODE:\n";
+          pr "      %s = guestfs_%s " n name;
+          generate_c_call_args ~handle:"g" style;
+          pr ";\n";
+          do_cleanups ();
+          pr "      if (%s == NULL)\n" n;
+          pr "        croak (\"%s: %%s\", guestfs_last_error (g));\n" name;
+          pr "      RETVAL = newSVpv (%s, size);\n" n;
+          pr "      free (%s);\n" n;
+          pr " OUTPUT:\n";
+          pr "      RETVAL\n"
       );
 
       pr "\n"
@@ -6121,7 +6418,7 @@ and generate_perl_struct_list_code typ cols name style n do_cleanups =
   pr "      HV *hv;\n";
   pr " PPCODE:\n";
   pr "      %s = guestfs_%s " n name;
-  generate_call_args ~handle:"g" (snd style);
+  generate_c_call_args ~handle:"g" style;
   pr ";\n";
   do_cleanups ();
   pr "      if (%s == NULL)\n" n;
@@ -6137,6 +6434,9 @@ and generate_perl_struct_list_code typ cols name style n do_cleanups =
     | name, FUUID ->
        pr "        (void) hv_store (hv, \"%s\", %d, newSVpv (%s->val[i].%s, 32), 0);\n"
          name (String.length name) n name
+    | name, FBuffer ->
+       pr "        (void) hv_store (hv, \"%s\", %d, newSVpv (%s->val[i].%s, %s->val[i].%s_len), 0);\n"
+         name (String.length name) n name n name
     | name, (FBytes|FUInt64) ->
        pr "        (void) hv_store (hv, \"%s\", %d, my_newSVull (%s->val[i].%s), 0);\n"
          name (String.length name) n name
@@ -6162,7 +6462,7 @@ and generate_perl_struct_code typ cols name style n do_cleanups =
   pr "      struct guestfs_%s *%s;\n" typ n;
   pr " PPCODE:\n";
   pr "      %s = guestfs_%s " n name;
-  generate_call_args ~handle:"g" (snd style);
+  generate_c_call_args ~handle:"g" style;
   pr ";\n";
   do_cleanups ();
   pr "      if (%s == NULL)\n" n;
@@ -6176,6 +6476,9 @@ and generate_perl_struct_code typ cols name style n do_cleanups =
       | name, FString ->
          pr "      PUSHs (sv_2mortal (newSVpv (%s->%s, 0)));\n"
            n name
+      | name, FBuffer ->
+         pr "      PUSHs (sv_2mortal (newSVpv (%s->%s, %s->%s_len)));\n"
+           n name n name
       | name, FUUID ->
          pr "      PUSHs (sv_2mortal (newSVpv (%s->%s, 32)));\n"
            n name
@@ -6332,7 +6635,8 @@ and generate_perl_prototype name style =
    | RInt n
    | RInt64 n
    | RConstString n
-   | RString n -> pr "$%s = " n
+   | RString n
+   | RBufferOut n -> pr "$%s = " n
    | RStruct (n,_)
    | RHashtable n -> pr "%%%s = " n
    | RStringList n
@@ -6508,6 +6812,10 @@ py_guestfs_close (PyObject *self, PyObject *args)
            pr "  PyDict_SetItemString (dict, \"%s\",\n" name;
            pr "                        PyString_FromString (%s->%s));\n"
              typ name
+       | name, FBuffer ->
+           pr "  PyDict_SetItemString (dict, \"%s\",\n" name;
+           pr "                        PyString_FromStringAndSize (%s->%s, %s->%s_len));\n"
+             typ name typ name
        | name, FUUID ->
            pr "  PyDict_SetItemString (dict, \"%s\",\n" name;
            pr "                        PyString_FromStringAndSize (%s->%s, 32));\n"
@@ -6579,7 +6887,11 @@ py_guestfs_close (PyObject *self, PyObject *args)
        | RStringList _ | RHashtable _ -> pr "  char **r;\n"; "NULL"
        | RStruct (_, typ) -> pr "  struct guestfs_%s *r;\n" typ; "NULL"
        | RStructList (_, typ) ->
-           pr "  struct guestfs_%s_list *r;\n" typ; "NULL" in
+           pr "  struct guestfs_%s_list *r;\n" typ; "NULL"
+       | RBufferOut _ ->
+           pr "  char *r;\n";
+           pr "  size_t size;\n";
+           "NULL" in
 
       List.iter (
        function
@@ -6630,7 +6942,7 @@ py_guestfs_close (PyObject *self, PyObject *args)
       pr "\n";
 
       pr "  r = guestfs_%s " name;
-      generate_call_args ~handle:"g" (snd style);
+      generate_c_call_args ~handle:"g" style;
       pr ";\n";
 
       List.iter (
@@ -6669,6 +6981,9 @@ py_guestfs_close (PyObject *self, PyObject *args)
        | RHashtable n ->
           pr "  py_r = put_table (r);\n";
           pr "  free_strings (r);\n"
+       | RBufferOut _ ->
+          pr "  py_r = PyString_FromStringAndSize (r, size);\n";
+          pr "  free (r);\n"
       );
 
       pr "  return py_r;\n";
@@ -6772,7 +7087,7 @@ class GuestFS:
   List.iter (
     fun (name, style, _, flags, _, _, longdesc) ->
       pr "    def %s " name;
-      generate_call_args ~handle:"self" (snd style);
+      generate_py_call_args ~handle:"self" (snd style);
       pr ":\n";
 
       if not (List.mem NotInDocs flags) then (
@@ -6780,7 +7095,7 @@ class GuestFS:
        let doc =
           match fst style with
          | RErr | RInt _ | RInt64 _ | RBool _ | RConstString _
-         | RString _ -> doc
+         | RString _ | RBufferOut _ -> doc
          | RStringList _ ->
              doc ^ "\n\nThis function returns a list of strings."
          | RStruct (_, typ) ->
@@ -6803,11 +7118,17 @@ class GuestFS:
        pr "        u\"\"\"%s\"\"\"\n" doc;
       );
       pr "        return libguestfsmod.%s " name;
-      generate_call_args ~handle:"self._o" (snd style);
+      generate_py_call_args ~handle:"self._o" (snd style);
       pr "\n";
       pr "\n";
   ) all_functions
 
+(* Generate Python call arguments, eg "(handle, foo, bar)" *)
+and generate_py_call_args ~handle args =
+  pr "(%s" handle;
+  List.iter (fun arg -> pr ", %s" (name_of_argt arg)) args;
+  pr ")"
+
 (* Useful if you need the longdesc POD text as plain text.  Returns a
  * list of lines.
  *
@@ -6960,11 +7281,15 @@ static VALUE ruby_guestfs_close (VALUE gv)
        | RStringList _ | RHashtable _ -> pr "  char **r;\n"; "NULL"
        | RStruct (_, typ) -> pr "  struct guestfs_%s *r;\n" typ; "NULL"
        | RStructList (_, typ) ->
-           pr "  struct guestfs_%s_list *r;\n" typ; "NULL" in
+           pr "  struct guestfs_%s_list *r;\n" typ; "NULL"
+       | RBufferOut _ ->
+           pr "  char *r;\n";
+           pr "  size_t size;\n";
+           "NULL" in
       pr "\n";
 
       pr "  r = guestfs_%s " name;
-      generate_call_args ~handle:"g" (snd style);
+      generate_c_call_args ~handle:"g" style;
       pr ";\n";
 
       List.iter (
@@ -7017,6 +7342,10 @@ static VALUE ruby_guestfs_close (VALUE gv)
           pr "  }\n";
           pr "  free (r);\n";
           pr "  return rv;\n"
+       | RBufferOut _ ->
+          pr "  VALUE rv = rb_str_new (r, size);\n";
+          pr "  free (r);\n";
+          pr "  return rv;\n";
       );
 
       pr "}\n";
@@ -7051,6 +7380,8 @@ and generate_ruby_struct_code typ cols =
     function
     | name, FString ->
        pr "  rb_hash_aset (rv, rb_str_new2 (\"%s\"), rb_str_new2 (r->%s));\n" name name
+    | name, FBuffer ->
+       pr "  rb_hash_aset (rv, rb_str_new2 (\"%s\"), rb_str_new (r->%s, r->%s_len));\n" name name name
     | name, FUUID ->
        pr "  rb_hash_aset (rv, rb_str_new2 (\"%s\"), rb_str_new (r->%s, 32));\n" name name
     | name, (FBytes|FUInt64) ->
@@ -7079,6 +7410,8 @@ and generate_ruby_struct_list_code typ cols =
     function
     | name, FString ->
        pr "    rb_hash_aset (hv, rb_str_new2 (\"%s\"), rb_str_new2 (r->val[i].%s));\n" name name
+    | name, FBuffer ->
+       pr "    rb_hash_aset (hv, rb_str_new2 (\"%s\"), rb_str_new (r->val[i].%s, r->val[i].%s_len));\n" name name name
     | name, FUUID ->
        pr "    rb_hash_aset (hv, rb_str_new2 (\"%s\"), rb_str_new (r->val[i].%s, 32));\n" name name
     | name, (FBytes|FUInt64) ->
@@ -7206,7 +7539,7 @@ public class GuestFS {
       pr "    ";
       if fst style <> RErr then pr "return ";
       pr "_%s " name;
-      generate_call_args ~handle:"g" (snd style);
+      generate_java_call_args ~handle:"g" (snd style);
       pr ";\n";
       pr "  }\n";
       pr "  ";
@@ -7217,6 +7550,12 @@ public class GuestFS {
 
   pr "}\n"
 
+(* Generate Java call arguments, eg "(handle, foo, bar)" *)
+and generate_java_call_args ~handle args =
+  pr "(%s" handle;
+  List.iter (fun arg -> pr ", %s" (name_of_argt arg)) args;
+  pr ")"
+
 and generate_java_prototype ?(public=false) ?(privat=false) ?(native=false)
     ?(semicolon=true) name style =
   if privat then pr "private ";
@@ -7229,7 +7568,7 @@ and generate_java_prototype ?(public=false) ?(privat=false) ?(native=false)
    | RInt _ -> pr "int ";
    | RInt64 _ -> pr "long ";
    | RBool _ -> pr "boolean ";
-   | RConstString _ | RString _ -> pr "String ";
+   | RConstString _ | RString _ | RBufferOut _ -> pr "String ";
    | RStringList _ -> pr "String[] ";
    | RStruct (_, typ) ->
        let name = java_name_of_struct typ in
@@ -7290,7 +7629,8 @@ public class %s {
   List.iter (
     function
     | name, FString
-    | name, FUUID -> pr "  public String %s;\n" name
+    | name, FUUID
+    | name, FBuffer -> pr "  public String %s;\n" name
     | name, (FBytes|FUInt64|FInt64) -> pr "  public long %s;\n" name
     | name, (FUInt32|FInt32) -> pr "  public int %s;\n" name
     | name, FChar -> pr "  public char %s;\n" name
@@ -7357,7 +7697,7 @@ Java_com_redhat_et_libguestfs_GuestFS__1close
        | RInt _ -> pr "jint ";
        | RInt64 _ -> pr "jlong ";
        | RBool _ -> pr "jboolean ";
-       | RConstString _ | RString _ -> pr "jstring ";
+       | RConstString _ | RString _ | RBufferOut _ -> pr "jstring ";
        | RStruct _ | RHashtable _ ->
           pr "jobject ";
        | RStringList _ | RStructList _ ->
@@ -7412,7 +7752,12 @@ Java_com_redhat_et_libguestfs_GuestFS__1close
            pr "  jfieldID fl;\n";
            pr "  jobject jfl;\n";
            pr "  struct guestfs_%s_list *r;\n" typ; "NULL", "NULL"
-       | RHashtable _ -> pr "  char **r;\n"; "NULL", "NULL" in
+       | RHashtable _ -> pr "  char **r;\n"; "NULL", "NULL"
+       | RBufferOut _ ->
+           pr "  jstring jr;\n";
+           pr "  char *r;\n";
+           pr "  size_t size;\n";
+           "NULL", "NULL" in
       List.iter (
        function
        | String n
@@ -7432,7 +7777,7 @@ Java_com_redhat_et_libguestfs_GuestFS__1close
        (match fst style with
         | RStringList _ | RStructList _ -> true
         | RErr | RBool _ | RInt _ | RInt64 _ | RConstString _
-        | RString _ | RStruct _ | RHashtable _ -> false) ||
+        | RString _ | RBufferOut _ | RStruct _ | RHashtable _ -> false) ||
          List.exists (function StringList _ -> true | _ -> false) (snd style) in
       if needs_i then
        pr "  int i;\n";
@@ -7467,7 +7812,7 @@ Java_com_redhat_et_libguestfs_GuestFS__1close
 
       (* Make the call. *)
       pr "  r = guestfs_%s " name;
-      generate_call_args ~handle:"g" (snd style);
+      generate_c_call_args ~handle:"g" style;
       pr ";\n";
 
       (* Release the parameters. *)
@@ -7532,6 +7877,10 @@ Java_com_redhat_et_libguestfs_GuestFS__1close
           (* XXX *)
           pr "  throw_exception (env, \"%s: internal error: please let us know how to make a Java HashMap from JNI bindings!\");\n" name;
           pr "  return NULL;\n"
+       | RBufferOut _ ->
+          pr "  jr = (*env)->NewStringUTF (env, r); /* XXX size */\n";
+          pr "  free (r);\n";
+          pr "  return jr;\n"
       );
 
       pr "}\n";
@@ -7554,6 +7903,15 @@ and generate_java_struct_return typ jtyp cols =
        pr "    fl = (*env)->GetFieldID (env, cl, \"%s\", \"Ljava/lang/String;\");\n" name;
        pr "    (*env)->SetObjectField (env, jr, fl, (*env)->NewStringUTF (env, s));\n";
        pr "  }\n";
+    | name, FBuffer ->
+       pr "  {\n";
+       pr "    int len = r->%s_len;\n" name;
+       pr "    char s[len+1];\n";
+       pr "    memcpy (s, r->%s, len);\n" name;
+       pr "    s[len] = 0;\n";
+       pr "    fl = (*env)->GetFieldID (env, cl, \"%s\", \"Ljava/lang/String;\");\n" name;
+       pr "    (*env)->SetObjectField (env, jr, fl, (*env)->NewStringUTF (env, s));\n";
+       pr "  }\n";
     | name, (FBytes|FUInt64|FInt64) ->
        pr "  fl = (*env)->GetFieldID (env, cl, \"%s\", \"J\");\n" name;
        pr "  (*env)->SetLongField (env, jr, fl, r->%s);\n" name;
@@ -7588,6 +7946,15 @@ and generate_java_struct_list_return typ jtyp cols =
        pr "      fl = (*env)->GetFieldID (env, cl, \"%s\", \"Ljava/lang/String;\");\n" name;
        pr "      (*env)->SetObjectField (env, jfl, fl, (*env)->NewStringUTF (env, s));\n";
        pr "    }\n";
+    | name, FBuffer ->
+       pr "    {\n";
+       pr "      int len = r->val[i].%s_len;\n" name;
+       pr "      char s[len+1];\n";
+       pr "      memcpy (s, r->val[i].%s, len);\n" name;
+       pr "      s[len] = 0;\n";
+       pr "      fl = (*env)->GetFieldID (env, cl, \"%s\", \"Ljava/lang/String;\");\n" name;
+       pr "      (*env)->SetObjectField (env, jfl, fl, (*env)->NewStringUTF (env, s));\n";
+       pr "    }\n";
     | name, (FBytes|FUInt64|FInt64) ->
        pr "    fl = (*env)->GetFieldID (env, cl, \"%s\", \"J\");\n" name;
        pr "    (*env)->SetLongField (env, jfl, fl, r->val[i].%s);\n" name;
@@ -7623,7 +7990,8 @@ and generate_haskell_hs () =
     | RStringList _, _
     | RStruct _, _
     | RStructList _, _
-    | RHashtable _, _ -> false in
+    | RHashtable _, _
+    | RBufferOut _, _ -> false in
 
   pr "\
 {-# INCLUDE <guestfs.h> #-}
@@ -7733,7 +8101,7 @@ last_error h = do
             pr "      err <- last_error h\n";
             pr "      fail err\n";
         | RConstString _ | RString _ | RStringList _ | RStruct _
-        | RStructList _ | RHashtable _ ->
+        | RStructList _ | RHashtable _ | RBufferOut _ ->
             pr "  if (r == nullPtr)\n";
             pr "    then do\n";
             pr "      err <- last_error h\n";
@@ -7753,7 +8121,8 @@ last_error h = do
         | RStringList _
         | RStruct _
         | RStructList _
-        | RHashtable _ ->
+        | RHashtable _
+        | RBufferOut _ ->
             pr "    else return ()\n" (* XXXXXXXXXXXXXXXXXXXX *)
        );
        pr "\n";
@@ -7795,6 +8164,7 @@ and generate_haskell_prototype ~handle ?(hs = false) style =
        let name = java_name_of_struct typ in
        pr "[%s]" name
    | RHashtable _ -> pr "Hashtable"
+   | RBufferOut _ -> pr "%s" string
   );
   pr ")"
 
@@ -7918,6 +8288,8 @@ print_strings (char * const* const argv)
             pr "  }\n";
             pr "  strs[n*2] = NULL;\n";
             pr "  return strs;\n"
+        | RBufferOut _ ->
+            pr "  return strdup (val);\n"
        );
        pr "}\n";
        pr "\n"
@@ -7933,7 +8305,8 @@ print_strings (char * const* const argv)
         | RConstString _
         | RString _ | RStringList _ | RStruct _
         | RStructList _
-        | RHashtable _ ->
+        | RHashtable _
+        | RBufferOut _ ->
             pr "  return NULL;\n"
        );
        pr "}\n";
@@ -8225,7 +8598,7 @@ let output_to filename =
 let () =
   check_functions ();
 
-  if not (Sys.file_exists "config.status") then (
+  if not (Sys.file_exists "HACKING") then (
     eprintf "\
 You are probably running this from the wrong directory.
 Run it from the top source directory using the command