Sfoglia il codice sorgente

Native lib rework part 1 (#8629)

* start on native lib unification (Java)

* progress (C#)

* absorb build logic into lib classes

* make swflibs work

* unify a bit

* fix duplicate public flags on Java interfaces

* be lazy with the zipping

* actually unify `build`
Simon Krajewski 6 anni fa
parent
commit
710eea679a

+ 76 - 66
src/codegen/dotnet.ml

@@ -22,6 +22,7 @@ open Globals
 open Ast
 open IlData
 open IlMeta
+open NativeLibraries
 
 (* see http://msdn.microsoft.com/en-us/library/2sk3x8a7(v=vs.71).aspx *)
 let cs_binops =
@@ -126,11 +127,11 @@ let netpath_to_hx std = function
 
 let lookup_ilclass std com ilpath =
 	let path = netpath_to_hx std ilpath in
-	List.fold_right (fun (_,_,_,get_raw_class) acc ->
+	List.fold_right (fun net_lib acc ->
 		match acc with
-		| None -> get_raw_class path
+		| None -> net_lib#lookup path
 		| Some p -> acc
-	) com.net_libs None
+	) com.native_libs.net_libs None
 
 let discard_nested = function
 	| (ns,_),cl -> (ns,[]),cl
@@ -1109,52 +1110,57 @@ let normalize_ilcls ctx cls =
 let add_net_std com file =
 	com.net_std <- file :: com.net_std
 
-let add_net_lib com file std =
-	let ilctx = ref None in
-	let netpath_to_hx = netpath_to_hx std in
-	let real_file = ref file in
-	let get_ctx () =
-		match !ilctx with
-		| Some c ->
-			c
-		| None ->
-			let file = if Sys.file_exists file then
-				file
-			else try Common.find_file com file with
-				| Not_found -> try Common.find_file com (file ^ ".dll") with
-				| Not_found ->
-					failwith (".NET lib " ^ file ^ " not found")
-			in
-			real_file := file;
-			let r = PeReader.create_r (open_in_bin file) com.defines.Define.values in
-			let ctx = PeReader.read r in
-			let clr_header = PeReader.read_clr_header ctx in
-			let cache = IlMetaReader.create_cache () in
-			let meta = IlMetaReader.read_meta_tables ctx clr_header cache in
-			close_in (r.PeReader.ch);
+class net_library com name file_path std = object(self)
+	inherit [net_lib_type,unit] native_library name file_path
+
+	val mutable ilctx = None
+	val cache = Hashtbl.create 0
+
+	method private netpath_to_hx =
+		netpath_to_hx std
+
+	method load =
+		let r = PeReader.create_r (open_in_bin file_path) com.defines.Define.values in
+		let ctx = PeReader.read r in
+		let clr_header = PeReader.read_clr_header ctx in
+		let cache = IlMetaReader.create_cache () in
+		let meta = IlMetaReader.read_meta_tables ctx clr_header cache in
+		close_in (r.PeReader.ch);
+		if PMap.mem "net_loader_debug" com.defines.Define.values then
+			print_endline ("for lib " ^ file_path);
+		let il_typedefs = Hashtbl.copy meta.il_typedefs in
+		Hashtbl.clear meta.il_typedefs;
+
+		Hashtbl.iter (fun _ td ->
+			let path = IlMetaTools.get_path (TypeDef td) in
 			if PMap.mem "net_loader_debug" com.defines.Define.values then
-				print_endline ("for lib " ^ file);
-			let il_typedefs = Hashtbl.copy meta.il_typedefs in
-			Hashtbl.clear meta.il_typedefs;
-
-			Hashtbl.iter (fun _ td ->
-				let path = IlMetaTools.get_path (TypeDef td) in
-				if PMap.mem "net_loader_debug" com.defines.Define.values then
-					Printf.printf "found %s\n" (s_type_path (netpath_to_hx path));
-				Hashtbl.replace com.net_path_map (netpath_to_hx path) path;
-				Hashtbl.replace meta.il_typedefs path td
-			) il_typedefs;
-			let meta = { nstd = std; ncom = com; nil = meta } in
-			ilctx := Some meta;
-			meta
-	in
+				Printf.printf "found %s\n" (s_type_path (self#netpath_to_hx path));
+			Hashtbl.replace com.net_path_map (self#netpath_to_hx path) path;
+			Hashtbl.replace meta.il_typedefs path td
+		) il_typedefs;
+		let meta = { nstd = std; ncom = com; nil = meta } in
+		ilctx <- Some meta
+
+	method get_ctx = match ilctx with
+		| None ->
+			self#load;
+			self#get_ctx
+		| Some ctx ->
+			ctx
 
-	let cache = Hashtbl.create 0 in
-	let lookup path =
+	method close =
+		()
+
+	method list_modules =
+		Hashtbl.fold (fun path _ acc -> match path with
+			| _,_ :: _, _ -> acc
+			| _ -> self#netpath_to_hx path :: acc) (self#get_ctx).nil.il_typedefs []
+
+	method lookup path : net_lib_type =
 		try
 			Hashtbl.find cache path
 		with | Not_found -> try
-			let ctx = get_ctx() in
+			let ctx = self#get_ctx in
 			let ns, n, cl = hxpath_to_net ctx path in
 			let cls = IlMetaTools.convert_class ctx.nil (ns,n,cl) in
 			let cls = normalize_ilcls ctx cls in
@@ -1163,38 +1169,31 @@ let add_net_lib com file std =
 		with | Not_found ->
 			Hashtbl.add cache path None;
 			None
-	in
 
-	let all_files () =
-		Hashtbl.fold (fun path _ acc -> match path with
-			| _,_ :: _, _ -> acc
-			| _ -> netpath_to_hx path :: acc) (get_ctx()).nil.il_typedefs []
-	in
-
-	let build path =
-		let p = { pfile = !real_file ^ " @ " ^ s_type_path path; pmin = 0; pmax = 0; } in
+	method build (path : path) (p : pos) : (string * Ast.package) option =
+		let p = { pfile = file_path ^ " @ " ^ s_type_path path; pmin = 0; pmax = 0; } in
 		let pack = match fst path with | ["haxe";"root"] -> [] | p -> p in
 		let cp = ref [] in
 		let rec build path = try
 			if PMap.mem "net_loader_debug" com.defines.Define.values then
 				Printf.printf "looking up %s\n" (s_type_path path);
-			match lookup path with
+			match self#lookup path with
 			| Some({csuper = Some{snorm = LClass( (["System"],[],("Delegate"|"MulticastDelegate")),_)}} as cls)
 				when List.mem SSealed cls.cflags.tdf_semantics ->
-				let ctx = get_ctx() in
+				let ctx = self#get_ctx in
 				let hxcls = convert_ilclass ctx p ~delegate:true cls in
 				let delegate = convert_delegate ctx p cls in
 				cp := (hxcls,p) :: (delegate,p) :: !cp;
 				List.iter (fun ilpath ->
-					let path = netpath_to_hx ilpath in
+					let path = netpath_to_hx std ilpath in
 					build path
 				) cls.cnested
 			| Some cls ->
-				let ctx = get_ctx() in
+				let ctx = self#get_ctx in
 				let hxcls = convert_ilclass ctx p cls in
 				cp := (hxcls,p) :: !cp;
 				List.iter (fun ilpath ->
-					let path = netpath_to_hx ilpath in
+					let path = netpath_to_hx std ilpath in
 					build path
 				) cls.cnested
 			| _ -> ()
@@ -1204,14 +1203,25 @@ let add_net_lib com file std =
 		build path;
 		match !cp with
 			| [] -> None
-			| cp -> Some (!real_file, (pack,cp))
-	in
-	let build path p =
-		build path
-	in
-	com.load_extern_type <- com.load_extern_type @ [build];
-	com.net_libs <- (file, std, all_files, lookup) :: com.net_libs
+			| cp -> Some (file_path, (pack,cp))
 
+	method get_data = ()
+
+	initializer
+		if std then self#add_flag FlagIsStd
+end
+
+let add_net_lib com file std =
+	let real_file = if Sys.file_exists file then
+		file
+	else try Common.find_file com file with
+		| Not_found -> try Common.find_file com (file ^ ".dll") with
+		| Not_found ->
+			failwith (".NET lib " ^ file ^ " not found")
+	in
+	let net_lib = new net_library com file real_file std in
+	com.load_extern_type <- com.load_extern_type @ [net_lib#build];
+	com.native_libs.net_libs <- (net_lib :> (net_lib_type,unit) native_library) :: com.native_libs.net_libs
 
 let before_generate com =
 	(* netcore version *)
@@ -1292,4 +1302,4 @@ let before_generate com =
 	) !matched;
 
 	(* now force all libraries to initialize *)
-	List.iter (function (_,_,_,lookup) -> ignore (lookup ([],""))) com.net_libs
+	List.iter (function net_lib -> ignore (net_lib#lookup ([],""))) com.native_libs.net_libs

+ 8 - 8
src/codegen/gencommon/gencommon.ml

@@ -947,19 +947,19 @@ let dump_descriptor gen name path_s module_s =
 				file
 	in
 	if Common.platform gen.gcon Java then
-		List.iter (fun (s,std,_,_,_) ->
-			if not std then begin
-				SourceWriter.write w (path s ".jar");
+		List.iter (fun java_lib ->
+			if not (java_lib#has_flag NativeLibraries.FlagIsStd) then begin
+				SourceWriter.write w (path java_lib#get_file_path ".jar");
 				SourceWriter.newline w;
 			end
-		) gen.gcon.java_libs
+		) gen.gcon.native_libs.java_libs
 	else if Common.platform gen.gcon Cs then
-		List.iter (fun (s,std,_,_) ->
-			if not std then begin
-				SourceWriter.write w (path s ".dll");
+		List.iter (fun net_lib ->
+			if not (net_lib#has_flag NativeLibraries.FlagIsStd) then begin
+				SourceWriter.write w (path net_lib#get_name ".dll");
 				SourceWriter.newline w;
 			end
-		) gen.gcon.net_libs;
+		) gen.gcon.native_libs.net_libs;
 	SourceWriter.write w "end libs";
 	SourceWriter.newline w;
 	let args = gen.gcon.c_args in

+ 170 - 119
src/codegen/java.ml

@@ -18,6 +18,7 @@
 *)
 open Unix
 open ExtString
+open NativeLibraries
 open Common
 open Globals
 open Ast
@@ -73,11 +74,11 @@ let real_java_path ctx (pack,name) =
 
 let lookup_jclass com path =
 	let path = jpath_to_hx path in
-	List.fold_right (fun (_,_,_,_,get_raw_class) acc ->
+	List.fold_right (fun java_lib acc ->
 		match acc with
-		| None -> get_raw_class path
+		| None -> java_lib#lookup path
 		| Some p -> Some p
-	) com.java_libs None
+	) com.native_libs.java_libs None
 
 let mk_type_path ctx path params =
 	let name, sub = try
@@ -778,7 +779,7 @@ let normalize_jclass com cls =
 				List.iter (fun jf ->
 					if not(List.mem JStatic jf.jf_flags) && not (List.exists (fun jf2 -> jf.jf_name = jf2.jf_name && not (List.mem JStatic jf2.jf_flags) && jf.jf_signature = jf2.jf_signature) all_methods) then begin
 						let jf = if abstract && force_check then del_override jf else jf in
-						let jf = { jf with jf_flags = JPublic :: jf.jf_flags } in (* interfaces implementations are always public *)
+						let jf = if not (List.mem JPublic jf.jf_flags) then { jf with jf_flags = JPublic :: jf.jf_flags } else jf in (* interfaces implementations are always public *)
 
 						added_interface_fields := jf :: !added_interface_fields;
 					end
@@ -890,101 +891,15 @@ let get_classes_zip zip =
 	) (Zip.entries zip);
 	!ret
 
-let add_java_lib com file std =
-	let file = if Sys.file_exists file then
-		file
-	else try Common.find_file com file with
-		| Not_found -> try Common.find_file com (file ^ ".jar") with
-		| Not_found ->
-			failwith ("Java lib " ^ file ^ " not found")
-	in
-	let hxpack_to_jpack = Hashtbl.create 16 in
-	let get_raw_class, close, list_all_files =
-		(* check if it is a directory or jar file *)
-		match (Unix.stat file).st_kind with
-		| S_DIR -> (* open classes directly from directory *)
-			let all = ref [] in
-			let rec iter_files pack dir path = try
-				let file = Unix.readdir dir in
-				let filepath = path ^ "/" ^ file in
-				(if String.ends_with file ".class" then
-					let name = String.sub file 0 (String.length file - 6) in
-					let path = jpath_to_hx (pack,name) in
-					if not (String.exists file "$") then all := path :: !all;
-					Hashtbl.add hxpack_to_jpack path (pack,name)
-				else if (Unix.stat filepath).st_kind = S_DIR && file <> "." && file <> ".." then
-					let pack = pack @ [file] in
-					iter_files (pack) (Unix.opendir filepath) filepath);
-				iter_files pack dir path
-			with | End_of_file | Unix.Unix_error _ ->
-				Unix.closedir dir
-			in
-			iter_files [] (Unix.opendir file) file;
-			let all = !all in
-
-			(fun (pack, name) ->
-				let real_path = file ^ "/" ^ (String.concat "/" pack) ^ "/" ^ (name ^ ".class") in
-				try
-					let data = Std.input_file ~bin:true real_path in
-					Some(JReader.parse_class (IO.input_string data), real_path, real_path)
-				with
-					| _ -> None), (fun () -> ()), (fun () -> all)
-		| _ -> (* open zip file *)
-			let closed = ref false in
-			let zip = ref (Zip.open_in file) in
-			let check_open () =
-				if !closed then begin
-					prerr_endline ("JAR file " ^ file ^ " already closed"); (* if this happens, find when *)
-					zip := Zip.open_in file;
-					closed := false
-				end
-			in
-			List.iter (function
-				| { Zip.is_directory = false; Zip.filename = filename } when String.ends_with filename ".class" ->
-					let pack = String.nsplit filename "/" in
-					(match List.rev pack with
-						| [] -> ()
-						| name :: pack ->
-							let name = String.sub name 0 (String.length name - 6) in
-							let pack = List.rev pack in
-							Hashtbl.add hxpack_to_jpack (jpath_to_hx (pack,name)) (pack,name))
-				| _ -> ()
-			) (Zip.entries !zip);
-			(fun (pack, name) ->
-				check_open();
-				try
-					let location = (String.concat "/" (pack @ [name]) ^ ".class") in
-					let entry = Zip.find_entry !zip location in
-					let data = Zip.read_entry !zip entry in
-					Some(JReader.parse_class (IO.input_string data), file, file ^ "@" ^ location)
-				with
-					| Not_found ->
-						None),
-			(fun () -> if not !closed then begin closed := true; Zip.close_in !zip end),
-			(fun () -> check_open(); get_classes_zip !zip)
-	in
-	let cached_types = Hashtbl.create 12 in
-	let get_raw_class path =
-		try
-			Hashtbl.find cached_types path
-		with | Not_found -> try
-			let pack, name = Hashtbl.find hxpack_to_jpack path in
-			let try_file (pack,name) =
-				match get_raw_class (pack,name) with
-				| None ->
-						Hashtbl.add cached_types path None;
-						None
-				| Some (i, p1, p2) ->
-						Hashtbl.add cached_types path (Some(i,p1,p2)); (* type loop normalization *)
-						let ret = Some (normalize_jclass com i, p1, p2) in
-						Hashtbl.replace cached_types path ret;
-						ret
-			in
-			try_file (pack,name)
-		with Not_found ->
-			None
-	in
-	let replace_canonical_name p pack name_original name_replace decl =
+class virtual java_library com name file_path = object(self)
+	inherit [java_lib_type,unit] native_library name file_path as super
+
+	val hxpack_to_jpack = Hashtbl.create 16
+
+	method convert_path (path : path) : path =
+		Hashtbl.find hxpack_to_jpack path
+
+	method private replace_canonical_name p pack name_original name_replace decl =
 		let mk_meta name = (Meta.JavaCanonical, [EConst (String (String.concat "." pack)), p; EConst(String name), p], p) in
 		let add_meta name metas =
 			if Meta.has Meta.JavaCanonical metas then
@@ -1006,8 +921,9 @@ let add_java_lib com file std =
 			| EAbstract a ->
 				EAbstract { a with d_meta = add_meta (fst a.d_name) a.d_meta }
 			| d -> d
-	in
-	let rec build ctx path p types =
+
+	method build path (p : pos) : (string * Ast.package) option =
+		let rec build ctx path p types =
 		try
 			if List.mem path !types then
 				None
@@ -1018,14 +934,14 @@ let add_java_lib com file std =
 						false
 				in
 				types := path :: !types;
-				match get_raw_class path, path with
-				| None, ([], c) -> build ctx (["haxe";"root"], c) p types
+				match self#lookup path, path with
+					| None, ([], c) -> build ctx (["haxe";"root"], c) p types
 				| None, _ -> None
 				| Some (cls, real_path, pos_path), _ ->
 						let is_disallowed_inner = first && String.exists (snd cls.cpath) "$" in
 						let is_disallowed_inner = if is_disallowed_inner then begin
 								let outer, inner = String.split (snd cls.cpath) "$" in
-								match get_raw_class (fst path, outer) with
+								match self#lookup (fst path, outer) with
 									| None -> false
 									| _ -> true
 							end else
@@ -1034,7 +950,7 @@ let add_java_lib com file std =
 						if is_disallowed_inner then
 							None
 						else begin
-							if com.verbose then print_endline ("Parsed Java class " ^ (s_type_path cls.cpath));
+							if ctx.jcom.verbose then print_endline ("Parsed Java class " ^ (s_type_path cls.cpath));
 							let old_types = ctx.jtparams in
 							ctx.jtparams <- cls.ctypes :: ctx.jtparams;
 
@@ -1042,16 +958,16 @@ let add_java_lib com file std =
 
 							let pack = match fst path with | ["haxe";"root"] -> [] | p -> p in
 
-							let ppath = Hashtbl.find hxpack_to_jpack path in
+							let ppath = self#convert_path path in
 							let inner = List.fold_left (fun acc (path,out,_,_) ->
 								let path = jpath_to_hx path in
 								(if out <> Some ppath then
 									acc
-								else match build ctx path p types with
+									else match build ctx path p types with
 									| Some(_,(_, classes)) ->
 										let base = snd ppath ^ "$" in
 										(List.map (fun (def,p) ->
-											replace_canonical_name p (fst ppath) base (snd ppath ^ ".") def, p) classes) @ acc
+											self#replace_canonical_name p (fst ppath) base (snd ppath ^ ".") def, p) classes) @ acc
 									| _ -> acc);
 							) [] cls.cinner_types in
 
@@ -1126,25 +1042,160 @@ let add_java_lib com file std =
 			prerr_endline ("Class reader failed: " ^ msg);
 			None
 		| e ->
-			if com.verbose then begin
+			if ctx.jcom.verbose then begin
 				(* prerr_endline (Printexc.get_backtrace ()); requires ocaml 3.11 *)
 				prerr_endline (Printexc.to_string e)
 			end;
 			None
-	in
-	let build path p = build (create_ctx com) path p (ref [["java";"lang"], "String"]) in
-	let cached_files = ref None in
-	let list_all_files () = match !cached_files with
+		in
+		build (create_ctx com) path p (ref [["java";"lang"], "String"])
+
+	method get_data = ()
+end
+
+class java_library_jar com name file_path = object(self)
+	inherit java_library com name file_path
+
+	val zip = lazy (Zip.open_in file_path)
+	val mutable cached_files = None
+	val cached_types = Hashtbl.create 12
+	val mutable closed = false
+
+	method load =
+		List.iter (function
+			| { Zip.is_directory = false; Zip.filename = filename } when String.ends_with filename ".class" ->
+				let pack = String.nsplit filename "/" in
+				(match List.rev pack with
+					| [] -> ()
+					| name :: pack ->
+						let name = String.sub name 0 (String.length name - 6) in
+						let pack = List.rev pack in
+						Hashtbl.add hxpack_to_jpack (jpath_to_hx (pack,name)) (pack,name))
+			| _ -> ()
+		) (Zip.entries (Lazy.force zip))
+
+	method private lookup' ((pack,name) : path) : java_lib_type =
+		try
+			let zip = Lazy.force zip in
+			let location = (String.concat "/" (pack @ [name]) ^ ".class") in
+			let entry = Zip.find_entry zip location in
+			let data = Zip.read_entry zip entry in
+			Some(JReader.parse_class (IO.input_string data), file_path, file_path ^ "@" ^ location)
+		with
+			| Not_found ->
+				None
+
+	method lookup (path : path) : java_lib_type =
+		try
+			Hashtbl.find cached_types path
+		with | Not_found -> try
+			let pack, name = self#convert_path path in
+			let try_file (pack,name) =
+				match self#lookup' (pack,name) with
+				| None ->
+						Hashtbl.add cached_types path None;
+						None
+				| Some (i, p1, p2) ->
+						Hashtbl.add cached_types path (Some(i,p1,p2)); (* type loop normalization *)
+						let ret = Some (normalize_jclass com i, p1, p2) in
+						Hashtbl.replace cached_types path ret;
+						ret
+			in
+			try_file (pack,name)
+		with Not_found ->
+			None
+
+	method close =
+		if not closed then begin
+			closed <- true;
+			Zip.close_in (Lazy.force zip)
+		end
+
+	method private list_modules' : path list =
+		let ret = ref [] in
+		List.iter (function
+			| { Zip.is_directory = false; Zip.filename = f } when (String.sub (String.uncapitalize f) (String.length f - 6) 6) = ".class" && not (String.exists f "$") ->
+					(match List.rev (String.nsplit f "/") with
+					| clsname :: pack ->
+						if not (String.contains clsname '$') then begin
+							let path = jpath_to_hx (List.rev pack, String.sub clsname 0 (String.length clsname - 6)) in
+							ret := path :: !ret
+						end
+					| _ ->
+							ret := ([], jname_to_hx f) :: !ret)
+			| _ -> ()
+		) (Zip.entries (Lazy.force zip));
+		!ret
+
+	method list_modules : path list = match cached_files with
 		| None ->
-				let ret = list_all_files () in
-				cached_files := Some ret;
-				ret
-		| Some r -> r
-	in
+			let ret = self#list_modules' in
+			cached_files <- Some ret;
+			ret
+		| Some r ->
+			r
+end
+
+class java_library_dir com name file_path = object(self)
+	inherit java_library com name file_path
+
+	val mutable files = []
+
+	method load =
+		let all = ref [] in
+		let rec iter_files pack dir path = try
+			let file = Unix.readdir dir in
+			let filepath = path ^ "/" ^ file in
+			(if String.ends_with file ".class" then
+				let name = String.sub file 0 (String.length file - 6) in
+				let path = jpath_to_hx (pack,name) in
+				if not (String.exists file "$") then all := path :: !all;
+				Hashtbl.add hxpack_to_jpack path (pack,name)
+			else if (Unix.stat filepath).st_kind = S_DIR && file <> "." && file <> ".." then
+				let pack = pack @ [file] in
+				iter_files (pack) (Unix.opendir filepath) filepath);
+			iter_files pack dir path
+		with | End_of_file | Unix.Unix_error _ ->
+			Unix.closedir dir
+		in
+		iter_files [] (Unix.opendir file_path) file_path;
+		files <- !all
+
+	method close =
+		()
+
+	method list_modules =
+		files
 
+	method lookup (pack,name) : java_lib_type =
+		let real_path = file_path ^ "/" ^ (String.concat "/" pack) ^ "/" ^ (name ^ ".class") in
+		try
+			let data = Std.input_file ~bin:true real_path in
+			Some(JReader.parse_class (IO.input_string data), real_path, real_path)
+		with
+			| _ -> None
+end
+
+let add_java_lib com name std =
+	let file = if Sys.file_exists name then
+		name
+	else try Common.find_file com name with
+		| Not_found -> try Common.find_file com (name ^ ".jar") with
+		| Not_found ->
+			failwith ("Java lib " ^ name ^ " not found")
+	in
+	let java_lib = match (Unix.stat file).st_kind with
+		| S_DIR ->
+			(new java_library_dir com name file :> java_library)
+		| _ ->
+			(new java_library_jar com name file :> java_library)
+	in
+	if std then java_lib#add_flag FlagIsStd;
+	java_lib#load;
+	let build path p = java_lib#build path p in
 	(* TODO: add_dependency m mdep *)
 	com.load_extern_type <- com.load_extern_type @ [build];
-	com.java_libs <- (file, std, close, list_all_files, get_raw_class) :: com.java_libs
+	com.native_libs.java_libs <- (java_lib :> (java_lib_type,unit) native_library) :: com.native_libs.java_libs
 
 let before_generate con =
 	let java_ver = try

+ 46 - 24
src/codegen/swfLoader.ml

@@ -22,6 +22,7 @@ open As3hl
 open Common
 open Globals
 open Ast
+open NativeLibraries
 
 let lowercase_pack pack =
 	let rec loop acc pack =
@@ -572,39 +573,60 @@ let parse_swf com file =
 	t();
 	(h,tags)
 
-let add_swf_lib com file extern =
-	let swf_data = ref None in
-	let swf_classes = ref None in
-	let getSWF = (fun() ->
-		match !swf_data with
+class swf_library com name file_path = object(self)
+	inherit [swf_lib_type,Swf.swf] native_library name file_path
+
+	val mutable swf_data = None
+	val mutable swf_classes = None
+
+	method load =
+		ignore(self#get_swf)
+
+	method get_swf = match swf_data with
 		| None ->
-			let d = parse_swf com file in
-			swf_data := Some d;
+			let d = parse_swf com file_path in
+			swf_data <- Some d;
 			d
-		| Some d -> d
-	) in
-	let extract = (fun() ->
-		match !swf_classes with
+		| Some d ->
+			d
+
+	method extract = match swf_classes with
 		| None ->
-			let d = extract_data (getSWF()) in
-			swf_classes := Some d;
+			let d = extract_data self#get_swf in
+			swf_classes <- Some d;
 			d
-		| Some d -> d
-	) in
-	let build cl p =
-		match (try Some (Hashtbl.find (extract()) cl) with Not_found -> None) with
+		| Some d ->
+			d
+
+	method lookup path =
+		try Some (Hashtbl.find (self#extract) path)
+		with Not_found -> None
+
+	method list_modules =
+		Hashtbl.fold (fun path _ acc -> path :: acc) (self#extract) []
+
+	method close =
+		()
+
+	method build (path : path) (p : pos) : (string * Ast.package) option =
+		match (try Some (Hashtbl.find (self#extract) path) with Not_found -> None) with
 		| None -> None
-		| Some c -> Some (file, build_class com c file)
-	in
-	com.load_extern_type <- com.load_extern_type @ [build];
-	if not extern then com.swf_libs <- (file,getSWF,extract) :: com.swf_libs
+		| Some c -> Some (file_path, build_class com c file_path)
+
+	method get_data = self#get_swf
+end
+
+let add_swf_lib com file extern =
+	let swf_lib = new swf_library com file file in
+	com.load_extern_type <- com.load_extern_type @ [swf_lib#build];
+	if not extern then com.native_libs.swf_libs <- (swf_lib :> (swf_lib_type,Swf.swf) native_library) :: com.native_libs.swf_libs
 
-let remove_classes toremove lib hcl =
-	let lib = lib() in
+let remove_classes toremove lib l =
 	match !toremove with
 	| [] -> lib
 	| _ ->
-		let hcl = hcl() in
+		let hcl = Hashtbl.create 0 in
+		List.iter (fun path -> Hashtbl.add hcl path ()) l;
 		match List.filter (fun c -> Hashtbl.mem hcl c) (!toremove) with
 		| [] -> lib
 		| classes ->

+ 7 - 28
src/compiler/displayOutput.ml

@@ -444,8 +444,8 @@ module TypePathHandler = struct
 				end;
 			) r;
 		) com.class_path;
-		List.iter (fun (_,_,extract) ->
-			Hashtbl.iter (fun (path,name) _ ->
+		let process_lib lib =
+			List.iter (fun (path,name) ->
 				if path = p then classes := name :: !classes else
 				let rec loop p1 p2 =
 					match p1, p2 with
@@ -454,32 +454,11 @@ module TypePathHandler = struct
 					| a :: p1, b :: p2 -> if a = b then loop p1 p2
 				in
 				loop path p
-			) (extract());
-		) com.swf_libs;
-		List.iter (fun (path,std,close,all_files,lookup) ->
-			List.iter (fun (path, name) ->
-				if path = p then classes := name :: !classes else
-				let rec loop p1 p2 =
-					match p1, p2 with
-					| [], _ -> ()
-					| x :: _, [] -> packages := x :: !packages
-					| a :: p1, b :: p2 -> if a = b then loop p1 p2
-				in
-				loop path p
-			) (all_files())
-		) com.java_libs;
-		List.iter (fun (path,std,all_files,lookup) ->
-			List.iter (fun (path, name) ->
-				if path = p then classes := name :: !classes else
-				let rec loop p1 p2 =
-					match p1, p2 with
-					| [], _ -> ()
-					| x :: _, [] -> packages := x :: !packages
-					| a :: p1, b :: p2 -> if a = b then loop p1 p2
-				in
-			loop path p
-			) (all_files())
-		) com.net_libs;
+			) lib#list_modules;
+		in
+		List.iter process_lib com.native_libs.swf_libs;
+		List.iter process_lib com.native_libs.net_libs;
+		List.iter process_lib com.native_libs.java_libs;
 		unique !packages, unique !classes
 
 	(** raise field completion listing packages and modules in a given package *)

+ 10 - 14
src/compiler/main.ml

@@ -246,7 +246,7 @@ module Initialize = struct
 			| Cs ->
 				let old_flush = ctx.flush in
 				ctx.flush <- (fun () ->
-					com.net_libs <- [];
+					com.native_libs.net_libs <- [];
 					old_flush()
 				);
 				Dotnet.before_generate com;
@@ -254,8 +254,8 @@ module Initialize = struct
 			| Java ->
 				let old_flush = ctx.flush in
 				ctx.flush <- (fun () ->
-					List.iter (fun (_,_,close,_,_) -> close()) com.java_libs;
-					com.java_libs <- [];
+					List.iter (fun java_lib -> java_lib#close) com.native_libs.java_libs;
+					com.native_libs.java_libs <- [];
 					old_flush()
 				);
 				Java.before_generate com;
@@ -809,17 +809,13 @@ try
 			(* TODO: this is something we're gonna remove once we have something nicer for generating flash externs *)
 			force_typing := true;
 			pre_compilation := (fun() ->
-				List.iter (fun (_,_,extract) ->
-					Hashtbl.iter (fun n _ -> classes := n :: !classes) (extract())
-				) com.swf_libs;
-				List.iter (fun (_,std,_,all_files,_) ->
-					if not std then
-						List.iter (fun path -> if path <> (["java";"lang"],"String") then classes := path :: !classes) (all_files())
-				) com.java_libs;
-				List.iter (fun (_,std,all_files,_) ->
-					if not std then
-						List.iter (fun path -> classes := path :: !classes) (all_files())
-				) com.net_libs;
+				let process_lib lib =
+					if not (lib#has_flag NativeLibraries.FlagIsStd) then
+						List.iter (fun path -> if path <> (["java";"lang"],"String") then classes := path :: !classes) lib#list_modules
+				in
+				List.iter process_lib com.native_libs.net_libs;
+				List.iter process_lib com.native_libs.swf_libs;
+				List.iter process_lib com.native_libs.java_libs;
 			) :: !pre_compilation;
 			xml_out := Some "hx"
 		end;

+ 7 - 6
src/context/common.ml

@@ -21,6 +21,7 @@ open Ast
 open Type
 open Globals
 open Define
+open NativeLibraries
 
 type package_rule =
 	| Forbidden
@@ -205,9 +206,7 @@ type context = {
 	mutable resources : (string,string) Hashtbl.t;
 	mutable neko_libs : string list;
 	mutable include_files : (string * string) list;
-	mutable swf_libs : (string * (unit -> Swf.swf) * (unit -> ((string list * string),As3hl.hl_class) Hashtbl.t)) list;
-	mutable java_libs : (string * bool * (unit -> unit) * (unit -> (path list)) * (path -> ((JData.jclass * string * string) option))) list; (* (path,std,close,all_files,lookup) *)
-	mutable net_libs : (string * bool * (unit -> path list) * (path -> IlData.ilclass option)) list; (* (path,std,all_files,lookup) *)
+	mutable native_libs : native_libraries;
 	mutable net_std : string list;
 	net_path_map : (path,string list * string list * string) Hashtbl.t;
 	mutable c_args : string list;
@@ -437,10 +436,12 @@ let create version s_version args =
 		main = None;
 		flash_version = 10.;
 		resources = Hashtbl.create 0;
-		swf_libs = [];
-		java_libs = [];
-		net_libs = [];
 		net_std = [];
+		native_libs = {
+			java_libs = [];
+			net_libs = [];
+			swf_libs = [];
+		};
 		net_path_map = Hashtbl.create 0;
 		c_args = [];
 		neko_libs = [];

+ 51 - 0
src/context/nativeLibraries.ml

@@ -0,0 +1,51 @@
+(*
+	The Haxe Compiler
+	Copyright (C) 2005-2019  Haxe Foundation
+
+	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., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301, USA.
+ *)
+
+open Globals
+open ExtString
+
+type native_lib_flags =
+	| FlagIsStd
+
+class virtual ['a,'data] native_library (name : string) (file_path : string) = object(self)
+	val mutable flags : native_lib_flags list = []
+
+	method add_flag flag = flags <- flag :: flags
+	method has_flag flag = List.mem flag flags
+
+	method get_name = name
+	method get_file_path = file_path
+
+	method virtual build : path -> pos -> (string * Ast.package) option
+	method virtual close : unit
+	method virtual list_modules : path list
+	method virtual load : unit
+	method virtual lookup : path -> 'a
+	method virtual get_data : 'data
+end
+
+type java_lib_type = (JData.jclass * string * string) option
+type net_lib_type = IlData.ilclass option
+type swf_lib_type = As3hl.hl_class option
+
+type native_libraries = {
+	mutable java_libs : (java_lib_type,unit) native_library list;
+	mutable net_libs : (net_lib_type,unit) native_library list;
+	mutable swf_libs : (swf_lib_type,Swf.swf) native_library list;
+}

+ 6 - 5
src/generators/gencs.ml

@@ -3347,15 +3347,16 @@ let generate con =
 		let hashes = Hashtbl.fold (fun i s acc -> incr nhash; (normalize_i i,s) :: acc) rcf_ctx.rcf_hash_fields [] in
 		let hashes = List.sort (fun (i,s) (i2,s2) -> compare i i2) hashes in
 
-		let haxe_libs = List.filter (function (_,_,_,lookup) -> is_some (lookup (["haxe";"lang"], "DceNo"))) gen.gcon.net_libs in
+		let haxe_libs = List.filter (function net_lib -> is_some (net_lib#lookup (["haxe";"lang"], "DceNo"))) gen.gcon.native_libs.net_libs in
 		(try
 			(* first let's see if we're adding a -net-lib that has already a haxe.lang.FieldLookup *)
-			let name,_,_,_ = List.find (function (_,_,_,lookup) -> is_some (lookup (["haxe";"lang"], "FieldLookup"))) gen.gcon.net_libs in
+			let net_lib = List.find (function net_lib -> is_some (net_lib#lookup (["haxe";"lang"], "FieldLookup"))) gen.gcon.native_libs.net_libs in
+			let name = net_lib#get_name in
 			if not (Common.defined gen.gcon Define.DllImport) then begin
 				gen.gcon.warning ("The -net-lib with path " ^ name ^ " contains a Haxe-generated assembly. Please define `-D dll_import` to handle Haxe-generated dll import correctly") null_pos;
 				raise Not_found
 			end;
-			if not (List.exists (function (n,_,_,_) -> n = name) haxe_libs) then
+			if not (List.exists (function net_lib -> net_lib#get_name = name) haxe_libs) then
 				gen.gcon.warning ("The -net-lib with path " ^ name ^ " contains a Haxe-generated assembly, however it wasn't compiled with `-dce no`. Recompilation with `-dce no` is recommended") null_pos;
 			(* it has; in this case, we need to add the used fields on each __init__ *)
 			flookup_cl.cl_extern <- true;
@@ -3407,8 +3408,8 @@ let generate con =
 						| (p,_) -> p
 					in
 					let path = (pack, snd c.cl_path ^ extra) in
-					ignore (List.find (function (_,_,_,lookup) ->
-						is_some (lookup path)) haxe_libs);
+					ignore (List.find (function net_lib ->
+						is_some (net_lib#lookup path)) haxe_libs);
 					c.cl_extern <- true;
 				with | Not_found -> ())
 				| _ -> ()) gen.gtypes

+ 5 - 5
src/generators/genjava.ml

@@ -962,12 +962,12 @@ let rec get_fun_modifiers meta access modifiers =
 
 let generate con =
 	let exists = ref false in
-	con.java_libs <- List.map (fun (file,std,close,la,gr) ->
-		if String.ends_with file "hxjava-std.jar" then begin
+	List.iter (fun java_lib ->
+		if String.ends_with java_lib#get_file_path "hxjava-std.jar" then begin
 			exists := true;
-			(file,true,close,la,gr)
-		end else
-			(file,std,close,la,gr)) con.java_libs;
+			java_lib#add_flag NativeLibraries.FlagIsStd;
+		end;
+	) con.native_libs.java_libs;
 	if not !exists then
 		failwith "Your version of hxjava is outdated. Please update it by running: `haxelib update hxjava`";
 	let gen = new_ctx con in

+ 5 - 5
src/generators/genjvm.ml

@@ -3026,13 +3026,13 @@ let generate com =
 		}
 	} in
 	Std.finally (Timer.timer ["generate";"java";"preprocess"]) Preprocessor.preprocess gctx;
-	let class_paths = ExtList.List.filter_map (fun (file,std,_,_,_) ->
-		if std then None
+	let class_paths = ExtList.List.filter_map (fun java_lib ->
+		if java_lib#has_flag NativeLibraries.FlagIsStd then None
 		else begin
 			let dir = Printf.sprintf "%slib/" jar_dir in
 			Path.mkdir_from_path dir;
-			let name = file_name_and_extension file in
-			let ch_in = open_in_bin file in
+			let name = file_name_and_extension java_lib#get_file_path in
+			let ch_in = open_in_bin java_lib#get_file_path in
 			let ch_out = open_out_bin (Printf.sprintf "%s%s" dir name) in
 			let b = IO.read_all (IO.input_channel ch_in) in
 			output_string ch_out b;
@@ -3040,7 +3040,7 @@ let generate com =
 			close_out ch_out;
 			Some (Printf.sprintf "lib/%s" name)
 		end
-	) com.java_libs in
+	) com.native_libs.java_libs in
 	let manifest_content =
 		"Manifest-Version: 1.0\n" ^
 		(match class_paths with [] -> "" | _ -> "Class-Path: " ^ (String.concat " " class_paths ^ "\n")) ^

+ 7 - 6
src/generators/genswf.ml

@@ -24,6 +24,7 @@ open Type
 open Common
 open Ast
 open Globals
+open NativeLibraries
 
 let tag ?(ext=false) d = {
 	tid = 0;
@@ -570,8 +571,8 @@ let generate swf_header com =
 	(* list exports *)
 	let exports = Hashtbl.create 0 in
 	let toremove = ref [] in
-	List.iter (fun (file,lib,_) ->
-		let _, tags = lib() in
+	List.iter (fun swf_lib ->
+		let _, tags = swf_lib#get_data in
 		List.iter (fun t ->
 			match t.tdata with
 			| TExport l -> List.iter (fun e -> Hashtbl.add exports e.exp_name ()) l
@@ -597,7 +598,7 @@ let generate swf_header com =
 				) el
 			| _ -> ()
 		) tags;
-	) com.swf_libs;
+	) com.native_libs.swf_libs;
 	(* build haxe swf *)
 	let tags = build_swf9 com file swc in
 	let header, bg = (match swf_header with None -> default_header com | Some h -> convert_header com h) in
@@ -638,11 +639,11 @@ let generate swf_header com =
 	let swf = header, fattr @ meta_data @ bg :: scene :: debug @ swf_script_limits @ tags @ [tag TShowFrame] in
 	(* merge swf libraries *)
 	let priority = ref (swf_header = None) in
-	let swf = List.fold_left (fun swf (file,lib,cl) ->
-		let swf = merge com file !priority swf (SwfLoader.remove_classes toremove lib cl) in
+	let swf = List.fold_left (fun swf swf_lib ->
+		let swf = merge com file !priority swf (SwfLoader.remove_classes toremove swf_lib#get_data swf_lib#list_modules) in
 		priority := false;
 		swf
-	) swf com.swf_libs in
+	) swf com.native_libs.swf_libs in
 	let swf = match swf with
 	| header,tags when Common.defined com Define.SwfPreloaderFrame ->
 		let rec loop l =