瀏覽代碼

parameter default values

Nicolas Cannasse 17 年之前
父節點
當前提交
0d80146fba
共有 13 個文件被更改,包括 164 次插入82 次删除
  1. 1 1
      ast.ml
  2. 11 7
      codegen.ml
  3. 1 0
      doc/CHANGES.txt
  4. 24 20
      genas3.ml
  5. 10 5
      genjs.ml
  6. 7 3
      genneko.ml
  7. 5 0
      genswf8.ml
  8. 19 8
      genswf9.ml
  9. 6 2
      parser.ml
  10. 22 0
      tests/unit/TestMisc.hx
  11. 3 1
      type.ml
  12. 35 7
      typeload.ml
  13. 20 28
      typer.ml

+ 1 - 1
ast.ml

@@ -155,7 +155,7 @@ and type_path =
 	| TPExtend of type_path_normal * (string * bool option * anonymous_field * pos) list
 
 type func = {
-	f_args : (string * bool * type_path option) list;
+	f_args : (string * bool * type_path option * constant option) list;
 	f_type : type_path option;
 	f_expr : expr;
 }

+ 11 - 7
codegen.ml

@@ -72,7 +72,7 @@ let extend_remoting ctx c t p async prot =
 	ctx.com.package_rules <- rules;
 	let base_fields = [
 		(FVar ("__cnx",None,[],Some (TPNormal { tpackage = ["haxe";"remoting"]; tname = if async then "AsyncConnection" else "Connection"; tparams = [] }),None),p);
-		(FFun ("new",None,[APublic],[],{ f_args = ["c",false,None]; f_type = None; f_expr = (EBinop (OpAssign,(EConst (Ident "__cnx"),p),(EConst (Ident "c"),p)),p) }),p);
+		(FFun ("new",None,[APublic],[],{ f_args = ["c",false,None,None]; f_type = None; f_expr = (EBinop (OpAssign,(EConst (Ident "__cnx"),p),(EConst (Ident "c"),p)),p) }),p);
 	] in
 	let tvoid = TPNormal { tpackage = []; tname = "Void"; tparams = [] } in
 	let build_field is_public acc (f,p) =
@@ -80,11 +80,11 @@ let extend_remoting ctx c t p async prot =
 		| FFun ("new",_,_,_,_) ->
 			acc
 		| FFun (name,doc,acl,pl,f) when (is_public || List.mem APublic acl) && not (List.mem AStatic acl) ->
-			if List.exists (fun (_,_,t) -> t = None) f.f_args then error ("Field " ^ name ^ " type is not complete and cannot be used by RemotingProxy") p;
-			let eargs = [EArrayDecl (List.map (fun (a,_,_) -> (EConst (Ident a),p)) f.f_args),p] in
+			if List.exists (fun (_,_,t,_) -> t = None) f.f_args then error ("Field " ^ name ^ " type is not complete and cannot be used by RemotingProxy") p;
+			let eargs = [EArrayDecl (List.map (fun (a,_,_,_) -> (EConst (Ident a),p)) f.f_args),p] in
 			let ftype = (match f.f_type with Some (TPNormal { tpackage = []; tname = "Void" }) -> None | _ -> f.f_type) in
 			let fargs, eargs = if async then match ftype with
-				| Some tret -> f.f_args @ ["__callb",true,Some (TPFunction ([tret],tvoid))], eargs @ [EConst (Ident "__callb"),p]
+				| Some tret -> f.f_args @ ["__callb",true,Some (TPFunction ([tret],tvoid)),None], eargs @ [EConst (Ident "__callb"),p]
 				| _ -> f.f_args, eargs @ [EConst (Ident "null"),p]
 			else 
 				f.f_args, eargs
@@ -482,14 +482,14 @@ let block_vars ctx e =
 				else
 					v, o, vt
 			) f.tf_args in
