Browse Source

added abstract types basic support (still keep old StdTypes until we fix bugs and test completely)

Nicolas Cannasse 13 years ago
parent
commit
d6fb3fa088
21 changed files with 272 additions and 64 deletions
  1. 8 0
      ast.ml
  2. 11 0
      codegen.ml
  3. 13 1
      genas3.ml
  4. 4 2
      gencpp.ml
  5. 2 1
      genjs.ml
  6. 4 4
      genneko.ml
  7. 21 9
      genphp.ml
  8. 4 0
      genswf.ml
  9. 3 1
      genswf8.ml
  10. 12 8
      genswf9.ml
  11. 23 11
      genxml.ml
  12. 12 3
      interp.ml
  13. 1 1
      lexer.mll
  14. 6 3
      optimizer.ml
  15. 16 1
      parser.ml
  16. 4 0
      std/haxe/macro/Type.hx
  17. 0 2
      std/neko/_std/Std.hx
  18. 3 8
      tests/unit/TestReflect.hx
  19. 51 1
      type.ml
  20. 34 2
      typeload.ml
  21. 40 6
      typer.ml

+ 8 - 0
ast.ml

@@ -65,6 +65,7 @@ type keyword =
 	| Null
 	| Null
 	| True
 	| True
 	| False
 	| False
+	| Abstract
 
 
 type binop =
 type binop =
 	| OpAdd
 	| OpAdd
@@ -239,6 +240,11 @@ type class_flag =
 	| HExtends of type_path
 	| HExtends of type_path
 	| HImplements of type_path
 	| HImplements of type_path
 
 
+type abstract_flag =
+	| APrivAbstract
+	| ASubType of complex_type
+	| ASuperType of complex_type
+
 type enum_constructor = string * documentation * metadata * (string * bool * complex_type) list * pos
 type enum_constructor = string * documentation * metadata * (string * bool * complex_type) list * pos
 
 
 type ('a,'b) definition = {
 type ('a,'b) definition = {
@@ -254,6 +260,7 @@ type type_def =
 	| EClass of (class_flag, class_field list) definition
 	| EClass of (class_flag, class_field list) definition
 	| EEnum of (enum_flag, enum_constructor list) definition
 	| EEnum of (enum_flag, enum_constructor list) definition
 	| ETypedef of (enum_flag, complex_type) definition
 	| ETypedef of (enum_flag, complex_type) definition
+	| EAbstract of (abstract_flag, unit) definition
 	| EImport of type_path
 	| EImport of type_path
 	| EUsing of type_path
 	| EUsing of type_path
 
 
@@ -368,6 +375,7 @@ let s_keyword = function
 	| Null -> "null"
 	| Null -> "null"
 	| True -> "true"
 	| True -> "true"
 	| False -> "false"
 	| False -> "false"
+	| Abstract -> "abstract"
 
 
 let rec s_binop = function
 let rec s_binop = function
 	| OpAdd -> "+"
 	| OpAdd -> "+"

+ 11 - 0
codegen.ml

@@ -221,6 +221,7 @@ let make_generic ctx ps pt p =
 			let path = (match follow t with		
 			let path = (match follow t with		
 				| TInst (ct,_) -> ct.cl_path
 				| TInst (ct,_) -> ct.cl_path
 				| TEnum (e,_) -> e.e_path
 				| TEnum (e,_) -> e.e_path
+				| TAbstract (a,_) when has_meta ":runtime_value" a.a_meta -> a.a_path
 				| TMono _ -> raise (Generic_Exception (("Could not determine type for parameter " ^ s), p))
 				| TMono _ -> raise (Generic_Exception (("Could not determine type for parameter " ^ s), p))
 				| t -> raise (Generic_Exception (("Type parameter must be a class or enum instance (found " ^ (s_type (print_context()) t) ^ ")"), p))
 				| t -> raise (Generic_Exception (("Type parameter must be a class or enum instance (found " ^ (s_type (print_context()) t) ^ ")"), p))
 			) in
 			) in
@@ -300,6 +301,7 @@ let rec build_generic ctx c p tl =
 			| TInst (c,tl) -> add_dep c.cl_module tl
 			| TInst (c,tl) -> add_dep c.cl_module tl
 			| TEnum (e,tl) -> add_dep e.e_module tl
 			| TEnum (e,tl) -> add_dep e.e_module tl
 			| TType (t,tl) -> add_dep t.t_module tl
 			| TType (t,tl) -> add_dep t.t_module tl
+			| TAbstract (a,tl) -> add_dep a.a_module tl
 			| TMono r ->
 			| TMono r ->
 				(match !r with
 				(match !r with
 				| None -> ()
 				| None -> ()
@@ -418,6 +420,8 @@ let build_metadata com t =
 			(e.e_pos, ["",e.e_meta],List.map (fun n -> n, (PMap.find n e.e_constrs).ef_meta) e.e_names, [])
 			(e.e_pos, ["",e.e_meta],List.map (fun n -> n, (PMap.find n e.e_constrs).ef_meta) e.e_names, [])
 		| TTypeDecl t ->
 		| TTypeDecl t ->
 			(t.t_pos, ["",t.t_meta],(match follow t.t_type with TAnon a -> PMap.fold (fun f acc -> (f.cf_name,f.cf_meta) :: acc) a.a_fields [] | _ -> []),[])
 			(t.t_pos, ["",t.t_meta],(match follow t.t_type with TAnon a -> PMap.fold (fun f acc -> (f.cf_name,f.cf_meta) :: acc) a.a_fields [] | _ -> []),[])
+		| TAbstractDecl a ->
+			(a.a_pos, ["",a.a_meta],[],[])
 	) in
 	) in
 	let filter l =
 	let filter l =
 		let l = List.map (fun (n,ml) -> n, List.filter (fun (m,_,_) -> m.[0] <> ':') ml) l in
 		let l = List.map (fun (n,ml) -> n, List.filter (fun (m,_,_) -> m.[0] <> ':') ml) l in
@@ -505,6 +509,8 @@ let build_instance ctx mtype p =
 		e.e_types , e.e_path , (fun t -> TEnum (e,t))
 		e.e_types , e.e_path , (fun t -> TEnum (e,t))
 	| TTypeDecl t ->
 	| TTypeDecl t ->
 		t.t_types , t.t_path , (fun tl -> TType(t,tl))
 		t.t_types , t.t_path , (fun tl -> TType(t,tl))
+	| TAbstractDecl a ->
+		a.a_types, a.a_path, (fun tl -> TAbstract(a,tl))
 
 
 let on_inherit ctx c p h =
 let on_inherit ctx c p h =
 	match h with
 	match h with
@@ -1075,6 +1081,7 @@ let rename_local_vars com e =
 		| TInst (c,_) -> check (TClassDecl c)
 		| TInst (c,_) -> check (TClassDecl c)
 		| TEnum (e,_) -> check (TEnumDecl e)
 		| TEnum (e,_) -> check (TEnumDecl e)
 		| TType (t,_) -> check (TTypeDecl t)
 		| TType (t,_) -> check (TTypeDecl t)
+		| TAbstract (a,_) -> check (TAbstractDecl a)
 		| TMono _ | TLazy _ | TAnon _ | TDynamic _ | TFun _ -> ()
 		| TMono _ | TLazy _ | TAnon _ | TDynamic _ | TFun _ -> ()
 	in
 	in
 	let rec loop e =
 	let rec loop e =
@@ -1276,6 +1283,7 @@ let post_process filters t =
 			c.cl_init <- Some (List.fold_left (fun e f -> f e) e filters));
 			c.cl_init <- Some (List.fold_left (fun e f -> f e) e filters));
 	| TEnumDecl _ -> ()
 	| TEnumDecl _ -> ()
 	| TTypeDecl _ -> ()
 	| TTypeDecl _ -> ()
+	| TAbstractDecl _ -> ()
 
 
 let post_process_end() =
 let post_process_end() =
 	incr pp_counter
 	incr pp_counter
@@ -1602,6 +1610,8 @@ let dump_types com =
 			print "}"
 			print "}"
 		| Type.TTypeDecl t ->
 		| Type.TTypeDecl t ->
 			print "%stype %s%s = %s" (if t.t_private then "private " else "") (s_type_path path) (params t.t_types) (s_type t.t_type);
 			print "%stype %s%s = %s" (if t.t_private then "private " else "") (s_type_path path) (params t.t_types) (s_type t.t_type);
+		| Type.TAbstractDecl a ->
+			print "%sabstract %s%s {}" (if a.a_private then "private " else "") (s_type_path path) (params a.a_types);
 		);
 		);
 		close();
 		close();
 	) com.types
 	) com.types
@@ -1638,6 +1648,7 @@ let default_cast ?(vtmp="$t") com e texpr t p =
 	let mk_texpr = function
 	let mk_texpr = function
 		| TClassDecl c -> TAnon { a_fields = PMap.empty; a_status = ref (Statics c) }
 		| TClassDecl c -> TAnon { a_fields = PMap.empty; a_status = ref (Statics c) }
 		| TEnumDecl e -> TAnon { a_fields = PMap.empty; a_status = ref (EnumStatics e) }
 		| TEnumDecl e -> TAnon { a_fields = PMap.empty; a_status = ref (EnumStatics e) }
+		| TAbstractDecl a -> TAnon { a_fields = PMap.empty; a_status = ref (AbstractStatics a) }
 		| TTypeDecl _ -> assert false
 		| TTypeDecl _ -> assert false
 	in
 	in
 	let vtmp = alloc_var vtmp e.etype in
 	let vtmp = alloc_var vtmp e.etype in

+ 13 - 1
genas3.ml

@@ -207,6 +207,14 @@ let rec type_str ctx t p =
 	match t with
 	match t with
 	| TEnum _ | TInst _ when List.memq t ctx.local_types ->
 	| TEnum _ | TInst _ when List.memq t ctx.local_types ->
 		"*"
 		"*"
