New API: inspect-get-hostname to return the hostname of the guest.
[libguestfs.git] / generator / generator_daemon.ml
1 (* libguestfs
2  * Copyright (C) 2009-2010 Red Hat Inc.
3  *
4  * This program is free software; you can redistribute it and/or modify
5  * it under the terms of the GNU General Public License as published by
6  * the Free Software Foundation; either version 2 of the License, or
7  * (at your option) any later version.
8  *
9  * This program is distributed in the hope that it will be useful,
10  * but WITHOUT ANY WARRANTY; without even the implied warranty of
11  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
12  * GNU General Public License for more details.
13  *
14  * You should have received a copy of the GNU General Public License
15  * along with this program; if not, write to the Free Software
16  * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
17  *)
18
19 (* Please read generator/README first. *)
20
21 open Printf
22
23 open Generator_types
24 open Generator_utils
25 open Generator_pr
26 open Generator_docstrings
27 open Generator_optgroups
28 open Generator_actions
29 open Generator_structs
30 open Generator_c
31
32 (* Generate daemon/actions.h. *)
33 let generate_daemon_actions_h () =
34   generate_header CStyle GPLv2plus;
35
36   pr "#include \"guestfs_protocol.h\"\n";
37   pr "\n";
38
39   List.iter (
40     fun (name, style, _, _, _, _, _) ->
41       generate_prototype
42         ~single_line:true ~newline:true ~in_daemon:true ~prefix:"do_"
43         name style;
44   ) daemon_functions
45
46 (* Generate the server-side stubs. *)
47 and generate_daemon_actions () =
48   generate_header CStyle GPLv2plus;
49
50   pr "#include <config.h>\n";
51   pr "\n";
52   pr "#include <stdio.h>\n";
53   pr "#include <stdlib.h>\n";
54   pr "#include <string.h>\n";
55   pr "#include <inttypes.h>\n";
56   pr "#include <rpc/types.h>\n";
57   pr "#include <rpc/xdr.h>\n";
58   pr "\n";
59   pr "#include \"daemon.h\"\n";
60   pr "#include \"c-ctype.h\"\n";
61   pr "#include \"guestfs_protocol.h\"\n";
62   pr "#include \"actions.h\"\n";
63   pr "\n";
64
65   List.iter (
66     fun (name, (ret, args, optargs), _, _, _, _, _) ->
67       if optargs <> [] then
68         failwithf "optional arguments not supported in the daemon yet";
69
70       (* Generate server-side stubs. *)
71       pr "static void %s_stub (XDR *xdr_in)\n" name;
72       pr "{\n";
73       let error_code =
74         match ret with
75         | RErr | RInt _ -> pr "  int r;\n"; "-1"
76         | RInt64 _ -> pr "  int64_t r;\n"; "-1"
77         | RBool _ -> pr "  int r;\n"; "-1"
78         | RConstString _ | RConstOptString _ ->
79             failwithf "RConstString|RConstOptString cannot be used by daemon functions"
80         | RString _ -> pr "  char *r;\n"; "NULL"
81         | RStringList _ | RHashtable _ -> pr "  char **r;\n"; "NULL"
82         | RStruct (_, typ) -> pr "  guestfs_int_%s *r;\n" typ; "NULL"
83         | RStructList (_, typ) -> pr "  guestfs_int_%s_list *r;\n" typ; "NULL"
84         | RBufferOut _ ->
85             pr "  size_t size = 1;\n";
86             pr "  char *r;\n";
87             "NULL" in
88
89       (match args with
90        | [] -> ()
91        | args ->
92            pr "  struct guestfs_%s_args args;\n" name;
93            List.iter (
94              function
95              | Device n | Dev_or_Path n
96              | Pathname n
97              | String n
98              | Key n -> ()
99              | OptString n -> pr "  char *%s;\n" n
100              | StringList n | DeviceList n -> pr "  char **%s;\n" n
101              | Bool n -> pr "  int %s;\n" n
102              | Int n -> pr "  int %s;\n" n
103              | Int64 n -> pr "  int64_t %s;\n" n
104              | FileIn _ | FileOut _ -> ()
105              | BufferIn n ->
106                  pr "  const char *%s;\n" n;
107                  pr "  size_t %s_size;\n" n
108              | Pointer _ -> assert false
109            ) args
110       );
111       pr "\n";
112
113       let is_filein =
114         List.exists (function FileIn _ -> true | _ -> false) args in
115
116       (match args with
117        | [] -> ()
118        | args ->
119            pr "  memset (&args, 0, sizeof args);\n";
120            pr "\n";
121            pr "  if (!xdr_guestfs_%s_args (xdr_in, &args)) {\n" name;
122            if is_filein then
123              pr "    if (cancel_receive () != -2)\n";
124            pr "      reply_with_error (\"daemon failed to decode procedure arguments\");\n";
125            pr "    goto done;\n";
126            pr "  }\n";
127            let pr_args n =
128              pr "  char *%s = args.%s;\n" n n
129            in
130            let pr_list_handling_code n =
131              pr "  %s = realloc (args.%s.%s_val,\n" n n n;
132              pr "                sizeof (char *) * (args.%s.%s_len+1));\n" n n;
133              pr "  if (%s == NULL) {\n" n;
134              if is_filein then
135                pr "    if (cancel_receive () != -2)\n";
136              pr "      reply_with_perror (\"realloc\");\n";
137              pr "    goto done;\n";
138              pr "  }\n";
139              pr "  %s[args.%s.%s_len] = NULL;\n" n n n;
140              pr "  args.%s.%s_val = %s;\n" n n n;
141            in
142            List.iter (
143              function
144              | Pathname n ->
145                  pr_args n;
146                  pr "  ABS_PATH (%s, %s, goto done);\n"
147                    n (if is_filein then "cancel_receive ()" else "0");
148              | Device n ->
149                  pr_args n;
150                  pr "  RESOLVE_DEVICE (%s, %s, goto done);\n"
151                    n (if is_filein then "cancel_receive ()" else "0");
152              | Dev_or_Path n ->
153                  pr_args n;
154                  pr "  REQUIRE_ROOT_OR_RESOLVE_DEVICE (%s, %s, goto done);\n"
155                    n (if is_filein then "cancel_receive ()" else "0");
156              | String n | Key n -> pr_args n
157              | OptString n -> pr "  %s = args.%s ? *args.%s : NULL;\n" n n n
158              | StringList n ->
159                  pr_list_handling_code n;
160              | DeviceList n ->
161                  pr_list_handling_code n;
162                  pr "  /* Ensure that each is a device,\n";
163                  pr "   * and perform device name translation.\n";
164                  pr "   */\n";
165                  pr "  {\n";
166                  pr "    size_t i;\n";
167                  pr "    for (i = 0; %s[i] != NULL; ++i)\n" n;
168                  pr "      RESOLVE_DEVICE (%s[i], %s, goto done);\n" n
169                    (if is_filein then "cancel_receive ()" else "0");
170                  pr "  }\n";
171              | Bool n -> pr "  %s = args.%s;\n" n n
172              | Int n -> pr "  %s = args.%s;\n" n n
173              | Int64 n -> pr "  %s = args.%s;\n" n n
174              | FileIn _ | FileOut _ -> ()
175              | BufferIn n ->
176                  pr "  %s = args.%s.%s_val;\n" n n n;
177                  pr "  %s_size = args.%s.%s_len;\n" n n n
178              | Pointer _ -> assert false
179            ) args;
180            pr "\n"
181       );
182
183       (* this is used at least for do_equal *)
184       if List.exists (function Pathname _ -> true | _ -> false) args then (
185         (* Emit NEED_ROOT just once, even when there are two or
186            more Pathname args *)
187         pr "  NEED_ROOT (%s, goto done);\n"
188           (if is_filein then "cancel_receive ()" else "0");
189       );
190
191       (* Don't want to call the impl with any FileIn or FileOut
192        * parameters, since these go "outside" the RPC protocol.
193        *)
194       let args' =
195         List.filter (function FileIn _ | FileOut _ -> false | _ -> true) args in
196       pr "  r = do_%s " name;
197       generate_c_call_args (ret, args', optargs);
198       pr ";\n";
199
200       (match ret with
201        | RErr | RInt _ | RInt64 _ | RBool _
202        | RConstString _ | RConstOptString _
203        | RString _ | RStringList _ | RHashtable _
204        | RStruct (_, _) | RStructList (_, _) ->
205            pr "  if (r == %s)\n" error_code;
206            pr "    /* do_%s has already called reply_with_error */\n" name;
207            pr "    goto done;\n";
208            pr "\n"
209        | RBufferOut _ ->
210            pr "  /* size == 0 && r == NULL could be a non-error case (just\n";
211            pr "   * an ordinary zero-length buffer), so be careful ...\n";
212            pr "   */\n";
213            pr "  if (size == 1 && r == %s)\n" error_code;
214            pr "    /* do_%s has already called reply_with_error */\n" name;
215            pr "    goto done;\n";
216            pr "\n"
217       );
218
219       (* If there are any FileOut parameters, then the impl must
220        * send its own reply.
221        *)
222       let no_reply =
223         List.exists (function FileOut _ -> true | _ -> false) args in
224       if no_reply then
225         pr "  /* do_%s has already sent a reply */\n" name
226       else (
227         match ret with
228         | RErr -> pr "  reply (NULL, NULL);\n"
229         | RInt n | RInt64 n | RBool n ->
230             pr "  struct guestfs_%s_ret ret;\n" name;
231             pr "  ret.%s = r;\n" n;
232             pr "  reply ((xdrproc_t) &xdr_guestfs_%s_ret, (char *) &ret);\n"
233               name
234         | RConstString _ | RConstOptString _ ->
235             failwithf "RConstString|RConstOptString cannot be used by daemon functions"
236         | RString n ->
237             pr "  struct guestfs_%s_ret ret;\n" name;
238             pr "  ret.%s = r;\n" n;
239             pr "  reply ((xdrproc_t) &xdr_guestfs_%s_ret, (char *) &ret);\n"
240               name;
241             pr "  free (r);\n"
242         | RStringList n | RHashtable n ->
243             pr "  struct guestfs_%s_ret ret;\n" name;
244             pr "  ret.%s.%s_len = count_strings (r);\n" n n;
245             pr "  ret.%s.%s_val = r;\n" n n;
246             pr "  reply ((xdrproc_t) &xdr_guestfs_%s_ret, (char *) &ret);\n"
247               name;
248             pr "  free_strings (r);\n"
249         | RStruct (n, _) ->
250             pr "  struct guestfs_%s_ret ret;\n" name;
251             pr "  ret.%s = *r;\n" n;
252             pr "  reply ((xdrproc_t) xdr_guestfs_%s_ret, (char *) &ret);\n"
253               name;
254             pr "  xdr_free ((xdrproc_t) xdr_guestfs_%s_ret, (char *) &ret);\n"
255               name
256         | RStructList (n, _) ->
257             pr "  struct guestfs_%s_ret ret;\n" name;
258             pr "  ret.%s = *r;\n" n;
259             pr "  reply ((xdrproc_t) xdr_guestfs_%s_ret, (char *) &ret);\n"
260               name;
261             pr "  xdr_free ((xdrproc_t) xdr_guestfs_%s_ret, (char *) &ret);\n"
262               name
263         | RBufferOut n ->
264             pr "  struct guestfs_%s_ret ret;\n" name;
265             pr "  ret.%s.%s_val = r;\n" n n;
266             pr "  ret.%s.%s_len = size;\n" n n;
267             pr "  reply ((xdrproc_t) &xdr_guestfs_%s_ret, (char *) &ret);\n"
268               name;
269             pr "  free (r);\n"
270       );
271
272       (* Free the args. *)
273       pr "done:\n";
274       (match args with
275        | [] -> ()
276        | _ ->
277            pr "  xdr_free ((xdrproc_t) xdr_guestfs_%s_args, (char *) &args);\n"
278              name
279       );
280       pr "  return;\n";
281       pr "}\n\n";
282   ) daemon_functions;
283
284   (* Dispatch function. *)
285   pr "void dispatch_incoming_message (XDR *xdr_in)\n";
286   pr "{\n";
287   pr "  switch (proc_nr) {\n";
288
289   List.iter (
290     fun (name, _, _, _, _, _, _) ->
291       pr "    case GUESTFS_PROC_%s:\n" (String.uppercase name);
292       pr "      %s_stub (xdr_in);\n" name;
293       pr "      break;\n"
294   ) daemon_functions;
295
296   pr "    default:\n";
297   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";
298   pr "  }\n";
299   pr "}\n";
300   pr "\n";
301
302   (* LVM columns and tokenization functions. *)
303   (* XXX This generates crap code.  We should rethink how we
304    * do this parsing.
305    *)
306   List.iter (
307     function
308     | typ, cols ->
309         pr "static const char *lvm_%s_cols = \"%s\";\n"
310           typ (String.concat "," (List.map fst cols));
311         pr "\n";
312
313         pr "static int lvm_tokenize_%s (char *str, guestfs_int_lvm_%s *r)\n" typ typ;
314         pr "{\n";
315         pr "  char *tok, *p, *next;\n";
316         pr "  size_t i, j;\n";
317         pr "\n";
318         (*
319           pr "  fprintf (stderr, \"%%s: <<%%s>>\\n\", __func__, str);\n";
320           pr "\n";
321         *)
322         pr "  if (!str) {\n";
323         pr "    fprintf (stderr, \"%%s: failed: passed a NULL string\\n\", __func__);\n";
324         pr "    return -1;\n";
325         pr "  }\n";
326         pr "  if (!*str || c_isspace (*str)) {\n";
327         pr "    fprintf (stderr, \"%%s: failed: passed a empty string or one beginning with whitespace\\n\", __func__);\n";
328         pr "    return -1;\n";
329         pr "  }\n";
330         pr "  tok = str;\n";
331         List.iter (
332           fun (name, coltype) ->
333             pr "  if (!tok) {\n";
334             pr "    fprintf (stderr, \"%%s: failed: string finished early, around token %%s\\n\", __func__, \"%s\");\n" name;
335             pr "    return -1;\n";
336             pr "  }\n";
337             pr "  p = strchrnul (tok, ',');\n";
338             pr "  if (*p) next = p+1; else next = NULL;\n";
339             pr "  *p = '\\0';\n";
340             (match coltype with
341              | FString ->
342                  pr "  r->%s = strdup (tok);\n" name;
343                  pr "  if (r->%s == NULL) {\n" name;
344                  pr "    perror (\"strdup\");\n";
345                  pr "    return -1;\n";
346                  pr "  }\n"
347              | FUUID ->
348                  pr "  for (i = j = 0; i < 32; ++j) {\n";
349                  pr "    if (tok[j] == '\\0') {\n";
350                  pr "      fprintf (stderr, \"%%s: failed to parse UUID from '%%s'\\n\", __func__, tok);\n";
351                  pr "      return -1;\n";
352                  pr "    } else if (tok[j] != '-')\n";
353                  pr "      r->%s[i++] = tok[j];\n" name;
354                  pr "  }\n";
355              | FBytes ->
356                  pr "  if (sscanf (tok, \"%%\"SCNu64, &r->%s) != 1) {\n" name;
357                  pr "    fprintf (stderr, \"%%s: failed to parse size '%%s' from token %%s\\n\", __func__, tok, \"%s\");\n" name;
358                  pr "    return -1;\n";
359                  pr "  }\n";
360              | FInt64 ->
361                  pr "  if (sscanf (tok, \"%%\"SCNi64, &r->%s) != 1) {\n" name;
362                  pr "    fprintf (stderr, \"%%s: failed to parse int '%%s' from token %%s\\n\", __func__, tok, \"%s\");\n" name;
363                  pr "    return -1;\n";
364                  pr "  }\n";
365              | FOptPercent ->
366                  pr "  if (tok[0] == '\\0')\n";
367                  pr "    r->%s = -1;\n" name;
368                  pr "  else if (sscanf (tok, \"%%f\", &r->%s) != 1) {\n" name;
369                  pr "    fprintf (stderr, \"%%s: failed to parse float '%%s' from token %%s\\n\", __func__, tok, \"%s\");\n" name;
370                  pr "    return -1;\n";
371                  pr "  }\n";
372              | FBuffer | FInt32 | FUInt32 | FUInt64 | FChar ->
373                  assert false (* can never be an LVM column *)
374             );
375             pr "  tok = next;\n";
376         ) cols;
377
378         pr "  if (tok != NULL) {\n";
379         pr "    fprintf (stderr, \"%%s: failed: extra tokens at end of string\\n\", __func__);\n";
380         pr "    return -1;\n";
381         pr "  }\n";
382         pr "  return 0;\n";
383         pr "}\n";
384         pr "\n";
385
386         pr "guestfs_int_lvm_%s_list *\n" typ;
387         pr "parse_command_line_%ss (void)\n" typ;
388         pr "{\n";
389         pr "  char *out, *err;\n";
390         pr "  char *p, *pend;\n";
391         pr "  int r, i;\n";
392         pr "  guestfs_int_lvm_%s_list *ret;\n" typ;
393         pr "  void *newp;\n";
394         pr "\n";
395         pr "  ret = malloc (sizeof *ret);\n";
396         pr "  if (!ret) {\n";
397         pr "    reply_with_perror (\"malloc\");\n";
398         pr "    return NULL;\n";
399         pr "  }\n";
400         pr "\n";
401         pr "  ret->guestfs_int_lvm_%s_list_len = 0;\n" typ;
402         pr "  ret->guestfs_int_lvm_%s_list_val = NULL;\n" typ;
403         pr "\n";
404         pr "  r = command (&out, &err,\n";
405         pr "           \"lvm\", \"%ss\",\n" typ;
406         pr "           \"-o\", lvm_%s_cols, \"--unbuffered\", \"--noheadings\",\n" typ;
407         pr "           \"--nosuffix\", \"--separator\", \",\", \"--units\", \"b\", NULL);\n";
408         pr "  if (r == -1) {\n";
409         pr "    reply_with_error (\"%%s\", err);\n";
410         pr "    free (out);\n";
411         pr "    free (err);\n";
412         pr "    free (ret);\n";
413         pr "    return NULL;\n";
414         pr "  }\n";
415         pr "\n";
416         pr "  free (err);\n";
417         pr "\n";
418         pr "  /* Tokenize each line of the output. */\n";
419         pr "  p = out;\n";
420         pr "  i = 0;\n";
421         pr "  while (p) {\n";
422         pr "    pend = strchr (p, '\\n');       /* Get the next line of output. */\n";
423         pr "    if (pend) {\n";
424         pr "      *pend = '\\0';\n";
425         pr "      pend++;\n";
426         pr "    }\n";
427         pr "\n";
428         pr "    while (*p && c_isspace (*p))    /* Skip any leading whitespace. */\n";
429         pr "      p++;\n";
430         pr "\n";
431         pr "    if (!*p) {                      /* Empty line?  Skip it. */\n";
432         pr "      p = pend;\n";
433         pr "      continue;\n";
434         pr "    }\n";
435         pr "\n";
436         pr "    /* Allocate some space to store this next entry. */\n";
437         pr "    newp = realloc (ret->guestfs_int_lvm_%s_list_val,\n" typ;
438         pr "                sizeof (guestfs_int_lvm_%s) * (i+1));\n" typ;
439         pr "    if (newp == NULL) {\n";
440         pr "      reply_with_perror (\"realloc\");\n";
441         pr "      free (ret->guestfs_int_lvm_%s_list_val);\n" typ;
442         pr "      free (ret);\n";
443         pr "      free (out);\n";
444         pr "      return NULL;\n";
445         pr "    }\n";
446         pr "    ret->guestfs_int_lvm_%s_list_val = newp;\n" typ;
447         pr "\n";
448         pr "    /* Tokenize the next entry. */\n";
449         pr "    r = lvm_tokenize_%s (p, &ret->guestfs_int_lvm_%s_list_val[i]);\n" typ typ;
450         pr "    if (r == -1) {\n";
451         pr "      reply_with_error (\"failed to parse output of '%ss' command\");\n" typ;
452         pr "      free (ret->guestfs_int_lvm_%s_list_val);\n" typ;
453         pr "      free (ret);\n";
454         pr "      free (out);\n";
455         pr "      return NULL;\n";
456         pr "    }\n";
457         pr "\n";
458         pr "    ++i;\n";
459         pr "    p = pend;\n";
460         pr "  }\n";
461         pr "\n";
462         pr "  ret->guestfs_int_lvm_%s_list_len = i;\n" typ;
463         pr "\n";
464         pr "  free (out);\n";
465         pr "  return ret;\n";
466         pr "}\n"
467
468   ) ["pv", lvm_pv_cols; "vg", lvm_vg_cols; "lv", lvm_lv_cols]
469
470 (* Generate a list of function names, for debugging in the daemon.. *)
471 and generate_daemon_names () =
472   generate_header CStyle GPLv2plus;
473
474   pr "#include <config.h>\n";
475   pr "\n";
476   pr "#include \"daemon.h\"\n";
477   pr "\n";
478
479   pr "/* This array is indexed by proc_nr.  See guestfs_protocol.x. */\n";
480   pr "const char *function_names[] = {\n";
481   List.iter (
482     fun (name, _, proc_nr, _, _, _, _) -> pr "  [%d] = \"%s\",\n" proc_nr name
483   ) daemon_functions;
484   pr "};\n";
485
486 (* Generate the optional groups for the daemon to implement
487  * guestfs_available.
488  *)
489 and generate_daemon_optgroups_c () =
490   generate_header CStyle GPLv2plus;
491
492   pr "#include <config.h>\n";
493   pr "\n";
494   pr "#include \"daemon.h\"\n";
495   pr "#include \"optgroups.h\"\n";
496   pr "\n";
497
498   pr "struct optgroup optgroups[] = {\n";
499   List.iter (
500     fun (group, _) ->
501       pr "  { \"%s\", optgroup_%s_available },\n" group group
502   ) optgroups;
503   pr "  { NULL, NULL }\n";
504   pr "};\n"
505
506 and generate_daemon_optgroups_h () =
507   generate_header CStyle GPLv2plus;
508
509   List.iter (
510     fun (group, _) ->
511       pr "extern int optgroup_%s_available (void);\n" group
512   ) optgroups