-			let e = { e with eexpr = TFunction { f with tf_args = fargs; tf_expr = !fexpr } } in
-			let args = List.map (fun (v,t) -> v, false, t) vars in
+			let e = { e with eexpr = TFunction { f with tf_args = fargs; tf_expr = !fexpr } } in			
+			let args = List.map (fun (v,t) -> v, None, t) vars in
 			mk (TCall (
 				(mk (TFunction {
 					tf_args = args;
 					tf_type = e.etype;
 					tf_expr = mk (TReturn (Some e)) e.etype e.epos;
-				}) (TFun (args,e.etype)) e.epos),
+				}) (TFun (fun_args args,e.etype)) e.epos),
 				List.map (fun (v,t) -> mk (TLocal v) t e.epos) vars)
 			) e.etype e.epos
 		| _ ->
@@ -720,3 +720,7 @@ let rec is_volatile t =
 		| _ -> is_volatile (apply_params t.t_types tl t.t_type))
 	| _ ->
 		false
+
+let set_default ctx a c t p =
+	let ve = mk (TLocal a) t p in
+	mk (TIf (mk (TBinop (OpEq,ve,mk (TConst TNull) t p)) ctx.type_api.tbool p, mk (TBinop (OpAssign,ve,mk (TConst c) t p)) t p,None)) ctx.type_api.tvoid p

+ 1 - 0
doc/CHANGES.txt

@@ -46,6 +46,7 @@ TODO inlining : substitute class+function type parameters in order to have fully
 	added haxe.TimerQueue, added haxe.Timer.delay, remove haxe.Timer.delayed
 	flash9 : bugfix, generated interfaces were empty
 	fixed bug while writing block-vars in flash/js
+	added parameters default value (constants)
 
 2008-04-05: 1.19
 	fixed flash9 Array.toString

+ 24 - 20
genas3.ml

@@ -226,6 +226,24 @@ let handle_break ctx e =
 
 let this ctx = if ctx.in_value <> None then "$this" else "this"
 
+let escape_bin s =
+	let b = Buffer.create 0 in
+	for i = 0 to String.length s - 1 do
+		match Char.code (String.unsafe_get s i) with
+		| c when c < 32 -> Buffer.add_string b (Printf.sprintf "\\x%.2X" c)
+		| c -> Buffer.add_char b (Char.chr c)
+	done;
+	Buffer.contents b
+
+let gen_constant ctx p = function
+	| TInt i -> print ctx "%ld" i
+	| TFloat s -> spr ctx s
+	| TString s -> print ctx "\"%s\"" (escape_bin (Ast.s_escape s))
+	| TBool b -> spr ctx (if b then "true" else "false")
+	| TNull -> spr ctx "null"
+	| TThis -> spr ctx (this ctx)
+	| TSuper -> spr ctx "super"
+
 let gen_function_header ctx name f params p =
 	let old = ctx.in_value in
 	let old_l = ctx.locals in
@@ -234,10 +252,14 @@ let gen_function_header ctx name f params p =
 	ctx.in_value <- None;
 	ctx.local_types <- List.map snd params @ ctx.local_types;
 	print ctx "function%s(" (match name with None -> "" | Some n -> " " ^ n);
