1 /** 
2  * Copyright: Enalye
3  * License: Zlib
4  * Authors: Enalye
5  */
6 module grimoire.compiler.parser;
7 
8 import std.stdio;
9 import std..string;
10 import std.array;
11 import std.conv;
12 import std.math;
13 import std.file;
14 import std.meta;
15 
16 import grimoire.runtime;
17 import grimoire.assembly;
18 import grimoire.compiler.util;
19 import grimoire.compiler.lexer;
20 import grimoire.compiler.mangle;
21 import grimoire.compiler.type;
22 import grimoire.compiler.primitive;
23 import grimoire.compiler.data;
24 import grimoire.compiler.pretty;
25 import grimoire.compiler.error;
26 
27 /**
28 Analyses the syntax and produce the data for the VM
29 The parser analyses the lexemes generated by the lexer and produce machine code.
30 */
31 final class GrParser {
32     package {
33         GrInt[] iconsts;
34         GrFloat[] fconsts;
35         GrString[] sconsts;
36 
37         uint scopeLevel;
38 
39         GrVariable[] globalVariables;
40         GrFunction[] instanciatedFunctions, functionsQueue, functions, events;
41         GrFunction[] anonymousFunctions;
42         GrTemplateFunction[] templatedFunctions;
43 
44         uint current;
45         GrFunction currentFunction;
46         GrFunction[] functionStack;
47         GrFunctionCall[] functionCalls;
48 
49         uint[][] breaksJumps;
50         uint[][] continuesJumps;
51         uint[] continuesDestinations;
52 
53         GrLexeme[] lexemes;
54 
55         bool isTypeChecking;
56 
57         /// Number of int based global variables declared.
58         uint iglobalsCount, /// Number of float based global variables declared.
59             fglobalsCount, /// Number of string based global variables declared.
60             sglobalsCount, /// Number of ptr based global variables declared.
61             oglobalsCount;
62     }
63 
64     private {
65         GrData _data;
66         bool _isAssignationOptimizable;
67         int _options;
68     }
69 
70     /// Reset to the start of the sequence.
71     private void reset() {
72         current = 0u;
73     }
74 
75     /// Advance to the next lexeme.
76     private void advance() {
77         if (current < lexemes.length)
78             current++;
79     }
80 
81     /// Return to the last lexeme.
82     private void goBack() {
83         if (current > 0u)
84             current--;
85     }
86 
87     /// Check for the end the sequence, then advance to the next lexeme.
88     private bool checkAdvance() {
89         if (isEnd())
90             return false;
91 
92         advance();
93         return true;
94     }
95 
96     /// Start of a block with `{`
97     private void openBlock() {
98         scopeLevel++;
99         if (currentFunction)
100             currentFunction.openScope();
101     }
102 
103     /// End of a block with '}'
104     private void closeBlock() {
105         scopeLevel--;
106         if (currentFunction)
107             currentFunction.closeScope();
108     }
109 
110     /// Check for the end of the sequence.
111     private bool isEnd(int offset = 0) {
112         return (current + offset) >= cast(uint) lexemes.length;
113     }
114 
115     private void set(uint position_) {
116         current = position_;
117         if (current < 0 || current >= cast(uint) lexemes.length) {
118             current = 0;
119         }
120     }
121 
122     /// Return the lexeme at the current position.
123     private GrLexeme get(int offset = 0) {
124         const uint position = current + offset;
125         if (position < 0 || position >= cast(uint) lexemes.length) {
126             logError("reached the end of the file", "unexpected end of file");
127         }
128         return lexemes[position];
129     }
130 
131     /// Register an integral value and returns its id.
132     private uint registerIntConstant(GrInt value) {
133         foreach (size_t index, GrInt iconst; iconsts) {
134             if (iconst == value)
135                 return cast(uint) index;
136         }
137         iconsts ~= value;
138         return cast(uint) iconsts.length - 1;
139     }
140 
141     /// Register an floating point value and returns its id.
142     private uint registerFloatConstant(GrFloat value) {
143         foreach (size_t index, GrFloat fconst; fconsts) {
144             if (fconst == value)
145                 return cast(uint) index;
146         }
147         fconsts ~= value;
148         return cast(uint) fconsts.length - 1;
149     }
150 
151     /// Register an string value and returns its id.
152     private uint registerStringConstant(GrString value) {
153         foreach (size_t index, GrString sconst; sconsts) {
154             if (sconst == value)
155                 return cast(uint) index;
156         }
157         sconsts ~= value;
158         return cast(uint) sconsts.length - 1;
159     }
160 
161     /// Register a special local variable, used for iterators, etc.
162     private GrVariable registerSpecialVariable(string name, GrType type) {
163         name = "~" ~ name;
164         GrVariable specialVariable = registerLocalVariable(name, type);
165         specialVariable.isAuto = false;
166         specialVariable.isInitialized = true; //We shortcut this check
167         return specialVariable;
168     }
169 
170     /// Register a global variable
171     private GrVariable registerGlobalVariable(string name, GrType type, bool isAuto, bool isPublic) {
172         //Check if declared globally.
173         assertNoGlobalDeclaration(name, get().fileId, isPublic);
174 
175         GrVariable variable = new GrVariable;
176         variable.isAuto = isAuto;
177         variable.isGlobal = true;
178         variable.isInitialized = false;
179         variable.type = type;
180         variable.name = name;
181         variable.isPublic = isPublic;
182         variable.fileId = get().fileId;
183         variable.lexPosition = current;
184         if (!isAuto)
185             setVariableRegister(variable);
186         globalVariables ~= variable;
187 
188         return variable;
189     }
190 
191     private GrVariable getGlobalVariable(string name, uint fileId, bool isPublic = false) {
192         foreach (GrVariable var; globalVariables) {
193             if (var.name == name && (var.fileId == fileId || var.isPublic || isPublic))
194                 return var;
195         }
196         return null;
197     }
198 
199     private void assertNoGlobalDeclaration(string name, uint fileId, bool isPublic) {
200         GrVariable var;
201         GrFunction func;
202         if ((var = getGlobalVariable(name, fileId, isPublic)) !is null)
203             logError("the name `" ~ name ~ "` is defined multiple times", "`" ~ name ~ "` is redefined here",
204                     "", 0, "previous definition of `" ~ name ~ "`", var.lexPosition);
205         if (_data.isPrimitiveDeclared(name))
206             logError("the name `" ~ name ~ "` is defined multiple times",
207                     "`" ~ name ~ "` is already defined as a primitive");
208         if ((func = getFunction(name, fileId, isPublic)) !is null)
209             logError("the name `" ~ name ~ "` is defined multiple times", "`" ~ name ~ "` is redefined here",
210                     "", 0, "previous definition of `" ~ name ~ "`", func.lexPosition);
211         if ((func = getEvent(name)) !is null)
212             logError("the name `" ~ name ~ "` is defined multiple times", "`" ~ name ~ "` is redefined here",
213                     "", 0, "previous definition of `" ~ name ~ "`", func.lexPosition);
214     }
215 
216     private void setVariableRegister(GrVariable variable) {
217         final switch (variable.type.baseType) with (GrBaseType) {
218         case int_:
219         case bool_:
220         case function_:
221         case task:
222         case enum_:
223             if (variable.isGlobal) {
224                 variable.register = iglobalsCount;
225                 iglobalsCount++;
226             }
227             else {
228                 if (currentFunction.iregisterAvailables.length) {
229                     variable.register = currentFunction.iregisterAvailables[$ - 1];
230                     currentFunction.iregisterAvailables.length--;
231                 }
232                 else {
233                     variable.register = currentFunction.ilocalsCount;
234                     currentFunction.ilocalsCount++;
235                 }
236             }
237             break;
238         case float_:
239             if (variable.isGlobal) {
240                 variable.register = fglobalsCount;
241                 fglobalsCount++;
242             }
243             else {
244                 if (currentFunction.fregisterAvailables.length) {
245                     variable.register = currentFunction.fregisterAvailables[$ - 1];
246                     currentFunction.fregisterAvailables.length--;
247                 }
248                 else {
249                     variable.register = currentFunction.flocalsCount;
250                     currentFunction.flocalsCount++;
251                 }
252             }
253             break;
254         case string_:
255             if (variable.isGlobal) {
256                 variable.register = sglobalsCount;
257                 sglobalsCount++;
258             }
259             else {
260                 if (currentFunction.sregisterAvailables.length) {
261                     variable.register = currentFunction.sregisterAvailables[$ - 1];
262                     currentFunction.sregisterAvailables.length--;
263                 }
264                 else {
265                     variable.register = currentFunction.slocalsCount;
266                     currentFunction.slocalsCount++;
267                 }
268             }
269             break;
270         case array_:
271         case class_:
272         case foreign:
273         case chan:
274             if (variable.isGlobal) {
275                 variable.register = oglobalsCount;
276                 oglobalsCount++;
277             }
278             else {
279                 if (currentFunction.oregisterAvailables.length) {
280                     variable.register = currentFunction.oregisterAvailables[$ - 1];
281                     currentFunction.oregisterAvailables.length--;
282                 }
283                 else {
284                     variable.register = currentFunction.olocalsCount;
285                     currentFunction.olocalsCount++;
286                 }
287             }
288             break;
289         case internalTuple:
290         case reference:
291         case null_:
292         case void_:
293             logError("can't define a variable of type " ~ grGetPrettyType(variable.type),
294                     "invalid type");
295             break;
296         }
297     }
298 
299     /// Register a local variable
300     private GrVariable registerLocalVariable(string name, GrType type) {
301         //Check if declared globally
302         assertNoGlobalDeclaration(name, get().fileId, false);
303 
304         GrVariable variable = new GrVariable;
305         variable.isGlobal = false;
306         variable.type = type;
307         variable.name = name;
308         variable.fileId = get().fileId;
309         variable.lexPosition = current;
310 
311         currentFunction.setLocal(variable);
312         if (variable.type.baseType != GrBaseType.void_)
313             setVariableRegister(variable);
314 
315         return variable;
316     }
317 
318     private void beginGlobalScope() {
319         GrFunction globalScope = getFunction("@global", 0);
320         if (globalScope) {
321             functionStack ~= currentFunction;
322             currentFunction = globalScope;
323         }
324         else {
325             GrFunction func = new GrFunction;
326             func.name = "@global";
327             func.mangledName = func.name;
328             func.isTask = false;
329             func.inSignature = [];
330             func.outSignature = [];
331             func.isPublic = true;
332             func.fileId = 0;
333             func.lexPosition = 0;
334             functions ~= func;
335             functionStack ~= currentFunction;
336             currentFunction = func;
337         }
338     }
339 
340     private void endGlobalScope() {
341         if (!functionStack.length)
342             throw new Exception("global scope mismatch");
343 
344         currentFunction = functionStack[$ - 1];
345         functionStack.length--;
346     }
347 
348     private void beginFunction(string name, uint fileId, GrType[] signature, bool isEvent = false) {
349         const string mangledName = grMangleComposite(name, signature);
350 
351         GrFunction func;
352         if (isEvent)
353             func = getEvent(mangledName);
354         else
355             func = getFunction(mangledName, fileId);
356 
357         if (func is null)
358             logError("`" ~ name ~ "` is not defined", "unknown function");
359 
360         functionStack ~= currentFunction;
361         currentFunction = func;
362     }
363 
364     private void preBeginFunction(string name, uint fileId, GrType[] signature,
365             string[] inputVariables, bool isTask, GrType[] outSignature = [],
366             bool isAnonymous = false, bool isEvent = false, bool isPublic = false) {
367         GrFunction func = new GrFunction;
368         func.isTask = isTask;
369         func.inputVariables = inputVariables;
370         func.inSignature = signature;
371         func.outSignature = outSignature;
372         func.fileId = fileId;
373 
374         if (isAnonymous) {
375             //func.index = cast(uint) anonymousFunctions.length;
376             func.anonParent = currentFunction;
377             func.anonReference = cast(uint) currentFunction.instructions.length;
378             func.name = currentFunction.name ~ "@anon" ~ to!string(func.index);
379             func.mangledName = grMangleComposite(func.name, func.inSignature);
380             anonymousFunctions ~= func;
381             func.lexPosition = current;
382 
383             //Is replaced by the addr of the function later (see solveFunctionCalls).
384             addInstruction(GrOpcode.const_int, 0u);
385         }
386         else {
387             //func.index = cast(uint) functions.length;
388             func.name = name;
389             func.isPublic = isPublic;
390 
391             func.mangledName = grMangleComposite(name, signature);
392             assertNoGlobalDeclaration(func.mangledName, fileId, isPublic);
393 
394             if (name == "main")
395                 func.isMain = true;
396 
397             func.isEvent = isEvent;
398             func.lexPosition = current;
399             functionsQueue ~= func;
400         }
401 
402         functionStack ~= currentFunction;
403         currentFunction = func;
404         generateFunctionInputs();
405     }
406 
407     private void endFunction() {
408         int prependInstructionCount;
409         if (_options & GrOption.profile) {
410             prependInstructionCount++;
411             const uint index = registerStringConstant(grGetPrettyFunction(currentFunction));
412             addInstructionInFront(GrOpcode.debugProfileBegin, index);
413         }
414 
415         if (currentFunction.ilocalsCount > 0) {
416             addInstructionInFront(GrOpcode.localStack_int, currentFunction.ilocalsCount);
417             prependInstructionCount++;
418         }
419 
420         if (currentFunction.flocalsCount > 0) {
421             addInstructionInFront(GrOpcode.localStack_float, currentFunction.flocalsCount);
422             prependInstructionCount++;
423         }
424 
425         if (currentFunction.slocalsCount > 0) {
426             addInstructionInFront(GrOpcode.localStack_string, currentFunction.slocalsCount);
427             prependInstructionCount++;
428         }
429 
430         if (currentFunction.olocalsCount > 0) {
431             addInstructionInFront(GrOpcode.localStack_object, currentFunction.olocalsCount);
432             prependInstructionCount++;
433         }
434 
435         foreach (call; currentFunction.functionCalls)
436             call.position += prependInstructionCount;
437 
438         currentFunction.offset += prependInstructionCount;
439 
440         if (!functionStack.length)
441             throw new Exception("attempting to close a non-existing function");
442 
443         currentFunction = functionStack[$ - 1];
444         functionStack.length--;
445     }
446 
447     private void preEndFunction() {
448         if (!functionStack.length)
449             throw new Exception("attempting to close a non-existing function");
450         currentFunction = functionStack[$ - 1];
451         functionStack.length--;
452     }
453 
454     /// Generate opcodes to fetch the function or the task's parameters
455     void generateFunctionInputs() {
456         void fetchParameter(string name, GrType type) {
457             final switch (type.baseType) with (GrBaseType) {
458             case void_:
459             case null_:
460                 logError("can't use `" ~ grGetPrettyType(type) ~ "` as a parameter type",
461                         "invalid parameter type");
462                 break;
463             case int_:
464             case bool_:
465             case function_:
466             case task:
467             case enum_:
468                 currentFunction.nbIntegerParameters++;
469                 if (currentFunction.isTask)
470                     addInstruction(GrOpcode.globalPop_int, 0u);
471                 break;
472             case float_:
473                 currentFunction.nbFloatParameters++;
474                 if (currentFunction.isTask)
475                     addInstruction(GrOpcode.globalPop_float, 0u);
476                 break;
477             case string_:
478                 currentFunction.nbStringParameters++;
479                 if (currentFunction.isTask)
480                     addInstruction(GrOpcode.globalPop_string, 0u);
481                 break;
482             case class_:
483             case array_:
484             case foreign:
485             case chan:
486             case reference:
487                 currentFunction.nbObjectParameters++;
488                 if (currentFunction.isTask)
489                     addInstruction(GrOpcode.globalPop_object, 0u);
490                 break;
491             case internalTuple:
492                 throw new Exception("tuples are not allowed here");
493             }
494 
495             GrVariable newVar = new GrVariable;
496             newVar.type = type;
497             newVar.isInitialized = true;
498             newVar.isGlobal = false;
499             newVar.name = name;
500             newVar.fileId = get().fileId;
501             newVar.lexPosition = current;
502             currentFunction.setLocal(newVar);
503             setVariableRegister(newVar);
504             addSetInstruction(newVar, currentFunction.fileId);
505         }
506 
507         foreach_reverse (size_t i, inputVariable; currentFunction.inputVariables) {
508             fetchParameter(currentFunction.inputVariables[i], currentFunction.inSignature[i]);
509         }
510     }
511 
512     GrFunction getFunction(string mangledName, uint fileId = 0, bool isPublic = false) {
513         foreach (GrFunction func; functions) {
514             if (func.mangledName == mangledName && (func.fileId == fileId
515                     || func.isPublic || isPublic)) {
516                 return func;
517             }
518         }
519         return null;
520     }
521 
522     GrFunction getFunction(string name, GrType[] signature, uint fileId = 0, bool isPublic = false) {
523         const string mangledName = grMangleComposite(name, signature);
524         foreach (GrFunction func; functions) {
525             if (func.mangledName == mangledName && (func.fileId == fileId
526                     || func.isPublic || isPublic)) {
527                 return func;
528             }
529         }
530         foreach (GrFunction func; functions) {
531             if (func.name == name && (func.fileId == fileId || func.isPublic || isPublic)) {
532                 if (_data.isSignatureCompatible(signature, func.inSignature, fileId, isPublic))
533                     return func;
534             }
535         }
536         foreach (GrFunction func; functionsQueue) {
537             if (func.mangledName == mangledName && (func.fileId == fileId
538                     || func.isPublic || isPublic)) {
539                 return func;
540             }
541         }
542         foreach (GrFunction func; functionsQueue) {
543             if (func.name == name && (func.fileId == fileId || func.isPublic || isPublic)) {
544                 if (_data.isSignatureCompatible(signature, func.inSignature, fileId, isPublic))
545                     return func;
546             }
547         }
548         foreach (GrFunction func; instanciatedFunctions) {
549             if (func.mangledName == mangledName && (func.fileId == fileId
550                     || func.isPublic || isPublic)) {
551                 functionsQueue ~= func;
552 
553                 functionStack ~= currentFunction;
554                 currentFunction = func;
555                 generateFunctionInputs();
556                 currentFunction = functionStack[$ - 1];
557                 functionStack.length--;
558 
559                 return func;
560             }
561         }
562         foreach (GrFunction func; instanciatedFunctions) {
563             if (func.name == name && (func.fileId == fileId || func.isPublic || isPublic)) {
564                 if (_data.isSignatureCompatible(signature, func.inSignature, fileId, isPublic)) {
565                     functionsQueue ~= func;
566 
567                     functionStack ~= currentFunction;
568                     currentFunction = func;
569                     generateFunctionInputs();
570                     currentFunction = functionStack[$ - 1];
571                     functionStack.length--;
572 
573                     return func;
574                 }
575             }
576         }
577         return null;
578     }
579 
580     /// Remove a declared function
581     void removeFunction(string name) {
582         import std.algorithm : remove;
583 
584         for (int i; i < functions.length; ++i) {
585             if (functions[i].mangledName == name) {
586                 functions = remove(functions, i);
587                 return;
588             }
589         }
590     }
591 
592     private GrFunction getEvent(string name) {
593         foreach (GrFunction func; events) {
594             if (func.mangledName == name)
595                 return func;
596         }
597         return null;
598     }
599 
600     private GrFunction getAnonymousFunction(string name) {
601         foreach (GrFunction func; anonymousFunctions) {
602             if (func.mangledName == name)
603                 return func;
604         }
605         return null;
606     }
607 
608     GrFunction getAnonymousFunction(string name, GrType[] signature, uint fileId) {
609         foreach (GrFunction func; anonymousFunctions) {
610             if (func.mangledName == name)
611                 return func;
612         }
613         foreach (GrFunction func; anonymousFunctions) {
614             if (func.name == name) {
615                 if (_data.isSignatureCompatible(signature, func.inSignature, fileId))
616                     return func;
617             }
618         }
619         return null;
620     }
621 
622     /// Retrieve a declared variable
623     private GrVariable getVariable(string name, uint fileId) {
624         GrVariable globalVar = getGlobalVariable(name, fileId);
625         if (globalVar !is null)
626             return globalVar;
627 
628         GrVariable localVar = currentFunction.getLocal(name);
629         if (!localVar)
630             logError("`" ~ name ~ "` is not declared", "unknown variable", "", -1);
631         return localVar;
632     }
633 
634     private void addIntConstant(GrInt value) {
635         addInstruction(GrOpcode.const_int, registerIntConstant(value));
636     }
637 
638     private void addFloatConstant(GrFloat value) {
639         addInstruction(GrOpcode.const_float, registerFloatConstant(value));
640     }
641 
642     private void addBoolConstant(bool value) {
643         addInstruction(GrOpcode.const_bool, value);
644     }
645 
646     private void addStringConstant(GrString value) {
647         addInstruction(GrOpcode.const_string, registerStringConstant(value));
648     }
649 
650     private void addMetaConstant(GrString value) {
651         addInstruction(GrOpcode.const_meta, registerStringConstant(value));
652     }
653 
654     private void addInstruction(GrOpcode opcode, int value = 0, bool isSigned = false) {
655         if (currentFunction is null)
656             throw new Exception(
657                     "the expression is located outside of a function or task, which is forbidden");
658 
659         GrInstruction instruction;
660         instruction.opcode = opcode;
661         if (isSigned) {
662             if ((value >= 0x800000) || (-value >= 0x800000))
663                 throw new Exception("an opcode's signed value is exceeding limits");
664             instruction.value = value + 0x800000;
665         }
666         else
667             instruction.value = value;
668         currentFunction.instructions ~= instruction;
669 
670         if (_options & GrOption.symbols) {
671             generateInstructionSymbol();
672         }
673     }
674 
675     private void addInstructionInFront(GrOpcode opcode, int value = 0, bool isSigned = false) {
676         if (currentFunction is null)
677             throw new Exception(
678                     "the expression is located outside of a function or task, which is forbidden");
679 
680         GrInstruction instruction;
681         instruction.opcode = opcode;
682         if (isSigned) {
683             if ((value >= 0x800000) || (-value >= 0x800000))
684                 throw new Exception("an opcode's signed value is exceeding limits");
685             instruction.value = value + 0x800000;
686         }
687         else
688             instruction.value = value;
689         currentFunction.instructions = instruction ~ currentFunction.instructions;
690 
691         if (_options & GrOption.symbols) {
692             generateInstructionSymbol();
693         }
694     }
695 
696     private void generateInstructionSymbol() {
697         GrFunction.DebugPositionSymbol symbol;
698         int lexPos = (cast(int) current) - 2;
699         if (lexPos < 0) {
700             lexPos = 0;
701         }
702         if (lexPos >= cast(uint) lexemes.length) {
703             lexPos = cast(uint)((cast(int) lexemes.length) - 1);
704         }
705         GrLexeme lex = lexemes[lexPos];
706         symbol.line = lex.line + 1;
707         symbol.column = lex.column;
708         currentFunction.debugSymbol ~= symbol;
709     }
710 
711     private void setInstruction(GrOpcode opcode, uint index, int value = 0u, bool isSigned = false) {
712         if (currentFunction is null)
713             throw new Exception(
714                     "the expression is located outside of a function or task, which is forbidden");
715 
716         if (index >= currentFunction.instructions.length)
717             throw new Exception("an instruction's index is exeeding the function size");
718 
719         GrInstruction instruction;
720         instruction.opcode = opcode;
721         if (isSigned) {
722             if ((value >= 0x800000) || (-value >= 0x800000))
723                 throw new Exception("an opcode's signed value is exceeding limits");
724             instruction.value = value + 0x800000;
725         }
726         else
727             instruction.value = value;
728         currentFunction.instructions[index] = instruction;
729     }
730 
731     private bool isBinaryOperator(GrLexemeType lexType) {
732         if (lexType >= GrLexemeType.add && lexType <= GrLexemeType.xor)
733             return true;
734         else if (lexType == GrLexemeType.send)
735             return true;
736         else
737             return false;
738     }
739 
740     private bool isUnaryOperator(GrLexemeType lexType) {
741         if (lexType >= GrLexemeType.plus && lexType <= GrLexemeType.minus)
742             return true;
743         else if (lexType >= GrLexemeType.increment && lexType <= GrLexemeType.decrement)
744             return true;
745         else if (lexType == GrLexemeType.not)
746             return true;
747         else if (lexType == GrLexemeType.receive)
748             return true;
749         else
750             return false;
751     }
752 
753     private GrType addCustomBinaryOperator(GrLexemeType lexType, GrType leftType,
754             GrType rightType, uint fileId) {
755         string name = "@op_" ~ grGetPrettyLexemeType(lexType);
756         GrType[] signature = [leftType, rightType];
757 
758         //GrPrimitive check
759         const GrPrimitive primitive = _data.getPrimitive(name, signature);
760         if (primitive) {
761             addInstruction(GrOpcode.primitiveCall, primitive.index);
762             if (primitive.outSignature.length != 1uL) {
763                 const string argStr = to!string(primitive.outSignature.length) ~ (
764                         primitive.outSignature.length > 1 ? " return values" : " return value");
765                 logError("an operator must have only one return value",
766                         "expected 1 return value, found " ~ argStr);
767             }
768             return primitive.outSignature[0];
769         }
770 
771         //GrFunction check
772         GrFunction func = getFunction(name, signature, fileId);
773         if (func) {
774             auto outSignature = addFunctionCall(func, fileId);
775             if (outSignature.length != 1uL) {
776                 const string argStr = to!string(outSignature.length) ~ (outSignature.length > 1
777                         ? " return values" : " return value");
778                 logError("an operator must have only one return value",
779                         "expected 1 return value, found " ~ argStr);
780             }
781             return outSignature[0];
782         }
783 
784         return grVoid;
785     }
786 
787     private GrType addCustomUnaryOperator(GrLexemeType lexType, const GrType type, uint fileId) {
788         string name = "@op_" ~ grGetPrettyLexemeType(lexType);
789         GrType[] signature = [type];
790 
791         //GrPrimitive check
792         const GrPrimitive primitive = _data.getPrimitive(name, signature);
793         if (primitive) {
794             addInstruction(GrOpcode.primitiveCall, primitive.index);
795             if (primitive.outSignature.length != 1uL) {
796                 const string argStr = to!string(primitive.outSignature.length) ~ (
797                         primitive.outSignature.length > 1 ? " return values" : " return value");
798                 logError("an operator must have only one return value",
799                         "expected 1 return value, found " ~ argStr);
800             }
801             return primitive.outSignature[0];
802         }
803 
804         //GrFunction check
805         GrFunction func = getFunction(name, signature, fileId);
806         if (func) {
807             auto outSignature = addFunctionCall(func, fileId);
808             if (outSignature.length != 1uL) {
809                 const string argStr = to!string(outSignature.length) ~ (outSignature.length > 1
810                         ? " return values" : " return value");
811                 logError("an operator must have only one return value",
812                         "expected 1 return value, found " ~ argStr);
813             }
814             return outSignature[0];
815         }
816 
817         return grVoid;
818     }
819 
820     private GrType addBinaryOperator(GrLexemeType lexType, const GrType leftType,
821             const GrType rightType, uint fileId) {
822         if (leftType.baseType == GrBaseType.internalTuple
823                 || rightType.baseType == GrBaseType.internalTuple)
824             logError("can't use an operator on multiple values",
825                     "the expression yields multiple values");
826         GrType resultType = GrBaseType.void_;
827 
828         if (leftType.baseType == GrBaseType.enum_ && rightType.baseType == GrBaseType.enum_
829                 && leftType.mangledType == rightType.mangledType) {
830             resultType = addInternalOperator(lexType, leftType);
831         }
832         else if (leftType.baseType == GrBaseType.chan) {
833             GrType chanType = grUnmangle(leftType.mangledType);
834             convertType(rightType, chanType, fileId);
835             resultType = addInternalOperator(lexType, leftType);
836             if (resultType.baseType == GrBaseType.void_) {
837                 resultType = addCustomBinaryOperator(lexType, leftType, rightType, fileId);
838             }
839         }
840         else if (lexType == GrLexemeType.concatenate
841                 && leftType.baseType == GrBaseType.array_ && leftType != rightType) {
842             const GrType subType = grUnmangle(leftType.mangledType);
843             convertType(rightType, subType, fileId);
844             final switch (subType.baseType) with (GrBaseType) {
845             case int_:
846             case bool_:
847             case enum_:
848             case function_:
849             case task:
850                 addInstruction(GrOpcode.append_int);
851                 break;
852             case float_:
853                 addInstruction(GrOpcode.append_float);
854                 break;
855             case string_:
856                 addInstruction(GrOpcode.append_string);
857                 break;
858             case class_:
859             case array_:
860             case foreign:
861             case chan:
862                 addInstruction(GrOpcode.append_object);
863                 break;
864             case null_:
865             case void_:
866             case reference:
867             case internalTuple:
868                 break;
869             }
870             resultType = leftType;
871         }
872         else if (lexType == GrLexemeType.concatenate
873                 && rightType.baseType == GrBaseType.array_ && leftType != rightType) {
874             const GrType subType = grUnmangle(rightType.mangledType);
875             convertType(leftType, subType, fileId);
876             final switch (subType.baseType) with (GrBaseType) {
877             case int_:
878             case bool_:
879             case enum_:
880             case function_:
881             case task:
882                 addInstruction(GrOpcode.prepend_int);
883                 break;
884             case float_:
885                 addInstruction(GrOpcode.prepend_float);
886                 break;
887             case string_:
888                 addInstruction(GrOpcode.prepend_string);
889                 break;
890             case class_:
891             case array_:
892             case foreign:
893             case chan:
894                 addInstruction(GrOpcode.prepend_object);
895                 break;
896             case null_:
897             case void_:
898             case reference:
899             case internalTuple:
900                 break;
901             }
902             resultType = rightType;
903         }
904         else if (lexType == GrLexemeType.concatenate
905                 && leftType.baseType == GrBaseType.string_ && leftType != rightType) {
906             convertType(rightType, leftType, fileId);
907             resultType = addInternalOperator(lexType, leftType);
908         }
909         else if (lexType == GrLexemeType.concatenate
910                 && rightType.baseType == GrBaseType.string_ && leftType != rightType) {
911             convertType(leftType, rightType, fileId);
912             resultType = addInternalOperator(lexType, rightType, true);
913         }
914         else if (leftType.baseType == GrBaseType.int_ && rightType.baseType == GrBaseType.float_) {
915             // Special case, we need to convert int to float, then swap the 2 values when needed.
916             convertType(leftType, rightType, fileId);
917             resultType = addInternalOperator(lexType, rightType, true);
918         }
919         else if (leftType != rightType) {
920             //Check custom operator
921             resultType = addCustomBinaryOperator(lexType, leftType, rightType, fileId);
922 
923             //If there is no custom operator defined, we try to convert and then try again
924             if (resultType.baseType == GrBaseType.void_) {
925                 resultType = convertType(rightType, leftType, fileId, true);
926                 if (resultType.baseType != GrBaseType.void_) {
927                     resultType = addBinaryOperator(lexType, resultType, resultType, fileId);
928                 }
929             }
930         }
931         else {
932             resultType = addInternalOperator(lexType, leftType);
933             if (resultType.baseType == GrBaseType.void_) {
934                 resultType = addCustomBinaryOperator(lexType, leftType, rightType, fileId);
935             }
936         }
937         if (resultType.baseType == GrBaseType.void_)
938             logError("there is no `" ~ grGetPrettyLexemeType(
939                     lexType) ~ "` binary operator defined for `" ~ grGetPrettyType(
940                     leftType) ~ "` and `" ~ grGetPrettyType(rightType) ~ "`",
941                     "unknown operator", "", -1);
942         return resultType;
943     }
944 
945     private GrType addUnaryOperator(GrLexemeType lexType, const GrType type, uint fileId) {
946         if (type.baseType == GrBaseType.internalTuple)
947             logError("can't use an operator on multiple values",
948                     "the expression yields multiple values");
949         GrType resultType = GrBaseType.void_;
950 
951         resultType = addInternalOperator(lexType, type);
952         if (resultType.baseType == GrBaseType.void_) {
953             resultType = addCustomUnaryOperator(lexType, type, fileId);
954         }
955 
956         if (resultType.baseType == GrBaseType.void_)
957             logError("there is no `" ~ grGetPrettyLexemeType(
958                     lexType) ~ "` unary operator defined for `" ~ grGetPrettyType(type) ~ "`",
959                     "unknown operator");
960         return resultType;
961     }
962 
963     private GrType addOperator(GrLexemeType lexType, ref GrType[] typeStack, uint fileId) {
964         if (isBinaryOperator(lexType)) {
965             typeStack[$ - 2] = addBinaryOperator(lexType, typeStack[$ - 2],
966                     typeStack[$ - 1], fileId);
967             typeStack.length--;
968             return typeStack[$ - 1];
969         }
970         else if (isUnaryOperator(lexType)) {
971             typeStack[$ - 1] = addUnaryOperator(lexType, typeStack[$ - 1], fileId);
972             return typeStack[$ - 1];
973         }
974 
975         return GrType(GrBaseType.void_);
976     }
977 
978     private GrType addInternalOperator(GrLexemeType lexType, GrType varType, bool isSwapped = false) {
979         switch (varType.baseType) with (GrBaseType) {
980         case class_:
981         case foreign:
982             switch (lexType) with (GrLexemeType) {
983             case not:
984                 addInstruction(GrOpcode.isNonNull_object);
985                 addInstruction(GrOpcode.not_int);
986                 return GrType(GrBaseType.bool_);
987             default:
988                 break;
989             }
990             break;
991         case enum_:
992             switch (lexType) with (GrLexemeType) {
993             case equal:
994                 addInstruction(GrOpcode.equal_int);
995                 return GrType(GrBaseType.bool_);
996             case notEqual:
997                 addInstruction(GrOpcode.notEqual_int);
998                 return GrType(GrBaseType.bool_);
999             case greater:
1000                 addInstruction(GrOpcode.greater_int);
1001                 return GrType(GrBaseType.bool_);
1002             case greaterOrEqual:
1003                 addInstruction(GrOpcode.greaterOrEqual_int);
1004                 return GrType(GrBaseType.bool_);
1005             case lesser:
1006                 addInstruction(GrOpcode.lesser_int);
1007                 return GrType(GrBaseType.bool_);
1008             case lesserOrEqual:
1009                 addInstruction(GrOpcode.lesserOrEqual_int);
1010                 return GrType(GrBaseType.bool_);
1011             default:
1012                 break;
1013             }
1014             break;
1015         case bool_:
1016             switch (lexType) with (GrLexemeType) {
1017             case and:
1018                 addInstruction(GrOpcode.and_int);
1019                 return GrType(GrBaseType.bool_);
1020             case or:
1021                 addInstruction(GrOpcode.or_int);
1022                 return GrType(GrBaseType.bool_);
1023             case not:
1024                 addInstruction(GrOpcode.not_int);
1025                 return GrType(GrBaseType.bool_);
1026             default:
1027                 break;
1028             }
1029             break;
1030         case int_:
1031             switch (lexType) with (GrLexemeType) {
1032             case add:
1033                 addInstruction(GrOpcode.add_int);
1034                 return GrType(GrBaseType.int_);
1035             case substract:
1036                 addInstruction(GrOpcode.substract_int);
1037                 return GrType(GrBaseType.int_);
1038             case multiply:
1039                 addInstruction(GrOpcode.multiply_int);
1040                 return GrType(GrBaseType.int_);
1041             case divide:
1042                 addInstruction(GrOpcode.divide_int);
1043                 return GrType(GrBaseType.int_);
1044             case remainder:
1045                 addInstruction(GrOpcode.remainder_int);
1046                 return GrType(GrBaseType.int_);
1047             case minus:
1048                 addInstruction(GrOpcode.negative_int);
1049                 return GrType(GrBaseType.int_);
1050             case plus:
1051                 return GrType(GrBaseType.int_);
1052             case increment:
1053                 addInstruction(GrOpcode.increment_int);
1054                 return GrType(GrBaseType.int_);
1055             case decrement:
1056                 addInstruction(GrOpcode.decrement_int);
1057                 return GrType(GrBaseType.int_);
1058             case equal:
1059                 addInstruction(GrOpcode.equal_int);
1060                 return GrType(GrBaseType.bool_);
1061             case notEqual:
1062                 addInstruction(GrOpcode.notEqual_int);
1063                 return GrType(GrBaseType.bool_);
1064             case greater:
1065                 addInstruction(GrOpcode.greater_int);
1066                 return GrType(GrBaseType.bool_);
1067             case greaterOrEqual:
1068                 addInstruction(GrOpcode.greaterOrEqual_int);
1069                 return GrType(GrBaseType.bool_);
1070             case lesser:
1071                 addInstruction(GrOpcode.lesser_int);
1072                 return GrType(GrBaseType.bool_);
1073             case lesserOrEqual:
1074                 addInstruction(GrOpcode.lesserOrEqual_int);
1075                 return GrType(GrBaseType.bool_);
1076             case not:
1077                 addInstruction(GrOpcode.not_int);
1078                 return GrType(GrBaseType.bool_);
1079             default:
1080                 break;
1081             }
1082             break;
1083         case float_:
1084             switch (lexType) with (GrLexemeType) {
1085             case add:
1086                 addInstruction(GrOpcode.add_float);
1087                 return GrType(GrBaseType.float_);
1088             case substract:
1089                 if (isSwapped)
1090                     addInstruction(GrOpcode.swap_float);
1091                 addInstruction(GrOpcode.substract_float);
1092                 return GrType(GrBaseType.float_);
1093             case multiply:
1094                 addInstruction(GrOpcode.multiply_float);
1095                 return GrType(GrBaseType.float_);
1096             case divide:
1097                 if (isSwapped)
1098                     addInstruction(GrOpcode.swap_float);
1099                 addInstruction(GrOpcode.divide_float);
1100                 return GrType(GrBaseType.float_);
1101             case remainder:
1102                 if (isSwapped)
1103                     addInstruction(GrOpcode.swap_float);
1104                 addInstruction(GrOpcode.remainder_float);
1105                 return GrType(GrBaseType.float_);
1106             case minus:
1107                 addInstruction(GrOpcode.negative_float);
1108                 return GrType(GrBaseType.float_);
1109             case plus:
1110                 return GrType(GrBaseType.float_);
1111             case increment:
1112                 addInstruction(GrOpcode.increment_float);
1113                 return GrType(GrBaseType.float_);
1114             case decrement:
1115                 addInstruction(GrOpcode.decrement_float);
1116                 return GrType(GrBaseType.float_);
1117             case equal:
1118                 addInstruction(GrOpcode.equal_float);
1119                 return GrType(GrBaseType.bool_);
1120             case notEqual:
1121                 addInstruction(GrOpcode.notEqual_float);
1122                 return GrType(GrBaseType.bool_);
1123             case greater:
1124                 if (isSwapped)
1125                     addInstruction(GrOpcode.lesserOrEqual_float);
1126                 else
1127                     addInstruction(GrOpcode.greater_float);
1128                 return GrType(GrBaseType.bool_);
1129             case greaterOrEqual:
1130                 if (isSwapped)
1131                     addInstruction(GrOpcode.lesser_float);
1132                 else
1133                     addInstruction(GrOpcode.greaterOrEqual_float);
1134                 return GrType(GrBaseType.bool_);
1135             case lesser:
1136                 if (isSwapped)
1137                     addInstruction(GrOpcode.greaterOrEqual_float);
1138                 else
1139                     addInstruction(GrOpcode.lesser_float);
1140                 return GrType(GrBaseType.bool_);
1141             case lesserOrEqual:
1142                 if (isSwapped)
1143                     addInstruction(GrOpcode.greater_float);
1144                 else
1145                     addInstruction(GrOpcode.lesserOrEqual_float);
1146                 return GrType(GrBaseType.bool_);
1147             default:
1148                 break;
1149             }
1150             break;
1151         case string_:
1152             switch (lexType) with (GrLexemeType) {
1153             case concatenate:
1154                 if (isSwapped)
1155                     addInstruction(GrOpcode.swap_string);
1156                 addInstruction(GrOpcode.concatenate_string);
1157                 return GrType(GrBaseType.string_);
1158             case equal:
1159                 addInstruction(GrOpcode.equal_string);
1160                 return GrType(GrBaseType.bool_);
1161             case notEqual:
1162                 addInstruction(GrOpcode.notEqual_string);
1163                 return GrType(GrBaseType.bool_);
1164             default:
1165                 break;
1166             }
1167             break;
1168         case array_:
1169             switch (lexType) with (GrLexemeType) {
1170             case equal:
1171                 const GrType subType = grUnmangle(varType.mangledType);
1172                 final switch (subType.baseType) with (GrBaseType) {
1173                 case int_:
1174                 case bool_:
1175                 case enum_:
1176                 case function_:
1177                 case task:
1178                     addInstruction(GrOpcode.equal_intArray);
1179                     return grBool;
1180                 case float_:
1181                     addInstruction(GrOpcode.equal_floatArray);
1182                     return grBool;
1183                 case string_:
1184                     addInstruction(GrOpcode.equal_stringArray);
1185                     return grBool;
1186                 case null_:
1187                 case void_:
1188                 case reference:
1189                 case internalTuple:
1190                 case array_:
1191                 case class_:
1192                 case foreign:
1193                 case chan:
1194                     break;
1195                 }
1196                 break;
1197             case notEqual:
1198                 const GrType subType = grUnmangle(varType.mangledType);
1199                 final switch (subType.baseType) with (GrBaseType) {
1200                 case int_:
1201                 case bool_:
1202                 case enum_:
1203                 case function_:
1204                 case task:
1205                     addInstruction(GrOpcode.notEqual_intArray);
1206                     return grBool;
1207                 case float_:
1208                     addInstruction(GrOpcode.notEqual_floatArray);
1209                     return grBool;
1210                 case string_:
1211                     addInstruction(GrOpcode.notEqual_stringArray);
1212                     return grBool;
1213                 case null_:
1214                 case void_:
1215                 case reference:
1216                 case internalTuple:
1217                 case array_:
1218                 case class_:
1219                 case foreign:
1220                 case chan:
1221                     break;
1222                 }
1223                 break;
1224             case concatenate:
1225                 const GrType subType = grUnmangle(varType.mangledType);
1226                 final switch (subType.baseType) with (GrBaseType) {
1227                 case int_:
1228                 case bool_:
1229                 case enum_:
1230                 case function_:
1231                 case task:
1232                     addInstruction(GrOpcode.concatenate_intArray);
1233                     return varType;
1234                 case float_:
1235                     addInstruction(GrOpcode.concatenate_floatArray);
1236                     return varType;
1237                 case string_:
1238                     addInstruction(GrOpcode.concatenate_stringArray);
1239                     return varType;
1240                 case class_:
1241                 case array_:
1242                 case foreign:
1243                 case chan:
1244                     addInstruction(GrOpcode.concatenate_objectArray);
1245                     return varType;
1246                 case null_:
1247                 case void_:
1248                 case reference:
1249                 case internalTuple:
1250                     break;
1251                 }
1252                 break;
1253             default:
1254                 break;
1255             }
1256             break;
1257         case chan:
1258             switch (lexType) with (GrLexemeType) {
1259             case send:
1260                 GrType chanType = grUnmangle(varType.mangledType);
1261                 final switch (chanType.baseType) with (GrBaseType) {
1262                 case int_:
1263                 case bool_:
1264                 case function_:
1265                 case task:
1266                 case enum_:
1267                     addInstruction(GrOpcode.send_int);
1268                     return chanType;
1269                 case float_:
1270                     addInstruction(GrOpcode.send_float);
1271                     return chanType;
1272                 case string_:
1273                     addInstruction(GrOpcode.send_string);
1274                     return chanType;
1275                 case class_:
1276                 case array_:
1277                 case foreign:
1278                 case chan:
1279                     addInstruction(GrOpcode.send_object);
1280                     return chanType;
1281                 case void_:
1282                 case null_:
1283                 case internalTuple:
1284                 case reference:
1285                     break;
1286                 }
1287                 break;
1288             case receive:
1289                 GrType chanType = grUnmangle(varType.mangledType);
1290                 final switch (chanType.baseType) with (GrBaseType) {
1291                 case int_:
1292                 case bool_:
1293                 case function_:
1294                 case task:
1295                 case enum_:
1296                     addInstruction(GrOpcode.receive_int);
1297                     return chanType;
1298                 case float_:
1299                     addInstruction(GrOpcode.receive_float);
1300                     return chanType;
1301                 case string_:
1302                     addInstruction(GrOpcode.receive_string);
1303                     return chanType;
1304                 case class_:
1305                 case array_:
1306                 case foreign:
1307                 case chan:
1308                     addInstruction(GrOpcode.receive_object);
1309                     return chanType;
1310                 case void_:
1311                 case null_:
1312                 case internalTuple:
1313                 case reference:
1314                     break;
1315                 }
1316                 break;
1317             default:
1318                 break;
1319             }
1320             break;
1321         default:
1322             break;
1323         }
1324         return GrType(GrBaseType.void_);
1325     }
1326 
1327     private void addSetInstruction(GrVariable variable, uint fileId,
1328             GrType valueType = grVoid, bool isExpectingValue = false) {
1329         _isAssignationOptimizable = true;
1330         if (variable.isConstant)
1331             logError("`" ~ variable.name ~ "` is const and can't be modified",
1332                     "can't modify a const `" ~ grGetPrettyType(variable.type) ~ "`");
1333         if (variable.type.baseType == GrBaseType.reference) {
1334             valueType = convertType(valueType, grUnmangle(variable.type.mangledType), fileId);
1335             final switch (valueType.baseType) with (GrBaseType) {
1336             case bool_:
1337             case int_:
1338             case function_:
1339             case task:
1340             case chan:
1341             case enum_:
1342                 addInstruction(isExpectingValue ? GrOpcode.refStore2_int : GrOpcode.refStore_int);
1343                 break;
1344             case float_:
1345                 addInstruction(isExpectingValue ? GrOpcode.refStore2_float : GrOpcode
1346                         .refStore_float);
1347                 break;
1348             case string_:
1349                 addInstruction(isExpectingValue ? GrOpcode.refStore2_string
1350                         : GrOpcode.refStore_string);
1351                 break;
1352             case class_:
1353                 addInstruction(isExpectingValue ? GrOpcode.refStore2_object
1354                         : GrOpcode.refStore_object);
1355                 break;
1356             case array_:
1357             case foreign:
1358                 addInstruction(isExpectingValue ? GrOpcode.refStore2_object
1359                         : GrOpcode.refStore_object);
1360                 break;
1361             case void_:
1362             case null_:
1363             case internalTuple:
1364             case reference:
1365                 logError("can't assign to a `" ~ grGetPrettyType(variable.type) ~ "` variable",
1366                         "the value is not assignable");
1367             }
1368             return;
1369         }
1370 
1371         if (variable.isAuto && !variable.isInitialized) {
1372             variable.isInitialized = true;
1373             variable.isAuto = false;
1374             variable.type = valueType;
1375             if (valueType.baseType == GrBaseType.void_)
1376                 logError("can't infer the type of variable",
1377                         "the variable has not been initialized");
1378             else
1379                 setVariableRegister(variable);
1380         }
1381 
1382         if (valueType.baseType != GrBaseType.void_)
1383             convertType(valueType, variable.type, fileId);
1384 
1385         //if(!variable.isInitialized && isExpectingValue)
1386         //    logError("Uninitialized variable", "The variable is being used without being assigned");
1387         variable.isInitialized = true;
1388 
1389         if (variable.isField) {
1390             final switch (variable.type.baseType) with (GrBaseType) {
1391             case bool_:
1392             case int_:
1393             case function_:
1394             case task:
1395             case enum_:
1396                 addInstruction(GrOpcode.fieldStore_int, isExpectingValue ? 0 : -1, true);
1397                 break;
1398             case float_:
1399                 addInstruction(GrOpcode.fieldStore_float, isExpectingValue ? 0 : -1, true);
1400                 break;
1401             case string_:
1402                 addInstruction(GrOpcode.fieldStore_string, isExpectingValue ? 0 : -1, true);
1403                 break;
1404             case foreign:
1405             case reference:
1406             case chan:
1407             case array_:
1408             case class_:
1409                 addInstruction(GrOpcode.fieldStore_object, isExpectingValue ? 0 : -1, true);
1410                 break;
1411             case void_:
1412             case null_:
1413             case internalTuple:
1414                 logError("can't assign to a `" ~ grGetPrettyType(variable.type) ~ "` variable",
1415                         "the value is not assignable");
1416             }
1417         }
1418         else if (variable.isGlobal) {
1419             final switch (variable.type.baseType) with (GrBaseType) {
1420             case bool_:
1421             case int_:
1422             case function_:
1423             case task:
1424             case enum_:
1425                 addInstruction(isExpectingValue ? GrOpcode.globalStore2_int
1426                         : GrOpcode.globalStore_int, variable.register);
1427                 break;
1428             case float_:
1429                 addInstruction(isExpectingValue ? GrOpcode.globalStore2_float
1430                         : GrOpcode.globalStore_float, variable.register);
1431                 break;
1432             case string_:
1433                 addInstruction(isExpectingValue ? GrOpcode.globalStore2_string
1434                         : GrOpcode.globalStore_string, variable.register);
1435                 break;
1436             case chan:
1437             case class_:
1438             case array_:
1439             case foreign:
1440                 addInstruction(isExpectingValue ? GrOpcode.globalStore2_object
1441                         : GrOpcode.globalStore_object, variable.register);
1442                 break;
1443             case void_:
1444             case null_:
1445             case internalTuple:
1446             case reference:
1447                 logError("can't assign to a `" ~ grGetPrettyType(variable.type) ~ "` variable",
1448                         "the value is not assignable");
1449             }
1450         }
1451         else {
1452             final switch (variable.type.baseType) with (GrBaseType) {
1453             case bool_:
1454             case int_:
1455             case function_:
1456             case task:
1457             case enum_:
1458                 addInstruction(isExpectingValue ? GrOpcode.localStore2_int
1459                         : GrOpcode.localStore_int, variable.register);
1460                 break;
1461             case float_:
1462                 addInstruction(isExpectingValue ? GrOpcode.localStore2_float
1463                         : GrOpcode.localStore_float, variable.register);
1464                 break;
1465             case string_:
1466                 addInstruction(isExpectingValue ? GrOpcode.localStore2_string
1467                         : GrOpcode.localStore_string, variable.register);
1468                 break;
1469             case class_:
1470                 addInstruction(isExpectingValue ? GrOpcode.localStore2_object
1471                         : GrOpcode.localStore_object, variable.register);
1472                 break;
1473             case array_:
1474             case foreign:
1475             case chan:
1476                 addInstruction(isExpectingValue ? GrOpcode.localStore2_object
1477                         : GrOpcode.localStore_object, variable.register);
1478                 break;
1479             case void_:
1480             case null_:
1481             case internalTuple:
1482             case reference:
1483                 logError("can't assign to a `" ~ grGetPrettyType(variable.type) ~ "` variable",
1484                         "the value is not assignable");
1485             }
1486         }
1487     }
1488 
1489     ///Add a load opcode, or optimize a previous store.
1490     void addGetInstruction(GrVariable variable, GrType expectedType = grVoid,
1491             bool allowOptimization = true) {
1492         if (!_isAssignationOptimizable) {
1493             /+--------------------------
1494                 Optimizing getters should take care of scope levels as jumps will break the VM.
1495                 This shouldn't be optimized as the stack will be empty on the second pass.
1496                 "main {
1497                     bool a = true;
1498                     loop {
1499                         if(a) {}  //a is just after a = true, so will be optimized.
1500                         yield;
1501                     } //We jump back to the loop where lstore2 is, crashing the VM.
1502                 }"
1503                 To avoid that, we disallow optimization of different scope levels.
1504             -------------------------+/
1505             allowOptimization = false;
1506         }
1507 
1508         if (variable.isField) {
1509             throw new Exception("attempt to get field value");
1510         }
1511         else if (variable.isGlobal) {
1512             final switch (variable.type.baseType) with (GrBaseType) {
1513             case bool_:
1514             case int_:
1515             case function_:
1516             case task:
1517             case enum_:
1518                 if (allowOptimization && currentFunction.instructions.length
1519                         && currentFunction.instructions[$ - 1].opcode == GrOpcode.globalStore_int
1520                         && currentFunction.instructions[$ - 1].value == variable.register)
1521                     currentFunction.instructions[$ - 1].opcode = GrOpcode.globalStore2_int;
1522                 else
1523                     addInstruction(GrOpcode.globalLoad_int, variable.register);
1524                 break;
1525             case float_:
1526                 if (allowOptimization && currentFunction.instructions.length
1527                         && currentFunction.instructions[$ - 1].opcode == GrOpcode.globalStore_float
1528                         && currentFunction.instructions[$ - 1].value == variable.register)
1529                     currentFunction.instructions[$ - 1].opcode = GrOpcode.globalStore2_float;
1530                 else
1531                     addInstruction(GrOpcode.globalLoad_float, variable.register);
1532                 break;
1533             case string_:
1534                 if (allowOptimization && currentFunction.instructions.length
1535                         && currentFunction.instructions[$ - 1].opcode == GrOpcode.globalStore_string
1536                         && currentFunction.instructions[$ - 1].value == variable.register)
1537                     currentFunction.instructions[$ - 1].opcode = GrOpcode.globalStore2_string;
1538                 else
1539                     addInstruction(GrOpcode.globalLoad_string, variable.register);
1540                 break;
1541             case class_:
1542                 if (allowOptimization && currentFunction.instructions.length
1543                         && currentFunction.instructions[$ - 1].opcode == GrOpcode.globalStore_object
1544                         && currentFunction.instructions[$ - 1].value == variable.register)
1545                     currentFunction.instructions[$ - 1].opcode = GrOpcode.globalStore2_object;
1546                 else
1547                     addInstruction(GrOpcode.globalLoad_object, variable.register);
1548                 break;
1549             case array_:
1550             case foreign:
1551             case chan:
1552                 if (allowOptimization && currentFunction.instructions.length
1553                         && currentFunction.instructions[$ - 1].opcode == GrOpcode.globalStore_object
1554                         && currentFunction.instructions[$ - 1].value == variable.register)
1555                     currentFunction.instructions[$ - 1].opcode = GrOpcode.globalStore2_object;
1556                 else
1557                     addInstruction(GrOpcode.globalLoad_object, variable.register);
1558                 break;
1559             case void_:
1560             case null_:
1561             case internalTuple:
1562             case reference:
1563                 logError("can't get the value of `" ~ grGetPrettyType(variable.type) ~ "`",
1564                         "the value is not fetchable");
1565             }
1566         }
1567         else {
1568             if (!variable.isInitialized)
1569                 logError("the local variable is being used without being assigned",
1570                         "uninitialized variable");
1571 
1572             final switch (variable.type.baseType) with (GrBaseType) {
1573             case bool_:
1574             case int_:
1575             case function_:
1576             case task:
1577             case enum_:
1578                 if (allowOptimization && currentFunction.instructions.length
1579                         && currentFunction.instructions[$ - 1].opcode == GrOpcode.localStore_int
1580                         && currentFunction.instructions[$ - 1].value == variable.register)
1581                     currentFunction.instructions[$ - 1].opcode = GrOpcode.localStore2_int;
1582                 else
1583                     addInstruction(GrOpcode.localLoad_int, variable.register);
1584                 break;
1585             case float_:
1586                 if (allowOptimization && currentFunction.instructions.length
1587                         && currentFunction.instructions[$ - 1].opcode == GrOpcode.localStore_float
1588                         && currentFunction.instructions[$ - 1].value == variable.register)
1589                     currentFunction.instructions[$ - 1].opcode = GrOpcode.localStore2_float;
1590                 else
1591                     addInstruction(GrOpcode.localLoad_float, variable.register);
1592                 break;
1593             case string_:
1594                 if (allowOptimization && currentFunction.instructions.length
1595                         && currentFunction.instructions[$ - 1].opcode == GrOpcode.localStore_string
1596                         && currentFunction.instructions[$ - 1].value == variable.register)
1597                     currentFunction.instructions[$ - 1].opcode = GrOpcode.localStore2_string;
1598                 else
1599                     addInstruction(GrOpcode.localLoad_string, variable.register);
1600                 break;
1601             case class_:
1602                 if (allowOptimization && currentFunction.instructions.length
1603                         && currentFunction.instructions[$ - 1].opcode == GrOpcode.localStore_object
1604                         && currentFunction.instructions[$ - 1].value == variable.register)
1605                     currentFunction.instructions[$ - 1].opcode = GrOpcode.localStore2_object;
1606                 else
1607                     addInstruction(GrOpcode.localLoad_object, variable.register);
1608                 break;
1609             case array_:
1610             case foreign:
1611             case chan:
1612                 if (allowOptimization && currentFunction.instructions.length
1613                         && currentFunction.instructions[$ - 1].opcode == GrOpcode.localStore_object
1614                         && currentFunction.instructions[$ - 1].value == variable.register)
1615                     currentFunction.instructions[$ - 1].opcode = GrOpcode.localStore2_object;
1616                 else
1617                     addInstruction(GrOpcode.localLoad_object, variable.register);
1618                 break;
1619             case void_:
1620             case null_:
1621             case internalTuple:
1622             case reference:
1623                 logError("can't get the value of `" ~ grGetPrettyType(variable.type) ~ "`",
1624                         "the value is not fetchable");
1625             }
1626         }
1627     }
1628 
1629     private GrType addFunctionAddress(string name, GrType[] signature, uint fileId) {
1630         if (name == "@global")
1631             return grVoid;
1632         GrFunctionCall call = new GrFunctionCall;
1633         call.name = name;
1634         call.signature = signature;
1635         call.caller = currentFunction;
1636         functionCalls ~= call;
1637         currentFunction.functionCalls ~= call;
1638         call.isAddress = true;
1639         auto func = getFunction(name, signature, fileId);
1640         if (func is null)
1641             func = getAnonymousFunction(name, signature, fileId);
1642         if (func !is null) {
1643             call.functionToCall = func;
1644             call.position = cast(uint) currentFunction.instructions.length;
1645             addInstruction(GrOpcode.const_int, 0);
1646 
1647             return grGetFunctionAsType(func);
1648         }
1649         return grVoid;
1650     }
1651 
1652     private GrType addFunctionAddress(GrFunction func, uint fileId) {
1653         if (func.name == "@global")
1654             return grVoid;
1655         GrFunctionCall call = new GrFunctionCall;
1656         call.caller = currentFunction;
1657         functionCalls ~= call;
1658         currentFunction.functionCalls ~= call;
1659         call.isAddress = true;
1660         call.functionToCall = func;
1661         call.position = cast(uint) currentFunction.instructions.length;
1662         addInstruction(GrOpcode.const_int, 0);
1663         return grGetFunctionAsType(func);
1664     }
1665 
1666     private GrType[] addFunctionCall(string name, GrType[] signature, uint fileId) {
1667         GrFunctionCall call = new GrFunctionCall;
1668         call.name = name;
1669         call.signature = signature;
1670         call.caller = currentFunction;
1671         functionCalls ~= call;
1672         currentFunction.functionCalls ~= call;
1673         call.isAddress = false;
1674         call.fileId = fileId;
1675 
1676         GrFunction func = getFunction(name, signature, call.fileId, false);
1677         if (func) {
1678             call.functionToCall = func;
1679             if (func.isTask) {
1680                 if (func.nbIntegerParameters > 0)
1681                     addInstruction(GrOpcode.globalPush_int, func.nbIntegerParameters);
1682                 if (func.nbFloatParameters > 0)
1683                     addInstruction(GrOpcode.globalPush_float, func.nbFloatParameters);
1684                 if (func.nbStringParameters > 0)
1685                     addInstruction(GrOpcode.globalPush_string, func.nbStringParameters);
1686                 if (func.nbObjectParameters > 0)
1687                     addInstruction(GrOpcode.globalPush_object, func.nbObjectParameters);
1688             }
1689 
1690             call.position = cast(uint) currentFunction.instructions.length;
1691             addInstruction(GrOpcode.call, 0);
1692 
1693             return func.outSignature;
1694         }
1695         else
1696             logError("`" ~ grGetPrettyFunctionCall(name,
1697                     signature) ~ "` is not declared", "unknown function", "", -1);
1698 
1699         return [];
1700     }
1701 
1702     private GrType[] addFunctionCall(GrFunction func, uint fileId) {
1703         GrFunctionCall call = new GrFunctionCall;
1704         call.name = func.name;
1705         call.signature = func.inSignature;
1706         call.caller = currentFunction;
1707         functionCalls ~= call;
1708         currentFunction.functionCalls ~= call;
1709         call.isAddress = false;
1710         call.fileId = fileId;
1711 
1712         call.functionToCall = func;
1713         if (func.isTask) {
1714             if (func.nbIntegerParameters > 0)
1715                 addInstruction(GrOpcode.globalPush_int, func.nbIntegerParameters);
1716             if (func.nbFloatParameters > 0)
1717                 addInstruction(GrOpcode.globalPush_float, func.nbFloatParameters);
1718             if (func.nbStringParameters > 0)
1719                 addInstruction(GrOpcode.globalPush_string, func.nbStringParameters);
1720             if (func.nbObjectParameters > 0)
1721                 addInstruction(GrOpcode.globalPush_object, func.nbObjectParameters);
1722         }
1723 
1724         call.position = cast(uint) currentFunction.instructions.length;
1725         addInstruction(GrOpcode.call, 0);
1726 
1727         return func.outSignature;
1728     }
1729 
1730     private void setOpcode(ref uint[] opcodes, uint position, GrOpcode opcode,
1731             uint value = 0u, bool isSigned = false) {
1732         GrInstruction instruction;
1733         instruction.opcode = opcode;
1734         if (isSigned) {
1735             if ((value >= 0x800000) || (-value >= 0x800000))
1736                 throw new Exception("an opcode's signed value is exceeding limits");
1737             instruction.value = value + 0x800000;
1738         }
1739         else
1740             instruction.value = value;
1741 
1742         uint makeOpcode(uint instr, uint value) {
1743             return ((value << 8u) & 0xffffff00) | (instr & 0xff);
1744         }
1745 
1746         opcodes[position] = makeOpcode(cast(uint) instruction.opcode, instruction.value);
1747     }
1748 
1749     package void solveFunctionCalls(ref uint[] opcodes) {
1750         foreach (GrFunctionCall call; functionCalls) {
1751             GrFunction func = call.functionToCall;
1752             if (!func)
1753                 func = getFunction(call.name, call.signature, call.fileId);
1754             if (!func)
1755                 func = getAnonymousFunction(call.name, call.signature, call.fileId);
1756             if (func) {
1757                 if (call.isAddress)
1758                     setOpcode(opcodes, call.position, GrOpcode.const_int,
1759                             registerIntConstant(func.position));
1760                 else if (func.isTask)
1761                     setOpcode(opcodes, call.position, GrOpcode.task, func.position);
1762                 else
1763                     setOpcode(opcodes, call.position, GrOpcode.call, func.position);
1764             }
1765             else
1766                 logError("`" ~ grGetPrettyFunctionCall(call.name,
1767                         call.signature) ~ "` is not declared", "unknown function");
1768         }
1769 
1770         foreach (func; anonymousFunctions)
1771             setOpcode(opcodes, func.anonParent.position + func.anonParent.offset + func.anonReference,
1772                     GrOpcode.const_int, registerIntConstant(func.position));
1773     }
1774 
1775     package void dump() {
1776         writeln("Code Generated:\n");
1777         foreach (size_t i, GrInt ivalue; iconsts)
1778             writeln(".iconst " ~ to!string(ivalue) ~ "\t;" ~ to!string(i));
1779 
1780         foreach (size_t i, GrFloat fvalue; fconsts)
1781             writeln(".fconst " ~ to!string(fvalue) ~ "\t;" ~ to!string(i));
1782 
1783         foreach (size_t i, GrString svalue; sconsts)
1784             writeln(".sconst " ~ to!string(svalue) ~ "\t;" ~ to!string(i));
1785 
1786         foreach (GrFunction func; functions) {
1787             if (func.isTask)
1788                 writeln("\n.task " ~ func.name);
1789             else
1790                 writeln("\n.function " ~ func.name);
1791 
1792             foreach (size_t i, GrInstruction instruction; func.instructions) {
1793                 writeln("[" ~ to!string(i) ~ "] " ~ to!string(
1794                         instruction.opcode) ~ " " ~ to!string(instruction.value));
1795             }
1796         }
1797     }
1798 
1799     package void parseScript(GrData data, GrLexer lexer, int options) {
1800         _data = data;
1801         _options = options;
1802 
1803         bool isPublic;
1804         lexemes = lexer.lexemes;
1805 
1806         beginGlobalScope();
1807         foreach (GrVariableDefinition variableDef; _data._variableDefinitions) {
1808             GrVariable variable = registerGlobalVariable(variableDef.name,
1809                     variableDef.type, false, true);
1810             variable.isConstant = variableDef.isConstant;
1811             variableDef.register = variable.register;
1812         }
1813         endGlobalScope();
1814 
1815         //Type definitions
1816         while (!isEnd()) {
1817             GrLexeme lex = get();
1818             isPublic = false;
1819             if (lex.type == GrLexemeType.public_) {
1820                 isPublic = true;
1821                 checkAdvance();
1822                 lex = get();
1823             }
1824             switch (lex.type) with (GrLexemeType) {
1825             case semicolon:
1826                 checkAdvance();
1827                 break;
1828             case class_:
1829                 registerClassDeclaration(isPublic);
1830                 break;
1831             case enum_:
1832                 parseEnumDeclaration(isPublic);
1833                 break;
1834             case main_:
1835             case event_:
1836             case taskType:
1837             case functionType:
1838                 skipDeclaration();
1839                 break;
1840             case type_:
1841             case template_:
1842             default:
1843                 skipExpression();
1844                 break;
1845             }
1846         }
1847 
1848         //Type aliases
1849         reset();
1850         while (!isEnd()) {
1851             GrLexeme lex = get();
1852             isPublic = false;
1853             if (lex.type == GrLexemeType.public_) {
1854                 isPublic = true;
1855                 checkAdvance();
1856                 lex = get();
1857             }
1858             switch (lex.type) with (GrLexemeType) {
1859             case semicolon:
1860                 checkAdvance();
1861                 break;
1862             case type_:
1863                 parseTypeAliasDeclaration(isPublic);
1864                 break;
1865             case main_:
1866             case event_:
1867             case taskType:
1868             case functionType:
1869             case class_:
1870             case enum_:
1871                 skipDeclaration();
1872                 break;
1873             case template_:
1874             default:
1875                 skipExpression();
1876                 break;
1877             }
1878         }
1879 
1880         //Function definitions
1881         reset();
1882         while (!isEnd()) {
1883             GrLexeme lex = get();
1884             isPublic = false;
1885             if (lex.type == GrLexemeType.public_) {
1886                 isPublic = true;
1887                 checkAdvance();
1888                 lex = get();
1889             }
1890             switch (lex.type) with (GrLexemeType) {
1891             case semicolon:
1892                 checkAdvance();
1893                 break;
1894             case enum_:
1895             case class_:
1896                 skipDeclaration();
1897                 break;
1898             case main_:
1899                 parseMainDeclaration(isPublic);
1900                 break;
1901             case event_:
1902                 parseEventDeclaration(isPublic);
1903                 break;
1904             case taskType:
1905                 if (get(1).type != GrLexemeType.identifier && get(1).type != GrLexemeType.lesser)
1906                     goto case intType;
1907                 parseTaskDeclaration(isPublic);
1908                 break;
1909             case functionType:
1910                 if (get(1).type != GrLexemeType.identifier && get(1)
1911                         .type != GrLexemeType.as && get(1).type != GrLexemeType.lesser)
1912                     goto case intType;
1913                 parseFunctionDeclaration(isPublic);
1914                 break;
1915             case intType: .. case chanType:
1916             case autoType:
1917             case identifier:
1918             case type_:
1919             case template_:
1920                 skipExpression();
1921                 break;
1922             default:
1923                 logError("a global declaration is expected",
1924                         "a global declaration is expected, found `" ~ grGetPrettyLexemeType(get()
1925                             .type) ~ "`");
1926             }
1927         }
1928 
1929         //Global variable definitions
1930         reset();
1931         beginGlobalScope();
1932         while (!isEnd()) {
1933             GrLexeme lex = get();
1934             isPublic = false;
1935             if (lex.type == GrLexemeType.public_) {
1936                 isPublic = true;
1937                 checkAdvance();
1938                 lex = get();
1939             }
1940             switch (lex.type) with (GrLexemeType) {
1941             case semicolon:
1942                 checkAdvance();
1943                 break;
1944             case event_:
1945             case enum_:
1946             case class_:
1947             case main_:
1948                 skipDeclaration();
1949                 break;
1950             case template_:
1951                 parseTemplateDeclaration(isPublic);
1952                 break;
1953             case taskType:
1954                 if (get(1).type != GrLexemeType.identifier && get(1).type != GrLexemeType.lesser)
1955                     goto case intType;
1956                 skipDeclaration();
1957                 break;
1958             case functionType:
1959                 if (get(1).type != GrLexemeType.identifier && get(1)
1960                         .type != GrLexemeType.as && get(1).type != GrLexemeType.lesser)
1961                     goto case intType;
1962                 skipDeclaration();
1963                 break;
1964             case intType: .. case chanType:
1965             case autoType:
1966                 parseGlobalDeclaration(isPublic);
1967                 break;
1968             case identifier:
1969                 if (_data.isTypeDeclared(get().svalue, get().fileId, false)) {
1970                     parseGlobalDeclaration(isPublic);
1971                     break;
1972                 }
1973                 goto default;
1974             case type_:
1975                 skipExpression();
1976                 break;
1977             default:
1978                 logError("a global declaration is expected",
1979                         "a global declaration is expected, found `" ~ grGetPrettyLexemeType(get()
1980                             .type) ~ "`");
1981             }
1982         }
1983         endGlobalScope();
1984 
1985         while (functionsQueue.length) {
1986             GrFunction func = functionsQueue[$ - 1];
1987             functionsQueue.length--;
1988             parseFunction(func);
1989         }
1990     }
1991 
1992     /**
1993     Parse the body of global functions
1994     */
1995     void parseFunction(GrFunction func) {
1996         if (func.isEvent) {
1997             func.index = cast(uint) events.length;
1998             events ~= func;
1999         }
2000         else {
2001             func.index = cast(uint) functions.length;
2002             functions ~= func;
2003         }
2004 
2005         functionStack ~= currentFunction;
2006         currentFunction = func;
2007 
2008         for (int i; i < func.templateVariables.length; ++i) {
2009             _data.addTemplateAlias(func.templateVariables[i],
2010                     func.templateSignature[i], func.fileId, func.isPublic);
2011         }
2012 
2013         openDeferrableSection();
2014         current = func.lexPosition;
2015         parseBlock();
2016         if (func.isTask || func.isMain || func.isEvent) {
2017             if (!currentFunction.instructions.length
2018                     || currentFunction.instructions[$ - 1].opcode != GrOpcode.kill_)
2019                 addKill();
2020         }
2021         else {
2022             if (!currentFunction.outSignature.length) {
2023                 if (!currentFunction.instructions.length
2024                         || currentFunction.instructions[$ - 1].opcode != GrOpcode.return_)
2025                     addReturn();
2026             }
2027             else {
2028                 if (!currentFunction.instructions.length
2029                         || currentFunction.instructions[$ - 1].opcode != GrOpcode.return_)
2030                     logError("the function is missing a return at the end of the scope",
2031                             "missing `return`");
2032             }
2033         }
2034         closeDeferrableSection();
2035         registerDeferBlocks();
2036 
2037         endFunction();
2038         _data.clearTemplateAliases();
2039     }
2040 
2041     /**
2042     Declare a new alias of a type.
2043     */
2044     private void parseTypeAliasDeclaration(bool isPublic) {
2045         const uint fileId = get().fileId;
2046         checkAdvance();
2047         if (get().type != GrLexemeType.identifier)
2048             logError("expected type alias name, found `" ~ grGetPrettyLexemeType(get()
2049                     .type) ~ "`", "missing identifier");
2050         const string typeAliasName = get().svalue;
2051         checkAdvance();
2052         if (get().type != GrLexemeType.assign)
2053             logError("missing assignment in `type`",
2054                     "expected `=`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
2055         checkAdvance();
2056         GrType type = parseType(true);
2057         if (get().type != GrLexemeType.semicolon)
2058             logError("missing semicolon after `type`",
2059                     "expected `;`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
2060 
2061         if (_data.isTypeDeclared(typeAliasName, fileId, isPublic))
2062             logError("the name `" ~ typeAliasName ~ "` is defined multiple times",
2063                     "`" ~ typeAliasName ~ "` is already declared");
2064         _data.addTypeAlias(typeAliasName, type, fileId, isPublic);
2065     }
2066 
2067     private void parseEnumDeclaration(bool isPublic) {
2068         const uint fileId = get().fileId;
2069         checkAdvance();
2070         if (get().type != GrLexemeType.identifier)
2071             logError("expected enum name, found `" ~ grGetPrettyLexemeType(get()
2072                     .type) ~ "`", "missing identifier");
2073         const string enumName = get().svalue;
2074         checkAdvance();
2075         if (get().type != GrLexemeType.leftCurlyBrace)
2076             logError("the enum definition does not have a body",
2077                     "expected `{`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
2078         checkAdvance();
2079 
2080         string[] fields;
2081         while (!isEnd()) {
2082             if (get().type == GrLexemeType.rightCurlyBrace) {
2083                 checkAdvance();
2084                 break;
2085             }
2086             if (get().type != GrLexemeType.identifier)
2087                 logError("expected enum field, found `" ~ grGetPrettyLexemeType(get()
2088                         .type) ~ "`", "missing identifier");
2089 
2090             auto fieldName = get().svalue;
2091             checkAdvance();
2092             fields ~= fieldName;
2093 
2094             if (get().type != GrLexemeType.semicolon)
2095                 logError("missing semicolon after type enum field",
2096                         "expected `;`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
2097             checkAdvance();
2098         }
2099         if (_data.isTypeDeclared(enumName, fileId, isPublic))
2100             logError("the name `" ~ enumName ~ "` is defined multiple times",
2101                     "`" ~ enumName ~ "` is already declared");
2102         _data.addEnum(enumName, fields, fileId, isPublic);
2103     }
2104 
2105     private void registerClassDeclaration(bool isPublic) {
2106         checkAdvance();
2107         string[] templateVariables = parseTemplateVariables();
2108         const uint fileId = get().fileId;
2109         const uint declPosition = current;
2110         if (get().type != GrLexemeType.identifier)
2111             logError("expected class name, found `" ~ grGetPrettyLexemeType(get()
2112                     .type) ~ "`", "missing identifier");
2113         const string className = get().svalue;
2114         if (_data.isTypeDeclared(className, fileId, isPublic))
2115             logError("the name `" ~ className ~ "` is defined multiple times",
2116                     "`" ~ className ~ "` is already declared");
2117         _data.registerClass(className, fileId, isPublic, templateVariables, declPosition);
2118         skipDeclaration();
2119     }
2120 
2121     private GrClassDefinition getClass(string mangledType, uint fileId) {
2122         GrClassDefinition class_ = _data.getClass(mangledType, fileId);
2123         if (!class_)
2124             return null;
2125         parseClassDeclaration(class_);
2126         return class_;
2127     }
2128 
2129     private void parseClassDeclaration(GrClassDefinition class_) {
2130         if (class_.isParsed)
2131             return;
2132         class_.isParsed = true;
2133         uint tempPos = current;
2134         current = class_.position;
2135 
2136         for (int i; i < class_.templateVariables.length; ++i) {
2137             _data.addTemplateAlias(class_.templateVariables[i],
2138                     class_.templateTypes[i], class_.fileId, class_.isPublic);
2139         }
2140 
2141         uint[] fieldPositions;
2142         if (get().type != GrLexemeType.identifier)
2143             logError("expected class name, found `" ~ grGetPrettyLexemeType(get()
2144                     .type) ~ "`", "missing identifier");
2145         const string className = get().svalue;
2146         string parentClassName;
2147         checkAdvance();
2148 
2149         //Inheritance
2150         if (get().type == GrLexemeType.colon) {
2151             checkAdvance();
2152             if (get().type != GrLexemeType.identifier)
2153                 logError("the parent class name is missing",
2154                         "expected class name, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
2155             parentClassName = get().svalue;
2156             checkAdvance();
2157             parentClassName = grMangleComposite(parentClassName, parseTemplateSignature());
2158         }
2159         if (get().type != GrLexemeType.leftCurlyBrace)
2160             logError("the class does not have a body",
2161                     "expected `{`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
2162         checkAdvance();
2163 
2164         string[] fields;
2165         GrType[] signature;
2166         bool[] fieldScopes;
2167         while (!isEnd()) {
2168             if (get().type == GrLexemeType.rightCurlyBrace) {
2169                 checkAdvance();
2170                 break;
2171             }
2172 
2173             bool isFieldPublic = false;
2174             if (get().type == GrLexemeType.public_) {
2175                 isFieldPublic = true;
2176                 checkAdvance();
2177             }
2178 
2179             GrType fieldType = parseType();
2180             do {
2181                 if (get().type == GrLexemeType.comma)
2182                     checkAdvance();
2183 
2184                 const string fieldName = get().svalue;
2185                 signature ~= fieldType;
2186                 fields ~= fieldName;
2187                 fieldScopes ~= isFieldPublic;
2188                 fieldPositions ~= current;
2189                 checkAdvance();
2190             }
2191             while (get().type == GrLexemeType.comma);
2192 
2193             if (get().type != GrLexemeType.semicolon)
2194                 logError("missing semicolon after class field declaration",
2195                         "expected `;`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
2196             checkAdvance();
2197 
2198             if (get().type == GrLexemeType.rightCurlyBrace) {
2199                 checkAdvance();
2200                 break;
2201             }
2202         }
2203 
2204         class_.parent = parentClassName;
2205         class_.signature = signature;
2206         class_.fields = fields;
2207 
2208         class_.fieldsInfo.length = fields.length;
2209         for (int i; i < class_.fieldsInfo.length; ++i) {
2210             class_.fieldsInfo[i].fileId = class_.fileId;
2211             class_.fieldsInfo[i].isPublic = fieldScopes[i];
2212             class_.fieldsInfo[i].position = fieldPositions[i];
2213         }
2214         current = tempPos;
2215         _data.clearTemplateAliases();
2216         resolveClassInheritence(class_);
2217     }
2218 
2219     /// Fetch fields and signature of parent classes
2220     private void resolveClassInheritence(GrClassDefinition class_) {
2221         uint fileId = class_.fileId;
2222         string parent = class_.parent;
2223         GrClassDefinition lastClass = class_;
2224         string[] usedClasses = [class_.name];
2225 
2226         while (parent.length) {
2227             GrClassDefinition parentClass = getClass(parent, fileId);
2228             if (!parentClass) {
2229                 set(lastClass.position + 2u);
2230                 logError("`" ~ grGetPrettyType(grGetClassType(class_.name)) ~ "` can't inherit from `" ~ parent ~ "`",
2231                         "unknown class");
2232             }
2233             for (int i; i < usedClasses.length; ++i) {
2234                 if (parent == usedClasses[i]) {
2235                     set(lastClass.position + 2u);
2236                     logError("`" ~ grGetPrettyType(grGetClassType(parent)) ~ "` is included recursively",
2237                             "recursive inheritence");
2238                 }
2239             }
2240             usedClasses ~= parent;
2241             class_.fields = parentClass.fields ~ class_.fields;
2242             class_.signature = parentClass.signature ~ class_.signature;
2243             class_.fieldsInfo = parentClass.fieldsInfo ~ class_.fieldsInfo;
2244             fileId = parentClass.fileId;
2245             parent = parentClass.parent;
2246             lastClass = parentClass;
2247         }
2248         for (int i; i < class_.signature.length; ++i) {
2249             for (int y; y < class_.fields.length; ++y) {
2250                 if (i != y && class_.fields[i] == class_.fields[y]) {
2251                     int first;
2252                     int second;
2253                     if (class_.fieldsInfo[i].position < class_.fieldsInfo[y].position) {
2254                         first = i;
2255                         second = y;
2256                     }
2257                     else {
2258                         first = y;
2259                         second = i;
2260                     }
2261                     set(class_.fieldsInfo[second].position);
2262                     logError("the field `" ~ class_.fields[second] ~ "` is declared multiple times",
2263                             "`" ~ class_.fields[second] ~ "` is redefined here",
2264                             "", 0, "previous definition of `" ~ class_.fields[first] ~ "`",
2265                             class_.fieldsInfo[first].position);
2266                 }
2267             }
2268             if (class_.signature[i].baseType != GrBaseType.class_) {
2269                 for (int y; y < usedClasses.length; ++y) {
2270                     if (class_.signature[i].mangledType == usedClasses[y]) {
2271                         set(class_.fieldsInfo[i].position);
2272                         logError("`" ~ class_.signature[i].mangledType ~ "` is included recursively",
2273                                 "recursive declaration");
2274                     }
2275                 }
2276             }
2277         }
2278     }
2279 
2280     private void skipDeclaration() {
2281         checkAdvance();
2282         while (!isEnd()) {
2283             if (get().type != GrLexemeType.leftCurlyBrace) {
2284                 checkAdvance();
2285             }
2286             else {
2287                 skipBlock();
2288                 return;
2289             }
2290         }
2291     }
2292 
2293     private void skipExpression() {
2294         checkAdvance();
2295         while (!isEnd()) {
2296             switch (get().type) with (GrLexemeType) {
2297             case semicolon:
2298                 checkAdvance();
2299                 return;
2300             case leftCurlyBrace:
2301                 skipBlock();
2302                 break;
2303             default:
2304                 checkAdvance();
2305                 break;
2306             }
2307         }
2308     }
2309 
2310     private GrType parseType(bool mustBeType = true) {
2311         GrType currentType = GrBaseType.void_;
2312 
2313         GrLexeme lex = get();
2314         if (!lex.isType) {
2315             if (lex.type == GrLexemeType.identifier
2316                     && _data.isTypeAlias(lex.svalue, lex.fileId, false)) {
2317                 currentType = _data.getTypeAlias(lex.svalue, lex.fileId).type;
2318                 checkAdvance();
2319                 return currentType;
2320             }
2321             else if (lex.type == GrLexemeType.identifier
2322                     && _data.isClass(lex.svalue, lex.fileId, false)) {
2323                 currentType.baseType = GrBaseType.class_;
2324                 checkAdvance();
2325                 currentType.mangledType = grMangleComposite(lex.svalue, parseTemplateSignature());
2326                 if (mustBeType) {
2327                     GrClassDefinition class_ = getClass(currentType.mangledType, lex.fileId);
2328                     if (!class_)
2329                         logError("`" ~ grGetPrettyType(currentType) ~ "` is not declared",
2330                                 "unknown class", "", -1);
2331                 }
2332                 return currentType;
2333             }
2334             else if (lex.type == GrLexemeType.identifier
2335                     && _data.isEnum(lex.svalue, lex.fileId, false)) {
2336                 currentType.baseType = GrBaseType.enum_;
2337                 currentType.mangledType = lex.svalue;
2338                 checkAdvance();
2339                 return currentType;
2340             }
2341             else if (lex.type == GrLexemeType.identifier && _data.isForeign(lex.svalue)) {
2342                 currentType.baseType = GrBaseType.foreign;
2343                 currentType.mangledType = lex.svalue;
2344                 checkAdvance();
2345                 currentType.mangledType = grMangleComposite(lex.svalue, parseTemplateSignature());
2346                 return currentType;
2347             }
2348             else if (mustBeType) {
2349                 const string typeName = lex.type == GrLexemeType.identifier
2350                     ? lex.svalue : grGetPrettyLexemeType(lex.type);
2351                 logError("`" ~ typeName ~ "` is not a valid type",
2352                         "expected a valid type, found `" ~ typeName ~ "`");
2353             }
2354             else {
2355                 return currentType;
2356             }
2357         }
2358 
2359         switch (lex.type) with (GrLexemeType) {
2360         case intType:
2361             currentType.baseType = GrBaseType.int_;
2362             checkAdvance();
2363             break;
2364         case floatType:
2365             currentType.baseType = GrBaseType.float_;
2366             checkAdvance();
2367             break;
2368         case boolType:
2369             currentType.baseType = GrBaseType.bool_;
2370             checkAdvance();
2371             break;
2372         case stringType:
2373             currentType.baseType = GrBaseType.string_;
2374             checkAdvance();
2375             break;
2376         case arrayType:
2377             currentType.baseType = GrBaseType.array_;
2378             checkAdvance();
2379             string[] temp;
2380             auto signature = parseInSignature(temp, true);
2381             if (signature.length > 1)
2382                 logError("an array can only contain one type of value", "conflicting array signature",
2383                         "try using `" ~ grGetPrettyType(grArray(signature[0])) ~ "` instead", -1);
2384             currentType.mangledType = grMangleSignature(signature);
2385             break;
2386         case functionType:
2387             currentType.baseType = GrBaseType.function_;
2388             checkAdvance();
2389             string[] temp;
2390             currentType.mangledType = grMangleSignature(parseInSignature(temp, true));
2391             currentType.mangledReturnType = grMangleSignature(parseOutSignature());
2392             break;
2393         case taskType:
2394             currentType.baseType = GrBaseType.task;
2395             checkAdvance();
2396             string[] temp;
2397             currentType.mangledType = grMangleSignature(parseInSignature(temp, true));
2398             break;
2399         case chanType:
2400             currentType.baseType = GrBaseType.chan;
2401             checkAdvance();
2402             string[] temp;
2403             GrType[] signature = parseInSignature(temp, true);
2404             if (signature.length != 1)
2405                 logError("a channel can only contain one type of value", "conflicting channel signature",
2406                         "try using `" ~ grGetPrettyType(grChannel(signature[0])) ~ "` instead", -1);
2407             currentType.mangledType = grMangleSignature(signature);
2408             break;
2409         default:
2410             logError("`" ~ grGetPrettyLexemeType(lex.type) ~ "` is not a valid type",
2411                     "invalid type");
2412         }
2413 
2414         return currentType;
2415     }
2416 
2417     private void addGlobalPop(GrType type) {
2418         final switch (type.baseType) with (GrBaseType) {
2419         case internalTuple:
2420         case null_:
2421         case void_:
2422             logError("`" ~ grGetPrettyType(type) ~ "` is not a valid type", "invalid type");
2423             break;
2424         case int_:
2425         case bool_:
2426         case function_:
2427         case task:
2428         case enum_:
2429             addInstruction(GrOpcode.globalPop_int, 0u);
2430             break;
2431         case float_:
2432             addInstruction(GrOpcode.globalPop_float, 0u);
2433             break;
2434         case string_:
2435             addInstruction(GrOpcode.globalPop_string, 0u);
2436             break;
2437         case class_:
2438         case array_:
2439         case foreign:
2440         case chan:
2441         case reference:
2442             addInstruction(GrOpcode.globalPop_object, 0u);
2443             break;
2444         }
2445     }
2446 
2447     private void addGlobalPush(GrType type, int nbPush = 1u) {
2448         if (nbPush == 0)
2449             return;
2450         final switch (type.baseType) with (GrBaseType) {
2451         case internalTuple:
2452         case null_:
2453         case void_:
2454             logError("`" ~ grGetPrettyType(type) ~ "` is not a valid type", "invalid type");
2455             break;
2456         case int_:
2457         case bool_:
2458         case function_:
2459         case task:
2460         case enum_:
2461             addInstruction(GrOpcode.globalPush_int, nbPush);
2462             break;
2463         case float_:
2464             addInstruction(GrOpcode.globalPush_float, nbPush);
2465             break;
2466         case string_:
2467             addInstruction(GrOpcode.globalPush_string, nbPush);
2468             break;
2469         case class_:
2470         case array_:
2471         case foreign:
2472         case chan:
2473         case reference:
2474             addInstruction(GrOpcode.globalPush_object, nbPush);
2475             break;
2476         }
2477     }
2478 
2479     private void addGlobalPush(GrType[] signature) {
2480         struct TypeCounter {
2481             uint nbIntParams, nbFloatParams, nbStringParams, nbObjectParams;
2482         }
2483 
2484         void countParameters(ref TypeCounter typeCounter, GrType type) {
2485             final switch (type.baseType) with (GrBaseType) {
2486             case internalTuple:
2487             case null_:
2488             case void_:
2489                 logError("`" ~ grGetPrettyType(type) ~ "` is not a valid type", "invalid type");
2490                 break;
2491             case int_:
2492             case bool_:
2493             case function_:
2494             case task:
2495             case enum_:
2496                 typeCounter.nbIntParams++;
2497                 break;
2498             case float_:
2499                 typeCounter.nbFloatParams++;
2500                 break;
2501             case string_:
2502                 typeCounter.nbStringParams++;
2503                 break;
2504             case class_:
2505             case array_:
2506             case foreign:
2507             case chan:
2508             case reference:
2509                 typeCounter.nbObjectParams++;
2510                 break;
2511             }
2512         }
2513 
2514         TypeCounter typeCounter;
2515         foreach (type; signature) {
2516             countParameters(typeCounter, type);
2517         }
2518 
2519         if (typeCounter.nbIntParams > 0)
2520             addInstruction(GrOpcode.globalPush_int, typeCounter.nbIntParams);
2521         if (typeCounter.nbFloatParams > 0)
2522             addInstruction(GrOpcode.globalPush_float, typeCounter.nbFloatParams);
2523         if (typeCounter.nbStringParams > 0)
2524             addInstruction(GrOpcode.globalPush_string, typeCounter.nbStringParams);
2525         if (typeCounter.nbObjectParams > 0)
2526             addInstruction(GrOpcode.globalPush_object, typeCounter.nbObjectParams);
2527     }
2528 
2529     private string[] parseTemplateVariables() {
2530         string[] variables;
2531         if (get().type != GrLexemeType.lesser)
2532             return variables;
2533         checkAdvance();
2534         if (get().type == GrLexemeType.greater) {
2535             checkAdvance();
2536             return variables;
2537         }
2538         for (;;) {
2539             if (get().type != GrLexemeType.identifier)
2540                 logError("an identifier is expected", "missing template value");
2541             variables ~= get().svalue;
2542             checkAdvance();
2543 
2544             const GrLexeme lex = get();
2545             if (lex.type == GrLexemeType.greater) {
2546                 checkAdvance();
2547                 break;
2548             }
2549             else if (lex.type != GrLexemeType.comma)
2550                 logError("template values should be separated by a comma",
2551                         "expected `,`, found `" ~ grGetPrettyLexemeType(lex.type) ~ "`");
2552             checkAdvance();
2553         }
2554         return variables;
2555     }
2556 
2557     private GrType[] parseTemplateSignature() {
2558         GrType[] signature;
2559         if (get().type != GrLexemeType.lesser)
2560             return signature;
2561         checkAdvance();
2562         if (get().type == GrLexemeType.greater) {
2563             checkAdvance();
2564             return signature;
2565         }
2566         for (;;) {
2567             signature ~= parseType();
2568 
2569             const GrLexeme lex = get();
2570             if (lex.type == GrLexemeType.greater) {
2571                 checkAdvance();
2572                 break;
2573             }
2574             else if (lex.type != GrLexemeType.comma)
2575                 logError("template types should be separated by a comma",
2576                         "expected `,`, found `" ~ grGetPrettyLexemeType(lex.type) ~ "`");
2577             checkAdvance();
2578         }
2579         return signature;
2580     }
2581 
2582     private GrType[] parseInSignature(ref string[] inputVariables, bool asType = false) {
2583         GrType[] inSignature;
2584 
2585         if (get().type != GrLexemeType.leftParenthesis)
2586             logError("missing parentheses",
2587                     "expected `(`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
2588 
2589         bool startLoop = true;
2590         for (;;) {
2591             checkAdvance();
2592             GrLexeme lex = get();
2593 
2594             if (startLoop && lex.type == GrLexemeType.rightParenthesis)
2595                 break;
2596             startLoop = false;
2597 
2598             inSignature ~= parseType();
2599 
2600             //If we want to know whether it's a type or an anon, we can't throw exceptions.
2601             if (isTypeChecking) {
2602                 lex = get();
2603                 if (get().type == GrLexemeType.identifier) {
2604                     inputVariables ~= lex.svalue;
2605                     checkAdvance();
2606                     lex = get();
2607                 }
2608 
2609                 if (lex.type == GrLexemeType.rightParenthesis)
2610                     break;
2611                 else if (lex.type != GrLexemeType.comma)
2612                     logError("parameters should be separated by a comma",
2613                             "expected `,`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
2614             }
2615             else {
2616                 //Is it a function type or a function declaration ?
2617                 if (!asType) {
2618                     lex = get();
2619                     if (get().type != GrLexemeType.identifier)
2620                         logError("expected identifier, found `" ~ grGetPrettyLexemeType(get()
2621                                 .type) ~ "`", "missing identifier");
2622                     inputVariables ~= lex.svalue;
2623                     checkAdvance();
2624                 }
2625 
2626                 lex = get();
2627                 if (lex.type == GrLexemeType.rightParenthesis)
2628                     break;
2629                 else if (lex.type != GrLexemeType.comma)
2630                     logError("parameters should be separated by a comma",
2631                             "expected `,`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
2632             }
2633         }
2634         checkAdvance();
2635 
2636         return inSignature;
2637     }
2638 
2639     private GrType[] parseOutSignature() {
2640         GrType[] outSignature;
2641         if (get().type != GrLexemeType.leftParenthesis)
2642             return outSignature;
2643         checkAdvance();
2644         if (get().type == GrLexemeType.rightParenthesis) {
2645             checkAdvance();
2646             return outSignature;
2647         }
2648         for (;;) {
2649             outSignature ~= parseType();
2650 
2651             const GrLexeme lex = get();
2652             if (lex.type == GrLexemeType.rightParenthesis) {
2653                 checkAdvance();
2654                 break;
2655             }
2656             else if (lex.type != GrLexemeType.comma)
2657                 logError("types should be separated by a comma",
2658                         "expected `,`, found `" ~ grGetPrettyLexemeType(lex.type) ~ "`");
2659             checkAdvance();
2660         }
2661         return outSignature;
2662     }
2663 
2664     private void parseMainDeclaration(bool isPublic) {
2665         if (isPublic)
2666             logError("adding `pub` before `main` is redundant", "main is already public");
2667         checkAdvance();
2668         preBeginFunction("main", get().fileId, [], [], false, [], false, false, true);
2669         skipBlock();
2670         preEndFunction();
2671     }
2672 
2673     private void parseEventDeclaration(bool isPublic) {
2674         if (isPublic)
2675             logError("adding `pub` before `event` is redundant", "event is already public");
2676         checkAdvance();
2677         if (get().type != GrLexemeType.identifier)
2678             logError("expected identifier, found `" ~ grGetPrettyLexemeType(get()
2679                     .type) ~ "`", "missing identifier");
2680         string name = get().svalue;
2681         string[] inputs;
2682         checkAdvance();
2683         GrType[] signature = parseInSignature(inputs);
2684         preBeginFunction(name, get().fileId, signature, inputs, false, [], false, true, true);
2685         skipBlock();
2686         preEndFunction();
2687     }
2688 
2689     private void parseTaskDeclaration(bool isPublic) {
2690         checkAdvance();
2691         string[] templateVariables = parseTemplateVariables();
2692         if (get().type != GrLexemeType.identifier)
2693             logError("expected identifier, found `" ~ grGetPrettyLexemeType(get()
2694                     .type) ~ "`", "missing identifier");
2695 
2696         string name = get().svalue;
2697         checkAdvance();
2698 
2699         GrTemplateFunction temp = new GrTemplateFunction;
2700         temp.isTask = true;
2701         temp.name = name;
2702         temp.templateVariables = templateVariables;
2703         temp.fileId = get().fileId;
2704         temp.isPublic = isPublic;
2705         temp.lexPosition = current;
2706 
2707         if (templateVariables.length)
2708             templatedFunctions ~= temp;
2709         else
2710             instanciatedFunctions ~= parseTemplatedFunctionDeclaration(temp, []);
2711 
2712         if (get().type == GrLexemeType.leftParenthesis)
2713             skipParenthesis();
2714         skipBlock();
2715     }
2716 
2717     private void parseFunctionDeclaration(bool isPublic) {
2718         checkAdvance();
2719         string[] templateVariables = parseTemplateVariables();
2720         string name;
2721         bool isConversion;
2722         if (get().type == GrLexemeType.as) {
2723             name = "@as";
2724             isConversion = true;
2725         }
2726         else {
2727             if (get().type != GrLexemeType.identifier)
2728                 logError("expected identifier, found `" ~ grGetPrettyLexemeType(get()
2729                         .type) ~ "`", "missing identifier");
2730             name = get().svalue;
2731             if (name == "operator") {
2732                 checkAdvance();
2733                 if (get().type >= GrLexemeType.add && get().type <= GrLexemeType.not) {
2734                     name = "@op_" ~ grGetPrettyLexemeType(get().type);
2735                 }
2736                 else
2737                     logError("can't override `" ~ grGetPrettyLexemeType(get()
2738                             .type) ~ "` operator", "this operator can't be overriden");
2739             }
2740         }
2741         checkAdvance();
2742 
2743         GrTemplateFunction temp = new GrTemplateFunction;
2744         temp.isTask = false;
2745         temp.name = name;
2746         temp.isConversion = isConversion;
2747         temp.templateVariables = templateVariables;
2748         temp.fileId = get().fileId;
2749         temp.isPublic = isPublic;
2750         temp.lexPosition = current;
2751 
2752         if (templateVariables.length)
2753             templatedFunctions ~= temp;
2754         else
2755             instanciatedFunctions ~= parseTemplatedFunctionDeclaration(temp, []);
2756 
2757         if (get().type == GrLexemeType.leftParenthesis)
2758             skipParenthesis();
2759         if (get().type == GrLexemeType.leftParenthesis)
2760             skipParenthesis();
2761         skipBlock();
2762     }
2763 
2764     private void parseTemplateDeclaration(bool isPublic) {
2765         checkAdvance();
2766         if (get().type != GrLexemeType.lesser)
2767             logError("missing template signature",
2768                     "expected `<`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
2769 
2770         GrType[] templateList = parseTemplateSignature();
2771 
2772         if (get().type != GrLexemeType.identifier)
2773             logError("missing function or task",
2774                     "expected a function or task name, found `" ~ grGetPrettyLexemeType(get()
2775                         .type) ~ "`");
2776         string name = get().svalue;
2777 
2778         if (name == "operator") {
2779             checkAdvance();
2780             if (get().type >= GrLexemeType.add && get().type <= GrLexemeType.not) {
2781                 name = "@op_" ~ grGetPrettyLexemeType(get().type);
2782             }
2783             else
2784                 logError("can't override `" ~ grGetPrettyLexemeType(get()
2785                         .type) ~ "` operator", "this operator can't be overriden");
2786         }
2787 
2788         const uint fileId = get().fileId;
2789         checkAdvance();
2790 
2791         if (!templateList.length)
2792             logError("empty template signature", "the template signature can't be empty", "", -1);
2793 
2794         if (get().type != GrLexemeType.semicolon)
2795             logError("missing semicolon after template declaration",
2796                     "expected `;`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
2797         checkAdvance();
2798 
2799         foreach (GrTemplateFunction temp; templatedFunctions) {
2800             if (temp.name == name && (temp.fileId == fileId || temp.isPublic)
2801                     && temp.templateVariables.length == templateList.length) {
2802                 GrFunction func = parseTemplatedFunctionDeclaration(temp, templateList);
2803                 func.isPublic = isPublic;
2804                 instanciatedFunctions ~= func;
2805             }
2806         }
2807     }
2808 
2809     private GrFunction parseTemplatedFunctionDeclaration(GrTemplateFunction temp,
2810             GrType[] templateList) {
2811         const auto lastPosition = current;
2812         current = temp.lexPosition;
2813 
2814         for (int i; i < temp.templateVariables.length; ++i) {
2815             _data.addTemplateAlias(temp.templateVariables[i], templateList[i],
2816                     temp.fileId, temp.isPublic);
2817         }
2818 
2819         string[] inputs;
2820         GrType[] inSignature = parseInSignature(inputs);
2821         GrType[] outSignature;
2822 
2823         if (!temp.isTask) {
2824             //Return Type.
2825             if (temp.isConversion) {
2826                 if (inSignature.length != 1uL) {
2827                     const string argStr = to!string(inSignature.length) ~ (inSignature.length > 1
2828                             ? " parameters" : " parameter");
2829                     logError("a conversion must have only one parameter",
2830                             "expected 1 parameter, found " ~ argStr);
2831                 }
2832                 outSignature = parseOutSignature();
2833                 if (outSignature.length != 1uL) {
2834                     const string argStr = to!string(outSignature.length) ~ (outSignature.length > 1
2835                             ? " return values" : " return value");
2836                     logError("a conversion must have only one return value",
2837                             "expected 1 return value, found " ~ argStr);
2838                 }
2839 
2840                 inSignature ~= outSignature[0];
2841             }
2842             else
2843                 outSignature = parseOutSignature();
2844         }
2845 
2846         GrFunction func = new GrFunction;
2847         func.isTask = temp.isTask;
2848         func.name = temp.name;
2849         func.inputVariables = inputs;
2850         func.inSignature = inSignature;
2851         func.outSignature = outSignature;
2852         func.fileId = temp.fileId;
2853         func.isPublic = temp.isPublic;
2854         func.lexPosition = current;
2855         func.templateVariables = temp.templateVariables;
2856         func.templateSignature = templateList;
2857 
2858         _data.clearTemplateAliases();
2859         current = lastPosition;
2860         return func;
2861     }
2862 
2863     private GrType parseAnonymousFunction(bool isTask) {
2864         checkAdvance();
2865         string[] inputs;
2866         GrType[] outSignature;
2867         GrType[] inSignature = parseInSignature(inputs);
2868 
2869         if (!isTask) {
2870             //Return Type.
2871             outSignature = parseOutSignature();
2872         }
2873         preBeginFunction("$anon", get().fileId, inSignature, inputs, isTask, outSignature, true);
2874         openDeferrableSection();
2875         parseBlock();
2876 
2877         if (isTask) {
2878             if (!currentFunction.instructions.length
2879                     || currentFunction.instructions[$ - 1].opcode != GrOpcode.kill_)
2880                 addKill();
2881         }
2882         else {
2883             if (!outSignature.length) {
2884                 if (!currentFunction.instructions.length
2885                         || currentFunction.instructions[$ - 1].opcode != GrOpcode.return_)
2886                     addReturn();
2887             }
2888             else {
2889                 if (!currentFunction.instructions.length
2890                         || currentFunction.instructions[$ - 1].opcode != GrOpcode.return_)
2891                     logError("the function is missing a return at the end of the scope",
2892                             "missing `return`");
2893             }
2894         }
2895 
2896         closeDeferrableSection();
2897         registerDeferBlocks();
2898 
2899         endFunction();
2900 
2901         GrType functionType = isTask ? GrBaseType.task : GrBaseType.function_;
2902         functionType.mangledType = grMangleSignature(inSignature);
2903         functionType.mangledReturnType = grMangleSignature(outSignature);
2904 
2905         return functionType;
2906     }
2907 
2908     /**
2909     Parse either multiple lines between `{` and `}` or a single expression.
2910     */
2911     private void parseBlock(bool changeOptimizationBlockLevel = false) {
2912         if (changeOptimizationBlockLevel)
2913             _isAssignationOptimizable = false;
2914         bool isMultiline;
2915         if (get().type == GrLexemeType.leftCurlyBrace) {
2916             isMultiline = true;
2917             if (!checkAdvance())
2918                 logError("unexpected end of file",
2919                         "expected `}`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
2920         }
2921         openBlock();
2922 
2923         void parseStatement() {
2924             switch (get().type) with (GrLexemeType) {
2925             case semicolon:
2926             case rightCurlyBrace:
2927                 advance();
2928                 break;
2929             case leftCurlyBrace:
2930                 parseBlock();
2931                 break;
2932             case defer:
2933                 parseDeferStatement();
2934                 break;
2935             case if_:
2936             case unless:
2937                 parseIfStatement();
2938                 break;
2939             case switch_:
2940                 parseSwitchStatement();
2941                 break;
2942             case select:
2943                 parseSelectStatement();
2944                 break;
2945             case until:
2946             case while_:
2947                 parseWhileStatement();
2948                 break;
2949             case do_:
2950                 parseDoWhileStatement();
2951                 break;
2952             case for_:
2953                 parseForStatement();
2954                 break;
2955             case loop:
2956                 parseLoopStatement();
2957                 break;
2958             case raise_:
2959                 parseRaiseStatement();
2960                 break;
2961             case try_:
2962                 parseExceptionHandler();
2963                 break;
2964             case return_:
2965                 parseReturnStatement();
2966                 break;
2967             case kill:
2968                 parseKill();
2969                 break;
2970             case killAll:
2971                 parseKillAll();
2972                 break;
2973             case yield:
2974                 parseYield();
2975                 break;
2976             case continue_:
2977                 parseContinue();
2978                 break;
2979             case break_:
2980                 parseBreak();
2981                 break;
2982             case intType: .. case autoType:
2983                 if (isDeclaration())
2984                     parseLocalDeclaration();
2985                 else
2986                     goto default;
2987                 break;
2988             case identifier:
2989                 if (_data.isTypeDeclared(get().svalue, get().fileId, false)
2990                         && get(1).type != GrLexemeType.leftParenthesis)
2991                     parseLocalDeclaration();
2992                 else
2993                     goto default;
2994                 break;
2995             default:
2996                 parseExpression();
2997                 break;
2998             }
2999         }
3000 
3001         if (isMultiline) {
3002             while (!isEnd()) {
3003                 if (get().type == GrLexemeType.rightCurlyBrace)
3004                     break;
3005                 parseStatement();
3006             }
3007         }
3008         else {
3009             if (get().type != GrLexemeType.semicolon)
3010                 parseStatement();
3011         }
3012 
3013         if (isMultiline) {
3014             if (get().type != GrLexemeType.rightCurlyBrace)
3015                 logError("missing curly braces",
3016                         "expected `}`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3017             checkAdvance();
3018         }
3019         closeBlock();
3020         if (changeOptimizationBlockLevel)
3021             _isAssignationOptimizable = false;
3022     }
3023 
3024     private bool isDeclaration() {
3025         const auto tempPos = current;
3026         isTypeChecking = true;
3027         if (get().type == GrLexemeType.autoType)
3028             checkAdvance();
3029         else
3030             parseType(false);
3031         isTypeChecking = false;
3032         bool isDecl;
3033         if (get().type == GrLexemeType.identifier)
3034             isDecl = true;
3035         current = tempPos;
3036         return isDecl;
3037     }
3038 
3039     private void skipBlock() {
3040         bool isMultiline;
3041         if (get().type == GrLexemeType.leftCurlyBrace) {
3042             isMultiline = true;
3043             if (!checkAdvance())
3044                 logError("unexpected end of file",
3045                         "expected `}`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3046         }
3047         openBlock();
3048 
3049         void skipStatement() {
3050             switch (get().type) with (GrLexemeType) {
3051             case leftParenthesis:
3052                 skipParenthesis();
3053                 break;
3054             case leftBracket:
3055                 skipBrackets();
3056                 break;
3057             case leftCurlyBrace:
3058                 skipBlock();
3059                 break;
3060             case defer:
3061                 checkAdvance();
3062                 skipBlock();
3063                 break;
3064             case switch_:
3065                 checkAdvance();
3066                 skipParenthesis();
3067                 while (get().type == GrLexemeType.case_) {
3068                     checkAdvance();
3069                     if (get().type == GrLexemeType.leftParenthesis)
3070                         skipParenthesis();
3071                     skipBlock();
3072                 }
3073                 break;
3074             case if_:
3075             case unless:
3076                 checkAdvance();
3077                 skipParenthesis();
3078                 skipBlock();
3079                 break;
3080             case select:
3081                 checkAdvance();
3082                 while (get().type == GrLexemeType.case_) {
3083                     checkAdvance();
3084                     if (get().type == GrLexemeType.leftParenthesis)
3085                         skipParenthesis();
3086                     skipBlock();
3087                 }
3088                 break;
3089             case until:
3090             case while_:
3091                 checkAdvance();
3092                 skipBlock();
3093                 break;
3094             case do_:
3095                 checkAdvance();
3096                 skipBlock();
3097                 checkAdvance();
3098                 skipParenthesis();
3099                 break;
3100             case for_:
3101                 checkAdvance();
3102                 skipParenthesis();
3103                 skipBlock();
3104                 break;
3105             case loop:
3106                 checkAdvance();
3107                 if (get().type == GrLexemeType.leftParenthesis)
3108                     skipParenthesis();
3109                 skipBlock();
3110                 break;
3111             case raise_:
3112                 checkAdvance();
3113                 skipBlock();
3114                 break;
3115             case try_:
3116                 checkAdvance();
3117                 skipBlock();
3118                 if (get().type == GrLexemeType.catch_) {
3119                     checkAdvance();
3120                     skipParenthesis();
3121                     skipBlock();
3122                 }
3123                 break;
3124             case yield:
3125                 checkAdvance();
3126                 break;
3127             case return_:
3128                 checkAdvance();
3129                 skipBlock();
3130                 break;
3131             default:
3132                 checkAdvance();
3133                 break;
3134             }
3135         }
3136 
3137         if (isMultiline) {
3138             while (!isEnd()) {
3139                 if (get().type == GrLexemeType.rightCurlyBrace)
3140                     break;
3141                 switch (get().type) with (GrLexemeType) {
3142                 case leftParenthesis:
3143                     skipParenthesis();
3144                     break;
3145                 case leftBracket:
3146                     skipBrackets();
3147                     break;
3148                 case leftCurlyBrace:
3149                     skipBlock();
3150                     break;
3151                 default:
3152                     checkAdvance();
3153                     break;
3154                 }
3155             }
3156 
3157             if (get().type != GrLexemeType.rightCurlyBrace)
3158                 logError("missing curly braces",
3159                         "expected `}`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3160             checkAdvance();
3161         }
3162         else {
3163             if (get().type != GrLexemeType.semicolon)
3164                 skipStatement();
3165         }
3166         closeBlock();
3167     }
3168 
3169     private void parseKill() {
3170         if (!currentFunction.instructions.length
3171                 || currentFunction.instructions[$ - 1].opcode != GrOpcode.kill_)
3172             addKill();
3173         advance();
3174     }
3175 
3176     private void parseKillAll() {
3177         if (!currentFunction.instructions.length
3178                 || currentFunction.instructions[$ - 1].opcode != GrOpcode.killAll_)
3179             addKillAll();
3180         advance();
3181     }
3182 
3183     private void parseYield() {
3184         addInstruction(GrOpcode.yield, 0u);
3185         advance();
3186     }
3187 
3188     //Exception handling
3189     private void parseRaiseStatement() {
3190         advance();
3191         GrType type = parseSubExpression(GR_SUBEXPR_TERMINATE_SEMICOLON | GR_SUBEXPR_EXPECTING_VALUE)
3192             .type;
3193         checkAdvance();
3194         convertType(type, grString);
3195         addInstruction(GrOpcode.raise_);
3196         checkDeferStatement();
3197     }
3198 
3199     private void parseExceptionHandler() {
3200         advance();
3201 
3202         const auto tryPosition = currentFunction.instructions.length;
3203         addInstruction(GrOpcode.try_);
3204 
3205         parseBlock();
3206 
3207         const uint fileId = get().fileId;
3208         if (get().type != GrLexemeType.catch_)
3209             logError("a `try` must always be followed by a `catch`",
3210                     "expected `catch`, fount `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3211         advance();
3212 
3213         if (get().type != GrLexemeType.leftParenthesis)
3214             logError("missing parentheses after `catch`",
3215                     "expected `(`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3216         advance();
3217 
3218         if (get().type != GrLexemeType.identifier)
3219             logError("missing identifier",
3220                     "expected `identifier`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3221         GrVariable errVariable = registerLocalVariable(get().svalue, grString);
3222 
3223         advance();
3224         if (get().type != GrLexemeType.rightParenthesis)
3225             logError("missing parentheses",
3226                     "expected `)`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3227         advance();
3228 
3229         const auto catchPosition = currentFunction.instructions.length;
3230         addInstruction(GrOpcode.catch_);
3231 
3232         addInstruction(GrOpcode.globalPop_string);
3233         addSetInstruction(errVariable, fileId, grString);
3234 
3235         parseBlock(true);
3236 
3237         const auto endPosition = currentFunction.instructions.length;
3238 
3239         setInstruction(GrOpcode.try_, cast(uint) tryPosition,
3240                 cast(uint)(catchPosition - tryPosition), true);
3241         setInstruction(GrOpcode.catch_, cast(uint) catchPosition,
3242                 cast(uint)(endPosition - catchPosition), true);
3243     }
3244 
3245     //defer
3246     private void openDeferrableSection() {
3247         auto deferrableSection = new GrDeferrableSection;
3248         deferrableSection.deferInitPositions = cast(uint) currentFunction.instructions.length;
3249         currentFunction.deferrableSections ~= deferrableSection;
3250 
3251         currentFunction.isDeferrableSectionLocked.length++;
3252     }
3253 
3254     private void closeDeferrableSection() {
3255         if (!currentFunction.deferrableSections.length)
3256             throw new Exception("attempting to close a non-existing function");
3257 
3258         foreach (deferBlock; currentFunction.deferrableSections[$ - 1].deferredBlocks) {
3259             currentFunction.registeredDeferBlocks ~= deferBlock;
3260         }
3261 
3262         currentFunction.deferrableSections.length--;
3263         currentFunction.isDeferrableSectionLocked.length--;
3264     }
3265 
3266     private void parseDeferStatement() {
3267         if (currentFunction.isDeferrableSectionLocked[$ - 1])
3268             logError("`defer` inside another `defer`", "can't `defer` inside another `defer`");
3269         advance();
3270 
3271         //Register the position of the block for a late parsing.
3272         GrDeferBlock deferBlock = new GrDeferBlock;
3273         deferBlock.position = cast(uint) currentFunction.instructions.length;
3274         deferBlock.parsePosition = current;
3275         deferBlock.scopeLevel = scopeLevel;
3276         currentFunction.deferrableSections[$ - 1].deferredBlocks ~= deferBlock;
3277 
3278         addInstruction(GrOpcode.defer);
3279 
3280         //Parse the deferred block at the end of the outer block.
3281         skipBlock();
3282     }
3283 
3284     private void checkDeferStatement() {
3285         if (currentFunction.isDeferrableSectionLocked[$ - 1]) {
3286             GrLexemeType type = get().type;
3287             logError("`" ~ grGetPrettyLexemeType(type) ~ "` inside a defer",
3288                     "can't `" ~ grGetPrettyLexemeType(type) ~ "` inside a defer");
3289         }
3290     }
3291 
3292     private void registerDeferBlocks() {
3293         const auto tempParsePosition = current;
3294         const auto startDeferPos = cast(uint) currentFunction.instructions.length;
3295 
3296         const int tempScopeLevel = scopeLevel;
3297         while (currentFunction.registeredDeferBlocks.length) {
3298             GrDeferBlock deferBlock = currentFunction.registeredDeferBlocks[0];
3299             currentFunction.registeredDeferBlocks = currentFunction.registeredDeferBlocks[1 .. $];
3300 
3301             setInstruction(GrOpcode.defer, deferBlock.position,
3302                     cast(int)(currentFunction.instructions.length - deferBlock.position), true);
3303             current = deferBlock.parsePosition;
3304             scopeLevel = deferBlock.scopeLevel;
3305 
3306             currentFunction.isDeferrableSectionLocked[$ - 1] = true;
3307             parseBlock(true);
3308             currentFunction.isDeferrableSectionLocked[$ - 1] = false;
3309 
3310             addInstruction(GrOpcode.unwind);
3311         }
3312         currentFunction.registeredDeferBlocks.length = 0;
3313         current = tempParsePosition;
3314         scopeLevel = tempScopeLevel;
3315     }
3316 
3317     //Break
3318     private void openBreakableSection() {
3319         breaksJumps ~= [null];
3320         _isAssignationOptimizable = false;
3321     }
3322 
3323     private void closeBreakableSection() {
3324         if (!breaksJumps.length)
3325             throw new Exception("attempting to close a non-existing function");
3326 
3327         uint[] breaks = breaksJumps[$ - 1];
3328         breaksJumps.length--;
3329 
3330         foreach (position; breaks)
3331             setInstruction(GrOpcode.jump, position,
3332                     cast(int)(currentFunction.instructions.length - position), true);
3333         _isAssignationOptimizable = false;
3334     }
3335 
3336     private void parseBreak() {
3337         if (!breaksJumps.length)
3338             logError("`break` outside of a loop", "can't `break` outside of a loop");
3339 
3340         breaksJumps[$ - 1] ~= cast(uint) currentFunction.instructions.length;
3341         addInstruction(GrOpcode.jump);
3342         advance();
3343     }
3344 
3345     //Continue
3346     private void openContinuableSection() {
3347         continuesJumps.length++;
3348         _isAssignationOptimizable = false;
3349     }
3350 
3351     private void closeContinuableSection() {
3352         if (!continuesJumps.length)
3353             throw new Exception("attempting to close a non-existing function");
3354 
3355         uint[] continues = continuesJumps[$ - 1];
3356         const uint destination = continuesDestinations[$ - 1];
3357         continuesJumps.length--;
3358         continuesDestinations.length--;
3359 
3360         foreach (position; continues)
3361             setInstruction(GrOpcode.jump, position, cast(int)(destination - position), true);
3362         _isAssignationOptimizable = false;
3363     }
3364 
3365     private void setContinuableSectionDestination() {
3366         continuesDestinations ~= cast(uint) currentFunction.instructions.length;
3367     }
3368 
3369     private void parseContinue() {
3370         if (!continuesJumps.length)
3371             logError("`continue` outside of a loop", "can't `continue` outside of a loop");
3372 
3373         continuesJumps[$ - 1] ~= cast(uint) currentFunction.instructions.length;
3374         addInstruction(GrOpcode.jump);
3375         advance();
3376     }
3377 
3378     private void parseGlobalDeclaration(bool isPublic) {
3379         //GrVariable type
3380         GrType type = GrBaseType.void_;
3381         bool isAuto;
3382 
3383         if (get().type == GrLexemeType.autoType) {
3384             isAuto = true;
3385             checkAdvance();
3386         }
3387         else
3388             type = parseType();
3389 
3390         GrVariable[] lvalues;
3391         do {
3392             if (get().type == GrLexemeType.comma)
3393                 checkAdvance();
3394             //Identifier
3395             if (get().type != GrLexemeType.identifier)
3396                 logError("expected identifier, found `" ~ grGetPrettyLexemeType(get()
3397                         .type) ~ "`", "missing identifier");
3398 
3399             string identifier = get().svalue;
3400 
3401             //Registering
3402             GrVariable lvalue = registerGlobalVariable(identifier, type, isAuto, isPublic);
3403             lvalues ~= lvalue;
3404 
3405             checkAdvance();
3406         }
3407         while (get().type == GrLexemeType.comma);
3408 
3409         parseAssignList(lvalues, true);
3410     }
3411 
3412     //Type Identifier [= EXPRESSION] ;
3413     private void parseLocalDeclaration() {
3414         //GrVariable type
3415         GrType type = GrBaseType.void_;
3416         bool isAuto;
3417         if (get().type == GrLexemeType.autoType) {
3418             isAuto = true;
3419             checkAdvance();
3420         }
3421         else
3422             type = parseType();
3423 
3424         GrVariable[] lvalues;
3425         do {
3426             if (get().type == GrLexemeType.comma)
3427                 checkAdvance();
3428             //Identifier
3429             if (get().type != GrLexemeType.identifier)
3430                 logError("expected identifier, found `" ~ grGetPrettyLexemeType(get()
3431                         .type) ~ "`", "missing identifier");
3432 
3433             string identifier = get().svalue;
3434 
3435             //Registering
3436             GrVariable lvalue = registerLocalVariable(identifier, type);
3437             lvalue.isAuto = isAuto;
3438             lvalues ~= lvalue;
3439 
3440             //A composite type does not need to be initialized.
3441             if (lvalue.type == GrBaseType.class_)
3442                 lvalue.isInitialized = true;
3443 
3444             checkAdvance();
3445         }
3446         while (get().type == GrLexemeType.comma);
3447 
3448         parseAssignList(lvalues, true);
3449     }
3450 
3451     private GrType parseFunctionReturnType() {
3452         GrType returnType = GrBaseType.void_;
3453         if (get().isType) {
3454             switch (get().type) with (GrLexemeType) {
3455             case intType:
3456                 returnType = GrType(GrBaseType.int_);
3457                 break;
3458             case floatType:
3459                 returnType = GrType(GrBaseType.float_);
3460                 break;
3461             case boolType:
3462                 returnType = GrType(GrBaseType.bool_);
3463                 break;
3464             case stringType:
3465                 returnType = GrType(GrBaseType.string_);
3466                 break;
3467             case arrayType:
3468                 returnType = GrType(GrBaseType.array_);
3469                 break;
3470             case functionType:
3471                 GrType type = GrBaseType.function_;
3472                 checkAdvance();
3473                 string[] temp;
3474                 type.mangledType = grMangleSignature(parseInSignature(temp, true));
3475                 returnType = type;
3476                 break;
3477             case taskType:
3478                 GrType type = GrBaseType.task;
3479                 checkAdvance();
3480                 string[] temp;
3481                 type.mangledType = grMangleSignature(parseInSignature(temp, true));
3482                 returnType = type;
3483                 break;
3484             default:
3485                 logError("`" ~ grGetPrettyLexemeType(get().type) ~ "` is not a valid return type",
3486                         "`" ~ grGetPrettyLexemeType(get().type) ~ "` is not a valid return type");
3487             }
3488             checkAdvance();
3489         }
3490 
3491         return returnType;
3492     }
3493 
3494     /**
3495     ---
3496     if(SUBEXPR) BLOCK
3497     else if(SUBEXPR) BLOCK
3498     else unless(SUBEXPR) BLOCK
3499     else(SUBEXPR) BLOCK
3500     ---
3501     */
3502     private void parseIfStatement() {
3503         bool isNegative = get().type == GrLexemeType.unless;
3504         advance();
3505         if (get().type != GrLexemeType.leftParenthesis)
3506             logError("missing parentheses after `if`",
3507                     "expected `(`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3508 
3509         advance();
3510         GrSubExprResult result = parseSubExpression();
3511         convertType(result.type, grBool, get().fileId);
3512         advance();
3513 
3514         uint jumpPosition = cast(uint) currentFunction.instructions.length;
3515         //Jumps to if(0) for "if", if(!= 0) for "unless".
3516         addInstruction(isNegative ? GrOpcode.jumpNotEqual : GrOpcode.jumpEqual);
3517 
3518         parseBlock(true); //{ .. }
3519 
3520         //If(1){}, jumps out.
3521         uint[] exitJumps;
3522         if (get().type == GrLexemeType.else_) {
3523             exitJumps ~= cast(uint) currentFunction.instructions.length;
3524             addInstruction(GrOpcode.jump);
3525         }
3526 
3527         //Jumps to if(0) for "if", if(!= 0) for "unless".
3528         setInstruction(isNegative ? GrOpcode.jumpNotEqual : GrOpcode.jumpEqual, jumpPosition,
3529                 cast(int)(currentFunction.instructions.length - jumpPosition), true);
3530 
3531         bool isElseIf;
3532         do {
3533             isElseIf = false;
3534             if (get().type == GrLexemeType.else_) {
3535                 checkAdvance();
3536                 if (get().type == GrLexemeType.if_ || get().type == GrLexemeType.unless) {
3537                     isNegative = get().type == GrLexemeType.unless;
3538                     isElseIf = true;
3539                     checkAdvance();
3540                     if (get().type != GrLexemeType.leftParenthesis)
3541                         logError("missing parentheses after `if`",
3542                                 "expected `(`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3543                     checkAdvance();
3544 
3545                     parseSubExpression();
3546                     advance();
3547 
3548                     jumpPosition = cast(uint) currentFunction.instructions.length;
3549                     //Jumps to if(0) for "if", if(!= 0) for "unless".
3550                     addInstruction(isNegative ? GrOpcode.jumpNotEqual : GrOpcode.jumpEqual);
3551 
3552                     parseBlock(true); //{ .. }
3553 
3554                     //If(1){}, jumps out.
3555                     exitJumps ~= cast(uint) currentFunction.instructions.length;
3556                     addInstruction(GrOpcode.jump);
3557 
3558                     //Jumps to if(0) for "if", if(!= 0) for "unless".
3559                     setInstruction(isNegative ? GrOpcode.jumpNotEqual : GrOpcode.jumpEqual, jumpPosition,
3560                             cast(int)(currentFunction.instructions.length - jumpPosition), true);
3561                 }
3562                 else
3563                     parseBlock(true);
3564             }
3565         }
3566         while (isElseIf);
3567 
3568         foreach (uint position; exitJumps)
3569             setInstruction(GrOpcode.jump, position,
3570                     cast(int)(currentFunction.instructions.length - position), true);
3571     }
3572 
3573     private GrType parseChannelBuilder() {
3574         GrType chanType = GrBaseType.chan;
3575         int channelSize = 1;
3576 
3577         checkAdvance();
3578         if (get().type != GrLexemeType.leftParenthesis)
3579             logError("missing parentheses after `chan`",
3580                     "expected `(`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3581         checkAdvance();
3582         GrType subType = parseType();
3583 
3584         GrLexeme lex = get();
3585         if (lex.type == GrLexemeType.comma) {
3586             checkAdvance();
3587             lex = get();
3588             if (lex.type != GrLexemeType.integer)
3589                 logError("a channel size must be a positive int value",
3590                         "expected `int`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3591             channelSize = lex.ivalue > int.max ? 1 : cast(int) lex.ivalue;
3592             if (channelSize < 1)
3593                 logError("the channel size must be one or higher",
3594                         "expected at least a size of 1, found " ~ to!string(channelSize));
3595             checkAdvance();
3596         }
3597         else if (lex.type != GrLexemeType.rightParenthesis) {
3598             logError("missing `,` or `)` inside channel signature",
3599                     "expected `,` or `)`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3600         }
3601         lex = get();
3602         if (lex.type != GrLexemeType.rightParenthesis)
3603             logError("missing parentheses after the channel signature",
3604                     "expected `)`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3605         checkAdvance();
3606         chanType.mangledType = grMangleSignature([subType]);
3607 
3608         final switch (subType.baseType) with (GrBaseType) {
3609         case int_:
3610         case bool_:
3611         case function_:
3612         case task:
3613         case enum_:
3614             addInstruction(GrOpcode.channel_int, channelSize);
3615             break;
3616         case float_:
3617             addInstruction(GrOpcode.channel_float, channelSize);
3618             break;
3619         case string_:
3620             addInstruction(GrOpcode.channel_string, channelSize);
3621             break;
3622         case class_:
3623         case array_:
3624         case foreign:
3625         case chan:
3626         case reference:
3627             addInstruction(GrOpcode.channel_object, channelSize);
3628             break;
3629         case void_:
3630         case null_:
3631         case internalTuple:
3632             logError("a channel can't be of type `" ~ grGetPrettyType(grChannel(subType)) ~ "`",
3633                     "invalid channel type");
3634         }
3635         return chanType;
3636     }
3637 
3638     /**
3639     ---
3640     switch(SUBEXPR)
3641     case(SUBEXPR) BLOCK
3642     case(SUBEXPR) BLOCK
3643     case() BLOCK
3644     ---
3645     */
3646     private void parseSwitchStatement() {
3647         advance();
3648         if (get().type != GrLexemeType.leftParenthesis)
3649             logError("missing parentheses after `switch`",
3650                     "expected `(`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3651 
3652         advance();
3653         const uint fileId = get().fileId;
3654         GrType switchType = parseSubExpression().type;
3655         GrVariable switchVar = registerSpecialVariable("switch", switchType);
3656         addSetInstruction(switchVar, fileId);
3657         advance();
3658 
3659         /* A switch is breakable. */
3660         openBreakableSection();
3661         uint[] exitJumps;
3662         uint jumpPosition, casePosition, defaultCasePosition, defaultCaseKeywordPosition;
3663         bool hasCase, hasDefaultCase;
3664 
3665         while (get().type == GrLexemeType.case_) {
3666             casePosition = current;
3667             advance();
3668             if (get().type != GrLexemeType.leftParenthesis)
3669                 logError("missing parentheses after `case`",
3670                         "expected `(`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3671             advance();
3672             if (get().type == GrLexemeType.rightParenthesis) {
3673                 if (hasDefaultCase)
3674                     logError("there must be only up to one default case per `switch`",
3675                             "default `case` already defined", "",
3676                             casePosition - current, "previous default `case` definition",
3677                             defaultCaseKeywordPosition);
3678                 advance();
3679                 hasDefaultCase = true;
3680                 defaultCasePosition = current;
3681                 defaultCaseKeywordPosition = casePosition;
3682                 skipBlock();
3683             }
3684             else {
3685                 hasCase = true;
3686                 addGetInstruction(switchVar);
3687                 GrType caseType = parseSubExpression().type;
3688                 addBinaryOperator(GrLexemeType.equal, switchType, caseType, fileId);
3689                 advance();
3690 
3691                 jumpPosition = cast(uint) currentFunction.instructions.length;
3692                 //Jumps to if(0).
3693                 addInstruction(GrOpcode.jumpEqual);
3694 
3695                 parseBlock(true);
3696 
3697                 exitJumps ~= cast(uint) currentFunction.instructions.length;
3698                 addInstruction(GrOpcode.jump);
3699 
3700                 //Jumps to if(0).
3701                 setInstruction(GrOpcode.jumpEqual, jumpPosition,
3702                         cast(int)(currentFunction.instructions.length - jumpPosition), true);
3703             }
3704         }
3705 
3706         if (hasDefaultCase) {
3707             const uint tmp = current;
3708             current = defaultCasePosition;
3709             parseBlock(true);
3710             current = tmp;
3711         }
3712 
3713         /* A switch is breakable. */
3714         closeBreakableSection();
3715 
3716         foreach (uint position; exitJumps)
3717             setInstruction(GrOpcode.jump, position,
3718                     cast(int)(currentFunction.instructions.length - position), true);
3719     }
3720 
3721     /**
3722     ---
3723     select
3724     case(SUBEXPR) BLOCK
3725     case(SUBEXPR) BLOCK
3726     case() BLOCK
3727     ---
3728     */
3729     private void parseSelectStatement() {
3730         advance();
3731 
3732         /* A select is breakable. */
3733         openBreakableSection();
3734         uint[] exitJumps;
3735         uint jumpPosition, casePosition, defaultCasePosition, defaultCaseKeywordPosition;
3736         bool hasCase, hasDefaultCase;
3737         uint startJump = cast(uint) currentFunction.instructions.length;
3738 
3739         addInstruction(GrOpcode.startSelectChannel);
3740         while (get().type == GrLexemeType.case_) {
3741             casePosition = current;
3742             advance();
3743             if (get().type != GrLexemeType.leftParenthesis)
3744                 logError("missing parentheses after `case`",
3745                         "expected `(`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3746             advance();
3747 
3748             if (get().type == GrLexemeType.rightParenthesis) {
3749                 if (hasDefaultCase)
3750                     logError("there must be only up to one default case per `switch`",
3751                             "default `case` already defined", "",
3752                             casePosition - current, "previous default `case` definition",
3753                             defaultCaseKeywordPosition);
3754                 advance();
3755                 hasDefaultCase = true;
3756                 defaultCasePosition = current;
3757                 defaultCaseKeywordPosition = casePosition;
3758                 skipBlock();
3759             }
3760             else {
3761                 hasCase = true;
3762                 jumpPosition = cast(uint) currentFunction.instructions.length;
3763                 addInstruction(GrOpcode.tryChannel);
3764                 parseSubExpression();
3765                 advance();
3766 
3767                 addInstruction(GrOpcode.checkChannel);
3768 
3769                 parseBlock(true);
3770 
3771                 exitJumps ~= cast(uint) currentFunction.instructions.length;
3772                 addInstruction(GrOpcode.jump);
3773 
3774                 setInstruction(GrOpcode.tryChannel, jumpPosition,
3775                         cast(int)(currentFunction.instructions.length - jumpPosition), true);
3776             }
3777         }
3778 
3779         if (hasDefaultCase) {
3780             /* With a default case specified, it is processed if no previous case has been processed in the select statement.
3781              * The select statement is not blocking here because at least one case is executed. */
3782             const uint tmp = current;
3783             current = defaultCasePosition;
3784             parseBlock(true);
3785             current = tmp;
3786         }
3787         else {
3788             /* Without default case, the select statement is a blocking operation until one case is processed.
3789              * So, we add a yield then jump back to the beggining of the statement to evaluate the select statement again. */
3790             addInstruction(GrOpcode.yield);
3791             addInstruction(GrOpcode.jump,
3792                     cast(int)(startJump - currentFunction.instructions.length), true);
3793         }
3794 
3795         /* A switch is breakable. */
3796         closeBreakableSection();
3797 
3798         foreach (uint position; exitJumps)
3799             setInstruction(GrOpcode.jump, position,
3800                     cast(int)(currentFunction.instructions.length - position), true);
3801         addInstruction(GrOpcode.endSelectChannel);
3802     }
3803 
3804     /**
3805     ---
3806     while(SUBEXPR)
3807         BLOCK
3808     ---
3809     */
3810     private void parseWhileStatement() {
3811         const bool isNegative = get().type == GrLexemeType.until;
3812         advance();
3813         if (get().type != GrLexemeType.leftParenthesis)
3814             logError("missing parentheses after `case`",
3815                     "expected `(`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3816 
3817         /* While is breakable and continuable. */
3818         openBreakableSection();
3819         openContinuableSection();
3820 
3821         /* Continue jump. */
3822         setContinuableSectionDestination();
3823 
3824         uint conditionPosition, blockPosition = cast(uint) currentFunction.instructions.length;
3825 
3826         advance();
3827         parseSubExpression();
3828 
3829         advance();
3830         conditionPosition = cast(uint) currentFunction.instructions.length;
3831         addInstruction(GrOpcode.jumpEqual);
3832 
3833         parseBlock(true);
3834 
3835         addInstruction(GrOpcode.jump,
3836                 cast(int)(blockPosition - currentFunction.instructions.length), true);
3837         setInstruction(isNegative ? GrOpcode.jumpNotEqual : GrOpcode.jumpEqual, conditionPosition,
3838                 cast(int)(currentFunction.instructions.length - conditionPosition), true);
3839 
3840         /* While is breakable and continuable. */
3841         closeBreakableSection();
3842         closeContinuableSection();
3843     }
3844 
3845     /**
3846     ---
3847     do BLOCK
3848     while(SUBEXPR)
3849     ---
3850     */
3851     private void parseDoWhileStatement() {
3852         advance();
3853 
3854         /* While is breakable and continuable. */
3855         openBreakableSection();
3856         openContinuableSection();
3857 
3858         uint blockPosition = cast(uint) currentFunction.instructions.length;
3859 
3860         parseBlock(true);
3861 
3862         bool isNegative;
3863         if (get().type == GrLexemeType.until)
3864             isNegative = true;
3865         else if (get().type != GrLexemeType.while_)
3866             logError("missing `while` or `until` after the loop",
3867                     "expected `while` or `until`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3868         advance();
3869 
3870         /* Continue jump. */
3871         setContinuableSectionDestination();
3872 
3873         if (get().type != GrLexemeType.leftParenthesis)
3874             logError("missing parentheses after " ~ (isNegative ? "`until`" : "`while`"),
3875                     "expected `(`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3876 
3877         advance();
3878         parseSubExpression();
3879         advance();
3880 
3881         addInstruction(isNegative ? GrOpcode.jumpEqual : GrOpcode.jumpNotEqual,
3882                 cast(int)(blockPosition - currentFunction.instructions.length), true);
3883 
3884         /* While is breakable and continuable. */
3885         closeBreakableSection();
3886         closeContinuableSection();
3887     }
3888 
3889     private GrVariable parseDeclarableArgument() {
3890         GrVariable lvalue;
3891         GrType type = GrBaseType.void_;
3892         bool isAuto, isTyped = true;
3893         switch (get().type) with (GrLexemeType) {
3894         case autoType:
3895             isAuto = true;
3896             checkAdvance();
3897             break;
3898         case intType: .. case chanType:
3899             type = parseType();
3900             break;
3901         case identifier:
3902             if (_data.isTypeDeclared(get().svalue, get().fileId, false))
3903                 type = parseType();
3904             else
3905                 isTyped = false;
3906             break;
3907         default:
3908             logError("a variable definition or reference is expected",
3909                     "a variable or reference is expected, found `" ~ grGetPrettyLexemeType(get()
3910                         .type) ~ "`");
3911             break;
3912         }
3913         GrLexeme identifier = get();
3914         if (identifier.type != GrLexemeType.identifier)
3915             logError("a variable name is expected",
3916                     "a variable name is expected, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3917 
3918         lvalue = registerLocalVariable(identifier.svalue, type);
3919         lvalue.isAuto = isTyped ? isAuto : true;
3920 
3921         //A composite type does not need to be initialized.
3922         if (lvalue.type == GrBaseType.class_)
3923             lvalue.isInitialized = true;
3924 
3925         checkAdvance();
3926         return lvalue;
3927     }
3928 
3929     /**
3930     The for statement takes an iterator and an array.
3931     */
3932     private void parseForStatement() {
3933         advance();
3934         const uint fileId = get().fileId;
3935         if (get().type != GrLexemeType.leftParenthesis)
3936             logError("missing parentheses after `for`",
3937                     "expected `(`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3938 
3939         advance();
3940         currentFunction.openScope();
3941 
3942         GrVariable variable = parseDeclarableArgument();
3943 
3944         if (get().type != GrLexemeType.comma)
3945             logError("missing comma in `for`",
3946                     "expected `,`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
3947         advance();
3948 
3949         //From length to 0
3950         GrType containerType = parseSubExpression().type;
3951 
3952         switch (containerType.baseType) with (GrBaseType) {
3953         case array_: {
3954                 /* Init */
3955                 GrType subType = grUnmangle(containerType.mangledType);
3956                 GrVariable iterator = registerSpecialVariable("iterator", grInt);
3957                 GrVariable index = registerSpecialVariable("index", grInt);
3958                 GrVariable array = registerSpecialVariable("array", containerType);
3959 
3960                 if (variable.isAuto && subType.baseType != GrBaseType.void_) {
3961                     variable.isAuto = false;
3962                     variable.type = subType;
3963                     setVariableRegister(variable);
3964                 }
3965 
3966                 addSetInstruction(array, fileId, containerType, true);
3967                 final switch (subType.baseType) with (GrBaseType) {
3968                 case bool_:
3969                 case int_:
3970                 case function_:
3971                 case task:
3972                 case enum_:
3973                     addInstruction(GrOpcode.length_int);
3974                     break;
3975                 case float_:
3976                     addInstruction(GrOpcode.length_float);
3977                     break;
3978                 case string_:
3979                     addInstruction(GrOpcode.length_string);
3980                     break;
3981                 case array_:
3982                 case class_:
3983                 case foreign:
3984                 case chan:
3985                 case reference:
3986                     addInstruction(GrOpcode.length_object);
3987                     break;
3988                 case void_:
3989                 case null_:
3990                 case internalTuple:
3991                     logError("an array can't be of type `" ~ grGetPrettyType(grArray(subType)) ~ "`",
3992                             "invalid array type");
3993                     break;
3994                 }
3995                 addInstruction(GrOpcode.setupIterator);
3996                 addSetInstruction(iterator, fileId);
3997 
3998                 //Set index to -1
3999                 addIntConstant(-1);
4000                 addSetInstruction(index, fileId);
4001 
4002                 /* For is breakable and continuable. */
4003                 openBreakableSection();
4004                 openContinuableSection();
4005 
4006                 /* Continue jump. */
4007                 setContinuableSectionDestination();
4008 
4009                 advance();
4010                 uint blockPosition = cast(uint) currentFunction.instructions.length;
4011 
4012                 addGetInstruction(iterator, GrType(GrBaseType.int_));
4013                 addInstruction(GrOpcode.decrement_int);
4014                 addSetInstruction(iterator, fileId);
4015 
4016                 addGetInstruction(iterator, GrType(GrBaseType.int_));
4017                 uint jumpPosition = cast(uint) currentFunction.instructions.length;
4018                 addInstruction(GrOpcode.jumpEqual);
4019 
4020                 //Set Index
4021                 addGetInstruction(array);
4022                 addGetInstruction(index);
4023                 addInstruction(GrOpcode.increment_int);
4024                 addSetInstruction(index, fileId, grVoid, true);
4025                 final switch (subType.baseType) with (GrBaseType) {
4026                 case bool_:
4027                 case int_:
4028                 case function_:
4029                 case task:
4030                 case enum_:
4031                     addInstruction(GrOpcode.index2_int);
4032                     break;
4033                 case float_:
4034                     addInstruction(GrOpcode.index2_float);
4035                     break;
4036                 case string_:
4037                     addInstruction(GrOpcode.index2_string);
4038                     break;
4039                 case array_:
4040                 case class_:
4041                 case foreign:
4042                 case chan:
4043                 case reference:
4044                     addInstruction(GrOpcode.index2_object);
4045                     break;
4046                 case void_:
4047                 case null_:
4048                 case internalTuple:
4049                     logError("an array can't be of type `" ~ grGetPrettyType(grArray(subType)) ~ "`",
4050                             "invalid array type");
4051                     break;
4052                 }
4053                 convertType(subType, variable.type, fileId);
4054                 addSetInstruction(variable, fileId);
4055 
4056                 parseBlock(true);
4057 
4058                 addInstruction(GrOpcode.jump,
4059                         cast(int)(blockPosition - currentFunction.instructions.length), true);
4060                 setInstruction(GrOpcode.jumpEqual, jumpPosition,
4061                         cast(int)(currentFunction.instructions.length - jumpPosition), true);
4062 
4063                 /* For is breakable and continuable. */
4064                 closeBreakableSection();
4065                 closeContinuableSection();
4066             }
4067             break;
4068         case foreign:
4069         case class_: {
4070                 GrVariable iterator = registerSpecialVariable("iterator", containerType);
4071 
4072                 GrType subType;
4073                 GrFunction nextFunc;
4074                 GrPrimitive nextPrim = _data.getPrimitive("next", [
4075                         containerType
4076                         ]);
4077                 if (nextPrim) {
4078                     if (nextPrim.outSignature.length != 2 || (nextPrim.outSignature.length >= 1
4079                             && nextPrim.outSignature[0].baseType != grBool)) {
4080                         logError("the primitive `" ~ grGetPrettyFunctionCall("next",
4081                                 [containerType]) ~ "` must return a bool and a value",
4082                                 "signature mismatch");
4083                     }
4084                     subType = nextPrim.outSignature[1];
4085                 }
4086                 else {
4087                     nextFunc = getFunction("next", [containerType], fileId);
4088                     if (!nextFunc) {
4089                         logError("there is no `" ~ grGetPrettyFunctionCall("next",
4090                                 [containerType]) ~ "` defined", "not iterable");
4091                     }
4092 
4093                     if (nextFunc.outSignature.length != 2 || (nextFunc.outSignature.length >= 1
4094                             && nextFunc.outSignature[0].baseType != grBool)) {
4095                         logError("the function `" ~ grGetPrettyFunction(nextFunc) ~ "` must return a bool and a value",
4096                                 "signature mismatch");
4097                     }
4098                     subType = nextFunc.outSignature[1];
4099                 }
4100 
4101                 if (variable.isAuto && subType.baseType != GrBaseType.void_) {
4102                     variable.isAuto = false;
4103                     variable.type = subType;
4104                     setVariableRegister(variable);
4105                 }
4106                 addSetInstruction(iterator, fileId, containerType);
4107 
4108                 /* For is breakable and continuable. */
4109                 openBreakableSection();
4110                 openContinuableSection();
4111 
4112                 /* Continue jump. */
4113                 setContinuableSectionDestination();
4114 
4115                 advance();
4116                 uint blockPosition = cast(uint) currentFunction.instructions.length;
4117 
4118                 addGetInstruction(iterator, containerType);
4119                 if (nextPrim)
4120                     addInstruction(GrOpcode.primitiveCall, nextPrim.index);
4121                 else
4122                     addFunctionCall(nextFunc, fileId);
4123                 addSetInstruction(variable, fileId);
4124 
4125                 uint jumpPosition = cast(uint) currentFunction.instructions.length;
4126                 addInstruction(GrOpcode.jumpEqual);
4127 
4128                 parseBlock(true);
4129 
4130                 addInstruction(GrOpcode.jump,
4131                         cast(int)(blockPosition - currentFunction.instructions.length), true);
4132                 setInstruction(GrOpcode.jumpEqual, jumpPosition,
4133                         cast(int)(currentFunction.instructions.length - jumpPosition), true);
4134 
4135                 /* For is breakable and continuable. */
4136                 closeBreakableSection();
4137                 closeContinuableSection();
4138             }
4139             break;
4140         default:
4141             logError("for can't iterate over a `" ~ grGetPrettyType(containerType) ~ "`",
4142                     "not iterable");
4143             break;
4144         }
4145         currentFunction.closeScope();
4146     }
4147 
4148     /// Skips everything from a `(` to its matching `)`.
4149     private void skipParenthesis() {
4150         if (get().type != GrLexemeType.leftParenthesis)
4151             return;
4152         advance();
4153 
4154         __loop: while (!isEnd()) {
4155             switch (get().type) with (GrLexemeType) {
4156             case rightParenthesis:
4157                 advance();
4158                 return;
4159             case rightBracket:
4160             case rightCurlyBrace:
4161             case semicolon:
4162                 break __loop;
4163             case leftParenthesis:
4164                 skipParenthesis();
4165                 break;
4166             case leftBracket:
4167                 skipBrackets();
4168                 break;
4169             case leftCurlyBrace:
4170                 skipBlock();
4171                 break;
4172             default:
4173                 advance();
4174                 break;
4175             }
4176         }
4177     }
4178 
4179     /// Skips everything from a `[` to its matching `]`.
4180     private void skipBrackets() {
4181         if (get().type != GrLexemeType.leftBracket)
4182             return;
4183         advance();
4184 
4185         __loop: while (!isEnd()) {
4186             switch (get().type) with (GrLexemeType) {
4187             case rightBracket:
4188                 advance();
4189                 return;
4190             case rightParenthesis:
4191             case rightCurlyBrace:
4192             case semicolon:
4193                 break __loop;
4194             case leftParenthesis:
4195                 skipParenthesis();
4196                 break;
4197             case leftBracket:
4198                 skipBrackets();
4199                 break;
4200             case leftCurlyBrace:
4201                 skipBlock();
4202                 break;
4203             default:
4204                 advance();
4205                 break;
4206             }
4207         }
4208     }
4209 
4210     /// Returns the number of parameters separated by commas inside a pair of (), [] or {}.
4211     private int checkArity() {
4212         int arity;
4213         const int position = current;
4214 
4215         bool useParenthesis, useBrackets, useCurlyBraces;
4216 
4217         switch (get().type) with (GrLexemeType) {
4218         case leftParenthesis:
4219             advance();
4220             useParenthesis = true;
4221             if (get(1).type != GrLexemeType.rightParenthesis)
4222                 arity++;
4223             break;
4224         case leftBracket:
4225             advance();
4226             useBrackets = true;
4227             if (get(1).type != GrLexemeType.rightBracket)
4228                 arity++;
4229             break;
4230         case leftCurlyBrace:
4231             advance();
4232             useCurlyBraces = true;
4233             if (get(1).type != GrLexemeType.rightCurlyBrace)
4234                 arity++;
4235             break;
4236         default:
4237             logError("can't evaluate the arity of an unknown compound", "arity evaluation error");
4238             break;
4239         }
4240 
4241         __loop: while (!isEnd()) {
4242             switch (get().type) with (GrLexemeType) {
4243             case comma:
4244                 arity++;
4245                 advance();
4246                 break;
4247             case rightParenthesis:
4248                 if (!useParenthesis)
4249                     goto default;
4250                 break __loop;
4251             case rightBracket:
4252                 if (!useBrackets)
4253                     goto default;
4254                 break __loop;
4255             case rightCurlyBrace:
4256                 if (!useCurlyBraces)
4257                     goto default;
4258                 break __loop;
4259             case semicolon:
4260                 break __loop;
4261             case leftParenthesis:
4262                 skipParenthesis();
4263                 break;
4264             case leftBracket:
4265                 skipBrackets();
4266                 break;
4267             case leftCurlyBrace:
4268                 skipBlock();
4269                 break;
4270             default:
4271                 advance();
4272                 break;
4273             }
4274         }
4275 
4276         current = position;
4277         return arity;
4278     }
4279 
4280     /**
4281     There are 3 types of loop.
4282     - The infinite loop with no parameters:
4283     ---
4284     loop printl("I'm infinite !");
4285     ---
4286     - The finite loop, with 1 parameter:
4287     ---
4288     loop(5) printl("I'm printed 5 times !");
4289     ---
4290     - The finite loop with an iterator:
4291     ---
4292     loop(i, 5) printl("Iterator = " ~ i as string);
4293     ---
4294     */
4295     private void parseLoopStatement() {
4296         bool isInfinite, hasCustomIterator;
4297         GrVariable iterator, customIterator;
4298 
4299         const uint fileId = get().fileId;
4300         currentFunction.openScope();
4301         advance();
4302         if (get().type == GrLexemeType.leftParenthesis) {
4303             const int arity = checkArity();
4304             advance();
4305             if (arity == 2) {
4306                 hasCustomIterator = true;
4307                 customIterator = parseDeclarableArgument();
4308                 if (customIterator.isAuto) {
4309                     customIterator.isAuto = false;
4310                     customIterator.type = grInt;
4311                     setVariableRegister(customIterator);
4312                 }
4313                 else if (customIterator.type != grInt) {
4314                     logError("the type of the iterator must be `int`, not `" ~ grGetPrettyType(
4315                             customIterator.type) ~ "`", "the iterator must be `int`");
4316                 }
4317 
4318                 addIntConstant(0);
4319                 addSetInstruction(customIterator, fileId);
4320 
4321                 if (get().type != GrLexemeType.comma)
4322                     logError("missing comma in `loop`",
4323                             "expected `,`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
4324                 advance();
4325             }
4326 
4327             /* Init */
4328             iterator = registerSpecialVariable("iterator", GrType(GrBaseType.int_));
4329 
4330             //Init counter
4331             GrType type = parseSubExpression().type;
4332             advance();
4333 
4334             convertType(type, grInt, fileId);
4335             addInstruction(GrOpcode.setupIterator);
4336             addSetInstruction(iterator, fileId);
4337         }
4338         else
4339             isInfinite = true;
4340 
4341         /* For is breakable and continuable. */
4342         openBreakableSection();
4343         openContinuableSection();
4344 
4345         /* Continue jump. */
4346         setContinuableSectionDestination();
4347 
4348         uint blockPosition = cast(uint) currentFunction.instructions.length;
4349         uint jumpPosition;
4350 
4351         if (!isInfinite) {
4352             addGetInstruction(iterator, grInt, false);
4353             addInstruction(GrOpcode.decrement_int);
4354             addSetInstruction(iterator, fileId);
4355 
4356             addGetInstruction(iterator, grInt);
4357             jumpPosition = cast(uint) currentFunction.instructions.length;
4358             addInstruction(GrOpcode.jumpEqual);
4359         }
4360 
4361         parseBlock(true);
4362 
4363         if (!isInfinite && hasCustomIterator) {
4364             addGetInstruction(customIterator, grInt, false);
4365             addInstruction(GrOpcode.increment_int);
4366             addSetInstruction(customIterator, fileId);
4367         }
4368 
4369         addInstruction(GrOpcode.jump,
4370                 cast(int)(blockPosition - currentFunction.instructions.length), true);
4371         if (!isInfinite)
4372             setInstruction(GrOpcode.jumpEqual, jumpPosition,
4373                     cast(int)(currentFunction.instructions.length - jumpPosition), true);
4374 
4375         /* For is breakable and continuable. */
4376         closeBreakableSection();
4377         closeContinuableSection();
4378         currentFunction.closeScope();
4379     }
4380 
4381     /**
4382     The type of the return must be that of the signature of the function.
4383     ---
4384     return "Hello"; // Returns a string.
4385     return; // Returns nothing but still end the function.
4386     ---
4387     */
4388     private void parseReturnStatement() {
4389         checkDeferStatement();
4390         checkAdvance();
4391         if (currentFunction.name == "main" || currentFunction.isTask) {
4392             if (!currentFunction.instructions.length
4393                     || currentFunction.instructions[$ - 1].opcode != GrOpcode.kill_)
4394                 addKill();
4395         }
4396         else {
4397             auto types = parseExpressionList();
4398 
4399             addReturn();
4400             if (types.length != currentFunction.outSignature.length) {
4401                 const string argStr = to!string(currentFunction.outSignature.length) ~ (
4402                         currentFunction.outSignature.length > 1 ? " return values" : " return value");
4403                 logError("mismatched number of return values",
4404                         "expected " ~ argStr ~ ", found " ~ to!string(types.length),
4405                         "the return signature is of type `" ~ grGetPrettyFunctionCall("",
4406                             currentFunction.outSignature) ~ "`", -1);
4407             }
4408             for (int i; i < types.length; i++) {
4409                 if (types[i] != currentFunction.outSignature[i])
4410                     logError("the returned type `" ~ grGetPrettyType(
4411                             types[i]) ~ "` does not match the signature `" ~ grGetPrettyType(
4412                             currentFunction.outSignature[i]) ~ "`",
4413                             "expected `" ~ grGetPrettyType(currentFunction.outSignature[i]) ~ "` value",
4414                             "the return signature is of type `" ~ grGetPrettyFunctionCall("",
4415                                 currentFunction.outSignature) ~ "`", -1);
4416             }
4417         }
4418     }
4419 
4420     /// Add a `return` instruction that pop the callstack.
4421     private void addReturn() {
4422         if (_options & GrOption.profile) {
4423             addInstruction(GrOpcode.debugProfileEnd);
4424         }
4425         addInstruction(GrOpcode.return_);
4426     }
4427 
4428     /// Add a `kill` instruction that stops the current task.
4429     private void addKill() {
4430         checkDeferStatement();
4431         if (_options & GrOption.profile) {
4432             addInstruction(GrOpcode.debugProfileEnd);
4433         }
4434         addInstruction(GrOpcode.kill_);
4435     }
4436 
4437     /// Add a `killall` instruction that stops every tasks.
4438     private void addKillAll() {
4439         checkDeferStatement();
4440         if (_options & GrOption.profile) {
4441             addInstruction(GrOpcode.debugProfileEnd);
4442         }
4443         addInstruction(GrOpcode.killAll_);
4444     }
4445 
4446     /// The more it is, the less you need parenthesis.
4447     private uint getLeftOperatorPriority(GrLexemeType type) {
4448         switch (type) with (GrLexemeType) {
4449         case assign: .. case powerAssign:
4450             return 6;
4451         case or:
4452             return 1;
4453         case xor:
4454             return 2;
4455         case and:
4456             return 3;
4457         case equal: .. case notEqual:
4458             return 14;
4459         case greaterOrEqual: .. case lesser:
4460             return 15;
4461         case add: .. case substract:
4462             return 16;
4463         case multiply: .. case remainder:
4464             return 17;
4465         case power:
4466             return 18;
4467         case not:
4468         case plus:
4469         case minus:
4470         case increment:
4471         case decrement:
4472         case send:
4473         case receive:
4474             return 19;
4475         default:
4476             logError("the operator is not listed in the operator priority table",
4477                     "unknown operator priority");
4478             return 0;
4479         }
4480     }
4481 
4482     /// The more it is, the less you need parenthesis.
4483     private uint getRightOperatorPriority(GrLexemeType type) {
4484         switch (type) with (GrLexemeType) {
4485         case assign: .. case powerAssign:
4486             return 20;
4487         case or:
4488             return 1;
4489         case xor:
4490             return 2;
4491         case and:
4492             return 3;
4493         case equal: .. case notEqual:
4494             return 4;
4495         case greaterOrEqual: .. case lesser:
4496             return 5;
4497         case add: .. case substract:
4498             return 16;
4499         case multiply: .. case remainder:
4500             return 17;
4501         case power:
4502             return 18;
4503         case not:
4504         case plus:
4505         case minus:
4506         case increment:
4507         case decrement:
4508         case send:
4509         case receive:
4510             return 19;
4511         default:
4512             logError("the operator is not listed in the operator priority table",
4513                     "unknown operator priority");
4514             return 0;
4515         }
4516     }
4517 
4518     /// Attempt to convert `src` type to the `dst` type.
4519     private GrType convertType(GrType src, GrType dst, uint fileId = 0,
4520             bool noFail = false, bool isExplicit = false) {
4521         if (src.baseType == dst.baseType) {
4522             final switch (src.baseType) with (GrBaseType) {
4523             case function_:
4524                 if (src.mangledType == dst.mangledType
4525                         && src.mangledReturnType == dst.mangledReturnType)
4526                     return dst;
4527                 break;
4528             case task:
4529                 if (src.mangledType == dst.mangledType)
4530                     return dst;
4531                 break;
4532             case null_:
4533                 break;
4534             case void_:
4535             case bool_:
4536             case int_:
4537             case float_:
4538             case string_:
4539             case enum_:
4540                 return dst;
4541             case class_:
4542                 string className = src.mangledType;
4543                 for (;;) {
4544                     if (className == dst.mangledType)
4545                         return dst;
4546                     const GrClassDefinition classType = getClass(className, fileId);
4547                     if (!classType.parent.length)
4548                         break;
4549                     className = classType.parent;
4550                 }
4551                 break;
4552             case array_:
4553             case chan:
4554             case reference:
4555             case internalTuple:
4556                 if (dst.mangledType == src.mangledType)
4557                     return dst;
4558                 break;
4559             case foreign:
4560                 string foreignName = src.mangledType;
4561                 for (;;) {
4562                     if (dst.mangledType == foreignName)
4563                         return dst;
4564                     const GrForeignDefinition foreignType = _data.getForeign(foreignName);
4565                     if (!foreignType.parent.length)
4566                         break;
4567                     foreignName = foreignType.parent;
4568                 }
4569                 break;
4570             }
4571         }
4572 
4573         if (src.baseType == GrBaseType.null_ && (dst.baseType == GrBaseType.class_
4574                 || dst.baseType == GrBaseType.foreign))
4575             return dst;
4576 
4577         if (src.baseType == GrBaseType.internalTuple || dst.baseType == GrBaseType.internalTuple)
4578             logError("expected `" ~ grGetPrettyType(dst) ~ "`, found `" ~ grGetPrettyType(src) ~ "`",
4579                     "mismatched types", "", -1);
4580 
4581         if (dst.baseType == GrBaseType.bool_) {
4582             final switch (src.baseType) with (GrBaseType) {
4583             case function_:
4584             case task:
4585             case void_:
4586             case bool_:
4587             case int_:
4588             case float_:
4589             case string_:
4590             case internalTuple:
4591             case enum_:
4592                 break;
4593             case array_:
4594             case class_:
4595             case foreign:
4596             case chan:
4597             case reference:
4598             case null_:
4599                 addInstruction(GrOpcode.isNonNull_object);
4600                 return dst;
4601             }
4602         }
4603 
4604         //User-defined conversions.
4605         if (addCustomConversion(src, dst, isExplicit, get().fileId) == dst)
4606             return dst;
4607 
4608         if (!noFail)
4609             logError("expected `" ~ grGetPrettyType(dst) ~ "`, found `" ~ grGetPrettyType(src) ~ "`",
4610                     "mismatched types", "", -1);
4611         return GrType(GrBaseType.void_);
4612     }
4613 
4614     /// Convert with a primitive or function.
4615     private GrType addCustomConversion(GrType leftType, GrType rightType,
4616             bool isExplicit, uint fileId) {
4617         GrType resultType = GrBaseType.void_;
4618 
4619         //as opposed to other functions, we need the return type (rightType) to be part of the signature.
4620         string name = "@as";
4621         GrType[] signature = [leftType, rightType];
4622 
4623         //GrPrimitive check
4624         const GrPrimitive primitive = _data.getPrimitive(name, signature);
4625         if (primitive) {
4626             //Some implicit conversions are disabled.
4627             //ex: float -> int because we might lose information.
4628             if (primitive.isExplicit && !isExplicit)
4629                 return resultType;
4630             addInstruction(GrOpcode.primitiveCall, primitive.index);
4631             if (primitive.outSignature.length != 1uL) {
4632                 const string argStr = to!string(primitive.outSignature.length) ~ (
4633                         primitive.outSignature.length > 1 ? " return values" : " return value");
4634                 logError("an operator must have only one return value",
4635                         "expected 1 return value, found " ~ argStr);
4636             }
4637             resultType = rightType;
4638         }
4639 
4640         //GrFunction check
4641         if (resultType.baseType == GrBaseType.void_) {
4642             GrFunction func = getFunction(name, signature, fileId);
4643             if (func) {
4644                 const GrType[] outSignature = addFunctionCall(func, fileId);
4645                 if (outSignature.length != 1uL) {
4646                     const string argStr = to!string(primitive.outSignature.length) ~ (primitive.outSignature.length > 1
4647                             ? " return values" : " return value");
4648                     logError("an operator must have only one return value",
4649                             "expected 1 return value, found " ~ argStr);
4650                 }
4651                 resultType = rightType;
4652             }
4653         }
4654         return resultType;
4655     }
4656 
4657     private GrType parseObjectBuilder() {
4658         if (get().type != GrLexemeType.new_)
4659             logError("expected `new`, found `" ~ grGetPrettyLexemeType(get()
4660                     .type) ~ "`", "missing `new`");
4661         checkAdvance();
4662         if (get().type != GrLexemeType.identifier)
4663             logError("expected class name, found `" ~ grGetPrettyLexemeType(get()
4664                     .type) ~ "`", "missing identifier");
4665         uint fileId = get().fileId;
4666         GrType classType = parseType(true);
4667         if (classType.baseType != GrBaseType.class_)
4668             logError("`" ~ grGetPrettyType(classType) ~ "` is not a class type",
4669                     "invalid type", "", -1);
4670         GrClassDefinition class_ = getClass(classType.mangledType, fileId);
4671         if (!class_)
4672             logError("`" ~ grGetPrettyType(classType) ~ "` is not declared",
4673                     "unknown class", "", -1);
4674         addInstruction(GrOpcode.new_, cast(uint) class_.index);
4675 
4676         bool[] initFields;
4677         uint[] lexPositions;
4678         initFields.length = class_.fields.length;
4679         lexPositions.length = class_.fields.length;
4680 
4681         // Init
4682         if (get().type == GrLexemeType.leftCurlyBrace) {
4683             checkAdvance();
4684             while (!isEnd()) {
4685                 if (get().type == GrLexemeType.rightCurlyBrace) {
4686                     checkAdvance();
4687                     break;
4688                 }
4689                 else if (get().type == GrLexemeType.identifier) {
4690                     const string fieldName = get().svalue;
4691                     checkAdvance();
4692                     bool hasField = false;
4693                     for (int i; i < class_.fields.length; ++i) {
4694                         if (class_.fields[i] == fieldName) {
4695                             hasField = true;
4696 
4697                             if (initFields[i])
4698                                 logError("the field `" ~ fieldName ~ "` is initialized multiple times",
4699                                         "`" ~ fieldName ~ "` is already initialized",
4700                                         "", -1, "previous initialization", lexPositions[i] - 1);
4701 
4702                             initFields[i] = true;
4703                             lexPositions[i] = current;
4704 
4705                             GrVariable fieldLValue = new GrVariable;
4706                             fieldLValue.isInitialized = false;
4707                             fieldLValue.isField = true;
4708                             fieldLValue.type = class_.signature[i];
4709                             fieldLValue.register = i;
4710                             fieldLValue.fileId = get().fileId;
4711                             fieldLValue.lexPosition = current;
4712                             addInstruction(GrOpcode.fieldLoad2, fieldLValue.register);
4713                             parseAssignList([fieldLValue], true);
4714                             break;
4715                         }
4716                     }
4717                     if (!hasField)
4718                         logError("the field `" ~ fieldName ~ "` doesn't exist", "unknown field");
4719                 }
4720                 else {
4721                     logError("expected field name, found `" ~ grGetPrettyLexemeType(get()
4722                             .type) ~ "`", "missing field");
4723                 }
4724             }
4725         }
4726 
4727         for (int i; i < class_.fields.length; ++i) {
4728             if (initFields[i])
4729                 continue;
4730             GrVariable fieldLValue = new GrVariable;
4731             fieldLValue.isInitialized = false;
4732             fieldLValue.isField = true;
4733             fieldLValue.type = class_.signature[i];
4734             fieldLValue.register = i;
4735             fieldLValue.fileId = get().fileId;
4736             fieldLValue.lexPosition = current;
4737             addInstruction(GrOpcode.fieldLoad2, fieldLValue.register);
4738             addDefaultValue(fieldLValue.type, fileId);
4739             addSetInstruction(fieldLValue, fileId, fieldLValue.type);
4740         }
4741 
4742         return classType;
4743     }
4744 
4745     /**
4746     Parse an array creation.
4747     The type is optional if the array is not empty.
4748     If no type is specified, the array subtype is set to the type of the first element.
4749     ---
4750     array(int)[1, 2, 3]
4751     ["1", "2", "3"]
4752     array(string)[]
4753     ---
4754     */
4755     private GrType parseArrayBuilder() {
4756         GrType arrayType = GrType(GrBaseType.array_);
4757         GrType subType = grVoid;
4758         const uint fileId = get().fileId;
4759 
4760         //Explicit type like: array(int)[1, 2, 3]
4761         if (get().type == GrLexemeType.arrayType) {
4762             checkAdvance();
4763             string[] temp;
4764             auto signature = parseInSignature(temp, true);
4765             if (signature.length > 1)
4766                 logError("an array can only contain one type of value", "conflicting array signature",
4767                         "try using `" ~ grGetPrettyType(grArray(signature[0])) ~ "` instead", -1);
4768             subType = signature[0];
4769             arrayType.mangledType = grMangleSignature(signature);
4770             if (subType.baseType == GrBaseType.void_)
4771                 logError("an array can't be of type `" ~ grGetPrettyType(arrayType) ~ "`",
4772                         "invalid array type");
4773         }
4774 
4775         if (get().type != GrLexemeType.leftBracket)
4776             logError("missing brackets after `" ~ grGetPrettyType(arrayType) ~ "`",
4777                     "expected `[`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
4778         advance();
4779 
4780         int arraySize;
4781         while (get().type != GrLexemeType.rightBracket) {
4782             if (subType.baseType == GrBaseType.void_) {
4783                 //Implicit type specified by the type of the first element.
4784                 subType = parseSubExpression(
4785                         GR_SUBEXPR_TERMINATE_BRACKET | GR_SUBEXPR_TERMINATE_COMMA
4786                         | GR_SUBEXPR_EXPECTING_VALUE).type;
4787                 arrayType.mangledType = grMangleSignature([subType]);
4788                 if (subType.baseType == GrBaseType.void_)
4789                     logError("an array can't be of type `" ~ grGetPrettyType(arrayType) ~ "`",
4790                             "invalid array type");
4791             }
4792             else {
4793                 convertType(parseSubExpression(
4794                         GR_SUBEXPR_TERMINATE_BRACKET | GR_SUBEXPR_TERMINATE_COMMA | GR_SUBEXPR_EXPECTING_VALUE)
4795                         .type, subType, fileId);
4796             }
4797             arraySize++;
4798 
4799             if (get().type == GrLexemeType.rightBracket)
4800                 break;
4801             if (get().type != GrLexemeType.comma)
4802                 logError("indexes should be separated by a comma",
4803                         "expected `,`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
4804             checkAdvance();
4805         }
4806 
4807         final switch (subType.baseType) with (GrBaseType) {
4808         case bool_:
4809         case int_:
4810         case function_:
4811         case task:
4812         case enum_:
4813             addInstruction(GrOpcode.array_int, arraySize);
4814             break;
4815         case float_:
4816             addInstruction(GrOpcode.array_float, arraySize);
4817             break;
4818         case string_:
4819             addInstruction(GrOpcode.array_string, arraySize);
4820             break;
4821         case array_:
4822         case class_:
4823         case foreign:
4824         case chan:
4825         case reference:
4826             addInstruction(GrOpcode.array_object, arraySize);
4827             break;
4828         case void_:
4829         case null_:
4830         case internalTuple:
4831             logError("an array can't be of type `" ~ grGetPrettyType(grArray(subType)) ~ "`",
4832                     "invalid array type");
4833             break;
4834         }
4835         advance();
4836         return arrayType;
4837     }
4838 
4839     private GrType parseArrayIndex(GrType arrayType) {
4840         const uint fileId = get().fileId;
4841         advance();
4842 
4843         for (;;) {
4844             if (get().type == GrLexemeType.comma)
4845                 logError("an index is expected, found `,`", "missing value");
4846             auto index = parseSubExpression(
4847                     GR_SUBEXPR_TERMINATE_BRACKET | GR_SUBEXPR_TERMINATE_COMMA
4848                     | GR_SUBEXPR_EXPECTING_VALUE).type;
4849             if (index.baseType == GrBaseType.void_)
4850                 logError("expected `int`, found nothing", "missing value");
4851             convertType(index, grInt, fileId);
4852 
4853             if (get().type == GrLexemeType.rightBracket) {
4854                 switch (arrayType.baseType) with (GrBaseType) {
4855                 case array_:
4856                     const GrType subType = grUnmangle(arrayType.mangledType);
4857                     final switch (subType.baseType) with (GrBaseType) {
4858                     case bool_:
4859                     case int_:
4860                     case function_:
4861                     case task:
4862                     case enum_:
4863                         addInstruction(GrOpcode.index_int);
4864                         break;
4865                     case float_:
4866                         addInstruction(GrOpcode.index_float);
4867                         break;
4868                     case string_:
4869                         addInstruction(GrOpcode.index_string);
4870                         break;
4871                     case array_:
4872                     case class_:
4873                     case foreign:
4874                     case chan:
4875                     case reference:
4876                         addInstruction(GrOpcode.index_object);
4877                         break;
4878                     case void_:
4879                     case null_:
4880                     case internalTuple:
4881                         logError("an array can't be of type `" ~ grGetPrettyType(grArray(subType)) ~ "`",
4882                                 "invalid array type");
4883                         break;
4884                     }
4885                     arrayType = subType;
4886                     break;
4887                 default:
4888                     logError("invalid array type",
4889                             "expected `array`, found `" ~ grGetPrettyType(arrayType) ~ "`");
4890                 }
4891                 break;
4892             }
4893             if (get().type != GrLexemeType.comma)
4894                 logError("indexes should be separated by a comma",
4895                         "expected `,`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
4896             checkAdvance();
4897             if (get().type == GrLexemeType.rightBracket)
4898                 logError("indexes should be separated by a comma",
4899                         "expected `,`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
4900 
4901             switch (arrayType.baseType) with (GrBaseType) {
4902             case array_:
4903                 const GrType subType = grUnmangle(arrayType.mangledType);
4904                 final switch (subType.baseType) with (GrBaseType) {
4905                 case bool_:
4906                 case int_:
4907                 case function_:
4908                 case task:
4909                 case enum_:
4910                     addInstruction(GrOpcode.index_int);
4911                     break;
4912                 case float_:
4913                     addInstruction(GrOpcode.index_float);
4914                     break;
4915                 case string_:
4916                     addInstruction(GrOpcode.index_string);
4917                     break;
4918                 case array_:
4919                 case class_:
4920                 case foreign:
4921                 case chan:
4922                 case reference:
4923                     addInstruction(GrOpcode.index_object);
4924                     break;
4925                 case void_:
4926                 case null_:
4927                 case internalTuple:
4928                     logError("an array can't be of type `" ~ grGetPrettyType(arrayType) ~ "`",
4929                             "invalid array type");
4930                     break;
4931                 }
4932                 arrayType = subType;
4933                 break;
4934             default:
4935                 logError("invalid array type",
4936                         "expected `array`, found `" ~ grGetPrettyType(arrayType) ~ "`");
4937             }
4938         }
4939         advance();
4940         return arrayType;
4941     }
4942 
4943     /**
4944     Parse a cast, or `as` operation.
4945     ---
4946     1 as float
4947     ---
4948     */
4949     private GrType parseConversionOperator(GrType[] typeStack) {
4950         const uint fileId = get().fileId;
4951         if (!typeStack.length)
4952             logError("no value to convert", "missing value");
4953         advance();
4954         auto asType = parseType();
4955         convertType(typeStack[$ - 1], asType, fileId, false, true);
4956         typeStack[$ - 1] = asType;
4957         return asType;
4958     }
4959 
4960     /// Parse an assignable (named) element.
4961     private GrVariable parseLValue() {
4962         const uint fileId = get().fileId;
4963         if (get().type != GrLexemeType.identifier)
4964             logError("expected variable, found `" ~ grGetPrettyLexemeType(get()
4965                     .type) ~ "`", "missing variable");
4966 
4967         const string identifierName = get().svalue;
4968 
4969         checkAdvance();
4970 
4971         GrVariable localLValue = currentFunction.getLocal(identifierName);
4972         if (localLValue !is null)
4973             return localLValue;
4974 
4975         GrVariable globalLValue = getGlobalVariable(identifierName, fileId);
4976         if (globalLValue !is null)
4977             return globalLValue;
4978 
4979         logError("expected variable, found `" ~ grGetPrettyLexemeType(get()
4980                 .type) ~ "`", "missing variable");
4981         return null;
4982     }
4983 
4984     /// Parse a single expression, not a statement.
4985     private void parseExpression() {
4986         bool isAssignmentList;
4987         const auto tempPos = current;
4988         __skipLoop: while (!isEnd()) {
4989             switch (get().type) with (GrLexemeType) {
4990             case leftBracket:
4991                 skipBrackets();
4992                 break;
4993             case leftParenthesis:
4994                 skipParenthesis();
4995                 break;
4996             case leftCurlyBrace:
4997                 skipBlock();
4998                 break;
4999             case semicolon:
5000                 isAssignmentList = false;
5001                 break __skipLoop;
5002             case comma:
5003                 isAssignmentList = true;
5004                 break __skipLoop;
5005             default:
5006                 checkAdvance();
5007                 break;
5008             }
5009         }
5010         current = tempPos;
5011 
5012         if (isAssignmentList) {
5013             //Get list of lvalues
5014             GrVariable[] lvalues;
5015             do {
5016                 if (lvalues.length)
5017                     checkAdvance();
5018                 //Identifier
5019                 if (get().type != GrLexemeType.identifier)
5020                     logError("expected identifier, found `" ~ grGetPrettyLexemeType(get()
5021                             .type) ~ "`", "missing identifier");
5022                 lvalues ~= parseSubExpression(
5023                         GR_SUBEXPR_TERMINATE_COMMA | GR_SUBEXPR_TERMINATE_ASSIGN
5024                         | GR_SUBEXPR_EXPECTING_LVALUE).lvalue;
5025             }
5026             while (get().type == GrLexemeType.comma);
5027 
5028             parseAssignList(lvalues);
5029         }
5030         else {
5031             parseSubExpression(GR_SUBEXPR_TERMINATE_SEMICOLON | GR_SUBEXPR_MUST_CLEAN);
5032             checkAdvance();
5033         }
5034     }
5035 
5036     /// Parse the right side of a multiple assignment.
5037     private GrType[] parseExpressionList() {
5038         GrType[] expressionTypes;
5039         for (;;) {
5040             GrType type = parseSubExpression(
5041                     GR_SUBEXPR_TERMINATE_SEMICOLON | GR_SUBEXPR_TERMINATE_COMMA
5042                     | GR_SUBEXPR_EXPECTING_VALUE).type;
5043             if (type.baseType == GrBaseType.internalTuple) {
5044                 auto types = grUnpackTuple(type);
5045                 if (!types.length)
5046                     logError("the expression yields no value", "expected value, found nothing");
5047                 else {
5048                     foreach (subType; types)
5049                         expressionTypes ~= subType;
5050                 }
5051             }
5052             else if (type.baseType != GrBaseType.void_)
5053                 expressionTypes ~= type;
5054             if (get().type != GrLexemeType.comma)
5055                 break;
5056             checkAdvance();
5057         }
5058         if (get().type != GrLexemeType.semicolon)
5059             logError("missing semicolon after expression list",
5060                     "expected `;`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
5061         checkAdvance();
5062         return expressionTypes;
5063     }
5064 
5065     /// Parse the right side of a multiple assignment and associate them with the `lvalues`.
5066     private void parseAssignList(GrVariable[] lvalues, bool isInitialization = false) {
5067         const uint fileId = get().fileId;
5068         switch (get().type) with (GrLexemeType) {
5069         case assign:
5070             advance();
5071             GrType[] expressionTypes = parseExpressionList();
5072 
5073             if (expressionTypes.length > lvalues.length) {
5074                 const string argStr = to!string(lvalues.length) ~ (lvalues.length > 1
5075                         ? " variables" : " variable");
5076                 logError("trying to assign `" ~ to!string(expressionTypes.length) ~ "` values to " ~ argStr,
5077                         "there are more values than variable to assign to", "", -1);
5078             }
5079             else if (!expressionTypes.length) {
5080                 logError("the assignation is missing a value", "the expression is empty", "", -1);
5081             }
5082 
5083             int variableIndex = to!int(lvalues.length) - 1;
5084             int expressionIndex = to!int(expressionTypes.length) - 1;
5085             bool passThrough;
5086             GrVariable[] skippedLvalues;
5087             while (variableIndex > expressionIndex) {
5088                 addSetInstruction(lvalues[variableIndex], fileId,
5089                         expressionTypes[expressionIndex], true);
5090                 variableIndex--;
5091                 passThrough = true;
5092             }
5093             if (passThrough) {
5094                 if (expressionTypes[expressionIndex].baseType == GrBaseType.void_) {
5095                     skippedLvalues ~= lvalues[variableIndex];
5096                 }
5097                 else {
5098                     addSetInstruction(lvalues[variableIndex], fileId,
5099                             lvalues[variableIndex + 1].type, false);
5100                 }
5101                 variableIndex--;
5102                 expressionIndex--;
5103             }
5104             while (variableIndex >= 0) {
5105                 if (expressionTypes[expressionIndex].baseType == GrBaseType.void_) {
5106                     skippedLvalues ~= lvalues[variableIndex];
5107                 }
5108                 else {
5109                     while (skippedLvalues.length) {
5110                         addSetInstruction(skippedLvalues[$ - 1], fileId,
5111                                 expressionTypes[expressionIndex], true);
5112                         skippedLvalues.length--;
5113                     }
5114                     addSetInstruction(lvalues[variableIndex], fileId,
5115                             expressionTypes[expressionIndex], false);
5116                 }
5117                 variableIndex--;
5118                 expressionIndex--;
5119             }
5120             if (skippedLvalues.length)
5121                 logError("first value of an assignment list can't be empty", "missing value");
5122             break;
5123         case semicolon:
5124             if (isInitialization) {
5125                 foreach (lvalue; lvalues) {
5126                     if (lvalue.isAuto)
5127                         logError("can't infer the type without assignment",
5128                                 "missing type information or initial value", "", -1);
5129                     addDefaultValue(lvalue.type, fileId);
5130                     addSetInstruction(lvalue, fileId, lvalue.type);
5131                 }
5132             }
5133             advance();
5134             break;
5135         default:
5136             logError("missing semicolon after assignment list",
5137                     "expected `;`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
5138         }
5139     }
5140 
5141     private void addDefaultValue(GrType type, uint fileId) {
5142         final switch (type.baseType) with (GrBaseType) {
5143         case int_:
5144         case bool_:
5145         case enum_:
5146             addIntConstant(0);
5147             break;
5148         case float_:
5149             addFloatConstant(0f);
5150             break;
5151         case string_:
5152             addStringConstant("");
5153             break;
5154         case function_:
5155             GrType[] inSignature = grUnmangleSignature(type.mangledType);
5156             GrType[] outSignature = grUnmangleSignature(type.mangledReturnType);
5157             string[] inputs;
5158             for (int i; i < inSignature.length; ++i) {
5159                 inputs ~= to!string(i);
5160             }
5161             preBeginFunction("$anon", fileId, inSignature, inputs, false, outSignature, true);
5162             openDeferrableSection();
5163             foreach (outType; outSignature) {
5164                 addDefaultValue(outType, fileId);
5165             }
5166             addReturn();
5167             closeDeferrableSection();
5168             registerDeferBlocks();
5169             endFunction();
5170             break;
5171         case task:
5172             GrType[] inSignature = grUnmangleSignature(type.mangledType);
5173             GrType[] outSignature = grUnmangleSignature(type.mangledReturnType);
5174             string[] inputs;
5175             for (int i; i < inSignature.length; ++i) {
5176                 inputs ~= to!string(i);
5177             }
5178             preBeginFunction("$anon", fileId, inSignature, inputs, true, outSignature, true);
5179             openDeferrableSection();
5180             addKill();
5181             closeDeferrableSection();
5182             registerDeferBlocks();
5183             endFunction();
5184             break;
5185         case array_:
5186             GrType[] subTypes = grUnmangleSignature(type.mangledType);
5187             if (subTypes.length != 1)
5188                 logError("an array can only contain one type of value", "conflicting array signature",
5189                         "try using `" ~ grGetPrettyType(grArray(subTypes[0])) ~ "` instead");
5190             final switch (subTypes[0].baseType) with (GrBaseType) {
5191             case bool_:
5192             case int_:
5193             case function_:
5194             case task:
5195             case enum_:
5196                 addInstruction(GrOpcode.array_int, 0);
5197                 break;
5198             case float_:
5199                 addInstruction(GrOpcode.array_float, 0);
5200                 break;
5201             case string_:
5202                 addInstruction(GrOpcode.array_string, 0);
5203                 break;
5204             case array_:
5205             case class_:
5206             case foreign:
5207             case chan:
5208             case reference:
5209                 addInstruction(GrOpcode.array_object, 0);
5210                 break;
5211             case void_:
5212             case null_:
5213             case internalTuple:
5214                 logError("an array can't be of type `" ~ grGetPrettyType(grArray(subTypes[0])) ~ "`",
5215                         "invalid array type");
5216                 break;
5217             }
5218             break;
5219         case class_:
5220             addInstruction(GrOpcode.const_null);
5221             break;
5222         case foreign:
5223             addInstruction(GrOpcode.const_null);
5224             break;
5225         case chan:
5226             GrType[] subTypes = grUnmangleSignature(type.mangledType);
5227             if (subTypes.length != 1)
5228                 logError("a channel can only contain one type of value", "conflicting channel signature",
5229                         "try using `" ~ grGetPrettyType(grChannel(subTypes[0])) ~ "` instead");
5230             final switch (subTypes[0].baseType) with (GrBaseType) {
5231             case int_:
5232             case bool_:
5233             case function_:
5234             case task:
5235             case enum_:
5236                 addInstruction(GrOpcode.channel_int, 1);
5237                 break;
5238             case float_:
5239                 addInstruction(GrOpcode.channel_float, 1);
5240                 break;
5241             case string_:
5242                 addInstruction(GrOpcode.channel_string, 1);
5243                 break;
5244             case class_:
5245             case array_:
5246             case foreign:
5247             case chan:
5248             case reference:
5249                 addInstruction(GrOpcode.channel_object, 1);
5250                 break;
5251             case void_:
5252             case null_:
5253             case internalTuple:
5254                 logError("a channel can't be of type `" ~ grGetPrettyType(grChannel(subTypes[0])) ~ "`",
5255                         "invalid channel type");
5256             }
5257             break;
5258         case reference:
5259         case void_:
5260         case null_:
5261         case internalTuple:
5262             logError("the type `" ~ grGetPrettyType(type) ~ "` has no default value",
5263                     "can't initialize this type");
5264         }
5265     }
5266 
5267     /**
5268     Count the number of D types used (int, float, string and void*).
5269     */
5270     private auto countSubTypes(GrType type) {
5271         struct TypeCounter {
5272             int iCount, fCount, sCount, oCount;
5273         }
5274 
5275         TypeCounter counter;
5276         void countSubTypes(GrType type, ref TypeCounter counter) {
5277             final switch (type.baseType) with (GrBaseType) {
5278             case int_:
5279             case bool_:
5280             case function_:
5281             case task:
5282             case enum_:
5283                 counter.iCount++;
5284                 break;
5285             case float_:
5286                 counter.fCount++;
5287                 break;
5288             case string_:
5289                 counter.sCount++;
5290                 break;
5291             case class_:
5292             case array_:
5293             case foreign:
5294             case chan:
5295             case reference:
5296                 counter.oCount++;
5297                 break;
5298             case void_:
5299             case null_:
5300                 throw new Exception("the type can't be counted as a subtype");
5301             case internalTuple:
5302                 auto types = grUnpackTuple(type);
5303                 if (!types.length)
5304                     logError("the expression yields no value", "expected value, found nothing");
5305                 else {
5306                     foreach (subType; types)
5307                         countSubTypes(subType, counter);
5308                 }
5309                 break;
5310             }
5311         }
5312 
5313         countSubTypes(type, counter);
5314         return counter;
5315     }
5316 
5317     /// Add an instruction to clean up a value from the stack.
5318     private void shiftStackPosition(GrType type, short count) {
5319         const auto counter = countSubTypes(type);
5320         if (counter.iCount)
5321             addInstruction(GrOpcode.shiftStack_int, counter.iCount * count, true);
5322         if (counter.fCount)
5323             addInstruction(GrOpcode.shiftStack_float, counter.fCount * count, true);
5324         if (counter.sCount)
5325             addInstruction(GrOpcode.shiftStack_string, counter.sCount * count, true);
5326         if (counter.oCount)
5327             addInstruction(GrOpcode.shiftStack_object, counter.oCount * count, true);
5328     }
5329 
5330     /// Does this operation require a left-expr ?
5331     private bool requireLValue(GrLexemeType operatorType) {
5332         switch (operatorType) with (GrLexemeType) {
5333         case increment:
5334         case decrement:
5335         case assign: .. case powerAssign:
5336             return true;
5337         default:
5338             return false;
5339         }
5340     }
5341 
5342     /**
5343     Parse a function reference expression. \
5344     Converts a public function/task into an anonymous one.
5345     */
5346     private GrType parseFunctionPointer(GrType currentType) {
5347         const uint fileId = get().fileId;
5348         checkAdvance();
5349         if (get().type == GrLexemeType.leftParenthesis) {
5350             checkAdvance();
5351             GrType refType = parseType();
5352             if (get().type != GrLexemeType.rightParenthesis)
5353                 logError("missing parenthesis after the type",
5354                         "expected `)`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
5355             checkAdvance();
5356             if (currentType.baseType == GrBaseType.void_)
5357                 currentType = refType;
5358             else
5359                 currentType = convertType(refType, currentType, fileId);
5360         }
5361         if (get().type != GrLexemeType.identifier)
5362             logError("expected function name, found `" ~ grGetPrettyLexemeType(get()
5363                     .type) ~ "`", "missing function name");
5364         if (currentType.baseType != GrBaseType.function_ && currentType.baseType != GrBaseType.task)
5365             logError("can't infer the type of `" ~ get().svalue ~ "`",
5366                     "the function type can't be inferred");
5367 
5368         GrType funcType = addFunctionAddress(get().svalue,
5369                 grUnmangleSignature(currentType.mangledType), get().fileId);
5370         convertType(funcType, currentType, fileId);
5371         checkAdvance();
5372         return currentType;
5373     }
5374 
5375     private enum {
5376         GR_SUBEXPR_TERMINATE_SEMICOLON = 0x1,
5377         GR_SUBEXPR_TERMINATE_BRACKET = 0x2,
5378         GR_SUBEXPR_TERMINATE_COMMA = 0x4,
5379         GR_SUBEXPR_TERMINATE_PARENTHESIS = 0x8,
5380         GR_SUBEXPR_TERMINATE_ASSIGN = 0x10,
5381         GR_SUBEXPR_MUST_CLEAN = 0x20,
5382         GR_SUBEXPR_EXPECTING_VALUE = 0x40,
5383         GR_SUBEXPR_EXPECTING_LVALUE = 0x80,
5384     }
5385 
5386     private struct GrSubExprResult {
5387         GrType type;
5388         GrVariable lvalue;
5389     }
5390 
5391     /**
5392     Evaluate a single subexpression.
5393     */
5394     private GrSubExprResult parseSubExpression(
5395             int flags = GR_SUBEXPR_TERMINATE_PARENTHESIS | GR_SUBEXPR_EXPECTING_VALUE) {
5396         const bool useSemicolon = (flags & GR_SUBEXPR_TERMINATE_SEMICOLON) > 0;
5397         const bool useBracket = (flags & GR_SUBEXPR_TERMINATE_BRACKET) > 0;
5398         const bool useComma = (flags & GR_SUBEXPR_TERMINATE_COMMA) > 0;
5399         const bool useParenthesis = (flags & GR_SUBEXPR_TERMINATE_PARENTHESIS) > 0;
5400         const bool useAssign = (flags & GR_SUBEXPR_TERMINATE_ASSIGN) > 0;
5401         const bool mustCleanValue = (flags & GR_SUBEXPR_MUST_CLEAN) > 0;
5402         const bool isExpectingValue = (flags & GR_SUBEXPR_EXPECTING_VALUE) > 0;
5403         const bool isExpectingLValue = (flags & GR_SUBEXPR_EXPECTING_LVALUE) > 0;
5404 
5405         GrVariable[] lvalues;
5406         GrLexemeType[] operatorsStack;
5407         GrType[] typeStack;
5408         GrType currentType = grVoid, lastType = grVoid;
5409         bool hasValue = false, hadValue = false, hasLValue = false, hadLValue = false, hasReference = false,
5410             hadReference = false, isRightUnaryOperator = true, isEndOfExpression = false;
5411 
5412         GrSubExprResult result;
5413         uint fileId;
5414 
5415         do {
5416             if (hasValue && currentType != lastType && lastType != grVoid) {
5417                 lastType = currentType;
5418                 currentType = lastType;
5419             }
5420             else
5421                 lastType = currentType;
5422 
5423             isRightUnaryOperator = false;
5424             hadValue = hasValue;
5425             hasValue = false;
5426 
5427             hadLValue = hasLValue;
5428             hasLValue = false;
5429 
5430             hadReference = hasReference;
5431             hasReference = false;
5432 
5433             GrLexeme lex = get();
5434             fileId = lex.fileId;
5435             switch (lex.type) with (GrLexemeType) {
5436             case semicolon:
5437                 if (useSemicolon)
5438                     isEndOfExpression = true;
5439                 else
5440                     logError("unexpected semicolon found in expression",
5441                             "a `;` can't exist inside this expression");
5442                 break;
5443             case comma:
5444                 if (useComma)
5445                     isEndOfExpression = true;
5446                 else
5447                     logError("unexpected comma found in expression",
5448                             "a `,` can't exist inside this expression");
5449                 break;
5450             case rightParenthesis:
5451                 if (useParenthesis)
5452                     isEndOfExpression = true;
5453                 else
5454                     logError("unexpected parenthesis found in expression",
5455                             "a `)` can't exist inside this expression");
5456                 break;
5457             case rightBracket:
5458                 if (useBracket)
5459                     isEndOfExpression = true;
5460                 else
5461                     logError("unexpected bracket found in expression",
5462                             "a `]` can't exist inside this expression");
5463                 break;
5464             case leftParenthesis:
5465                 if (hadValue) {
5466                     currentType = parseAnonymousCall(typeStack[$ - 1]);
5467                     //Unpack function value for 1 or less return values
5468                     //Multiples values are left as a tuple for parseExpressionList()
5469                     if (currentType.baseType == GrBaseType.internalTuple) {
5470                         auto types = grUnpackTuple(currentType);
5471                         if (!types.length)
5472                             currentType = grVoid;
5473                         else if (types.length == 1uL)
5474                             currentType = types[0];
5475                     }
5476                     if (currentType.baseType == GrBaseType.void_) {
5477                         typeStack.length--;
5478                     }
5479                     else {
5480                         hadValue = false;
5481                         hasValue = true;
5482                         typeStack[$ - 1] = currentType;
5483                     }
5484                 }
5485                 else {
5486                     advance();
5487                     currentType = parseSubExpression().type;
5488                     advance();
5489                     hasValue = true;
5490                     typeStack ~= currentType;
5491                 }
5492                 break;
5493             case doubleColon:
5494                 advance();
5495                 if (!hadValue)
5496                     logError("a method call must be placed after a value", "missing value");
5497                 if (get().type != GrLexemeType.identifier)
5498                     logError("expected function name, found `" ~ grGetPrettyLexemeType(get()
5499                             .type) ~ "`", "missing function name");
5500 
5501                 GrType selfType = grVoid;
5502                 selfType = typeStack[$ - 1];
5503                 typeStack.length--;
5504                 hadValue = false;
5505 
5506                 GrVariable lvalue;
5507                 currentType = parseIdentifier(lvalue, lastType, selfType, isExpectingLValue);
5508                 //Unpack function value for 1 or less return values
5509                 //Multiples values are left as a tuple for parseExpressionList()
5510                 if (currentType.baseType == GrBaseType.internalTuple) {
5511                     auto types = grUnpackTuple(currentType);
5512                     if (!types.length)
5513                         currentType = grVoid;
5514                     else if (types.length == 1uL)
5515                         currentType = types[0];
5516                 }
5517 
5518                 const auto nextLexeme = get();
5519                 if (nextLexeme.type == GrLexemeType.leftBracket)
5520                     hasReference = true;
5521                 if (currentType != GrType(GrBaseType.void_)) {
5522                     hasValue = true;
5523                     typeStack ~= currentType;
5524                 }
5525                 break;
5526             case arrayType:
5527                 currentType = parseArrayBuilder();
5528                 typeStack ~= currentType;
5529                 hasValue = true;
5530                 break;
5531             case leftBracket:
5532                 //Index
5533                 if (hadValue) {
5534                     hadValue = false;
5535                     currentType = parseArrayIndex(lastType);
5536                     hasReference = true;
5537                     //Check if there is an assignement or not, discard if it's only a rvalue
5538                     const auto nextLexeme = get();
5539                     if (requireLValue(nextLexeme.type) || (isExpectingLValue
5540                             && nextLexeme.type == GrLexemeType.comma)) {
5541                         if ((nextLexeme.type > GrLexemeType.assign && nextLexeme.type <= GrLexemeType.powerAssign)
5542                                 || nextLexeme.type == GrLexemeType.increment
5543                                 || nextLexeme.type == GrLexemeType.decrement) {
5544                             final switch (currentType.baseType) with (GrBaseType) {
5545                             case bool_:
5546                             case int_:
5547                             case function_:
5548                             case task:
5549                             case enum_:
5550                                 setInstruction(GrOpcode.index3_int,
5551                                         cast(int) currentFunction.instructions.length - 1);
5552                                 break;
5553                             case float_:
5554                                 setInstruction(GrOpcode.index3_float,
5555                                         cast(int) currentFunction.instructions.length - 1);
5556                                 break;
5557                             case string_:
5558                                 setInstruction(GrOpcode.index3_string,
5559                                         cast(int) currentFunction.instructions.length - 1);
5560                                 break;
5561                             case array_:
5562                             case class_:
5563                             case foreign:
5564                             case chan:
5565                             case reference:
5566                                 setInstruction(GrOpcode.index3_object,
5567                                         cast(int) currentFunction.instructions.length - 1);
5568                                 break;
5569                             case void_:
5570                             case null_:
5571                             case internalTuple:
5572                                 logError("an array can't be indexed by a `" ~ grGetPrettyType(currentType) ~ "`",
5573                                         "invalid array index type");
5574                                 break;
5575                             }
5576                         }
5577                         hasLValue = true;
5578                         GrVariable refVar = new GrVariable;
5579                         refVar.type.baseType = GrBaseType.reference;
5580                         refVar.type.mangledType = grMangleSignature([
5581                                 currentType
5582                                 ]);
5583                         lvalues ~= refVar;
5584                     }
5585                     else {
5586                         final switch (currentType.baseType) with (GrBaseType) {
5587                         case bool_:
5588                         case int_:
5589                         case function_:
5590                         case task:
5591                         case enum_:
5592                             setInstruction(GrOpcode.index2_int,
5593                                     cast(int) currentFunction.instructions.length - 1);
5594                             break;
5595                         case float_:
5596                             setInstruction(GrOpcode.index2_float,
5597                                     cast(int) currentFunction.instructions.length - 1);
5598                             break;
5599                         case string_:
5600                             setInstruction(GrOpcode.index2_string,
5601                                     cast(int) currentFunction.instructions.length - 1);
5602                             break;
5603                         case array_:
5604                         case class_:
5605                         case foreign:
5606                         case chan:
5607                         case reference:
5608                             setInstruction(GrOpcode.index2_object,
5609                                     cast(int) currentFunction.instructions.length - 1);
5610                             break;
5611                         case void_:
5612                         case null_:
5613                         case internalTuple:
5614                             logError("an array can't be indexed by a `" ~ grGetPrettyType(currentType) ~ "`",
5615                                     "invalid array index type");
5616                             break;
5617                         }
5618                     }
5619                     lastType = currentType;
5620                     typeStack[$ - 1] = currentType;
5621                     hasValue = true;
5622                 }
5623                 else {
5624                     currentType = parseArrayBuilder();
5625                     typeStack ~= currentType;
5626                     hasValue = true;
5627                 }
5628                 break;
5629             case integer:
5630                 currentType = GrType(GrBaseType.int_);
5631                 addIntConstant(lex.ivalue);
5632                 hasValue = true;
5633                 typeStack ~= currentType;
5634                 checkAdvance();
5635                 break;
5636             case float_:
5637                 currentType = GrType(GrBaseType.float_);
5638                 addFloatConstant(lex.fvalue);
5639                 hasValue = true;
5640                 typeStack ~= currentType;
5641                 checkAdvance();
5642                 break;
5643             case boolean:
5644                 currentType = GrType(GrBaseType.bool_);
5645                 addBoolConstant(lex.bvalue);
5646                 hasValue = true;
5647                 typeStack ~= currentType;
5648                 checkAdvance();
5649                 break;
5650             case string_:
5651                 currentType = GrType(GrBaseType.string_);
5652                 addStringConstant(lex.svalue);
5653                 hasValue = true;
5654                 typeStack ~= currentType;
5655                 checkAdvance();
5656                 break;
5657             case null_:
5658                 currentType = GrType(GrBaseType.null_);
5659                 hasValue = true;
5660                 typeStack ~= currentType;
5661                 addInstruction(GrOpcode.const_null);
5662                 checkAdvance();
5663                 break;
5664             case new_:
5665                 currentType = parseObjectBuilder();
5666                 hasValue = true;
5667                 typeStack ~= currentType;
5668                 break;
5669             case chanType:
5670                 currentType = parseChannelBuilder();
5671                 hasValue = true;
5672                 typeStack ~= currentType;
5673                 break;
5674             case period:
5675                 if (currentType.baseType != GrBaseType.class_)
5676                     logError("can't access a field on type `" ~ grGetPrettyType(currentType) ~ "`",
5677                             "expected a class, found `" ~ grGetPrettyType(currentType) ~ "`");
5678                 checkAdvance();
5679                 if (get().type != GrLexemeType.identifier)
5680                     logError("expected field name, found `" ~ grGetPrettyLexemeType(get()
5681                             .type) ~ "`", "missing field");
5682                 const string identifier = get().svalue;
5683                 checkAdvance();
5684                 GrClassDefinition class_ = getClass(currentType.mangledType, get().fileId);
5685                 if (!class_)
5686                     logError("the type `" ~ grGetPrettyType(currentType) ~ "` is not declared",
5687                             "unknown type");
5688                 const auto nbFields = class_.signature.length;
5689                 bool hasField;
5690                 for (int i; i < nbFields; i++) {
5691                     if (identifier == class_.fields[i]) {
5692                         if ((class_.fieldsInfo[i].fileId != fileId)
5693                                 && !class_.fieldsInfo[i].isPublic)
5694                             logError("`" ~ identifier ~ "` on type `" ~ grGetPrettyType(currentType) ~ "` is private",
5695                                     "private field", "", -1);
5696                         hasField = true;
5697                         currentType = class_.signature[i];
5698                         currentType.isField = true;
5699                         GrVariable fieldLValue = new GrVariable;
5700                         fieldLValue.isInitialized = true;
5701                         fieldLValue.isField = true;
5702                         fieldLValue.type = currentType;
5703                         fieldLValue.register = i;
5704                         fieldLValue.fileId = get().fileId;
5705                         fieldLValue.lexPosition = current;
5706 
5707                         if (requireLValue(get().type)) {
5708                             if (hadLValue)
5709                                 lvalues[$ - 1] = fieldLValue;
5710                             else
5711                                 lvalues ~= fieldLValue;
5712                         }
5713 
5714                         if (hadValue)
5715                             typeStack[$ - 1] = currentType;
5716                         else
5717                             typeStack ~= currentType;
5718 
5719                         hasValue = true;
5720                         hadValue = false;
5721                         hasLValue = true;
5722                         hadLValue = false;
5723 
5724                         switch (get().type) with (GrLexemeType) {
5725                         case period:
5726                             addInstruction(GrOpcode.fieldLoad_object, fieldLValue.register);
5727                             break;
5728                         case assign:
5729                             addInstruction(GrOpcode.fieldLoad, fieldLValue.register);
5730                             break;
5731                         case increment:
5732                         case decrement:
5733                         case addAssign: .. case powerAssign:
5734                             addLoadFieldInstruction(currentType, fieldLValue.register, true);
5735                             break;
5736                         case leftParenthesis:
5737                             lvalues.length--;
5738                             addLoadFieldInstruction(currentType, fieldLValue.register, false);
5739                             currentType = parseAnonymousCall(typeStack[$ - 1]);
5740                             //Unpack function value for 1 or less return values
5741                             //Multiples values are left as a tuple for parseExpressionList()
5742                             if (currentType.baseType == GrBaseType.internalTuple) {
5743                                 auto types = grUnpackTuple(currentType);
5744                                 if (!types.length)
5745                                     currentType = grVoid;
5746                                 else if (types.length == 1uL)
5747                                     currentType = types[0];
5748                             }
5749                             if (currentType.baseType == GrBaseType.void_) {
5750                                 typeStack.length--;
5751                             }
5752                             else {
5753                                 hadValue = false;
5754                                 hasValue = true;
5755                                 typeStack[$ - 1] = currentType;
5756                             }
5757                             break;
5758                         case comma:
5759                             if (isExpectingLValue)
5760                                 goto case assign;
5761                             goto default;
5762                         default:
5763                             addLoadFieldInstruction(currentType, fieldLValue.register, false);
5764                             break;
5765                         }
5766                         break;
5767                     }
5768                 }
5769                 if (!hasField) {
5770                     const string[] nearestValues = findNearestStrings(identifier, class_.fields);
5771                     string errorNote;
5772                     if (nearestValues.length) {
5773                         errorNote = "available fields are: ";
5774                         foreach (size_t i, const string value; nearestValues) {
5775                             errorNote ~= "`" ~ value ~ "`";
5776                             if ((i + 1) < nearestValues.length)
5777                                 errorNote ~= ", ";
5778                         }
5779                         errorNote ~= ".";
5780                     }
5781                     logError("no field `" ~ identifier ~ "` on type `" ~ grGetPrettyType(currentType) ~ "`",
5782                             "unknown field", errorNote, -1);
5783                 }
5784                 break;
5785             case colon:
5786                 const size_t methodCallPos = current;
5787                 if (!hadValue)
5788                     logError("missing parameter on method call",
5789                             "the method call must be done after a value");
5790                 checkAdvance();
5791                 GrType selfType = currentType;
5792                 if (get().type != GrLexemeType.identifier)
5793                     logError("expected function name, found `" ~ grGetPrettyLexemeType(get()
5794                             .type) ~ "`", "missing function name");
5795                 const string identifier = get().svalue;
5796                 checkAdvance();
5797                 bool hasField;
5798 
5799                 if (currentType.baseType == GrBaseType.class_) {
5800                     GrClassDefinition class_ = getClass(currentType.mangledType, get().fileId);
5801                     if (!class_)
5802                         logError("`" ~ grGetPrettyType(currentType) ~ "` is not declared",
5803                                 "unknown class", "", -1);
5804                     const auto nbFields = class_.signature.length;
5805                     for (int i; i < nbFields; i++) {
5806                         if (identifier == class_.fields[i]) {
5807                             if ((class_.fieldsInfo[i].fileId != fileId)
5808                                     && !class_.fieldsInfo[i].isPublic) {
5809                                 const string errMsg = "`" ~ identifier ~ "` of type `" ~ grGetPrettyType(
5810                                         currentType) ~ "` is private";
5811                                 logError(errMsg, "private field", "", -1);
5812                             }
5813                             hasField = true;
5814                             currentType = class_.signature[i];
5815                             currentType.isField = true;
5816                             GrVariable fieldLValue = new GrVariable;
5817                             fieldLValue.isInitialized = true;
5818                             fieldLValue.isField = true;
5819                             fieldLValue.type = currentType;
5820                             fieldLValue.register = i;
5821                             fieldLValue.fileId = get().fileId;
5822                             fieldLValue.lexPosition = current;
5823 
5824                             if (hadLValue)
5825                                 lvalues.length--;
5826 
5827                             if (hadValue)
5828                                 typeStack[$ - 1] = currentType;
5829                             else
5830                                 typeStack ~= currentType;
5831 
5832                             hasValue = true;
5833                             hadValue = false;
5834                             hasLValue = true;
5835                             hadLValue = false;
5836 
5837                             addInstruction(GrOpcode.copy_object);
5838                             addLoadFieldInstruction(currentType, fieldLValue.register, false);
5839                             currentType = parseAnonymousCall(typeStack[$ - 1], selfType);
5840                             //Unpack function value for 1 or less return values
5841                             //Multiples values are left as a tuple for parseExpressionList()
5842                             if (currentType.baseType == GrBaseType.internalTuple) {
5843                                 auto types = grUnpackTuple(currentType);
5844                                 if (!types.length)
5845                                     currentType = grVoid;
5846                                 else if (types.length == 1uL)
5847                                     currentType = types[0];
5848                             }
5849                             if (currentType.baseType == GrBaseType.void_) {
5850                                 typeStack.length--;
5851                             }
5852                             else {
5853                                 hadValue = false;
5854                                 hasValue = true;
5855                                 typeStack[$ - 1] = currentType;
5856                             }
5857                             break;
5858                         }
5859                     }
5860                 }
5861                 if (!hasField) {
5862                     current = methodCallPos;
5863                     goto case doubleColon;
5864                 }
5865                 break;
5866             case pointer:
5867                 currentType = parseFunctionPointer(currentType);
5868                 typeStack ~= currentType;
5869                 hasValue = true;
5870                 break;
5871             case as:
5872                 if (!hadValue)
5873                     logError("`as` must be placed after a value", "missing value");
5874                 currentType = parseConversionOperator(typeStack);
5875                 hasValue = true;
5876                 hadValue = false;
5877                 break;
5878             case self:
5879                 // Parse a function call that refers to its parent. 
5880                 checkAdvance();
5881                 currentType = addFunctionAddress(currentFunction, get().fileId);
5882                 if (currentType.baseType == GrBaseType.void_)
5883                     logError("`self` must be inside a function or a task",
5884                             "`self` references no function nor task", "", -1);
5885                 typeStack ~= currentType;
5886                 hasValue = true;
5887                 break;
5888             case functionType:
5889                 currentType = parseAnonymousFunction(false);
5890                 typeStack ~= currentType;
5891                 hasValue = true;
5892                 break;
5893             case taskType:
5894                 currentType = parseAnonymousFunction(true);
5895                 typeStack ~= currentType;
5896                 hasValue = true;
5897                 break;
5898             case assign:
5899                 if (useAssign) {
5900                     isEndOfExpression = true;
5901                     break;
5902                 }
5903                 goto case addAssign;
5904             case addAssign: .. case powerAssign:
5905                 if (!hadLValue)
5906                     logError("the value before assignation is not referenceable",
5907                             "missing reference before assignation");
5908                 hadLValue = false;
5909                 goto case multiply;
5910             case add:
5911                 if (!hadValue)
5912                     lex.type = GrLexemeType.plus;
5913                 goto case multiply;
5914             case substract:
5915                 if (!hadValue)
5916                     lex.type = GrLexemeType.minus;
5917                 goto case multiply;
5918             case send:
5919                 if (!hadValue)
5920                     lex.type = GrLexemeType.receive;
5921                 goto case multiply;
5922             case increment: .. case decrement:
5923                 isRightUnaryOperator = true;
5924                 goto case multiply;
5925             case multiply: .. case not:
5926                 if (isExpectingLValue)
5927                     logError(
5928                             "can't do this kind of operation on the left side of an assignment",
5929                             "unexpected operation");
5930                 if (!hadValue && lex.type != GrLexemeType.plus
5931                         && lex.type != GrLexemeType.minus && lex.type != GrLexemeType.not
5932                         && lex.type != GrLexemeType.receive)
5933                     logError("a binary operation must have 2 operands", "missing value");
5934 
5935                 while (operatorsStack.length
5936                         && getLeftOperatorPriority(operatorsStack[$ - 1]) > getRightOperatorPriority(
5937                             lex.type)) {
5938                     GrLexemeType operator = operatorsStack[$ - 1];
5939 
5940                     switch (operator) with (GrLexemeType) {
5941                     case assign:
5942                         addSetInstruction(lvalues[$ - 1], fileId, currentType, true);
5943                         lvalues.length--;
5944                         break;
5945                     case addAssign: .. case powerAssign:
5946                         currentType = addOperator(operator - (GrLexemeType.addAssign - GrLexemeType.add),
5947                                 typeStack, fileId);
5948                         addSetInstruction(lvalues[$ - 1], fileId, currentType, true);
5949                         lvalues.length--;
5950                         break;
5951                     case increment: .. case decrement:
5952                         currentType = addOperator(operator, typeStack, fileId);
5953                         addSetInstruction(lvalues[$ - 1], fileId, currentType, true);
5954                         lvalues.length--;
5955                         break;
5956                     default:
5957                         currentType = addOperator(operator, typeStack, fileId);
5958                         break;
5959                     }
5960 
5961                     operatorsStack.length--;
5962                 }
5963 
5964                 operatorsStack ~= lex.type;
5965                 if (hadValue && isRightUnaryOperator) {
5966                     hasValue = true;
5967                     hadValue = false;
5968                 }
5969                 else
5970                     hasValue = false;
5971                 checkAdvance();
5972                 break;
5973             case identifier:
5974                 GrVariable lvalue;
5975                 currentType = parseIdentifier(lvalue, lastType, grVoid, isExpectingLValue);
5976                 //Unpack function value for 1 or less return values
5977                 //Multiples values are left as a tuple for parseExpressionList()
5978                 if (currentType.baseType == GrBaseType.internalTuple) {
5979                     auto types = grUnpackTuple(currentType);
5980                     if (!types.length)
5981                         currentType = grVoid;
5982                     else if (types.length == 1uL)
5983                         currentType = types[0];
5984                 }
5985 
5986                 //Check if there is an assignement or not, discard if it's only a rvalue
5987                 const auto nextLexeme = get();
5988                 if (lvalue !is null && (requireLValue(nextLexeme.type)
5989                         || (isExpectingLValue && nextLexeme.type == GrLexemeType.comma))) {
5990                     hasLValue = true;
5991                     lvalues ~= lvalue;
5992 
5993                     if (lvalue.isAuto)
5994                         hasValue = true;
5995                 }
5996 
5997                 if (!hasLValue && nextLexeme.type == GrLexemeType.leftBracket)
5998                     hasReference = true;
5999 
6000                 if (currentType != GrType(GrBaseType.void_)) {
6001                     hasValue = true;
6002                     typeStack ~= currentType;
6003                 }
6004                 break;
6005             default:
6006                 logError("unexpected `" ~ grGetPrettyLexemeType(lex.type) ~ "` symbol in the expression",
6007                         "unexpected symbol");
6008             }
6009 
6010             if (hasValue && hadValue)
6011                 logError("missing semicolon at the end of the expression",
6012                         "expected `;`, found `" ~ grGetPrettyLexemeType(get().type) ~ "`");
6013         }
6014         while (!isEndOfExpression);
6015 
6016         if (operatorsStack.length) {
6017             if (!hadValue) {
6018                 logError("a binary operation must have 2 operands", "missing value");
6019             }
6020         }
6021 
6022         while (operatorsStack.length) {
6023             GrLexemeType operator = operatorsStack[$ - 1];
6024 
6025             switch (operator) with (GrLexemeType) {
6026             case assign:
6027                 addSetInstruction(lvalues[$ - 1], fileId, currentType,
6028                         isExpectingValue || operatorsStack.length > 1uL);
6029                 lvalues.length--;
6030 
6031                 if (operatorsStack.length <= 1uL)
6032                     hadValue = false;
6033                 break;
6034             case addAssign: .. case powerAssign:
6035                 currentType = addOperator(
6036                         operator - (GrLexemeType.addAssign - GrLexemeType.add), typeStack, fileId);
6037                 addSetInstruction(lvalues[$ - 1], fileId, currentType,
6038                         isExpectingValue || operatorsStack.length > 1uL);
6039                 lvalues.length--;
6040 
6041                 if (operatorsStack.length <= 1uL)
6042                     hadValue = false;
6043                 break;
6044             case increment: .. case decrement:
6045                 currentType = addOperator(operator, typeStack, fileId);
6046                 addSetInstruction(lvalues[$ - 1], fileId, currentType,
6047                         isExpectingValue || operatorsStack.length > 1uL);
6048                 lvalues.length--;
6049 
6050                 if (operatorsStack.length <= 1uL)
6051                     hadValue = false;
6052                 break;
6053             default:
6054                 currentType = addOperator(operator, typeStack, fileId);
6055                 break;
6056             }
6057 
6058             operatorsStack.length--;
6059         }
6060 
6061         if (isExpectingLValue) {
6062             if (!hadLValue)
6063                 logError("the value before assignation is not referenceable",
6064                         "missing reference before assignation");
6065             result.lvalue = lvalues[$ - 1];
6066         }
6067 
6068         if (mustCleanValue && hadValue && currentType.baseType != GrBaseType.void_)
6069             shiftStackPosition(currentType, -1);
6070 
6071         result.type = currentType;
6072         return result;
6073     }
6074 
6075     private void addLoadFieldInstruction(GrType type, uint index, bool asCopy) {
6076         final switch (type.baseType) with (GrBaseType) {
6077         case bool_:
6078         case int_:
6079         case function_:
6080         case task:
6081         case enum_:
6082             addInstruction(asCopy ? GrOpcode.fieldLoad2_int : GrOpcode.fieldLoad_int, index);
6083             break;
6084         case float_:
6085             addInstruction(asCopy ? GrOpcode.fieldLoad2_float : GrOpcode.fieldLoad_float, index);
6086             break;
6087         case string_:
6088             addInstruction(asCopy ? GrOpcode.fieldLoad2_string : GrOpcode.fieldLoad_string, index);
6089             break;
6090         case reference:
6091         case chan:
6092         case class_:
6093         case array_:
6094         case foreign:
6095             addInstruction(asCopy ? GrOpcode.fieldLoad2_object : GrOpcode.fieldLoad_object, index);
6096             break;
6097         case internalTuple:
6098         case null_:
6099         case void_:
6100             logError("can't load a field of type `" ~ grGetPrettyType(type) ~ "`",
6101                     "the field type is invalid");
6102             break;
6103         }
6104     }
6105 
6106     /// Parse a function call from a runtime value.
6107     private GrType parseAnonymousCall(GrType type, GrType selfType = grVoid) {
6108         const uint fileId = get().fileId;
6109 
6110         GrVariable functionId;
6111         if (type.baseType == GrBaseType.function_) {
6112             functionId = registerSpecialVariable("anon", GrType(GrBaseType.int_));
6113             addSetInstruction(functionId, fileId, GrType(GrBaseType.int_));
6114         }
6115         else if (type.baseType != GrBaseType.task) {
6116             logError("can't call a `" ~ grGetPrettyType(type) ~ "`",
6117                     "`" ~ grGetPrettyType(type) ~ "` is not a function nor a task");
6118         }
6119 
6120         //Signature parsing with type conversion
6121         GrType[] signature;
6122         GrType[] anonSignature = grUnmangleSignature(type.mangledType);
6123         int i;
6124         if (selfType != grVoid) {
6125             signature ~= convertType(selfType, anonSignature[i], fileId);
6126             i++;
6127         }
6128         if (get().type == GrLexemeType.leftParenthesis) {
6129             checkAdvance();
6130             if (get().type != GrLexemeType.rightParenthesis) {
6131                 for (;;) {
6132                     if (i >= anonSignature.length) {
6133                         const string argStr = to!string(anonSignature.length) ~ (anonSignature.length > 1
6134                                 ? " arguments" : " argument");
6135                         logError("the function takes " ~ argStr ~ " but more were supplied", "expected " ~ argStr,
6136                                 "the function is of type `" ~ grGetPrettyType(type) ~ "`");
6137                     }
6138                     GrType subType = parseSubExpression(
6139                             GR_SUBEXPR_TERMINATE_COMMA | GR_SUBEXPR_TERMINATE_PARENTHESIS
6140                             | GR_SUBEXPR_EXPECTING_VALUE).type;
6141                     signature ~= convertType(subType, anonSignature[i], fileId);
6142                     if (get().type == GrLexemeType.rightParenthesis) {
6143                         checkAdvance();
6144                         break;
6145                     }
6146                     advance();
6147                     i++;
6148                 }
6149             }
6150             else {
6151                 checkAdvance();
6152             }
6153         }
6154         if (signature.length != anonSignature.length) {
6155             const string argStr = to!string(anonSignature.length) ~ (anonSignature.length > 1
6156                     ? " arguments" : " argument");
6157             const string argStr2 = to!string(signature.length) ~ (signature.length > 1
6158                     ? " arguments" : " argument");
6159             logError("the function takes " ~ argStr ~ " but " ~ argStr2 ~ " were supplied",
6160                     "expected " ~ argStr ~ ", found " ~ argStr2,
6161                     "the function is of type `" ~ grGetPrettyType(type) ~ "`");
6162         }
6163 
6164         //Push the values on the global stack for task spawning.
6165         if (type.baseType == GrBaseType.task)
6166             addGlobalPush(signature);
6167 
6168         //Anonymous call.
6169         GrType retTypes = grPackTuple(grUnmangleSignature(type.mangledReturnType));
6170 
6171         if (type.baseType == GrBaseType.function_) {
6172             addGetInstruction(functionId, GrType(GrBaseType.int_));
6173         }
6174 
6175         if (type.baseType == GrBaseType.function_)
6176             addInstruction(GrOpcode.anonymousCall, 0u);
6177         else
6178             addInstruction(GrOpcode.anonymousTask, 0u);
6179         return retTypes;
6180     }
6181 
6182     /// Parse an identifier or function call and return the deduced return type and lvalue.
6183     private GrType parseIdentifier(ref GrVariable variable, GrType expectedType,
6184             GrType selfType = grVoid, bool isAssignment = false) {
6185         GrType returnType = GrBaseType.void_;
6186         const GrLexeme identifier = get();
6187         bool isFunctionCall = false, isMethodCall = false, hasParenthesis = false;
6188         string identifierName = identifier.svalue;
6189         const uint fileId = identifier.fileId;
6190 
6191         advance();
6192 
6193         if (selfType.baseType != GrBaseType.void_) {
6194             isMethodCall = true;
6195             isFunctionCall = true;
6196         }
6197 
6198         if (get().type == GrLexemeType.leftParenthesis) {
6199             isFunctionCall = true;
6200             hasParenthesis = true;
6201         }
6202 
6203         if (isFunctionCall) {
6204             GrType[] signature;
6205 
6206             if (hasParenthesis)
6207                 advance();
6208 
6209             GrVariable var = currentFunction.getLocal(identifierName);
6210             if (!var)
6211                 var = getGlobalVariable(identifierName, fileId);
6212             if (var) {
6213                 if (var.type.baseType != GrBaseType.function_ && var.type.baseType
6214                         != GrBaseType.task)
6215                     logError("`" ~ identifierName ~ "` is not callable",
6216                             "function or task expected, found `" ~ grGetPrettyType(var.type) ~ "`",
6217                             "", -1);
6218                 //Signature parsing with type conversion
6219                 GrType[] anonSignature = grUnmangleSignature(var.type.mangledType);
6220                 int i;
6221                 if (isMethodCall) {
6222                     if (!anonSignature.length)
6223                         logError("missing parameter on method call",
6224                                 "the method call must be done after a value");
6225                     signature ~= convertType(selfType, anonSignature[i], fileId);
6226                     i++;
6227                 }
6228                 if (hasParenthesis && get().type != GrLexemeType.rightParenthesis) {
6229                     for (;;) {
6230                         if (i >= anonSignature.length) {
6231                             const string argStr = to!string(anonSignature.length) ~ (anonSignature.length > 1
6232                                     ? " arguments" : " argument");
6233                             logError("the function takes " ~ argStr ~ " but more were supplied", "expected " ~ argStr,
6234                                     "the function is of type `" ~ grGetPrettyType(var.type) ~ "`",
6235                                     0, "function defined here", var.lexPosition);
6236                         }
6237                         GrType subType = parseSubExpression(
6238                                 GR_SUBEXPR_TERMINATE_COMMA | GR_SUBEXPR_TERMINATE_PARENTHESIS
6239                                 | GR_SUBEXPR_EXPECTING_VALUE).type;
6240                         if (subType.baseType == GrBaseType.internalTuple) {
6241                             auto types = grUnpackTuple(subType);
6242                             if (types.length) {
6243                                 for (int y; y < types.length; y++, i++) {
6244                                     signature ~= convertType(types[y], anonSignature[i], fileId);
6245                                 }
6246                             }
6247                             else
6248                                 logError("the expression yields no value",
6249                                         "expected value, found nothing");
6250                         }
6251                         else {
6252                             signature ~= convertType(subType, anonSignature[i], fileId);
6253                             i++;
6254                         }
6255                         if (get().type == GrLexemeType.rightParenthesis) {
6256                             if (signature.length != anonSignature.length) {
6257                                 const string argStr = to!string(anonSignature.length) ~ (anonSignature.length > 1
6258                                         ? " arguments" : " argument");
6259                                 const string argStr2 = to!string(signature.length) ~ (signature.length > 1
6260                                         ? " arguments" : " argument");
6261                                 logError("the function takes " ~ argStr ~ " but " ~ argStr2 ~ " were supplied",
6262                                         "expected " ~ argStr ~ ", found " ~ argStr2,
6263                                         "the function is of type `" ~ grGetPrettyType(var.type)
6264                                         ~ "`");
6265                             }
6266                             break;
6267                         }
6268                         advance();
6269                     }
6270                     if (hasParenthesis && get().type == GrLexemeType.rightParenthesis)
6271                         advance();
6272                 }
6273                 else {
6274                     if (hasParenthesis && get().type == GrLexemeType.rightParenthesis)
6275                         advance();
6276                     if (signature.length != anonSignature.length) {
6277                         const string argStr = to!string(anonSignature.length) ~ (anonSignature.length > 1
6278                                 ? " arguments" : " argument");
6279                         const string argStr2 = to!string(signature.length) ~ (signature.length > 1
6280                                 ? " arguments" : " argument");
6281                         logError("the function takes " ~ argStr ~ " but " ~ argStr2 ~ " were supplied",
6282                                 "expected " ~ argStr ~ ", found " ~ argStr2,
6283                                 "the function is of type `" ~ grGetPrettyType(var.type) ~ "`");
6284                     }
6285                 }
6286 
6287                 //Push the values on the global stack for task spawning.
6288                 if (var.type.baseType == GrBaseType.task)
6289                     addGlobalPush(signature);
6290 
6291                 //Anonymous call.
6292                 //bool hasAnonFunc = false;
6293                 addGetInstruction(var);
6294 
6295                 returnType = grPackTuple(grUnmangleSignature(var.type.mangledReturnType));
6296 
6297                 if (var.type.baseType == GrBaseType.function_)
6298                     addInstruction(GrOpcode.anonymousCall, 0u);
6299                 else if (var.type.baseType == GrBaseType.task)
6300                     addInstruction(GrOpcode.anonymousTask, 0u);
6301             }
6302             else {
6303                 if (isMethodCall) {
6304                     if (selfType.baseType == GrBaseType.internalTuple)
6305                         signature ~= grUnpackTuple(selfType);
6306                     else
6307                         signature ~= selfType;
6308                 }
6309                 //Signature parsing, no coercion is made
6310                 if (hasParenthesis && get().type != GrLexemeType.rightParenthesis) {
6311                     for (;;) {
6312                         auto type = parseSubExpression(
6313                                 GR_SUBEXPR_TERMINATE_COMMA | GR_SUBEXPR_TERMINATE_PARENTHESIS
6314                                 | GR_SUBEXPR_EXPECTING_VALUE).type;
6315                         if (type.baseType == GrBaseType.internalTuple) {
6316                             auto types = grUnpackTuple(type);
6317                             if (types.length)
6318                                 signature ~= types;
6319                             else
6320                                 logError("the expression yields no value",
6321                                         "expected value, found nothing");
6322                         }
6323                         else
6324                             signature ~= type;
6325 
6326                         if (get().type == GrLexemeType.rightParenthesis)
6327                             break;
6328                         advance();
6329                     }
6330                 }
6331                 if (hasParenthesis && get().type == GrLexemeType.rightParenthesis)
6332                     advance();
6333 
6334                 //GrPrimitive call.
6335                 GrPrimitive primitive = _data.getPrimitive(identifierName, signature);
6336                 if (primitive) {
6337                     addInstruction(GrOpcode.primitiveCall, primitive.index);
6338                     returnType = grPackTuple(primitive.outSignature);
6339                 }
6340                 else //GrFunction/Task call.
6341                     returnType = grPackTuple(addFunctionCall(identifierName, signature, fileId));
6342             }
6343         }
6344         else if (_data.isEnum(identifier.svalue, fileId, false)) {
6345             const GrEnumDefinition definition = _data.getEnum(identifier.svalue, fileId);
6346             if (get().type != GrLexemeType.period)
6347                 logError("expected a `.` after the enum type", "missing the enum constant name");
6348             checkAdvance();
6349             if (get().type != GrLexemeType.identifier)
6350                 logError("expected a constant name after the enum type",
6351                         "missing the enum constant name");
6352             const string fieldName = get().svalue;
6353             if (!definition.hasField(fieldName)) {
6354                 const string[] nearestValues = findNearestStrings(fieldName, definition.fields);
6355                 string errorNote;
6356                 if (nearestValues.length) {
6357                     errorNote = "available fields are: ";
6358                     foreach (size_t i, const string value; nearestValues) {
6359                         errorNote ~= "`" ~ value ~ "`";
6360                         if ((i + 1) < nearestValues.length)
6361                             errorNote ~= ", ";
6362                     }
6363                     errorNote ~= ".";
6364                 }
6365                 logError("no field `" ~ fieldName ~ "` on type `" ~ definition.name ~ "`",
6366                         "unknown field", errorNote);
6367             }
6368             checkAdvance();
6369 
6370             returnType = GrType(GrBaseType.enum_);
6371             returnType.mangledType = definition.name;
6372             addIntConstant(definition.getField(fieldName));
6373         }
6374         else {
6375             //Declared variable.
6376             variable = getVariable(identifierName, fileId);
6377             returnType = variable.type;
6378             //If it's an assignement, we want the GET instruction to be after the assignement, not there.
6379             const auto nextLexeme = get();
6380             if (!(nextLexeme.type == GrLexemeType.assign || (isAssignment
6381                     && nextLexeme.type == GrLexemeType.comma)))
6382                 addGetInstruction(variable, expectedType);
6383         }
6384         return returnType;
6385     }
6386 
6387     /// Check an raise_ an error.
6388     private void assertError(bool assertion, string message, string info,
6389             string note = "", int offset = 0) {
6390         if (assertion)
6391             return;
6392         logError(message, info, note, offset);
6393     }
6394 
6395     /// Log an error and throw an exception.
6396     private void logError(string message, string info, string note = "",
6397             int offset = 0, string otherInfo = "", uint otherPos = 0) {
6398         GrError error = new GrError;
6399         error.type = GrError.Type.parser;
6400         error.message = message;
6401         error.info = info;
6402         error.note = note;
6403 
6404         GrLexeme lex = (isEnd() && offset >= 0) ? get(-1) : get(offset);
6405         error.filePath = lex.getFile();
6406         error.lineText = lex.getLine().replace("\t", " ");
6407         error.line = lex.line + 1u; // By convention, the first line is 1, not 0.
6408         error.column = lex.column;
6409         error.textLength = lex.textLength;
6410 
6411         if (otherInfo.length) {
6412             error.otherInfo = otherInfo;
6413 
6414             set(otherPos);
6415 
6416             GrLexeme otherLex = isEnd() ? get(-1) : get();
6417             error.otherFilePath = otherLex.getFile();
6418             error.otherLineText = otherLex.getLine().replace("\t", " ");
6419             error.otherLine = otherLex.line + 1u; // By convention, the first line is 1, not 0.
6420             error.otherColumn = otherLex.column;
6421             error.otherTextLength = otherLex.textLength;
6422         }
6423 
6424         throw new GrParserException(error);
6425     }
6426 }
6427 
6428 /**
6429 Syntatic error during parsing
6430 */
6431 package final class GrParserException : Exception {
6432     GrError error;
6433 
6434     /// Ctor
6435     this(GrError error_, string file = __FILE__, size_t line = __LINE__) {
6436         super(error_.message, file, line);
6437         error = error_;
6438     }
6439 }