+	| TAbstract (a,_) ->
+		(match a.a_path with
+		| [], "Void" -> "void"
+		| [], "UInt" -> "uint"
+		| [], "Int" -> "int"
+		| [], "Float" -> "Number"
+		| [], "Bool" -> "Boolean"
+		| _ -> s_path ctx true a.a_path p)
 	| TEnum (e,_) ->
 	| TEnum (e,_) ->
 		if e.e_extern then (match e.e_path with
 		if e.e_extern then (match e.e_path with
 			| [], "Void" -> "void"
 			| [], "Void" -> "void"
@@ -243,6 +251,10 @@ let rec type_str ctx t p =
 			(match args with
 			(match args with
 			| [t] ->
 			| [t] ->
 				(match follow t with
 				(match follow t with
+				| TAbstract ({ a_path = [],"UInt" },_)
+				| TAbstract ({ a_path = [],"Int" },_)
+				| TAbstract ({ a_path = [],"Float" },_)
+				| TAbstract ({ a_path = [],"Bool" },_)
 				| TInst ({ cl_path = [],"Int" },_)
 				| TInst ({ cl_path = [],"Int" },_)
 				| TInst ({ cl_path = [],"Float" },_)
 				| TInst ({ cl_path = [],"Float" },_)
 				| TEnum ({ e_path = [],"Bool" },_) -> "*"
 				| TEnum ({ e_path = [],"Bool" },_) -> "*"
@@ -1204,7 +1216,7 @@ let generate com =
 				let ctx = init infos e.e_path in
 				let ctx = init infos e.e_path in
 				generate_enum ctx e;
 				generate_enum ctx e;
 				close ctx
 				close ctx
-		| TTypeDecl t ->
+		| TTypeDecl _ | TAbstractDecl _ ->
 			()
 			()
 	) com.types;
 	) com.types;
 	(match com.main with
 	(match com.main with

+ 4 - 2
gencpp.ml

@@ -403,6 +403,8 @@ and type_string_suff suffix haxe_type =
       *)
       *)
 	| TDynamic haxe_type -> "Dynamic" ^ suffix
 	| TDynamic haxe_type -> "Dynamic" ^ suffix
 	| TLazy func -> type_string_suff suffix ((!func)())
 	| TLazy func -> type_string_suff suffix ((!func)())
+	| TAbstract (abs,pl) ->
+		"::" ^ (join_class_path abs.a_path "::") ^ suffix
 	)
 	)
 and type_string haxe_type =
 and type_string haxe_type =
 	type_string_suff "" haxe_type
 	type_string_suff "" haxe_type
@@ -2119,7 +2121,7 @@ let find_referenced_types ctx obj super_deps constructor_deps header_only =
 	| TClassDecl class_def -> visit_class class_def;
 	| TClassDecl class_def -> visit_class class_def;
 		(match class_def.cl_init with Some expression -> visit_types expression | _ -> ())
 		(match class_def.cl_init with Some expression -> visit_types expression | _ -> ())
 	| TEnumDecl enum_def -> visit_enum enum_def
 	| TEnumDecl enum_def -> visit_enum enum_def
-	| TTypeDecl _ -> (* These are expanded *) ());
+	| TTypeDecl _ | TAbstractDecl _ -> (* These are expanded *) ());
 
 
 	List.sort inc_cmp (List.filter (fun path -> (include_class_header path) ) (pmap_keys !types))
 	List.sort inc_cmp (List.filter (fun path -> (include_class_header path) ) (pmap_keys !types))
 	;;
 	;;
@@ -3146,7 +3148,7 @@ let generate common_ctx =
 				let deps = generate_enum_files common_ctx enum_def super_deps meta file_info in
 				let deps = generate_enum_files common_ctx enum_def super_deps meta file_info in
 				exe_classes := (enum_def.e_path, deps) :: !exe_classes;
 				exe_classes := (enum_def.e_path, deps) :: !exe_classes;
 			end
 			end
-		| TTypeDecl _ -> (* already done *) ()
+		| TTypeDecl _ | TAbstractDecl _ -> (* already done *) ()
 		);
 		);
 	) common_ctx.types;
 	) common_ctx.types;
 
 

+ 2 - 1
genjs.ml