-	concat ctx "," (fun (arg,o,t) ->
+	concat ctx "," (fun (arg,c,t) ->
 		let arg = define_local ctx arg in
 		print ctx "%s : %s" arg (type_str ctx t p);
-		if o then spr ctx " = null";
+		match c with
+		| None -> ()
+		| Some c -> 
+			spr ctx " = ";
+			gen_constant ctx p c
 	) f.tf_args;
 	print ctx ") : %s " (type_str ctx f.tf_type p);
 	(fun () ->
@@ -247,24 +269,6 @@ let gen_function_header ctx name f params p =
 		ctx.local_types <- old_t;
 	)
 
-let escape_bin s =
-	let b = Buffer.create 0 in
-	for i = 0 to String.length s - 1 do
-		match Char.code (String.unsafe_get s i) with
-		| c when c < 32 -> Buffer.add_string b (Printf.sprintf "\\x%.2X" c)
-		| c -> Buffer.add_char b (Char.chr c)
-	done;
-	Buffer.contents b
-
-let gen_constant ctx p = function
-	| TInt i -> print ctx "%ld" i
-	| TFloat s -> spr ctx s
-	| TString s -> print ctx "\"%s\"" (escape_bin (Ast.s_escape s))
-	| TBool b -> spr ctx (if b then "true" else "false")
-	| TNull -> spr ctx "null"
-	| TThis -> spr ctx (this ctx)
-	| TSuper -> spr ctx "super"
-
 let rec gen_call ctx e el =
 	match e.eexpr , el with
 	| TCall (x,_) , el ->

+ 10 - 5
genjs.ml

@@ -71,11 +71,16 @@ let rec concat ctx s f = function
 		spr ctx s;
 		concat ctx s f l
 
-let fun_block ctx f =
+let fun_block ctx f p =
+	let e = List.fold_left (fun e (a,c,t) ->
+		match c with
+		| None | Some TNull -> e
+		| Some c -> Codegen.concat (Codegen.set_default ctx.com a c t p) e
+	) f.tf_expr f.tf_args in
 	if ctx.com.debug then
-		Codegen.stack_block ctx.stack ctx.current (fst ctx.curmethod) f.tf_expr
+		Codegen.stack_block ctx.stack ctx.current (fst ctx.curmethod) e
 	else
-		mk_block f.tf_expr
+		mk_block e
 
 let parent e =
 	match e.eexpr with
@@ -253,7 +258,7 @@ and gen_expr ctx e =
 		else
 			ctx.curmethod <- (fst ctx.curmethod, true);
 		print ctx "function(%s) " (String.concat "," (List.map ident (List.map arg_name f.tf_args)));
-		gen_expr ctx (fun_block ctx f);
+		gen_expr ctx (fun_block ctx f e.epos);
 		ctx.curmethod <- old_meth;
 		ctx.in_value <- old;
 	| TCall (e,el) ->
@@ -607,7 +612,7 @@ let generate_class ctx c =
 			let args  = List.map arg_name f.tf_args in
 			let a, args = (match args with [] -> "p" , ["p"] | x :: _ -> x, args) in
 			print ctx "function(%s) { if( %s === $_ ) return; " (String.concat "," (List.map ident args)) a;
-			gen_expr ctx (fun_block ctx f);
+			gen_expr ctx (fun_block ctx f e.epos);
 			print ctx "}";
 		| _ -> assert false)
 	| _ -> print ctx "function() { }");

+ 7 - 3
genneko.ml

@@ -304,14 +304,18 @@ and gen_expr ctx e =
 		) vl),p)
 	| TFunction f ->
 		let b = block ctx [f.tf_expr] in
-		let inits = List.fold_left (fun acc (a,_,_) ->
+		let inits = List.fold_left (fun acc (a,c,t) ->
+			let acc = (match c with
+				| None | Some TNull -> acc
+				| Some c ->	gen_expr ctx (Codegen.set_default ctx.com a c t e.epos) :: acc
+			) in
 			if add_local ctx a p then
-				(a, Some (call p (builtin p "array") [ident p a])) :: acc
+				(EBinop ("=",ident p a,call p (builtin p "array") [ident p a]),p) :: acc
 			else
 				acc
 		) [] f.tf_args in
 		let e = gen_expr ctx f.tf_expr in
-		let e = (match inits with [] -> e | _ -> (EBlock [(EVars (List.rev inits),p);e],p)) in
+		let e = (match inits with [] -> e | _ -> EBlock (List.rev (e :: inits)),p) in
 		let e = (EFunction (List.map arg_name f.tf_args, with_return e),p) in
 		b();
 		e

+ 5 - 0
genswf8.ml

@@ -968,6 +968,11 @@ and gen_expr_2 ctx retval e =
 			end
 		) f.tf_args in
 		let tf = begin_func ctx reg_super (Codegen.local_find true "__arguments__" f.tf_expr) rargs in
+		List.iter (fun (a,c,t) ->
+			match c with
+			| None | Some TNull -> ()
+			| Some c -> gen_expr ctx false (Codegen.set_default ctx.com a c t e.epos)
+		) f.tf_args;
 		ctx.fun_pargs <- (ctx.code_pos, List.rev !pargs) :: ctx.fun_pargs;
 		if ctx.com.debug then begin
 			gen_expr ctx false (ctx.stack.Codegen.stack_push ctx.curclass (fst ctx.curmethod));

+ 19 - 8
genswf9.ml

@@ -489,10 +489,21 @@ let debug ctx p =
 
 let end_fun ctx args tret =
 	let dparams = ref None in
