Forráskód Böngészése

2.0 base :
no more plugin, use common
dynamic methods
override mandatory

Nicolas Cannasse 17 éve
szülő
commit
fde6d7ed2f

+ 10 - 8
Makefile.win

@@ -7,14 +7,14 @@ LIBS=extLib.cmxa extc.cmxa swfLib.cmxa unix.cmxa xml-light.cmxa
 LFLAGS=-g -o haxe.exe -I ../neko/libs/include/ocaml
 OUTPUT=sed 's/File "\([^"]\+\)", line \([0-9]\+\), \(.*\)/\1(\2): \3/' tmp.cmi
 
-FILES = ../neko/libs/include/ocaml/nast.cmx ast.cmx plugin.cmx ../neko/libs/include/ocaml/nxml.cmx ../neko/libs/include/ocaml/binast.cmx lexer.cmx type.cmx parser.cmx transform.cmx typer.cmx genswf9.cmx genswf8.cmx genneko.cmx genjs.cmx genswf.cmx genxml.cmx genas3.cmx main.cmx
+FILES = ../neko/libs/include/ocaml/nast.cmx ast.cmx common.cmx ../neko/libs/include/ocaml/nxml.cmx ../neko/libs/include/ocaml/binast.cmx lexer.cmx type.cmx parser.cmx transform.cmx typer.cmx genswf9.cmx genswf8.cmx genneko.cmx genjs.cmx genswf.cmx genxml.cmx genas3.cmx main.cmx
 
 all: haxe.exe
 
 haxe.exe: $(FILES)
 	ocamlopt $(LFLAGS) $(LIBS) $(FILES)
 
-genneko.cmx: typer.cmx type.cmx plugin.cmx ../neko/libs/include/ocaml/binast.cmx ../neko/libs/include/ocaml/nast.cmx lexer.cmx ast.cmx
+genneko.cmx: typer.cmx type.cmx common.cmx ../neko/libs/include/ocaml/binast.cmx ../neko/libs/include/ocaml/nast.cmx lexer.cmx ast.cmx
 
 ../neko/libs/include/ocaml/binast.cmx: ../neko/libs/include/ocaml/nast.cmx
 
@@ -24,11 +24,11 @@ genjs.cmx: typer.cmx type.cmx transform.cmx ast.cmx
 
 genas3.cmx: typer.cmx type.cmx transform.cmx ast.cmx
 
-genswf.cmx: typer.cmx type.cmx plugin.cmx genswf8.cmx genswf9.cmx
+genswf.cmx: typer.cmx type.cmx common.cmx genswf8.cmx genswf9.cmx
 
-genswf8.cmx: typer.cmx type.cmx transform.cmx plugin.cmx ast.cmx
+genswf8.cmx: typer.cmx type.cmx transform.cmx common.cmx ast.cmx
 
-genswf9.cmx: type.cmx ast.cmx typer.cmx transform.cmx plugin.cmx
+genswf9.cmx: type.cmx ast.cmx typer.cmx transform.cmx common.cmx
 
 genxml.cmx: typer.cmx type.cmx lexer.cmx ast.cmx
 
@@ -36,16 +36,18 @@ lexer.cmx: lexer.ml
 
 lexer.cmx: ast.cmx
 
-main.cmx: typer.cmx plugin.cmx parser.cmx lexer.cmx genxml.cmx genswf.cmx genneko.cmx genjs.cmx genas3.cmx ast.cmx
+main.cmx: typer.cmx common.cmx parser.cmx lexer.cmx genxml.cmx genswf.cmx genneko.cmx genjs.cmx genas3.cmx ast.cmx
 
-parser.cmx: parser.ml plugin.cmx lexer.cmx ast.cmx
+parser.cmx: parser.ml common.cmx lexer.cmx ast.cmx
 	(ocamlopt -pp camlp4o $(CFLAGS) -c parser.ml 2>tmp.cmi && $(OUTPUT)) || ($(OUTPUT) && exit 1)
 
 transform.cmx: type.cmx
 
 type.cmx: ast.cmx
 
-typer.cmx: type.cmx plugin.cmx parser.cmx lexer.cmx ast.cmx transform.cmx
+typer.cmx: type.cmx common.cmx parser.cmx lexer.cmx ast.cmx transform.cmx
+
+common.cmx: type.cmx
 
 clean:
 	rm -f haxe.exe

+ 3 - 3
ast.ml

@@ -57,7 +57,7 @@ type keyword =
 	| Cast
 	| Override
 	| Typedef
-	| F9Dynamic
+	| Dynamic
 	| Package
 	| Callback
 	| Inline
@@ -203,7 +203,7 @@ type access =
 	| APrivate
 	| AStatic
 	| AOverride
-	| AF9Dynamic
+	| ADynamic
 	| AInline
 
 type class_field =
@@ -320,7 +320,7 @@ let s_keyword = function
 	| Cast -> "cast"
 	| Override -> "override"
 	| Typedef -> "typedef"
-	| F9Dynamic -> "f9dynamic"
+	| Dynamic -> "dynamic"
 	| Package -> "package"
 	| Callback -> "callback"
 	| Inline -> "inline"

+ 116 - 0
common.ml

@@ -0,0 +1,116 @@
+(*
+ *  Haxe Compiler
+ *  Copyright (c)2005-2008 Nicolas Cannasse
+ *
+ *  This program is free software; you can redistribute it and/or modify
+ *  it under the terms of the GNU General Public License as published by
+ *  the Free Software Foundation; either version 2 of the License, or
+ *  (at your option) any later version.
+ *
+ *  This program is distributed in the hope that it will be useful,
+ *  but WITHOUT ANY WARRANTY; without even the implied warranty of
+ *  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ *  GNU General Public License for more details.
+ *
+ *  You should have received a copy of the GNU General Public License
+ *  along with this program; if not, write to the Free Software
+ *  Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
+ *)
+
+type package_rule =
+	| Forbidden
+	| Directory of string
+
+type platform =
+	| Cross
+	| Flash
+	| Js
+	| Neko
+	| Flash9
+	| Php
+
+type context = {
+	(* config *)
+	mutable debug : bool;
+	mutable verbose : bool;
+	mutable platform : platform;
+	mutable class_path : string list;
+	mutable main_class : Type.module_path option; 
+	mutable defines : (string,unit) PMap.t;
+	mutable package_rules : (string,package_rule) PMap.t;
+	(* output *)
+	mutable file : string;
+	mutable flash_version : int;
+	mutable types : Type.module_type list;
+	mutable resources : (string,string) Hashtbl.t;
+}
+
+let create() =
+	{
+		debug = false;
+		verbose = false;
+		platform = Cross;
+		class_path = [];
+		main_class = None;
+		defines = PMap.add "true" () PMap.empty;
+		package_rules = PMap.empty;
+		file = "";
+		types = [];
+		flash_version = 8;
+		resources = Hashtbl.create 0;
+	}
+
+let defined ctx v = PMap.mem v ctx.defines
+let define ctx v = ctx.defines <- PMap.add v () ctx.defines
+
+let platform ctx p = ctx.platform = p
+
+let find_file ctx f =
+	let rec loop = function
+		| [] -> raise Not_found
+		| p :: l ->
+			let file = p ^ f in
+			if Sys.file_exists file then
+				file
+			else
+				loop l
+	in
+	loop ctx.class_path
+
+let get_full_path = Extc.get_full_path
+
+(* ------------------------- TIMERS ----------------------------- *)
+
+type timer_infos = {
+	name : string;
+	mutable start : float;
+	mutable total : float;
+}
+
+let get_time = Unix.gettimeofday
+let htimers = Hashtbl.create 0
+
+let new_timer name =
+	try
+		let t = Hashtbl.find htimers name in
+		t.start <- get_time();
+		t
+	with Not_found ->
+		let t = { name = name; start = get_time(); total = 0.; } in
+		Hashtbl.add htimers name t;
+		t
+
+let curtime = ref None
+
+let timer name =
+	let t = new_timer name in
+	let old = !curtime in
+	curtime := Some t;
+	(function() ->
+		let dt = get_time() -. t.start in
+		t.total <- t.total +. dt;
+		curtime := old;
+		match !curtime with
+		| None -> ()
+		| Some ct -> ct.start <- ct.start +. dt
+	)

+ 6 - 4
genas3.ml

@@ -17,6 +17,7 @@
  *  Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
  *)
 open Type
+open Common
 
 type context = {
 	ch : out_channel;
@@ -924,7 +925,8 @@ let generate_base_enum ctx =
 	print ctx "}";
 	newline ctx
 
-let generate dir types =
+let generate com =
+	let dir = com.file in
 	let ctx = init dir ([],"enum") in
 	generate_base_enum ctx;
 	close ctx;
@@ -962,7 +964,7 @@ let generate dir types =
 				close ctx
 		| TTypeDecl t ->
 			()
-	) types;
+	) com.types;
 	match !boot with
 	| None -> assert false
 	| Some c ->
@@ -1191,8 +1193,8 @@ let genhx_class ctx c s =
 	prerr_endline ";";
 	IO.close_out ch
 
-let genhx file =
-	let file = (try Plugin.find_file file with Not_found -> failwith ("File not found : " ^ file)) in
+let genhx com =
+	let file = (try Common.find_file com com.file with Not_found -> failwith ("File not found : " ^ com.file)) in
 	let ch = IO.input_channel (open_in_bin file) in
 	SwfParser.full_parsing := true;
 	let _, swf = Swf.parse ch in

+ 10 - 9
genjs.ml

@@ -17,8 +17,10 @@
  *  Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
  *)
 open Type
+open Common
 
 type ctx = {
+	com : Common.context;
 	buf : Buffer.t;
 	packages : (string list,unit) Hashtbl.t;
 	mutable current : tclass;
@@ -28,7 +30,6 @@ type ctx = {
 	mutable in_value : bool;
 	mutable handle_break : bool;
 	mutable id_counter : int;
-	debug : bool;
 	mutable curmethod : (string * bool);
 }
 
@@ -72,7 +73,7 @@ let rec concat ctx s f = function
 let block = Transform.block
 
 let fun_block ctx f =
-	if ctx.debug then
+	if ctx.com.debug then
 		Transform.stack_block (ctx.current,fst ctx.curmethod) f.tf_expr
 	else
 		block f.tf_expr
@@ -672,8 +673,9 @@ let generate_type ctx = function
 	| TEnumDecl e -> generate_enum ctx e
 	| TTypeDecl _ -> ()
 
-let generate file types hres =
+let generate com =
 	let ctx = {
+		com = com;
 		buf = Buffer.create 16000;
 		packages = Hashtbl.create 0;
 		statics = [];
@@ -682,19 +684,18 @@ let generate file types hres =
 		tabs = "";
 		in_value = false;
 		handle_break = false;
-		debug = Plugin.defined "debug";
 		id_counter = 0;
 		curmethod = ("",false);
 	} in
-	let t = Plugin.timer "generate js" in
+	let t = Common.timer "generate js" in
 	print ctx "$estr = function() { return js.Boot.__string_rec(this,''); }";
 	newline ctx;
-	List.iter (generate_type ctx) types;
+	List.iter (generate_type ctx) com.types;
 	print ctx "$_ = {}";
 	newline ctx;
 	print ctx "js.Boot.__res = {}";
 	newline ctx;
-	if ctx.debug then begin
+	if com.debug then begin
 		print ctx "%s = []" Transform.stack_var;
 		newline ctx;
 		print ctx "%s = []" Transform.exc_stack_var;
@@ -704,7 +705,7 @@ let generate file types hres =
 		if String.contains data '\000' then failwith ("Resource " ^ name ^ " contains \\0 characters that can't be used in JavaScript");
 		print ctx "js.Boot.__res[\"%s\"] = \"%s\"" (Ast.s_escape name) (Ast.s_escape data);
 		newline ctx;
-	) hres;
+	) com.resources;
 	print ctx "js.Boot.__init()";
 	newline ctx;
 	List.iter (fun e ->
@@ -712,7 +713,7 @@ let generate file types hres =
 		newline ctx;
 	) (List.rev ctx.inits);
 	List.iter (generate_static ctx) (List.rev ctx.statics);
-	let ch = open_out file in
+	let ch = open_out com.file in
 	output_string ch (Buffer.contents ctx.buf);
 	close_out ch;
 	t()

+ 20 - 18
genneko.ml

@@ -20,9 +20,10 @@ open Ast
 open Type
 open Nast
 open Nxml