@@ -586,6 +586,7 @@ and gen_expr ctx e =
 			let t = (match follow v.v_type with
 			let t = (match follow v.v_type with
 			| TEnum (e,_) -> Some (TEnumDecl e)
 			| TEnum (e,_) -> Some (TEnumDecl e)
 			| TInst (c,_) -> Some (TClassDecl c)
 			| TInst (c,_) -> Some (TClassDecl c)
+			| TAbstract (a,_) -> Some (TAbstractDecl a)
 			| TFun _
 			| TFun _
 			| TLazy _
 			| TLazy _
 			| TType _
 			| TType _
@@ -1071,7 +1072,7 @@ let generate_type ctx = function
 	| TEnumDecl e when e.e_extern ->
 	| TEnumDecl e when e.e_extern ->
 		()
 		()
 	| TEnumDecl e -> generate_enum ctx e
 	| TEnumDecl e -> generate_enum ctx e
-	| TTypeDecl _ -> ()
+	| TTypeDecl _ | TAbstractDecl _ -> ()
 
 
 let set_current_class ctx c =
 let set_current_class ctx c =
 	ctx.current <- c
 	ctx.current <- c

+ 4 - 4
genneko.ml

@@ -610,12 +610,12 @@ let gen_type ctx t acc =
 			acc
 			acc
 		else
 		else
 			gen_enum ctx e :: acc
 			gen_enum ctx e :: acc
-	| TTypeDecl t ->
+	| TTypeDecl _ | TAbstractDecl _ ->
 		acc
 		acc
 
 
 let gen_static_vars ctx t =
 let gen_static_vars ctx t =
 	match t with
 	match t with
-	| TEnumDecl _ | TTypeDecl _ -> []
+	| TEnumDecl _ | TTypeDecl _ | TAbstractDecl _ -> []
 	| TClassDecl c ->
 	| TClassDecl c ->
 		if c.cl_extern then
 		if c.cl_extern then
 			[]
 			[]
@@ -643,7 +643,7 @@ let gen_package ctx t =
 		| x :: l ->
 		| x :: l ->
 			let path = acc @ [x] in
 			let path = acc @ [x] in
 			if not (Hashtbl.mem ctx.packages path) then begin
 			if not (Hashtbl.mem ctx.packages path) then begin
-				let p = pos ctx (match t with TClassDecl c -> c.cl_pos | TEnumDecl e -> e.e_pos | TTypeDecl t -> t.t_pos) in
+				let p = pos ctx (t_infos t).mt_pos in
 				let e = (EBinop ("=",gen_type_path p (acc,x),call p (builtin p "new") [null p]),p) in
 				let e = (EBinop ("=",gen_type_path p (acc,x),call p (builtin p "new") [null p]),p) in
 				Hashtbl.add ctx.packages path ();
 				Hashtbl.add ctx.packages path ();
 				(match acc with
 				(match acc with
@@ -698,7 +698,7 @@ let gen_name ctx acc t =
 			| l ->
 			| l ->
 				let interf = field p (gen_type_path p c.cl_path) "__interfaces__" in
 				let interf = field p (gen_type_path p c.cl_path) "__interfaces__" in
 				(EBinop ("=",interf, call p (field p (ident p "Array") "new1") [interf; int p (List.length l)]),p) :: acc)
 				(EBinop ("=",interf, call p (field p (ident p "Array") "new1") [interf; int p (List.length l)]),p) :: acc)
-	| TTypeDecl _ ->
+	| TTypeDecl _ | TAbstractDecl _ ->
 		acc
 		acc
 
 
 let generate_libs_init = function
 let generate_libs_init = function

+ 21 - 9
genphp.ml

@@ -104,12 +104,17 @@ let rec class_string klass suffix params =
 and type_string_suff suffix haxe_type =
 and type_string_suff suffix haxe_type =
 	(match haxe_type with
 	(match haxe_type with
 	| TMono r -> (match !r with None -> "Dynamic" | Some t -> type_string_suff suffix t)
 	| TMono r -> (match !r with None -> "Dynamic" | Some t -> type_string_suff suffix t)
+	| TAbstract ({ a_path = [],"Int" },[]) -> "int"
+	| TAbstract ({ a_path = [],"Float" },[]) -> "double"
+	| TAbstract ({ a_path = [],"Bool" },[]) -> "bool"
+	| TAbstract ({ a_path = [],"Void" },[]) -> "Void"
 	| TEnum ({ e_path = ([],"Void") },[]) -> "Void"
 	| TEnum ({ e_path = ([],"Void") },[]) -> "Void"
 	| TEnum ({ e_path = ([],"Bool") },[]) -> "bool"
 	| TEnum ({ e_path = ([],"Bool") },[]) -> "bool"
 	| TInst ({ cl_path = ([],"Float") },[]) -> "double"
 	| TInst ({ cl_path = ([],"Float") },[]) -> "double"
 	| TInst ({ cl_path = ([],"Int") },[]) -> "int"
 	| TInst ({ cl_path = ([],"Int") },[]) -> "int"
 	| TEnum (enum,params) ->  (join_class_path enum.e_path "::") ^ suffix
 	| TEnum (enum,params) ->  (join_class_path enum.e_path "::") ^ suffix
 	| TInst (klass,params) ->  (class_string klass suffix params)
 	| TInst (klass,params) ->  (class_string klass suffix params)
+	| TAbstract (abs,params) ->  (join_class_path abs.a_path "::") ^ suffix
 	| TType (type_def,params) ->
 	| TType (type_def,params) ->
 		(match type_def.t_path with
 		(match type_def.t_path with
 		| [] , "Null" ->
 		| [] , "Null" ->
@@ -1497,20 +1502,26 @@ and gen_expr ctx e =
 			let b = save_locals ctx in
 			let b = save_locals ctx in
 			if not !first then spr ctx "else ";
 			if not !first then spr ctx "else ";
 			(match follow v.v_type with
 			(match follow v.v_type with
-			| TEnum (te,_) -> (match snd te.e_path with
-				| "Bool"   -> print ctx "if(is_bool($%s = $%s))" ev evar
+			| TEnum (te,_) -> (match te.e_path with
+				| [], "Bool"   -> print ctx "if(is_bool($%s = $%s))" ev evar
 				| _ -> print ctx "if(($%s = $%s) instanceof %s)" ev evar (s_path ctx te.e_path te.e_extern e.epos));
 				| _ -> print ctx "if(($%s = $%s) instanceof %s)" ev evar (s_path ctx te.e_path te.e_extern e.epos));
 				restore_in_block ctx in_block;
 				restore_in_block ctx in_block;
 				gen_expr ctx (mk_block e);
 				gen_expr ctx (mk_block e);
-			| TInst (tc,_) -> (match snd tc.cl_path with
-				| "Int"	-> print ctx "if(is_int($%s = $%s))"		ev evar
-				| "Float"  -> print ctx "if(is_numeric($%s = $%s))"	ev evar
-				| "String" -> print ctx "if(is_string($%s = $%s))"	ev evar
-				| "Array"  -> print ctx "if(($%s = $%s) instanceof _hx_array)"	ev evar
+			| TInst (tc,_) -> (match tc.cl_path with
+				| [], "Int"	-> print ctx "if(is_int($%s = $%s))"		ev evar
+				| [], "Float"  -> print ctx "if(is_numeric($%s = $%s))"	ev evar
+				| [], "String" -> print ctx "if(is_string($%s = $%s))"	ev evar
+				| [], "Array"  -> print ctx "if(($%s = $%s) instanceof _hx_array)"	ev evar
 				| _ -> print ctx "if(($%s = $%s) instanceof %s)"    ev evar (s_path ctx tc.cl_path tc.cl_extern e.epos));
 				| _ -> print ctx "if(($%s = $%s) instanceof %s)"    ev evar (s_path ctx tc.cl_path tc.cl_extern e.epos));
 				restore_in_block ctx in_block;
 				restore_in_block ctx in_block;
 				gen_expr ctx (mk_block e);
 				gen_expr ctx (mk_block e);
-
+			| TAbstract (ta,_) -> (match ta.a_path with
+				| [], "Int"	-> print ctx "if(is_int($%s = $%s))"		ev evar
+				| [], "Float"  -> print ctx "if(is_numeric($%s = $%s))"	ev evar
+				| [], "Bool"   -> print ctx "if(is_bool($%s = $%s))" ev evar
+				| _ -> print ctx "if(($%s = $%s) instanceof %s)"    ev evar (s_path ctx ta.a_path false e.epos));
+				restore_in_block ctx in_block;
+				gen_expr ctx (mk_block e);
 			| TFun _
 			| TFun _
 			| TLazy _
 			| TLazy _
 			| TType _
 			| TType _
@@ -1622,6 +1633,7 @@ and gen_expr ctx e =
 		let mk_texpr = function
 		let mk_texpr = function
 			| TClassDecl c -> TAnon { a_fields = PMap.empty; a_status = ref (Statics c) }
 			| TClassDecl c -> TAnon { a_fields = PMap.empty; a_status = ref (Statics c) }
 			| TEnumDecl e -> TAnon { a_fields = PMap.empty; a_status = ref (EnumStatics e) }
 			| TEnumDecl e -> TAnon { a_fields = PMap.empty; a_status = ref (EnumStatics e) }
+			| TAbstractDecl a -> TAnon { a_fields = PMap.empty; a_status = ref (AbstractStatics a) }
 			| TTypeDecl _ -> assert false
 			| TTypeDecl _ -> assert false
 		in
 		in
 		spr ctx "_hx_cast(";
 		spr ctx "_hx_cast(";
@@ -2324,7 +2336,7 @@ let generate com =
 				let ctx = init com php_lib_path e.e_path 1 in
 				let ctx = init com php_lib_path e.e_path 1 in
 			generate_enum ctx e;
 			generate_enum ctx e;
 			close ctx
 			close ctx
-		| TTypeDecl t ->
+		| TTypeDecl _ | TAbstractDecl _ ->
 			());
 			());
 	) com.types;
 	) com.types;
 	(match com.main with
 	(match com.main with

+ 4 - 0
genswf.ml

@@ -647,6 +647,9 @@ let build_dependencies t =
 		| TInst (c,pl) ->
 		| TInst (c,pl) ->
 			add_path c.cl_path DKType;
 			add_path c.cl_path DKType;
 			List.iter (add_type_rec (t::l)) pl;
 			List.iter (add_type_rec (t::l)) pl;
+		| TAbstract (a,pl) ->
+			add_path a.a_path DKType;
+			List.iter (add_type_rec (t::l)) pl;
 		| TFun (pl,t2) ->
 		| TFun (pl,t2) ->
 			List.iter (fun (_,_,t2) -> add_type_rec (t::l) t2) pl;
 			List.iter (fun (_,_,t2) -> add_type_rec (t::l) t2) pl;
 			add_type_rec (t::l) t2;
 			add_type_rec (t::l) t2;
@@ -1101,6 +1104,7 @@ let generate com swf_header =
 						let extern = (match t with
 						let extern = (match t with
 							| TClassDecl c -> c.cl_extern
 							| TClassDecl c -> c.cl_extern
 							| TEnumDecl e -> e.e_extern
 							| TEnumDecl e -> e.e_extern
+							| TAbstractDecl a -> false
 							| TTypeDecl t -> false
 							| TTypeDecl t -> false
 						) in
 						) in
 						if not extern && s_type_path (t_path t) = e.f9_classname then
 						if not extern && s_type_path (t_path t) = e.f9_classname then

+ 3 - 1
genswf8.ml

@@ -629,6 +629,7 @@ let rec gen_access ?(read_write=false) ctx forcall e =
 		(match t with
 		(match t with
 		| TClassDecl c -> gen_path ctx c.cl_path c.cl_extern
 		| TClassDecl c -> gen_path ctx c.cl_path c.cl_extern
 		| TEnumDecl e -> gen_path ctx e.e_path false
 		| TEnumDecl e -> gen_path ctx e.e_path false
+		| TAbstractDecl a -> gen_path ctx a.a_path false
 		| TTypeDecl _ -> assert false)
 		| TTypeDecl _ -> assert false)
 	| _ ->
 	| _ ->
 		if not forcall then invalid_expr e.epos;
 		if not forcall then invalid_expr e.epos;
@@ -658,6 +659,7 @@ and gen_try_catch ctx retval e catchs =
 		else let t = (match follow v.v_type with
 		else let t = (match follow v.v_type with
 			| TEnum (e,_) -> Some (TEnumDecl e)
 			| TEnum (e,_) -> Some (TEnumDecl e)
 			| TInst (c,_) -> Some (TClassDecl c)
 			| TInst (c,_) -> Some (TClassDecl c)
+			| TAbstract (a,_) -> Some (TAbstractDecl a)
 			| TFun _
 			| TFun _
 			| TLazy _
 			| TLazy _
 			| TType _
 			| TType _
@@ -1438,7 +1440,7 @@ let gen_type_def ctx t =
 			write ctx AObjSet;
 			write ctx AObjSet;
 		);
 		);
 		PMap.iter (fun _ f -> gen_enum_field ctx e f) e.e_constrs
 		PMap.iter (fun _ f -> gen_enum_field ctx e f) e.e_constrs
-	| TTypeDecl _ ->
+	| TTypeDecl _ | TAbstractDecl _ ->
 		()
 		()
 
 
 let gen_boot ctx =
 let gen_boot ctx =

+ 12 - 8
genswf9.ml

@@ -183,6 +183,10 @@ let rec follow_basic t =
 		(match follow_basic tp with
 		(match follow_basic tp with
 		| TMono _
 		| TMono _
 		| TFun _
 		| TFun _
+		| TAbstract ({ a_path = ([],"Int") },[])
+		| TAbstract ({ a_path = ([],"Float") },[])
+		| TAbstract ({ a_path = [],"UInt" },[])
+		| TAbstract ({ a_path = ([],"Bool") },[])
 		| TInst ({ cl_path = (["haxe"],"Int32") },[])
 		| TInst ({ cl_path = (["haxe"],"Int32") },[])
 		| TInst ({ cl_path = ([],"Int") },[])
 		| TInst ({ cl_path = ([],"Int") },[])
 		| TInst ({ cl_path = ([],"Float") },[])
 		| TInst ({ cl_path = ([],"Float") },[])
@@ -241,13 +245,13 @@ let type_void ctx t =
 
 
 let classify ctx t =
 let classify ctx t =
 	match follow_basic t with
 	match follow_basic t with
-	| TInst ({ cl_path = [],"Int" },_) | TInst ({ cl_path = ["haxe"],"Int32" },_) ->
+	| TAbstract ({ a_path = [],"Int" },_) | TInst ({ cl_path = [],"Int" },_) | TInst ({ cl_path = ["haxe"],"Int32" },_) ->
 		KInt
 		KInt
-	| TInst ({ cl_path = [],"Float" },_) ->
+	| TAbstract ({ a_path = [],"Float" },_) | TInst ({ cl_path = [],"Float" },_) ->
 		KFloat
 		KFloat
-	| TEnum ({ e_path = [],"Bool" },_) ->
+	| TAbstract ({ a_path = [],"Bool" },_) | TEnum ({ e_path = [],"Bool" },_) ->
 		KBool
 		KBool
-	| TEnum ({ e_path = [],"Void" },_) ->
+	| TAbstract ({ a_path = [],"Void" },_) | TEnum ({ e_path = [],"Void" },_) ->
 		KDynamic
 		KDynamic
 	| TEnum ({ e_path = [],"XmlType"; e_extern = true },_) ->
 	| TEnum ({ e_path = [],"XmlType"; e_extern = true },_) ->
 		KType (HMPath ([],"String"))
 		KType (HMPath ([],"String"))
@@ -263,9 +267,7 @@ let classify ctx t =
 			| _ :: l -> loop l
 			| _ :: l -> loop l
 		in
 		in
 		loop e.e_meta
 		loop e.e_meta
-	| TInst _ ->
-		KType (type_id ctx t)
-	| TType ({ t_path = [],"UInt" },_) ->
+	| TAbstract ({ a_path = [],"UInt" },_) | TType ({ t_path = [],"UInt" },_) ->
 		KUInt
 		KUInt
 	| TFun _ | TType ({ t_path = ["flash";"utils"],"Function" },[]) ->
 	| TFun _ | TType ({ t_path = ["flash";"utils"],"Function" },[]) ->
 		KType (HMPath ([],"Function"))
 		KType (HMPath ([],"Function"))
@@ -275,6 +277,8 @@ let classify ctx t =
 		| _ -> KDynamic)
 		| _ -> KDynamic)
 	| TType ({ t_path = ["flash";"utils"],"Object" },[]) ->
 	| TType ({ t_path = ["flash";"utils"],"Object" },[]) ->
 		KType (HMPath ([],"Object"))
 		KType (HMPath ([],"Object"))
+	| TInst _ | TAbstract _ ->
+		KType (type_id ctx t)
 	| TMono _
 	| TMono _
 	| TType _
 	| TType _
 	| TDynamic _ ->
 	| TDynamic _ ->
@@ -2307,7 +2311,7 @@ let generate_type ctx t =
 				hlf_kind = HFClass hlc;
 				hlf_kind = HFClass hlc;
 				hlf_metas = extract_meta e.e_meta;
 				hlf_metas = extract_meta e.e_meta;
 			})
 			})
-	| TTypeDecl _ ->
+	| TTypeDecl _ | TAbstractDecl _ ->
 		None
 		None
 
 
 let resource_path name =
 let resource_path name =

+ 23 - 11
genxml.ml

@@ -62,11 +62,9 @@ let real_path path meta =
 	in
 	in
 	loop meta
 	loop meta
 
 
-let cpath c =
-	real_path c.cl_path c.cl_meta
-
-let epath e =
-	real_path e.e_path e.e_meta
+let tpath t =
+	let i = t_infos t in
+	real_path i.mt_path i.mt_meta
 
 
 let rec follow_param t =
 let rec follow_param t =
 	match t with
 	match t with
@@ -100,14 +98,19 @@ let gen_meta meta =
 let rec gen_type t =
 let rec gen_type t =
 	match t with
 	match t with
 	| TMono m -> (match !m with None -> tag "unknown" | Some t -> gen_type t)
 	| TMono m -> (match !m with None -> tag "unknown" | Some t -> gen_type t)
-	| TEnum (e,params) -> node "e" [gen_path (epath e) e.e_private] (List.map gen_type params)
-	| TInst (c,params) -> node "c" [gen_path (cpath c) c.cl_private] (List.map gen_type params)
-	| TType (t,params) -> node "t" [gen_path t.t_path t.t_private] (List.map gen_type params)
+	| TEnum (e,params) -> gen_type_decl "e" (TEnumDecl e) params
+	| TInst (c,params) -> gen_type_decl "c" (TClassDecl c) params
+	| TAbstract (a,params) -> gen_type_decl "x" (TAbstractDecl a) params
+	| TType (t,params) -> gen_type_decl "t" (TTypeDecl t) params
 	| TFun (args,r) -> node "f" ["a",String.concat ":" (List.map gen_arg_name args)] (List.map gen_type (List.map (fun (_,opt,t) -> if opt then follow_param t else t) args @ [r]))
 	| TFun (args,r) -> node "f" ["a",String.concat ":" (List.map gen_arg_name args)] (List.map gen_type (List.map (fun (_,opt,t) -> if opt then follow_param t else t) args @ [r]))
 	| TAnon a -> node "a" [] (pmap (fun f -> gen_field [] { f with cf_public = false }) a.a_fields)
 	| TAnon a -> node "a" [] (pmap (fun f -> gen_field [] { f with cf_public = false }) a.a_fields)
 	| TDynamic t2 -> node "d" [] (if t == t2 then [] else [gen_type t2])
 	| TDynamic t2 -> node "d" [] (if t == t2 then [] else [gen_type t2])
 	| TLazy f -> gen_type (!f())
 	| TLazy f -> gen_type (!f())
 
 
+and gen_type_decl n t pl =
+	let i = t_infos t in
+	node n [gen_path (tpath t) i.mt_private] (List.map gen_type pl)
+
 and gen_field att f =
 and gen_field att f =
 	let add_get_set acc name att =
 	let add_get_set acc name att =
 		match acc with
 		match acc with
@@ -146,7 +149,7 @@ let gen_type_params ipos priv path params pos m =
 	gen_path path priv :: ("params", String.concat ":" (List.map fst params)) :: (file @ mpriv @ mpath)
 	gen_path path priv :: ("params", String.concat ":" (List.map fst params)) :: (file @ mpriv @ mpath)
 
 
 let gen_class_path name (c,pl) =
 let gen_class_path name (c,pl) =
-	node name [("path",s_type_path (cpath c))] (List.map gen_type pl)
+	node name [("path",s_type_path (tpath (TClassDecl c)))] (List.map gen_type pl)
 
 
 let rec exists f c =
 let rec exists f c =
 	PMap.exists f.cf_name c.cl_fields ||
 	PMap.exists f.cf_name c.cl_fields ||
@@ -178,16 +181,20 @@ let gen_type_decl com pos t =
 			| None -> []
 			| None -> []
 			| Some t -> [node "haxe_dynamic" [] [gen_type t]]
 			| Some t -> [node "haxe_dynamic" [] [gen_type t]]
 		) in
 		) in