-	List.iter (fun (_,opt,t) ->
+	let constant_value = function
+		| None -> HVNone
+		| Some c ->
+			match c with
+			| TInt i -> HVInt i
+			| TFloat s -> HVFloat (float_of_string s)
+			| TString s -> HVString s
+			| TBool b -> HVBool b
+			| TNull -> HVNone
+			| TThis	| TSuper -> assert false
+	in		
+	List.iter (fun (_,c,t) ->
 		match !dparams with
-		| None -> if opt then dparams := Some [HVNone]
-		| Some l -> dparams := Some (HVNone :: l)
+		| None -> if c <> None then dparams := Some [constant_value c]
+		| Some l -> dparams := Some (constant_value c :: l)
 	) args;
 	{
 		hlmt_index = 0;
@@ -501,7 +512,7 @@ let end_fun ctx args tret =
 		hlmt_native = false;
 		hlmt_var_args = false;
 		hlmt_debug_name = None;
-		hlmt_dparams = !dparams;
+		hlmt_dparams = (match !dparams with None -> None | Some l -> Some (List.rev l));
 		hlmt_pnames = None;
 		hlmt_new_block = false;
 		hlmt_unused_flag = false;
@@ -1370,7 +1381,7 @@ let generate_method ctx fdata stat =
 
 let generate_construct ctx fdata c =
 	(* make all args optional to allow no-param constructor *)
-	let f = begin_fun ctx (List.map (fun (a,o,t) -> a,true,t) fdata.tf_args) fdata.tf_type [ethis;fdata.tf_expr] false fdata.tf_expr.epos in
+	let f = begin_fun ctx (List.map (fun (a,c,t) -> a,(match c with None -> Some TNull | _ -> c),t) fdata.tf_args) fdata.tf_type [ethis;fdata.tf_expr] false fdata.tf_expr.epos in
 	(* if skip_constructor, then returns immediatly *)
 	(match c.cl_kind with
 	| KGenericInstance _ -> ()
@@ -1499,7 +1510,7 @@ let generate_field_kind ctx f c stat =
 		(match follow f.cf_type with
 		| TFun (args,tret) when f.cf_set = MethodCantAccess ->
 			Some (HFMethod {
-				hlm_type = end_fun ctx args tret;
+				hlm_type = end_fun ctx (List.map (fun (a,opt,t) -> a, (if opt then Some TNull else None), t) args) tret;
 				hlm_final = false;
 				hlm_override = false;
 				hlm_kind = MK3Normal;
@@ -1585,7 +1596,7 @@ let generate_class ctx c =
 
 let generate_enum ctx e =
 	let name_id = type_path ctx e.e_path in
-	let f = begin_fun ctx [("tag",false,t_string);("index",false,t_int);("params",false,mk_mono())] t_void [ethis] false e.e_pos in
+	let f = begin_fun ctx [("tag",None,t_string);("index",None,t_int);("params",None,mk_mono())] t_void [ethis] false e.e_pos in
 	let tag_id = ident "tag" in
 	let index_id = ident "index" in
 	let params_id = ident "params" in
@@ -1614,7 +1625,7 @@ let generate_enum ctx e =
 			hlf_slot = !st_count;
 			hlf_kind = (match f.ef_type with
 				| TFun (args,_) ->
-					let fdata = begin_fun ctx args (TEnum (e,[])) [] true f.ef_pos in
+					let fdata = begin_fun ctx (List.map (fun (a,opt,t) -> a, (if opt then Some TNull else None), t) args) (TEnum (e,[])) [] true f.ef_pos in
 					write ctx (HFindPropStrict name_id);
 					write ctx (HString f.ef_name);
 					write ctx (HInt f.ef_index);

+ 6 - 2
parser.ml

@@ -395,8 +395,12 @@ and parse_fun_name = parser
 	| [< '(Kwd New,_) >] -> "new"
 
 and parse_fun_param = parser
-	| [< '(Question,_); name = any_ident; t = parse_type_opt >] -> (name,true,t)
-	| [< name = any_ident; t = parse_type_opt >] -> (name,false,t)
+	| [< '(Question,_); name = any_ident; t = parse_type_opt; c = parse_fun_param_value >] -> (name,true,t,c)
+	| [< name = any_ident; t = parse_type_opt; c = parse_fun_param_value >] -> (name,false,t,c)
+
+and parse_fun_param_value = parser
+	| [< '(Binop OpAssign,_); '(Const c,_) >] -> Some c
+	| [< >] -> None
 
 and parse_fun_param_type = parser
 	| [< '(Question,_); name = any_ident; '(DblDot,_); t = parse_type_path >] -> (name,true,t)

+ 22 - 0
tests/unit/TestMisc.hx

@@ -29,5 +29,27 @@ class TestMisc extends Test {
 		// depending of ISO/UTF8 native
 		allow( haxe.Md5.encode("héllo"), ["1a722f7e6c801d9e470a10cb91ba406d","be50e8478cf24ff3595bc7307fb91b50"] );
 	}
+	
+	function opt1( ?x : Int, ?y : String ) {
+		return { x : x, y : y };
+	}
+	
+	function opt2( ?x = 5, ?y = "hello" ) {
+		return { x : x, y : y };
+	}
+	
+	function testOptionalParams() {
+		eq( opt1().x, null );
+		eq( opt1().y, null );
+		eq( opt1(55).x, 55 );
+		eq( opt1(55).y, null );
+		eq( opt1("str").x, null );
+		eq( opt1("str").y, "str" );
+		eq( opt1(66,"hello").x, 66 );
+		eq( opt1(66,"hello").y, "hello" );
+		
+		eq( opt2().x, 5 );
+		eq( opt2().y, "hello" );
+	}
 
 }

+ 3 - 1
type.ml

@@ -51,7 +51,7 @@ and tconstant =
 	| TSuper
 
 and tfunc = {
-	tf_args : (string * bool * t) list;
+	tf_args : (string * tconstant option * t) list;
 	tf_type : t;
 	tf_expr : texpr;
 }
@@ -196,6 +196,8 @@ let rec t_dynamic = TDynamic t_dynamic
 
 let tfun pl r = TFun (List.map (fun t -> "",false,t) pl,r)
 
+let fun_args l = List.map (fun (a,c,t) -> a, c <> None, t) l
+
 let mk_class path pos doc priv =
 	{
 		cl_path = path;

+ 35 - 7
typeload.ml

@@ -21,6 +21,31 @@ open Type
 open Common
 open Typecore
 
+let type_constant ctx c p =
+	match c with
+	| Int s ->
+		(try
+			mk (TConst (TInt (Int32.of_string s))) ctx.api.tint p
+		with
+			_ -> mk (TConst (TFloat s)) ctx.api.tfloat p)
+	| Float f -> mk (TConst (TFloat f)) ctx.api.tfloat p
+	| String s -> mk (TConst (TString s)) ctx.api.tstring p
+	| Ident "true" -> mk (TConst (TBool true)) ctx.api.tbool p
+	| Ident "false" -> mk (TConst (TBool false)) ctx.api.tbool p
+	| Ident "null" -> mk (TConst TNull) (ctx.api.tnull (mk_mono())) p
+	| _ -> assert false
+
+let type_function_param ctx t c opt p =
+	match c with
+	| None ->
+		if opt then ctx.api.tnull t, Some TNull else t, None
+	| Some c ->
+		let c = (try type_constant ctx c p with _ -> error "Parameter default value should be constant" p) in
+		unify ctx t c.etype p;
+		match c.eexpr with
+		| TConst c -> t, Some c
+		| _ -> assert false
+
 let exc_protect f =
 	let rec r = ref (fun() ->
 		try
@@ -479,13 +504,13 @@ let init_class ctx c p herits fields =
 			with
 				Not_found -> get_parent csup name
 	in
-	let type_opt ?opt ctx p t =
+	let type_opt ctx p t =
 		match t with
 		| None when c.cl_extern || c.cl_interface ->
 			display_error ctx "Type required for extern classes and interfaces" p;
 			t_dynamic
 		| _ ->
-			load_type_opt ?opt ctx p t
+			load_type_opt ctx p t
 	in
 	let rec has_field f = function
 		| None -> false
@@ -553,8 +578,11 @@ let init_class ctx c p herits fields =
 				type_params = if stat then params else params @ ctx.type_params;
 			} in
 			let ret = type_opt ctx p f.f_type in
-			let args = List.map (fun (name,opt,t) -> name , opt, type_opt ~opt ctx p t) f.f_args in
-			let t = TFun (args,ret) in
+			let args = List.map (fun (name,opt,t,c) ->
+				let t, c = type_function_param ctx (type_opt ctx p t) c opt p in
+				name, c, t
+			) f.f_args in
+			let t = TFun (fun_args args,ret) in
 			let constr = (name = "new") in
 			if constr && c.cl_interface then error "An interface cannot have a constructor" p;
 			if c.cl_interface && not stat && (match f.f_expr with EBlock [] , _ -> false | _ -> true) then error "An interface method cannot have a body" p;
@@ -577,7 +605,7 @@ let init_class ctx c p herits fields =
 				if ctx.com.verbose then print_endline ("Typing " ^ s_type_path c.cl_path ^ "." ^ name);
 				let e , fargs = type_function ctx t stat constr f p in
 				let f = {
-					tf_args = fargs;
+					tf_args = args;
 					tf_type = ret;
 					tf_expr = e;
 				} in
@@ -679,7 +707,7 @@ let init_class ctx c p herits fields =
 				| None -> None
 				| Some (acc,pl,f) as infos ->
 					let p = c.cl_pos in
-					let esuper = (ECall ((EConst (Ident "super"),p),List.map (fun (n,_,_) -> (EConst (Ident n),p)) f.f_args),p) in
+					let esuper = (ECall ((EConst (Ident "super"),p),List.map (fun (n,_,_,_) -> (EConst (Ident n),p)) f.f_args),p) in
 					let acc = (if csuper.cl_extern && acc = [] then [APublic] else acc) in
 					(* remove types that are superclass type-parameters *)
 					let replace_type = function
@@ -687,7 +715,7 @@ let init_class ctx c p herits fields =
 							None
 						| t -> t
 					in
-					let fnew = { f with f_expr = esuper; f_args = List.map (fun (a,opt,t) -> a,opt,replace_type t) f.f_args } in
+					let fnew = { f with f_expr = esuper; f_args = List.map (fun (a,opt,t,c) -> a,opt,replace_type t,c) f.f_args } in
 					let _, _, cf, delayed = loop_cf (FFun ("new",None,acc,pl,fnew)) p in
 					c.cl_constructor <- Some cf;
 					Hashtbl.add ctx.constructs c.cl_path (acc,pl,f);

+ 20 - 28
typer.ml

@@ -376,23 +376,6 @@ let type_ident ctx i is_type p get =
 			raise (Error (Unknown_ident i,p))
 		end
 
-let type_constant ctx c p =
-	match c with
-	| Int s ->
-		(try
-			mk (TConst (TInt (Int32.of_string s))) ctx.api.tint p
-		with
-			_ -> mk (TConst (TFloat s)) ctx.api.tfloat p)
-	| Float f -> mk (TConst (TFloat f)) ctx.api.tfloat p
-	| String s -> mk (TConst (TString s)) ctx.api.tstring p
-	| Regexp (r,opt) ->
-		let str = mk (TConst (TString r)) ctx.api.tstring p in
-		let opt = mk (TConst (TString opt)) ctx.api.tstring p in
-		let t = Typeload.load_core_type ctx "EReg" in
-		mk (TNew ((match t with TInst (c,[]) -> c | _ -> assert false),[],[str;opt])) t p
-	| Ident _
-	| Type _ -> assert false
-
 let type_matching ctx (enum,params) (e,p) ecases first_case =
 	let invalid() = raise (Error (Invalid_enum_matching,p)) in
 	let needs n = error ("This constructor needs " ^ string_of_int n ^ " parameters") p in
@@ -448,7 +431,7 @@ let type_field ctx e i p get =
 			| Some t ->
 				let t = apply_params c.cl_types params t in
 				if get && PMap.mem "resolve" c.cl_fields then
-					AccExpr (mk (TCall (mk (TField (e,"resolve")) (tfun [ctx.api.tstring] t) p,[type_constant ctx (String i) p])) t p)
+					AccExpr (mk (TCall (mk (TField (e,"resolve")) (tfun [ctx.api.tstring] t) p,[Typeload.type_constant ctx (String i) p])) t p)
 				else
 					AccExpr (mk (TField (e,i)) t p)
 			| None ->
@@ -1004,8 +987,13 @@ and type_expr ctx ?(need_val=true) (e,p) =
 	| EConst (Ident _)
 	| EConst (Type _) ->
 		acc_get (type_access ctx e p true) p
+	| EConst (Regexp (r,opt)) ->
+		let str = mk (TConst (TString r)) ctx.api.tstring p in
+		let opt = mk (TConst (TString opt)) ctx.api.tstring p in
+		let t = Typeload.load_core_type ctx "EReg" in
+		mk (TNew ((match t with TInst (c,[]) -> c | _ -> assert false),[],[str;opt])) t p
 	| EConst c ->
-		type_constant ctx c p
+		Typeload.type_constant ctx c p
     | EBinop (op,e1,e2) ->
 		type_binop ctx op e1 e2 p
 	| EBlock [] when need_val ->
@@ -1214,7 +1202,11 @@ and type_expr ctx ?(need_val=true) (e,p) =
 		type_unop ctx op flag e p
 	| EFunction f ->
 		let rt = Typeload.load_type_opt ctx p f.f_type in
-		let args = List.map (fun (s,opt,t) -> s , opt, Typeload.load_type_opt ~opt ctx p t) f.f_args in
+		let args = List.map (fun (s,opt,t,c) -> 
+			let t = Typeload.load_type_opt ctx p t in
+			let t, c = Typeload.type_function_param ctx t c opt p in
+			s , c, t
+		) f.f_args in
 		(match ctx.param_type with
 		| None -> ()
 		| Some t ->
@@ -1227,10 +1219,10 @@ and type_expr ctx ?(need_val=true) (e,p) =
 					| _ -> ()
 				) args args2;
 			| _ -> ());
-		let ft = TFun (args,rt) in
+		let ft = TFun (fun_args args,rt) in
 		let e , fargs = Typeload.type_function ctx ft true false f p in
 		let f = {
-			tf_args = fargs;
+			tf_args = args;
 			tf_type = rt;
 			tf_expr = e;
 		} in
@@ -1335,9 +1327,9 @@ and type_call ctx e el p =
 				match args, params with
 				| _ , [] ->
 					let k = ref 0 in
-					let fun_arg = ("f",false,e.etype) in
-					let first_args = List.map (fun t -> incr k; "a" ^ string_of_int !k, false, t) (List.rev eargs) in
-					let missing_args = List.map (fun (_,opt,t) -> incr k; "a" ^ string_of_int !k, opt, t) args in
+					let fun_arg = ("f",None,e.etype) in
+					let first_args = List.map (fun t -> incr k; "a" ^ string_of_int !k, None, t) (List.rev eargs) in
+					let missing_args = List.map (fun (_,opt,t) -> incr k; "a" ^ string_of_int !k, (if opt then Some TNull else None), t) args in
 					let vexpr (v,_,t) = mk (TLocal v) t p in
 					let func = mk (TFunction {
 						tf_args = missing_args;
@@ -1345,13 +1337,13 @@ and type_call ctx e el p =
 						tf_expr = mk (TReturn (Some (
 							mk (TCall (vexpr fun_arg,List.map vexpr (first_args @ missing_args))) ret p
 						))) ret p;
-					}) (TFun (missing_args,ret)) p in
+					}) (TFun (fun_args missing_args,ret)) p in
 					let func = mk (TFunction {
 						tf_args = fun_arg :: first_args;
 						tf_type = func.etype;
 						tf_expr = mk (TReturn (Some func)) e.etype p;
-					}) (TFun (first_args,func.etype)) p in
-					mk (TCall (func,e :: eparams)) (TFun (missing_args,ret)) p
+					}) (TFun (fun_args first_args,func.etype)) p in
+					mk (TCall (func,e :: eparams)) (TFun (fun_args missing_args,ret)) p
 				| [], _ -> error "Too many callback arguments" p
 				| (_,_,t) :: args , e :: params ->
 					unify ctx e.etype t p;