+open Common
 
 type context = {
-	methods : bool;
+	com : Common.context;	
 	mutable curclass : string;
 	mutable curmethod : string;
 	mutable locals : (string , bool) PMap.t;
@@ -36,17 +37,18 @@ let error msg p =
 let files = Hashtbl.create 0
 
 let pos ctx p =
-	let file = (match ctx.methods with
+	let file = (match ctx.com.debug with
 		| true -> ctx.curclass ^ "::" ^ ctx.curmethod
 		| false ->
 			try
 				Hashtbl.find files p.pfile
 			with Not_found -> try
+				(* lookup relative path *)
 				let len = String.length p.pfile in
 				let base = List.find (fun path ->
 					let l = String.length path in
-					len > l  && String.sub p.pfile 0 l = path
-				) (!Plugin.class_path) in
+					len > l && String.sub p.pfile 0 l = path
+				) ctx.com.Common.class_path in
 				let l = String.length base in
 				let path = String.sub p.pfile l (len - l) in
 				Hashtbl.add files p.pfile path;
@@ -728,16 +730,16 @@ let generate_libs_init = function
 			acc ^ "$loader.path = $array(" ^ (if full_path then "" else "@b + ") ^ "\"" ^ Nast.escape l ^ "\" + @s,$loader.path);"
 		) boot libs
 
-let generate file types hres libs =
+let generate com libs =
 	let ctx = {
-		methods = Plugin.defined "debug";
+		com = com;		
 		curclass = "$boot";
 		curmethod = "$init";
 		inits = [];
 		curblock = [];
 		locals = PMap.empty;
 	} in
-	let t = Plugin.timer "neko ast" in
+	let t = Common.timer "neko ast" in
 	let h = Hashtbl.create 0 in
 	let header = ENeko (
 		"@classes = $new(null);" ^
@@ -747,30 +749,30 @@ let generate file types hres libs =
 		"@tag_serialize = function() { return neko.Boot.__tagserialize(this); };" ^
 		generate_libs_init libs
 	) , { psource = "<header>"; pline = 1; } in
-	let packs = List.concat (List.map (gen_package ctx h) types) in
-	let names = List.fold_left (gen_name ctx) [] types in
-	let methods = List.rev (List.fold_left (fun acc t -> gen_type ctx t acc) [] types) in
-	let boot = gen_boot ctx hres in
+	let packs = List.concat (List.map (gen_package ctx h) com.types) in
+	let names = List.fold_left (gen_name ctx) [] com.types in
+	let methods = List.rev (List.fold_left (fun acc t -> gen_type ctx t acc) [] com.types) in
+	let boot = gen_boot ctx com.resources in
 	let inits = List.map (gen_expr ctx) (List.rev ctx.inits) in
-	let vars = List.concat (List.map (gen_static_vars ctx) types) in
+	let vars = List.concat (List.map (gen_static_vars ctx) com.types) in
 	let e = (EBlock (header :: packs @ methods @ boot :: names @ inits @ vars), null_pos) in
 	t();
-	let neko_file = (try Filename.chop_extension file with _ -> file) ^ ".neko" in
-	let w = Plugin.timer "neko ast write" in
+	let neko_file = (try Filename.chop_extension com.file with _ -> com.file) ^ ".neko" in
+	let w = Common.timer "neko ast write" in
 	let ch = IO.output_channel (open_out_bin neko_file) in
-	let source = Plugin.defined "neko_source" in
+	let source = Common.defined com "neko_source" in
 	if source then Nxml.write ch (Nxml.to_xml e) else Binast.write ch e;
 	IO.close_out ch;
 	let command cmd = try Sys.command cmd with _ -> -1 in
 	if source then begin
 		if command ("nekoc -p \"" ^ neko_file ^ "\"") <> 0 then failwith "Failed to print neko code";
 		Sys.remove neko_file;
-		Sys.rename ((try Filename.chop_extension file with _ -> file) ^ "2.neko") neko_file;
+		Sys.rename ((try Filename.chop_extension com.file with _ -> com.file) ^ "2.neko") neko_file;
 	end;
 	w();
-	let c = Plugin.timer "neko compilation" in
+	let c = Common.timer "neko compilation" in
 	if command ("nekoc \"" ^ neko_file ^ "\"") <> 0 then failwith "Neko compilation failure";
 	c();
 	let output = Filename.chop_extension neko_file ^ ".n" in
-	if output <> file then Sys.rename output file;
+	if output <> com.file then Sys.rename output com.file;
 	if not source then Sys.remove neko_file

+ 23 - 33
genswf.ml

@@ -21,12 +21,7 @@ open As3
 open As3hl
 open Genswf9
 open Type
-
-type swfinfos = {
-	mutable swf_version : int;
-	mutable swf_header : (int * int * float * int) option;
-	mutable swf_lib : string option;
-}
+open Common
 
 type context = {
 	mutable f8clips : string list;
@@ -43,9 +38,9 @@ let tag ?(ext=false) d = {
 	tdata = d;
 }
 
-let convert_header ver (w,h,fps,bg) =
+let convert_header com (w,h,fps,bg) =
 	{
-		h_version = ver;
+		h_version = com.flash_version;
 		h_size = {
 			rect_nbits = if (max w h) >= 820 then 16 else 15;
 			left = 0;
@@ -55,11 +50,11 @@ let convert_header ver (w,h,fps,bg) =
 		};
 		h_frame_count = 1;
 		h_fps = to_float16 (if fps > 127.0 then 127.0 else fps);
-		h_compressed = not (Plugin.defined "no-swf-compress");
+		h_compressed = not (Common.defined com "no-swf-compress");
 	} , bg
 
-let default_header ver =
-	convert_header ver (400,300,30.,0xFFFFFF)
+let default_header com =
+	convert_header com (400,300,30.,0xFFFFFF)
 
 let getclass i =
 	if Array.length i.hls_fields <> 1 then
@@ -151,10 +146,10 @@ let add_as3_code ctx data types =
 let add_as3_clips ctx cl =
 	ctx.f9clips <- List.filter (fun c -> c.f9_cid <> None) cl @ ctx.f9clips
 
-let generate file infos types hres =
-	let ver = infos.swf_version in
-	let t = Plugin.timer "generate swf" in
-	let file , codeclip = (try let f , c = ExtString.String.split file "@" in f, Some c with _ -> file , None) in
+let generate com swf_header swf_lib =
+	let ver = com.flash_version in
+	let t = Common.timer "generate swf" in
+	let file , codeclip = (try let f , c = ExtString.String.split com.file "@" in f, Some c with _ -> com.file , None) in
 	let ctx = {
 		f8clips = [];
 		f9clips = [];
@@ -164,11 +159,7 @@ let generate file infos types hres =
 		genmethod = (fun() -> assert false);
 	} in
 	if ver = 9 then begin
-		(* hack for an ocaml bug *)
-		(* instead of : let code, boot = Genswf9.generate types hres in *)
-		let f (h:(string,string) Hashtbl.t) = Genswf9.generate types h in
-		let tmp : (string,string) Hashtbl.t = hres in
-		let code, boot, m = f (Obj.magic tmp) in
+		let code, boot, m = Genswf9.generate com in
 		ctx.hx9code <- (match code with
 			| [i] when Array.length i.hls_fields = 0 ->
 				(* if we don't have any class defined, don't include Boot *)
@@ -179,13 +170,13 @@ let generate file infos types hres =
 		);
 		ctx.genmethod <- m;
 	end else begin
-		let code, clips = Genswf8.generate file ver types hres in
+		let code, clips = Genswf8.generate com in
 		ctx.code <- code;
 		ctx.f8clips <- List.map Ast.s_type_path clips;
 	end;
 	let build_swf content =
 		let sandbox = (if ver >= 8 then
-				let net = Plugin.defined "network-sandbox" in
+				let net = Common.defined com "network-sandbox" in
 				[tag (TSandbox (match ver, net with
 					| 9, true -> SBUnknown 9
 					| 9, false -> SBUnknown 8
@@ -195,7 +186,7 @@ let generate file infos types hres =
 			else
 				[]
 		) in
-		let debug = (if ver = 9 && Plugin.defined "fdb" then [tag (TEnableDebugger2 (0,""))] else []) in
+		let debug = (if ver = 9 && Common.defined com "fdb" then [tag (TEnableDebugger2 (0,""))] else []) in
 		let base_id = ref 0x5000 in
 		let clips = List.fold_left (fun acc m ->
 			incr base_id;
@@ -219,28 +210,28 @@ let generate file infos types hres =
 		List.iter (fun c ->
 			let path = ExtString.String.nsplit c.f9_classname "." in
 			let path = (match List.rev path with [] -> assert false | x :: l -> List.rev l, x) in
-			if c.f9_cid <> None && not (movieclip_exists types ctx.as3code path) then
+			if c.f9_cid <> None && not (movieclip_exists com.types ctx.as3code path) then
 				ctx.as3code <- build_movieclip ctx path :: ctx.as3code;
 		) ctx.f9clips;
 		let as3code = (match ctx.as3code @ ctx.hx9code with [] -> [] | l -> [tag (TActionScript3 (None,As3hlparse.flatten l))]) in
 		let clips9 = (if ver = 9 then [tag (TF9Classes ctx.f9clips)] else []) in
 		sandbox @ debug @ content @ clips @ code @ as3code @ clips9
 	in
-	let swf = (match infos.swf_lib with
+	let swf = (match swf_lib with
 		| None ->
-			let header , bg = (match infos.swf_header with None -> default_header ver | Some h -> convert_header ver h) in
+			let header , bg = (match swf_header with None -> default_header com | Some h -> convert_header com h) in
 			let tagbg = tag (TSetBgColor { cr = bg lsr 16; cg = (bg lsr 8) land 0xFF; cb = bg land 0xFF }) in
 			let tagshow = tag TShowFrame in
 			(header,build_swf [tagbg] @ [tagshow])
 		| Some file ->
-			let file = (try Plugin.find_file file with Not_found -> failwith ("File not found : " ^ file)) in
+			let file = (try Common.find_file com com.file with Not_found -> failwith ("File not found : " ^ file)) in
 			let ch = IO.input_channel (open_in_bin file) in
 			let h, swf = (try Swf.parse ch with _ -> failwith ("The input swf " ^ file ^ " is corrupted")) in
-			let header , tagbg = (match infos.swf_header with
+			let header , tagbg = (match swf_header with
 				| None ->
 					{ h with h_version = ver }, None
 				| Some h ->
-					let h , bg = convert_header ver h in
+					let h , bg = convert_header com h in
 					let tagbg = tag (TSetBgColor { cr = bg lsr 16; cg = (bg lsr 8) land 0xFF; cb = bg land 0xFF }) in
 					h , Some tagbg
 			) in
@@ -255,7 +246,7 @@ let generate file infos types hres =
 				| TPlaceObject2 _
 				| TPlaceObject3 _
 				| TRemoveObject2 _
-				| TRemoveObject _ when not (Plugin.defined "flash_use_stage") ->
+				| TRemoveObject _ when not (Common.defined com "flash_use_stage") ->
 					loop acc l
 				| TSetBgColor _ ->
 					(match tagbg with
@@ -283,16 +274,15 @@ let generate file infos types hres =
 					if ver = 9 then add_as3_clips ctx cl;
 					loop acc l
 				| TActionScript3 (_,data) ->
-					if ver = 9 then add_as3_code ctx data types;
+					if ver = 9 then add_as3_code ctx data com.types;
 					loop acc l
 				| _ ->
 					loop (t :: acc) l
 			in
 			(header , loop [] swf)
 	) in
-	let swf = if ver = 8 && Plugin.defined "flash_v9" then ({ (fst swf) with h_version = 9 }, snd swf) else swf in
 	t();
-	let t = Plugin.timer "write swf" in
+	let t = Common.timer "write swf" in
 	let ch = IO.output_channel (open_out_bin file) in
 	Swf.write ch swf;
 	IO.close_out ch;

+ 27 - 26
genswf8.ml

@@ -19,6 +19,7 @@
 open Swf
 open Ast
 open Type
+open Common
 
 type register =
 	| NoReg
@@ -38,7 +39,9 @@ type context = {
 	mutable ident_size : int;
 
 	(* management *)
+	com : Common.context;
 	packages : (string list,unit) Hashtbl.t;
+	flash6 : bool;
 	mutable idents : (string * bool,int) Hashtbl.t;
 	mutable movieclips : module_path list;
 	mutable inits : texpr list;
@@ -47,8 +50,6 @@ type context = {
 	mutable reg_count : int;
 	mutable reg_max : int;
 	mutable fun_stack : int;
-	version : int;
-	debug : bool;
 	mutable curclass : tclass;
 	mutable curmethod : (string * bool);
 	mutable fun_pargs : (int * bool list) list;
@@ -342,7 +343,7 @@ let gen_path ctx ?(protect=false) (p,t) is_extern =
 		VarObj
 
 let begin_func ctx need_super need_args args =
-	if ctx.version = 6 then
+	if ctx.flash6 then
 		let f = {
 			f_name = "";
 			Swf.f_args = List.map snd args;
@@ -436,7 +437,7 @@ let segment ctx =
 (* Generation Helpers *)
 
 let define_var ctx v ef exprs =
-	if ctx.version = 6 || List.exists (Transform.local_find false v) exprs then begin
+	if ctx.flash6 || List.exists (Transform.local_find false v) exprs then begin
 		push ctx [VStr (v,false)];
 		ctx.regs <- PMap.add v NoReg ctx.regs;
 		match ef with
@@ -457,7 +458,7 @@ let define_var ctx v ef exprs =
 
 let alloc_tmp ctx =
 	let r = alloc_reg ctx in
-	if ctx.version = 6 then
+	if ctx.flash6 then
 		let name = "$" ^ string_of_int r in		
 		define_var ctx name None [];
 		TmpVar (name,r);
@@ -551,7 +552,7 @@ let rec gen_access ctx forcall e =
 	match e.eexpr with
 	| TConst TSuper ->
 		(* for superconstructor *)
-		if ctx.version = 6 then begin
+		if ctx.flash6 then begin
 			push ctx [VStr ("super",true)];
 			VarStr
 		end else if forcall then begin
@@ -561,7 +562,7 @@ let rec gen_access ctx forcall e =
 		end else
 			VarReg 2
 	| TConst TThis ->
-		if ctx.version = 6 then begin
+		if ctx.flash6 then begin
 			push ctx [VStr ("this",true)];
 			VarStr
 		end else
@@ -951,7 +952,7 @@ and gen_expr_2 ctx retval e =
 		ctx.in_loop <- false;
 		let pargs = ref [] in
 		let rargs = List.map (fun (a,_,t) ->
-			let no_reg = ctx.version = 6 || Transform.local_find false a f.tf_expr in
+			let no_reg = ctx.flash6 || Transform.local_find false a f.tf_expr in
 			if no_reg then begin
 				ctx.regs <- PMap.add a NoReg ctx.regs;
 				pargs := unprotect a :: !pargs;
@@ -965,7 +966,7 @@ and gen_expr_2 ctx retval e =
 		) f.tf_args in
 		let tf = begin_func ctx reg_super (Transform.local_find true "__arguments__" f.tf_expr) rargs in
 		ctx.fun_pargs <- (ctx.code_pos, List.rev !pargs) :: ctx.fun_pargs;
-		if ctx.debug then begin
+		if ctx.com.debug then begin
 			let start_try = gen_try ctx in
 			gen_expr ctx false (Transform.stack_block ~useadd:true (ctx.curclass,fst ctx.curmethod) f.tf_expr);
 			let end_try = start_try() in
@@ -1143,7 +1144,7 @@ let gen_enum_field ctx e f =
 	| TFun (args,r) ->
 		ctx.regs <- PMap.empty;
 		ctx.reg_count <- 1;
-		let no_reg = ctx.version = 6 in
+		let no_reg = ctx.flash6 in
 		let rargs = List.map (fun (n,_,_) -> if no_reg then 0, n else alloc_reg ctx , "") args in
 		let nregs = List.length rargs + 2 in
 		let tf = begin_func ctx false false rargs in
@@ -1268,7 +1269,7 @@ let gen_type_def ctx t =
 			push ctx [VReg 0; VStr ("__super__",false)];
 			getvar ctx (gen_path ctx path csuper.cl_extern);
 			setvar ctx VarObj;
-			if ctx.version = 6 then begin
+			if ctx.flash6 then begin
 				(* myclass.prototype.__proto__ = superclass.prototype *)
 				push ctx [VReg 0; VStr ("prototype",true)];
 				getvar ctx VarObj;
@@ -1297,7 +1298,7 @@ let gen_type_def ctx t =
 			List.iter (fun (c,_) -> getvar ctx (gen_path ctx c.cl_path c.cl_extern)) l;
 			init_array ctx nimpl;
 			setvar ctx VarObj;
-			if ctx.version > 6 then begin
+			if not ctx.flash6 then begin
 				List.iter (fun (c,_) -> getvar ctx (gen_path ctx c.cl_path c.cl_extern)) l;
 				push ctx [VInt nimpl; VReg 0];
 				write ctx AImplements;
@@ -1383,7 +1384,7 @@ let build_tag (opcodes,idents) =
 	DynArray.set opcodes 0 idents;
 	TDoAction opcodes , pidents
 
-let convert_header ver (w,h,fps,bg) =
+let convert_header ctx ver (w,h,fps,bg) =
 	{
 		h_version = ver;
 		h_size = {
@@ -1395,14 +1396,16 @@ let convert_header ver (w,h,fps,bg) =
 		};
 		h_frame_count = 1;
 		h_fps = to_float16 (if fps > 127.0 then 127.0 else fps);
-		h_compressed = not (Plugin.defined "no-swf-compress");
+		h_compressed = not (Common.defined ctx "no-swf-compress");
 	} , bg
 
-let default_header ver =
-	convert_header ver (400,300,30.,0xFFFFFF)
+let default_header ctx ver =
+	convert_header ctx ver (400,300,30.,0xFFFFFF)
 
-let generate file ver types hres =
+let generate com =
 	let ctx = {
+		com = com;
+		flash6 = com.flash_version = 6;
 		segs = [];
 		opcodes = DynArray.create();
 		code_pos = 0;
@@ -1423,17 +1426,15 @@ let generate file ver types hres =
 		statics = [];
 		movieclips = [];
 		inits = [];
-		version = ver;
 		curclass = null_class;
 		curmethod = ("",false);
 		fun_pargs = [];
-		in_loop = false;
-		debug = Plugin.defined "debug";
+		in_loop = false;		
 	} in
 	write ctx (AStringPool []);
-	protect_all := not (Plugin.defined "swf-mark");
+	protect_all := not (Common.defined com "swf-mark");
 	extern_boot := true;
-	if ctx.debug then begin
+	if com.debug then begin
 		push ctx [VStr (Transform.stack_var,false); VInt 0];
 		write ctx AInitArray;
 		write ctx ASet;
@@ -1454,8 +1455,8 @@ let generate file ver types hres =
 	write ctx ASet;
 	ctx.reg_count <- 0;
 	(* ---- *)
-	List.iter (fun t -> gen_type_def ctx t) types;
-	gen_boot ctx hres;
+	List.iter (fun t -> gen_type_def ctx t) com.types;
+	gen_boot ctx com.resources;
 	List.iter (fun m -> gen_movieclip ctx m) ctx.movieclips;
 	let global_try = gen_try ctx in
 	List.iter (gen_expr ctx false) (List.rev ctx.inits);
@@ -1470,10 +1471,10 @@ let generate file ver types hres =
 	end_try();
 	let segs = List.rev ((ctx.opcodes,ctx.idents) :: ctx.segs) in
 	let tags = List.map build_tag segs in
-	if Plugin.defined "swf-mark" then begin
+	if Common.defined com "swf-mark" then begin
 		if List.length segs > 1 then assert false;
 		let pidents = snd (List.hd tags) in
-		let ch = IO.output_channel (open_out_bin (Filename.chop_extension file ^ ".mark")) in
+		let ch = IO.output_channel (open_out_bin (Filename.chop_extension com.file ^ ".mark")) in
 		IO.write_i32 ch (List.length ctx.fun_pargs);
 		List.iter (fun (id,l) ->
 			IO.write_i32 ch id;

+ 13 - 12
genswf9.ml

@@ -20,6 +20,7 @@ open Ast
 open Type
 open As3
 open As3hl
+open Common
 
 type read = Read
 type write = Unused__ | Write
@@ -74,7 +75,7 @@ type try_infos = {
 
 type context = {
 	(* globals *)
-	debug : bool;
+	com : Common.context;
 	mutable last_line : int;
 	mutable last_file : string;
 	boot : string;
@@ -360,7 +361,7 @@ let define_local ctx ?(init=false) name t el =
 			LScope pos
 		end else
 			let r = alloc_reg ctx (classify ctx t) in
-			if ctx.debug then write ctx (HDebugReg (name, r.rid, ctx.last_line));
+			if ctx.com.debug then write ctx (HDebugReg (name, r.rid, ctx.last_line));
 			r.rinit <- init;
 			LReg r
 	) in
@@ -498,7 +499,7 @@ let begin_fun ctx args tret el stat p =
 	ctx.in_static <- stat;
 	ctx.last_line <- -1;
 	ctx.last_file <- "";
-	if ctx.debug then debug ctx p;	
+	if ctx.com.debug then debug ctx p;	
 	let rec find_this e =
 		match e.eexpr with
 		| TFunction _ -> ()
@@ -1286,7 +1287,7 @@ and gen_binop ctx retval op e1 e2 t =
 
 and gen_expr ctx retval e =
 	let old = ctx.infos.istack in
-	if ctx.debug then debug ctx e.epos;
+	if ctx.com.debug then debug ctx e.epos;
 	gen_expr_content ctx retval e;
 	if old <> ctx.infos.istack then begin
 		if old + 1 <> ctx.infos.istack then stack_error e.epos;
@@ -1667,7 +1668,7 @@ let generate_type ctx t =
 	| TTypeDecl _ ->
 		None
 
-let generate_resources ctx hres =
+let generate_resources ctx =
 	write ctx HGetGlobalScope;
 	write ctx (HGetProp (type_path ctx ([],ctx.boot)));
 	let id = type_path ctx (["flash";"utils"],"Dictionary") in
@@ -1680,11 +1681,11 @@ let generate_resources ctx hres =
 		write ctx (HString name);
 		write ctx (HString data);
 		setvar ctx VArray false;
-	) hres;
+	) ctx.com.resources;
 	write ctx (HReg r.rid);
 	write ctx (HInitProp (ident "__res"))
 
-let generate_inits ctx types hres =
+let generate_inits ctx types =
 	let f = begin_fun ctx [] t_void [ethis] false null_pos in
 	let slot = ref 0 in
 	let classes = List.fold_left (fun acc (t,hc) ->
@@ -1736,7 +1737,7 @@ let generate_inits ctx types hres =
 	write ctx (HInitProp (ident "init"));
 
 	(* generate resources *)
-	generate_resources ctx hres;
+	generate_resources ctx;
 
 	write ctx HRetVoid;
 	{
@@ -1744,8 +1745,9 @@ let generate_inits ctx types hres =
 		hls_fields = Array.of_list (List.rev classes);
 	}
 
-let generate types hres =
+let generate com =
 	let ctx = {
+		com = com;
 		boot = "Boot_" ^ Printf.sprintf "%X" (Random.int 0xFFFFFF);
 		code = DynArray.create();
 		locals = PMap.empty;
@@ -1756,14 +1758,13 @@ let generate types hres =
 		curblock = [];
 		block_vars = [];
 		in_static = false;
-		debug = Plugin.defined "debug";
 		last_line = -1;
 		last_file = "";
 		try_scope_reg = None;
 		for_call = false;
 	} in
-	let classes = List.map (fun t -> (t,generate_type ctx t)) types in
-	let init = generate_inits ctx classes hres in
+	let classes = List.map (fun t -> (t,generate_type ctx t)) com.types in
+	let init = generate_inits ctx classes in
 	[init], ctx.boot, (fun () -> empty_method ctx null_pos)
 
 ;;

+ 6 - 5
genxml.ml

@@ -18,6 +18,7 @@
  *)
 open Ast
 open Type
+open Common
 
 type xml =
 	| Node of string * (string * string) list * xml list
@@ -171,12 +172,12 @@ let rec write_xml ch tabs x =
 	| CData s ->
 		IO.printf ch "<![CDATA[%s]]>" s
 
-let generate file ctx types =
-	let t = Plugin.timer "construct xml" in
-	let x = node "haxe" [] (List.map (gen_type_decl ctx) types) in
+let generate com ctx =
+	let t = Common.timer "construct xml" in
+	let x = node "haxe" [] (List.map (gen_type_decl ctx) com.types) in
 	t();
-	let t = Plugin.timer "write xml" in
-	let ch = IO.output_channel (open_out_bin file) in
+	let t = Common.timer "write xml" in
+	let ch = IO.output_channel (open_out_bin com.file) in
 	write_xml ch "" x;
 	IO.close_out ch;
 	t()

+ 3 - 3
haxe.vcproj

@@ -67,6 +67,9 @@
 		<File
 			RelativePath=".\ast.ml">
 		</File>
+		<File
+			RelativePath=".\common.ml">
+		</File>
 		<File
 			RelativePath=".\genas3.ml">
 		</File>
@@ -94,9 +97,6 @@
 		<File
 			RelativePath=".\parser.ml">
 		</File>
-		<File
-			RelativePath=".\plugin.ml">
-		</File>
 		<File
 			RelativePath=".\transform.ml">
 		</File>

+ 1 - 1
lexer.mll

@@ -56,7 +56,7 @@ let keywords =
 		Break;Return;Continue;Extends;Implements;Import;
 		Switch;Case;Default;Public;Private;Try;Untyped;
 		Catch;New;This;Throw;Extern;Enum;In;Interface;
-		Cast;Override;F9Dynamic;Typedef;Package;Callback;Inline];
+		Cast;Override;Dynamic;Typedef;Package;Callback;Inline];
 	h
 
 let init file =

+ 129 - 163
main.ml

@@ -18,26 +18,16 @@
  *)
 open Printf
 open Genswf
-
-type target =
-	| No
-	| Js of string
-	| Swf of string
-	| Neko of string
-	| As3 of string
+open Common
 
 let prompt = ref false
-let alt_format = ref false
 let has_error = ref false
-let auto_xml = ref false
 let display = ref false
+let measure_times = ref false
 
 let executable_path() =
 	Extc.executable_path()
 
-let get_full_path file =
-	Extc.get_full_path file
-
 let normalize_path p =
 	let l = String.length p in
 	if l = 0 then
@@ -50,12 +40,7 @@ let warn msg p =
 	if p = Ast.null_pos then
 		prerr_endline msg
 	else begin
-		let error_printer file line =
-			if !alt_format then
-				sprintf "%s(%d):" file line
-			else
-				sprintf "%s:%d:" file line
-		in
+		let error_printer file line = sprintf "%s:%d:" file line in
 		let epos = Lexer.get_error_pos error_printer p in
 		let msg = String.concat ("\n" ^ epos ^ " : ") (ExtString.String.nsplit msg "\n") in
 		prerr_endline (sprintf "%s : %s" epos msg)
@@ -124,10 +109,19 @@ let make_path f =
 	in
 	loop cl
 
-let read_type_path p cp =
+let read_type_path com p =
 	let classes = ref [] in
 	let packages = ref [] in
-	let p = (match p with "flash" :: l when Plugin.defined "flash9" -> "flash9" :: l | _ -> p) in
+	let p = (match p with 
+		| x :: l ->
+			(try
+				match PMap.find x com.package_rules with
+				| Directory d -> d :: l
+				| _ -> p
+			with
+				Not_found -> p)
+		| _ -> p
+	) in
 	List.iter (fun path ->
 		let dir = path ^ String.concat "/" p in
 		let r = (try Sys.readdir dir with _ -> [||]) in
@@ -139,7 +133,7 @@ let read_type_path p cp =
 				if String.length c < 2 || String.sub c (String.length c - 2) 2 <> "__" then classes := c :: !classes;
 			end;
 		) r;
-	) cp;
+	) com.class_path;
 	List.sort compare (!packages), List.sort compare (!classes)
 
 let delete_file f = try Sys.remove f with _ -> ()
@@ -168,9 +162,6 @@ let parse_hxml file =
 			[l]
 	) lines)
 
-
-let base_defines = !Plugin.defines
-
 exception Hxml_found
 
 let rec process_params acc = function
@@ -183,29 +174,23 @@ let rec process_params acc = function
 		process_params (x :: acc) l
 
 and init params =
-try
-	let version = 119 in
+	let version = 200 in
 	let version_str = Printf.sprintf "%d.%.2d" (version / 100) (version mod 100) in
 	let usage = "Haxe Compiler " ^ version_str ^ " - (c)2005-2008 Motion-Twin\n Usage : haxe.exe [options] <class names...>\n Options :" in
 	let classes = ref [([],"Std")] in
-	let target = ref No in
+	let com = Common.create() in
+try
 	let xml_out = ref None in
-	let main_class = ref None in
-	let swf_infos = {
-		swf_version = 8;
-		swf_header = None;
-		swf_lib = None;
-	} in
-	let hres = Hashtbl.create 0 in
+	let swf_header = ref None in
+	let swf_lib = ref None in	
 	let cmds = ref [] in
 	let excludes = ref [] in
 	let libs = ref [] in
-	let gen_hx = ref false in
+	let gen_as3 = ref false in
 	let no_output = ref false in
-	Plugin.defines := base_defines;
-	Plugin.define ("haxe_" ^ string_of_int version);
-	Typer.check_override := false;
-	Typer.forbidden_packages := ["js"; "neko"; "flash"];
+	let did_something = ref false in
+	let root_packages = ["neko"; "flash"; "flash9"; "js"; "php"] in
+	Common.define com ("haxe_" ^ string_of_int version);
 	Parser.display_error := parse_error;
 	Parser.use_doc := false;
 	(try
@@ -219,45 +204,45 @@ try
 			| l ->
 				l
 		in
-		Plugin.class_path := List.map normalize_path (loop (ExtString.String.nsplit p ":"))
+		com.class_path <- List.map normalize_path (loop (ExtString.String.nsplit p ":"))
 	with
 		Not_found ->
 			if Sys.os_type = "Unix" then
-				Plugin.class_path := ["/usr/lib/haxe/std/";"/usr/local/lib/haxe/std/";"";"/"]
+				com.class_path <- ["/usr/lib/haxe/std/";"/usr/local/lib/haxe/std/";"";"/"]
 			else
 				let base_path = normalize_path (try executable_path() with _ -> "./") in
-				Plugin.class_path := [base_path ^ "std/";"";"/"]);
-	let check_targets() =
-		if !target <> No then failwith "Multiple targets";
+				com.class_path <- [base_path ^ "std/";"";"/"]);
+	let set_platform pf name file = 
+		if com.platform <> Cross then failwith "Multiple targets";
+		com.platform <- pf;
+		com.file <- file;
+		let forbid acc p = if p = name then acc else PMap.add p Forbidden acc in
+		com.package_rules <- List.fold_left forbid com.package_rules root_packages;
+		Common.define com name; (* define platform name *)
 	in
-	let define f = Arg.Unit (fun () -> Plugin.define f) in
+	let define f = Arg.Unit (fun () -> Common.define com f) in
 	let args_spec = [
 		("-cp",Arg.String (fun path ->
-			Plugin.class_path := normalize_path path :: !Plugin.class_path
+			com.class_path <- normalize_path path :: com.class_path
 		),"<path> : add a directory to find source files");
-		("-js",Arg.String (fun file ->
-			check_targets();
-			Typer.forbidden_packages := ["neko"; "flash"];
-			target := Js file
-		),"<file> : compile code to JavaScript file");
+		("-js",Arg.String (set_platform Js "js"),"<file> : compile code to JavaScript file");
 		("-as3",Arg.String (fun dir ->
-			check_targets();
-			swf_infos.swf_version <- 9;
-			Plugin.define "as3gen";
-			Typer.forbidden_packages := ["js"; "neko"];
-			target := As3 dir;
+			set_platform Flash "flash" dir;
+			com.flash_version <- 9;
+			gen_as3 := true;
+			Common.define com "as3gen";
 		),"<directory> : generate AS3 code into target directory");
-		("-swf",Arg.String (fun file ->
-			check_targets();
-			Typer.forbidden_packages := ["js"; "neko"];
-			target := Swf file
-		),"<file> : compile code to Flash SWF file");
-		("-swf-version",Arg.Int (fun v ->
-			swf_infos.swf_version <- v;
+		("-swf",Arg.String (set_platform Flash "flash"),"<file> : compile code to Flash SWF file");
+		("-swf9",Arg.String (fun file ->
+			set_platform Flash "flash" file;
+			com.flash_version <- 9;
+		),"<file> : compile code to Flash9 SWF file");
+		("-swf-version",Arg.Int (fun v ->			
+			com.flash_version <- v;
 		),"<version> : change the SWF version (6,7,8,9)");
 		("-swf-header",Arg.String (fun h ->
 			try
-				swf_infos.swf_header <- Some (match ExtString.String.nsplit h ":" with
+				swf_header := Some (match ExtString.String.nsplit h ":" with
 				| [width; height; fps] ->
 					(int_of_string width,int_of_string height,float_of_string fps,0xFFFFFF)
 				| [width; height; fps; color] ->
@@ -267,22 +252,16 @@ try
 				_ -> raise (Arg.Bad "Invalid SWF header format")
 		),"<header> : define SWF header (width:height:fps:color)");
 		("-swf-lib",Arg.String (fun file ->
-			if swf_infos.swf_lib <> None then raise (Arg.Bad "Only one SWF Library is allowed");
-			swf_infos.swf_lib <- Some file
+			if !swf_lib <> None then raise (Arg.Bad "Only one SWF Library is allowed");
+			swf_lib := Some file
 		),"<file> : add the SWF library to the compiled SWF");
-		("-neko",Arg.String (fun file ->
-			check_targets();
-			Typer.forbidden_packages := ["js"; "flash"];
-			target := Neko file
-		),"<file> : compile code to Neko Binary");
+		("-neko",Arg.String (set_platform Neko "neko"),"<file> : compile code to Neko Binary");
 		("-x", Arg.String (fun file ->
-			check_targets();
-			Typer.forbidden_packages := ["js"; "flash"];
 			let neko_file = file ^ ".n" in
-			target := Neko neko_file;
-			if !main_class = None then begin
+			set_platform Neko "neko" neko_file;
+			if com.main_class = None then begin
 				let cpath = make_path file in
-				main_class := Some cpath;
+				com.main_class <- Some cpath;
 				classes := cpath :: !classes
 			end;
 			cmds := ("neko " ^ neko_file) :: !cmds;
@@ -292,31 +271,26 @@ try
 			xml_out := Some file
 		),"<file> : generate XML types description");
 		("-main",Arg.String (fun cl ->
-			if !main_class <> None then raise (Arg.Bad "Multiple -main");
+			if com.main_class <> None then raise (Arg.Bad "Multiple -main");
 			let cpath = make_path cl in
-			main_class := Some cpath;
+			com.main_class <- Some cpath;
 			classes := cpath :: !classes
 		),"<class> : select startup class");
 		("-lib",Arg.String (fun l -> libs := l :: !libs),"<library[:version]> : use an haxelib library");
-		("-D",Arg.String (fun def ->
-			Plugin.define def;
-		),"<var> : define a conditional compilation flag");
+		("-D",Arg.String (Common.define com),"<var> : define a conditional compilation flag");
 		("-resource",Arg.String (fun res ->
-			match ExtString.String.nsplit res "@" with
-			| [file; name] ->
-				let file = (try Plugin.find_file file with Not_found -> file) in
-				let data = Std.input_file ~bin:true file in
-				if Hashtbl.mem hres name then failwith ("Duplicate resource name " ^ name);
-				Hashtbl.add hres name data
-			| [file] ->
-				let file = (try Plugin.find_file file with Not_found -> file) in
-				let data = Std.input_file ~bin:true file in
-				Hashtbl.replace hres file data
-			| _ ->
-				raise (Arg.Bad "Invalid Resource format : should be file@name")
-		),"<file@name> : add a named resource file");
+			let file, name = (match ExtString.String.nsplit res "@" with
+				| [file; name] -> file, name
+				| [file] -> file, file
+				| _ -> raise (Arg.Bad "Invalid Resource format : should be file@name")
+			) in
+			let file = (try Common.find_file com file with Not_found -> file) in
+			let data = Std.input_file ~bin:true file in
+			if Hashtbl.mem com.resources name then failwith ("Duplicate resource name " ^ name);
+			Hashtbl.add com.resources name data
+		),"<file>[@name] : add a named resource file");
 		("-exclude",Arg.String (fun file ->
-			let file = (try Plugin.find_file file with Not_found -> file) in
+			let file = (try Common.find_file com file with Not_found -> file) in
 			let ch = open_in file in
 			let lines = Std.input_list ch in
 			close_in ch;
@@ -328,40 +302,36 @@ try
 				| x :: l -> (List.rev l,x)
 			) lines) @ !excludes;
 		),"<filename> : don't generate code for classes listed in this file");
-		("-v",Arg.Unit (fun () -> Plugin.verbose := true),": turn on verbose mode");
+		("-v",Arg.Unit (fun () -> com.verbose <- true),": turn on verbose mode");
 		("-debug", define "debug", ": add debug informations to the compiled code");
 		("-prompt", Arg.Unit (fun() -> prompt := true),": prompt on error");
 		("-cmd", Arg.String (fun cmd ->
 			cmds := cmd :: !cmds
 		),": run the specified command after successful compilation");
 		("--flash-strict", define "flash_strict", ": more type strict flash API");
-		("--override", Arg.Unit (fun() ->
-			Typer.check_override := true
-		),": ensure that overriden methods are declared with 'override'");
 		("--no-traces", define "no_traces", ": don't compile trace calls in the program");
 		("--flash-use-stage", define "flash_use_stage", ": place objects found on the stage of the SWF lib");
 		("--neko-source", define "neko_source", ": keep generated neko source");
 		("--gen-hx-classes", Arg.String (fun file ->
-			gen_hx := true;
-			Genas3.genhx file
+			com.file <- file;
+			Genas3.genhx com;
+			did_something := true;
 		),"<file> : generate hx headers from SWF9 file");
 		("--next", Arg.Unit (fun() -> assert false), ": separate several haxe compilations");
-		("--altfmt", Arg.Unit (fun() -> alt_format := true),": use alternative error output format");
-		("--auto-xml", Arg.Unit (fun() -> auto_xml := true),": automatically create an XML for each target");
 		("--display", Arg.String (fun file_pos ->
 			let file, pos = try ExtString.String.split file_pos "@" with _ -> failwith ("Invalid format : " ^ file_pos) in
 			let pos = try int_of_string pos with _ -> failwith ("Invalid format : "  ^ pos) in
 			display := true;
 			no_output := true;
 			Parser.resume_display := {
-				Ast.pfile = (!Plugin.get_full_path) file;
+				Ast.pfile = Common.get_full_path file;
 				Ast.pmin = pos;
 				Ast.pmax = pos;
 			};
 		),": display code tips");
 		("--no-output", Arg.Unit (fun() -> no_output := true),": compiles but does not generate any file");
-		("--times", Arg.Unit (fun() -> Plugin.times := true),": mesure compilation times");
-		("--no-inline", Arg.Unit (fun() -> Plugin.define "no_inline"),": disable inlining");
+		("--times", Arg.Unit (fun() -> measure_times := true),": mesure compilation times");
+		("--no-inline", define "no_inline", ": disable inlining");
 	] in
 	let current = ref 0 in
 	let args = Array.of_list ("" :: params) in
@@ -371,7 +341,7 @@ try
 			let hxml_args = parse_hxml cl in
 			let p1 = Array.to_list (Array.sub args 1 (!current - 1)) in
 			let p2 = Array.to_list (Array.sub args (!current + 1) (Array.length args - !current - 1)) in
-			if !Plugin.verbose then print_endline ("Processing HXML : " ^ cl);
+			if com.verbose then print_endline ("Processing HXML : " ^ cl);
 			process_params [] (p1 @ hxml_args @ p2);
 			raise Hxml_found
 		| _ ->
@@ -396,67 +366,65 @@ try
 				l :: acc
 		) [] lines in
 		if ret <> Unix.WEXITED 0 then failwith (String.concat "\n" lines);
-		Plugin.class_path := lines @ !Plugin.class_path;
-	);
-	(match !target with
-	| No ->
-		()
-	| Swf file | As3 file ->
-		(* check file extension. In case of wrong commandline, we don't want
-		   to accidentaly delete a source file. *)
-		if not !no_output && file_extension file = "swf" then delete_file file;
-		Plugin.define "flash";
-		Plugin.define ("flash"  ^ string_of_int swf_infos.swf_version);
-	| Neko file ->
-		if not !no_output && file_extension file = "n" then delete_file file;
-		Plugin.define "neko";
-	| Js file ->
-		if not !no_output && file_extension file = "js" then delete_file file;
-		Plugin.define "js";
+		com.class_path <- lines @ com.class_path;
 	);
+	let ext = (match com.platform with
+		| Cross ->
+			(* no platform selected *)
+			no_output := true; ""
+		| Flash | Flash9 ->			
+			Common.define com ("flash" ^ string_of_int com.flash_version);
+			if com.flash_version >= 9 then begin
+				com.package_rules <- PMap.add "flash" (Directory "flash9") com.package_rules;
+				com.platform <- Flash9;
+			end;
+			"swf"
+		| Neko -> "n"
+		| Js -> "js"
+		| Php -> "php"
+	) in
+	(* check file extension. In case of wrong commandline, we don't want
+		to accidentaly delete a source file. *)
+	if not !no_output && file_extension com.file = ext then delete_file com.file;
 	if !classes = [([],"Std")] then begin
-		if !cmds = [] && not !gen_hx then Arg.usage args_spec usage;
+		if !cmds = [] && not !did_something then Arg.usage args_spec usage;
 	end else begin
-		if !Plugin.verbose then print_endline ("Classpath : " ^ (String.concat ";" !Plugin.class_path));
-		let t = Plugin.timer "typing" in
-		let ctx = Typer.context type_error warn in
+		if com.verbose then print_endline ("Classpath : " ^ (String.concat ";" com.class_path));
+		let t = Common.timer "typing" in
+		let ctx = Typer.context com type_error warn in
 		List.iter (fun cpath -> ignore(Typer.load ctx cpath Ast.null_pos)) (List.rev !classes);
 		Typer.finalize ctx;
 		t();
 		if !has_error then do_exit();
-		if !display then begin
-			xml_out := None;
-			auto_xml := false;
-		end;
-		if !no_output then target := No;
-		let do_auto_xml file = if !auto_xml then xml_out := Some (file ^ ".xml") in
-		let types = Typer.types ctx (!main_class) (!excludes) in
-		(match !target with
-		| No -> ()
-		| Swf file ->
-			do_auto_xml file;
-			if !Plugin.verbose then print_endline ("Generating swf : " ^ file);
-			Genswf.generate file swf_infos types hres
-		| Neko file ->
-			do_auto_xml file;
-			if !Plugin.verbose then print_endline ("Generating neko : " ^ file);
-			Genneko.generate file types hres !libs
-		| Js file ->
-			do_auto_xml file;
-			if !Plugin.verbose then print_endline ("Generating js : " ^ file);
-			Genjs.generate file types hres
-		| As3 dir ->
-			if !Plugin.verbose then print_endline ("Generating AS3 in : " ^ dir);
-			Genas3.generate dir types
+		if !display then xml_out := None;		
+		if !no_output then com.platform <- Cross;		
+		com.types <- Typer.types ctx com.main_class (!excludes);
+		(match com.platform with
+		| Cross ->
+			()
+		| Flash | Flash9 when !gen_as3 ->
+			if com.verbose then print_endline ("Generating AS3 in : " ^ com.file);
+			Genas3.generate com;
+		| Flash | Flash9 ->
+			if com.verbose then print_endline ("Generating swf : " ^ com.file);
+			Genswf.generate com !swf_header !swf_lib;
+		| Neko ->			
+			if com.verbose then print_endline ("Generating neko : " ^ com.file);
+			Genneko.generate com !libs;
+		| Js ->
+			if com.verbose then print_endline ("Generating js : " ^ com.file);
+			Genjs.generate com
+		| Php ->
+			assert false
 		);
 		(match !xml_out with
 		| None -> ()
 		| Some file ->
-			if !Plugin.verbose then print_endline ("Generating xml : " ^ file);
-			Genxml.generate file ctx types);
+			if com.verbose then print_endline ("Generating xml : " ^ com.file);
+			Genxml.generate com ctx);
 	end;
 	if not !no_output then List.iter (fun cmd ->
-		let t = Plugin.timer "command" in
+		let t = Common.timer "command" in
 		let len = String.length cmd in
 		if len > 3 && String.sub cmd 0 3 = "cd " then
 			Sys.chdir (String.sub cmd 3 (len - 3))
@@ -487,7 +455,7 @@ with
 			prerr_endline "</type>");
 		exit 0;
 	| Parser.TypePath p ->
-		let packs, classes = read_type_path p (!Plugin.class_path) in
+		let packs, classes = read_type_path com p in
 		if packs = [] && classes = [] then report ("No classes found in " ^ String.concat "." p) Ast.null_pos;
 		report_list (List.map (fun f -> f,"","") (packs @ classes));
 		exit 0;
@@ -495,17 +463,15 @@ with
 		report (Printexc.to_string e) Ast.null_pos
 
 ;;
-let all = Plugin.timer "other" in
-Plugin.times := false;
-Plugin.get_full_path := get_full_path;
+let all = Common.timer "other" in
 process_params [] (List.tl (Array.to_list Sys.argv));
 all();
-if !Plugin.times then begin
+if !measure_times then begin
 	let tot = ref 0. in
-	Hashtbl.iter (fun _ t -> tot := !tot +. t.Plugin.total) Plugin.htimers;
+	Hashtbl.iter (fun _ t -> tot := !tot +. t.total) Common.htimers;
 	Printf.eprintf "Total time : %.3fs\n" !tot;
 	Printf.eprintf "------------------------------------\n";
 	Hashtbl.iter (fun _ t ->
-		Printf.eprintf "  %s : %.3fs, %.0f%%\n" t.Plugin.name t.Plugin.total (t.Plugin.total *. 100. /. !tot);
-	) Plugin.htimers;
+		Printf.eprintf "  %s : %.3fs, %.0f%%\n" t.name t.total (t.total *. 100. /. !tot);
+	) Common.htimers;
 end;

+ 6 - 5
parser.ml

@@ -58,7 +58,7 @@ let display e = raise (Display e)
 
 let is_resuming p =
 	let p2 = !resume_display in
-	p.pmax = p2.pmin && (!Plugin.get_full_path) p.pfile = p2.pfile
+	p.pmax = p2.pmin && Common.get_full_path p.pfile = p2.pfile
 
 let priority = function
 	| OpAssign | OpAssignOp _ -> -4
@@ -129,6 +129,7 @@ let any_ident = parser
 
 let property_ident = parser
 	| [< i = any_ident >] -> i
+	| [< '(Kwd Dynamic,_) >] -> "dynamic"
 	| [< '(Kwd Default,_) >] -> "default"
 
 let log m s =
@@ -383,8 +384,8 @@ and parse_cf_rights allow_static l = parser
 	| [< '(Kwd Static,_) when allow_static; l = parse_cf_rights false (AStatic :: l) >] -> l
 	| [< '(Kwd Public,_) when not(List.mem APublic l || List.mem APrivate l); l = parse_cf_rights allow_static (APublic :: l) >] -> l
 	| [< '(Kwd Private,_) when not(List.mem APublic l || List.mem APrivate l); l = parse_cf_rights allow_static (APrivate :: l) >] -> l
-	| [< '(Kwd Override,_) when allow_static; l = parse_cf_rights false (AOverride :: l) >] -> l
-	| [< '(Kwd F9Dynamic,_) when not (List.mem AF9Dynamic l); l = parse_cf_rights false (AF9Dynamic :: l) >] -> l
+	| [< '(Kwd Override,_) when not (List.mem AOverride l); l = parse_cf_rights false (AOverride :: l) >] -> l
+	| [< '(Kwd Dynamic,_) when not (List.mem ADynamic l); l = parse_cf_rights allow_static (ADynamic :: l) >] -> l
 	| [< '(Kwd Inline,_); l = parse_cf_rights allow_static (AInline :: l) >] -> l
 	| [< >] -> l
 
@@ -633,7 +634,7 @@ and toplevel_expr s =
 	with
 		Display e -> e
 
-let parse code file =
+let parse ctx code file =
 	let old = Lexer.save() in
 	let old_cache = !cache in
 	let mstack = ref [] in
@@ -688,7 +689,7 @@ let parse code file =
 		match Lexer.token code with
 		| (Const (Ident s),p) | (Const (Type s),p) ->
 			if s = "error" then error Unimplemented p;
-			let ok = Plugin.defined s in
+			let ok = Common.defined ctx s in
 			(match Lexer.token code with
 			| (Binop OpBoolOr,_) when allow_expr ->
 				let ok2 , tk = eval_macro allow_expr in

+ 1 - 11
std/all.hxml

@@ -1,24 +1,19 @@
 
 -neko all.n
 -xml neko.xml
---override
 haxe.ImportAll
 
 --next
 
 -swf all.swf
 -xml flash.xml
--D flash9doc
 -D flash_lite
--D flash_v9
---override
 haxe.ImportAll
 
 --next
 
 -js all.js
 -xml js.xml
---override
 haxe.ImportAll
 
 --next
@@ -26,17 +21,12 @@ haxe.ImportAll
 -swf all_strict.swf
 -D flash_strict
 -D flash_lite
--D flash9doc
 -xml flash_strict.xml
---override
 haxe.ImportAll
 
 
 --next
 
--swf all9.swf
--D flash_strict
+-swf9 all9.swf
 -xml flash9.xml
--swf-version 9
---override
 haxe.ImportAll

+ 11 - 11
std/flash/Button.hx

@@ -32,17 +32,17 @@ implements Dynamic
 	var _ymouse : Float;
 	var _yscale : Float;
 
-	function onDragOut() : Void;
-	function onDragOver() : Void;
-	function onKeyDown() : Void;
-	function onKeyUp() : Void;
-	function onKillFocus(newFocus : Dynamic) : Void;
-	function onPress() : Void;
-	function onRelease() : Void;
-	function onReleaseOutside() : Void;
-	function onRollOut() : Void;
-	function onRollOver() : Void;
-	function onSetFocus(oldFocus : Dynamic) : Void;
+	dynamic function onDragOut() : Void;
+	dynamic function onDragOver() : Void;
+	dynamic function onKeyDown() : Void;
+	dynamic function onKeyUp() : Void;
+	dynamic function onKillFocus(newFocus : Dynamic) : Void;
+	dynamic function onPress() : Void;
+	dynamic function onRelease() : Void;
+	dynamic function onReleaseOutside() : Void;
+	dynamic function onRollOut() : Void;
+	dynamic function onRollOver() : Void;
+	dynamic function onSetFocus(oldFocus : Dynamic) : Void;
 
 	function getDepth() : Int;
 

+ 2 - 2
std/flash/Camera.hx

@@ -32,8 +32,8 @@ extern class Camera {
 	function setKeyFrameInterval(keyFrameInterval:Int):Void;
 	function setLoopback(compress:Bool):Void;
 
-	function onActivity( active:Bool ):Void;
-	function onStatus( infoObject:Dynamic ):Void;
+	dynamic function onActivity( active:Bool ):Void;
+	dynamic function onStatus( infoObject:Dynamic ):Void;
 
 	private static function __init__() : Void untyped {
 		flash.Camera = _global["Camera"];

+ 6 - 6
std/flash/ContextMenu.hx

@@ -1,13 +1,13 @@
 package flash;
 
 extern class ContextMenu {
-	public function new( ?callb:Dynamic->ContextMenu->Void ) : Void;
-	public function hideBuiltInItems():Void;
-	public function copy() : ContextMenu;
+	function new( ?callb:Dynamic->ContextMenu->Void ) : Void;
+	function hideBuiltInItems():Void;
+	function copy() : ContextMenu;
 
-	public var customItems:Array<ContextMenuItem>;
-	public var builtInItems:Dynamic;
-	public function onSelect( v : Dynamic, c : ContextMenu ) : Void;
+	var customItems:Array<ContextMenuItem>;
+	var builtInItems:Dynamic;
+	dynamic function onSelect( v : Dynamic, c : ContextMenu ) : Void;
 
 	private static function __init__() : Void untyped {
 		flash.ContextMenu = _global["ContextMenu"];

+ 7 - 7
std/flash/ContextMenuItem.hx

@@ -1,15 +1,15 @@
 package flash;
 
 extern class ContextMenuItem {
-	public function new(caption:String, callb:Dynamic->ContextMenuItem->Void, ?separatorBefore:Bool, ?enabled:Bool, ?visible:Bool) : Void;
-	public function copy() : ContextMenuItem;
+	function new(caption:String, callb:Dynamic->ContextMenuItem->Void, ?separatorBefore:Bool, ?enabled:Bool, ?visible:Bool) : Void;
+	function copy() : ContextMenuItem;
 
-	public function onSelect( v : Dynamic, c : ContextMenuItem ) : Void;
+	dynamic function onSelect( v : Dynamic, c : ContextMenuItem ) : Void;
 
-	public var enabled:Bool;
-	public var visible:Bool;
-	public var caption:String;
-	public var separatorBefore:Bool;
+	var enabled:Bool;
+	var visible:Bool;
+	var caption:String;
+	var separatorBefore:Bool;
 
 	private static function __init__() : Void untyped {
 		flash.ContextMenuItem = _global["ContextMenuItem"];

+ 2 - 2
std/flash/Key.hx

@@ -36,8 +36,8 @@ extern class Key
 	static function isDown(code:Int):Bool;
 	static function isToggled(code:Int):Bool;
 
-	static function onKeyDown() : Void;
-	static function onKeyUp() : Void;
+	static dynamic function onKeyDown() : Void;
+	static dynamic function onKeyUp() : Void;
 
 #if flash_strict
 	static function addListener(listener:KeyListener):Void;

+ 3 - 3
std/flash/LoadVars.hx

@@ -18,11 +18,11 @@ extern class LoadVars implements Dynamic<String>
 	function decode(queryString:String):Void;
 	function toString():String;
 
-	function onLoad(success:Bool):Void;
-	function onData(src:String):Void;
+	dynamic function onLoad(success:Bool):Void;
+	dynamic function onData(src:String):Void;
 
 	#if flash8
-	function onHTTPStatus( status : Int ) : Void;
+	dynamic function onHTTPStatus( status : Int ) : Void;
 	#end
 
 	// undocumented var _customHeaders:Array<String>;

+ 3 - 4
std/flash/LocalConnection.hx

@@ -13,10 +13,9 @@ implements Dynamic
 
 	function close():Void;
 	function domain():String;
-	function allowDomain(domain:String):Bool;
-	function allowInsecureDomain(domain:String):Bool;
-
-	function onStatus(infoObject:Dynamic):Void;
+	dynamic function allowDomain(domain:String):Bool;
+	dynamic function allowInsecureDomain(domain:String):Bool;
+	dynamic function onStatus(infoObject:Dynamic):Void;
 
 	private static function __init__() : Void untyped {
 		flash.LocalConnection = _global["LocalConnection"];

+ 2 - 2
std/flash/Microphone.hx

@@ -21,8 +21,8 @@ extern class Microphone
 	function setGain(gain:Float):Void;
 	function setUseEchoSuppression(useEchoSuppression:Bool):Void;
 
-	function onActivity(active:Bool):Void;
-	function onStatus(infoObject:Dynamic):Void;
+	dynamic function onActivity(active:Bool):Void;
+	dynamic function onStatus(infoObject:Dynamic):Void;
 
 	private static function __init__() : Void untyped {
 		flash.Microphone = _global["Microphone"];

+ 3 - 3
std/flash/Mouse.hx

@@ -13,9 +13,9 @@ extern class Mouse
 {
 	static function show():Int;
 	static function hide():Int;
-	static function onMouseDown() : Void;
-	static function onMouseMove() : Void;
-	static function onMouseUp() : Void;
+	static dynamic function onMouseDown() : Void;
+	static dynamic function onMouseMove() : Void;
+	static dynamic function onMouseUp() : Void;
 
 #if flash_strict
 	static function addListener(listener:MouseListener):Void;

+ 18 - 18
std/flash/MovieClip.hx

@@ -126,24 +126,24 @@ implements Dynamic
 	function getTextSnapshot() : TextSnapshot;
 	function getSWFVersion() : Int;
 
-	function onData() : Void;
-	function onDragOut() : Void;
-	function onDragOver() : Void;
-	function onEnterFrame() : Void;
-	function onKeyDown() : Void;
-	function onKeyUp() : Void;
-	function onKillFocus(newFocus : Dynamic) : Void;
-	function onLoad() : Void;
-	function onMouseDown() : Void;
-	function onMouseMove() : Void;
-	function onMouseUp() : Void;
-	function onPress() : Void;
-	function onRelease() : Void;
-	function onReleaseOutside() : Void;
-	function onRollOut() : Void;
-	function onRollOver() : Void;
-	function onSetFocus(oldFocus : Dynamic) : Void;
-	function onUnload() : Void;
+	dynamic function onData() : Void;
+	dynamic function onDragOut() : Void;
+	dynamic function onDragOver() : Void;
+	dynamic function onEnterFrame() : Void;
+	dynamic function onKeyDown() : Void;
+	dynamic function onKeyUp() : Void;
+	dynamic function onKillFocus(newFocus : Dynamic) : Void;
+	dynamic function onLoad() : Void;
+	dynamic function onMouseDown() : Void;
+	dynamic function onMouseMove() : Void;
+	dynamic function onMouseUp() : Void;
+	dynamic function onPress() : Void;
+	dynamic function onRelease() : Void;
+	dynamic function onReleaseOutside() : Void;
+	dynamic function onRollOut() : Void;
+	dynamic function onRollOver() : Void;
+	dynamic function onSetFocus(oldFocus : Dynamic) : Void;
+	dynamic function onUnload() : Void;
 
 #if flash8
 	var filters : Array<Dynamic>; // does not use variance here.

+ 5 - 5
std/flash/MovieClipLoader.hx

@@ -22,11 +22,11 @@ extern class MovieClipLoader
 	function loadClip(url:String, target:MovieClip):Bool;
 	function unloadClip(target:MovieClip):Bool;
 
-	function onLoadInit(target:MovieClip) : Void;
-	function onLoadStart(target:MovieClip) : Void;
-	function onLoadProgress(target:MovieClip, loaded : Int, total : Int) : Void;
-	function onLoadComplete(target:MovieClip) : Void;
-	function onLoadError(target:MovieClip, error:String) : Void;
+	dynamic function onLoadInit(target:MovieClip) : Void;
+	dynamic function onLoadStart(target:MovieClip) : Void;
+	dynamic function onLoadProgress(target:MovieClip, loaded : Int, total : Int) : Void;
+	dynamic function onLoadComplete(target:MovieClip) : Void;
+	dynamic function onLoadError(target:MovieClip, error:String) : Void;
 
 #if flash_strict
 	function addListener(listener:MclListener):Bool;

+ 2 - 2
std/flash/NetConnection.hx

@@ -16,8 +16,8 @@ implements Dynamic
 	function close() : Void;
 
 	// events
-	function onStatus(infoObject : Dynamic) : Void;
-	function onResult(infoObject : Dynamic) : Void;
+	dynamic function onStatus(infoObject : Dynamic) : Void;
+	dynamic function onResult(infoObject : Dynamic) : Void;
 
 	private static function __init__() : Void untyped {
 		flash.NetConnection = _global["NetConnection"];

+ 3 - 3
std/flash/NetStream.hx

@@ -15,8 +15,8 @@ extern class NetStream
 #end
 
 	function new( connection : NetConnection ) : Void;
-	function onMetaData( info : Dynamic ) : Void;
-	function onStatus( info : Dynamic ) : Void;
+	dynamic function onMetaData( info : Dynamic ) : Void;
+	dynamic function onStatus( info : Dynamic ) : Void;
 	function publish( name : Dynamic, ?type : String ) : Void;
 	function play( name : String, ?start : Float, ?len : Float, ?reset : Dynamic ) : Void;
 	function receiveAudio( flag : Bool ) : Void;
@@ -30,7 +30,7 @@ extern class NetStream
 	function setBufferTime( bufferTime : Float ) : Void;
 
 #if flash8
-	function onCuePoint( info : Dynamic ) : Void;
+	dynamic function onCuePoint( info : Dynamic ) : Void;
 #end
 
 	private static function __init__() : Void untyped {

+ 2 - 2
std/flash/SharedObject.hx

@@ -19,8 +19,8 @@ extern class SharedObject
 	function getSize():Float;
 	function setFps(updatesPerSecond:Float):Bool;
 
-	function onStatus(infoObject:Dynamic):Void;
-	function onSync(objArray:Array<Dynamic>):Void;
+	dynamic function onStatus(infoObject:Dynamic):Void;
+	dynamic function onSync(objArray:Array<Dynamic>):Void;
 
 	function clear() : Void;
 

+ 3 - 3
std/flash/Sound.hx

@@ -11,9 +11,9 @@ extern class Sound
 
 	function new( ?target:Dynamic ) : Void;
 
-	function onLoad(success:Bool):Void;
-	function onSoundComplete():Void;
-	function onID3():Void;
+	dynamic function onLoad(success:Bool):Void;
+	dynamic function onSoundComplete():Void;
+	dynamic function onID3():Void;
 
 	function getPan():Float;
 	function getTransform():Dynamic;

+ 1 - 1
std/flash/Stage.hx

@@ -18,7 +18,7 @@ extern class Stage
 	**/
 	static var displayState : String;
 	static var fullScreenSourceRect : flash.geom.Rectangle<Int>;
-	static function onFullScreen( full : Bool ) : Void;
+	static dynamic function onFullScreen( full : Bool ) : Void;
 #end
 
 	private static function __init__() : Void untyped {

+ 1 - 1
std/flash/System.hx

@@ -6,7 +6,7 @@ extern class System
 	static var exactSettings:Bool;
 	static function showSettings(?tabID:Float):Void;
 	static function setClipboard(text:String):Void;
-	static function onStatus(infoObject:Dynamic):Void;
+	static dynamic function onStatus(infoObject:Dynamic):Void;
 
 	private static function __init__() : Void untyped {
 		flash.System = _global["System"];

+ 4 - 4
std/flash/TextField.hx

@@ -81,10 +81,10 @@ extern class TextField
 	function removeListener(listener:Dynamic):Bool;
 	static function getFontList():Array<Dynamic>;
 
-	function onChanged(changedField:TextField):Void;
-	function onKillFocus(newFocus:Dynamic):Void;
-	function onScroller(scrolledField:TextField):Void;
-	function onSetFocus(oldFocus:Dynamic):Void;
+	dynamic function onChanged(changedField:TextField):Void;
+	dynamic function onKillFocus(newFocus:Dynamic):Void;
+	dynamic function onScroller(scrolledField:TextField):Void;
+	dynamic function onSetFocus(oldFocus:Dynamic):Void;
 
 	private static function __init__() : Void untyped {
 		flash.TextField = _global["TextField"];

+ 4 - 4
std/flash/XMLSocket.hx

@@ -6,10 +6,10 @@ extern class XMLSocket {
 	function connect( url : String, port : Int ) : Void;
 	function send( data : Dynamic ) : Bool;
 	function close() : Bool;
-	function onData( src : String ) : Void;
-	//function onXML( src : Xml ) : Void;
-	function onConnect( success : Bool ) : Void;
-	function onClose() : Void;
+	dynamic function onData( src : String ) : Void;
+	//dynamic function onXML( src : Xml ) : Void;
+	dynamic function onConnect( success : Bool ) : Void;
+	dynamic function onClose() : Void;
 
 	private static function __init__() : Void untyped {
 		flash.XMLSocket = _global["XMLSocket"];

+ 1 - 1
std/flash/text/StyleSheet.hx

@@ -11,7 +11,7 @@ extern class StyleSheet
 	function parseCSS(cssText:String):Bool;
 	function parse(cssText:String):Bool;
 	function load(url:String):Bool;
-	function onLoad(success:Bool):Void;
+	dynamic function onLoad(success:Bool):Void;
 
 	private static function __init__() : Void untyped {
 		flash.text.StyleSheet = _global["TextField"]["StyleSheet"];

+ 5 - 7
std/haxe/Http.hx

@@ -233,11 +233,9 @@ class Http {
 			err = true;
 			old(e);
 		}
-		output.close = function() {
-			if( !err )
-				me.onData(output.toString());
-		};
 		customRequest(post,output);
+		if( !err )
+			me.onData(output.toString());
 	#end
 	}
 
@@ -571,13 +569,13 @@ class Http {
 
 #end
 
-	public f9dynamic function onData( data : String ) {
+	public dynamic function onData( data : String ) {
 	}
 
-	public f9dynamic function onError( msg : String ) {
+	public dynamic function onError( msg : String ) {
 	}
 
-	public f9dynamic function onStatus( status : Int ) {
+	public dynamic function onStatus( status : Int ) {
 	}
 
 #if flash

+ 0 - 184
std/haxe/ImportAll.hx

@@ -319,190 +319,6 @@ import flash.text.StyleSheet;
 import flash.system.Capabilities;
 import flash.system.Security;
 
-// generated by haxe
-import flash9.Boot;
-import flash9.Lib;
-import flash9.FlashXml__;
-import flash9.accessibility.Accessibility;
-import flash9.accessibility.AccessibilityImplementation;
-import flash9.accessibility.AccessibilityProperties;
-import flash9.display.ActionScriptVersion;
-import flash9.display.AVM1Movie;
-import flash9.display.Bitmap;
-import flash9.display.BitmapData;
-import flash9.display.BitmapDataChannel;
-import flash9.display.BlendMode;
-import flash9.display.CapsStyle;
-import flash9.display.DisplayObject;
-import flash9.display.DisplayObjectContainer;
-import flash9.display.FrameLabel;
-import flash9.display.GradientType;
-import flash9.display.Graphics;
-import flash9.display.IBitmapDrawable;
-import flash9.display.InteractiveObject;
-import flash9.display.InterpolationMethod;
-import flash9.display.JointStyle;
-import flash9.display.LineScaleMode;
-import flash9.display.Loader;
-import flash9.display.LoaderInfo;
-import flash9.display.MorphShape;
-import flash9.display.MovieClip;
-import flash9.display.PixelSnapping;
-import flash9.display.Scene;
-import flash9.display.Shape;
-import flash9.display.SimpleButton;
-import flash9.display.SpreadMethod;
-import flash9.display.Sprite;
-import flash9.display.Stage;
-import flash9.display.StageAlign;
-import flash9.display.StageQuality;
-import flash9.display.StageScaleMode;
-import flash9.display.SWFVersion;
-import flash9.events.ActivityEvent;
-import flash9.events.AsyncErrorEvent;
-import flash9.events.ContextMenuEvent;
-import flash9.events.DataEvent;
-import flash9.events.ErrorEvent;
-import flash9.events.Event;
-import flash9.events.EventDispatcher;
-import flash9.events.EventPhase;
-import flash9.events.FocusEvent;
-import flash9.events.FullScreenEvent;
-import flash9.events.HTTPStatusEvent;
-import flash9.events.IEventDispatcher;
-import flash9.events.IMEEvent;
-import flash9.events.IOErrorEvent;
-import flash9.events.KeyboardEvent;
-import flash9.events.MouseEvent;
-import flash9.events.NetFilterEvent;
-import flash9.events.NetStatusEvent;
-import flash9.events.ProgressEvent;
-import flash9.events.SecurityErrorEvent;
-import flash9.events.StatusEvent;
-import flash9.events.SyncEvent;
-import flash9.events.TextEvent;
-import flash9.events.TimerEvent;
-import flash9.events.WeakFunctionClosure;
-import flash9.events.WeakMethodClosure;
-import flash9.external.ExternalInterface;
-import flash9.filters.BevelFilter;
-import flash9.filters.BitmapFilter;
-import flash9.filters.BitmapFilterQuality;
-import flash9.filters.BitmapFilterType;
-import flash9.filters.BlurFilter;
-import flash9.filters.ColorMatrixFilter;
-import flash9.filters.ConvolutionFilter;
-import flash9.filters.DisplacementMapFilter;
-import flash9.filters.DisplacementMapFilterMode;
-import flash9.filters.DropShadowFilter;
-import flash9.filters.GlowFilter;
-import flash9.filters.GradientBevelFilter;
-import flash9.filters.GradientGlowFilter;
-import flash9.geom.ColorTransform;
-import flash9.geom.Matrix;
-import flash9.geom.Point;
-import flash9.geom.Rectangle;
-import flash9.geom.Transform;
-import flash9.media.Camera;
-import flash9.media.ID3Info;
-import flash9.media.Microphone;
-import flash9.media.Sound;
-import flash9.media.SoundChannel;
-import flash9.media.SoundLoaderContext;
-import flash9.media.SoundMixer;
-import flash9.media.SoundTransform;
-import flash9.media.Video;
-import flash9.net.DynamicPropertyOutput;
-import flash9.net.FileFilter;
-import flash9.net.FileReference;
-import flash9.net.FileReferenceList;
-import flash9.net.IDynamicPropertyOutput;
-import flash9.net.IDynamicPropertyWriter;
-import flash9.net.LocalConnection;
-import flash9.net.NetConnection;
-import flash9.net.NetStream;
-import flash9.net.ObjectEncoding;
-import flash9.net.Responder;
-import flash9.net.SharedObject;
-import flash9.net.SharedObjectFlushStatus;
-import flash9.net.Socket;
-import flash9.net.URLLoader;
-import flash9.net.URLLoaderDataFormat;
-import flash9.net.URLRequest;
-import flash9.net.URLRequestHeader;
-import flash9.net.URLRequestMethod;
-import flash9.net.URLStream;
-import flash9.net.URLVariables;
-import flash9.net.XMLSocket;
-import flash9.printing.PrintJob;
-import flash9.printing.PrintJobOptions;
-import flash9.printing.PrintJobOrientation;
-import flash9.system.ApplicationDomain;
-import flash9.system.Capabilities;
-import flash9.system.FSCommand;
-import flash9.system.IME;
-import flash9.system.IMEConversionMode;
-import flash9.system.LoaderContext;
-import flash9.system.Security;
-import flash9.system.SecurityDomain;
-import flash9.system.SecurityPanel;
-import flash9.system.System;
-import flash9.text.AntiAliasType;
-import flash9.text.CSMSettings;
-import flash9.text.Font;
-import flash9.text.FontStyle;
-import flash9.text.FontType;
-import flash9.text.GridFitType;
-import flash9.text.StaticText;
-import flash9.text.StyleSheet;
-import flash9.text.TextColorType;
-import flash9.text.TextDisplayMode;
-import flash9.text.TextExtent;
-import flash9.text.TextField;
-import flash9.text.TextFieldAutoSize;
-import flash9.text.TextFieldType;
-import flash9.text.TextFormat;
-import flash9.text.TextFormatAlign;
-import flash9.text.TextFormatDisplay;
-import flash9.text.TextLineMetrics;
-import flash9.text.TextRenderer;
-import flash9.text.TextRun;
-import flash9.text.TextSnapshot;
-import flash9.ui.ContextMenu;
-import flash9.ui.ContextMenuBuiltInItems;
-import flash9.ui.ContextMenuItem;
-import flash9.ui.Keyboard;
-import flash9.ui.KeyLocation;
-import flash9.ui.Mouse;
-import flash9.utils.ByteArray;
-import flash9.utils.Dictionary;
-import flash9.utils.Endian;
-import flash9.utils.IDataInput;
-import flash9.utils.IDataOutput;
-import flash9.utils.IExternalizable;
-import flash9.utils.ObjectInput;
-import flash9.utils.ObjectOutput;
-import flash9.utils.Proxy;
-import flash9.utils.SetIntervalTimer;
-import flash9.utils.Timer;
-import flash9.utils.TypedDictionary;
-import flash9.utils.QName;
-import flash9.utils.Namespace;
-import flash9.xml.XML;
-import flash9.xml.XMLList;
-import flash9.xml.XMLDocument;
-import flash9.xml.XMLNode;
-import flash9.xml.XMLNodeType;
-import flash9.xml.XMLParser;
-import flash9.xml.XMLTag;
-import flash9.trace.Trace;
-import flash9.sampler.Api;
-import flash9.sampler.DeleteObjectSample;
-import flash9.sampler.NewObjectSample;
-import flash9.sampler.Sample;
-import flash9.sampler.StackFrame;
-
-
 #end
 
 #if flash8

+ 3 - 3
std/haxe/Log.hx

@@ -26,7 +26,7 @@ package haxe;
 
 class Log {
 
-	public static f9dynamic function trace( v : Dynamic, ?infos : PosInfos ) : Void {
+	public static dynamic function trace( v : Dynamic, ?infos : PosInfos ) : Void {
 		#if flash
 		untyped flash.Boot.__trace(v,infos);
 		#else neko
@@ -37,7 +37,7 @@ class Log {
 		#end
 	}
 
-	public static f9dynamic function clear() : Void {
+	public static dynamic function clear() : Void {
 		#if flash
 		untyped flash.Boot.__clear_trace();
 		#else js
@@ -49,7 +49,7 @@ class Log {
 	}
 
 	#if flash
-	public static f9dynamic function setColor( rgb : Int ) {
+	public static dynamic function setColor( rgb : Int ) {
 		untyped flash.Boot.__set_trace_color(rgb);
 	}
 	#end

+ 1 - 1
std/haxe/Timer.hx

@@ -71,7 +71,7 @@ class Timer {
 		id = null;
 	}
 
-	public f9dynamic function run(){
+	public dynamic function run(){
 	}
 
 	public static function delayed( f : Void -> Void, time : Int ) : Void -> Void {

+ 3 - 3
std/haxe/remoting/AsyncDebugConnection.hx

@@ -58,14 +58,14 @@ class AsyncDebugConnection extends AsyncConnection, implements Dynamic<AsyncDebu
 		return s;
 	}
 
-	public f9dynamic function onErrorDisplay( path : Array<String>, params : Array<Dynamic>, err : Dynamic ) {
+	public dynamic function onErrorDisplay( path : Array<String>, params : Array<Dynamic>, err : Dynamic ) {
 		trace(path.join(".")+"("+params.join(",")+") = ERROR "+Std.string(err));
 	}
 
-	public f9dynamic function onCall( path : Array<String>, params : Array<Dynamic> ) {
+	public dynamic function onCall( path : Array<String>, params : Array<Dynamic> ) {
 	}
 
-	public f9dynamic function onResult( path : Array<String>, params : Array<Dynamic>, result : Dynamic ) {
+	public dynamic function onResult( path : Array<String>, params : Array<Dynamic>, result : Dynamic ) {
 		trace(path.join(".")+"("+params.join(",")+") = "+Std.string(result));
 	}
 

+ 1 - 1
std/haxe/rtti/Type.hx

@@ -56,7 +56,7 @@ typedef Classdef = {> TypeInfos,
 	var interfaces : List<PathParams>;
 	var fields : List<ClassField>;
 	var statics : List<ClassField>;
-	var dynamic : Null<Type>;
+	var tdynamic : Null<Type>;
 }
 
 typedef EnumField = {

+ 3 - 3
std/haxe/rtti/XmlParser.hx

@@ -244,7 +244,7 @@ class XmlParser {
 	function xclass( x : Fast ) : Classdef {
 		var csuper = null;
 		var doc = null;
-		var dynamic = null;
+		var tdynamic = null;
 		var interfaces = new List();
 		var fields = new List();
 		var statics = new List();
@@ -253,7 +253,7 @@ class XmlParser {
 			case "haxe_doc": doc = c.innerData;
 			case "extends": csuper = xpath(c);
 			case "implements": interfaces.add(xpath(c));
-			case "haxe_dynamic": dynamic = xtype(new Fast(c.x.firstElement()));
+			case "haxe_dynamic": tdynamic = xtype(new Fast(c.x.firstElement()));
 			default:
 				if( c.x.exists("static") )
 					statics.add(xclassfield(c));
@@ -272,7 +272,7 @@ class XmlParser {
 			interfaces : interfaces,
 			fields : fields,
 			statics : statics,
-			dynamic : dynamic,
+			tdynamic : tdynamic,
 			platforms : defplat(),
 		};
 	}

+ 1 - 1
std/haxe/unit/TestRunner.hx

@@ -35,7 +35,7 @@ class TestRunner {
 	static var tf : flash.TextField = null;
 #end
 
-	public static f9dynamic function print( v : Dynamic ) {
+	public static dynamic function print( v : Dynamic ) {
 		#if flash9
 		untyped {
 			if( tf == null ) {

+ 3 - 3
std/js/XMLSocket.hx

@@ -61,13 +61,13 @@ class XMLSocket {
 		cnx.close.call([]);
 	}
 
-	public function onData( data : String ) {
+	public dynamic function onData( data : String ) {
 	}
 
-	public function onClose() {
+	public dynamic function onClose() {
 	}
 
-	public function onConnect( b : Bool ) {
+	public dynamic function onConnect( b : Bool ) {
 	}
 
 }

+ 1 - 1
std/neko/db/Object.hx

@@ -58,7 +58,7 @@ class Object #if spod_rtti implements haxe.rtti.Infos #end {
 		local_manager.doInsert(this);
 	}
 
-	public function update() {
+	public dynamic function update() {
 		local_manager.doUpdate(this);
 	}
 

+ 0 - 2
std/neko/io/Error.hx

@@ -30,8 +30,6 @@ package neko.io;
 enum Error {
 	/** The IO is set into nonblocking mode and some data cannot be read or written **/
 	Blocked;
-	/** An operation has occured while the Input or Output has already been closed **/
-	Closed;
 	/** An operation is outside of its valid range **/
 	Overflow;
 	/** Other errors **/

+ 0 - 4
std/neko/io/Input.hx

@@ -47,12 +47,8 @@ class Input {
 	}
 
 	public function close() {
-		readBytes = function(_,_,_) { return throw Error.Closed; };
-		readChar = function() { return throw Error.Closed; };
-		close = function() { };
 	}
 
-
 	/* ------------------ API ------------------ */
 
 	public function readAll( ?bufsize : Int ) : String {

+ 4 - 8
std/neko/io/Output.hx

@@ -50,10 +50,6 @@ class Output {
 	}
 
 	public function close() {
-		writeBytes = function(_,_,_) { return throw Error.Closed; };
-		writeChar = function(_) { throw Error.Closed; };
-		flush = function() { throw Error.Closed; };
-		close = function() { };
 	}
 
 	/* ------------------ API ------------------ */
@@ -126,14 +122,14 @@ class Output {
 		else
 			writeUInt24(x);
 	}
-	
+
 	public function writeUInt24( x : Int ) {
 		if( x < 0 || x > 0xFFFFFF ) throw Error.Overflow;
 		writeChar(x & 0xFF);
 		writeChar((x >> 8) & 0xFF);
 		writeChar(x >> 16);
 	}
-	
+
 	public function writeUInt24B( x : Int ) {
 		if( x < 0 || x > 0xFFFFFF ) throw Error.Overflow;
 		writeChar(x >> 16);
@@ -152,7 +148,7 @@ class Output {
 		if( x < 0 ) throw Error.Overflow;
 		writeInt32(x);
 	}
-	
+
 	public function writeUInt32B( x : Int ) {
 		if( x < 0 ) throw Error.Overflow;
 		writeChar(x >>> 24);
@@ -160,7 +156,7 @@ class Output {
 		writeChar((x >> 8) & 0xFF);
 		writeChar(x & 0xFF);
 	}
-	
+
 	/**
 		Inform that we are about to write at least a specified number of bytes.
 		The underlying implementation can allocate proper working space depending

+ 3 - 3
std/tools/haxedoc/HtmlPrinter.hx

@@ -35,7 +35,7 @@ class HtmlPrinter {
 		typeParams = new Array();
 	}
 
-	public function output(str) {
+	public dynamic function output(str) {
 		neko.Lib.print(str);
 	}
 
@@ -218,9 +218,9 @@ class HtmlPrinter {
 			processPath(i.path,i.params);
 			print('</div>');
 		}
-		if( c.dynamic != null ) {
+		if( c.tdynamic != null ) {
 			var d = new List();
-			d.add(c.dynamic);
+			d.add(c.tdynamic);
 			print('<div class="implements">implements ');
 			processPath("Dynamic",d);
 			print('</div>');

+ 41 - 39
typer.ml

@@ -18,6 +18,7 @@
  *)
 open Ast
 open Type
+open Common
 
 type error_msg =
 	| Module_not_found of module_path
@@ -29,13 +30,13 @@ type error_msg =
 
 type context = {
 	(* shared *)
+	com : Common.context;
 	types : (module_path, module_path) Hashtbl.t;
 	modules : (module_path , module_def) Hashtbl.t;
 	delays : (unit -> unit) list list ref;
 	constructs : (module_path , access list * type_param list * func) Hashtbl.t;
 	warn : string -> pos -> unit;
 	error : error_msg -> pos -> unit;
-	fdynamic : bool;
 	fnullable : bool;
 	doinline : bool;
 	mutable std : module_def;
@@ -85,7 +86,7 @@ let access_str = function
 	| NoAccess -> "null"
 	| NeverAccess -> "never"
 	| MethodAccess m -> m
-	| MethodCantAccess -> "f9dynamic"
+	| MethodCantAccess -> "dynamic"
 	| ResolveAccess -> "resolve"
 	| InlineAccess -> "inline"
 
@@ -117,9 +118,6 @@ let rec error_msg = function
 	| Stack (m1,m2) -> error_msg m1 ^ "\n" ^ error_msg m2
 	| Protect m -> error_msg m
 
-let forbidden_packages = ref []
-let check_override = ref false
-
 let error msg p = raise (Error (Custom msg,p))
 
 let display_error ctx msg p = ctx.error (Custom msg) p
@@ -133,21 +131,21 @@ let null p t = mk (TConst TNull) t p
 
 let load ctx m p = (!load_ref) ctx m p
 
-let context err warn =
+let context com err warn =
 	let empty =	{
 		mpath = [] , "";
 		mtypes = [];
 		mimports = [];
 	} in
-	let f9 = Plugin.defined "flash9" in
+	let f9 = platform com Flash9 in
 	let ctx = {
+		com = com;
 		modules = Hashtbl.create 0;
 		types = Hashtbl.create 0;
 		constructs = Hashtbl.create 0;
 		delays = ref [];
-		fdynamic = f9 || Plugin.defined "php";
 		fnullable = f9;
-		doinline = not (Plugin.defined "no_inline");
+		doinline = not (Common.defined com "no_inline");
 		in_constructor = false;
 		in_static = false;
 		in_loop = false;
@@ -264,12 +262,12 @@ let field_access ctx get f t e p =
 		| _ ->
 			if ctx.untyped then normal else AccNo f.cf_name)
 	| MethodCantAccess when not ctx.untyped ->
-		error "Cannot rebind this method : please use 'f9dynamic' before method declaration" p
+		error "Cannot rebind this method : please use 'dynamic' before method declaration" p
 	| NormalAccess | MethodCantAccess ->
 		AccExpr (mk (TField (e,f.cf_name)) t p)
 	| MethodAccess m ->
 		if m = ctx.curmethod && (match e.eexpr with TConst TThis -> true | TTypeExpr (TClassDecl c) when c == ctx.curclass -> true | _ -> false) then
-			let prefix = if Plugin.defined "as3gen" then "$" else "" in
+			let prefix = if Common.defined ctx.com "as3gen" then "$" else "" in
 			AccExpr (mk (TField (e,prefix ^ f.cf_name)) t p)
 		else if get then
 			AccExpr (mk (TCall (mk (TField (e,m)) (mk_mono()) p,[])) t p)
@@ -416,7 +414,7 @@ and load_type ctx p t =
 				| AFFun (tl,t) ->
 					let t = load_type ctx p t in
 					let args = List.map (fun (name,o,t) -> name , o, load_type ctx p t) tl in
-					TFun (args,t), NormalAccess, (if ctx.fdynamic then MethodCantAccess else NormalAccess)
+					TFun (args,t), NormalAccess, MethodCantAccess
 				| AFProp (t,i1,i2) ->
 					let access m get =
 						match m with
@@ -575,12 +573,13 @@ let extend_remoting ctx c t p async prot =
 	if ctx.isproxy then
 		() (* skip this proxy generation, we shouldn't need it anyway *)
 	else
-	let ctx2 = context ctx.error ctx.warn in
-	let fb = !forbidden_packages in
-	forbidden_packages := [];
+	let ctx2 = context ctx.com ctx.error ctx.warn in
+	(* remove forbidden packages *)
+	let rules = ctx.com.package_rules in
+	ctx.com.package_rules <- PMap.foldi (fun key r acc -> match r with Forbidden -> acc | _ -> PMap.add key r acc) rules PMap.empty;
 	ctx2.isproxy <- true;
-	let ct = (try load_normal_type ctx2 t p false with e -> forbidden_packages := fb; raise e) in
-	forbidden_packages := fb;
+	let ct = (try load_normal_type ctx2 t p false with e -> ctx.com.package_rules <- rules; raise e) in
+	ctx.com.package_rules <- rules;
 	let tvoid = TPNormal { tpackage = []; tname = "Void"; tparams = [] } in
 	let make_field name args ret =
 		try
@@ -644,7 +643,7 @@ let extend_remoting ctx c t p async prot =
 
 let extend_xml_proxy ctx c t file p =
 	let t = load_type ctx p t in
-	let file = (try Plugin.find_file file with Not_found -> file) in
+	let file = (try Common.find_file ctx.com file with Not_found -> file) in
 	try
 		let rec loop = function
 			| Xml.Element (_,attrs,childs) ->
@@ -937,7 +936,7 @@ let unify_call_params ctx name el args p =
 	let rec loop acc l l2 skip =
 		match l , l2 with
 		| [] , [] ->
-			if Plugin.defined "flash" || Plugin.defined "js" then
+			if Common.defined ctx.com "flash" || Common.defined ctx.com "js" then
 				List.rev (no_opt acc)
 			else
 				List.rev (List.map fst acc)
@@ -1228,7 +1227,7 @@ let type_field ctx e i p get =
 		in
 		(try
 			let t , f = class_field c i in
-			if ctx.fdynamic && e.eexpr = TConst TSuper && f.cf_set = NormalAccess then error "Cannot access superclass variable for calling : needs to be a proper method" p;
+			if e.eexpr = TConst TSuper && f.cf_set = NormalAccess && Common.platform ctx.com Flash9 then error "Cannot access superclass variable for calling : needs to be a proper method" p;
 			if not f.cf_public && not (is_parent c ctx.curclass) && not ctx.untyped then display_error ctx ("Cannot access to private field " ^ i) p;
 			field_access ctx get f (apply_params c.cl_types params t) e p
 		with Not_found -> try
@@ -1266,7 +1265,7 @@ let type_field ctx e i p get =
 			field_access ctx get f (field_type f) e p
 		)
 	| TMono r ->
-		if ctx.untyped && Plugin.defined "swf-mark" && Plugin.defined "flash" then ctx.warn "Mark" p;
+		if ctx.untyped && Common.defined ctx.com "swf-mark" && Common.defined ctx.com "flash" then ctx.warn "Mark" p;
 		let f = {
 			cf_name = i;
 			cf_type = mk_mono();
@@ -2121,7 +2120,7 @@ and type_expr ctx ?(need_val=true) (e,p) =
 and type_call ctx e el p =
 	match e, el with
 	| (EConst (Ident "trace"),p) , e :: el ->
-		if Plugin.defined "no_traces" then
+		if Common.defined ctx.com "no_traces" then
 			mk (TConst TNull) (t_void ctx) p
 		else
 		let params = (match el with [] -> [] | _ -> ["customParams",(EArrayDecl el , p)]) in
@@ -2166,7 +2165,7 @@ and type_call ctx e el p =
 		e
 	| (EConst (Ident "__unprotect__"),_) , [(EConst (String _),_) as e] ->
 		let e = type_expr ctx e in
-		if Plugin.defined "flash" then
+		if Common.defined ctx.com "flash" then
 			mk (TCall (mk (TLocal "__unprotect__") (mk_mono()) p,[e])) e.etype e.epos
 		else
 			e
@@ -2323,7 +2322,7 @@ and type_inline ctx f ethis params tret p =
 	in
 	let e = (if PMap.is_empty subst then e else inline_params e) in
 	let init = (match vars with [] -> None | l -> Some (mk (TVars (List.rev l)) (t_void ctx) p)) in
-	if 	Plugin.defined "js" && (init <> None || !has_vars) then
+	if Common.defined ctx.com "js" && (init <> None || !has_vars) then
 		None
 	else match e.eexpr, init with
 	| TBlock [e] , None -> Some { e with etype = tret; }
@@ -2536,7 +2535,7 @@ let check_overriding ctx c p () =
 				let t = apply_params csup.cl_types params t in
 				ignore(follow f.cf_type); (* force evaluation *)
 				let p = (match f.cf_expr with None -> p | Some e -> e.epos) in
-				if !check_override && not (List.mem i c.cl_overrides) then
+				if not (List.mem i c.cl_overrides) then
 					display_error ctx ("Field " ^ i ^ " should be declared with 'override' since it is inherited from superclass") p
 				else if f.cf_public <> f2.cf_public then
 					display_error ctx ("Field " ^ i ^ " has different visibility (public/private) than superclass one") p
@@ -2667,7 +2666,7 @@ let init_class ctx c p herits fields =
 					let ctx = { ctx with curclass = c; tthis = tthis } in
 					let r = exc_protect (fun r ->
 						r := (fun() -> t);
-						if !Plugin.verbose then print_endline ("Typing " ^ s_type_path c.cl_path ^ "." ^ name);
+						if ctx.com.verbose then print_endline ("Typing " ^ s_type_path c.cl_path ^ "." ^ name);
 						cf.cf_expr <- Some (type_static_var ctx t e p);
 						t
 					) in
@@ -2705,14 +2704,14 @@ let init_class ctx c p herits fields =
 				cf_doc = doc;
 				cf_type = t;
 				cf_get = if inline then InlineAccess else NormalAccess;
-				cf_set = (if ctx.fdynamic && not (List.mem AF9Dynamic access) then MethodCantAccess else if inline then NeverAccess else NormalAccess);
+				cf_set = (if not (List.mem ADynamic access) then MethodCantAccess else if inline then NeverAccess else NormalAccess);
 				cf_expr = None;
 				cf_public = is_public access;
 				cf_params = params;
 			} in
 			let r = exc_protect (fun r ->
 				r := (fun() -> t);
-				if !Plugin.verbose then print_endline ("Typing " ^ s_type_path c.cl_path ^ "." ^ name);
+				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;
@@ -2755,7 +2754,7 @@ let init_class ctx c p herits fields =
 			let set = (match set with
 				| "null" ->
 					(* standard flash library read-only variables can't be accessed for writing, even in subclasses *)
-					if c.cl_extern && (match c.cl_path with "flash" :: _  , _ -> true | _ -> false) && Plugin.defined "flash9" then
+					if c.cl_extern && (match c.cl_path with "flash" :: _  , _ -> true | _ -> false) && Common.defined ctx.com "flash9" then
 						NeverAccess
 					else
 						NoAccess
@@ -2781,7 +2780,7 @@ let init_class ctx c p herits fields =
 	let fl = List.map (fun (f,p) ->
 		let access , constr, f , delayed = loop_cf f p in
 		let is_static = List.mem AStatic access in
-		if is_static && f.cf_name = "name" && Plugin.defined "js" then error "This identifier cannot be used in Javascript for statics" p;
+		if is_static && f.cf_name = "name" && Common.defined ctx.com "js" then error "This identifier cannot be used in Javascript for statics" p;
 		if (is_static || constr) && c.cl_interface && f.cf_name <> "__init__" then error "You can't declare static fields in interfaces" p;
 		if constr then begin
 			if c.cl_constructor <> None then error "Duplicate constructor" p;
@@ -2901,6 +2900,7 @@ let type_module ctx m tdecls loadp =
 	Hashtbl.add ctx.modules m.mpath m;
 	(* PASS 2 : build types structure - does not type any expression ! *)
 	let ctx = {
+		com = ctx.com;
 		modules = ctx.modules;
 		delays = ctx.delays;
 		constructs = ctx.constructs;
@@ -2912,7 +2912,6 @@ let type_module ctx m tdecls loadp =
 		std = ctx.std;
 		ret = ctx.ret;
 		isproxy = ctx.isproxy;
-		fdynamic = ctx.fdynamic;
 		fnullable = ctx.fnullable;
 		doinline = ctx.doinline;
 		current = m;
@@ -2984,7 +2983,7 @@ let type_module ctx m tdecls loadp =
 			let names = ref [] in
 			let index = ref 0 in
 			List.iter (fun (c,doc,t,p) ->
-				if c = "name" && Plugin.defined "js" then error "This identifier cannot be used in Javascript" p;
+				if c = "name" && Common.defined ctx.com "js" then error "This identifier cannot be used in Javascript" p;
 				let t = (match t with
 					| [] -> et
 					| l -> TFun (List.map (fun (s,opt,t) -> s, opt, load_type_opt ~opt ctx p (Some t)) l, et)
@@ -3096,18 +3095,21 @@ let load ctx m p =
 			let file = (match m with
 				| [] , name -> name
 				| x :: l , name ->
-					if List.mem x (!forbidden_packages) then error ("You can't access the " ^ x ^ " package with current compilation flags") p;
-					let x = (match x with "flash" when Plugin.defined "flash9" -> "flash9" | _ -> x) in
+					let x = (try
+						match PMap.find x ctx.com.package_rules with
+						| Forbidden -> error ("You can't access the " ^ x ^ " package with current compilation flags") p;
+						| Directory d -> d
+						with Not_found -> x
+					) in
 					String.concat "/" (x :: l) ^ "/" ^ name
 			) ^ ".hx" in
-			let file = (try Plugin.find_file file with Not_found -> raise (Error (Module_not_found m,p))) in
+			let file = (try Common.find_file ctx.com file with Not_found -> raise (Error (Module_not_found m,p))) in
 			let ch = (try open_in_bin file with _ -> error ("Could not open " ^ file) p) in
-			let t = Plugin.timer "parsing" in
-			let pack , decls = (try Parser.parse (Lexing.from_channel ch) file with e -> close_in ch; t(); raise e) in
+			let t = Common.timer "parsing" in
+			let pack , decls = (try Parser.parse ctx.com (Lexing.from_channel ch) file with e -> close_in ch; t(); raise e) in
 			t();
-			let pack , decls = (match pack , fst m with "flash" :: l , "flash9" :: l2 when l = l2 && Plugin.defined "flash9doc" -> fst m, List.map f9decl decls | _ -> pack , decls) in
 			close_in ch;
-			if !Plugin.verbose then print_endline ("Parsed " ^ file);
+			if ctx.com.verbose then print_endline ("Parsed " ^ file);
 			if pack <> fst m then begin
 				let spack m = if m = [] then "<empty>" else String.concat "." m in
 				if p == Ast.null_pos then