-		node "class" (gen_type_params pos c.cl_private (cpath c) c.cl_types c.cl_pos m @ ext @ interf) (tree @ stats @ fields @ constr @ doc @ meta @ dynamic)
+		node "class" (gen_type_params pos c.cl_private (tpath t) c.cl_types c.cl_pos m @ ext @ interf) (tree @ stats @ fields @ constr @ doc @ meta @ dynamic)
 	| TEnumDecl e ->
 	| TEnumDecl e ->
 		let doc = gen_doc_opt e.e_doc in
 		let doc = gen_doc_opt e.e_doc in
 		let meta = gen_meta e.e_meta in
 		let meta = gen_meta e.e_meta in
-		node "enum" (gen_type_params pos e.e_private (epath e) e.e_types e.e_pos m) (pmap gen_constr e.e_constrs @ doc @ meta)
+		node "enum" (gen_type_params pos e.e_private (tpath t) e.e_types e.e_pos m) (pmap gen_constr e.e_constrs @ doc @ meta)
 	| TTypeDecl t ->
 	| TTypeDecl t ->
 		let doc = gen_doc_opt t.t_doc in
 		let doc = gen_doc_opt t.t_doc in
 		let meta = gen_meta t.t_meta in
 		let meta = gen_meta t.t_meta in
 		let tt = gen_type t.t_type in
 		let tt = gen_type t.t_type in
 		node "typedef" (gen_type_params pos t.t_private t.t_path t.t_types t.t_pos m) (tt :: doc @ meta)
 		node "typedef" (gen_type_params pos t.t_private t.t_path t.t_types t.t_pos m) (tt :: doc @ meta)
+	| TAbstractDecl a ->
+		let doc = gen_doc_opt a.a_doc in
+		let meta = gen_meta a.a_meta in
+		node "abstract" (gen_type_params pos a.a_private (tpath t) a.a_types a.a_pos m) ([] @ doc @ meta)
 
 
 let att_str att =
 let att_str att =
 	String.concat "" (List.map (fun (a,v) -> Printf.sprintf " %s=\"%s\"" a v) att)
 	String.concat "" (List.map (fun (a,v) -> Printf.sprintf " %s=\"%s\"" a v) att)
@@ -287,6 +294,8 @@ let generate_type com t =
 			path e.e_path tl
 			path e.e_path tl
 		| TType (t,tl) ->
 		| TType (t,tl) ->
 			path t.t_path tl
 			path t.t_path tl
+		| TAbstract (a,tl) ->
+			path a.a_path tl
 		| TAnon a ->
 		| TAnon a ->
 			let fields = PMap.fold (fun f acc -> (f.cf_name ^ " : " ^ stype f.cf_type) :: acc) a.a_fields [] in
 			let fields = PMap.fold (fun f acc -> (f.cf_name ^ " : " ^ stype f.cf_type) :: acc) a.a_fields [] in
 			"{" ^ String.concat ", " fields ^ "}"
 			"{" ^ String.concat ", " fields ^ "}"
@@ -439,6 +448,9 @@ let generate_type com t =
 		p "typedef %s = " (stype (TType (t,List.map snd t.t_types)));
 		p "typedef %s = " (stype (TType (t,List.map snd t.t_types)));
 		p "%s" (stype t.t_type);
 		p "%s" (stype t.t_type);
 		p "\n";
 		p "\n";
+	| TAbstractDecl a ->
+		print_meta a.a_meta;
+		p "abstract %s {}" (stype (TAbstract (a,List.map snd a.a_types)));
 	);
 	);
 	IO.close_out ch
 	IO.close_out ch
 
 

+ 12 - 3
interp.ml

@@ -2260,7 +2260,7 @@ let macro_lib =
 					(match !r with
 					(match !r with
 					| None -> t
 					| None -> t
 					| Some t -> t)
 					| Some t -> t)
-				| TEnum _ | TInst _ | TFun _ | TAnon _ | TDynamic _ ->
+				| TAbstract _ | TEnum _ | TInst _ | TFun _ | TAnon _ | TDynamic _ ->
 					t
 					t
 				| TType (t,tl) ->
 				| TType (t,tl) ->
 					apply_params t.t_types tl t.t_type
 					apply_params t.t_types tl t.t_type
@@ -3897,6 +3897,7 @@ let rec encode_mtype t fields =
 		"module", enc_string (s_type_path i.mt_module.m_path);
 		"module", enc_string (s_type_path i.mt_module.m_path);
 		"isPrivate", VBool i.mt_private;
 		"isPrivate", VBool i.mt_private;
 		"meta", encode_meta i.mt_meta (fun m -> i.mt_meta <- m);
 		"meta", encode_meta i.mt_meta (fun m -> i.mt_meta <- m);
+		"doc", null enc_string i.mt_doc;
 	] @ fields)
 	] @ fields)
 
 
 and encode_tenum e =
 and encode_tenum e =
