*)
| FileIn of string
| FileOut of string
-(* Not implemented:
(* Opaque buffer which can contain arbitrary 8 bit data.
- * In the C API, this is expressed as <char *, int> pair.
+ * In the C API, this is expressed as <const char *, size_t> pair.
* Most other languages have a string type which can contain
* ASCII NUL. We use whatever type is appropriate for each
* language.
* To return an arbitrary buffer, use RBufferOut.
*)
| BufferIn of string
-*)
type flags =
| ProtocolLimitWarning (* display warning about protocol size limits *)
Int64 "integer64";
FileIn "filein";
FileOut "fileout";
+ BufferIn "bufferin";
]
let test_all_rets = [
| CallInt of int
| CallInt64 of int64
| CallBool of bool
+ | CallBuffer of string
(* Used to memoize the result of pod2text. *)
let pod2text_memo_filename = "src/.pod2text.data"
done;
!count
+let explode str =
+ let r = ref [] in
+ for i = 0 to String.length str - 1 do
+ let c = String.unsafe_get str i in
+ r := c :: !r;
+ done;
+ List.rev !r
+
+let map_chars f str =
+ List.map f (explode str)
+
let name_of_argt = function
| Pathname n | Device n | Dev_or_Path n | String n | OptString n
| StringList n | DeviceList n | Bool n | Int n | Int64 n
- | FileIn n | FileOut n -> n
+ | FileIn n | FileOut n | BufferIn n -> n
let java_name_of_struct typ =
try List.assoc typ java_structs
| Bool n -> pr " bool %s;\n" n
| Int n -> pr " int %s;\n" n
| Int64 n -> pr " hyper %s;\n" n
+ | BufferIn n ->
+ pr " opaque %s<>;\n" n
| FileIn _ | FileOut _ -> ()
) args;
pr "};\n\n"
| Pathname n
| Dev_or_Path n
| FileIn n
- | FileOut n ->
+ | FileOut n
+ | BufferIn n ->
(* guestfish doesn't support string escaping, so neither do we *)
pr " printf (\" \\\"%%s\\\"\", %s);\n" n
| OptString n -> (* string option *)
| Int64 n ->
pr " args.%s = %s;\n" n n
| FileIn _ | FileOut _ -> ()
+ | BufferIn n ->
+ pr " /* Just catch grossly large sizes. XDR encoding will make this precise. */\n";
+ pr " if (%s_size >= GUESTFS_MESSAGE_MAX) {\n" n;
+ pr " error (g, \"%%s: size of input buffer too large\", \"%s\");\n"
+ shortname;
+ pr " guestfs___end_busy (g);\n";
+ pr " return %s;\n" error_code;
+ pr " }\n";
+ pr " args.%s.%s_val = (char *) %s;\n" n n n;
+ pr " args.%s.%s_len = %s_size;\n" n n n
) args;
pr " serial = guestfs___send (g, GUESTFS_PROC_%s,\n"
(String.uppercase shortname);
| Int n -> pr " int %s;\n" n
| Int64 n -> pr " int64_t %s;\n" n
| FileIn _ | FileOut _ -> ()
+ | BufferIn n ->
+ pr " const char *%s;\n" n;
+ pr " size_t %s_size;\n" n
) args
);
pr "\n";
| Int n -> pr " %s = args.%s;\n" n n
| Int64 n -> pr " %s = args.%s;\n" n n
| FileIn _ | FileOut _ -> ()
+ | BufferIn n ->
+ pr " %s = args.%s.%s_val;\n" n n n;
+ pr " %s_size = args.%s.%s_len;\n" n n n
) args;
pr "\n"
);
-
(* this is used at least for do_equal *)
if List.exists (function Pathname _ -> true | _ -> false) (snd style) then (
(* Emit NEED_ROOT just once, even when there are two or
| String n, arg
| OptString n, arg ->
pr " const char *%s = \"%s\";\n" n (c_quote arg);
+ | BufferIn n, arg ->
+ pr " const char *%s = \"%s\";\n" n (c_quote arg);
+ pr " size_t %s_size = %d;\n" n (String.length arg)
| Int _, _
| Int64 _, _
| Bool _, _
| String n, _
| OptString n, _ ->
pr ", %s" n
+ | BufferIn n, _ ->
+ pr ", %s, %s_size" n n
| FileIn _, arg | FileOut _, arg ->
pr ", \"%s\"" (c_quote arg)
| StringList n, _ | DeviceList n, _ ->
| Dev_or_Path n
| FileIn n
| FileOut n -> pr " char *%s;\n" n
+ | BufferIn n ->
+ pr " const char *%s;\n" n;
+ pr " size_t %s_size;\n" n
| StringList n | DeviceList n -> pr " char **%s;\n" n
| Bool n -> pr " int %s;\n" n
| Int n -> pr " int %s;\n" n
| OptString name ->
pr " %s = STRNEQ (argv[%d], \"\") ? argv[%d] : NULL;\n"
name i i
+ | BufferIn name ->
+ pr " %s = argv[%d];\n" name i;
+ pr " %s_size = strlen (argv[%d]);\n" name i
| FileIn name ->
pr " %s = file_in (argv[%d]);\n" name i;
pr " if (%s == NULL) return -1;\n" name
function
| Device name | String name
| OptString name | Bool name
- | Int name | Int64 name -> ()
+ | Int name | Int64 name
+ | BufferIn name -> ()
| Pathname name | Dev_or_Path name | FileOut name ->
pr " free (%s);\n" name
| FileIn name ->
| Int n -> pr " %s" n
| Int64 n -> pr " %s" n
| FileIn n | FileOut n -> pr " (%s|-)" n
+ | BufferIn n -> pr " %s" n
) (snd style);
pr "\n";
pr "\n";
| FileIn n
| FileOut n ->
if not in_daemon then (next (); pr "const char *%s" n)
+ | BufferIn n ->
+ next ();
+ pr "const char *%s" n;
+ next ();
+ pr "size_t %s_size" n
) (snd style);
if is_RBufferOut then (next (); pr "size_t *size_r");
);
| Some handle -> pr "%s" handle; comma := true
);
List.iter (
- fun arg ->
- next ();
- pr "%s" (name_of_argt arg)
+ function
+ | BufferIn n ->
+ next ();
+ pr "%s, %s_size" n n
+ | arg ->
+ next ();
+ pr "%s" (name_of_argt arg)
) (snd style);
(* For RBufferOut calls, add implicit &size parameter. *)
if not decl then (
pr " const char *%s =\n" n;
pr " %sv != Val_int (0) ? String_val (Field (%sv, 0)) : NULL;\n"
n n
+ | BufferIn n ->
+ pr " const char *%s = String_val (%sv);\n" n n;
+ pr " size_t %s_size = caml_string_length (%sv);\n" n n
| StringList n | DeviceList n ->
pr " char **%s = ocaml_guestfs_strings_val (g, %sv);\n" n n
| Bool n ->
pr " ocaml_guestfs_free_strings (%s);\n" n;
| Pathname _ | Device _ | Dev_or_Path _ | String _ | OptString _
| Bool _ | Int _ | Int64 _
- | FileIn _ | FileOut _ -> ()
+ | FileIn _ | FileOut _ | BufferIn _ -> ()
) (snd style);
pr " if (r == %s)\n" error_code;
pr "%s : t -> " name;
List.iter (
function
- | Pathname _ | Device _ | Dev_or_Path _ | String _ | FileIn _ | FileOut _ -> pr "string -> "
+ | Pathname _ | Device _ | Dev_or_Path _ | String _ | FileIn _ | FileOut _
+ | BufferIn _ -> pr "string -> "
| OptString _ -> pr "string option -> "
| StringList _ | DeviceList _ -> pr "string array -> "
| Bool _ -> pr "bool -> "
pr "void\n" (* all lists returned implictly on the stack *)
);
(* Call and arguments. *)
- pr "%s " name;
- generate_c_call_args ~handle:"g" ~decl:true style;
- pr "\n";
+ pr "%s (g" name;
+ List.iter (
+ fun arg -> pr ", %s" (name_of_argt arg)
+ ) (snd style);
+ pr ")\n";
pr " guestfs_h *g;\n";
iteri (
fun i ->
function
- | Pathname n | Device n | Dev_or_Path n | String n | FileIn n | FileOut n ->
+ | Pathname n | Device n | Dev_or_Path n | String n
+ | FileIn n | FileOut n ->
pr " char *%s;\n" n
+ | BufferIn n ->
+ pr " char *%s;\n" n;
+ pr " size_t %s_size = SvCUR (ST(%d));\n" n (i+1)
| OptString n ->
(* http://www.perlmonks.org/?node_id=554277
* Note that the implicit handle argument means we have
function
| Pathname _ | Device _ | Dev_or_Path _ | String _ | OptString _
| Bool _ | Int _ | Int64 _
- | FileIn _ | FileOut _ -> ()
+ | FileIn _ | FileOut _
+ | BufferIn _ -> ()
| StringList n | DeviceList n -> pr " free (%s);\n" n
) (snd style)
in
comma := true;
match arg with
| Pathname n | Device n | Dev_or_Path n | String n
- | OptString n | Bool n | Int n | Int64 n | FileIn n | FileOut n ->
+ | OptString n | Bool n | Int n | Int64 n | FileIn n | FileOut n
+ | BufferIn n ->
pr "$%s" n
| StringList n | DeviceList n ->
pr "\\@%s" n
generate_header CStyle LGPLv2plus;
pr "\
+#define PY_SSIZE_T_CLEAN 1
#include <Python.h>
#include <stdio.h>
List.iter (
function
- | Pathname n | Device n | Dev_or_Path n | String n | FileIn n | FileOut n ->
+ | Pathname n | Device n | Dev_or_Path n | String n
+ | FileIn n | FileOut n ->
pr " const char *%s;\n" n
| OptString n -> pr " const char *%s;\n" n
+ | BufferIn n ->
+ pr " const char *%s;\n" n;
+ pr " Py_ssize_t %s_size;\n" n
| StringList n | DeviceList n ->
pr " PyObject *py_%s;\n" n;
pr " char **%s;\n" n
| Int64 _ -> pr "L" (* XXX Whoever thought it was a good idea to
* emulate C's int/long/long long in Python?
*)
+ | BufferIn _ -> pr "s#"
) (snd style);
pr ":guestfs_%s\",\n" name;
pr " &py_g";
| Bool n -> pr ", &%s" n
| Int n -> pr ", &%s" n
| Int64 n -> pr ", &%s" n
+ | BufferIn n -> pr ", &%s, &%s_size" n n
) (snd style);
pr "))\n";
List.iter (
function
| Pathname _ | Device _ | Dev_or_Path _ | String _
- | FileIn _ | FileOut _ | OptString _ | Bool _ | Int _ | Int64 _ -> ()
+ | FileIn _ | FileOut _ | OptString _ | Bool _ | Int _ | Int64 _
+ | BufferIn _ -> ()
| StringList n | DeviceList n ->
pr " %s = get_string_list (py_%s);\n" n n;
pr " if (!%s) return NULL;\n" n
List.iter (
function
| Pathname _ | Device _ | Dev_or_Path _ | String _
- | FileIn _ | FileOut _ | OptString _ | Bool _ | Int _ | Int64 _ -> ()
+ | FileIn _ | FileOut _ | OptString _ | Bool _ | Int _ | Int64 _
+ | BufferIn _ -> ()
| StringList n | DeviceList n ->
pr " free (%s);\n" n
) (snd style);
pr " if (!%s)\n" n;
pr " rb_raise (rb_eTypeError, \"expected string for parameter %%s of %%s\",\n";
pr " \"%s\", \"%s\");\n" n name
+ | BufferIn n ->
+ pr " Check_Type (%sv, T_STRING);\n" n;
+ pr " const char *%s = RSTRING (%sv)->ptr;\n" n n;
+ pr " if (!%s)\n" n;
+ pr " rb_raise (rb_eTypeError, \"expected string for parameter %%s of %%s\",\n";
+ pr " \"%s\", \"%s\");\n" n name;
+ pr " size_t %s_size = RSTRING (%sv)->len;\n" n n
| OptString n ->
pr " const char *%s = !NIL_P (%sv) ? StringValueCStr (%sv) : NULL;\n" n n n
| StringList n | DeviceList n ->
List.iter (
function
| Pathname _ | Device _ | Dev_or_Path _ | String _
- | FileIn _ | FileOut _ | OptString _ | Bool _ | Int _ | Int64 _ -> ()
+ | FileIn _ | FileOut _ | OptString _ | Bool _ | Int _ | Int64 _
+ | BufferIn _ -> ()
| StringList n | DeviceList n ->
pr " free (%s);\n" n
) (snd style);
| FileIn n
| FileOut n ->
pr "String %s" n
+ | BufferIn n ->
+ pr "byte[] %s" n
| StringList n | DeviceList n ->
pr "String[] %s" n
| Bool n ->
| FileIn n
| FileOut n ->
pr ", jstring j%s" n
+ | BufferIn n ->
+ pr ", jbyteArray j%s" n
| StringList n | DeviceList n ->
pr ", jobjectArray j%s" n
| Bool n ->
| FileIn n
| FileOut n ->
pr " const char *%s;\n" n
+ | BufferIn n ->
+ pr " jbyte *%s;\n" n;
+ pr " size_t %s_size;\n" n
| StringList n | DeviceList n ->
pr " int %s_len;\n" n;
pr " const char **%s;\n" n
* a NULL parameter.
*)
pr " %s = j%s ? (*env)->GetStringUTFChars (env, j%s, NULL) : NULL;\n" n n n
+ | BufferIn n ->
+ pr " %s = (*env)->GetByteArrayElements (env, j%s, NULL);\n" n n;
+ pr " %s_size = (*env)->GetArrayLength (env, j%s);\n" n n
| StringList n | DeviceList n ->
pr " %s_len = (*env)->GetArrayLength (env, j%s);\n" n n;
pr " %s = guestfs_safe_malloc (g, sizeof (char *) * (%s_len+1));\n" n n;
| OptString n ->
pr " if (j%s)\n" n;
pr " (*env)->ReleaseStringUTFChars (env, j%s, %s);\n" n n
+ | BufferIn n ->
+ pr " (*env)->ReleaseByteArrayElements (env, j%s, %s, 0);\n" n n
| StringList n | DeviceList n ->
pr " for (i = 0; i < %s_len; ++i) {\n" n;
pr " jobject o = (*env)->GetObjectArrayElement (env, j%s, i);\n"
function
| FileIn n
| FileOut n
- | Pathname n | Device n | Dev_or_Path n | String n -> pr "withCString %s $ \\%s -> " n n
+ | Pathname n | Device n | Dev_or_Path n | String n ->
+ pr "withCString %s $ \\%s -> " n n
+ | BufferIn n ->
+ pr "withCStringLen %s $ \\(%s, %s_size) -> " n n n
| OptString n -> pr "maybeWith withCString %s $ \\%s -> " n n
| StringList n | DeviceList n -> pr "withMany withCString %s $ \\%s -> withArray0 nullPtr %s $ \\%s -> " n n n n
| Bool _ | Int _ | Int64 _ -> ()
| Int64 n -> sprintf "(fromIntegral %s)" n
| FileIn n | FileOut n
| Pathname n | Device n | Dev_or_Path n | String n | OptString n | StringList n | DeviceList n -> n
+ | BufferIn n -> sprintf "%s (fromIntegral %s_size)" n n
) (snd style) in
pr "withForeignPtr h (\\p -> c_%s %s)\n" name
(String.concat " " ("p" :: args));
fun arg ->
(match arg with
| Pathname _ | Device _ | Dev_or_Path _ | String _ -> pr "%s" string
+ | BufferIn _ ->
+ if hs then pr "String"
+ else pr "CString -> CInt"
| OptString _ -> if hs then pr "Maybe String" else pr "CString"
| StringList _ | DeviceList _ -> if hs then pr "[String]" else pr "Ptr CString"
| Bool _ -> pr "%s" bool
List.iter (
function
| Pathname n | Device n | Dev_or_Path n | String n | OptString n
- | FileIn n | FileOut n ->
+ | FileIn n | FileOut n
+ | BufferIn n ->
pr ", [In] string %s" n
| StringList n | DeviceList n ->
pr ", [In] string[] %s" n
List.iter (
function
| Pathname n | Device n | Dev_or_Path n | String n | OptString n
- | FileIn n | FileOut n ->
+ | FileIn n | FileOut n
+ | BufferIn n ->
next (); pr "string %s" n
| StringList n | DeviceList n ->
next (); pr "string[] %s" n
| String n
| FileIn n
| FileOut n -> pr " printf (\"%%s\\n\", %s);\n" n
+ | BufferIn n ->
+ pr " for (size_t i = 0; i < %s_size; ++i)\n" n;
+ pr " printf (\"<%%02x>\", %s[i]);\n" n;
+ pr " printf (\"\\n\");\n"
| OptString n -> pr " printf (\"%%s\\n\", %s ? %s : \"null\");\n" n n
| StringList n | DeviceList n -> pr " print_strings (%s);\n" n
| Bool n -> pr " printf (\"%%s\\n\", %s ? \"true\" : \"false\");\n" n
| CallInt64 i when i >= 0L -> Int64.to_string i ^ "L"
| CallInt64 i (* when i < 0L *) -> "(" ^ Int64.to_string i ^ "L)"
| CallBool b -> string_of_bool b
+ | CallBuffer s -> sprintf "%S" s
) args
)
in
| CallInt i -> string_of_int i
| CallInt64 i -> Int64.to_string i
| CallBool b -> if b then "1" else "0"
+ | CallBuffer s -> "\"" ^ c_quote s ^ "\""
) args
)
in
| CallInt i -> string_of_int i
| CallInt64 i -> Int64.to_string i
| CallBool b -> if b then "1" else "0"
+ | CallBuffer s -> "\"" ^ c_quote s ^ "\""
) args
)
in
| CallInt i -> string_of_int i
| CallInt64 i -> Int64.to_string i
| CallBool b -> string_of_bool b
+ | CallBuffer s -> "\"" ^ c_quote s ^ "\""
) args
)
in
| CallInt i -> string_of_int i
| CallInt64 i -> Int64.to_string i
| CallBool b -> string_of_bool b
+ | CallBuffer s ->
+ "new byte[] { " ^ String.concat "," (
+ map_chars (fun c -> string_of_int (Char.code c)) s
+ ) ^ " }"
) args
)
in
| CallInt64 i -> Int64.to_string i
| CallBool true -> "True"
| CallBool false -> "False"
+ | CallBuffer s -> "\"" ^ c_quote s ^ "\""
) args
)
in
and generate_lang_bindtests call =
call "test0" [CallString "abc"; CallOptString (Some "def");
CallStringList []; CallBool false;
- CallInt 0; CallInt64 0L; CallString "123"; CallString "456"];
+ CallInt 0; CallInt64 0L; CallString "123"; CallString "456";
+ CallBuffer "abc\000abc"];
call "test0" [CallString "abc"; CallOptString None;
CallStringList []; CallBool false;
- CallInt 0; CallInt64 0L; CallString "123"; CallString "456"];
+ CallInt 0; CallInt64 0L; CallString "123"; CallString "456";
+ CallBuffer "abc\000abc"];
call "test0" [CallString ""; CallOptString (Some "def");
CallStringList []; CallBool false;
- CallInt 0; CallInt64 0L; CallString "123"; CallString "456"];
+ CallInt 0; CallInt64 0L; CallString "123"; CallString "456";
+ CallBuffer "abc\000abc"];
call "test0" [CallString ""; CallOptString (Some "");
CallStringList []; CallBool false;
- CallInt 0; CallInt64 0L; CallString "123"; CallString "456"];
+ CallInt 0; CallInt64 0L; CallString "123"; CallString "456";
+ CallBuffer "abc\000abc"];
call "test0" [CallString "abc"; CallOptString (Some "def");
CallStringList ["1"]; CallBool false;
- CallInt 0; CallInt64 0L; CallString "123"; CallString "456"];
+ CallInt 0; CallInt64 0L; CallString "123"; CallString "456";
+ CallBuffer "abc\000abc"];
call "test0" [CallString "abc"; CallOptString (Some "def");
CallStringList ["1"; "2"]; CallBool false;
- CallInt 0; CallInt64 0L; CallString "123"; CallString "456"];
+ CallInt 0; CallInt64 0L; CallString "123"; CallString "456";
+ CallBuffer "abc\000abc"];
call "test0" [CallString "abc"; CallOptString (Some "def");
CallStringList ["1"]; CallBool true;
- CallInt 0; CallInt64 0L; CallString "123"; CallString "456"];
+ CallInt 0; CallInt64 0L; CallString "123"; CallString "456";
+ CallBuffer "abc\000abc"];
call "test0" [CallString "abc"; CallOptString (Some "def");
CallStringList ["1"]; CallBool false;
- CallInt (-1); CallInt64 (-1L); CallString "123"; CallString "456"];
+ CallInt (-1); CallInt64 (-1L); CallString "123"; CallString "456";
+ CallBuffer "abc\000abc"];
call "test0" [CallString "abc"; CallOptString (Some "def");
CallStringList ["1"]; CallBool false;
- CallInt (-2); CallInt64 (-2L); CallString "123"; CallString "456"];
+ CallInt (-2); CallInt64 (-2L); CallString "123"; CallString "456";
+ CallBuffer "abc\000abc"];
call "test0" [CallString "abc"; CallOptString (Some "def");
CallStringList ["1"]; CallBool false;
- CallInt 1; CallInt64 1L; CallString "123"; CallString "456"];
+ CallInt 1; CallInt64 1L; CallString "123"; CallString "456";
+ CallBuffer "abc\000abc"];
call "test0" [CallString "abc"; CallOptString (Some "def");
CallStringList ["1"]; CallBool false;
- CallInt 2; CallInt64 2L; CallString "123"; CallString "456"];
+ CallInt 2; CallInt64 2L; CallString "123"; CallString "456";
+ CallBuffer "abc\000abc"];
call "test0" [CallString "abc"; CallOptString (Some "def");
CallStringList ["1"]; CallBool false;
- CallInt 4095; CallInt64 4095L; CallString "123"; CallString "456"];
+ CallInt 4095; CallInt64 4095L; CallString "123"; CallString "456";
+ CallBuffer "abc\000abc"];
call "test0" [CallString "abc"; CallOptString (Some "def");
CallStringList ["1"]; CallBool false;
- CallInt 0; CallInt64 0L; CallString ""; CallString ""]
+ CallInt 0; CallInt64 0L; CallString ""; CallString "";
+ CallBuffer "abc\000abc"]
(* XXX Add here tests of the return and error functions. *)