1 module d.semantic.symbol;
2 
3 import d.semantic.caster;
4 import d.semantic.declaration;
5 import d.semantic.semantic;
6 
7 import d.ast.declaration;
8 import d.ast.expression;
9 import d.ast.identifier;
10 
11 import d.ir.expression;
12 import d.ir.symbol;
13 import d.ir.type;
14 
15 alias AstModule = d.ast.declaration.Module;
16 alias Module = d.ir.symbol.Module;
17 
18 alias BinaryExpression = d.ir.expression.BinaryExpression;
19 
20 // Conflict with Interface in object.di
21 alias Interface = d.ir.symbol.Interface;
22 
23 enum isSchedulable(D, S) = is(D : Declaration) &&
24 	is(S : Symbol) &&
25 	!__traits(isAbstractClass, S);
26 
27 struct SymbolVisitor {
28 	private SemanticPass pass;
29 	alias pass this;
30 
31 	this(SemanticPass pass) {
32 		this.pass = pass;
33 	}
34 	
35 	void visit(Declaration d, Symbol s) {
36 		auto tid = typeid(s);
37 		
38 		import std.traits, std.typetuple;
39 		alias Members = TypeTuple!(__traits(getOverloads, SymbolAnalyzer, "analyze"));
40 		foreach(visit; Members) {
41 			alias parameters = ParameterTypeTuple!visit;
42 			static assert(parameters.length == 2);
43 			
44 			static if (isSchedulable!parameters) {
45 				alias DeclType = parameters[0];
46 				alias SymType  = parameters[1];
47 				
48 				if (tid is typeid(SymType)) {
49 					auto decl = cast(DeclType) d;
50 					assert(
51 						decl,
52 						"Unexpected declaration type "
53 							~ typeid(DeclType).toString(),
54 					);
55 					
56 					scheduler.schedule(decl, () @trusted {
57 						// Fast cast can be trusted in this case,
58 						// we already did the check.
59 						import util.fastcast;
60 						return fastCast!SymType(s);
61 					} ());
62 					return;
63 				}
64 			}
65 		}
66 		
67 		assert(0, "Can't process " ~ tid.toString());
68 	}
69 }
70 
71 struct SymbolAnalyzer {
72 	private SemanticPass pass;
73 	alias pass this;
74 	
75 	alias Step = SemanticPass.Step;
76 	
77 	this(SemanticPass pass) {
78 		this.pass = pass;
79 	}
80 	
81 	void analyze(AstModule astm, Module m) {
82 		auto oldManglePrefix = manglePrefix;
83 		scope(exit) manglePrefix = oldManglePrefix;
84 		
85 		manglePrefix = "";
86 		
87 		import std.conv;
88 		foreach(name; astm.packages) {
89 			auto s = name.toString(context);
90 			manglePrefix = s.length.to!string() ~ s ~ manglePrefix;
91 		}
92 		
93 		auto name = astm.name.toString(context);
94 		manglePrefix ~= name.length.to!string() ~ name;
95 		
96 		auto mangle = m.mangle = context.getName(manglePrefix);
97 		
98 		import source.name;
99 		// All modules implicitely import object.
100 		auto obj = importModule([BuiltinName!"object"]);
101 		m.addImport(obj);
102 		
103 		import d.semantic.declaration;
104 		m.members = DeclarationVisitor(pass).flatten(astm.declarations, m);
105 		
106 		// sdc.intrinsics is a magic module !
107 		if (mangle == BuiltinName!"3sdc10intrinsics") {
108 			fillIntrinsics(m);
109 		}
110 		
111 		scheduler.require(m.members);
112 		m.step = Step.Processed;
113 	}
114 	
115 	private void fillIntrinsics(Module m) {
116 		void setInstrinsic(Function f, Intrinsic i) in {
117 			assert(f, "intrinsic not defined");
118 		} do {
119 			pass.scheduler.require(f);
120 			f.intrinsicID = i;
121 		}
122 		
123 		import source.name;
124 		void set(Name name, Intrinsic i) {
125 			import source.location;
126 			auto s = m.resolve(Location.init, name);
127 			if (s is null) {
128 				return;
129 			}
130 			
131 			if (auto f = cast(Function) s) {
132 				return setInstrinsic(f, i);
133 			}
134 			
135 			auto os = cast(OverloadSet) s;
136 			assert(os);
137 			foreach (c; os.set) {
138 				if (auto f = cast(Function) c) {
139 					setInstrinsic(f, i);
140 				}
141 			}
142 		}
143 		
144 		// Ideally we'd use UDA, but as they are not implemented,
145 		// we just bake the magic in the compiler.
146 		set(BuiltinName!"expect", Intrinsic.Expect);
147 		set(BuiltinName!"cas", Intrinsic.CompareAndSwap);
148 		set(BuiltinName!"casWeak", Intrinsic.CompareAndSwapWeak);
149 		set(BuiltinName!"popCount", Intrinsic.PopCount);
150 		set(BuiltinName!"countLeadingZeros", Intrinsic.CountLeadingZeros);
151 		set(BuiltinName!"countTrailingZeros", Intrinsic.CountTrailingZeros);
152 		set(BuiltinName!"bswap", Intrinsic.ByteSwap);
153 	}
154 	
155 	void analyze(FunctionDeclaration fd, Function f) {
156 		import std.algorithm, std.array;
157 		auto params = fd.params.map!((p) {
158 			import d.semantic.type;
159 			auto t = TypeVisitor(pass).visit(p.type);
160 			
161 			Expression value;
162 			if (p.value) {
163 				import d.semantic.expression;
164 				value = ExpressionVisitor(pass).visit(p.value);
165 			}
166 			
167 			return new Variable(p.location, t, p.name, value);
168 		}).array();
169 		
170 		// Functions are always populated as resolution is order dependant
171 		f.step = Step.Populated;
172 		
173 		// Prepare statement visitor for return type.
174 		auto oldThisType = thisType;
175 		auto oldReturnType = returnType;
176 		auto oldManglePrefix = manglePrefix;
177 		scope(exit) {
178 			thisType = oldThisType;
179 			returnType = oldReturnType;
180 			manglePrefix = oldManglePrefix;
181 		}
182 		
183 		import std.conv;
184 		auto name = f.name.toString(context);
185 		manglePrefix = manglePrefix ~ to!string(name.length) ~ name;
186 		
187 		auto fbody = fd.fbody;
188 		bool isAuto = false;
189 		
190 		import source.name;
191 		immutable isCtor = f.name == BuiltinName!"__ctor";
192 		immutable isDtor = f.name == BuiltinName!"__dtor";
193 		
194 		// Make sure we take the type qualifier into account
195 		if (f.hasThis) {
196 			// XXX: Maybe we should offer a way to requalify ParamType.
197 			thisType = thisType.getType()
198 				.qualify(fd.storageClass.qualifier)
199 				.getParamType(oldThisType.paramKind);
200 		} else {
201 			assert(
202 				fd.storageClass.qualifier == TypeQualifier.Mutable,
203 				"Unexpected qualifier for a function without this",
204 			);
205 		}
206 		
207 		void buildType() {
208 			f.type = FunctionType(
209 				f.linkage,
210 				pass.returnType,
211 				params.map!(p => p.paramType).array(),
212 				fd.isVariadic,
213 			);
214 			
215 			assert(
216 				!isCtor || !isDtor || f.linkage == Linkage.D,
217 				"Only D linkage is supported for ctors and dtors",
218 			);
219 			
220 			switch (f.linkage) with(Linkage) {
221 				case D:
222 					import d.semantic.mangler;
223 					auto mangle = TypeMangler(pass).visit(f.type);
224 					mangle = f.hasThis ? mangle : ("FM" ~ mangle[1 .. $]);
225 					f.mangle = pass.context
226 						.getName("_D" ~ pass.manglePrefix ~ mangle);
227 					break;
228 				
229 				case C:
230 					f.mangle = f.name;
231 					break;
232 				
233 				default:
234 					import std.conv;
235 					assert(
236 						0,
237 						"Linkage " ~ to!string(f.linkage) ~ " is not supported",
238 					);
239 			}
240 			
241 			f.step = Step.Signed;
242 		}
243 		
244 		if (isCtor || isDtor) {
245 			assert(f.hasThis, "Constructor must have a this pointer");
246 			
247 			// However, we don't want usual hasThis behavior to kick in
248 			// as constructor are kind of magic.
249 			f.hasThis = false;
250 			
251 			returnType = Type.get(BuiltinType.Void)
252 				.getParamType(ParamKind.Regular);
253 			
254 			auto xtorType = thisType;
255 			
256 			// For small struct, we construct by value.
257 			if (isCtor && xtorType.kind == TypeKind.Struct) {
258 				auto s = xtorType.getType().dstruct;
259 				scheduler.require(s, Step.Signed);
260 				
261 				if (s.isSmall) {
262 					xtorType = xtorType.getParamType(ParamKind.Regular);
263 					returnType = xtorType;
264 					
265 					if (fbody) {
266 						import d.ast.statement;
267 						fbody = new BlockStatement(fbody.location, [
268 							fbody,
269 							new ReturnStatement(
270 								f.location,
271 								new ThisExpression(f.location),
272 							),
273 						]);
274 					}
275 				}
276 			}
277 			
278 			auto thisParameter = new Variable(
279 				f.location,
280 				xtorType,
281 				BuiltinName!"this",
282 			);
283 			
284 			params = thisParameter ~ params;
285 			
286 			// If we have a dtor body, we need to tweak it.
287 			if (isDtor && fbody) {
288 				auto a = xtorType.getType().getCanonical().aggregate;
289 				scheduler.require(a, Step.Signed);
290 				
291 				import d.ast.statement;
292 				Statement[] fieldDtors;
293 				
294 				import std.algorithm;
295 				auto fields = a.members
296 					.map!(m => cast(Field) m)
297 					.filter!(f => f !is null);
298 				
299 				foreach(field; fields) {
300 					auto t = field.type.getCanonical();
301 					if (t.kind != TypeKind.Struct) {
302 						continue;
303 					}
304 					
305 					auto s = t.dstruct;
306 					scheduler.require(s, Step.Signed);
307 					if (s.isPod) {
308 						continue;
309 					}
310 					
311 					import d.ast.expression;
312 					auto fieldDtor = new IdentifierDotIdentifier(
313 						fbody.location,
314 						BuiltinName!"__dtor",
315 						new ExpressionDotIdentifier(
316 							fbody.location,
317 							field.name,
318 							new ThisExpression(fbody.location),
319 						),
320 					);
321 					
322 					fieldDtors ~= new ScopeStatement(
323 						f.location,
324 						ScopeKind.Exit,
325 						new ExpressionStatement(
326 							new IdentifierCallExpression(
327 								fbody.location,
328 								fieldDtor,
329 								[],
330 							),
331 						),
332 					);
333 				}
334 				
335 				// Ok, we have fields to destroy, let's do it !
336 				if (fieldDtors.length > 0) {
337 					import std.algorithm;
338 					foreach (i; 0 .. fieldDtors.length / 2) {
339 						swap(fieldDtors[i], fieldDtors[$ - i - 1]);
340 					}
341 					
342 					fieldDtors ~= fbody;
343 					fbody = new BlockStatement(fbody.location, fieldDtors);
344 				}
345 			}
346 		} else {
347 			// If it has a this pointer, add it as parameter.
348 			if (f.hasThis) {
349 				assert(
350 					thisType.getType().isAggregate(),
351 					"thisType must be defined if funtion has a this pointer.",
352 				);
353 				
354 				auto thisParameter = new Variable(
355 					f.location,
356 					thisType,
357 					BuiltinName!"this",
358 				);
359 				
360 				params = thisParameter ~ params;
361 			}
362 			
363 			isAuto = fd.returnType.getType().isAuto;
364 			
365 			import d.semantic.type;
366 			returnType = isAuto
367 				? Type.get(BuiltinType.None).getParamType(ParamKind.Regular)
368 				: TypeVisitor(pass).visit(fd.returnType);
369 		}
370 		
371 		// Add this as a parameter, but not context.
372 		// Why ? Because bullshit !
373 		f.params = params;
374 		
375 		// If this is a closure, we add the context parameter.
376 		if (f.hasContext) {
377 			assert(
378 				ctxSym,
379 				"ctxSym must be defined if function has a context pointer."
380 			);
381 			
382 			import source.name;
383 			auto contextParameter = new Variable(
384 				f.location,
385 				Type.getContextType(ctxSym).getParamType(ParamKind.Ref),
386 				BuiltinName!"__ctx",
387 			);
388 			
389 			params = contextParameter ~ params;
390 		}
391 		
392 		if (!isAuto) {
393 			buildType();
394 		}
395 		
396 		if (fbody) {
397 			auto oldCtxSym = ctxSym;
398 			scope(exit) ctxSym = oldCtxSym;
399 			
400 			ctxSym = f;
401 			
402 			// Register parameters.
403 			foreach(p; params) {
404 				p.mangle = p.name;
405 				p.step = Step.Processed;
406 				
407 				if (!p.name.isEmpty()) {
408 					f.addSymbol(p);
409 				}
410 			}
411 			
412 			// And flatten.
413 			import d.semantic.statement;
414 			StatementVisitor(pass).getBody(f, fbody);
415 			
416 			import d.semantic.flow;
417 			f.closure = FlowAnalyzer(pass, f).getClosure();
418 		}
419 		
420 		if (isAuto) {
421 			// If nothing has been set, the function returns void.
422 			auto t = returnType.getType();
423 			if (t.kind == TypeKind.Builtin && t.builtin == BuiltinType.None) {
424 				returnType = Type.get(BuiltinType.Void)
425 					.getParamType(returnType.paramKind);
426 			}
427 			
428 			buildType();
429 		}
430 		
431 		assert(f.fbody || !isAuto, "Auto functions must have a body");
432 		f.step = Step.Processed;
433 	}
434 	
435 	void analyze(FunctionDeclaration d, Method m) {
436 		analyze(d, cast(Function) m);
437 	}
438 	
439 	private auto getValue(VariableDeclaration d) {
440 		auto stc = d.storageClass;
441 		
442 		if (d.type.isAuto) {
443 			// XXX: remove selective import when dmd is sane.
444 			import d.semantic.expression : ExpressionVisitor;
445 			return ExpressionVisitor(pass).visit(d.value);
446 		}
447 		
448 		import d.semantic.type : TypeVisitor;
449 		auto type = TypeVisitor(pass).withStorageClass(stc).visit(d.type);
450 		if (auto vi = cast(AstVoidInitializer) d.value) {
451 			return new VoidInitializer(vi.location, type);
452 		}
453 		
454 		// XXX: remove selective import when dmd is sane.
455 		import d.semantic.expression : ExpressionVisitor;
456 		import d.semantic.defaultinitializer : InitBuilder;
457 		auto value = d.value
458 			? ExpressionVisitor(pass).visit(d.value)
459 			: InitBuilder(pass, d.location).visit(type);
460 		
461 		return buildImplicitCast(pass, d.location, type, value);
462 	}
463 	
464 	private void analyzeVarLike(V)(VariableDeclaration d, V v) {
465 		auto value = getValue(d);
466 		
467 		// We peel alias for auto variable as it can lead to
468 		// very confusing results, like a template parameter.
469 		v.type = d.type.isAuto
470 			? value.type.getCanonical()
471 			: value.type;
472 		
473 		assert(value);
474 		static if (is(typeof(v.value) : CompileTimeExpression)) {
475 			value = v.value = evaluate(value);
476 		} else {
477 			value = v.value = v.storage.isGlobal
478 				? evaluate(value)
479 				: value;
480 		}
481 		
482 		// XXX: Make sure type is at least signed.
483 		import d.semantic.sizeof;
484 		SizeofVisitor(pass).visit(value.type);
485 		
486 		v.mangle = v.name;
487 		static if(is(V : Variable)) {
488 			if (v.storage == Storage.Static) {
489 				assert(v.linkage == Linkage.D, "I mangle only D !");
490 				
491 				auto name = v.name.toString(context);
492 				
493 				import d.semantic.mangler;
494 				auto mangle = TypeMangler(pass).visit(v.type);
495 				
496 				import std.conv;
497 				mangle = "_D" ~ manglePrefix
498 					~ to!string(name.length) ~ name
499 					~ mangle;
500 				
501 				v.mangle = context.getName(mangle);
502 			}
503 		}
504 		
505 		v.step = Step.Processed;
506 	}
507 	
508 	void analyze(VariableDeclaration d, Variable v) {
509 		analyzeVarLike(d, v);
510 	}
511 	
512 	void analyze(VariableDeclaration d, Field f) {
513 		analyzeVarLike(d, f);
514 	}
515 	
516 	void analyze(IdentifierAliasDeclaration iad, SymbolAlias a) {
517 		import d.semantic.identifier;
518 		a.symbol = IdentifierResolver(pass)
519 			.resolve(iad.identifier)
520 			.apply!(function Symbol(identified) {
521 				alias T = typeof(identified);
522 				static if (is(T : Symbol)) {
523 					return identified;
524 				} else {
525 					assert(0, "Not implemented for "
526 						~ typeid(identified).toString());
527 				}
528 			})();
529 		
530 		process(a);
531 	}
532 	
533 	void process(SymbolAlias a) {
534 		assert(a.symbol, "SymbolAlias must alias to something");
535 		a.step = Step.Populated;
536 		
537 		scheduler.require(a.symbol, Step.Signed);
538 		a.hasContext = a.symbol.hasContext;
539 		a.hasThis = a.symbol.hasThis;
540 		a.mangle = a.symbol.mangle;
541 		a.step = Step.Processed;
542 	}
543 	
544 	void analyze(TypeAliasDeclaration d, TypeAlias a) {
545 		import d.semantic.type : TypeVisitor;
546 		a.type = TypeVisitor(pass).visit(d.type);
547 		
548 		// If it is a function or delegate type, we need to apply the linkage.
549 		if (a.type.kind == TypeKind.Function) {
550 			auto f = a.type.asFunctionType();
551 			a.type = f.withLinkage(a.linkage).getType(a.type.qualifier);
552 		}
553 		
554 		import d.semantic.mangler;
555 		a.mangle = context.getName(TypeMangler(pass).visit(a.type));
556 		
557 		a.step = Step.Processed;
558 	}
559 	
560 	void analyze(ValueAliasDeclaration d, ValueAlias a) {
561 		// XXX: remove selective import when dmd is sane.
562 		import d.semantic.expression : ExpressionVisitor;
563 		a.value = evaluate(ExpressionVisitor(pass).visit(d.value));
564 		
565 		import d.semantic.mangler;
566 		auto typeMangle = TypeMangler(pass).visit(a.value.type);
567 		auto valueMangle = ValueMangler(pass).visit(a.value);
568 		a.mangle = context.getName(typeMangle ~ valueMangle);
569 		
570 		a.step = Step.Processed;
571 	}
572 	
573 	void analyze(StructDeclaration d, Struct s) {
574 		auto oldManglePrefix = manglePrefix;
575 		auto oldThisType = thisType;
576 		
577 		scope(exit) {
578 			manglePrefix = oldManglePrefix;
579 			thisType = oldThisType;
580 		}
581 		
582 		auto type = Type.get(s);
583 		thisType = type.getParamType(ParamKind.Ref);
584 		
585 		// Update mangle prefix.
586 		import std.conv;
587 		auto name = s.name.toString(context);
588 		manglePrefix = manglePrefix ~ name.length.to!string() ~ name;
589 		
590 		assert(s.linkage == Linkage.D || s.linkage == Linkage.C);
591 		auto mangle = "S" ~ manglePrefix;
592 		s.mangle = context.getName(mangle);
593 		
594 		// XXX: d is hijacked without explicit import
595 		import source.name : BuiltinName;
596 		Field[] fields;
597 		if (s.hasContext) {
598 			auto ctxPtr = Type.getContextType(ctxSym).getPointer();
599 			auto ctx = new Field(
600 				s.location,
601 				0,
602 				ctxPtr,
603 				BuiltinName!"__ctx",
604 				new NullLiteral(s.location, ctxPtr),
605 			);
606 			
607 			ctx.step = Step.Processed;
608 			fields = [ctx];
609 		}
610 		
611 		auto members = DeclarationVisitor(pass).flatten(d.members, s);
612 		
613 		auto init = new Variable(d.location, type, BuiltinName!"init");
614 		init.storage = Storage.Static;
615 		init.step = Step.Signed;
616 		init.mangle = context.getName(
617 			"_D" ~ manglePrefix
618 				~ to!string("init".length) ~ "init"
619 				~ mangle,
620 		);
621 		
622 		s.addSymbol(init);
623 		s.step = Step.Populated;
624 		
625 		import std.algorithm, std.array;
626 		auto otherSymbols = members.filter!((m) {
627 			if (auto f = cast(Field) m) {
628 				fields ~= f;
629 				return false;
630 			}
631 			
632 			return true;
633 		}).array();
634 		
635 		scheduler.require(fields, Step.Signed);
636 		
637 		s.members ~= init;
638 		s.members ~= fields;
639 		
640 		scheduler.require(fields);
641 		
642 		init.step = Step.Processed;
643 		init.value = new CompileTimeTupleExpression(
644 			d.location,
645 			type,
646 			fields.map!(f => cast(CompileTimeExpression) f.value).array(),
647 		);
648 		
649 		// If the struct has no dtor and only pod fields, it is a pod.
650 		auto hasDtor = s.resolve(s.location, BuiltinName!"__dtor");
651 		auto hasPostblit = s.resolve(s.location, BuiltinName!"__postblit");
652 		
653 		bool hasIndirection = false;
654 		bool isPod = !hasDtor && !hasPostblit;
655 		foreach(f; fields) {
656 			auto t = f.type.getCanonical();
657 			if (t.kind == TypeKind.Struct) {
658 				isPod = isPod && t.dstruct.isPod;
659 			}
660 			
661 			hasIndirection = hasIndirection || t.hasIndirection;
662 		}
663 		
664 		s.hasIndirection = hasIndirection;
665 		s.isPod = isPod;
666 		
667 		if (!isPod) {
668 			// TODO: Create default ctor and dtor
669 		}
670 		
671 		s.step = Step.Signed;
672 		
673 		// Must be done once the struct is signed, but really is part
674 		// of the process to get it signed, so we do it immediatly.
675 		s.isSmall = (dataLayout.getSize(Type.get(s)) <= 32);
676 		
677 		scheduler.require(otherSymbols);
678 		s.members ~= otherSymbols;
679 		
680 		s.step = Step.Processed;
681 	}
682 	
683 	void analyze(UnionDeclaration d, Union u) {
684 		auto oldManglePrefix = manglePrefix;
685 		auto oldThisType = thisType;
686 		
687 		scope(exit) {
688 			manglePrefix = oldManglePrefix;
689 			thisType = oldThisType;
690 		}
691 		
692 		auto type = Type.get(u);
693 		thisType = type.getParamType(ParamKind.Ref);
694 		
695 		// Update mangle prefix.
696 		import std.conv;
697 		auto name = u.name.toString(context);
698 		manglePrefix = manglePrefix ~ name.length.to!string() ~ name;
699 		
700 		// XXX: For some reason dmd mangle the same way as structs ???
701 		assert(u.linkage == Linkage.D || u.linkage == Linkage.C);
702 		auto mangle = "S" ~ manglePrefix;
703 		u.mangle = context.getName(mangle);
704 		
705 		// XXX: d is hijacked without explicit import
706 		import source.name : BuiltinName;
707 		
708 		Field[] fields;
709 		if (u.hasContext) {
710 			auto ctxPtr = Type.getContextType(ctxSym).getPointer();
711 			auto ctx = new Field(
712 				u.location,
713 				0,
714 				ctxPtr,
715 				BuiltinName!"__ctx",
716 				new NullLiteral(u.location, ctxPtr),
717 			);
718 			
719 			ctx.step = Step.Processed;
720 			fields = [ctx];
721 		}
722 		
723 		auto members = DeclarationVisitor(pass).flatten(d.members, u);
724 		
725 		auto init = new Variable(u.location, type, BuiltinName!"init");
726 		init.storage = Storage.Static;
727 		init.step = Step.Signed;
728 		init.mangle = context.getName(
729 			"_D" ~ manglePrefix
730 				~ to!string("init".length) ~ "init"
731 				~ mangle,
732 		);
733 		
734 		u.addSymbol(init);
735 		u.step = Step.Populated;
736 		
737 		import std.algorithm, std.array;
738 		auto otherSymbols = members.filter!((m) {
739 			if (auto f = cast(Field) m) {
740 				fields ~= f;
741 				return false;
742 			}
743 			
744 			return true;
745 		}).array();
746 		
747 		scheduler.require(fields, Step.Signed);
748 		
749 		u.members ~= init;
750 		u.members ~= fields;
751 		
752 		scheduler.require(fields);
753 		
754 		init.value = new VoidInitializer(u.location, type);
755 		init.step = Step.Processed;
756 		
757 		import std.algorithm;
758 		u.hasIndirection = fields.any!(f => f.type.hasIndirection);
759 		
760 		u.step = Step.Signed;
761 		
762 		scheduler.require(otherSymbols);
763 		u.members ~= otherSymbols;
764 		
765 		u.step = Step.Processed;
766 	}
767 	
768 	void analyze(ClassDeclaration d, Class c) {
769 		auto oldManglePrefix = manglePrefix;
770 		auto oldThisType = thisType;
771 		
772 		scope(exit) {
773 			manglePrefix = oldManglePrefix;
774 			thisType = oldThisType;
775 		}
776 		
777 		thisType = Type.get(c).getParamType(ParamKind.Final);
778 		
779 		// Update mangle prefix.
780 		import std.conv;
781 		auto name = c.name.toString(context);
782 		manglePrefix = manglePrefix ~ name.length.to!string() ~ name;
783 		c.mangle = context.getName("C" ~ manglePrefix);
784 		
785 		Field[] baseFields;
786 		Method[] baseMethods;
787 		foreach(i; d.bases) {
788 			import d.semantic.identifier;
789 			c.base = IdentifierResolver(pass)
790 				.resolve(i)
791 				.apply!(function Class(identified) {
792 					static if (is(typeof(identified) : Symbol)) {
793 						if (auto c = cast(Class) identified) {
794 							return c;
795 						}
796 					}
797 					
798 					static if (is(typeof(identified.location))) {
799 						import source.exception;
800 						throw new CompileException(
801 							identified.location,
802 							typeid(identified).toString() ~ " is not a class.",
803 						);
804 					} else {
805 						// for typeof(null)
806 						assert(0);
807 					}
808 				})();
809 			
810 			break;
811 		}
812 		
813 		// If no inheritance is specified, inherit from object.
814 		if (!c.base) {
815 			c.base = pass.object.getObject();
816 		}
817 		
818 		uint fieldIndex = 0;
819 		uint methodIndex = 0;
820 		
821 		// object.Object, let's do some compiler magic.
822 		if (c is c.base) {
823 			auto vtblType = Type.get(BuiltinType.Void)
824 				.getPointer(TypeQualifier.Immutable);
825 			
826 			// XXX: d is hijacked without explicit import
827 			import source.name : BuiltinName;
828 
829 			// TODO: use defaultinit.
830 			auto vtbl = new Field(
831 				d.location,
832 				0,
833 				vtblType,
834 				BuiltinName!"__vtbl",
835 				null,
836 			);
837 			
838 			vtbl.step = Step.Processed;
839 			
840 			baseFields = [vtbl];
841 			
842 			fieldIndex = 1;
843 		} else {
844 			scheduler.require(c.base);
845 			
846 			fieldIndex = 0;
847 			foreach(m; c.base.members) {
848 				import std.algorithm;
849 				if (auto field = cast(Field) m) {
850 					baseFields ~= field;
851 					fieldIndex = max(fieldIndex, field.index);
852 					
853 					c.addSymbol(field);
854 				} else if (auto method = cast(Method) m) {
855 					baseMethods ~= method;
856 					methodIndex = max(methodIndex, method.index + 1);
857 					
858 					c.addOverloadableSymbol(method);
859 				}
860 			}
861 			
862 			fieldIndex++;
863 		}
864 		
865 		if (c.hasContext) {
866 			// XXX: check for duplicate.
867 			auto ctxPtr = Type.getContextType(ctxSym).getPointer();
868 
869 			import source.name;
870 			auto ctx = new Field(
871 				c.location,
872 				fieldIndex++,
873 				ctxPtr,
874 				BuiltinName!"__ctx",
875 				new NullLiteral(c.location, ctxPtr),
876 			);
877 			
878 			ctx.step = Step.Processed;
879 			baseFields ~= ctx;
880 		}
881 		
882 		auto members = DeclarationVisitor(pass)
883 			.flatten(d.members, c, fieldIndex, methodIndex);
884 		
885 		c.step = Step.Signed;
886 		
887 		uint overloadCount = 0;
888 		foreach(m; members) {
889 			if (auto method = cast(Method) m) {
890 				scheduler.require(method, Step.Signed);
891 				
892 				auto mt = method.type;
893 				auto rt = mt.returnType;
894 				auto ats = mt.parameters[1 .. $];
895 				
896 				CandidatesLoop: foreach(ref candidate; baseMethods) {
897 					if (!candidate || method.name != candidate.name) {
898 						continue;
899 					}
900 					
901 					auto ct = candidate.type;
902 					if (ct.isVariadic != mt.isVariadic) {
903 						continue;
904 					}
905 					
906 					auto crt = ct.returnType;
907 					auto cpts = ct.parameters[1 .. $];
908 					if (ats.length != cpts.length || rt.isRef != crt.isRef) {
909 						continue;
910 					}
911 					
912 					auto rk = implicitCastFrom(
913 						pass,
914 						rt.getType(),
915 						crt.getType(),
916 					);
917 					
918 					if (rk < CastKind.Exact) {
919 						continue;
920 					}
921 					
922 					import std.range;
923 					foreach(at, cpt; lockstep(ats, cpts)) {
924 						if (at.isRef != cpt.isRef) {
925 							continue CandidatesLoop;
926 						}
927 						
928 						auto pk = implicitCastFrom(
929 							pass,
930 							cpt.getType(),
931 							at.getType(),
932 						);
933 						
934 						if (pk < CastKind.Exact) {
935 							continue CandidatesLoop;
936 						}
937 					}
938 					
939 					if (method.index == -1) {
940 						method.index = candidate.index;
941 						
942 						// Remove candidate from scope.
943 						auto os = cast(OverloadSet) c
944 							.resolve(c.location, method.name);
945 						assert(os, "This must be an overload set");
946 						
947 						uint i = 0;
948 						while (os.set[i] !is candidate) {
949 							i++;
950 						}
951 						
952 						foreach(s; os.set[i + 1 .. $]) {
953 							os.set[i++] = s;
954 						}
955 						
956 						os.set = os.set[0 .. i];
957 						
958 						overloadCount++;
959 						candidate = null;
960 						break;
961 					} else {
962 						import source.exception;
963 						throw new CompileException(
964 							method.location,
965 							method.name.toString(context)
966 								~ " overrides a base class methode "
967 								~ "but is not marked override",
968 						);
969 					}
970 				}
971 				
972 				if (method.index == -1) {
973 					import source.exception;
974 					throw new CompileException(
975 						method.location,
976 						"Override not found for "
977 							~ method.name.toString(context),
978 					);
979 				}
980 			}
981 		}
982 		
983 		// Remove overlaoded base method.
984 		if (overloadCount) {
985 			uint i = 0;
986 			while(baseMethods[i] !is null) {
987 				i++;
988 			}
989 			
990 			foreach(baseMethod; baseMethods[i + 1 .. $]) {
991 				if (baseMethod) {
992 					baseMethods[i++] = baseMethod;
993 				}
994 			}
995 			
996 			baseMethods = baseMethods[0 .. i];
997 		}
998 		
999 		c.members = cast(Symbol[]) baseFields;
1000 		c.members ~= baseMethods;
1001 		scheduler.require(members);
1002 		c.members ~= members;
1003 		
1004 		c.step = Step.Processed;
1005 	}
1006 
1007 	void analyze(InterfaceDeclaration d, Interface i) {
1008 		auto oldManglePrefix = manglePrefix;
1009 		auto oldThisType = thisType;
1010 		
1011 		scope(exit) {
1012 			manglePrefix = oldManglePrefix;
1013 			thisType = oldThisType;
1014 		}
1015 		
1016 		thisType = Type.get(i).getParamType(ParamKind.Final);
1017 		
1018 		import std.conv;
1019 		auto name = i.name.toString(context);
1020 		manglePrefix = manglePrefix ~ name.length.to!string();
1021 		
1022 		i.mangle = context.getName("I" ~ manglePrefix);
1023 		
1024 		assert(
1025 			d.members.length == 0,
1026 			"Member support not implemented for interfaces yet"
1027 		);
1028 		
1029 		assert(
1030 			d.bases.length == 0,
1031 			"Interface inheritance not implemented yet"
1032 		);
1033 		
1034 		// TODO: lots of stuff to add
1035 		
1036 		i.step = Step.Processed;
1037 	}
1038 
1039 	void analyze(EnumDeclaration d, Enum e) in {
1040 		assert(e.name.isDefined, "anonymous enums must be flattened !");
1041 	} do {
1042 		auto oldManglePrefix = manglePrefix;
1043 		auto oldScope = currentScope;
1044 		
1045 		scope(exit) {
1046 			manglePrefix = oldManglePrefix;
1047 			currentScope = oldScope;
1048 		}
1049 		
1050 		currentScope = e;
1051 		
1052 		import d.semantic.type : TypeVisitor;
1053 		e.type = d.type.isAuto
1054 			? Type.get(BuiltinType.Int)
1055 			: TypeVisitor(pass).visit(d.type);
1056 		
1057 		auto type = Type.get(e);
1058 		
1059 		if (e.type.kind != TypeKind.Builtin) {
1060 			import source.exception;
1061 			throw new CompileException(
1062 				e.location,
1063 				"Unsupported enum type " ~ e.type.toString(context),
1064 			);
1065 		}
1066 		
1067 		auto bt = e.type.builtin;
1068 		if (!isIntegral(bt) && bt != BuiltinType.Bool) {
1069 			import source.exception;
1070 			throw new CompileException(
1071 				e.location,
1072 				"Unsupported enum type " ~ e.type.toString(context),
1073 			);
1074 		}
1075 		
1076 		import std.conv;
1077 		auto name = e.name.toString(context);
1078 		manglePrefix = manglePrefix ~ to!string(name.length) ~ name;
1079 		
1080 		assert(e.linkage == Linkage.D || e.linkage == Linkage.C);
1081 		e.mangle = context.getName("E" ~ manglePrefix);
1082 		
1083 		Variable previous;
1084 		Expression one;
1085 		foreach(vd; d.entries) {
1086 			auto location = vd.location;
1087 			auto v = new Variable(vd.location, type, vd.name);
1088 			v.storage = Storage.Enum;
1089 			
1090 			e.addSymbol(v);
1091 			e.entries ~= v;
1092 			
1093 			auto dv = vd.value;
1094 			if (dv is null) {
1095 				if (previous) {
1096 					if (!one) {
1097 						one = new IntegerLiteral(location, 1, bt);
1098 					}
1099 					
1100 					// XXX: consider using AstExpression and always
1101 					// follow th same path.
1102 					scheduler.require(previous, Step.Signed);
1103 					v.value = new BinaryExpression(
1104 						location,
1105 						type,
1106 						BinaryOp.Add,
1107 						new VariableExpression(location, previous),
1108 						one,
1109 					);
1110 				} else {
1111 					v.value = new IntegerLiteral(location, 0, bt);
1112 				}
1113 			}
1114 			
1115 			pass.scheduler.schedule(dv, v);
1116 			previous = v;
1117 		}
1118 		
1119 		e.step = Step.Signed;
1120 		
1121 		scheduler.require(e.entries);
1122 		e.step = Step.Processed;
1123 	}
1124 	
1125 	void analyze(AstExpression dv, Variable v) in {
1126 		assert(v.storage == Storage.Enum);
1127 		assert(v.type.kind == TypeKind.Enum);
1128 	} do {
1129 		auto e = v.type.denum;
1130 		
1131 		if (dv !is null) {
1132 			assert(v.value is null);
1133 			
1134 			import d.semantic.expression;
1135 			v.value = ExpressionVisitor(pass).visit(dv);
1136 		}
1137 		
1138 		assert(v.value);
1139 		v.step = Step.Signed;
1140 		
1141 		v.value = evaluate(v.value);
1142 		v.step = Step.Processed;
1143 	}
1144 	
1145 	void analyze(TemplateDeclaration d, Template t) {
1146 		// XXX: compute a proper mangling for templates.
1147 		import std.conv;
1148 		auto name = t.name.toString(context);
1149 		t.mangle = context
1150 			.getName(manglePrefix ~ name.length.to!string() ~ name);
1151 		
1152 		auto oldScope = currentScope;
1153 		auto oldInPattern = inPattern;
1154 		scope(exit) {
1155 			currentScope = oldScope;
1156 			inPattern = oldInPattern;
1157 		}
1158 		
1159 		currentScope = t;
1160 		inPattern = true;
1161 		
1162 		t.parameters.length = d.parameters.length;
1163 		
1164 		// Register parameter in the scope.
1165 		auto none = Type.get(BuiltinType.None);
1166 		foreach_reverse(i, p; d.parameters) {
1167 			if (auto atp = cast(AstTypeTemplateParameter) p) {
1168 				auto tp = new TypeTemplateParameter(
1169 					atp.location,
1170 					atp.name,
1171 					cast(uint) i,
1172 					none,
1173 					none,
1174 				);
1175 				
1176 				t.addSymbol(tp);
1177 				
1178 				import d.semantic.type : TypeVisitor;
1179 				tp.specialization = TypeVisitor(pass).visit(atp.specialization);
1180 				tp.defaultValue = TypeVisitor(pass).visit(atp.defaultValue);
1181 				
1182 				tp.step = Step.Signed;
1183 				t.parameters[i] = tp;
1184 			} else if (auto avp = cast(AstValueTemplateParameter) p) {
1185 				auto vp = new ValueTemplateParameter(
1186 					avp.location,
1187 					avp.name,
1188 					cast(uint) i,
1189 					none,
1190 					null,
1191 				);
1192 				
1193 				t.addSymbol(vp);
1194 				
1195 				import d.semantic.type : TypeVisitor;
1196 				vp.type = TypeVisitor(pass).visit(avp.type);
1197 				
1198 				if (avp.defaultValue !is null) {
1199 					import d.semantic.expression : ExpressionVisitor;
1200 					vp.defaultValue = ExpressionVisitor(pass)
1201 						.visit(avp.defaultValue);
1202 				}
1203 				
1204 				vp.step = Step.Signed;
1205 				t.parameters[i] = vp;
1206 			} else if (auto aap = cast(AstAliasTemplateParameter) p) {
1207 				auto ap = new AliasTemplateParameter(
1208 					aap.location,
1209 					aap.name,
1210 					cast(uint) i,
1211 				);
1212 				
1213 				t.addSymbol(ap);
1214 				
1215 				ap.step = Step.Signed;
1216 				t.parameters[i] = ap;
1217 			} else if (auto atap = cast(AstTypedAliasTemplateParameter) p) {
1218 				auto tap = new TypedAliasTemplateParameter(
1219 					atap.location,
1220 					atap.name,
1221 					cast(uint) i,
1222 					none,
1223 				);
1224 				
1225 				t.addSymbol(tap);
1226 				
1227 				import d.semantic.type : TypeVisitor;
1228 				tap.type = TypeVisitor(pass).visit(atap.type);
1229 				
1230 				tap.step = Step.Signed;
1231 				t.parameters[i] = tap;
1232 			} else {
1233 				assert(0, typeid(p).toString()
1234 						~ " template parameters are not supported.");
1235 			}
1236 		}
1237 		
1238 		// TODO: support multiple IFTI.
1239 		foreach(m; t.members) {
1240 			if (auto fun = cast(FunctionDeclaration) m) {
1241 				if (fun.name != t.name) {
1242 					continue;
1243 				}
1244 				
1245 				import d.semantic.type, std.algorithm, std.array;
1246 				t.ifti = fun.params
1247 					.map!(p => TypeVisitor(pass).visit(p.type).getType())
1248 					.array();
1249 				
1250 				break;
1251 			}
1252 		}
1253 		
1254 		t.step = Step.Processed;
1255 	}
1256 	
1257 	void analyze(Template t, TemplateInstance i) {
1258 		auto oldManglePrefix = manglePrefix;
1259 		auto oldCtxSym = ctxSym;
1260 		
1261 		scope(exit) {
1262 			manglePrefix = oldManglePrefix;
1263 			ctxSym = oldCtxSym;
1264 		}
1265 		
1266 		ctxSym = null;
1267 		if (t.hasThis) {
1268 			i.hasThis = true;
1269 			i.storage = Storage.Local;
1270 			
1271 			// Try to recover the template type.
1272 			// XXX: There should be a way to keep it around.
1273 			auto cs = t.getParentScope();
1274 			while(true) {
1275 				auto o = cast(Object) cs;
1276 				if (auto s = cast(Struct) o) {
1277 					thisType = Type.get(s).getParamType(ParamKind.Ref);
1278 					break;
1279 				}
1280 				
1281 				if (auto c = cast(Class) o) {
1282 					thisType = Type.get(c).getParamType(ParamKind.Final);
1283 					break;
1284 				}
1285 				
1286 				if (auto u = cast(Union) o) {
1287 					thisType = Type.get(u).getParamType(ParamKind.Ref);
1288 					break;
1289 				}
1290 				
1291 				if (auto iface = cast(Interface) o) {
1292 					thisType = Type.get(iface).getParamType(ParamKind.Final);
1293 					break;
1294 				}
1295 				
1296 				cs = cs.getParentScope();
1297 			}
1298 		}
1299 		
1300 		manglePrefix = i.mangle.toString(context);
1301 		
1302 		// Prefilled members are template arguments.
1303 		foreach(a; i.args) {
1304 			if (a.tag != TemplateArgument.Tag.Symbol) {
1305 				continue;
1306 			}
1307 			
1308 			auto s = a.get!(TemplateArgument.Tag.Symbol);
1309 			if (!s.hasContext) {
1310 				continue;
1311 			}
1312 			
1313 			assert(
1314 				!i.hasContext,
1315 				"template can only have one context"
1316 			);
1317 			
1318 			import d.semantic.closure;
1319 			ctxSym = ContextFinder(pass).visit(s);
1320 			
1321 			i.hasContext = true;
1322 			i.storage = Storage.Local;
1323 		}
1324 		
1325 		import d.semantic.declaration;
1326 		i.members = DeclarationVisitor(pass).flatten(t.members, i);
1327 		i.step = Step.Signed;
1328 		
1329 		scheduler.require(i.members);
1330 		i.step = Step.Processed;
1331 	}
1332 	
1333 	void analyze(UnittestDeclaration ud, Function f) {
1334 		// Functions are always populated as resolution is order dependant.
1335 		f.step = Step.Populated;
1336 		
1337 		// Prepare statement visitor for return type.
1338 		auto oldReturnType = returnType;
1339 		auto oldManglePrefix = manglePrefix;
1340 		auto oldCtxSym = ctxSym;
1341 		scope(exit) {
1342 			returnType = oldReturnType;
1343 			manglePrefix = oldManglePrefix;
1344 			ctxSym = oldCtxSym;
1345 		}
1346 		
1347 		returnType = Type.get(BuiltinType.Void)
1348 			.getParamType(ParamKind.Regular);
1349 		
1350 		f.type = FunctionType(Linkage.D, returnType, [], false);
1351 		
1352 		string name;
1353 		
1354 		import source.name;
1355 		if (f.name == BuiltinName!"") {
1356 			// FIXME: can still collide with mixins,
1357 			// but that should rare enough for now.
1358 			auto offset = f.location.getFullLocation(context).getStartOffset();
1359 			
1360 			import std.conv;
1361 			name = "__unittest" ~ offset.to!string();
1362 			f.name = context.getName(name);
1363 		} else {
1364 			name = "__unittest." ~ f.name.toString(context);
1365 		}
1366 		
1367 		import std.conv;
1368 		manglePrefix = manglePrefix ~ to!string(name.length) ~ name;
1369 		f.mangle = context.getName("_D" ~ manglePrefix);
1370 		
1371 		// Typed and mangled, ready to go !
1372 		f.step = Step.Signed;
1373 		
1374 		// Now generate the body.
1375 		ctxSym = f;
1376 		
1377 		import d.semantic.statement;
1378 		StatementVisitor(pass).getBody(f, ud.fbody);
1379 		
1380 		import d.semantic.flow;
1381 		f.closure = FlowAnalyzer(pass, f).getClosure();
1382 		
1383 		f.step = Step.Processed;
1384 		
1385 		// Register the test at the module level.
1386 		// XXX: This may not be the right module when instanciating templates.
1387 		currentScope.getModule().tests ~= f;
1388 	}
1389 }