@@ -3906,7 +3907,11 @@ and encode_tenum e =
 		"params", enc_array (List.map (fun (n,t) -> enc_obj ["name",enc_string n;"t",encode_type t]) e.e_types);
 		"params", enc_array (List.map (fun (n,t) -> enc_obj ["name",enc_string n;"t",encode_type t]) e.e_types);
 		"constructs", encode_pmap encode_efield e.e_constrs;
 		"constructs", encode_pmap encode_efield e.e_constrs;
 		"names", enc_array (List.map enc_string e.e_names);
 		"names", enc_array (List.map enc_string e.e_names);
-		"doc", null enc_string e.e_doc;
+	]
+
+and encode_tabstract a =
+	encode_mtype (TAbstractDecl a) [
+		"params", enc_array (List.map (fun (n,t) -> enc_obj ["name",enc_string n;"t",encode_type t]) a.a_types);
 	]
 	]
 
 
 and encode_efield f =
 and encode_efield f =
@@ -4039,6 +4044,8 @@ and encode_type t =
 				6, [encode_type tsub]
 				6, [encode_type tsub]
 		| TLazy f ->
 		| TLazy f ->
 			loop (!f())
 			loop (!f())
+		| TAbstract (a, pl) ->
+			7, [encode_ref a encode_tabstract (fun() -> s_type_path a.a_path); encode_tparams pl]
 	in
 	in
 	let tag, pl = loop t in
 	let tag, pl = loop t in
 	enc_enum IType tag pl
 	enc_enum IType tag pl
@@ -4170,6 +4177,8 @@ let rec make_type = function
 		tpath c.cl_path (List.map make_type pl)
 		tpath c.cl_path (List.map make_type pl)
 	| TType (t,pl) ->
 	| TType (t,pl) ->
 		tpath t.t_path (List.map make_type pl)
 		tpath t.t_path (List.map make_type pl)
+	| TAbstract (a,pl) ->
+		tpath a.a_path (List.map make_type pl)
 	| TFun (args,ret) ->
 	| TFun (args,ret) ->
 		CTFunction (List.map (fun (_,_,t) -> make_type t) args, make_type ret)
 		CTFunction (List.map (fun (_,_,t) -> make_type t) args, make_type ret)
 	| TAnon a ->
 	| TAnon a ->
@@ -4274,7 +4283,7 @@ let rec make_ast e =
 		let t = (match t with
 		let t = (match t with
 			| None -> None
 			| None -> None
 			| Some t ->
 			| Some t ->
-				let t = (match t with TClassDecl c -> TInst (c,[]) | TEnumDecl e -> TEnum (e,[]) | TTypeDecl t -> TType (t,[])) in
+				let t = (match t with TClassDecl c -> TInst (c,[]) | TEnumDecl e -> TEnum (e,[]) | TTypeDecl t -> TType (t,[]) | TAbstractDecl a -> TAbstract (a,[])) in
 				Some (try make_type t with Exit -> assert false)
 				Some (try make_type t with Exit -> assert false)
 		) in
 		) in
 		ECast (make_ast e,t))
 		ECast (make_ast e,t))

+ 1 - 1
lexer.mll

@@ -75,7 +75,7 @@ let keywords =
 		Switch;Case;Default;Public;Private;Try;Untyped;
 		Switch;Case;Default;Public;Private;Try;Untyped;
 		Catch;New;This;Throw;Extern;Enum;In;Interface;
 		Catch;New;This;Throw;Extern;Enum;In;Interface;
 		Cast;Override;Dynamic;Typedef;Package;Callback;
 		Cast;Override;Dynamic;Typedef;Package;Callback;
-		Inline;Using;Null;True;False];
+		Inline;Using;Null;True;False;Abstract];
 	h
 	h
 
 
 let init file =
 let init file =

+ 6 - 3
optimizer.ml

@@ -180,7 +180,7 @@ let rec type_inline ctx cf f ethis params tret p force =
 	let in_local_fun = ref false in
 	let in_local_fun = ref false in
 	let cancel_inlining = ref false in
 	let cancel_inlining = ref false in
 	let has_return_value = ref false in
 	let has_return_value = ref false in
-	let ret_val = (match follow f.tf_type with TEnum ({ e_path = ([],"Void") },[]) -> false | _ -> true) in
+	let ret_val = (match follow f.tf_type with TEnum ({ e_path = ([],"Void") },[]) | TAbstract ({ a_path = ([],"Void") },[]) -> false | _ -> true) in
 	let rec map term e =
 	let rec map term e =
 		let po = e.epos in
 		let po = e.epos in
 		let e = { e with epos = p } in
 		let e = { e with epos = p } in
@@ -349,7 +349,7 @@ let rec type_inline ctx cf f ethis params tret p force =
 				(match follow e.etype with 
 				(match follow e.etype with 
 				| TMono _ -> 
 				| TMono _ -> 
 					(match follow tret with
 					(match follow tret with
-					| TEnum ({ e_path = [],"Void" },_) -> e
+					| TEnum ({ e_path = [],"Void" },_) | TAbstract ({ a_path = [],"Void" },_) -> e
 					| _ -> raise (Unify_error []))
 					| _ -> raise (Unify_error []))
 				| _ -> 
 				| _ -> 
 					type_eq EqStrict (if has_params then map_type e.etype else e.etype) tret;
 					type_eq EqStrict (if has_params then map_type e.etype else e.etype) tret;
@@ -541,6 +541,9 @@ let rec add_final_return e t =
 			| TInst ({ cl_path = [],"Int" },_) -> TInt 0l
 			| TInst ({ cl_path = [],"Int" },_) -> TInt 0l
 			| TInst ({ cl_path = [],"Float" },_) -> TFloat "0."
 			| TInst ({ cl_path = [],"Float" },_) -> TFloat "0."
 			| TEnum ({ e_path = [],"Bool" },_) -> TBool false
 			| TEnum ({ e_path = [],"Bool" },_) -> TBool false
+			| TAbstract ({ a_path = [],"Int" },_) -> TInt 0l
+			| TAbstract ({ a_path = [],"Float" },_) -> TFloat "0."
+			| TAbstract ({ a_path = [],"Bool" },_) -> TBool false
 			| _ -> TNull
 			| _ -> TNull
 		) in
 		) in
 		{ eexpr = TReturn (Some { eexpr = TConst c; epos = p; etype = t }); etype = t; epos = p }
 		{ eexpr = TReturn (Some { eexpr = TConst c; epos = p; etype = t }); etype = t; epos = p }
@@ -633,7 +636,7 @@ let sanitize_expr com e =
 		{ e with eexpr = TFor (v,e1,e2) }
 		{ e with eexpr = TFor (v,e1,e2) }
 	| TFunction f ->
 	| TFunction f ->
 		let f = (match follow f.tf_type with
 		let f = (match follow f.tf_type with
-			| TEnum ({ e_path = [],"Void" },[]) -> f
+			| TEnum ({ e_path = [],"Void" },[]) | TAbstract ({ a_path = [],"Void" },[]) -> f
 			| t ->
 			| t ->
 				if com.config.pf_add_final_return then { f with tf_expr = add_final_return f.tf_expr t } else f
 				if com.config.pf_add_final_return then { f with tf_expr = add_final_return f.tf_expr t } else f
 		) in
 		) in

+ 16 - 1
parser.ml

@@ -232,6 +232,21 @@ and parse_type_decl s =
 				d_flags = List.map snd c;
 				d_flags = List.map snd c;
 				d_data = t;
 				d_data = t;
 			}, punion p1 p2)
 			}, punion p1 p2)
+		| [< '(Kwd Abstract,p1); doc = get_doc; name = type_name; tl = parse_constraint_params; sl = psep Comma parse_abstract_relations; '(BrOpen,_); '(BrClose,p2) >] ->
+			let flags = List.map (fun (_,c) -> match c with EPrivate -> APrivAbstract | EExtern -> error (Custom "extern abstract not allowed") p1) c in
+			(EAbstract {
+				d_name = name;
+				d_doc = doc;
+				d_meta = meta;
+				d_params = tl;
+				d_flags = flags @ sl;
+				d_data = ();
+			},punion p1 p2)
+
+and parse_abstract_relations s =
+	match s with parser
+	| [< '(Binop OpLte,_); t = parse_complex_type >] -> ASuperType t
+	| [< '(Binop OpAssign,p1); '(Binop OpGt,p2) when p1.pmax = p2.pmin; t = parse_complex_type >] -> ASubType t
 
 
 and parse_package s = psep Dot lower_ident s
 and parse_package s = psep Dot lower_ident s
 
 
@@ -298,7 +313,7 @@ and parse_class_field_resume tdecl s =
 				junk_tokens (k - 1);
 				junk_tokens (k - 1);
 				[]
 				[]
 			(* type declaration *)
 			(* type declaration *)
-			| Eof :: _ | Kwd Import :: _ | Kwd Using :: _ | Kwd Extern :: _ | Kwd Class :: _ | Kwd Interface :: _ | Kwd Enum :: _ | Kwd Typedef :: _ ->
+			| Eof :: _ | Kwd Import :: _ | Kwd Using :: _ | Kwd Extern :: _ | Kwd Class :: _ | Kwd Interface :: _ | Kwd Enum :: _ | Kwd Typedef :: _ | Kwd Abstract :: _->
 				junk_tokens (k - 1);
 				junk_tokens (k - 1);
 				[]
 				[]
 			| [] ->
 			| [] ->

+ 4 - 0
std/haxe/macro/Type.hx

@@ -38,6 +38,7 @@ enum Type {
 	TAnonymous( a : Ref<AnonType> );
 	TAnonymous( a : Ref<AnonType> );
 	TDynamic( t : Null<Type> );
 	TDynamic( t : Null<Type> );
 	TLazy( f : Void -> Type );
 	TLazy( f : Void -> Type );
+	TAbstract( t : Ref<AbstractType>, params : Array<Type> );
 }
 }
 
 
 typedef AnonType = {
 typedef AnonType = {
@@ -111,6 +112,9 @@ typedef DefType = {> BaseType,
 	var type : Type;
 	var type : Type;
 }
 }
 
 
+
+typedef AbstractType = BaseType;
+
 typedef MetaAccess = {
 typedef MetaAccess = {
 	function get() : Expr.Metadata;
 	function get() : Expr.Metadata;
 	function add( name : String, params : Array<Expr>, pos : Expr.Position ) : Void;
 	function add( name : String, params : Array<Expr>, pos : Expr.Position ) : Void;

+ 0 - 2
std/neko/_std/Std.hx

@@ -72,7 +72,6 @@
 		Dynamic = { __name__ : ["Dynamic"] };
 		Dynamic = { __name__ : ["Dynamic"] };
 		Class = { __name__ : ["Class"] };
 		Class = { __name__ : ["Class"] };
 		Enum = {};
 		Enum = {};
-		Void = { __ename__ : ["Void"] };
 		var cl = neko.Boot.__classes;
 		var cl = neko.Boot.__classes;
 		cl.Int = Int;
 		cl.Int = Int;
 		cl.Float = Float;
 		cl.Float = Float;
@@ -80,7 +79,6 @@
 		cl.Dynamic = Dynamic;
 		cl.Dynamic = Dynamic;
 		cl.Class = Class;
 		cl.Class = Class;
 		cl.Enum = Enum;
 		cl.Enum = Enum;
-		cl.Void = Void;
 	}
 	}
 
 
 }
 }

