2 * Copyright (C) 2009-2010 Red Hat Inc.
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.
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.
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
19 (* Please read generator/README first. *)
26 open Generator_docstrings
27 open Generator_optgroups
28 open Generator_actions
29 open Generator_structs
32 (* Generate daemon/actions.h. *)
33 let generate_daemon_actions_h () =
34 generate_header CStyle GPLv2plus;
36 pr "#include \"guestfs_protocol.h\"\n";
41 | shortname, (_, _, (_::_ as optargs)), _, _, _, _, _ ->
44 let uc_shortname = String.uppercase shortname in
45 let n = name_of_argt arg in
46 let uc_n = String.uppercase n in
47 pr "#define GUESTFS_%s_%s_BITMASK (UINT64_C(1)<<%d)\n"
54 fun (name, (ret, args, optargs), _, _, _, _, _) ->
55 let style = ret, args @ optargs, [] in
57 ~single_line:true ~newline:true ~in_daemon:true ~prefix:"do_"
61 (* Generate the server-side stubs. *)
62 and generate_daemon_actions () =
63 generate_header CStyle GPLv2plus;
65 pr "#include <config.h>\n";
67 pr "#include <stdio.h>\n";
68 pr "#include <stdlib.h>\n";
69 pr "#include <string.h>\n";
70 pr "#include <inttypes.h>\n";
71 pr "#include <rpc/types.h>\n";
72 pr "#include <rpc/xdr.h>\n";
74 pr "#include \"daemon.h\"\n";
75 pr "#include \"c-ctype.h\"\n";
76 pr "#include \"guestfs_protocol.h\"\n";
77 pr "#include \"actions.h\"\n";
81 fun (name, (ret, args, optargs), _, _, _, _, _) ->
82 (* Generate server-side stubs. *)
83 pr "static void %s_stub (XDR *xdr_in)\n" name;
86 | RErr | RInt _ -> pr " int r;\n"
87 | RInt64 _ -> pr " int64_t r;\n"
88 | RBool _ -> pr " int r;\n"
89 | RConstString _ | RConstOptString _ ->
90 failwithf "RConstString|RConstOptString cannot be used by daemon functions"
91 | RString _ -> pr " char *r;\n"
92 | RStringList _ | RHashtable _ -> pr " char **r;\n"
93 | RStruct (_, typ) -> pr " guestfs_int_%s *r;\n" typ
94 | RStructList (_, typ) -> pr " guestfs_int_%s_list *r;\n" typ
96 pr " size_t size = 1;\n";
100 if args <> [] || optargs <> [] then (
101 pr " struct guestfs_%s_args args;\n" name;
104 | Device n | Dev_or_Path n
108 | OptString n -> pr " char *%s;\n" n
109 | StringList n | DeviceList n -> pr " char **%s;\n" n
110 | Bool n -> pr " int %s;\n" n
111 | Int n -> pr " int %s;\n" n
112 | Int64 n -> pr " int64_t %s;\n" n
113 | FileIn _ | FileOut _ -> ()
115 pr " const char *%s;\n" n;
116 pr " size_t %s_size;\n" n
117 | Pointer _ -> assert false
123 List.exists (function FileIn _ -> true | _ -> false) args in
125 (* Reject unknown optional arguments. *)
126 if optargs <> [] then (
127 let len = List.length optargs in
128 let mask = Int64.lognot (Int64.pred (Int64.shift_left 1L len)) in
129 pr " if (optargs_bitmask & UINT64_C(0x%Lx)) {\n" mask;
131 pr " cancel_receive ();\n";
132 pr " reply_with_error (\"unknown option in optional arguments bitmask (this can happen if a program is compiled against a newer version of libguestfs, then run against an older version of the daemon)\");\n";
138 (* Decode arguments. *)
139 if args <> [] || optargs <> [] then (
140 pr " memset (&args, 0, sizeof args);\n";
142 pr " if (!xdr_guestfs_%s_args (xdr_in, &args)) {\n" name;
144 pr " cancel_receive ();\n";
145 pr " reply_with_error (\"daemon failed to decode procedure arguments\");\n";
149 pr " char *%s = args.%s;\n" n n
151 let pr_list_handling_code n =
152 pr " %s = realloc (args.%s.%s_val,\n" n n n;
153 pr " sizeof (char *) * (args.%s.%s_len+1));\n" n n;
154 pr " if (%s == NULL) {\n" n;
156 pr " cancel_receive ();\n";
157 pr " reply_with_perror (\"realloc\");\n";
160 pr " %s[args.%s.%s_len] = NULL;\n" n n n;
161 pr " args.%s.%s_val = %s;\n" n n n;
167 pr " ABS_PATH (%s, %s, goto done);\n"
168 n (if is_filein then "cancel_receive ()" else "");
171 pr " RESOLVE_DEVICE (%s, %s, goto done);\n"
172 n (if is_filein then "cancel_receive ()" else "");
175 pr " REQUIRE_ROOT_OR_RESOLVE_DEVICE (%s, %s, goto done);\n"
176 n (if is_filein then "cancel_receive ()" else "");
177 | String n | Key n -> pr_args n
178 | OptString n -> pr " %s = args.%s ? *args.%s : NULL;\n" n n n
180 pr_list_handling_code n;
182 pr_list_handling_code n;
183 pr " /* Ensure that each is a device,\n";
184 pr " * and perform device name translation.\n";
188 pr " for (i = 0; %s[i] != NULL; ++i)\n" n;
189 pr " RESOLVE_DEVICE (%s[i], %s, goto done);\n" n
190 (if is_filein then "cancel_receive ()" else "");
192 | Bool n -> pr " %s = args.%s;\n" n n
193 | Int n -> pr " %s = args.%s;\n" n n
194 | Int64 n -> pr " %s = args.%s;\n" n n
195 | FileIn _ | FileOut _ -> ()
197 pr " %s = args.%s.%s_val;\n" n n n;
198 pr " %s_size = args.%s.%s_len;\n" n n n
199 | Pointer _ -> assert false
204 (* this is used at least for do_equal *)
205 if List.exists (function Pathname _ -> true | _ -> false) args then (
206 (* Emit NEED_ROOT just once, even when there are two or
207 more Pathname args *)
208 pr " NEED_ROOT (%s, goto done);\n"
209 (if is_filein then "cancel_receive ()" else "");
212 (* Don't want to call the impl with any FileIn or FileOut
213 * parameters, since these go "outside" the RPC protocol.
218 (function FileIn _ | FileOut _ -> false | _ -> true) args in
219 let style = ret, args' @ optargs, [] in
220 pr " r = do_%s " name;
221 generate_c_call_args style;
225 | RConstOptString _ -> assert false
226 | RErr | RInt _ | RInt64 _ | RBool _
228 | RString _ | RStringList _ | RHashtable _
229 | RStruct (_, _) | RStructList (_, _) ->
231 match errcode_of_ret ret with
232 | `CannotReturnError -> assert false
233 | (`ErrorIsMinusOne | `ErrorIsNULL) as e -> e in
234 pr " if (r == %s)\n" (string_of_errcode errcode);
235 pr " /* do_%s has already called reply_with_error */\n" name;
239 pr " /* size == 0 && r == NULL could be a non-error case (just\n";
240 pr " * an ordinary zero-length buffer), so be careful ...\n";
242 pr " if (size == 1 && r == NULL)\n";
243 pr " /* do_%s has already called reply_with_error */\n" name;
248 (* If there are any FileOut parameters, then the impl must
249 * send its own reply.
252 List.exists (function FileOut _ -> true | _ -> false) args in
254 pr " /* do_%s has already sent a reply */\n" name
257 | RErr -> pr " reply (NULL, NULL);\n"
258 | RInt n | RInt64 n | RBool n ->
259 pr " struct guestfs_%s_ret ret;\n" name;
260 pr " ret.%s = r;\n" n;
261 pr " reply ((xdrproc_t) &xdr_guestfs_%s_ret, (char *) &ret);\n"
263 | RConstString _ | RConstOptString _ ->
264 failwithf "RConstString|RConstOptString cannot be used by daemon functions"
266 pr " struct guestfs_%s_ret ret;\n" name;
267 pr " ret.%s = r;\n" n;
268 pr " reply ((xdrproc_t) &xdr_guestfs_%s_ret, (char *) &ret);\n"
271 | RStringList n | RHashtable n ->
272 pr " struct guestfs_%s_ret ret;\n" name;
273 pr " ret.%s.%s_len = count_strings (r);\n" n n;
274 pr " ret.%s.%s_val = r;\n" n n;
275 pr " reply ((xdrproc_t) &xdr_guestfs_%s_ret, (char *) &ret);\n"
277 pr " free_strings (r);\n"
279 pr " struct guestfs_%s_ret ret;\n" name;
280 pr " ret.%s = *r;\n" n;
281 pr " reply ((xdrproc_t) xdr_guestfs_%s_ret, (char *) &ret);\n"
283 pr " xdr_free ((xdrproc_t) xdr_guestfs_%s_ret, (char *) &ret);\n"
285 | RStructList (n, _) ->
286 pr " struct guestfs_%s_ret ret;\n" name;
287 pr " ret.%s = *r;\n" n;
288 pr " reply ((xdrproc_t) xdr_guestfs_%s_ret, (char *) &ret);\n"
290 pr " xdr_free ((xdrproc_t) xdr_guestfs_%s_ret, (char *) &ret);\n"
293 pr " struct guestfs_%s_ret ret;\n" name;
294 pr " ret.%s.%s_val = r;\n" n n;
295 pr " ret.%s.%s_len = size;\n" n n;
296 pr " reply ((xdrproc_t) &xdr_guestfs_%s_ret, (char *) &ret);\n"
306 pr " xdr_free ((xdrproc_t) xdr_guestfs_%s_args, (char *) &args);\n"
313 (* Dispatch function. *)
314 pr "void dispatch_incoming_message (XDR *xdr_in)\n";
316 pr " switch (proc_nr) {\n";
319 fun (name, _, _, _, _, _, _) ->
320 pr " case GUESTFS_PROC_%s:\n" (String.uppercase name);
321 pr " %s_stub (xdr_in);\n" name;
326 pr " reply_with_error (\"dispatch_incoming_message: unknown procedure number %%d, set LIBGUESTFS_PATH to point to the matching libguestfs appliance directory\", proc_nr);\n";
331 (* LVM columns and tokenization functions. *)
332 (* XXX This generates crap code. We should rethink how we
338 pr "static const char *lvm_%s_cols = \"%s\";\n"
339 typ (String.concat "," (List.map fst cols));
342 pr "static int lvm_tokenize_%s (char *str, guestfs_int_lvm_%s *r)\n" typ typ;
344 pr " char *tok, *p, *next;\n";
345 pr " size_t i, j;\n";
348 pr " fprintf (stderr, \"%%s: <<%%s>>\\n\", __func__, str);\n";
352 pr " fprintf (stderr, \"%%s: failed: passed a NULL string\\n\", __func__);\n";
355 pr " if (!*str || c_isspace (*str)) {\n";
356 pr " fprintf (stderr, \"%%s: failed: passed a empty string or one beginning with whitespace\\n\", __func__);\n";
361 fun (name, coltype) ->
363 pr " fprintf (stderr, \"%%s: failed: string finished early, around token %%s\\n\", __func__, \"%s\");\n" name;
366 pr " p = strchrnul (tok, ',');\n";
367 pr " if (*p) next = p+1; else next = NULL;\n";
371 pr " r->%s = strdup (tok);\n" name;
372 pr " if (r->%s == NULL) {\n" name;
373 pr " perror (\"strdup\");\n";
377 pr " for (i = j = 0; i < 32; ++j) {\n";
378 pr " if (tok[j] == '\\0') {\n";
379 pr " fprintf (stderr, \"%%s: failed to parse UUID from '%%s'\\n\", __func__, tok);\n";
381 pr " } else if (tok[j] != '-')\n";
382 pr " r->%s[i++] = tok[j];\n" name;
385 pr " if (sscanf (tok, \"%%\"SCNu64, &r->%s) != 1) {\n" name;
386 pr " fprintf (stderr, \"%%s: failed to parse size '%%s' from token %%s\\n\", __func__, tok, \"%s\");\n" name;
390 pr " if (sscanf (tok, \"%%\"SCNi64, &r->%s) != 1) {\n" name;
391 pr " fprintf (stderr, \"%%s: failed to parse int '%%s' from token %%s\\n\", __func__, tok, \"%s\");\n" name;
395 pr " if (tok[0] == '\\0')\n";
396 pr " r->%s = -1;\n" name;
397 pr " else if (sscanf (tok, \"%%f\", &r->%s) != 1) {\n" name;
398 pr " fprintf (stderr, \"%%s: failed to parse float '%%s' from token %%s\\n\", __func__, tok, \"%s\");\n" name;
401 | FBuffer | FInt32 | FUInt32 | FUInt64 | FChar ->
402 assert false (* can never be an LVM column *)
407 pr " if (tok != NULL) {\n";
408 pr " fprintf (stderr, \"%%s: failed: extra tokens at end of string\\n\", __func__);\n";
415 pr "guestfs_int_lvm_%s_list *\n" typ;
416 pr "parse_command_line_%ss (void)\n" typ;
418 pr " char *out, *err;\n";
419 pr " char *p, *pend;\n";
421 pr " guestfs_int_lvm_%s_list *ret;\n" typ;
424 pr " ret = malloc (sizeof *ret);\n";
426 pr " reply_with_perror (\"malloc\");\n";
427 pr " return NULL;\n";
430 pr " ret->guestfs_int_lvm_%s_list_len = 0;\n" typ;
431 pr " ret->guestfs_int_lvm_%s_list_val = NULL;\n" typ;
433 pr " r = command (&out, &err,\n";
434 pr " \"lvm\", \"%ss\",\n" typ;
435 pr " \"-o\", lvm_%s_cols, \"--unbuffered\", \"--noheadings\",\n" typ;
436 pr " \"--nosuffix\", \"--separator\", \",\", \"--units\", \"b\", NULL);\n";
437 pr " if (r == -1) {\n";
438 pr " reply_with_error (\"%%s\", err);\n";
442 pr " return NULL;\n";
447 pr " /* Tokenize each line of the output. */\n";
451 pr " pend = strchr (p, '\\n'); /* Get the next line of output. */\n";
453 pr " *pend = '\\0';\n";
457 pr " while (*p && c_isspace (*p)) /* Skip any leading whitespace. */\n";
460 pr " if (!*p) { /* Empty line? Skip it. */\n";
465 pr " /* Allocate some space to store this next entry. */\n";
466 pr " newp = realloc (ret->guestfs_int_lvm_%s_list_val,\n" typ;
467 pr " sizeof (guestfs_int_lvm_%s) * (i+1));\n" typ;
468 pr " if (newp == NULL) {\n";
469 pr " reply_with_perror (\"realloc\");\n";
470 pr " free (ret->guestfs_int_lvm_%s_list_val);\n" typ;
473 pr " return NULL;\n";
475 pr " ret->guestfs_int_lvm_%s_list_val = newp;\n" typ;
477 pr " /* Tokenize the next entry. */\n";
478 pr " r = lvm_tokenize_%s (p, &ret->guestfs_int_lvm_%s_list_val[i]);\n" typ typ;
479 pr " if (r == -1) {\n";
480 pr " reply_with_error (\"failed to parse output of '%ss' command\");\n" typ;
481 pr " free (ret->guestfs_int_lvm_%s_list_val);\n" typ;
484 pr " return NULL;\n";
491 pr " ret->guestfs_int_lvm_%s_list_len = i;\n" typ;
497 ) ["pv", lvm_pv_cols; "vg", lvm_vg_cols; "lv", lvm_lv_cols]
499 (* Generate a list of function names, for debugging in the daemon.. *)
500 and generate_daemon_names () =
501 generate_header CStyle GPLv2plus;
503 pr "#include <config.h>\n";
505 pr "#include \"daemon.h\"\n";
508 pr "/* This array is indexed by proc_nr. See guestfs_protocol.x. */\n";
509 pr "const char *function_names[] = {\n";
511 fun (name, _, proc_nr, _, _, _, _) -> pr " [%d] = \"%s\",\n" proc_nr name
515 (* Generate the optional groups for the daemon to implement
518 and generate_daemon_optgroups_c () =
519 generate_header CStyle GPLv2plus;
521 pr "#include <config.h>\n";
523 pr "#include \"daemon.h\"\n";
524 pr "#include \"optgroups.h\"\n";
527 pr "struct optgroup optgroups[] = {\n";
530 pr " { \"%s\", optgroup_%s_available },\n" group group
532 pr " { NULL, NULL }\n";
535 and generate_daemon_optgroups_h () =
536 generate_header CStyle GPLv2plus;
540 pr "extern int optgroup_%s_available (void);\n" group