Lines Matching refs:ty

60 def stub_fn_name(ty, name):  argument
61 return "stub_xl_%s_%s" % (ty.rawname,name)
63 def ocaml_type_of(ty): argument
64 if ty.rawname in ["domid","devid"]:
65 return ty.rawname
66 elif isinstance(ty,idl.UInt):
67 if ty.width in [8, 16]:
70 elif ty.width in [32, 64]:
71 width = ty.width
73 raise NotImplementedError("Cannot handle %d-bit int" % ty.width)
75 return "int%d" % ty.width
78 elif isinstance(ty,idl.Array):
79 return "%s array" % ocaml_type_of(ty.elem_type)
80 elif isinstance(ty,idl.Builtin):
81 if not builtins.has_key(ty.typename):
82 raise NotImplementedError("Unknown Builtin %s (%s)" % (ty.typename, type(ty)))
83 typename,_,_ = builtins[ty.typename]
85 raise NotImplementedError("No typename for Builtin %s (%s)" % (ty.typename, type(ty)))
87 elif isinstance(ty,idl.KeyedUnion):
88 return ty.union_name
89 elif isinstance(ty,idl.Aggregate):
90 if ty.rawname is None:
91 return ty.anon_struct
93 return ty.rawname.capitalize() + ".t"
95 return ty.rawname
117 def gen_struct(ty, indent): argument
119 for f in ty.fields:
127 def gen_ocaml_keyedunions(ty, interface, indent, parent = None): argument
131 if ty.rawname is not None:
134 elif isinstance(ty, idl.KeyedUnion):
136 nparent = ty.keyvar.name
138 nparent = parent + "_" + ty.keyvar.name
140 for f in ty.fields:
149 name = "%s__union" % ty.keyvar.name
153 for f in ty.fields:
167 ty.union_name = name
169 union_type = "?%s:%s" % (munge_name(nparent), ty.keyvar.type.rawname)
175 def gen_ocaml_anonstruct(ty, interface, indent, parent = None): argument
178 if ty.rawname is not None:
181 elif isinstance(ty, idl.Struct):
184 s += gen_struct(ty, indent)
186 ty.anon_struct = name
192 def gen_ocaml_ml(ty, interface, indent=""): argument
195 s = ("""(* %s interface *)\n""" % ty.typename)
197 s = ("""(* %s implementation *)\n""" % ty.typename)
199 if isinstance(ty, idl.Enumeration):
200 s += "type %s = \n" % ty.rawname
201 for v in ty.values:
205 s += "\nval string_of_%s : %s -> string\n" % (ty.rawname, ty.rawname)
207 s += "\nlet string_of_%s = function\n" % ty.rawname
208 for v in ty.values:
211 elif isinstance(ty, idl.Aggregate):
214 if ty.typename is None:
215 raise NotImplementedError("%s has no typename" % type(ty))
218 module_name = ty.rawname[0].upper() + ty.rawname[1:]
227 for f in ty.fields:
236 for f in ty.fields:
244 s += gen_struct(ty, "\t\t")
247 if ty.init_fn is not None:
252 … += "\texternal default : ctx -> %sunit -> t = \"stub_libxl_%s_init\"\n" % (union_args, ty.rawname)
254 if functions.has_key(ty.rawname):
255 for name,args in functions[ty.rawname]:
258 s += " = \"%s\"\n" % stub_fn_name(ty,name)
263 raise NotImplementedError("%s" % type(ty))
266 def c_val(ty, c, o, indent="", parent = None): argument
268 if isinstance(ty,idl.UInt):
269 if ty.width in [8, 16]:
272 elif ty.width in [32, 64]:
273 width = ty.width
275 raise NotImplementedError("Cannot handle %d-bit int" % ty.width)
280 elif isinstance(ty,idl.Builtin):
281 if not builtins.has_key(ty.typename):
282 raise NotImplementedError("Unknown Builtin %s (%s)" % (ty.typename, type(ty)))
283 _,fn,_ = builtins[ty.typename]
285 raise NotImplementedError("No c_val fn for Builtin %s (%s)" % (ty.typename, type(ty)))
287 elif isinstance (ty,idl.Array):
290 s += "\t%s = Wosize_val(%s);\n" % (parent + ty.lenvar.name, o)
291 s += "\t%s = (%s) calloc(%s, sizeof(*%s));\n" % (c, ty.typename, parent + ty.lenvar.name, c)
292 s += "\tfor(i=0; i<%s; i++) {\n" % (parent + ty.lenvar.name)
293 s += c_val(ty.elem_type, c+"[i]", "Field(%s, i)" % o, indent="\t\t", parent=parent) + "\n"
296 elif isinstance(ty,idl.Enumeration) and (parent is None):
299 for e in ty.values:
302 …s += " default: failwith_xl(ERROR_FAIL, \"cannot convert value to %s\"); break;\n" % ty.typename
304 elif isinstance(ty, idl.KeyedUnion):
309 for f in ty.fields:
312 parent + ty.keyvar.name,
315 …_xl(ERROR_FAIL, \"variant handling bug %s%s (long)\"); break;\n" % (parent, ty.keyvar.name)
321 for f in ty.fields:
326 s += "\t\t %s = %s;\n" % (parent + ty.keyvar.name, f.enumname)
327 (nparent,fexpr) = ty.member(c, f, False)
331 …ailwith_xl(ERROR_FAIL, \"variant handling bug %s%s (block)\"); break;\n" % (parent, ty.keyvar.name)
335 elif isinstance(ty, idl.Aggregate) and (parent is None or ty.rawname is None):
337 for f in ty.fields:
340 (nparent,fexpr) = ty.member(c, f, ty.rawname is not None)
344 …s += "%s_val(ctx, %s, %s);" % (ty.rawname, ty.pass_arg(c, parent is None, passby=idl.PASS_BY_REFER…
348 def gen_c_val(ty, indent=""): argument
349 s = "/* Convert caml value to %s */\n" % ty.rawname
351 …s += "static int %s_val (libxl_ctx *ctx, %s, value v)\n" % (ty.rawname, ty.make_arg("c_val", passb…
356 s += c_val(ty, "c_val", "v", indent="\t") + "\n"
363 def ocaml_Val(ty, o, c, indent="", parent = None): argument
365 if isinstance(ty,idl.UInt):
366 if ty.width in [8, 16]:
369 elif ty.width in [32, 64]:
370 width = ty.width
372 raise NotImplementedError("Cannot handle %d-bit int" % ty.width)
377 elif isinstance(ty,idl.Builtin):
378 if not builtins.has_key(ty.typename):
379 raise NotImplementedError("Unknown Builtin %s (%s)" % (ty.typename, type(ty)))
380 _,_,fn = builtins[ty.typename]
382 … raise NotImplementedError("No ocaml Val fn for Builtin %s (%s)" % (ty.typename, type(ty)))
384 elif isinstance(ty, idl.Array):
388 s += "\t %s = caml_alloc(%s,0);\n" % (o, parent + ty.lenvar.name)
389 s += "\t for(i=0; i<%s; i++) {\n" % (parent + ty.lenvar.name)
390 s += "\t %s\n" % ocaml_Val(ty.elem_type, "array_elem", c + "[i]", "", parent=parent)
394 elif isinstance(ty,idl.Enumeration) and (parent is None):
397 for e in ty.values:
400 …+= " default: failwith_xl(ERROR_FAIL, \"cannot convert value from %s\"); break;\n" % ty.typename
402 elif isinstance(ty, idl.KeyedUnion):
405 s += "switch(%s) {\n" % (parent + ty.keyvar.name)
406 for f in ty.fields:
418 (nparent,fexpr) = ty.member(c, f, parent is None)
429 … "\t default: failwith_xl(ERROR_FAIL, \"cannot convert value from %s\"); break;\n" % ty.typename
431 elif isinstance(ty,idl.Aggregate) and (parent is None or ty.rawname is None):
433 if ty.rawname is None:
436 fn = "%s_field" % ty.rawname
439 s += "\t%s = caml_alloc_tuple(%d);\n" % (o, len(ty.fields))
442 for f in ty.fields:
446 (nparent,fexpr) = ty.member(c, f, parent is None)
449 s += "\t%s\n" % ocaml_Val(f.type, fn, ty.pass_arg(fexpr, c), parent=nparent)
454 s += "%s = Val_%s(%s);" % (o, ty.rawname, ty.pass_arg(c, parent is None))
458 def gen_Val_ocaml(ty, indent=""): argument
459 s = "/* Convert %s to a caml value */\n" % ty.rawname
461 s += "static value Val_%s (%s)\n" % (ty.rawname, ty.make_arg(ty.rawname+"_c"))
464 s += "\tCAMLlocal1(%s_ocaml);\n" % ty.rawname
466 s += ocaml_Val(ty, "%s_ocaml" % ty.rawname, "%s_c" % ty.rawname, indent="\t") + "\n"
468 s += "\tCAMLreturn(%s_ocaml);\n" % ty.rawname
472 def gen_c_stub_prototype(ty, fns): argument
473 s = "/* Stubs for %s */\n" % ty.rawname
476 s += "value %s(" % stub_fn_name(ty, name)
481 def gen_c_default(ty): argument
482 s = "/* Get the defaults for %s */\n" % ty.rawname
485 for f in ty.fields:
489 s += "value stub_libxl_%s_init(value ctx, %svalue unit)\n" % (ty.rawname,
494 s += "\tlibxl_%s c_val;\n" % ty.rawname
495 s += "\tlibxl_%s_init(&c_val);\n" % ty.rawname
500 s += "\t\tlibxl_%s_init_%s(&c_val, c);\n" % (ty.rawname, u.name)
502 s += "\tval = Val_%s(&c_val);\n" % ty.rawname
503 if ty.dispose_fn:
504 s += "\tlibxl_%s_dispose(&c_val);\n" % ty.rawname
509 def gen_c_defaults(ty): argument
510 s = gen_c_default(ty)
535 if t not in [ty.rawname for ty in types]:
538 types = [ty for ty in types if not ty.rawname in blacklist]
552 for ty in types:
553 if ty.private:
556 ml.write(gen_ocaml_ml(ty, False))
559 mli.write(gen_ocaml_ml(ty, True))
562 if ty.marshal_in():
563 cinc.write(gen_c_val(ty))
565 cinc.write(gen_Val_ocaml(ty))
567 if functions.has_key(ty.rawname):
568 cinc.write(gen_c_stub_prototype(ty, functions[ty.rawname]))
570 if ty.init_fn is not None:
571 cinc.write(gen_c_defaults(ty))