+ 3 - 8
tests/unit/TestReflect.hx

@@ -63,7 +63,7 @@ class TestReflect extends Test {
 		null,Int,String,Bool,Float,
 		null,Int,String,Bool,Float,
 		Array,Hash,List,Date,Xml,Math,
 		Array,Hash,List,Date,Xml,Math,
 		unit.MyEnum,unit.MyClass,unit.MySubClass,
 		unit.MyEnum,unit.MyClass,unit.MySubClass,
-		Class,Enum,#if !(java || cs)Void,#end Dynamic,unit.MyInterface
+		Class,Enum,Dynamic,unit.MyInterface
 	];
 	];
 
 
 	static inline function u( s : String ) : String {
 	static inline function u( s : String ) : String {
@@ -87,7 +87,7 @@ class TestReflect extends Test {
 		"null","Int","String","Bool","Float",
 		"null","Int","String","Bool","Float",
 		"Array",u("Hash"),u("List"),"Date","Xml","Math",
 		"Array",u("Hash"),u("List"),"Date","Xml","Math",
 		u2("unit","MyEnum"),u2("unit","MyClass"),u2("unit","MySubClass"),
 		u2("unit","MyEnum"),u2("unit","MyClass"),u2("unit","MySubClass"),
-		#if !flash9 u #end("Class"), u("Enum"), #if !(java || cs) u("Void"), #end u("Dynamic"),
+		#if !flash9 u #end("Class"), u("Enum"), u("Dynamic"),
 		u2("unit","MyInterface")
 		u2("unit","MyInterface")
 	];
 	];
 
 
@@ -99,7 +99,7 @@ class TestReflect extends Test {
 			f( t == null );
 			f( t == null );
 			if( name == u("Enum") ) {
 			if( name == u("Enum") ) {
 				// neither an enum or a class
 				// neither an enum or a class
-			} else if( t == MyEnum || #if !(java || cs) t == Void || #end t == Bool ) {
+			} else if( t == MyEnum || t == Bool ) {
 				eq( Type.getEnumName(t), name );
 				eq( Type.getEnumName(t), name );
 				eq( Type.resolveEnum(name), t );
 				eq( Type.resolveEnum(name), t );
 			} else {
 			} else {
@@ -108,9 +108,6 @@ class TestReflect extends Test {
 			}
 			}
 		}
 		}
 		infos(null);
 		infos(null);
-		// these are very specific cases since we can't allow reflection on core type
-		unspec( function() Type.getEnumConstructs(Void) );
-		unspec( function() Type.getEnumConstructs(Bool) );
 	}
 	}
 
 
 	public function testIs() {
 	public function testIs() {
@@ -143,7 +140,6 @@ class TestReflect extends Test {
 		is(function() { },null);
 		is(function() { },null);
 		is(MyClass,Class);
 		is(MyClass,Class);
 		is(MyEnum,Enum);
 		is(MyEnum,Enum);
-		is(Void,Enum);
 		is(Class,Class);
 		is(Class,Class);
 	}
 	}
 
 
@@ -184,7 +180,6 @@ class TestReflect extends Test {
 		typeof(function() {},TFunction);
 		typeof(function() {},TFunction);
 		typeof(MyClass,TObject);
 		typeof(MyClass,TObject);
 		typeof(MyEnum,TObject);
 		typeof(MyEnum,TObject);
-		typeof(Void,TObject);
 		#if !flash9
 		#if !flash9
 		// on flash9, Type.typeof(Class) is crashing the player
 		// on flash9, Type.typeof(Class) is crashing the player
 		typeof(Class,TObject);
 		typeof(Class,TObject);

+ 51 - 1
type.ml

@@ -53,6 +53,7 @@ type t =
 	| TAnon of tanon
 	| TAnon of tanon
 	| TDynamic of t
 	| TDynamic of t
 	| TLazy of (unit -> t) ref
 	| TLazy of (unit -> t) ref
+	| TAbstract of tabstract * tparams
 
 
 and tparams = t list
 and tparams = t list
 
 
@@ -87,6 +88,7 @@ and anon_status =
 	| Const
 	| Const
 	| Statics of tclass
 	| Statics of tclass
 	| EnumStatics of tenum
 	| EnumStatics of tenum
+	| AbstractStatics of tabstract
 
 
 and tanon = {
 and tanon = {
 	mutable a_fields : (string, tclass_field) PMap.t;
 	mutable a_fields : (string, tclass_field) PMap.t;
@@ -223,10 +225,23 @@ and tdef = {
 	mutable t_type : t;
 	mutable t_type : t;
 }
 }
 
 
+and tabstract = {
+	a_path : path;
+	a_module : module_def;
+	a_pos : Ast.pos;
+	a_private : bool;
+	a_doc : Ast.documentation;
+	mutable a_meta : metadata;
+	mutable a_types : type_params;
+	mutable a_sub : t list;
+	mutable a_super : t list;
+}
+
 and module_type =
 and module_type =
 	| TClassDecl of tclass
 	| TClassDecl of tclass
 	| TEnumDecl of tenum
 	| TEnumDecl of tenum
 	| TTypeDecl of tdef
 	| TTypeDecl of tdef
+	| TAbstractDecl of tabstract
 
 
 and module_def = {
 and module_def = {
 	m_id : int;
 	m_id : int;
@@ -342,6 +357,7 @@ let t_infos t : tinfos =
 	| TClassDecl c -> Obj.magic c
 	| TClassDecl c -> Obj.magic c
 	| TEnumDecl e -> Obj.magic e
 	| TEnumDecl e -> Obj.magic e
 	| TTypeDecl t -> Obj.magic t
 	| TTypeDecl t -> Obj.magic t
+	| TAbstractDecl a -> Obj.magic a
 
 
 let t_path t = (t_infos t).mt_path
 let t_path t = (t_infos t).mt_path
 
 
@@ -361,6 +377,8 @@ let rec s_type ctx t =
 		Ast.s_type_path c.cl_path ^ s_type_params ctx tl
 		Ast.s_type_path c.cl_path ^ s_type_params ctx tl
 	| TType (t,tl) ->
 	| TType (t,tl) ->
 		Ast.s_type_path t.t_path ^ s_type_params ctx tl
 		Ast.s_type_path t.t_path ^ s_type_params ctx tl
+	| TAbstract (a,tl) ->
+		Ast.s_type_path a.a_path ^ s_type_params ctx tl
 	| TFun ([],t) ->
 	| TFun ([],t) ->
 		"Void -> " ^ s_fun ctx t false
 		"Void -> " ^ s_fun ctx t false
 	| TFun (l,t) ->
 	| TFun (l,t) ->
@@ -381,6 +399,8 @@ and s_fun ctx t void =
 		"(" ^ s_type ctx t ^ ")"
 		"(" ^ s_type ctx t ^ ")"
 	| TEnum ({ e_path = ([],"Void") },[]) when void ->
 	| TEnum ({ e_path = ([],"Void") },[]) when void ->
 		"(" ^ s_type ctx t ^ ")"
 		"(" ^ s_type ctx t ^ ")"
+	| TAbstract ({ a_path = ([],"Void") },[]) when void ->
+		"(" ^ s_type ctx t ^ ")"
 	| TMono r ->
 	| TMono r ->
 		(match !r with
 		(match !r with
 		| None -> s_type ctx t
 		| None -> s_type ctx t
@@ -434,6 +454,8 @@ let map loop t =
 		TInst (c, List.map loop tl)
 		TInst (c, List.map loop tl)
 	| TType (t2,tl) ->
 	| TType (t2,tl) ->
 		TType (t2,List.map loop tl)
 		TType (t2,List.map loop tl)
+	| TAbstract (a,tl) ->
+		TAbstract (a,List.map loop tl)
 	| TFun (tl,r) ->
 	| TFun (tl,r) ->
 		TFun (List.map (fun (s,o,t) -> s, o, loop t) tl,loop r)
 		TFun (List.map (fun (s,o,t) -> s, o, loop t) tl,loop r)
 	| TAnon a ->
 	| TAnon a ->
@@ -478,6 +500,10 @@ let apply_params cparams params t =
 			(match tl with
 			(match tl with
 			| [] -> t
 			| [] -> t
 			| _ -> TType (t2,List.map loop tl))
 			| _ -> TType (t2,List.map loop tl))
+		| TAbstract (a,tl) ->
+			(match tl with
+			| [] -> t
+			| _ -> TAbstract (a,List.map loop tl))
 		| TInst (c,tl) ->
 		| TInst (c,tl) ->
 			(match tl with
 			(match tl with
 			| [] ->
 			| [] ->
@@ -551,6 +577,7 @@ let rec is_nullable ?(no_lazy=false) = function
 	| TInst ({ cl_path = ([],"Int") },[])
 	| TInst ({ cl_path = ([],"Int") },[])
 	| TInst ({ cl_path = ([],"Float") },[])
 	| TInst ({ cl_path = ([],"Float") },[])
 	| TEnum ({ e_path = ([],"Bool") },[]) -> false
 	| TEnum ({ e_path = ([],"Bool") },[]) -> false
+	| TAbstract (a,_) -> not (List.exists (fun (m2,_,_) -> m2 = ":notNull") a.a_meta)
 	| _ ->
 	| _ ->
 		true
 		true
 
 
@@ -574,7 +601,7 @@ let rec link e a b =
 		else match t with
 		else match t with
 		| TMono t -> (match !t with None -> false | Some t -> loop t)
 		| TMono t -> (match !t with None -> false | Some t -> loop t)
 		| TEnum (_,tl) -> List.exists loop tl
 		| TEnum (_,tl) -> List.exists loop tl
-		| TInst (_,tl) | TType (_,tl) -> List.exists loop tl
+		| TInst (_,tl) | TType (_,tl) | TAbstract (_,tl) -> List.exists loop tl
 		| TFun (tl,t) -> List.exists (fun (_,_,t) -> loop t) tl || loop t
 		| TFun (tl,t) -> List.exists (fun (_,_,t) -> loop t) tl || loop t
 		| TDynamic t2 ->
 		| TDynamic t2 ->
 			if t == t2 then
 			if t == t2 then
@@ -740,6 +767,9 @@ let rec type_eq param a b =
 			Unify_error l -> error (cannot_unify a b :: l))
 			Unify_error l -> error (cannot_unify a b :: l))
 	| TDynamic a , TDynamic b ->
 	| TDynamic a , TDynamic b ->
 		type_eq param a b
 		type_eq param a b
+	| TAbstract (a1,tl1) , TAbstract (a2,tl2) ->
+		if a1 != a2 && not (param = EqCoreType && a1.a_path = a2.a_path) then error [cannot_unify a b];
+		List.iter2 (type_eq param) tl1 tl2
 	| TAnon a1, TAnon a2 ->
 	| TAnon a1, TAnon a2 ->
 		(try
 		(try
 			PMap.iter (fun n f1 ->
 			PMap.iter (fun n f1 ->
@@ -892,6 +922,16 @@ let rec unify a b =
 	| TEnum (ea,tl1) , TEnum (eb,tl2) ->
 	| TEnum (ea,tl1) , TEnum (eb,tl2) ->
 		if ea != eb then error [cannot_unify a b];
 		if ea != eb then error [cannot_unify a b];
 		unify_types a b tl1 tl2
 		unify_types a b tl1 tl2
+	| TAbstract (a1,tl1) , TAbstract (a2,tl2) when a1 == a2 ->
+		unify_types a b tl1 tl2
+	| TAbstract (a1,tl1) , TAbstract (a2,tl2) ->		
+		if not (List.exists (fun t ->
+			let t = apply_params a1.a_types tl1 t in
+			try unify t b; true with Unify_error _ -> false
+		) a1.a_super) && not (List.exists (fun t ->
+			let t = apply_params a2.a_types tl2 t in
+			try unify a t; true with Unify_error _ -> false
+		) a2.a_sub) then error [cannot_unify a b]		
 	| TInst (c1,tl1) , TInst (c2,tl2) ->
 	| TInst (c1,tl1) , TInst (c2,tl2) ->
 		let rec loop c tl =
 		let rec loop c tl =
 			if c == c2 then begin
 			if c == c2 then begin
@@ -1032,6 +1072,16 @@ let rec unify a b =
 				error (cannot_unify a b :: l))
 				error (cannot_unify a b :: l))
 		| _ ->
 		| _ ->
 			error [cannot_unify a b])
 			error [cannot_unify a b])
+	| TAbstract (aa,tl), _  ->
+		if not (List.exists (fun t ->
+			let t = apply_params aa.a_types tl t in
+			try unify t b; true with Unify_error _ -> false
+		) aa.a_super) then error [cannot_unify a b];
+	| _, TAbstract (bb,tl) ->
+		if not (List.exists (fun t ->
+			let t = apply_params bb.a_types tl t in
+			try unify a t; true with Unify_error _ -> false
+		) bb.a_sub) then error [cannot_unify a b];
 	| _ , _ ->
 	| _ , _ ->
 		error [cannot_unify a b]
 		error [cannot_unify a b]
 
 

+ 34 - 2
typeload.ml

@@ -918,7 +918,7 @@ let init_class ctx c p herits fields =
 		match t with
 		match t with
 		| TFun (args,ret) -> is_full_type ret && List.for_all (fun (_,_,t) -> is_full_type t) args
 		| TFun (args,ret) -> is_full_type ret && List.for_all (fun (_,_,t) -> is_full_type t) args
 		| TMono r -> (match !r with None -> false | Some t -> is_full_type t)
 		| TMono r -> (match !r with None -> false | Some t -> is_full_type t)
-		| TInst _ | TEnum _ | TLazy _ | TDynamic _ | TAnon _ | TType _ -> true
+		| TAbstract _ | TInst _ | TEnum _ | TLazy _ | TDynamic _ | TAnon _ | TType _ -> true
 	in
 	in
 	let bind_type cf r p macro =
 	let bind_type cf r p macro =
 		if ctx.com.display then begin
 		if ctx.com.display then begin
@@ -1286,11 +1286,12 @@ let init_class ctx c p herits fields =
 
 
 let resolve_typedef t =
 let resolve_typedef t =
 	match t with
 	match t with
-	| TClassDecl _ | TEnumDecl _ -> t
+	| TClassDecl _ | TEnumDecl _ | TAbstractDecl _ -> t
 	| TTypeDecl td ->
 	| TTypeDecl td ->
 		match follow td.t_type with
 		match follow td.t_type with
 		| TEnum (e,_) -> TEnumDecl e
 		| TEnum (e,_) -> TEnumDecl e
 		| TInst (c,_) -> TClassDecl c
 		| TInst (c,_) -> TClassDecl c
+		| TAbstract (a,_) -> TAbstractDecl a
 		| _ -> t
 		| _ -> t
 
 
 let add_module ctx m p =
 let add_module ctx m p =
@@ -1362,6 +1363,21 @@ let type_module ctx m file tdecls loadp =
 				t_meta = d.d_meta;
 				t_meta = d.d_meta;
 			} in
 			} in
 			decls := TTypeDecl t :: !decls
 			decls := TTypeDecl t :: !decls
+	   | EAbstract d ->
+			let priv = List.mem APrivAbstract d.d_flags in
+			let path = make_path d.d_name priv in
+			let a = {
+				a_path = path;
+				a_private = priv;
+				a_module = m;
+				a_pos = p;
+				a_doc = d.d_doc;
+				a_types = [];
+				a_meta = d.d_meta;
+				a_sub = [];
+				a_super = [];
+			} in
+			decls := TAbstractDecl a :: !decls
 	) tdecls;
 	) tdecls;
 	m.m_types <- List.rev !decls;
 	m.m_types <- List.rev !decls;
 	add_module ctx m loadp;
 	add_module ctx m loadp;
@@ -1403,6 +1419,10 @@ let type_module ctx m file tdecls loadp =
 		let s = List.find (fun d -> match d with TTypeDecl { t_path = _ , n } -> n = name | _ -> false) m.m_types in
 		let s = List.find (fun d -> match d with TTypeDecl { t_path = _ , n } -> n = name | _ -> false) m.m_types in
 		match s with TTypeDecl s -> s | _ -> assert false
 		match s with TTypeDecl s -> s | _ -> assert false
 	in
 	in
+	let get_abstract name =
+		let s = List.find (fun d -> match d with TAbstractDecl { a_path = _ , n } -> n = name | _ -> false) m.m_types in
+		match s with TAbstractDecl a -> a | _ -> assert false
+	in
 	let filter_classes types =
 	let filter_classes types =
 		let rec loop acc types = match List.rev types with
 		let rec loop acc types = match List.rev types with
 			| t :: l ->
 			| t :: l ->
@@ -1425,6 +1445,9 @@ let type_module ctx m file tdecls loadp =
 		| ETypedef d ->
 		| ETypedef d ->
 			let t = get_tdef d.d_name in
 			let t = get_tdef d.d_name in
 			t.t_types <- List.map (type_type_params ctx t.t_path (fun() -> t.t_types) p) d.d_params;
 			t.t_types <- List.map (type_type_params ctx t.t_path (fun() -> t.t_types) p) d.d_params;
+		| EAbstract d ->
+			let a = get_abstract d.d_name in
+			a.a_types <- List.map (type_type_params ctx a.a_path (fun() -> a.a_types) p) d.d_params;
 	) tdecls;
 	) tdecls;
 	(* back to PASS2 *)
 	(* back to PASS2 *)
 	List.iter (fun (d,p) ->
 	List.iter (fun (d,p) ->
@@ -1530,6 +1553,14 @@ let type_module ctx m file tdecls loadp =
 				| None -> r := Some tt;
 				| None -> r := Some tt;
 				| Some _ -> assert false);
 				| Some _ -> assert false);
 			| _ -> assert false);
 			| _ -> assert false);
