Pārlūkot izejas kodu

Retyper (#10724)

* demo retyper

* add load_only_cached_modules

* two-pass class pairing

* collect retyper logs

* add some tests

* support variables and properties

* support inference

* start to generalize for enum/typedef/abstract

* check enums and typedefs

* support abstract fields

* remove log noise

* handle tests like an actual programmer

* move retyper templates

* make tests look a bit less like cancer

* check class relations
Simon Krajewski 3 gadi atpakaļ
vecāks
revīzija
78c779d298
29 mainītis faili ar 616 papildinājumiem un 22 dzēšanām
  1. 279 0
      src/compiler/retyper.ml
  2. 15 0
      src/compiler/server.ml
  3. 13 0
      src/compiler/serverMessage.ml
  4. 1 0
      src/context/typecore.ml
  5. 1 0
      src/core/tType.ml
  6. 28 22
      src/typing/typeloadFields.ml
  7. 1 0
      src/typing/typeloadModule.ml
  8. 1 0
      src/typing/typer.ml
  9. 4 0
      std/haxe/macro/CompilationServer.hx
  10. 203 0
      tests/server/src/cases/RetyperTests.hx
  11. 2 0
      tests/server/test/templates/Dependency.hx
  12. 5 0
      tests/server/test/templates/retyper/AbstractWithDependency.hx
  13. 3 0
      tests/server/test/templates/retyper/AbstractWithSignatureDependency.hx
  14. 3 0
      tests/server/test/templates/retyper/DependentEnum.hx
  15. 1 0
      tests/server/test/templates/retyper/DependentTypedef.hx
  16. 9 0
      tests/server/test/templates/retyper/IndependentEnum.hx
  17. 7 0
      tests/server/test/templates/retyper/IndependentTypedef.hx
  18. 1 0
      tests/server/test/templates/retyper/InterfaceDependency.hx
  19. 5 0
      tests/server/test/templates/retyper/MutualDependency.hx
  20. 1 0
      tests/server/test/templates/retyper/WithInterfaceDependency.hx
  21. 7 0
      tests/server/test/templates/retyper/WithMutualDependency.hx
  22. 1 0
      tests/server/test/templates/retyper/WithParentDependency.hx
  23. 3 0
      tests/server/test/templates/retyper/WithSignatureDependency.hx
  24. 5 0
      tests/server/test/templates/retyper/WithSignatureDependencyInferredArg.hx
  25. 3 0
      tests/server/test/templates/retyper/WithSignatureDependencyInferredProperty.hx
  26. 5 0
      tests/server/test/templates/retyper/WithSignatureDependencyInferredRet.hx
  27. 3 0
      tests/server/test/templates/retyper/WithSignatureDependencyInferredVariable.hx
  28. 3 0
      tests/server/test/templates/retyper/WithSignatureDependencyProperty.hx
  29. 3 0
      tests/server/test/templates/retyper/WithSignatureDependencyVariable.hx

+ 279 - 0
src/compiler/retyper.ml

@@ -0,0 +1,279 @@
+open Globals
+open Ast
+open Typecore
+open Type
+open TypeloadModule
+open TypeloadFields
+
+exception Fail of string
+
+type retyping_context = {
+	typer : typer;
+	print_stack : string list;
+}
+
+let fail rctx s =
+	let stack = String.concat " " (List.rev rctx.print_stack) in
+	raise (Fail (Printf.sprintf "%s: %s" stack s))
+
+let disable_typeloading rctx ctx f =
+	let old = ctx.g.load_only_cached_modules in
+	ctx.g.load_only_cached_modules <- true;
+	try
+		Std.finally (fun () -> ctx.g.load_only_cached_modules <- old) f ()
+	with (Error.Error (Module_not_found path,_)) ->
+		fail rctx (Printf.sprintf "Could not load [Module %s]" (s_type_path path))
+
+let pair_type th t = match th with
+	| None ->
+		TExprToExpr.convert_type t,null_pos
+	| Some t ->
+		t
+
+let pair_class_field rctx ctx cctx fctx cf cff p =
+	match cff.cff_kind with
+	| FFun fd ->
+		let targs,tret = match follow cf.cf_type with
+			| TFun(args,ret) ->
+				args,ret
+			| _ ->
+				fail rctx "Type change"
+		in
+		let args = try
+			List.map2 (fun (name,opt,meta,th,eo) (_,_,t) ->
+				(name,opt,meta,Some (pair_type th t),eo)
+			) fd.f_args targs
+		with Invalid_argument _ ->
+			fail rctx "Type change"
+		in
+		let ret = pair_type fd.f_type tret in
+		let fd = {
+			fd with
+			f_args = args;
+			f_type = Some ret
+		} in
+		let load_args_ret () =
+			setup_args_ret ctx cctx fctx (fst cff.cff_name) fd p
+		in
+		let args,ret = disable_typeloading rctx ctx load_args_ret in
+		let t = TFun(args#for_type,ret) in
+		(fun () ->
+			(* This is the only part that should actually modify anything. *)
+			cf.cf_type <- t;
+			TypeBinding.bind_method ctx cctx fctx cf t args ret fd.f_expr (match fd.f_expr with Some e -> snd e | None -> cff.cff_pos);
+			if ctx.com.display.dms_full_typing then
+				remove_class_field_flag cf CfPostProcessed;
+		)
+	| FVar(th,eo) | FProp(_,_,th,eo) ->
+		let th = Some (pair_type th cf.cf_type) in
+		let t = disable_typeloading rctx ctx (fun () -> load_variable_type_hint ctx eo (pos cff.cff_name) th) in
+		(fun () ->
+			cf.cf_type <- t;
+			TypeBinding.bind_var ctx cctx fctx cf eo;
+			if ctx.com.display.dms_full_typing then
+				remove_class_field_flag cf CfPostProcessed;
+		)
+
+let pair_classes rctx context_init c d p =
+	let rctx = {rctx with
+		print_stack = (Printf.sprintf "[Class %s]" (s_type_path c.cl_path)) :: rctx.print_stack
+	} in
+	c.cl_restore();
+	(* TODO: What do we do with build macros? *)
+	let cctx = create_class_context c context_init p in
+	let ctx = create_typer_context_for_class rctx.typer cctx p in
+	let _ =
+		let rctx = {rctx with
+			print_stack = (Printf.sprintf "[Relations]") :: rctx.print_stack
+		} in
+		let has_extends = ref false in
+		let implements = ref c.cl_implements in
+		List.iter (function
+			| HExtends(path,p) ->
+				has_extends := true;
+				begin match c.cl_super with
+				| None ->
+					fail rctx (Printf.sprintf "parent %s appeared" (Ast.Printer.s_complex_type_path "" (path,p)))
+				| Some(c,tl) ->
+					let th = pair_type (Some(CTPath path,p)) (TInst(c,tl)) in
+					ignore (disable_typeloading rctx ctx (fun () -> Typeload.load_complex_type ctx false th))
+				end
+			| HImplements(path,p) ->
+				begin match !implements with
+					| (c,tl) :: rest ->
+						(* TODO: I think this should somehow check if it's actually the same interface. There could be cases
+						   where the order changes or something like that... Maybe we can compare the loaded type.
+						   However, this doesn't matter until we start retyping invalidated modules.
+						*)
+						implements := rest;
+						let th = pair_type (Some(CTPath path,p)) (TInst(c,tl)) in
+						ignore (disable_typeloading rctx ctx (fun () -> Typeload.load_complex_type ctx false th));
+					| [] ->
+						fail rctx (Printf.sprintf "interface %s appeared" (Ast.Printer.s_complex_type_path "" (path,p)))
+				end
+			| _ ->
+				()
+		) d.d_flags;
+		(* TODO: There are probably cases where the compiler generates a cl_super even though it's not in syntax *)
+		if not !has_extends then begin match c.cl_super with
+			| None -> ()
+			| Some(c,_) -> fail rctx (Printf.sprintf "parent %s disappeared" (s_type_path c.cl_path))
+		end;
+		begin match !implements with
+			| (c,_) :: _ -> fail rctx (Printf.sprintf "interface %s disappeared" (s_type_path c.cl_path))
+			| [] -> ()
+		end
+	in
+	let fl = List.map (fun cff ->
+		let name = fst cff.cff_name in
+		let rctx = {rctx with
+			print_stack = (Printf.sprintf "[Field %s]" name) :: rctx.print_stack
+		} in
+		let display_modifier = Typeload.check_field_access ctx cff in
+		let fctx = create_field_context cctx cff ctx.is_display_file display_modifier in
+		let cf = match fctx.field_kind with
+			| FKConstructor ->
+				begin match c.cl_constructor with
+				| None ->
+					fail rctx "Constructor not found"
+				| Some cf ->
+					cf
+				end
+			| FKNormal ->
+				begin try
+					PMap.find name (if fctx.is_static then c.cl_statics else c.cl_fields)
+				with Not_found ->
+					fail rctx "Field not found"
+				end
+			| FKInit ->
+				fail rctx "TODO"
+		in
+		pair_class_field rctx ctx cctx fctx cf cff p
+	) d.d_data in
+	fl @ [fun () -> TypeloadFields.finalize_class ctx cctx]
+
+let pair_enums ctx rctx en d =
+	let ctx = { ctx with type_params = en.e_params } in
+	let rctx = {rctx with
+		print_stack = (Printf.sprintf "[Enum %s]" (s_type_path en.e_path)) :: rctx.print_stack
+	} in
+	List.iter (fun eff ->
+		let name = fst eff.ec_name in
+		let rctx = {rctx with
+			print_stack = (Printf.sprintf "[Field %s]" name) :: rctx.print_stack
+		} in
+		let ef = try
+			PMap.find name en.e_constrs
+		with Not_found ->
+			fail rctx "Field not found"
+		in
+		let th = pair_type eff.ec_type ef.ef_type in
+		ignore (disable_typeloading rctx ctx (fun () -> Typeload.load_complex_type ctx false th))
+	) d.d_data;
+	[]
+
+let pair_typedefs ctx rctx td d =
+	let rctx = {rctx with
+		print_stack = (Printf.sprintf "[Typedef %s]" (s_type_path td.t_path)) :: rctx.print_stack
+	} in
+	let ctx = { ctx with type_params = td.t_params } in
+	ignore (disable_typeloading rctx ctx (fun () -> Typeload.load_complex_type ctx false d.d_data));
+	[]
+
+let pair_abstracts ctx rctx context_init a d p =
+	let rctx = {rctx with
+		print_stack = (Printf.sprintf "[Abstract %s]" (s_type_path a.a_path)) :: rctx.print_stack
+	} in
+	match a.a_impl with
+	| Some c ->
+		c.cl_restore();
+		let cctx = create_class_context c context_init p in
+		let ctx = create_typer_context_for_class rctx.typer cctx p in
+		let fl = List.map (fun cff ->
+			let cff = TypeloadFields.transform_abstract_field2 ctx a cff in
+			let name = fst cff.cff_name in
+			let rctx = {rctx with
+				print_stack = (Printf.sprintf "[Field %s]" name) :: rctx.print_stack
+			} in
+			let display_modifier = Typeload.check_field_access ctx cff in
+			let fctx = create_field_context cctx cff ctx.is_display_file display_modifier in
+			let cf = try
+				PMap.find name c.cl_statics
+			with Not_found ->
+				fail rctx "Field not found"
+			in
+			pair_class_field rctx ctx cctx fctx cf cff p
+		) d.d_data in
+		fl @ [fun () -> TypeloadFields.finalize_class ctx cctx]
+	| None ->
+		(* ?*)
+		[]
+
+let attempt_retyping ctx m p =
+	let com = ctx.com in
+	let file,_,_,decls = TypeloadParse.parse_module' com m.m_path p in
+	let ctx = create_typer_context_for_module ctx m in
+	let rctx = {
+		typer = ctx;
+		print_stack = [Printf.sprintf "[Module %s]" (s_type_path m.m_path)];
+	} in
+	(* log rctx 0 (Printf.sprintf "Retyping module %s" (s_type_path m.m_path)); *)
+	let context_init = new TypeloadFields.context_init in
+	let find_type name = try
+		List.find (fun t -> snd (t_infos t).mt_path = name) ctx.m.curmod.m_types
+	with Not_found ->
+		fail rctx (Printf.sprintf "Type %s not found" name)
+	in
+	let rec loop acc decls = match decls with
+		| [] ->
+			List.rev acc
+		| (d,p) :: decls ->
+			begin match d with
+			| EImport (path,mode) ->
+				ImportHandling.init_import ctx context_init path mode p;
+				ImportHandling.commit_import ctx path mode p;
+				loop acc decls
+			| EUsing path ->
+				ImportHandling.init_using ctx context_init path p;
+				loop acc decls
+			| EClass c ->
+				let mt = find_type (fst c.d_name) in
+				loop ((d,mt) :: acc) decls
+			| EEnum en ->
+				let mt = find_type (fst en.d_name) in
+				loop ((d,mt) :: acc) decls
+			| ETypedef td ->
+				let mt = find_type (fst td.d_name) in
+				loop ((d,mt) :: acc) decls
+			| EAbstract a ->
+				let mt = find_type (fst a.d_name) in
+				loop ((d,mt) :: acc) decls
+			| _ ->
+				loop acc decls
+			end;
+	in
+	try
+		m.m_extra.m_cache_state <- MSUnknown;
+		let pairs = loop [] decls in
+		let fl = List.map (fun (d,mt) -> match d,mt with
+			| EClass d,TClassDecl c ->
+				pair_classes rctx context_init c d p
+			| EEnum d,TEnumDecl en ->
+				pair_enums ctx rctx en d
+			| ETypedef d,TTypeDecl td ->
+				pair_typedefs ctx rctx td d
+			| EAbstract d,TAbstractDecl a ->
+				pair_abstracts ctx rctx context_init a d p
+			| _ ->
+				fail rctx "?"
+		) pairs in
+		(* If we get here we know that the everything is ok. *)
+		delay ctx PConnectField (fun () -> context_init#run);
+		List.iter (fun fl ->
+			List.iter (fun f -> f()) fl
+		) fl;
+		m.m_extra.m_cache_state <- MSGood;
+		m.m_extra.m_time <- Common.file_time file;
+		None
+	with Fail s ->
+		Some s

+ 15 - 0
src/compiler/server.ml

@@ -361,6 +361,21 @@ let check_module sctx ctx m p =
 					m.m_extra.m_cache_state <- MSUnknown;
 					check ()
 			in
+			let dirty = match dirty with
+				| Some (DependencyDirty _) when has_policy Retype ->
+					let result = Retyper.attempt_retyping ctx m p in
+					begin match result with
+					| None ->
+						ServerMessage.retyper_ok com "" m;
+						None
+					| Some reason ->
+						ServerMessage.retyper_fail com "" m reason;
+						dirty
+					end
+				| _ ->
+					dirty
+			in
+			(* Update the module now. It will use this dirty status for the remainder of this compilation. *)
 			begin match dirty with
 			| Some reason ->
 				(* Update the state if we're dirty. *)

+ 13 - 0
src/compiler/serverMessage.ml

@@ -13,6 +13,7 @@ type server_message_options = {
 	mutable print_parsed : bool;
 	mutable print_removed_directory : bool;
 	mutable print_reusing : bool;
+	mutable print_retyping : bool;
 	mutable print_skipping_dep : bool;
 	mutable print_unchanged_content : bool;
 	mutable print_cached_modules : bool;
@@ -38,6 +39,7 @@ let config = {
 	print_parsed = false;
 	print_removed_directory = false;
 	print_reusing = false;
+	print_retyping = false;
 	print_skipping_dep = false;
 	print_unchanged_content = false;
 	print_cached_modules = false;
@@ -85,6 +87,15 @@ let removed_directory com tabs dir =
 let reusing com tabs m =
 	if config.print_reusing then print_endline (Printf.sprintf "%s%sreusing %s" (sign_string com) tabs (s_type_path m.m_path))
 
+let retyper_ok com tabs m =
+	if config.print_retyping then print_endline (Printf.sprintf "%s%sretyped %s" (sign_string com) tabs (s_type_path m.m_path))
+
+let retyper_fail com tabs m reason =
+	if config.print_retyping then begin
+		print_endline (Printf.sprintf "%s%sfailed retyping %s" (sign_string com) tabs (s_type_path m.m_path));
+		print_endline (Printf.sprintf "%s%s%s" (sign_string com) (tabs ^ "  ") reason);
+	end
+
 let skipping_dep com tabs (m,reason) =
 	if config.print_skipping_dep then print_endline (Printf.sprintf "%sskipping %s (%s)" (sign_string com) (s_type_path m.m_path) reason)
 
@@ -154,6 +165,7 @@ let enable_all () =
 	config.print_parsed <- true;
 	config.print_removed_directory <- true;
 	config.print_reusing <- true;
+	config.print_retyping <- true;
 	config.print_skipping_dep <- true;
 	config.print_unchanged_content <- true;
 	config.print_cached_modules <- true;
@@ -177,6 +189,7 @@ let set_by_name name value = match name with
 	| "parsed" -> config.print_parsed <- value;
 	| "removedDirectory" -> config.print_removed_directory <- value;
 	| "reusing" -> config.print_reusing <- value;
+	| "retyping" -> config.print_retyping <- value;
 	| "skippingDep" -> config.print_skipping_dep <- value;
 	| "unchangedContent" -> config.print_unchanged_content <- value;
 	| "cachedModules" -> config.print_cached_modules <- value;

+ 1 - 0
src/context/typecore.ml

@@ -81,6 +81,7 @@ type typer_globals = {
 	(* Indicates that Typer.create() finished building this instance *)
 	mutable complete : bool;
 	mutable type_hints : (module_def_display * pos * t) list;
+	mutable load_only_cached_modules : bool;
 	(* api *)
 	do_inherit : typer -> Type.tclass -> pos -> (bool * placed_type_path) -> bool;
 	do_create : Common.context -> typer;

+ 1 - 0
src/core/tType.ml

@@ -30,6 +30,7 @@ type module_check_policy =
 	| CheckFileContentModification
 	| NoCheckDependencies
 	| NoCheckShadowing
+	| Retype
 
 type module_skip_reason =
 	| DependencyDirty of path

+ 28 - 22
src/typing/typeloadFields.ml

@@ -670,12 +670,15 @@ let rec get_parent c name =
 		with
 			Not_found -> get_parent csup name
 
+let transform_abstract_field2 ctx a cff =
+	let a_t = TExprToExpr.convert_type' (TAbstract(a,extract_param_types a.a_params)) in
+	let this_t = TExprToExpr.convert_type' a.a_this in (* TODO: better pos? *)
+	transform_abstract_field ctx.com this_t a_t a cff
+
 let transform_field (ctx,cctx) c f fields p =
 	let f = match cctx.abstract with
 		| Some a ->
-			let a_t = TExprToExpr.convert_type' (TAbstract(a,extract_param_types a.a_params)) in
-			let this_t = TExprToExpr.convert_type' a.a_this in (* TODO: better pos? *)
-			transform_abstract_field ctx.com this_t a_t a f
+			transform_abstract_field2 ctx a f
 		| None ->
 			f
 	in
@@ -970,6 +973,14 @@ module TypeBinding = struct
 		bind_type ctx cctx fctx cf r p
 end
 
+let load_variable_type_hint ctx eo p = function
+	| None when eo = None ->
+		typing_error ("Variable requires type-hint or initialization") p;
+	| None ->
+		mk_mono()
+	| Some t ->
+		lazy_display_type ctx (fun () -> load_type_hint ctx p (Some t))
+
 let create_variable (ctx,cctx,fctx) c f t eo p =
 	let is_abstract_enum_field = Meta.has Meta.Enum f.cff_meta in
 	if fctx.is_abstract_member && not is_abstract_enum_field then typing_error (fst f.cff_name ^ ": Cannot declare member variable in abstract") p;
@@ -982,14 +993,7 @@ let create_variable (ctx,cctx,fctx) c f t eo p =
 	in
 	if missing_initialization && fctx.is_static && fctx.is_final then
 		typing_error (fst f.cff_name ^ ": Static final variable must be initialized") p;
-	let t = (match t with
-		| None when eo = None ->
-			typing_error ("Variable requires type-hint or initialization") (pos f.cff_name);
-		| None ->
-			mk_mono()
-		| Some t ->
-			lazy_display_type ctx (fun () -> load_type_hint ctx p (Some t))
-	) in
+	let t = load_variable_type_hint ctx eo (pos f.cff_name) t in
 	let kind = if fctx.is_inline then
 		{ v_read = AccInline ; v_write = AccNever }
 	else if fctx.is_final then
@@ -1197,8 +1201,7 @@ let type_opt (ctx,cctx,fctx) p t =
 	| _ ->
 		Typeload.load_type_hint ctx p t
 
-let setup_args_ret ctx cctx fctx f fd p =
-	let name = fst f.cff_name in
+let setup_args_ret ctx cctx fctx name fd p =
 	let c = cctx.tclass in
 	let mk = lazy (
 		if String.length name < 4 then
@@ -1240,7 +1243,7 @@ let setup_args_ret ctx cctx fctx f fd p =
 		maybe_use_property_type fd.f_type (fun () -> match Lazy.force mk with MKGetter | MKSetter -> true | _ -> false) def
 	end in
 	let abstract_this = match cctx.abstract with
-		| Some a when fctx.is_abstract_member && fst f.cff_name <> "_new" (* TODO: this sucks *) && not fctx.is_macro ->
+		| Some a when fctx.is_abstract_member && name <> "_new" (* TODO: this sucks *) && not fctx.is_macro ->
 			Some a.a_this
 		| _ ->
 			None
@@ -1328,7 +1331,7 @@ let create_method (ctx,cctx,fctx) c f fd p =
 
 	ctx.type_params <- if fctx.is_static && not fctx.is_abstract_member then params else params @ ctx.type_params;
 	(* TODO is_lib: avoid forcing the return type to be typed *)
-	let args,ret = setup_args_ret ctx cctx fctx f fd p in
+	let args,ret = setup_args_ret ctx cctx fctx (fst f.cff_name) fd p in
 	let t = TFun (args#for_type,ret) in
 	let cf = {
 		(mk_field name ~public:(is_public (ctx,cctx) f.cff_access parent) t f.cff_pos (pos f.cff_name)) with
@@ -1658,6 +1661,15 @@ let check_overloads ctx c =
 	List.iter check_field c.cl_ordered_statics;
 	Option.may check_field c.cl_constructor
 
+let finalize_class ctx cctx =
+	(* push delays in reverse order so they will be run in correct order *)
+	List.iter (fun (ctx,r) ->
+		init_class_done ctx;
+		(match r with
+		| None -> ()
+		| Some r -> delay ctx PTypeField (fun() -> ignore(lazy_type r)))
+	) cctx.delayed_expr
+
 let init_class ctx c p context_init herits fields =
 	let cctx = create_class_context c context_init p in
 	let ctx = create_typer_context_for_class ctx cctx p in
@@ -1851,10 +1863,4 @@ let init_class ctx c p context_init herits fields =
 	if not has_struct_init then
 		(* add_constructor does not deal with overloads correctly *)
 		if not ctx.com.config.pf_overload then TypeloadFunction.add_constructor ctx c cctx.force_constructor p;
-	(* push delays in reverse order so they will be run in correct order *)
-	List.iter (fun (ctx,r) ->
-		init_class_done ctx;
-		(match r with
-		| None -> ()
-		| Some r -> delay ctx PTypeField (fun() -> ignore(lazy_type r)))
-	) cctx.delayed_expr
+	finalize_class ctx cctx

+ 1 - 0
src/typing/typeloadModule.ml

@@ -799,6 +799,7 @@ let load_module' ctx g m p =
 				raise (Error (Module_not_found m,p))
 			in
 			if ctx.com.module_nonexistent_lut#mem m then raise_not_found();
+			if ctx.g.load_only_cached_modules then raise_not_found();
 			let is_extern = ref false in
 			let file, decls = try
 				(* Try parsing *)

+ 1 - 0
src/typing/typer.ml

@@ -1971,6 +1971,7 @@ let rec create com =
 			global_using = [];
 			complete = false;
 			type_hints = [];
+			load_only_cached_modules = false;
 			do_inherit = MagicTypes.on_inherit;
 			do_create = create;
 			do_macro = MacroContext.type_macro;

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

@@ -52,6 +52,10 @@ enum abstract ModuleCheckPolicy(Int) {
 		of the current module file.
 	**/
 	var NoCheckShadowing = 3;
+	/**
+		Retype the module's contents if its file is invalidated. This is currently experimental.
+	**/
+	var Retype = 4;
 }
 
 enum abstract ContextOptions(Int) {

+ 203 - 0
tests/server/src/cases/RetyperTests.hx

@@ -0,0 +1,203 @@
+package cases;
+
+import haxe.display.FsPath;
+import haxe.display.Server;
+import utest.Assert;
+
+using StringTools;
+using Lambda;
+
+class RetyperTests extends TestCase {
+	static function getBaseArgs(moduleName:String) {
+		return [
+			moduleName + ".hx",
+			"--no-output",
+			"-js",
+			"no.js",
+			"--macro",
+			"haxe.macro.CompilationServer.setModuleCheckPolicy(['" + moduleName + "'], [Retype], false)"
+		];
+	}
+
+	function testNonSignature() {
+		vfs.putContent("WithDependency.hx", getTemplate("WithDependency.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("WithDependency");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('retyped WithDependency'));
+	}
+
+	function testSignature() {
+		vfs.putContent("WithSignatureDependency.hx", getTemplate("retyper/WithSignatureDependency.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("WithSignatureDependency");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('failed retyping WithSignatureDependency'));
+		Assert.isTrue(hasMessage('[Module WithSignatureDependency] [Class WithSignatureDependency] [Field test]: Could not load [Module Dependency]'));
+	}
+
+	function testSignatureInferredArg() {
+		vfs.putContent("WithSignatureDependency.hx", getTemplate("retyper/WithSignatureDependencyInferredArg.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("WithSignatureDependency");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('failed retyping WithSignatureDependency'));
+		Assert.isTrue(hasMessage('[Module WithSignatureDependency] [Class WithSignatureDependency] [Field test]: Could not load [Module Dependency]'));
+	}
+
+	function testSignatureInferredRet() {
+		vfs.putContent("WithSignatureDependency.hx", getTemplate("retyper/WithSignatureDependencyInferredRet.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("WithSignatureDependency");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('failed retyping WithSignatureDependency'));
+		Assert.isTrue(hasMessage('[Module WithSignatureDependency] [Class WithSignatureDependency] [Field test]: Could not load [Module Dependency]'));
+	}
+
+	function testSignatureVariable() {
+		vfs.putContent("WithSignatureDependency.hx", getTemplate("retyper/WithSignatureDependencyVariable.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("WithSignatureDependency");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('failed retyping WithSignatureDependency'));
+		Assert.isTrue(hasMessage('[Module WithSignatureDependency] [Class WithSignatureDependency] [Field test]: Could not load [Module Dependency]'));
+	}
+
+	function testSignatureInferredVariable() {
+		vfs.putContent("WithSignatureDependency.hx", getTemplate("retyper/WithSignatureDependencyInferredVariable.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("WithSignatureDependency");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('failed retyping WithSignatureDependency'));
+		Assert.isTrue(hasMessage('[Module WithSignatureDependency] [Class WithSignatureDependency] [Field test]: Could not load [Module Dependency]'));
+	}
+
+	function testSignatureProperty() {
+		vfs.putContent("WithSignatureDependency.hx", getTemplate("retyper/WithSignatureDependencyProperty.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("WithSignatureDependency");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('failed retyping WithSignatureDependency'));
+		Assert.isTrue(hasMessage('[Module WithSignatureDependency] [Class WithSignatureDependency] [Field test]: Could not load [Module Dependency]'));
+	}
+
+	function testSignatureInferredProperty() {
+		vfs.putContent("WithSignatureDependency.hx", getTemplate("retyper/WithSignatureDependencyInferredProperty.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("WithSignatureDependency");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('failed retyping WithSignatureDependency'));
+		Assert.isTrue(hasMessage('[Module WithSignatureDependency] [Class WithSignatureDependency] [Field test]: Could not load [Module Dependency]'));
+	}
+
+	function testMutual() {
+		vfs.putContent("WithMutualDependency.hx", getTemplate("retyper/WithMutualDependency.hx"));
+		vfs.putContent("MutualDependency.hx", getTemplate("retyper/MutualDependency.hx"));
+		var args = getBaseArgs("WithMutualDependency");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("MutualDependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('retyped WithMutualDependency'));
+	}
+
+	function testParent() {
+		vfs.putContent("WithParentDependency.hx", getTemplate("retyper/WithParentDependency.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("WithParentDependency");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('failed retyping WithParentDependency'));
+		Assert.isTrue(hasMessage('[Module WithParentDependency] [Class WithParentDependency] [Relations]: Could not load [Module Dependency]'));
+	}
+
+	function testInterface() {
+		vfs.putContent("WithInterfaceDependency.hx", getTemplate("retyper/WithInterfaceDependency.hx"));
+		vfs.putContent("InterfaceDependency.hx", getTemplate("retyper/InterfaceDependency.hx"));
+		var args = getBaseArgs("WithInterfaceDependency");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("InterfaceDependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('failed retyping WithInterfaceDependency'));
+		Assert.isTrue(hasMessage('[Module WithInterfaceDependency] [Class WithInterfaceDependency] [Relations]: Could not load [Module InterfaceDependency]'));
+	}
+
+	function testIndependentEnum() {
+		vfs.putContent("IndependentEnum.hx", getTemplate("retyper/IndependentEnum.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("IndependentEnum");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('retyped IndependentEnum'));
+	}
+
+	function testDependentEnum() {
+		vfs.putContent("DependentEnum.hx", getTemplate("retyper/DependentEnum.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("DependentEnum");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('failed retyping DependentEnum'));
+		Assert.isTrue(hasMessage('[Module DependentEnum] [Enum DependentEnum] [Field Constructor]: Could not load [Module Dependency]'));
+	}
+
+	function testIndependentTypedef() {
+		vfs.putContent("IndependentTypedef.hx", getTemplate("retyper/IndependentTypedef.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("IndependentTypedef");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('retyped IndependentTypedef'));
+	}
+
+	function testDependentTypedef() {
+		vfs.putContent("DependentTypedef.hx", getTemplate("retyper/DependentTypedef.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("DependentTypedef");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('failed retyping DependentTypedef'));
+		Assert.isTrue(hasMessage('[Module DependentTypedef] [Typedef DependentTypedef]: Could not load [Module Dependency]'));
+	}
+
+	function testAbstractNonSignature() {
+		vfs.putContent("AbstractWithDependency.hx", getTemplate("retyper/AbstractWithDependency.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("AbstractWithDependency");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('retyped AbstractWithDependency'));
+	}
+
+	function testAbstractSignature() {
+		vfs.putContent("AbstractWithSignatureDependency.hx", getTemplate("retyper/AbstractWithSignatureDependency.hx"));
+		vfs.putContent("Dependency.hx", getTemplate("Dependency.hx"));
+		var args = getBaseArgs("AbstractWithSignatureDependency");
+		runHaxe(args);
+		runHaxeJson([], ServerMethods.Invalidate, {file: new FsPath("Dependency.hx")});
+		runHaxe(args);
+		Assert.isTrue(hasMessage('failed retyping AbstractWithSignatureDependency'));
+		Assert.isTrue(hasMessage('[Module AbstractWithSignatureDependency] [Abstract AbstractWithSignatureDependency] [Field test]: Could not load [Module Dependency]'));
+	}
+}

+ 2 - 0
tests/server/test/templates/Dependency.hx

@@ -2,4 +2,6 @@ class Dependency {
 	static public function get() {
 		return "Hello World";
 	}
+
+	public function new() {}
 }

+ 5 - 0
tests/server/test/templates/retyper/AbstractWithDependency.hx

@@ -0,0 +1,5 @@
+abstract AbstractWithDependency(String) {
+	public static function notMain() {
+		trace(Dependency.get());
+	}
+}

+ 3 - 0
tests/server/test/templates/retyper/AbstractWithSignatureDependency.hx

@@ -0,0 +1,3 @@
+abstract AbstractWithSignatureDependency(String) {
+	public static function test(d:Dependency) {}
+}

+ 3 - 0
tests/server/test/templates/retyper/DependentEnum.hx

@@ -0,0 +1,3 @@
+enum DependentEnum {
+	Constructor(s:Dependency);
+}

+ 1 - 0
tests/server/test/templates/retyper/DependentTypedef.hx

@@ -0,0 +1 @@
+typedef DependentTypedef = Dependency;

+ 9 - 0
tests/server/test/templates/retyper/IndependentEnum.hx

@@ -0,0 +1,9 @@
+enum IndependentEnum {
+	Constructor(s:String);
+}
+
+class MakeDependency {
+	static function f() {
+		Dependency.get();
+	}
+}

+ 7 - 0
tests/server/test/templates/retyper/IndependentTypedef.hx

@@ -0,0 +1,7 @@
+typedef IndependentTypedef = String;
+
+class MakeDependency {
+	static function f() {
+		Dependency.get();
+	}
+}

+ 1 - 0
tests/server/test/templates/retyper/InterfaceDependency.hx

@@ -0,0 +1 @@
+interface InterfaceDependency {}

+ 5 - 0
tests/server/test/templates/retyper/MutualDependency.hx

@@ -0,0 +1,5 @@
+class MutualDependency {
+	static public function get() {
+		return WithMutualDependency.value;
+	}
+}

+ 1 - 0
tests/server/test/templates/retyper/WithInterfaceDependency.hx

@@ -0,0 +1 @@
+class WithInterfaceDependency implements InterfaceDependency {}

+ 7 - 0
tests/server/test/templates/retyper/WithMutualDependency.hx

@@ -0,0 +1,7 @@
+class WithMutualDependency {
+	static public var value = "Hello World";
+
+	public static function main() {
+		trace(MutualDependency.get());
+	}
+}

+ 1 - 0
tests/server/test/templates/retyper/WithParentDependency.hx

@@ -0,0 +1 @@
+class WithParentDependency extends Dependency {}

+ 3 - 0
tests/server/test/templates/retyper/WithSignatureDependency.hx

@@ -0,0 +1,3 @@
+class WithSignatureDependency {
+	public static function test(d:Dependency) {}
+}

+ 5 - 0
tests/server/test/templates/retyper/WithSignatureDependencyInferredArg.hx

@@ -0,0 +1,5 @@
+class WithSignatureDependency {
+	public static function test(d) {
+		d = new Dependency();
+	}
+}

+ 3 - 0
tests/server/test/templates/retyper/WithSignatureDependencyInferredProperty.hx

@@ -0,0 +1,3 @@
+class WithSignatureDependency {
+	public static var test(default, null) = new Dependency();
+}

+ 5 - 0
tests/server/test/templates/retyper/WithSignatureDependencyInferredRet.hx

@@ -0,0 +1,5 @@
+class WithSignatureDependency {
+	public static function test() {
+		return new Dependency();
+	}
+}

+ 3 - 0
tests/server/test/templates/retyper/WithSignatureDependencyInferredVariable.hx

@@ -0,0 +1,3 @@
+class WithSignatureDependency {
+	public static var test = new Dependency();
+}

+ 3 - 0
tests/server/test/templates/retyper/WithSignatureDependencyProperty.hx

@@ -0,0 +1,3 @@
+class WithSignatureDependency {
+	public static var test(default, null):Dependency;
+}

+ 3 - 0
tests/server/test/templates/retyper/WithSignatureDependencyVariable.hx

@@ -0,0 +1,3 @@
+class WithSignatureDependency {
+	public static var test:Dependency;
+}