+		| EAbstract d ->
+			let a = get_abstract d.d_name in
+			let ctx = { ctx with type_params = a.a_types } in
+			List.iter (function
+				| APrivAbstract -> ()
+				| ASubType t -> a.a_sub <- load_complex_type ctx p t :: a.a_sub
+				| ASuperType t -> a.a_super <- load_complex_type ctx p t :: a.a_super
+			) d.d_flags
 	) tdecls;
 	) tdecls;
 	(* PASS 3 : type checking, delayed until all modules and types are built *)
 	(* PASS 3 : type checking, delayed until all modules and types are built *)
 	List.iter (delay ctx) (List.rev (!delays));
 	List.iter (delay ctx) (List.rev (!delays));
@@ -1592,6 +1623,7 @@ let parse_module ctx m p =
 			| EClass d -> build HPrivate d
 			| EClass d -> build HPrivate d
 			| EEnum d -> build EPrivate d
 			| EEnum d -> build EPrivate d
 			| ETypedef d -> build EPrivate d
 			| ETypedef d -> build EPrivate d
+			| EAbstract d -> build APrivAbstract d
 			| EImport _ | EUsing _ -> acc
 			| EImport _ | EUsing _ -> acc
 		) [(EImport { tpackage = !remap; tname = snd m; tparams = []; tsub = None; },null_pos)] decls)
 		) [(EImport { tpackage = !remap; tname = snd m; tparams = []; tsub = None; },null_pos)] decls)
 	else
 	else

+ 40 - 6
typer.ml

@@ -80,6 +80,8 @@ let rec classify t =
 	| TInst ({ cl_path = ([],"Int") },[]) -> KInt
 	| TInst ({ cl_path = ([],"Int") },[]) -> KInt
 	| TInst ({ cl_path = ([],"Float") },[]) -> KFloat
 	| TInst ({ cl_path = ([],"Float") },[]) -> KFloat
 	| TInst ({ cl_path = ([],"String") },[]) -> KString
 	| TInst ({ cl_path = ([],"String") },[]) -> KString
+	| TAbstract ({ a_path = [],"Int" },[]) -> KInt
+	| TAbstract ({ a_path = [],"Float" },[]) -> KFloat	
 	| TInst ({ cl_kind = KTypeParameter ctl },_) when List.exists (fun t -> match classify t with KInt | KFloat -> true | _ -> false) ctl -> KParam t
 	| TInst ({ cl_kind = KTypeParameter ctl },_) when List.exists (fun t -> match classify t with KInt | KFloat -> true | _ -> false) ctl -> KParam t
 	| TMono r when !r = None -> KUnk
 	| TMono r when !r = None -> KUnk
 	| TDynamic _ -> KDyn
 	| TDynamic _ -> KDyn
@@ -412,13 +414,31 @@ let rec type_module_type ctx t tparams p =
 		mk (TTypeExpr (TEnumDecl e)) (TType (t_tmp,types)) p
 		mk (TTypeExpr (TEnumDecl e)) (TType (t_tmp,types)) p
 	| TTypeDecl s ->
 	| TTypeDecl s ->
 		let t = apply_params s.t_types (List.map (fun _ -> mk_mono()) s.t_types) s.t_type in
 		let t = apply_params s.t_types (List.map (fun _ -> mk_mono()) s.t_types) s.t_type in
-		match follow t with
+		(match follow t with
 		| TEnum (e,params) ->
 		| TEnum (e,params) ->
 			type_module_type ctx (TEnumDecl e) (Some params) p
 			type_module_type ctx (TEnumDecl e) (Some params) p
 		| TInst (c,params) ->
 		| TInst (c,params) ->
 			type_module_type ctx (TClassDecl c) (Some params) p
 			type_module_type ctx (TClassDecl c) (Some params) p
+		| TAbstract (a,params) ->
+			type_module_type ctx (TAbstractDecl a) (Some params) p
 		| _ ->
 		| _ ->
-			error (s_type_path s.t_path ^ " is not a value") p
+			error (s_type_path s.t_path ^ " is not a value") p)
+	| TAbstractDecl a ->
+		if not (has_meta ":runtime_value" a.a_meta) then error (s_type_path a.a_path ^ " is not a value") p;
+		let t_tmp = {
+			t_path = fst a.a_path, "#" ^ snd a.a_path;
+			t_module = a.a_module;
+			t_doc = None;
+			t_pos = a.a_pos;
+			t_type = TAnon {
+				a_fields = PMap.empty;
+				a_status = ref (AbstractStatics a);
+			};
+			t_private = true;
+			t_types = [];
+			t_meta = no_meta;
+		} in
+		mk (TTypeExpr (TAbstractDecl a)) (TType (t_tmp,[])) p		
 
 
 let type_type ctx tpath p =
 let type_type ctx tpath p =
 	type_module_type ctx (Typeload.load_type_def ctx p { tpackage = fst tpath; tname = snd tpath; tparams = []; tsub = None }) None p
 	type_module_type ctx (Typeload.load_type_def ctx p { tpackage = fst tpath; tname = snd tpath; tparams = []; tsub = None }) None p
@@ -714,7 +734,7 @@ let type_ident_raise ?(imported_enums=true) ctx i p mode =
 			| [] -> raise Not_found
 			| [] -> raise Not_found
 			| t :: l ->
 			| t :: l ->
 				match t with
 				match t with
-				| TClassDecl _ ->
+				| TClassDecl _ | TAbstractDecl _ ->
 					loop l
 					loop l
 				| TTypeDecl t ->
 				| TTypeDecl t ->
 					(match follow t.t_type with
 					(match follow t.t_type with
@@ -2421,7 +2441,7 @@ let get_main ctx =
 	| Some cl ->
 	| Some cl ->
 		let t = Typeload.load_type_def ctx null_pos { tpackage = fst cl; tname = snd cl; tparams = []; tsub = None } in
 		let t = Typeload.load_type_def ctx null_pos { tpackage = fst cl; tname = snd cl; tparams = []; tsub = None } in
 		let ft, r = (match t with
 		let ft, r = (match t with
-		| TEnumDecl _ | TTypeDecl _ ->
+		| TEnumDecl _ | TTypeDecl _ | TAbstractDecl _ ->
 			error ("Invalid -main : " ^ s_type_path cl ^ " is not a class") null_pos
 			error ("Invalid -main : " ^ s_type_path cl ^ " is not a class") null_pos
 		| TClassDecl c ->
 		| TClassDecl c ->
 			try
 			try
@@ -2474,7 +2494,7 @@ let generate ctx =
 			| TClassDecl c ->
 			| TClassDecl c ->
 				walk_class p c;
 				walk_class p c;
 				t
 				t
-			| TEnumDecl _ | TTypeDecl _ ->
+			| TEnumDecl _ | TTypeDecl _ | TAbstractDecl _ ->
 				t
 				t
 			) in
 			) in
 			Hashtbl.replace states p Done;
 			Hashtbl.replace states p Done;
@@ -2486,6 +2506,9 @@ let generate ctx =
 	and loop_enum p e =
 	and loop_enum p e =
 		if e.e_path <> p then loop (TEnumDecl e)
 		if e.e_path <> p then loop (TEnumDecl e)
 
 
+	and loop_abstract p a =
+		if a.a_path <> p then loop (TAbstractDecl a)
+
 	and walk_static_call p c name =
 	and walk_static_call p c name =
 		try
 		try
 			let f = PMap.find name c.cl_statics in
 			let f = PMap.find name c.cl_statics in
@@ -2507,6 +2530,7 @@ let generate ctx =
 			(match t with
 			(match t with
 			| TClassDecl c -> loop_class p c
 			| TClassDecl c -> loop_class p c
 			| TEnumDecl e -> loop_enum p e
 			| TEnumDecl e -> loop_enum p e
+			| TAbstractDecl a -> loop_abstract p a
 			| TTypeDecl _ -> assert false)
 			| TTypeDecl _ -> assert false)
 		| TEnumField (e,_) ->
 		| TEnumField (e,_) ->
 			loop_enum p e
 			loop_enum p e
@@ -2538,6 +2562,7 @@ let generate ctx =
 				| TField ({ eexpr = TTypeExpr t },name) ->
 				| TField ({ eexpr = TTypeExpr t },name) ->
 					(match t with
 					(match t with
 					| TEnumDecl _ -> ()
 					| TEnumDecl _ -> ()
+					| TAbstractDecl _ -> assert false
 					| TTypeDecl _ -> assert false
 					| TTypeDecl _ -> assert false
 					| TClassDecl c -> walk_static_call p c name)
 					| TClassDecl c -> walk_static_call p c name)
 				| _ -> ()
 				| _ -> ()
@@ -2650,6 +2675,7 @@ let make_macro_api ctx p =
 		| TClassDecl c -> TInst (c,List.map snd c.cl_types)
 		| TClassDecl c -> TInst (c,List.map snd c.cl_types)
 		| TEnumDecl e -> TEnum (e,List.map snd e.e_types)
 		| TEnumDecl e -> TEnum (e,List.map snd e.e_types)
 		| TTypeDecl t -> TType (t,List.map snd t.t_types)
 		| TTypeDecl t -> TType (t,List.map snd t.t_types)
+		| TAbstractDecl a -> TAbstract (a,List.map snd a.a_types)
 	in
 	in
 	{
 	{
 		Interp.pos = p;
 		Interp.pos = p;
@@ -2768,7 +2794,8 @@ let make_macro_api ctx p =
 				Some (match mt with
 				Some (match mt with
 					| TClassDecl c -> TInst (c,[])
 					| TClassDecl c -> TInst (c,[])
 					| TEnumDecl e -> TEnum (e,[])
 					| TEnumDecl e -> TEnum (e,[])
-					| TTypeDecl t -> TType (t,[]))
+					| TTypeDecl t -> TType (t,[])
+					| TAbstractDecl a -> TAbstract(a,[]))
 			| None ->
 			| None ->
 				if ctx.curclass == null_class then
 				if ctx.curclass == null_class then
 					None
 					None
@@ -3103,6 +3130,13 @@ let rec create com =
 	);
 	);
 	List.iter (fun t ->
 	List.iter (fun t ->
 		match t with
 		match t with
+		| TAbstractDecl a ->
+			(match snd a.a_path with
+			| "Void" -> ctx.t.tvoid <- TAbstract (a,[]);
+			| "Float" -> ctx.t.tfloat <- TAbstract (a,[]);
+			| "Int" -> ctx.t.tint <- TAbstract (a,[])
+			| "Bool" -> ctx.t.tbool <- TAbstract (a,[])
+			| _ -> ());
 		| TEnumDecl e ->
 		| TEnumDecl e ->
 			(match snd e.e_path with
 			(match snd e.e_path with
 			| "Void" -> ctx.t.tvoid <- TEnum (e,[])
 			| "Void" -> ctx.t.tvoid <- TEnum (e,[])