d: Merge dmd, druntime d8e3976a58, phobos 7a6e95688
[official-gcc.git] / gcc / d / dmd / dinterpret.d
blobeda91d1ea0580545e0516fe0bd85ce65132b5e63
1 /**
2 * The entry point for CTFE.
4 * Specification: ($LINK2 https://dlang.org/spec/function.html#interpretation, Compile Time Function Execution (CTFE))
6 * Copyright: Copyright (C) 1999-2024 by The D Language Foundation, All Rights Reserved
7 * Authors: $(LINK2 https://www.digitalmars.com, Walter Bright)
8 * License: $(LINK2 https://www.boost.org/LICENSE_1_0.txt, Boost License 1.0)
9 * Source: $(LINK2 https://github.com/dlang/dmd/blob/master/src/dmd/dinterpret.d, _dinterpret.d)
10 * Documentation: https://dlang.org/phobos/dmd_dinterpret.html
11 * Coverage: https://codecov.io/gh/dlang/dmd/src/master/src/dmd/dinterpret.d
14 module dmd.dinterpret;
16 import core.stdc.stdio;
17 import core.stdc.stdlib;
18 import core.stdc.string;
19 import dmd.arraytypes;
20 import dmd.astenums;
21 import dmd.attrib;
22 import dmd.builtin;
23 import dmd.constfold;
24 import dmd.ctfeexpr;
25 import dmd.dcast;
26 import dmd.dclass;
27 import dmd.declaration;
28 import dmd.dstruct;
29 import dmd.dsymbol;
30 import dmd.dsymbolsem;
31 import dmd.dtemplate;
32 import dmd.errors;
33 import dmd.expression;
34 import dmd.expressionsem;
35 import dmd.func;
36 import dmd.globals;
37 import dmd.hdrgen;
38 import dmd.id;
39 import dmd.identifier;
40 import dmd.init;
41 import dmd.initsem;
42 import dmd.location;
43 import dmd.mtype;
44 import dmd.root.rmem;
45 import dmd.root.array;
46 import dmd.root.ctfloat;
47 import dmd.root.region;
48 import dmd.rootobject;
49 import dmd.root.utf;
50 import dmd.statement;
51 import dmd.tokens;
52 import dmd.visitor;
54 /*************************************
55 * Entry point for CTFE.
56 * A compile-time result is required. Give an error if not possible.
58 * `e` must be semantically valid expression. In other words, it should not
59 * contain any `ErrorExp`s in it. But, CTFE interpretation will cross over
60 * functions and may invoke a function that contains `ErrorStatement` in its body.
61 * If that, the "CTFE failed because of previous errors" error is raised.
63 extern(C++) public Expression ctfeInterpret(Expression e)
65 switch (e.op)
67 case EXP.int64:
68 case EXP.float64:
69 case EXP.complex80:
70 case EXP.null_:
71 case EXP.void_:
72 case EXP.string_:
73 case EXP.this_:
74 case EXP.super_:
75 case EXP.type:
76 case EXP.typeid_:
77 case EXP.template_: // non-eponymous template/instance
78 case EXP.scope_: // ditto
79 case EXP.dotTemplateDeclaration: // ditto, e.e1 doesn't matter here
80 case EXP.dotTemplateInstance: // ditto
81 case EXP.dot: // ditto
82 if (e.type.ty == Terror)
83 return ErrorExp.get();
84 goto case EXP.error;
86 case EXP.error:
87 return e;
89 default:
90 break;
93 assert(e.type); // https://issues.dlang.org/show_bug.cgi?id=14642
94 //assert(e.type.ty != Terror); // FIXME
95 if (e.type.ty == Terror)
96 return ErrorExp.get();
98 auto rgnpos = ctfeGlobals.region.savePos();
100 Expression result = interpret(e, null);
102 // Report an error if the expression contained a `ThrowException` and
103 // hence generated an uncaught exception
104 if (auto tee = result.isThrownExceptionExp())
106 tee.generateUncaughtError();
107 result = CTFEExp.cantexp;
109 else
110 result = copyRegionExp(result);
112 if (!CTFEExp.isCantExp(result))
113 result = scrubReturnValue(e.loc, result);
114 if (CTFEExp.isCantExp(result))
115 result = ErrorExp.get();
117 ctfeGlobals.region.release(rgnpos);
119 return result;
122 /* Run CTFE on the expression, but allow the expression to be a TypeExp
123 * or a tuple containing a TypeExp. (This is required by pragma(msg)).
125 public Expression ctfeInterpretForPragmaMsg(Expression e)
127 if (e.op == EXP.error || e.op == EXP.type)
128 return e;
130 // It's also OK for it to be a function declaration (happens only with
131 // __traits(getOverloads))
132 if (auto ve = e.isVarExp())
133 if (ve.var.isFuncDeclaration())
135 return e;
138 auto tup = e.isTupleExp();
139 if (!tup)
140 return e.ctfeInterpret();
142 // Tuples need to be treated separately, since they are
143 // allowed to contain a TypeExp in this case.
145 Expressions* expsx = null;
146 foreach (i, g; *tup.exps)
148 auto h = ctfeInterpretForPragmaMsg(g);
149 if (h != g)
151 if (!expsx)
153 expsx = tup.exps.copy();
155 (*expsx)[i] = h;
158 if (expsx)
160 auto te = new TupleExp(e.loc, expsx);
161 expandTuples(te.exps);
162 te.type = new TypeTuple(te.exps);
163 return te;
165 return e;
168 public Expression getValue(VarDeclaration vd)
170 return ctfeGlobals.stack.getValue(vd);
173 /*************************************************
174 * Allocate an Expression in the ctfe region.
175 * Params:
176 * T = type of Expression to allocate
177 * args = arguments to Expression's constructor
178 * Returns:
179 * allocated Expression
181 T ctfeEmplaceExp(T : Expression, Args...)(Args args)
183 if (mem.isGCEnabled)
184 return new T(args);
185 auto p = ctfeGlobals.region.malloc(__traits(classInstanceSize, T));
186 emplaceExp!T(p, args);
187 return cast(T)p;
190 // CTFE diagnostic information
191 public extern (C++) void printCtfePerformanceStats()
193 debug (SHOWPERFORMANCE)
195 printf(" ---- CTFE Performance ----\n");
196 printf("max call depth = %d\tmax stack = %d\n", ctfeGlobals.maxCallDepth, ctfeGlobals.stack.maxStackUsage());
197 printf("array allocs = %d\tassignments = %d\n\n", ctfeGlobals.numArrayAllocs, ctfeGlobals.numAssignments);
201 /**************************
204 void incArrayAllocs()
206 ++ctfeGlobals.numArrayAllocs;
209 /* ================================================ Implementation ======================================= */
211 private:
213 /***************
214 * Collect together globals used by CTFE
216 struct CtfeGlobals
218 Region region;
220 CtfeStack stack;
222 int callDepth = 0; // current number of recursive calls
224 // When printing a stack trace, suppress this number of calls
225 int stackTraceCallsToSuppress = 0;
227 int maxCallDepth = 0; // highest number of recursive calls
228 int numArrayAllocs = 0; // Number of allocated arrays
229 int numAssignments = 0; // total number of assignments executed
232 __gshared CtfeGlobals ctfeGlobals;
234 enum CTFEGoal : int
236 RValue, /// Must return an Rvalue (== CTFE value)
237 LValue, /// Must return an Lvalue (== CTFE reference)
238 Nothing, /// The return value is not required
241 //debug = LOG;
242 //debug = LOGASSIGN;
243 //debug = LOGCOMPILE;
244 //debug = SHOWPERFORMANCE;
246 // Maximum allowable recursive function calls in CTFE
247 enum CTFE_RECURSION_LIMIT = 1000;
250 The values of all CTFE variables
252 struct CtfeStack
254 private:
255 /* The stack. Every declaration we encounter is pushed here,
256 * together with the VarDeclaration, and the previous
257 * stack address of that variable, so that we can restore it
258 * when we leave the stack frame.
259 * Note that when a function is forward referenced, the interpreter must
260 * run semantic3, and that may start CTFE again with a NULL istate. Thus
261 * the stack might not be empty when CTFE begins.
263 * Ctfe Stack addresses are just 0-based integers, but we save
264 * them as 'void *' because Array can only do pointers.
266 Expressions values; // values on the stack
267 VarDeclarations vars; // corresponding variables
268 Array!(void*) savedId; // id of the previous state of that var
270 Array!(void*) frames; // all previous frame pointers
271 Expressions savedThis; // all previous values of localThis
273 /* Global constants get saved here after evaluation, so we never
274 * have to redo them. This saves a lot of time and memory.
276 Expressions globalValues; // values of global constants
278 size_t framepointer; // current frame pointer
279 size_t maxStackPointer; // most stack we've ever used
280 Expression localThis; // value of 'this', or NULL if none
282 public:
283 size_t stackPointer() @safe
285 return values.length;
288 // The current value of 'this', or NULL if none
289 Expression getThis() @safe
291 return localThis;
294 // Largest number of stack positions we've used
295 size_t maxStackUsage() @safe
297 return maxStackPointer;
300 // Start a new stack frame, using the provided 'this'.
301 void startFrame(Expression thisexp)
303 frames.push(cast(void*)cast(size_t)framepointer);
304 savedThis.push(localThis);
305 framepointer = stackPointer();
306 localThis = thisexp;
309 void endFrame()
311 size_t oldframe = cast(size_t)frames[frames.length - 1];
312 localThis = savedThis[savedThis.length - 1];
313 popAll(framepointer);
314 framepointer = oldframe;
315 frames.setDim(frames.length - 1);
316 savedThis.setDim(savedThis.length - 1);
319 bool isInCurrentFrame(VarDeclaration v)
321 if (v.isDataseg() && !v.isCTFE())
322 return false; // It's a global
323 return v.ctfeAdrOnStack >= framepointer;
326 Expression getValue(VarDeclaration v)
328 //printf("getValue() %s\n", v.toChars());
329 if ((v.isDataseg() || v.storage_class & STC.manifest) && !v.isCTFE())
331 assert(v.ctfeAdrOnStack < globalValues.length);
332 return globalValues[v.ctfeAdrOnStack];
334 assert(v.ctfeAdrOnStack < stackPointer());
335 return values[v.ctfeAdrOnStack];
338 void setValue(VarDeclaration v, Expression e)
340 //printf("setValue() %s : %s\n", v.toChars(), e.toChars());
341 assert(!v.isDataseg() || v.isCTFE());
342 assert(v.ctfeAdrOnStack < stackPointer());
343 values[v.ctfeAdrOnStack] = e;
346 void push(VarDeclaration v)
348 //printf("push() %s\n", v.toChars());
349 assert(!v.isDataseg() || v.isCTFE());
350 if (v.ctfeAdrOnStack != VarDeclaration.AdrOnStackNone && v.ctfeAdrOnStack >= framepointer)
352 // Already exists in this frame, reuse it.
353 values[v.ctfeAdrOnStack] = null;
354 return;
356 savedId.push(cast(void*)cast(size_t)v.ctfeAdrOnStack);
357 v.ctfeAdrOnStack = cast(uint)values.length;
358 vars.push(v);
359 values.push(null);
362 void pop(VarDeclaration v)
364 assert(!v.isDataseg() || v.isCTFE());
365 assert(!v.isReference());
366 const oldid = v.ctfeAdrOnStack;
367 v.ctfeAdrOnStack = cast(uint)cast(size_t)savedId[oldid];
368 if (v.ctfeAdrOnStack == values.length - 1)
370 values.pop();
371 vars.pop();
372 savedId.pop();
376 void popAll(size_t stackpointer)
378 if (stackPointer() > maxStackPointer)
379 maxStackPointer = stackPointer();
380 assert(values.length >= stackpointer);
381 for (size_t i = stackpointer; i < values.length; ++i)
383 VarDeclaration v = vars[i];
384 v.ctfeAdrOnStack = cast(uint)cast(size_t)savedId[i];
386 values.setDim(stackpointer);
387 vars.setDim(stackpointer);
388 savedId.setDim(stackpointer);
391 void saveGlobalConstant(VarDeclaration v, Expression e)
393 assert(v._init && (v.isConst() || v.isImmutable() || v.storage_class & STC.manifest) && !v.isCTFE());
394 v.ctfeAdrOnStack = cast(uint)globalValues.length;
395 globalValues.push(copyRegionExp(e));
399 private struct InterState
401 InterState* caller; // calling function's InterState
402 FuncDeclaration fd; // function being interpreted
403 Statement start; // if !=NULL, start execution at this statement
405 /* target of CTFEExp result; also
406 * target of labelled CTFEExp or
407 * CTFEExp. (null if no label).
409 Statement gotoTarget;
412 /*************************************
413 * Attempt to interpret a function given the arguments.
414 * Params:
415 * pue = storage for result
416 * fd = function being called
417 * istate = state for calling function (NULL if none)
418 * arguments = function arguments
419 * thisarg = 'this', if a needThis() function, NULL if not.
421 * Returns:
422 * result expression if successful, EXP.cantExpression if not,
423 * or CTFEExp if function returned void.
425 private Expression interpretFunction(UnionExp* pue, FuncDeclaration fd, InterState* istate, Expressions* arguments, Expression thisarg)
427 debug (LOG)
429 printf("\n********\n%s FuncDeclaration::interpret(istate = %p) %s\n", fd.loc.toChars(), istate, fd.toChars());
432 void fdError(const(char)* msg)
434 error(fd.loc, "%s `%s` %s", fd.kind, fd.toPrettyChars, msg);
437 assert(pue);
438 if (fd.semanticRun == PASS.semantic3)
440 fdError("circular dependency. Functions cannot be interpreted while being compiled");
441 return CTFEExp.cantexp;
443 if (!fd.functionSemantic3())
444 return CTFEExp.cantexp;
445 if (fd.semanticRun < PASS.semantic3done)
447 fdError("circular dependency. Functions cannot be interpreted while being compiled");
448 return CTFEExp.cantexp;
451 auto tf = fd.type.toBasetype().isTypeFunction();
452 if (tf.parameterList.varargs != VarArg.none && arguments &&
453 ((fd.parameters && arguments.length != fd.parameters.length) || (!fd.parameters && arguments.length)))
455 fdError("C-style variadic functions are not yet implemented in CTFE");
456 return CTFEExp.cantexp;
459 // Nested functions always inherit the 'this' pointer from the parent,
460 // except for delegates. (Note that the 'this' pointer may be null).
461 // Func literals report isNested() even if they are in global scope,
462 // so we need to check that the parent is a function.
463 if (fd.isNested() && fd.toParentLocal().isFuncDeclaration() && !thisarg && istate)
464 thisarg = ctfeGlobals.stack.getThis();
466 if (fd.needThis() && !thisarg)
468 // error, no this. Prevent segfault.
469 // Here should be unreachable by the strict 'this' check in front-end.
470 error(fd.loc, "%s `%s` need `this` to access member `%s`", fd.kind, fd.toPrettyChars, fd.toChars());
471 return CTFEExp.cantexp;
474 // Place to hold all the arguments to the function while
475 // we are evaluating them.
476 size_t dim = arguments ? arguments.length : 0;
477 assert((fd.parameters ? fd.parameters.length : 0) == dim);
479 /* Evaluate all the arguments to the function,
480 * store the results in eargs[]
482 Expressions eargs = Expressions(dim);
483 for (size_t i = 0; i < dim; i++)
485 Expression earg = (*arguments)[i];
486 Parameter fparam = tf.parameterList[i];
488 if (fparam.isReference())
490 if (!istate && (fparam.storageClass & STC.out_))
492 // initializing an out parameter involves writing to it.
493 error(earg.loc, "global `%s` cannot be passed as an `out` parameter at compile time", earg.toChars());
494 return CTFEExp.cantexp;
496 // Convert all reference arguments into lvalue references
497 earg = interpretRegion(earg, istate, CTFEGoal.LValue);
498 if (CTFEExp.isCantExp(earg))
499 return earg;
501 else if (fparam.isLazy())
504 else
506 /* Value parameters
508 Type ta = fparam.type.toBasetype();
509 if (ta.ty == Tsarray)
510 if (auto eaddr = earg.isAddrExp())
512 /* Static arrays are passed by a simple pointer.
513 * Skip past this to get at the actual arg.
515 earg = eaddr.e1;
518 earg = interpretRegion(earg, istate);
519 if (CTFEExp.isCantExp(earg))
520 return earg;
522 /* Struct literals are passed by value, but we don't need to
523 * copy them if they are passed as const
525 if (earg.op == EXP.structLiteral && !(fparam.storageClass & (STC.const_ | STC.immutable_)))
526 earg = copyLiteral(earg).copy();
528 if (auto tee = earg.isThrownExceptionExp())
530 if (istate)
531 return tee;
532 tee.generateUncaughtError();
533 return CTFEExp.cantexp;
535 eargs[i] = earg;
538 // Now that we've evaluated all the arguments, we can start the frame
539 // (this is the moment when the 'call' actually takes place).
540 InterState istatex;
541 istatex.caller = istate;
542 istatex.fd = fd;
544 if (fd.hasDualContext())
546 Expression arg0 = thisarg;
547 if (arg0 && arg0.type.ty == Tstruct)
549 Type t = arg0.type.pointerTo();
550 arg0 = ctfeEmplaceExp!AddrExp(arg0.loc, arg0);
551 arg0.type = t;
553 auto elements = new Expressions(2);
554 (*elements)[0] = arg0;
555 (*elements)[1] = ctfeGlobals.stack.getThis();
556 Type t2 = Type.tvoidptr.sarrayOf(2);
557 const loc = thisarg ? thisarg.loc : fd.loc;
558 thisarg = ctfeEmplaceExp!ArrayLiteralExp(loc, t2, elements);
559 thisarg = ctfeEmplaceExp!AddrExp(loc, thisarg);
560 thisarg.type = t2.pointerTo();
563 ctfeGlobals.stack.startFrame(thisarg);
564 if (fd.vthis && thisarg)
566 ctfeGlobals.stack.push(fd.vthis);
567 setValue(fd.vthis, thisarg);
570 for (size_t i = 0; i < dim; i++)
572 Expression earg = eargs[i];
573 Parameter fparam = tf.parameterList[i];
574 VarDeclaration v = (*fd.parameters)[i];
575 debug (LOG)
577 printf("arg[%zu] = %s\n", i, earg.toChars());
579 ctfeGlobals.stack.push(v);
581 if (fparam.isReference() && earg.op == EXP.variable &&
582 earg.isVarExp().var.toParent2() == fd)
584 VarDeclaration vx = earg.isVarExp().var.isVarDeclaration();
585 if (!vx)
587 error(fd.loc, "%s `%s` cannot interpret `%s` as a `ref` parameter", fd.kind, fd.toPrettyChars, earg.toChars());
588 return CTFEExp.cantexp;
591 /* vx is a variable that is declared in fd.
592 * It means that fd is recursively called. e.g.
594 * void fd(int n, ref int v = dummy) {
595 * int vx;
596 * if (n == 1) fd(2, vx);
598 * fd(1);
600 * The old value of vx on the stack in fd(1)
601 * should be saved at the start of fd(2, vx) call.
603 const oldadr = vx.ctfeAdrOnStack;
605 ctfeGlobals.stack.push(vx);
606 assert(!hasValue(vx)); // vx is made uninitialized
608 // https://issues.dlang.org/show_bug.cgi?id=14299
609 // v.ctfeAdrOnStack should be saved already
610 // in the stack before the overwrite.
611 v.ctfeAdrOnStack = oldadr;
612 assert(hasValue(v)); // ref parameter v should refer existing value.
614 else
616 // Value parameters and non-trivial references
617 setValueWithoutChecking(v, earg);
619 debug (LOG)
621 printf("interpreted arg[%zu] = %s\n", i, earg.toChars());
622 showCtfeExpr(earg);
624 debug (LOGASSIGN)
626 printf("interpreted arg[%zu] = %s\n", i, earg.toChars());
627 showCtfeExpr(earg);
631 if (fd.vresult)
632 ctfeGlobals.stack.push(fd.vresult);
634 // Enter the function
635 ++ctfeGlobals.callDepth;
636 if (ctfeGlobals.callDepth > ctfeGlobals.maxCallDepth)
637 ctfeGlobals.maxCallDepth = ctfeGlobals.callDepth;
639 Expression e = null;
640 while (1)
642 if (ctfeGlobals.callDepth > CTFE_RECURSION_LIMIT)
644 fdError("CTFE recursion limit exceeded");
645 e = CTFEExp.cantexp;
646 break;
648 e = interpretStatement(pue, fd.fbody, &istatex);
649 if (CTFEExp.isCantExp(e))
651 debug (LOG)
653 printf("function body failed to interpret\n");
657 if (istatex.start)
659 error(fd.loc, "%s `%s` CTFE internal error: failed to resume at statement `%s`", fd.kind, fd.toPrettyChars, istatex.start.toChars());
660 return CTFEExp.cantexp;
663 /* This is how we deal with a recursive statement AST
664 * that has arbitrary goto statements in it.
665 * Bubble up a 'result' which is the target of the goto
666 * statement, then go recursively down the AST looking
667 * for that statement, then execute starting there.
669 if (CTFEExp.isGotoExp(e))
671 istatex.start = istatex.gotoTarget; // set starting statement
672 istatex.gotoTarget = null;
674 else
676 assert(!e || (e.op != EXP.continue_ && e.op != EXP.break_));
677 break;
680 // If fell off the end of a void function, return void
681 if (!e)
683 if (tf.next.ty == Tvoid)
684 e = CTFEExp.voidexp;
685 else
687 /* missing a return statement can happen with C functions
688 * https://issues.dlang.org/show_bug.cgi?id=23056
690 fdError("no return value from function");
691 e = CTFEExp.cantexp;
695 if (tf.isref && e.op == EXP.variable && e.isVarExp().var == fd.vthis)
696 e = thisarg;
697 if (tf.isref && fd.hasDualContext() && e.op == EXP.index)
699 auto ie = e.isIndexExp();
700 auto pe = ie.e1.isPtrExp();
701 auto ve = !pe ? null : pe.e1.isVarExp();
702 if (ve && ve.var == fd.vthis)
704 auto ne = ie.e2.isIntegerExp();
705 assert(ne);
706 auto ale = thisarg.isAddrExp().e1.isArrayLiteralExp();
707 e = (*ale.elements)[cast(size_t)ne.getInteger()];
708 if (auto ae = e.isAddrExp())
710 e = ae.e1;
715 // Leave the function
716 --ctfeGlobals.callDepth;
718 ctfeGlobals.stack.endFrame();
720 // If it generated an uncaught exception, report error.
721 if (!istate && e.isThrownExceptionExp())
723 if (e == pue.exp())
724 e = pue.copy();
725 e.isThrownExceptionExp().generateUncaughtError();
726 e = CTFEExp.cantexp;
729 return e;
732 /// used to collect coverage information in ctfe
733 void incUsageCtfe(InterState* istate, const ref Loc loc)
735 if (global.params.ctfe_cov && istate)
737 auto line = loc.linnum;
738 auto mod = istate.fd.getModule();
740 ++mod.ctfe_cov[line];
744 /***********************************
745 * Interpret the statement.
746 * Params:
747 * s = Statement to interpret
748 * istate = context
749 * Returns:
750 * NULL continue to next statement
751 * EXP.cantExpression cannot interpret statement at compile time
752 * !NULL expression from return statement, or thrown exception
755 Expression interpretStatement(Statement s, InterState* istate)
757 UnionExp ue = void;
758 auto result = interpretStatement(&ue, s, istate);
759 if (result == ue.exp())
760 result = ue.copy();
761 return result;
765 Expression interpretStatement(UnionExp* pue, Statement s, InterState* istate)
767 Expression result;
769 // If e is EXP.throw_exception or EXP.cantExpression,
770 // set it to 'result' and returns true.
771 bool exceptionOrCant(Expression e)
773 if (exceptionOrCantInterpret(e))
775 // Make sure e is not pointing to a stack temporary
776 result = (e.op == EXP.cantExpression) ? CTFEExp.cantexp : e;
777 return true;
779 return false;
782 /******************************** Statement ***************************/
784 void visitDefaultCase(Statement s)
786 debug (LOG)
788 printf("%s Statement::interpret() %s\n", s.loc.toChars(), s.toChars());
790 if (istate.start)
792 if (istate.start != s)
793 return;
794 istate.start = null;
797 error(s.loc, "statement `%s` cannot be interpreted at compile time", s.toChars());
798 result = CTFEExp.cantexp;
801 void visitExp(ExpStatement s)
803 debug (LOG)
805 printf("%s ExpStatement::interpret(%s)\n", s.loc.toChars(), s.exp ? s.exp.toChars() : "");
807 if (istate.start)
809 if (istate.start != s)
810 return;
811 istate.start = null;
813 if (s.exp && s.exp.hasCode)
814 incUsageCtfe(istate, s.loc);
816 Expression e = interpret(pue, s.exp, istate, CTFEGoal.Nothing);
817 if (exceptionOrCant(e))
818 return;
821 void visitDtorExp(DtorExpStatement s)
823 visitExp(s);
826 void visitCompound(CompoundStatement s)
828 debug (LOG)
830 printf("%s CompoundStatement::interpret()\n", s.loc.toChars());
832 if (istate.start == s)
833 istate.start = null;
835 const dim = s.statements ? s.statements.length : 0;
836 foreach (i; 0 .. dim)
838 Statement sx = (*s.statements)[i];
839 result = interpretStatement(pue, sx, istate);
840 if (result)
841 break;
843 debug (LOG)
845 printf("%s -CompoundStatement::interpret() %p\n", s.loc.toChars(), result);
849 void visitCompoundAsm(CompoundAsmStatement s)
851 visitCompound(s);
854 void visitUnrolledLoop(UnrolledLoopStatement s)
856 debug (LOG)
858 printf("%s UnrolledLoopStatement::interpret()\n", s.loc.toChars());
860 if (istate.start == s)
861 istate.start = null;
863 const dim = s.statements ? s.statements.length : 0;
864 foreach (i; 0 .. dim)
866 Statement sx = (*s.statements)[i];
867 Expression e = interpretStatement(pue, sx, istate);
868 if (!e) // succeeds to interpret, or goto target was not found
869 continue;
870 if (exceptionOrCant(e))
871 return;
872 if (e.op == EXP.break_)
874 if (istate.gotoTarget && istate.gotoTarget != s)
876 result = e; // break at a higher level
877 return;
879 istate.gotoTarget = null;
880 result = null;
881 return;
883 if (e.op == EXP.continue_)
885 if (istate.gotoTarget && istate.gotoTarget != s)
887 result = e; // continue at a higher level
888 return;
890 istate.gotoTarget = null;
891 continue;
894 // expression from return statement, or thrown exception
895 result = e;
896 break;
900 void visitIf(IfStatement s)
902 debug (LOG)
904 printf("%s IfStatement::interpret(%s)\n", s.loc.toChars(), s.condition.toChars());
906 incUsageCtfe(istate, s.loc);
907 if (istate.start == s)
908 istate.start = null;
909 if (istate.start)
911 Expression e = null;
912 e = interpretStatement(s.ifbody, istate);
913 if (!e && istate.start)
914 e = interpretStatement(s.elsebody, istate);
915 result = e;
916 return;
919 UnionExp ue = void;
920 Expression e = interpret(&ue, s.condition, istate);
921 assert(e);
922 if (exceptionOrCant(e))
923 return;
925 if (isTrueBool(e))
926 result = interpretStatement(pue, s.ifbody, istate);
927 else if (e.toBool().hasValue(false))
928 result = interpretStatement(pue, s.elsebody, istate);
929 else
931 // no error, or assert(0)?
932 result = CTFEExp.cantexp;
936 void visitScope(ScopeStatement s)
938 debug (LOG)
940 printf("%s ScopeStatement::interpret()\n", s.loc.toChars());
942 if (istate.start == s)
943 istate.start = null;
945 result = interpretStatement(pue, s.statement, istate);
948 void visitReturn(ReturnStatement s)
950 debug (LOG)
952 printf("%s ReturnStatement::interpret(%s)\n", s.loc.toChars(), s.exp ? s.exp.toChars() : "");
954 if (istate.start)
956 if (istate.start != s)
957 return;
958 istate.start = null;
961 if (!s.exp)
963 result = CTFEExp.voidexp;
964 return;
967 incUsageCtfe(istate, s.loc);
968 assert(istate && istate.fd && istate.fd.type && istate.fd.type.ty == Tfunction);
969 TypeFunction tf = cast(TypeFunction)istate.fd.type;
971 /* If the function returns a ref AND it's been called from an assignment,
972 * we need to return an lvalue. Otherwise, just do an (rvalue) interpret.
974 if (tf.isref)
976 result = interpret(pue, s.exp, istate, CTFEGoal.LValue);
977 return;
979 if (tf.next && tf.next.ty == Tdelegate && istate.fd.closureVars.length > 0)
981 // To support this, we need to copy all the closure vars
982 // into the delegate literal.
983 error(s.loc, "closures are not yet supported in CTFE");
984 result = CTFEExp.cantexp;
985 return;
988 // We need to treat pointers specially, because EXP.symbolOffset can be used to
989 // return a value OR a pointer
990 Expression e = interpret(pue, s.exp, istate);
991 if (exceptionOrCant(e))
992 return;
995 * Interpret `return a ~= b` (i.e. `return _d_arrayappendT{,Trace}(a, b)`) as:
996 * a ~= b;
997 * return a;
998 * This is needed because `a ~= b` has to be interpreted as an lvalue, in order to avoid
999 * assigning a larger array into a smaller one, such as:
1000 * `a = [1, 2], a ~= [3]` => `[1, 2] ~= [3]` => `[1, 2] = [1, 2, 3]`
1002 if (isRuntimeHook(s.exp, Id._d_arrayappendT) || isRuntimeHook(s.exp, Id._d_arrayappendTTrace))
1004 auto rs = new ReturnStatement(s.loc, e);
1005 visitReturn(rs);
1006 return;
1009 // Disallow returning pointers to stack-allocated variables (bug 7876)
1010 if (!stopPointersEscaping(s.loc, e))
1012 result = CTFEExp.cantexp;
1013 return;
1016 if (needToCopyLiteral(e))
1017 e = copyLiteral(e).copy();
1018 debug (LOGASSIGN)
1020 printf("RETURN %s\n", s.loc.toChars());
1021 showCtfeExpr(e);
1023 result = e;
1026 void visitBreak(BreakStatement s)
1028 debug (LOG)
1030 printf("%s BreakStatement::interpret()\n", s.loc.toChars());
1032 incUsageCtfe(istate, s.loc);
1033 if (istate.start)
1035 if (istate.start != s)
1036 return;
1037 istate.start = null;
1040 istate.gotoTarget = findGotoTarget(istate, s.ident);
1041 result = CTFEExp.breakexp;
1044 void visitContinue(ContinueStatement s)
1046 debug (LOG)
1048 printf("%s ContinueStatement::interpret()\n", s.loc.toChars());
1050 incUsageCtfe(istate, s.loc);
1051 if (istate.start)
1053 if (istate.start != s)
1054 return;
1055 istate.start = null;
1058 istate.gotoTarget = findGotoTarget(istate, s.ident);
1059 result = CTFEExp.continueexp;
1062 void visitWhile(WhileStatement s)
1064 debug (LOG)
1066 printf("WhileStatement::interpret()\n");
1068 assert(0); // rewritten to ForStatement
1071 void visitDo(DoStatement s)
1073 debug (LOG)
1075 printf("%s DoStatement::interpret()\n", s.loc.toChars());
1077 if (istate.start == s)
1078 istate.start = null;
1080 while (1)
1082 Expression e = interpretStatement(s._body, istate);
1083 if (!e && istate.start) // goto target was not found
1084 return;
1085 assert(!istate.start);
1087 if (exceptionOrCant(e))
1088 return;
1089 if (e && e.op == EXP.break_)
1091 if (istate.gotoTarget && istate.gotoTarget != s)
1093 result = e; // break at a higher level
1094 return;
1096 istate.gotoTarget = null;
1097 break;
1099 if (e && e.op == EXP.continue_)
1101 if (istate.gotoTarget && istate.gotoTarget != s)
1103 result = e; // continue at a higher level
1104 return;
1106 istate.gotoTarget = null;
1107 e = null;
1109 if (e)
1111 result = e; // bubbled up from ReturnStatement
1112 return;
1115 UnionExp ue = void;
1116 incUsageCtfe(istate, s.condition.loc);
1117 e = interpret(&ue, s.condition, istate);
1118 if (exceptionOrCant(e))
1119 return;
1120 if (!e.isConst())
1122 result = CTFEExp.cantexp;
1123 return;
1125 if (e.toBool().hasValue(false))
1126 break;
1127 assert(isTrueBool(e));
1129 assert(result is null);
1132 void visitFor(ForStatement s)
1134 debug (LOG)
1136 printf("%s ForStatement::interpret()\n", s.loc.toChars());
1138 if (istate.start == s)
1139 istate.start = null;
1141 UnionExp ueinit = void;
1142 Expression ei = interpretStatement(&ueinit, s._init, istate);
1143 if (exceptionOrCant(ei))
1144 return;
1145 assert(!ei); // s.init never returns from function, or jumps out from it
1147 while (1)
1149 if (s.condition && !istate.start)
1151 UnionExp ue = void;
1152 incUsageCtfe(istate, s.condition.loc);
1153 Expression e = interpret(&ue, s.condition, istate);
1154 if (exceptionOrCant(e))
1155 return;
1156 if (e.toBool().hasValue(false))
1157 break;
1158 assert(isTrueBool(e));
1161 Expression e = interpretStatement(pue, s._body, istate);
1162 if (!e && istate.start) // goto target was not found
1163 return;
1164 assert(!istate.start);
1166 if (exceptionOrCant(e))
1167 return;
1168 if (e && e.op == EXP.break_)
1170 if (istate.gotoTarget && istate.gotoTarget != s)
1172 result = e; // break at a higher level
1173 return;
1175 istate.gotoTarget = null;
1176 break;
1178 if (e && e.op == EXP.continue_)
1180 if (istate.gotoTarget && istate.gotoTarget != s)
1182 result = e; // continue at a higher level
1183 return;
1185 istate.gotoTarget = null;
1186 e = null;
1188 if (e)
1190 result = e; // bubbled up from ReturnStatement
1191 return;
1194 UnionExp uei = void;
1195 if (s.increment)
1196 incUsageCtfe(istate, s.increment.loc);
1197 e = interpret(&uei, s.increment, istate, CTFEGoal.Nothing);
1198 if (exceptionOrCant(e))
1199 return;
1201 assert(result is null);
1204 void visitForeach(ForeachStatement s)
1206 assert(0); // rewritten to ForStatement
1209 void visitForeachRange(ForeachRangeStatement s)
1211 assert(0); // rewritten to ForStatement
1214 void visitSwitch(SwitchStatement s)
1216 debug (LOG)
1218 printf("%s SwitchStatement::interpret()\n", s.loc.toChars());
1220 incUsageCtfe(istate, s.loc);
1221 if (istate.start == s)
1222 istate.start = null;
1223 if (istate.start)
1225 Expression e = interpretStatement(s._body, istate);
1226 if (istate.start) // goto target was not found
1227 return;
1228 if (exceptionOrCant(e))
1229 return;
1230 if (e && e.op == EXP.break_)
1232 if (istate.gotoTarget && istate.gotoTarget != s)
1234 result = e; // break at a higher level
1235 return;
1237 istate.gotoTarget = null;
1238 e = null;
1240 result = e;
1241 return;
1244 UnionExp uecond = void;
1245 Expression econdition = interpret(&uecond, s.condition, istate);
1246 if (exceptionOrCant(econdition))
1247 return;
1249 Statement scase = null;
1250 if (s.cases)
1251 foreach (cs; *s.cases)
1253 UnionExp uecase = void;
1254 Expression ecase = interpret(&uecase, cs.exp, istate);
1255 if (exceptionOrCant(ecase))
1256 return;
1257 if (ctfeEqual(cs.exp.loc, EXP.equal, econdition, ecase))
1259 scase = cs;
1260 break;
1263 if (!scase)
1265 if (!s.hasDefault)
1266 error(s.loc, "no `default` or `case` for `%s` in `switch` statement", econdition.toChars());
1267 scase = s.sdefault;
1270 assert(scase);
1272 /* Jump to scase
1274 istate.start = scase;
1275 Expression e = interpretStatement(pue, s._body, istate);
1276 assert(!istate.start); // jump must not fail
1277 if (e && e.op == EXP.break_)
1279 if (istate.gotoTarget && istate.gotoTarget != s)
1281 result = e; // break at a higher level
1282 return;
1284 istate.gotoTarget = null;
1285 e = null;
1287 result = e;
1290 void visitCase(CaseStatement s)
1292 debug (LOG)
1294 printf("%s CaseStatement::interpret(%s) this = %p\n", s.loc.toChars(), s.exp.toChars(), s);
1296 incUsageCtfe(istate, s.loc);
1297 if (istate.start == s)
1298 istate.start = null;
1300 result = interpretStatement(pue, s.statement, istate);
1303 void visitDefault(DefaultStatement s)
1305 debug (LOG)
1307 printf("%s DefaultStatement::interpret()\n", s.loc.toChars());
1309 incUsageCtfe(istate, s.loc);
1310 if (istate.start == s)
1311 istate.start = null;
1313 result = interpretStatement(pue, s.statement, istate);
1316 void visitGoto(GotoStatement s)
1318 debug (LOG)
1320 printf("%s GotoStatement::interpret()\n", s.loc.toChars());
1322 if (istate.start)
1324 if (istate.start != s)
1325 return;
1326 istate.start = null;
1328 incUsageCtfe(istate, s.loc);
1330 assert(s.label && s.label.statement);
1331 istate.gotoTarget = s.label.statement;
1332 result = CTFEExp.gotoexp;
1335 void visitGotoCase(GotoCaseStatement s)
1337 debug (LOG)
1339 printf("%s GotoCaseStatement::interpret()\n", s.loc.toChars());
1341 if (istate.start)
1343 if (istate.start != s)
1344 return;
1345 istate.start = null;
1347 incUsageCtfe(istate, s.loc);
1349 assert(s.cs);
1350 istate.gotoTarget = s.cs;
1351 result = CTFEExp.gotoexp;
1354 void visitGotoDefault(GotoDefaultStatement s)
1356 debug (LOG)
1358 printf("%s GotoDefaultStatement::interpret()\n", s.loc.toChars());
1360 if (istate.start)
1362 if (istate.start != s)
1363 return;
1364 istate.start = null;
1366 incUsageCtfe(istate, s.loc);
1368 assert(s.sw && s.sw.sdefault);
1369 istate.gotoTarget = s.sw.sdefault;
1370 result = CTFEExp.gotoexp;
1373 void visitLabel(LabelStatement s)
1375 debug (LOG)
1377 printf("%s LabelStatement::interpret()\n", s.loc.toChars());
1379 if (istate.start == s)
1380 istate.start = null;
1382 result = interpretStatement(pue, s.statement, istate);
1385 void visitTryCatch(TryCatchStatement s)
1387 debug (LOG)
1389 printf("%s TryCatchStatement::interpret()\n", s.loc.toChars());
1391 if (istate.start == s)
1392 istate.start = null;
1393 if (istate.start)
1395 Expression e = null;
1396 e = interpretStatement(pue, s._body, istate);
1397 foreach (ca; *s.catches)
1399 if (e || !istate.start) // goto target was found
1400 break;
1401 e = interpretStatement(pue, ca.handler, istate);
1403 result = e;
1404 return;
1407 Expression e = interpretStatement(s._body, istate);
1409 // An exception was thrown
1410 if (e && e.isThrownExceptionExp())
1412 ThrownExceptionExp ex = e.isThrownExceptionExp();
1413 Type extype = ex.thrown.originalClass().type;
1415 // Search for an appropriate catch clause.
1416 foreach (ca; *s.catches)
1418 Type catype = ca.type;
1419 if (!catype.equals(extype) && !catype.isBaseOf(extype, null))
1420 continue;
1422 // Execute the handler
1423 if (ca.var)
1425 ctfeGlobals.stack.push(ca.var);
1426 setValue(ca.var, ex.thrown);
1428 e = interpretStatement(ca.handler, istate);
1429 while (CTFEExp.isGotoExp(e))
1431 /* This is an optimization that relies on the locality of the jump target.
1432 * If the label is in the same catch handler, the following scan
1433 * would find it quickly and can reduce jump cost.
1434 * Otherwise, the catch block may be unnnecessary scanned again
1435 * so it would make CTFE speed slower.
1437 InterState istatex = *istate;
1438 istatex.start = istate.gotoTarget; // set starting statement
1439 istatex.gotoTarget = null;
1440 Expression eh = interpretStatement(ca.handler, &istatex);
1441 if (istatex.start)
1443 // The goto target is outside the current scope.
1444 break;
1446 // The goto target was within the body.
1447 if (CTFEExp.isCantExp(eh))
1449 e = eh;
1450 break;
1452 *istate = istatex;
1453 e = eh;
1455 break;
1458 result = e;
1461 void visitTryFinally(TryFinallyStatement s)
1463 debug (LOG)
1465 printf("%s TryFinallyStatement::interpret()\n", s.loc.toChars());
1467 if (istate.start == s)
1468 istate.start = null;
1469 if (istate.start)
1471 Expression e = null;
1472 e = interpretStatement(pue, s._body, istate);
1473 // Jump into/out from finalbody is disabled in semantic analysis.
1474 // and jump inside will be handled by the ScopeStatement == finalbody.
1475 result = e;
1476 return;
1479 Expression ex = interpretStatement(s._body, istate);
1480 if (CTFEExp.isCantExp(ex))
1482 result = ex;
1483 return;
1485 while (CTFEExp.isGotoExp(ex))
1487 // If the goto target is within the body, we must not interpret the finally statement,
1488 // because that will call destructors for objects within the scope, which we should not do.
1489 InterState istatex = *istate;
1490 istatex.start = istate.gotoTarget; // set starting statement
1491 istatex.gotoTarget = null;
1492 Expression bex = interpretStatement(s._body, &istatex);
1493 if (istatex.start)
1495 // The goto target is outside the current scope.
1496 break;
1498 // The goto target was within the body.
1499 if (CTFEExp.isCantExp(bex))
1501 result = bex;
1502 return;
1504 *istate = istatex;
1505 ex = bex;
1508 Expression ey = interpretStatement(s.finalbody, istate);
1509 if (CTFEExp.isCantExp(ey))
1511 result = ey;
1512 return;
1514 if (ey && ey.isThrownExceptionExp())
1516 // Check for collided exceptions
1517 if (ex && ex.isThrownExceptionExp())
1518 ex = chainExceptions(ex.isThrownExceptionExp(), ey.isThrownExceptionExp());
1519 else
1520 ex = ey;
1522 result = ex;
1525 void visitThrow(ThrowStatement s)
1527 debug (LOG)
1529 printf("%s ThrowStatement::interpret()\n", s.loc.toChars());
1531 if (istate.start)
1533 if (istate.start != s)
1534 return;
1535 istate.start = null;
1538 interpretThrow(result, s.exp, s.loc, istate);
1541 void visitScopeGuard(ScopeGuardStatement s)
1543 assert(0);
1546 void visitWith(WithStatement s)
1548 debug (LOG)
1550 printf("%s WithStatement::interpret()\n", s.loc.toChars());
1552 if (istate.start == s)
1553 istate.start = null;
1554 if (istate.start)
1556 result = s._body ? interpretStatement(s._body, istate) : null;
1557 return;
1560 // If it is with(Enum) {...}, just execute the body.
1561 if (s.exp.op == EXP.scope_ || s.exp.op == EXP.type)
1563 result = interpretStatement(pue, s._body, istate);
1564 return;
1567 incUsageCtfe(istate, s.loc);
1569 Expression e = interpret(s.exp, istate);
1570 if (exceptionOrCant(e))
1571 return;
1573 if (s.wthis.type.ty == Tpointer && s.exp.type.ty != Tpointer)
1575 e = ctfeEmplaceExp!AddrExp(s.loc, e, s.wthis.type);
1577 ctfeGlobals.stack.push(s.wthis);
1578 setValue(s.wthis, e);
1579 e = interpretStatement(s._body, istate);
1580 while (CTFEExp.isGotoExp(e))
1582 /* This is an optimization that relies on the locality of the jump target.
1583 * If the label is in the same WithStatement, the following scan
1584 * would find it quickly and can reduce jump cost.
1585 * Otherwise, the statement body may be unnnecessary scanned again
1586 * so it would make CTFE speed slower.
1588 InterState istatex = *istate;
1589 istatex.start = istate.gotoTarget; // set starting statement
1590 istatex.gotoTarget = null;
1591 Expression ex = interpretStatement(s._body, &istatex);
1592 if (istatex.start)
1594 // The goto target is outside the current scope.
1595 break;
1597 // The goto target was within the body.
1598 if (CTFEExp.isCantExp(ex))
1600 e = ex;
1601 break;
1603 *istate = istatex;
1604 e = ex;
1606 ctfeGlobals.stack.pop(s.wthis);
1607 result = e;
1610 void visitAsm(AsmStatement s)
1612 debug (LOG)
1614 printf("%s AsmStatement::interpret()\n", s.loc.toChars());
1616 if (istate.start)
1618 if (istate.start != s)
1619 return;
1620 istate.start = null;
1622 error(s.loc, "`asm` statements cannot be interpreted at compile time");
1623 result = CTFEExp.cantexp;
1626 void visitInlineAsm(InlineAsmStatement s)
1628 visitAsm(s);
1631 void visitGccAsm(GccAsmStatement s)
1633 visitAsm(s);
1636 void visitImport(ImportStatement s)
1638 debug (LOG)
1640 printf("ImportStatement::interpret()\n");
1642 if (istate.start)
1644 if (istate.start != s)
1645 return;
1646 istate.start = null;
1650 if (!s)
1651 return null;
1653 mixin VisitStatement!void visit;
1654 visit.VisitStatement(s);
1655 return result;
1660 private extern (C++) final class Interpreter : Visitor
1662 alias visit = Visitor.visit;
1663 public:
1664 InterState* istate;
1665 CTFEGoal goal;
1666 Expression result;
1667 UnionExp* pue; // storage for `result`
1669 extern (D) this(UnionExp* pue, InterState* istate, CTFEGoal goal) scope @safe
1671 this.pue = pue;
1672 this.istate = istate;
1673 this.goal = goal;
1676 // If e is EXP.throw_exception or EXP.cantExpression,
1677 // set it to 'result' and returns true.
1678 bool exceptionOrCant(Expression e)
1680 if (exceptionOrCantInterpret(e))
1682 // Make sure e is not pointing to a stack temporary
1683 result = (e.op == EXP.cantExpression) ? CTFEExp.cantexp : e;
1684 return true;
1686 return false;
1689 /******************************** Expression ***************************/
1691 override void visit(Expression e)
1693 debug (LOG)
1695 printf("%s Expression::interpret() '%s' %s\n", e.loc.toChars(), EXPtoString(e.op).ptr, e.toChars());
1696 printf("type = %s\n", e.type.toChars());
1697 showCtfeExpr(e);
1699 error(e.loc, "cannot interpret `%s` at compile time", e.toChars());
1700 result = CTFEExp.cantexp;
1703 override void visit(TypeExp e)
1705 debug (LOG)
1707 printf("%s TypeExp.interpret() %s\n", e.loc.toChars(), e.toChars());
1709 result = e;
1712 override void visit(ThisExp e)
1714 debug (LOG)
1716 printf("%s ThisExp::interpret() %s\n", e.loc.toChars(), e.toChars());
1718 if (goal == CTFEGoal.LValue)
1720 // We might end up here with istate being zero
1721 // https://issues.dlang.org/show_bug.cgi?id=16382
1722 if (istate && istate.fd.vthis)
1724 result = ctfeEmplaceExp!VarExp(e.loc, istate.fd.vthis);
1725 if (istate.fd.hasDualContext())
1727 result = ctfeEmplaceExp!PtrExp(e.loc, result);
1728 result.type = Type.tvoidptr.sarrayOf(2);
1729 result = ctfeEmplaceExp!IndexExp(e.loc, result, IntegerExp.literal!0);
1731 result.type = e.type;
1733 else
1734 result = e;
1735 return;
1738 result = ctfeGlobals.stack.getThis();
1739 if (result)
1741 if (istate && istate.fd.hasDualContext())
1743 assert(result.op == EXP.address);
1744 result = result.isAddrExp().e1;
1745 assert(result.op == EXP.arrayLiteral);
1746 result = (*result.isArrayLiteralExp().elements)[0];
1747 if (e.type.ty == Tstruct)
1749 result = result.isAddrExp().e1;
1751 return;
1753 assert(result.op == EXP.structLiteral || result.op == EXP.classReference || result.op == EXP.type);
1754 return;
1756 error(e.loc, "value of `this` is not known at compile time");
1757 result = CTFEExp.cantexp;
1760 override void visit(NullExp e)
1762 result = e;
1765 override void visit(IntegerExp e)
1767 debug (LOG)
1769 printf("%s IntegerExp::interpret() %s\n", e.loc.toChars(), e.toChars());
1771 result = e;
1774 override void visit(RealExp e)
1776 debug (LOG)
1778 printf("%s RealExp::interpret() %s\n", e.loc.toChars(), e.toChars());
1780 result = e;
1783 override void visit(ComplexExp e)
1785 result = e;
1788 override void visit(StringExp e)
1790 debug (LOG)
1792 printf("%s StringExp::interpret() %s\n", e.loc.toChars(), e.toChars());
1794 if (e.ownedByCtfe >= OwnedBy.ctfe) // We've already interpreted the string
1796 result = e;
1797 return;
1800 if (e.type.ty != Tsarray ||
1801 (cast(TypeNext)e.type).next.mod & (MODFlags.const_ | MODFlags.immutable_))
1803 // If it's immutable, we don't need to dup it. Attempts to modify
1804 // string literals are prevented in BinExp::interpretAssignCommon.
1805 result = e;
1807 else
1809 // https://issues.dlang.org/show_bug.cgi?id=20811
1810 // Create a copy of mutable string literals, so that any change in
1811 // value via an index or slice will not survive CTFE.
1812 *pue = copyLiteral(e);
1813 result = pue.exp();
1817 override void visit(FuncExp e)
1819 debug (LOG)
1821 printf("%s FuncExp::interpret() %s\n", e.loc.toChars(), e.toChars());
1823 result = e;
1826 override void visit(SymOffExp e)
1828 debug (LOG)
1830 printf("%s SymOffExp::interpret() %s\n", e.loc.toChars(), e.toChars());
1832 if (e.var.isFuncDeclaration() && e.offset == 0)
1834 result = e;
1835 return;
1837 if (isTypeInfo_Class(e.type) && e.offset == 0)
1839 result = e;
1840 return;
1842 if (e.type.ty != Tpointer)
1844 // Probably impossible
1845 error(e.loc, "cannot interpret `%s` at compile time", e.toChars());
1846 result = CTFEExp.cantexp;
1847 return;
1849 Type pointee = (cast(TypePointer)e.type).next;
1850 if (e.var.isThreadlocal())
1852 error(e.loc, "cannot take address of thread-local variable %s at compile time", e.var.toChars());
1853 result = CTFEExp.cantexp;
1854 return;
1856 // Check for taking an address of a shared variable.
1857 // If the shared variable is an array, the offset might not be zero.
1858 Type fromType = null;
1859 if (e.var.type.ty == Tarray || e.var.type.ty == Tsarray)
1861 fromType = (cast(TypeArray)e.var.type).next;
1863 if (e.var.isDataseg() && ((e.offset == 0 && isSafePointerCast(e.var.type, pointee)) ||
1864 (fromType && isSafePointerCast(fromType, pointee)) ||
1865 (e.var.isCsymbol() && e.offset + pointee.size() <= e.var.type.size())))
1867 result = e;
1868 return;
1871 Expression val = getVarExp(e.loc, istate, e.var, goal);
1872 if (exceptionOrCant(val))
1873 return;
1874 if (val.type.ty == Tarray || val.type.ty == Tsarray)
1876 // Check for unsupported type painting operations
1877 Type elemtype = (cast(TypeArray)val.type).next;
1878 const elemsize = elemtype.size();
1880 // It's OK to cast from fixed length to fixed length array, eg &int[n] to int[d]*.
1881 if (val.type.ty == Tsarray && pointee.ty == Tsarray && elemsize == pointee.nextOf().size())
1883 size_t d = cast(size_t)(cast(TypeSArray)pointee).dim.toInteger();
1884 Expression elwr = ctfeEmplaceExp!IntegerExp(e.loc, e.offset / elemsize, Type.tsize_t);
1885 Expression eupr = ctfeEmplaceExp!IntegerExp(e.loc, e.offset / elemsize + d, Type.tsize_t);
1887 // Create a CTFE pointer &val[ofs..ofs+d]
1888 auto se = ctfeEmplaceExp!SliceExp(e.loc, val, elwr, eupr);
1889 se.type = pointee;
1890 emplaceExp!(AddrExp)(pue, e.loc, se, e.type);
1891 result = pue.exp();
1892 return;
1895 if (!isSafePointerCast(elemtype, pointee))
1897 // It's also OK to cast from &string to string*.
1898 if (e.offset == 0 && isSafePointerCast(e.var.type, pointee))
1900 // Create a CTFE pointer &var
1901 auto ve = ctfeEmplaceExp!VarExp(e.loc, e.var);
1902 ve.type = elemtype;
1903 emplaceExp!(AddrExp)(pue, e.loc, ve, e.type);
1904 result = pue.exp();
1905 return;
1907 error(e.loc, "reinterpreting cast from `%s` to `%s` is not supported in CTFE", val.type.toChars(), e.type.toChars());
1908 result = CTFEExp.cantexp;
1909 return;
1912 const dinteger_t sz = pointee.size();
1913 dinteger_t indx = e.offset / sz;
1914 assert(sz * indx == e.offset);
1915 Expression aggregate = null;
1916 if (val.op == EXP.arrayLiteral || val.op == EXP.string_)
1918 aggregate = val;
1920 else if (auto se = val.isSliceExp())
1922 aggregate = se.e1;
1923 UnionExp uelwr = void;
1924 Expression lwr = interpret(&uelwr, se.lwr, istate);
1925 indx += lwr.toInteger();
1927 if (aggregate)
1929 // Create a CTFE pointer &aggregate[ofs]
1930 auto ofs = ctfeEmplaceExp!IntegerExp(e.loc, indx, Type.tsize_t);
1931 auto ei = ctfeEmplaceExp!IndexExp(e.loc, aggregate, ofs);
1932 ei.type = elemtype;
1933 emplaceExp!(AddrExp)(pue, e.loc, ei, e.type);
1934 result = pue.exp();
1935 return;
1938 else if (e.offset == 0 && isSafePointerCast(e.var.type, pointee))
1940 // Create a CTFE pointer &var
1941 auto ve = ctfeEmplaceExp!VarExp(e.loc, e.var);
1942 ve.type = e.var.type;
1943 emplaceExp!(AddrExp)(pue, e.loc, ve, e.type);
1944 result = pue.exp();
1945 return;
1948 error(e.loc, "cannot convert `&%s` to `%s` at compile time", e.var.type.toChars(), e.type.toChars());
1949 result = CTFEExp.cantexp;
1952 override void visit(AddrExp e)
1954 debug (LOG)
1956 printf("%s AddrExp::interpret() %s\n", e.loc.toChars(), e.toChars());
1958 if (auto ve = e.e1.isVarExp())
1960 Declaration decl = ve.var;
1962 // We cannot take the address of an imported symbol at compile time
1963 if (decl.isImportedSymbol()) {
1964 error(e.loc, "cannot take address of imported symbol `%s` at compile time", decl.toChars());
1965 result = CTFEExp.cantexp;
1966 return;
1969 if (decl.isDataseg()) {
1970 // Normally this is already done by optimize()
1971 // Do it here in case optimize(WANTvalue) wasn't run before CTFE
1972 emplaceExp!(SymOffExp)(pue, e.loc, e.e1.isVarExp().var, 0);
1973 result = pue.exp();
1974 result.type = e.type;
1975 return;
1978 auto er = interpret(e.e1, istate, CTFEGoal.LValue);
1979 if (auto ve = er.isVarExp())
1980 if (istate && ve.var == istate.fd.vthis)
1981 er = interpret(er, istate);
1983 if (exceptionOrCant(er))
1984 return;
1986 // Return a simplified address expression
1987 emplaceExp!(AddrExp)(pue, e.loc, er, e.type);
1988 result = pue.exp();
1991 override void visit(DelegateExp e)
1993 debug (LOG)
1995 printf("%s DelegateExp::interpret() %s\n", e.loc.toChars(), e.toChars());
1997 // TODO: Really we should create a CTFE-only delegate expression
1998 // of a pointer and a funcptr.
2000 // If it is &nestedfunc, just return it
2001 // TODO: We should save the context pointer
2002 if (auto ve1 = e.e1.isVarExp())
2003 if (ve1.var == e.func)
2005 result = e;
2006 return;
2009 auto er = interpret(pue, e.e1, istate);
2010 if (exceptionOrCant(er))
2011 return;
2012 if (er == e.e1)
2014 // If it has already been CTFE'd, just return it
2015 result = e;
2017 else
2019 er = (er == pue.exp()) ? pue.copy() : er;
2020 emplaceExp!(DelegateExp)(pue, e.loc, er, e.func, false);
2021 result = pue.exp();
2022 result.type = e.type;
2026 static Expression getVarExp(const ref Loc loc, InterState* istate, Declaration d, CTFEGoal goal)
2028 Expression e = CTFEExp.cantexp;
2029 if (VarDeclaration v = d.isVarDeclaration())
2031 /* Magic variable __ctfe always returns true when interpreting
2033 if (v.ident == Id.ctfe)
2034 return IntegerExp.createBool(true);
2036 if (!v.originalType && v.semanticRun < PASS.semanticdone) // semantic() not yet run
2038 v.dsymbolSemantic(null);
2039 if (v.type.ty == Terror)
2040 return CTFEExp.cantexp;
2043 if ((v.isConst() || v.isImmutable() || v.storage_class & STC.manifest) && !hasValue(v) && v._init && !v.isCTFE())
2045 if (v.inuse)
2047 error(loc, "circular initialization of %s `%s`", v.kind(), v.toPrettyChars());
2048 return CTFEExp.cantexp;
2050 if (v._scope)
2052 v.inuse++;
2053 v._init = v._init.initializerSemantic(v._scope, v.type, INITinterpret); // might not be run on aggregate members
2054 v.inuse--;
2056 e = v._init.initializerToExpression(v.type);
2057 if (!e)
2058 return CTFEExp.cantexp;
2059 assert(e.type);
2061 // There's a terrible hack in `dmd.dsymbolsem` that special case
2062 // a struct with all zeros to an `ExpInitializer(BlitExp(IntegerExp(0)))`
2063 // There's matching code for it in e2ir (toElem's visitAssignExp),
2064 // so we need the same hack here.
2065 // This does not trigger for global as they get a normal initializer.
2066 if (auto ts = e.type.isTypeStruct())
2067 if (auto ae = e.isBlitExp())
2068 if (ae.e2.op == EXP.int64)
2069 e = ts.defaultInitLiteral(loc);
2071 if (e.op == EXP.construct || e.op == EXP.blit)
2073 AssignExp ae = cast(AssignExp)e;
2074 e = ae.e2;
2077 if (e.op == EXP.error)
2079 // FIXME: Ultimately all errors should be detected in prior semantic analysis stage.
2081 else if (v.isDataseg() || (v.storage_class & STC.manifest))
2083 /* https://issues.dlang.org/show_bug.cgi?id=14304
2084 * e is a value that is not yet owned by CTFE.
2085 * Mark as "cached", and use it directly during interpretation.
2087 e = scrubCacheValue(e);
2088 ctfeGlobals.stack.saveGlobalConstant(v, e);
2090 else
2092 v.inuse++;
2093 e = interpret(e, istate);
2094 v.inuse--;
2095 if (CTFEExp.isCantExp(e) && !global.gag && !ctfeGlobals.stackTraceCallsToSuppress)
2096 errorSupplemental(loc, "while evaluating %s.init", v.toChars());
2097 if (exceptionOrCantInterpret(e))
2098 return e;
2101 else if (v.isCTFE() && !hasValue(v))
2103 if (v._init && v.type.size() != 0)
2105 if (v._init.isVoidInitializer())
2107 // var should have been initialized when it was created
2108 error(loc, "CTFE internal error: trying to access uninitialized var");
2109 assert(0);
2111 e = v._init.initializerToExpression();
2113 else
2114 // Zero-length arrays don't have an initializer
2115 e = v.type.defaultInitLiteral(e.loc);
2117 e = interpret(e, istate);
2119 else if (!(v.isDataseg() || v.storage_class & STC.manifest) && !v.isCTFE() && !istate)
2121 error(loc, "variable `%s` cannot be read at compile time", v.toChars());
2122 return CTFEExp.cantexp;
2124 else
2126 e = hasValue(v) ? getValue(v) : null;
2127 if (!e)
2129 // Zero-length arrays don't have an initializer
2130 if (v.type.size() == 0)
2131 e = v.type.defaultInitLiteral(loc);
2132 else if (!v.isCTFE() && v.isDataseg())
2134 error(loc, "static variable `%s` cannot be read at compile time", v.toChars());
2135 return CTFEExp.cantexp;
2137 else
2139 assert(!(v._init && v._init.isVoidInitializer()));
2140 // CTFE initiated from inside a function
2141 error(loc, "variable `%s` cannot be read at compile time", v.toChars());
2142 return CTFEExp.cantexp;
2145 if (auto vie = e.isVoidInitExp())
2147 error(loc, "cannot read uninitialized variable `%s` in ctfe", v.toPrettyChars());
2148 errorSupplemental(vie.var.loc, "`%s` was uninitialized and used before set", vie.var.toChars());
2149 return CTFEExp.cantexp;
2151 if (goal != CTFEGoal.LValue && v.isReference())
2152 e = interpret(e, istate, goal);
2154 if (!e)
2155 e = CTFEExp.cantexp;
2157 else if (SymbolDeclaration s = d.isSymbolDeclaration())
2159 // exclude void[]-typed `__traits(initSymbol)`
2160 if (auto ta = s.type.toBasetype().isTypeDArray())
2162 assert(ta.next.ty == Tvoid);
2163 error(loc, "cannot determine the address of the initializer symbol during CTFE");
2164 return CTFEExp.cantexp;
2167 // Struct static initializers, for example
2168 e = s.dsym.type.defaultInitLiteral(loc);
2169 if (e.op == EXP.error)
2170 error(loc, "CTFE failed because of previous errors in `%s.init`", s.toChars());
2171 e = e.expressionSemantic(null);
2172 if (e.op == EXP.error)
2173 e = CTFEExp.cantexp;
2174 else // Convert NULL to CTFEExp
2175 e = interpret(e, istate, goal);
2177 else
2178 error(loc, "cannot interpret declaration `%s` at compile time", d.toChars());
2179 return e;
2182 override void visit(VarExp e)
2184 debug (LOG)
2186 printf("%s VarExp::interpret() `%s`, goal = %d\n", e.loc.toChars(), e.toChars(), goal);
2188 if (e.var.isFuncDeclaration())
2190 result = e;
2191 return;
2194 if (goal == CTFEGoal.LValue)
2196 if (auto v = e.var.isVarDeclaration())
2198 if (!hasValue(v))
2200 // Compile-time known non-CTFE variable from an outer context
2201 // e.g. global or from a ref argument
2202 if (v.isConst() || v.isImmutable())
2204 result = getVarExp(e.loc, istate, v, goal);
2205 return;
2208 if (!v.isCTFE() && v.isDataseg())
2209 error(e.loc, "static variable `%s` cannot be read at compile time", v.toChars());
2210 else // CTFE initiated from inside a function
2211 error(e.loc, "variable `%s` cannot be read at compile time", v.toChars());
2212 result = CTFEExp.cantexp;
2213 return;
2216 if (v.storage_class & (STC.out_ | STC.ref_))
2218 // Strip off the nest of ref variables
2219 Expression ev = getValue(v);
2220 if (ev.op == EXP.variable ||
2221 ev.op == EXP.index ||
2222 (ev.op == EXP.slice && ev.type.toBasetype().ty == Tsarray) ||
2223 ev.op == EXP.dotVariable)
2225 result = interpret(pue, ev, istate, goal);
2226 return;
2230 result = e;
2231 return;
2233 result = getVarExp(e.loc, istate, e.var, goal);
2234 if (exceptionOrCant(result))
2235 return;
2237 // Visit the default initializer for noreturn variables
2238 // (Custom initializers would abort the current function call and exit above)
2239 if (result.type.ty == Tnoreturn)
2241 result.accept(this);
2242 return;
2245 if ((e.var.storage_class & (STC.ref_ | STC.out_)) == 0 && e.type.baseElemOf().ty != Tstruct)
2247 /* Ultimately, STC.ref_|STC.out_ check should be enough to see the
2248 * necessity of type repainting. But currently front-end paints
2249 * non-ref struct variables by the const type.
2251 * auto foo(ref const S cs);
2252 * S s;
2253 * foo(s); // VarExp('s') will have const(S)
2255 // A VarExp may include an implicit cast. It must be done explicitly.
2256 result = paintTypeOntoLiteral(pue, e.type, result);
2260 override void visit(DeclarationExp e)
2262 debug (LOG)
2264 printf("%s DeclarationExp::interpret() %s\n", e.loc.toChars(), e.toChars());
2266 Dsymbol s = e.declaration;
2267 while (s.isAttribDeclaration())
2269 auto ad = cast(AttribDeclaration)s;
2270 assert(ad.decl && ad.decl.length == 1); // Currently, only one allowed when parsing
2271 s = (*ad.decl)[0];
2273 if (VarDeclaration v = s.isVarDeclaration())
2275 if (TupleDeclaration td = v.toAlias().isTupleDeclaration())
2277 result = null;
2279 // Reserve stack space for all tuple members
2280 td.foreachVar((s)
2282 VarDeclaration v2 = s.isVarDeclaration();
2283 assert(v2);
2284 if (v2.isDataseg() && !v2.isCTFE())
2285 return 0;
2287 ctfeGlobals.stack.push(v2);
2288 if (v2._init)
2290 Expression einit;
2291 if (ExpInitializer ie = v2._init.isExpInitializer())
2293 einit = interpretRegion(ie.exp, istate, goal);
2294 if (exceptionOrCant(einit))
2295 return 1;
2297 else if (v2._init.isVoidInitializer())
2299 einit = voidInitLiteral(v2.type, v2).copy();
2301 else
2303 error(e.loc, "declaration `%s` is not yet implemented in CTFE", e.toChars());
2304 result = CTFEExp.cantexp;
2305 return 1;
2307 setValue(v2, einit);
2309 return 0;
2311 return;
2313 if (v.isStatic())
2315 // Just ignore static variables which aren't read or written yet
2316 result = null;
2317 return;
2319 if (!(v.isDataseg() || v.storage_class & STC.manifest) || v.isCTFE())
2320 ctfeGlobals.stack.push(v);
2321 if (v._init)
2323 if (ExpInitializer ie = v._init.isExpInitializer())
2325 result = interpretRegion(ie.exp, istate, goal);
2326 return;
2328 else if (v._init.isVoidInitializer())
2330 result = voidInitLiteral(v.type, v).copy();
2331 // There is no AssignExp for void initializers,
2332 // so set it here.
2333 setValue(v, result);
2334 return;
2336 else if (v._init.isArrayInitializer())
2338 result = v._init.initializerToExpression(v.type);
2339 if (result !is null)
2340 return;
2342 error(e.loc, "declaration `%s` is not yet implemented in CTFE", e.toChars());
2343 result = CTFEExp.cantexp;
2345 else if (v.type.size() == 0)
2347 // Zero-length arrays don't need an initializer
2348 result = v.type.defaultInitLiteral(e.loc);
2350 else
2352 error(e.loc, "variable `%s` cannot be modified at compile time", v.toChars());
2353 result = CTFEExp.cantexp;
2355 return;
2357 if (s.isTemplateMixin() || s.isTupleDeclaration())
2359 // These can be made to work, too lazy now
2360 error(e.loc, "declaration `%s` is not yet implemented in CTFE", e.toChars());
2361 result = CTFEExp.cantexp;
2362 return;
2365 // Others should not contain executable code, so are trivial to evaluate
2366 result = null;
2367 debug (LOG)
2369 printf("-DeclarationExp::interpret(%s): %p\n", e.toChars(), result);
2373 override void visit(TypeidExp e)
2375 debug (LOG)
2377 printf("%s TypeidExp::interpret() %s\n", e.loc.toChars(), e.toChars());
2379 if (Type t = isType(e.obj))
2381 result = e;
2382 return;
2384 if (Expression ex = isExpression(e.obj))
2386 result = interpret(pue, ex, istate);
2387 if (exceptionOrCant(ex))
2388 return;
2390 if (result.op == EXP.null_)
2392 error(e.loc, "null pointer dereference evaluating typeid. `%s` is `null`", ex.toChars());
2393 result = CTFEExp.cantexp;
2394 return;
2396 if (result.op != EXP.classReference)
2398 error(e.loc, "CTFE internal error: determining classinfo");
2399 result = CTFEExp.cantexp;
2400 return;
2403 ClassDeclaration cd = result.isClassReferenceExp().originalClass();
2404 assert(cd);
2406 emplaceExp!(TypeidExp)(pue, e.loc, cd.type);
2407 result = pue.exp();
2408 result.type = e.type;
2409 return;
2411 visit(cast(Expression)e);
2414 override void visit(TupleExp e)
2416 debug (LOG)
2418 printf("%s TupleExp::interpret() %s\n", e.loc.toChars(), e.toChars());
2420 if (exceptionOrCant(interpretRegion(e.e0, istate, CTFEGoal.Nothing)))
2421 return;
2423 auto expsx = e.exps;
2424 foreach (i, exp; *expsx)
2426 Expression ex = interpretRegion(exp, istate);
2427 if (exceptionOrCant(ex))
2428 return;
2430 // A tuple of assignments can contain void (Bug 5676).
2431 if (goal == CTFEGoal.Nothing)
2432 continue;
2433 if (ex.op == EXP.voidExpression)
2435 error(e.loc, "CTFE internal error: void element `%s` in sequence", exp.toChars());
2436 assert(0);
2439 /* If any changes, do Copy On Write
2441 if (ex !is exp)
2443 expsx = copyArrayOnWrite(expsx, e.exps);
2444 (*expsx)[i] = copyRegionExp(ex);
2448 if (expsx !is e.exps)
2450 expandTuples(expsx);
2451 emplaceExp!(TupleExp)(pue, e.loc, expsx);
2452 result = pue.exp();
2453 result.type = new TypeTuple(expsx);
2455 else
2456 result = e;
2459 override void visit(ArrayLiteralExp e)
2461 debug (LOG)
2463 printf("%s ArrayLiteralExp::interpret() %s, %s\n", e.loc.toChars(), e.type.toChars(), e.toChars());
2465 if (e.ownedByCtfe >= OwnedBy.ctfe) // We've already interpreted all the elements
2467 result = e;
2468 return;
2471 Type tb = e.type.toBasetype();
2472 Type tn = tb.nextOf().toBasetype();
2473 bool wantCopy = (tn.ty == Tsarray || tn.ty == Tstruct);
2475 auto basis = interpretRegion(e.basis, istate);
2476 if (exceptionOrCant(basis))
2477 return;
2479 auto expsx = e.elements;
2480 size_t dim = expsx ? expsx.length : 0;
2482 for (size_t i = 0; i < dim; i++)
2484 Expression exp = (*expsx)[i];
2485 Expression ex;
2486 if (!exp)
2488 ex = copyLiteral(basis).copy();
2490 else
2492 // segfault bug 6250
2493 assert(exp.op != EXP.index || exp.isIndexExp().e1 != e);
2495 ex = interpretRegion(exp, istate);
2496 if (exceptionOrCant(ex))
2497 return;
2499 /* Each elements should have distinct CTFE memory.
2500 * int[1] z = 7;
2501 * int[1][] pieces = [z,z]; // here
2503 if (wantCopy)
2504 ex = copyLiteral(ex).copy();
2507 /* If any changes, do Copy On Write
2509 if (ex !is exp)
2511 expsx = copyArrayOnWrite(expsx, e.elements);
2512 (*expsx)[i] = ex;
2516 if (expsx !is e.elements)
2518 // todo: all tuple expansions should go in semantic phase.
2519 expandTuples(expsx);
2520 if (expsx.length != dim)
2522 error(e.loc, "CTFE internal error: invalid array literal");
2523 result = CTFEExp.cantexp;
2524 return;
2526 emplaceExp!(ArrayLiteralExp)(pue, e.loc, e.type, basis, expsx);
2527 auto ale = pue.exp().isArrayLiteralExp();
2528 ale.ownedByCtfe = OwnedBy.ctfe;
2529 result = ale;
2531 else if ((cast(TypeNext)e.type).next.mod & (MODFlags.const_ | MODFlags.immutable_))
2533 // If it's immutable, we don't need to dup it
2534 result = e;
2536 else
2538 *pue = copyLiteral(e);
2539 result = pue.exp();
2543 override void visit(AssocArrayLiteralExp e)
2545 debug (LOG)
2547 printf("%s AssocArrayLiteralExp::interpret() %s\n", e.loc.toChars(), e.toChars());
2549 if (e.ownedByCtfe >= OwnedBy.ctfe) // We've already interpreted all the elements
2551 result = e;
2552 return;
2555 auto keysx = e.keys;
2556 auto valuesx = e.values;
2557 foreach (i, ekey; *keysx)
2559 auto evalue = (*valuesx)[i];
2561 auto ek = interpretRegion(ekey, istate);
2562 if (exceptionOrCant(ek))
2563 return;
2564 auto ev = interpretRegion(evalue, istate);
2565 if (exceptionOrCant(ev))
2566 return;
2568 /* If any changes, do Copy On Write
2570 if (ek !is ekey ||
2571 ev !is evalue)
2573 keysx = copyArrayOnWrite(keysx, e.keys);
2574 valuesx = copyArrayOnWrite(valuesx, e.values);
2575 (*keysx)[i] = ek;
2576 (*valuesx)[i] = ev;
2579 if (keysx !is e.keys)
2580 expandTuples(keysx);
2581 if (valuesx !is e.values)
2582 expandTuples(valuesx);
2583 if (keysx.length != valuesx.length)
2585 error(e.loc, "CTFE internal error: invalid AA");
2586 result = CTFEExp.cantexp;
2587 return;
2590 /* Remove duplicate keys
2592 for (size_t i = 1; i < keysx.length; i++)
2594 auto ekey = (*keysx)[i - 1];
2595 for (size_t j = i; j < keysx.length; j++)
2597 auto ekey2 = (*keysx)[j];
2598 if (!ctfeEqual(e.loc, EXP.equal, ekey, ekey2))
2599 continue;
2601 // Remove ekey
2602 keysx = copyArrayOnWrite(keysx, e.keys);
2603 valuesx = copyArrayOnWrite(valuesx, e.values);
2604 keysx.remove(i - 1);
2605 valuesx.remove(i - 1);
2607 i -= 1; // redo the i'th iteration
2608 break;
2612 if (keysx !is e.keys ||
2613 valuesx !is e.values)
2615 assert(keysx !is e.keys &&
2616 valuesx !is e.values);
2617 auto aae = ctfeEmplaceExp!AssocArrayLiteralExp(e.loc, keysx, valuesx);
2618 aae.type = e.type;
2619 aae.ownedByCtfe = OwnedBy.ctfe;
2620 result = aae;
2622 else
2624 *pue = copyLiteral(e);
2625 result = pue.exp();
2629 override void visit(StructLiteralExp e)
2631 debug (LOG)
2633 printf("%s StructLiteralExp::interpret() %s ownedByCtfe = %d\n", e.loc.toChars(), e.toChars(), e.ownedByCtfe);
2635 if (e.ownedByCtfe >= OwnedBy.ctfe)
2637 result = e;
2638 return;
2641 size_t dim = e.elements ? e.elements.length : 0;
2642 auto expsx = e.elements;
2644 if (dim != e.sd.fields.length)
2646 // guaranteed by AggregateDeclaration.fill and TypeStruct.defaultInitLiteral
2647 const nvthis = e.sd.fields.length - e.sd.nonHiddenFields();
2648 assert(e.sd.fields.length - dim == nvthis);
2650 /* If a nested struct has no initialized hidden pointer,
2651 * set it to null to match the runtime behaviour.
2653 foreach (const i; 0 .. nvthis)
2655 auto ne = ctfeEmplaceExp!NullExp(e.loc);
2656 auto vthis = i == 0 ? e.sd.vthis : e.sd.vthis2;
2657 ne.type = vthis.type;
2659 expsx = copyArrayOnWrite(expsx, e.elements);
2660 expsx.push(ne);
2661 ++dim;
2664 assert(dim == e.sd.fields.length);
2666 foreach (i; 0 .. dim)
2668 auto v = e.sd.fields[i];
2669 Expression exp = (*expsx)[i];
2670 Expression ex;
2671 if (!exp)
2673 ex = voidInitLiteral(v.type, v).copy();
2675 else
2677 ex = interpretRegion(exp, istate);
2678 if (exceptionOrCant(ex))
2679 return;
2680 if ((v.type.ty != ex.type.ty) && v.type.ty == Tsarray)
2682 // Block assignment from inside struct literals
2683 auto tsa = cast(TypeSArray)v.type;
2684 auto len = cast(size_t)tsa.dim.toInteger();
2685 UnionExp ue = void;
2686 ex = createBlockDuplicatedArrayLiteral(&ue, ex.loc, v.type, ex, len);
2687 if (ex == ue.exp())
2688 ex = ue.copy();
2692 /* If any changes, do Copy On Write
2694 if (ex !is exp)
2696 expsx = copyArrayOnWrite(expsx, e.elements);
2697 (*expsx)[i] = ex;
2701 if (expsx !is e.elements)
2703 expandTuples(expsx);
2704 if (expsx.length != e.sd.fields.length)
2706 error(e.loc, "CTFE internal error: invalid struct literal");
2707 result = CTFEExp.cantexp;
2708 return;
2710 emplaceExp!(StructLiteralExp)(pue, e.loc, e.sd, expsx);
2711 auto sle = pue.exp().isStructLiteralExp();
2712 sle.type = e.type;
2713 sle.ownedByCtfe = OwnedBy.ctfe;
2714 sle.origin = e.origin;
2715 result = sle;
2717 else
2719 *pue = copyLiteral(e);
2720 result = pue.exp();
2724 // Create an array literal of type 'newtype' with dimensions given by
2725 // 'arguments'[argnum..$]
2726 static Expression recursivelyCreateArrayLiteral(UnionExp* pue, const ref Loc loc, Type newtype, InterState* istate, Expressions* arguments, int argnum)
2728 Expression lenExpr = interpret(pue, (*arguments)[argnum], istate);
2729 if (exceptionOrCantInterpret(lenExpr))
2730 return lenExpr;
2731 size_t len = cast(size_t)lenExpr.toInteger();
2732 Type elemType = (cast(TypeArray)newtype).next;
2733 if (elemType.ty == Tarray && argnum < arguments.length - 1)
2735 Expression elem = recursivelyCreateArrayLiteral(pue, loc, elemType, istate, arguments, argnum + 1);
2736 if (exceptionOrCantInterpret(elem))
2737 return elem;
2739 auto elements = new Expressions(len);
2740 foreach (ref element; *elements)
2741 element = copyLiteral(elem).copy();
2742 emplaceExp!(ArrayLiteralExp)(pue, loc, newtype, elements);
2743 auto ae = pue.exp().isArrayLiteralExp();
2744 ae.ownedByCtfe = OwnedBy.ctfe;
2745 return ae;
2747 assert(argnum == arguments.length - 1);
2748 if (elemType.ty.isSomeChar)
2750 const ch = cast(dchar)elemType.defaultInitLiteral(loc).toInteger();
2751 const sz = cast(ubyte)elemType.size();
2752 return createBlockDuplicatedStringLiteral(pue, loc, newtype, ch, len, sz);
2754 else
2756 auto el = interpret(elemType.defaultInitLiteral(loc), istate);
2757 return createBlockDuplicatedArrayLiteral(pue, loc, newtype, el, len);
2761 override void visit(NewExp e)
2763 debug (LOG)
2765 printf("%s NewExp::interpret() %s\n", e.loc.toChars(), e.toChars());
2768 Expression epre = interpret(pue, e.argprefix, istate, CTFEGoal.Nothing);
2769 if (exceptionOrCant(epre))
2770 return;
2772 if (e.newtype.ty == Tarray && e.arguments)
2774 result = recursivelyCreateArrayLiteral(pue, e.loc, e.newtype, istate, e.arguments, 0);
2775 return;
2777 if (auto ts = e.newtype.toBasetype().isTypeStruct())
2779 if (e.member)
2781 Expression se = e.newtype.defaultInitLiteral(e.loc);
2782 se = interpret(se, istate);
2783 if (exceptionOrCant(se))
2784 return;
2785 result = interpretFunction(pue, e.member, istate, e.arguments, se);
2787 // Repaint as same as CallExp::interpret() does.
2788 result.loc = e.loc;
2790 else
2792 StructDeclaration sd = ts.sym;
2793 auto exps = new Expressions();
2794 exps.reserve(sd.fields.length);
2795 if (e.arguments)
2797 exps.setDim(e.arguments.length);
2798 foreach (i, ex; *e.arguments)
2800 ex = interpretRegion(ex, istate);
2801 if (exceptionOrCant(ex))
2802 return;
2803 (*exps)[i] = ex;
2806 sd.fill(e.loc, *exps, false);
2808 auto se = ctfeEmplaceExp!StructLiteralExp(e.loc, sd, exps, e.newtype);
2809 se.origin = se;
2810 se.type = e.newtype;
2811 se.ownedByCtfe = OwnedBy.ctfe;
2812 result = interpret(pue, se, istate);
2814 if (exceptionOrCant(result))
2815 return;
2816 Expression ev = (result == pue.exp()) ? pue.copy() : result;
2817 emplaceExp!(AddrExp)(pue, e.loc, ev, e.type);
2818 result = pue.exp();
2819 return;
2821 if (auto tc = e.newtype.toBasetype().isTypeClass())
2823 ClassDeclaration cd = tc.sym;
2824 size_t totalFieldCount = 0;
2825 for (ClassDeclaration c = cd; c; c = c.baseClass)
2826 totalFieldCount += c.fields.length;
2827 auto elems = new Expressions(totalFieldCount);
2828 size_t fieldsSoFar = totalFieldCount;
2829 for (ClassDeclaration c = cd; c; c = c.baseClass)
2831 fieldsSoFar -= c.fields.length;
2832 foreach (i, v; c.fields)
2834 if (v.inuse)
2836 error(e.loc, "circular reference to `%s`", v.toPrettyChars());
2837 result = CTFEExp.cantexp;
2838 return;
2840 Expression m;
2841 if (v._init)
2843 if (v._init.isVoidInitializer())
2844 m = voidInitLiteral(v.type, v).copy();
2845 else
2846 m = v.getConstInitializer(true);
2848 else if (v.type.isTypeNoreturn())
2850 // Noreturn field with default initializer
2851 (*elems)[fieldsSoFar + i] = null;
2852 continue;
2854 else
2855 m = v.type.defaultInitLiteral(e.loc);
2856 if (exceptionOrCant(m))
2857 return;
2858 (*elems)[fieldsSoFar + i] = copyLiteral(m).copy();
2861 // Hack: we store a ClassDeclaration instead of a StructDeclaration.
2862 // We probably won't get away with this.
2863 // auto se = new StructLiteralExp(e.loc, cast(StructDeclaration)cd, elems, e.newtype);
2864 auto se = ctfeEmplaceExp!StructLiteralExp(e.loc, cast(StructDeclaration)cd, elems, e.newtype);
2865 se.origin = se;
2866 se.ownedByCtfe = OwnedBy.ctfe;
2867 Expression eref = ctfeEmplaceExp!ClassReferenceExp(e.loc, se, e.type);
2868 if (e.member)
2870 // Call constructor
2871 if (!e.member.fbody)
2873 Expression ctorfail = evaluateIfBuiltin(pue, istate, e.loc, e.member, e.arguments, eref);
2874 if (ctorfail)
2876 if (exceptionOrCant(ctorfail))
2877 return;
2878 result = eref;
2879 return;
2881 auto m = e.member;
2882 error(m.loc, "%s `%s` `%s` cannot be constructed at compile time, because the constructor has no available source code",
2883 m.kind, m.toPrettyChars, e.newtype.toChars());
2884 result = CTFEExp.cantexp;
2885 return;
2887 UnionExp ue = void;
2888 Expression ctorfail = interpretFunction(&ue, e.member, istate, e.arguments, eref);
2889 if (exceptionOrCant(ctorfail))
2890 return;
2892 /* https://issues.dlang.org/show_bug.cgi?id=14465
2893 * Repaint the loc, because a super() call
2894 * in the constructor modifies the loc of ClassReferenceExp
2895 * in CallExp::interpret().
2897 eref.loc = e.loc;
2899 result = eref;
2900 return;
2902 if (e.newtype.toBasetype().isscalar())
2904 Expression newval;
2905 if (e.arguments && e.arguments.length)
2906 newval = (*e.arguments)[0];
2907 else
2908 newval = e.newtype.defaultInitLiteral(e.loc);
2909 newval = interpretRegion(newval, istate);
2910 if (exceptionOrCant(newval))
2911 return;
2913 // Create a CTFE pointer &[newval][0]
2914 auto elements = new Expressions(1);
2915 (*elements)[0] = newval;
2916 auto ae = ctfeEmplaceExp!ArrayLiteralExp(e.loc, e.newtype.arrayOf(), elements);
2917 ae.ownedByCtfe = OwnedBy.ctfe;
2919 auto ei = ctfeEmplaceExp!IndexExp(e.loc, ae, ctfeEmplaceExp!IntegerExp(Loc.initial, 0, Type.tsize_t));
2920 ei.type = e.newtype;
2921 emplaceExp!(AddrExp)(pue, e.loc, ei, e.type);
2922 result = pue.exp();
2923 return;
2925 error(e.loc, "cannot interpret `%s` at compile time", e.toChars());
2926 result = CTFEExp.cantexp;
2929 override void visit(UnaExp e)
2931 debug (LOG)
2933 printf("%s UnaExp::interpret() %s\n", e.loc.toChars(), e.toChars());
2935 UnionExp ue = void;
2936 Expression e1 = interpret(&ue, e.e1, istate);
2937 if (exceptionOrCant(e1))
2938 return;
2939 switch (e.op)
2941 case EXP.negate:
2942 *pue = Neg(e.type, e1);
2943 break;
2945 case EXP.tilde:
2946 *pue = Com(e.type, e1);
2947 break;
2949 case EXP.not:
2950 *pue = Not(e.type, e1);
2951 break;
2953 default:
2954 assert(0);
2956 result = (*pue).exp();
2959 override void visit(DotTypeExp e)
2961 debug (LOG)
2963 printf("%s DotTypeExp::interpret() %s\n", e.loc.toChars(), e.toChars());
2965 UnionExp ue = void;
2966 Expression e1 = interpret(&ue, e.e1, istate);
2967 if (exceptionOrCant(e1))
2968 return;
2969 if (e1 == e.e1)
2970 result = e; // optimize: reuse this CTFE reference
2971 else
2973 auto edt = e.copy().isDotTypeExp();
2974 edt.e1 = (e1 == ue.exp()) ? e1.copy() : e1; // don't return pointer to ue
2975 result = edt;
2979 private alias fp_t = extern (D) UnionExp function(const ref Loc loc, Type, Expression, Expression);
2980 private alias fp2_t = extern (D) bool function(const ref Loc loc, EXP, Expression, Expression);
2982 extern (D) private void interpretCommon(BinExp e, fp_t fp)
2984 debug (LOG)
2986 printf("%s BinExp::interpretCommon() %s\n", e.loc.toChars(), e.toChars());
2988 if (e.e1.type.ty == Tpointer && e.e2.type.ty == Tpointer && e.op == EXP.min)
2990 UnionExp ue1 = void;
2991 Expression e1 = interpret(&ue1, e.e1, istate);
2992 if (exceptionOrCant(e1))
2993 return;
2994 UnionExp ue2 = void;
2995 Expression e2 = interpret(&ue2, e.e2, istate);
2996 if (exceptionOrCant(e2))
2997 return;
2998 result = pointerDifference(pue, e.loc, e.type, e1, e2);
2999 return;
3001 if (e.e1.type.ty == Tpointer && e.e2.type.isintegral())
3003 UnionExp ue1 = void;
3004 Expression e1 = interpret(&ue1, e.e1, istate);
3005 if (exceptionOrCant(e1))
3006 return;
3007 UnionExp ue2 = void;
3008 Expression e2 = interpret(&ue2, e.e2, istate);
3009 if (exceptionOrCant(e2))
3010 return;
3011 result = pointerArithmetic(pue, e.loc, e.op, e.type, e1, e2);
3012 return;
3014 if (e.e2.type.ty == Tpointer && e.e1.type.isintegral() && e.op == EXP.add)
3016 UnionExp ue1 = void;
3017 Expression e1 = interpret(&ue1, e.e1, istate);
3018 if (exceptionOrCant(e1))
3019 return;
3020 UnionExp ue2 = void;
3021 Expression e2 = interpret(&ue2, e.e2, istate);
3022 if (exceptionOrCant(e2))
3023 return;
3024 result = pointerArithmetic(pue, e.loc, e.op, e.type, e2, e1);
3025 return;
3027 if (e.e1.type.ty == Tpointer || e.e2.type.ty == Tpointer)
3029 error(e.loc, "pointer expression `%s` cannot be interpreted at compile time", e.toChars());
3030 result = CTFEExp.cantexp;
3031 return;
3034 bool evalOperand(UnionExp* pue, Expression ex, out Expression er)
3036 er = interpret(pue, ex, istate);
3037 if (exceptionOrCant(er))
3038 return false;
3039 return true;
3042 UnionExp ue1 = void;
3043 Expression e1;
3044 if (!evalOperand(&ue1, e.e1, e1))
3045 return;
3047 UnionExp ue2 = void;
3048 Expression e2;
3049 if (!evalOperand(&ue2, e.e2, e2))
3050 return;
3052 if (e.op == EXP.rightShift || e.op == EXP.leftShift || e.op == EXP.unsignedRightShift)
3054 const sinteger_t i2 = e2.toInteger();
3055 const uinteger_t sz = e1.type.size() * 8;
3056 if (i2 < 0 || i2 >= sz)
3058 error(e.loc, "shift by %lld is outside the range 0..%llu", i2, cast(ulong)sz - 1);
3059 result = CTFEExp.cantexp;
3060 return;
3064 /******************************************
3065 * Perform the operation fp on operands e1 and e2.
3067 UnionExp evaluate(Loc loc, Type type, Expression e1, Expression e2)
3069 UnionExp ue = void;
3070 auto ae1 = e1.isArrayLiteralExp();
3071 auto ae2 = e2.isArrayLiteralExp();
3072 if (ae1 || ae2)
3074 /* Cases:
3075 * 1. T[] op T[]
3076 * 2. T op T[]
3077 * 3. T[] op T
3079 if (ae1 && e2.implicitConvTo(e1.type.toBasetype().nextOf())) // case 3
3080 ae2 = null;
3081 else if (ae2 && e1.implicitConvTo(e2.type.toBasetype().nextOf())) // case 2
3082 ae1 = null;
3083 // else case 1
3085 auto aex = ae1 ? ae1 : ae2;
3086 if (!aex.elements)
3088 emplaceExp!ArrayLiteralExp(&ue, loc, type, cast(Expressions*) null);
3089 return ue;
3091 const length = aex.elements.length;
3092 Expressions* elements = new Expressions(length);
3094 emplaceExp!ArrayLiteralExp(&ue, loc, type, elements);
3095 foreach (i; 0 .. length)
3097 Expression e1x = ae1 ? ae1[i] : e1;
3098 Expression e2x = ae2 ? ae2[i] : e2;
3099 UnionExp uex = evaluate(loc, e1x.type, e1x, e2x);
3100 // This can be made more efficient by making use of ue.basis
3101 (*elements)[i] = uex.copy();
3103 return ue;
3106 if (e1.isConst() != 1)
3108 // The following should really be an assert()
3109 error(e1.loc, "CTFE internal error: non-constant value `%s`", e1.toChars());
3110 emplaceExp!CTFEExp(&ue, EXP.cantExpression);
3111 return ue;
3113 if (e2.isConst() != 1)
3115 error(e2.loc, "CTFE internal error: non-constant value `%s`", e2.toChars());
3116 emplaceExp!CTFEExp(&ue, EXP.cantExpression);
3117 return ue;
3120 return (*fp)(loc, type, e1, e2);
3123 *pue = evaluate(e.loc, e.type, e1, e2);
3124 result = (*pue).exp();
3125 if (CTFEExp.isCantExp(result))
3126 error(e.loc, "`%s` cannot be interpreted at compile time", e.toChars());
3129 extern (D) private void interpretCompareCommon(BinExp e, fp2_t fp)
3131 debug (LOG)
3133 printf("%s BinExp::interpretCompareCommon() %s\n", e.loc.toChars(), e.toChars());
3135 UnionExp ue1 = void;
3136 UnionExp ue2 = void;
3137 if (e.e1.type.ty == Tpointer && e.e2.type.ty == Tpointer)
3139 Expression e1 = interpret(&ue1, e.e1, istate);
3140 if (exceptionOrCant(e1))
3141 return;
3142 Expression e2 = interpret(&ue2, e.e2, istate);
3143 if (exceptionOrCant(e2))
3144 return;
3145 //printf("e1 = %s %s, e2 = %s %s\n", e1.type.toChars(), e1.toChars(), e2.type.toChars(), e2.toChars());
3146 dinteger_t ofs1, ofs2;
3147 Expression agg1 = getAggregateFromPointer(e1, &ofs1);
3148 Expression agg2 = getAggregateFromPointer(e2, &ofs2);
3149 //printf("agg1 = %p %s, agg2 = %p %s\n", agg1, agg1.toChars(), agg2, agg2.toChars());
3150 const cmp = comparePointers(e.op, agg1, ofs1, agg2, ofs2);
3151 if (cmp == -1)
3153 char dir = (e.op == EXP.greaterThan || e.op == EXP.greaterOrEqual) ? '<' : '>';
3154 error(e.loc, "the ordering of pointers to unrelated memory blocks is indeterminate in CTFE. To check if they point to the same memory block, use both `>` and `<` inside `&&` or `||`, eg `%s && %s %c= %s + 1`", e.toChars(), e.e1.toChars(), dir, e.e2.toChars());
3155 result = CTFEExp.cantexp;
3156 return;
3158 if (e.type.equals(Type.tbool))
3159 result = IntegerExp.createBool(cmp != 0);
3160 else
3162 emplaceExp!(IntegerExp)(pue, e.loc, cmp, e.type);
3163 result = (*pue).exp();
3165 return;
3167 Expression e1 = interpret(&ue1, e.e1, istate);
3168 if (exceptionOrCant(e1))
3169 return;
3170 if (!isCtfeComparable(e1))
3172 error(e.loc, "cannot compare `%s` at compile time", e1.toChars());
3173 result = CTFEExp.cantexp;
3174 return;
3176 Expression e2 = interpret(&ue2, e.e2, istate);
3177 if (exceptionOrCant(e2))
3178 return;
3179 if (!isCtfeComparable(e2))
3181 error(e.loc, "cannot compare `%s` at compile time", e2.toChars());
3182 result = CTFEExp.cantexp;
3183 return;
3185 const cmp = (*fp)(e.loc, e.op, e1, e2);
3186 if (e.type.equals(Type.tbool))
3187 result = IntegerExp.createBool(cmp);
3188 else
3190 emplaceExp!(IntegerExp)(pue, e.loc, cmp, e.type);
3191 result = (*pue).exp();
3195 override void visit(BinExp e)
3197 switch (e.op)
3199 case EXP.add:
3200 interpretCommon(e, &Add);
3201 return;
3203 case EXP.min:
3204 interpretCommon(e, &Min);
3205 return;
3207 case EXP.mul:
3208 interpretCommon(e, &Mul);
3209 return;
3211 case EXP.div:
3212 interpretCommon(e, &Div);
3213 return;
3215 case EXP.mod:
3216 interpretCommon(e, &Mod);
3217 return;
3219 case EXP.leftShift:
3220 interpretCommon(e, &Shl);
3221 return;
3223 case EXP.rightShift:
3224 interpretCommon(e, &Shr);
3225 return;
3227 case EXP.unsignedRightShift:
3228 interpretCommon(e, &Ushr);
3229 return;
3231 case EXP.and:
3232 interpretCommon(e, &And);
3233 return;
3235 case EXP.or:
3236 interpretCommon(e, &Or);
3237 return;
3239 case EXP.xor:
3240 interpretCommon(e, &Xor);
3241 return;
3243 case EXP.pow:
3244 interpretCommon(e, &Pow);
3245 return;
3247 case EXP.equal:
3248 case EXP.notEqual:
3249 interpretCompareCommon(e, &ctfeEqual);
3250 return;
3252 case EXP.identity:
3253 case EXP.notIdentity:
3254 interpretCompareCommon(e, &ctfeIdentity);
3255 return;
3257 case EXP.lessThan:
3258 case EXP.lessOrEqual:
3259 case EXP.greaterThan:
3260 case EXP.greaterOrEqual:
3261 interpretCompareCommon(e, &ctfeCmp);
3262 return;
3264 default:
3265 printf("be = '%s' %s at [%s]\n", EXPtoString(e.op).ptr, e.toChars(), e.loc.toChars());
3266 assert(0);
3270 /* Helper functions for BinExp::interpretAssignCommon
3272 // Returns the variable which is eventually modified, or NULL if an rvalue.
3273 // thisval is the current value of 'this'.
3274 static VarDeclaration findParentVar(Expression e) @safe
3276 for (;;)
3278 if (auto ve = e.isVarExp())
3280 VarDeclaration v = ve.var.isVarDeclaration();
3281 assert(v);
3282 return v;
3284 if (auto ie = e.isIndexExp())
3285 e = ie.e1;
3286 else if (auto dve = e.isDotVarExp())
3287 e = dve.e1;
3288 else if (auto dtie = e.isDotTemplateInstanceExp())
3289 e = dtie.e1;
3290 else if (auto se = e.isSliceExp())
3291 e = se.e1;
3292 else
3293 return null;
3297 extern (D) private void interpretAssignCommon(BinExp e, fp_t fp, int post = 0)
3299 debug (LOG)
3301 printf("%s BinExp::interpretAssignCommon() %s\n", e.loc.toChars(), e.toChars());
3303 result = CTFEExp.cantexp;
3305 Expression e1 = e.e1;
3306 if (!istate)
3308 error(e.loc, "value of `%s` is not known at compile time", e1.toChars());
3309 return;
3312 ++ctfeGlobals.numAssignments;
3314 /* Before we begin, we need to know if this is a reference assignment
3315 * (dynamic array, AA, or class) or a value assignment.
3316 * Determining this for slice assignments are tricky: we need to know
3317 * if it is a block assignment (a[] = e) rather than a direct slice
3318 * assignment (a[] = b[]). Note that initializers of multi-dimensional
3319 * static arrays can have 2D block assignments (eg, int[7][7] x = 6;).
3320 * So we need to recurse to determine if it is a block assignment.
3322 bool isBlockAssignment = false;
3323 if (e1.op == EXP.slice)
3325 // a[] = e can have const e. So we compare the naked types.
3326 Type tdst = e1.type.toBasetype();
3327 Type tsrc = e.e2.type.toBasetype();
3328 while (tdst.ty == Tsarray || tdst.ty == Tarray)
3330 tdst = (cast(TypeArray)tdst).next.toBasetype();
3331 if (tsrc.equivalent(tdst))
3333 isBlockAssignment = true;
3334 break;
3339 // ---------------------------------------
3340 // Deal with reference assignment
3341 // ---------------------------------------
3342 // If it is a construction of a ref variable, it is a ref assignment
3343 if ((e.op == EXP.construct || e.op == EXP.blit) &&
3344 ((cast(AssignExp)e).memset == MemorySet.referenceInit))
3346 assert(!fp);
3348 Expression newval = interpretRegion(e.e2, istate, CTFEGoal.LValue);
3349 if (exceptionOrCant(newval))
3350 return;
3352 VarDeclaration v = e1.isVarExp().var.isVarDeclaration();
3353 setValue(v, newval);
3355 // Get the value to return. Note that 'newval' is an Lvalue,
3356 // so if we need an Rvalue, we have to interpret again.
3357 if (goal == CTFEGoal.RValue)
3358 result = interpretRegion(newval, istate);
3359 else
3360 result = e1; // VarExp is a CTFE reference
3361 return;
3364 if (fp)
3366 while (e1.op == EXP.cast_)
3368 CastExp ce = e1.isCastExp();
3369 e1 = ce.e1;
3373 // ---------------------------------------
3374 // Interpret left hand side
3375 // ---------------------------------------
3376 AssocArrayLiteralExp existingAA = null;
3377 Expression lastIndex = null;
3378 Expression oldval = null;
3379 if (e1.op == EXP.index && e1.isIndexExp().e1.type.toBasetype().ty == Taarray)
3381 // ---------------------------------------
3382 // Deal with AA index assignment
3383 // ---------------------------------------
3384 /* This needs special treatment if the AA doesn't exist yet.
3385 * There are two special cases:
3386 * (1) If the AA is itself an index of another AA, we may need to create
3387 * multiple nested AA literals before we can insert the new value.
3388 * (2) If the ultimate AA is null, no insertion happens at all. Instead,
3389 * we create nested AA literals, and change it into a assignment.
3391 IndexExp ie = e1.isIndexExp();
3392 int depth = 0; // how many nested AA indices are there?
3393 while (ie.e1.op == EXP.index && ie.e1.isIndexExp().e1.type.toBasetype().ty == Taarray)
3395 assert(ie.modifiable);
3396 ie = ie.e1.isIndexExp();
3397 ++depth;
3400 // Get the AA value to be modified.
3401 Expression aggregate = interpretRegion(ie.e1, istate);
3402 if (exceptionOrCant(aggregate))
3403 return;
3404 if ((existingAA = aggregate.isAssocArrayLiteralExp()) !is null)
3406 // Normal case, ultimate parent AA already exists
3407 // We need to walk from the deepest index up, checking that an AA literal
3408 // already exists on each level.
3409 lastIndex = interpretRegion(e1.isIndexExp().e2, istate);
3410 lastIndex = resolveSlice(lastIndex); // only happens with AA assignment
3411 if (exceptionOrCant(lastIndex))
3412 return;
3414 while (depth > 0)
3416 // Walk the syntax tree to find the indexExp at this depth
3417 IndexExp xe = e1.isIndexExp();
3418 foreach (d; 0 .. depth)
3419 xe = xe.e1.isIndexExp();
3421 Expression ekey = interpretRegion(xe.e2, istate);
3422 if (exceptionOrCant(ekey))
3423 return;
3424 UnionExp ekeyTmp = void;
3425 ekey = resolveSlice(ekey, &ekeyTmp); // only happens with AA assignment
3427 // Look up this index in it up in the existing AA, to get the next level of AA.
3428 AssocArrayLiteralExp newAA = cast(AssocArrayLiteralExp)findKeyInAA(e.loc, existingAA, ekey);
3429 if (exceptionOrCant(newAA))
3430 return;
3431 if (!newAA)
3433 // Doesn't exist yet, create an empty AA...
3434 auto keysx = new Expressions();
3435 auto valuesx = new Expressions();
3436 newAA = ctfeEmplaceExp!AssocArrayLiteralExp(e.loc, keysx, valuesx);
3437 newAA.type = xe.type;
3438 newAA.ownedByCtfe = OwnedBy.ctfe;
3439 //... and insert it into the existing AA.
3440 existingAA.keys.push(ekey);
3441 existingAA.values.push(newAA);
3443 existingAA = newAA;
3444 --depth;
3447 if (fp)
3449 oldval = findKeyInAA(e.loc, existingAA, lastIndex);
3450 if (!oldval)
3451 oldval = copyLiteral(e.e1.type.defaultInitLiteral(e.loc)).copy();
3454 else
3456 /* The AA is currently null. 'aggregate' is actually a reference to
3457 * whatever contains it. It could be anything: var, dotvarexp, ...
3458 * We rewrite the assignment from:
3459 * aa[i][j] op= newval;
3460 * into:
3461 * aa = [i:[j:T.init]];
3462 * aa[j] op= newval;
3464 oldval = copyLiteral(e.e1.type.defaultInitLiteral(e.loc)).copy();
3466 Expression newaae = oldval;
3467 while (e1.op == EXP.index && e1.isIndexExp().e1.type.toBasetype().ty == Taarray)
3469 Expression ekey = interpretRegion(e1.isIndexExp().e2, istate);
3470 if (exceptionOrCant(ekey))
3471 return;
3472 ekey = resolveSlice(ekey); // only happens with AA assignment
3474 auto keysx = new Expressions();
3475 auto valuesx = new Expressions();
3476 keysx.push(ekey);
3477 valuesx.push(newaae);
3479 auto aae = ctfeEmplaceExp!AssocArrayLiteralExp(e.loc, keysx, valuesx);
3480 aae.type = e1.isIndexExp().e1.type;
3481 aae.ownedByCtfe = OwnedBy.ctfe;
3482 if (!existingAA)
3484 existingAA = aae;
3485 lastIndex = ekey;
3487 newaae = aae;
3488 e1 = e1.isIndexExp().e1;
3491 // We must set to aggregate with newaae
3492 e1 = interpretRegion(e1, istate, CTFEGoal.LValue);
3493 if (exceptionOrCant(e1))
3494 return;
3495 e1 = assignToLvalue(e, e1, newaae);
3496 if (exceptionOrCant(e1))
3497 return;
3499 assert(existingAA && lastIndex);
3500 e1 = null; // stomp
3502 else if (e1.op == EXP.arrayLength)
3504 oldval = interpretRegion(e1, istate);
3505 if (exceptionOrCant(oldval))
3506 return;
3508 else if (e.op == EXP.construct || e.op == EXP.blit)
3510 // Unless we have a simple var assignment, we're
3511 // only modifying part of the variable. So we need to make sure
3512 // that the parent variable exists.
3513 VarDeclaration ultimateVar = findParentVar(e1);
3514 if (auto ve = e1.isVarExp())
3516 VarDeclaration v = ve.var.isVarDeclaration();
3517 assert(v);
3518 if (v.storage_class & STC.out_)
3519 goto L1;
3521 else if (ultimateVar && !getValue(ultimateVar))
3523 Expression ex = interpretRegion(ultimateVar.type.defaultInitLiteral(e.loc), istate);
3524 if (exceptionOrCant(ex))
3525 return;
3526 setValue(ultimateVar, ex);
3528 else
3529 goto L1;
3531 else
3534 e1 = interpretRegion(e1, istate, CTFEGoal.LValue);
3535 if (exceptionOrCant(e1))
3536 return;
3538 if (e1.op == EXP.index && e1.isIndexExp().e1.type.toBasetype().ty == Taarray)
3540 IndexExp ie = e1.isIndexExp();
3541 assert(ie.e1.op == EXP.assocArrayLiteral);
3542 existingAA = ie.e1.isAssocArrayLiteralExp();
3543 lastIndex = ie.e2;
3547 // ---------------------------------------
3548 // Interpret right hand side
3549 // ---------------------------------------
3550 Expression newval = interpretRegion(e.e2, istate);
3551 if (exceptionOrCant(newval))
3552 return;
3553 if (e.op == EXP.blit && newval.op == EXP.int64)
3555 Type tbn = e.type.baseElemOf();
3556 if (tbn.ty == Tstruct)
3558 /* Look for special case of struct being initialized with 0.
3560 newval = e.type.defaultInitLiteral(e.loc);
3561 if (newval.op == EXP.error)
3563 result = CTFEExp.cantexp;
3564 return;
3566 newval = interpretRegion(newval, istate); // copy and set ownedByCtfe flag
3567 if (exceptionOrCant(newval))
3568 return;
3572 // ----------------------------------------------------
3573 // Deal with read-modify-write assignments.
3574 // Set 'newval' to the final assignment value
3575 // Also determine the return value (except for slice
3576 // assignments, which are more complicated)
3577 // ----------------------------------------------------
3578 if (fp)
3580 if (!oldval)
3582 // Load the left hand side after interpreting the right hand side.
3583 oldval = interpretRegion(e1, istate);
3584 if (exceptionOrCant(oldval))
3585 return;
3588 if (e.e1.type.ty != Tpointer)
3590 // ~= can create new values (see bug 6052)
3591 if (e.op == EXP.concatenateAssign || e.op == EXP.concatenateElemAssign || e.op == EXP.concatenateDcharAssign)
3593 // We need to dup it and repaint the type. For a dynamic array
3594 // we can skip duplication, because it gets copied later anyway.
3595 if (newval.type.ty != Tarray)
3597 newval = copyLiteral(newval).copy();
3598 newval.type = e.e2.type; // repaint type
3600 else
3602 newval = paintTypeOntoLiteral(e.e2.type, newval);
3603 newval = resolveSlice(newval);
3606 oldval = resolveSlice(oldval);
3608 newval = (*fp)(e.loc, e.type, oldval, newval).copy();
3610 else if (e.e2.type.isintegral() &&
3611 (e.op == EXP.addAssign ||
3612 e.op == EXP.minAssign ||
3613 e.op == EXP.plusPlus ||
3614 e.op == EXP.minusMinus))
3616 newval = pointerArithmetic(pue, e.loc, e.op, e.type, oldval, newval).copy();
3617 if (newval == pue.exp())
3618 newval = pue.copy();
3620 else
3622 error(e.loc, "pointer expression `%s` cannot be interpreted at compile time", e.toChars());
3623 result = CTFEExp.cantexp;
3624 return;
3626 if (exceptionOrCant(newval))
3628 if (CTFEExp.isCantExp(newval))
3629 error(e.loc, "cannot interpret `%s` at compile time", e.toChars());
3630 return;
3634 if (existingAA)
3636 if (existingAA.ownedByCtfe != OwnedBy.ctfe)
3638 error(e.loc, "cannot modify read-only constant `%s`", existingAA.toChars());
3639 result = CTFEExp.cantexp;
3640 return;
3643 //printf("\t+L%d existingAA = %s, lastIndex = %s, oldval = %s, newval = %s\n",
3644 // __LINE__, existingAA.toChars(), lastIndex.toChars(), oldval ? oldval.toChars() : NULL, newval.toChars());
3645 assignAssocArrayElement(e.loc, existingAA, lastIndex, newval);
3647 // Determine the return value
3648 result = ctfeCast(pue, e.loc, e.type, e.type, fp && post ? oldval : newval);
3649 return;
3651 if (e1.op == EXP.arrayLength)
3653 /* Change the assignment from:
3654 * arr.length = n;
3655 * into:
3656 * arr = new_length_array; (result is n)
3659 // Determine the return value
3660 result = ctfeCast(pue, e.loc, e.type, e.type, fp && post ? oldval : newval);
3661 if (exceptionOrCant(result))
3662 return;
3664 if (result == pue.exp())
3665 result = pue.copy();
3667 size_t oldlen = cast(size_t)oldval.toInteger();
3668 size_t newlen = cast(size_t)newval.toInteger();
3669 if (oldlen == newlen) // no change required -- we're done!
3670 return;
3672 // We have changed it into a reference assignment
3673 // Note that returnValue is still the new length.
3674 e1 = e1.isArrayLengthExp().e1;
3675 Type t = e1.type.toBasetype();
3676 if (t.ty != Tarray)
3678 error(e.loc, "`%s` is not yet supported at compile time", e.toChars());
3679 result = CTFEExp.cantexp;
3680 return;
3682 e1 = interpretRegion(e1, istate, CTFEGoal.LValue);
3683 if (exceptionOrCant(e1))
3684 return;
3686 if (oldlen != 0) // Get the old array literal.
3687 oldval = interpretRegion(e1, istate);
3688 UnionExp utmp = void;
3689 oldval = resolveSlice(oldval, &utmp);
3691 newval = changeArrayLiteralLength(pue, e.loc, cast(TypeArray)t, oldval, oldlen, newlen);
3692 if (newval == pue.exp())
3693 newval = pue.copy();
3695 e1 = assignToLvalue(e, e1, newval);
3696 if (exceptionOrCant(e1))
3697 return;
3699 return;
3702 if (!isBlockAssignment)
3704 newval = ctfeCast(pue, e.loc, e.type, e.type, newval);
3705 if (exceptionOrCant(newval))
3706 return;
3707 if (newval == pue.exp())
3708 newval = pue.copy();
3710 // Determine the return value
3711 if (goal == CTFEGoal.LValue) // https://issues.dlang.org/show_bug.cgi?id=14371
3712 result = e1;
3713 else
3715 result = ctfeCast(pue, e.loc, e.type, e.type, fp && post ? oldval : newval);
3716 if (result == pue.exp())
3717 result = pue.copy();
3719 if (exceptionOrCant(result))
3720 return;
3722 if (exceptionOrCant(newval))
3723 return;
3725 debug (LOGASSIGN)
3727 printf("ASSIGN: %s=%s\n", e1.toChars(), newval.toChars());
3728 showCtfeExpr(newval);
3731 /* Block assignment or element-wise assignment.
3733 if (e1.op == EXP.slice ||
3734 e1.op == EXP.vector ||
3735 e1.op == EXP.arrayLiteral ||
3736 e1.op == EXP.string_ ||
3737 e1.op == EXP.null_ && e1.type.toBasetype().ty == Tarray)
3739 // Note that slice assignments don't support things like ++, so
3740 // we don't need to remember 'returnValue'.
3741 result = interpretAssignToSlice(pue, e, e1, newval, isBlockAssignment);
3742 if (exceptionOrCant(result))
3743 return;
3744 if (auto se = e.e1.isSliceExp())
3746 Expression e1x = interpretRegion(se.e1, istate, CTFEGoal.LValue);
3747 if (auto dve = e1x.isDotVarExp())
3749 auto ex = dve.e1;
3750 auto sle = ex.op == EXP.structLiteral ? ex.isStructLiteralExp()
3751 : ex.op == EXP.classReference ? ex.isClassReferenceExp().value
3752 : null;
3753 auto v = dve.var.isVarDeclaration();
3754 if (!sle || !v)
3756 error(e.loc, "CTFE internal error: dotvar slice assignment");
3757 result = CTFEExp.cantexp;
3758 return;
3760 stompOverlappedFields(sle, v);
3763 return;
3765 assert(result);
3767 /* Assignment to a CTFE reference.
3769 if (Expression ex = assignToLvalue(e, e1, newval))
3770 result = ex;
3772 return;
3775 /* Set all sibling fields which overlap with v to VoidExp.
3777 private void stompOverlappedFields(StructLiteralExp sle, VarDeclaration v)
3779 if (!v.overlapped)
3780 return;
3781 foreach (size_t i, v2; sle.sd.fields)
3783 if (v is v2 || !v.isOverlappedWith(v2))
3784 continue;
3785 auto e = (*sle.elements)[i];
3786 if (e.op != EXP.void_)
3787 (*sle.elements)[i] = voidInitLiteral(e.type, v).copy();
3791 private Expression assignToLvalue(BinExp e, Expression e1, Expression newval)
3793 //printf("assignToLvalue() e: %s e1: %s newval: %s\n", e.toChars(), e1.toChars(), newval.toChars());
3794 VarDeclaration vd = null;
3795 Expression* payload = null; // dead-store to prevent spurious warning
3796 Expression oldval;
3798 if (auto ve = e1.isVarExp())
3800 vd = ve.var.isVarDeclaration();
3801 oldval = getValue(vd);
3803 else if (auto dve = e1.isDotVarExp())
3805 /* Assignment to member variable of the form:
3806 * e.v = newval
3808 auto ex = dve.e1;
3809 auto sle = ex.op == EXP.structLiteral ? ex.isStructLiteralExp()
3810 : ex.op == EXP.classReference ? ex.isClassReferenceExp().value
3811 : null;
3812 auto v = e1.isDotVarExp().var.isVarDeclaration();
3813 if (!sle || !v)
3815 error(e.loc, "CTFE internal error: dotvar assignment");
3816 return CTFEExp.cantexp;
3818 if (sle.ownedByCtfe != OwnedBy.ctfe)
3820 error(e.loc, "cannot modify read-only constant `%s`", sle.toChars());
3821 return CTFEExp.cantexp;
3824 int fieldi = ex.op == EXP.structLiteral ? findFieldIndexByName(sle.sd, v)
3825 : ex.isClassReferenceExp().findFieldIndexByName(v);
3826 if (fieldi == -1)
3828 error(e.loc, "CTFE internal error: cannot find field `%s` in `%s`", v.toChars(), ex.toChars());
3829 return CTFEExp.cantexp;
3831 assert(0 <= fieldi && fieldi < sle.elements.length);
3833 // If it's a union, set all other members of this union to void
3834 stompOverlappedFields(sle, v);
3836 payload = &(*sle.elements)[fieldi];
3837 oldval = *payload;
3838 if (auto ival = newval.isIntegerExp())
3840 if (auto bf = v.isBitFieldDeclaration())
3842 sinteger_t value = ival.toInteger();
3843 if (bf.type.isunsigned())
3844 value &= (1L << bf.fieldWidth) - 1; // zero extra bits
3845 else
3846 { // sign extend extra bits
3847 value = value << (64 - bf.fieldWidth);
3848 value = value >> (64 - bf.fieldWidth);
3850 ival.setInteger(value);
3854 else if (auto ie = e1.isIndexExp())
3856 assert(ie.e1.type.toBasetype().ty != Taarray);
3858 Expression aggregate;
3859 uinteger_t indexToModify;
3860 if (!resolveIndexing(ie, istate, &aggregate, &indexToModify, true))
3862 return CTFEExp.cantexp;
3864 size_t index = cast(size_t)indexToModify;
3866 if (auto existingSE = aggregate.isStringExp())
3868 if (existingSE.ownedByCtfe != OwnedBy.ctfe)
3870 error(e.loc, "cannot modify read-only string literal `%s`", ie.e1.toChars());
3871 return CTFEExp.cantexp;
3873 existingSE.setCodeUnit(index, cast(dchar)newval.toInteger());
3874 return null;
3876 if (aggregate.op != EXP.arrayLiteral)
3878 error(e.loc, "index assignment `%s` is not yet supported in CTFE ", e.toChars());
3879 return CTFEExp.cantexp;
3882 ArrayLiteralExp existingAE = aggregate.isArrayLiteralExp();
3883 if (existingAE.ownedByCtfe != OwnedBy.ctfe)
3885 error(e.loc, "cannot modify read-only constant `%s`", existingAE.toChars());
3886 return CTFEExp.cantexp;
3889 payload = &(*existingAE.elements)[index];
3890 oldval = *payload;
3892 else
3894 error(e.loc, "`%s` cannot be evaluated at compile time", e.toChars());
3895 return CTFEExp.cantexp;
3898 Type t1b = e1.type.toBasetype();
3899 bool wantCopy = t1b.baseElemOf().ty == Tstruct;
3901 if (auto ve = newval.isVectorExp())
3903 // Ensure ve is an array literal, and not a broadcast
3904 if (ve.e1.op == EXP.int64 || ve.e1.op == EXP.float64) // if broadcast
3906 UnionExp ue = void;
3907 Expression ex = interpretVectorToArray(&ue, ve);
3908 ve.e1 = (ex == ue.exp()) ? ue.copy() : ex;
3912 if (newval.op == EXP.structLiteral && oldval)
3914 assert(oldval.op == EXP.structLiteral || oldval.op == EXP.arrayLiteral || oldval.op == EXP.string_);
3915 newval = copyLiteral(newval).copy();
3916 assignInPlace(oldval, newval);
3918 else if (wantCopy && (e.op == EXP.assign || e.op == EXP.loweredAssignExp))
3920 // Currently postblit/destructor calls on static array are done
3921 // in the druntime internal functions so they don't appear in AST.
3922 // Therefore interpreter should handle them specially.
3924 assert(oldval);
3925 version (all) // todo: instead we can directly access to each elements of the slice
3927 newval = resolveSlice(newval);
3928 if (CTFEExp.isCantExp(newval))
3930 error(e.loc, "CTFE internal error: assignment `%s`", e.toChars());
3931 return CTFEExp.cantexp;
3934 assert(oldval.op == EXP.arrayLiteral);
3935 assert(newval.op == EXP.arrayLiteral);
3937 Expressions* oldelems = oldval.isArrayLiteralExp().elements;
3938 Expressions* newelems = newval.isArrayLiteralExp().elements;
3939 assert(oldelems.length == newelems.length);
3941 Type elemtype = oldval.type.nextOf();
3942 foreach (i, ref oldelem; *oldelems)
3944 Expression newelem = paintTypeOntoLiteral(elemtype, (*newelems)[i]);
3945 // https://issues.dlang.org/show_bug.cgi?id=9245
3946 if (e.e2.isLvalue())
3948 if (Expression ex = evaluatePostblit(istate, newelem))
3949 return ex;
3951 // https://issues.dlang.org/show_bug.cgi?id=13661
3952 if (Expression ex = evaluateDtor(istate, oldelem))
3953 return ex;
3954 oldelem = newelem;
3957 else
3959 // e1 has its own payload, so we have to create a new literal.
3960 if (wantCopy)
3961 newval = copyLiteral(newval).copy();
3963 if (t1b.ty == Tsarray && e.op == EXP.construct && e.e2.isLvalue())
3965 // https://issues.dlang.org/show_bug.cgi?id=9245
3966 if (Expression ex = evaluatePostblit(istate, newval))
3967 return ex;
3970 oldval = newval;
3973 if (vd)
3974 setValue(vd, oldval);
3975 else
3976 *payload = oldval;
3978 // Blit assignment should return the newly created value.
3979 if (e.op == EXP.blit)
3980 return oldval;
3982 return null;
3985 /*************
3986 * Deal with assignments of the form:
3987 * dest[] = newval
3988 * dest[low..upp] = newval
3989 * where newval has already been interpreted
3991 * This could be a slice assignment or a block assignment, and
3992 * dest could be either an array literal, or a string.
3994 * Returns EXP.cantExpression on failure. If there are no errors,
3995 * it returns aggregate[low..upp], except that as an optimisation,
3996 * if goal == CTFEGoal.Nothing, it will return NULL
3998 private Expression interpretAssignToSlice(UnionExp* pue, BinExp e, Expression e1, Expression newval, bool isBlockAssignment)
4000 //printf("interpretAssignToSlice(e: %s e1: %s newval: %s\n", e.toChars(), e1.toChars(), newval.toChars());
4002 dinteger_t lowerbound;
4003 dinteger_t upperbound;
4004 dinteger_t firstIndex;
4006 Expression aggregate;
4008 if (auto se = e1.isSliceExp())
4010 // ------------------------------
4011 // aggregate[] = newval
4012 // aggregate[low..upp] = newval
4013 // ------------------------------
4014 aggregate = interpretRegion(se.e1, istate);
4015 lowerbound = se.lwr ? se.lwr.toInteger() : 0;
4016 upperbound = se.upr ? se.upr.toInteger() : resolveArrayLength(aggregate);
4018 // Slice of a slice --> change the bounds
4019 if (auto oldse = aggregate.isSliceExp())
4021 aggregate = oldse.e1;
4022 firstIndex = lowerbound + oldse.lwr.toInteger();
4024 else
4025 firstIndex = lowerbound;
4027 else
4029 if (auto ale = e1.isArrayLiteralExp())
4031 lowerbound = 0;
4032 upperbound = ale.elements.length;
4034 else if (auto se = e1.isStringExp())
4036 lowerbound = 0;
4037 upperbound = se.len;
4039 else if (e1.op == EXP.null_)
4041 lowerbound = 0;
4042 upperbound = 0;
4044 else if (VectorExp ve = e1.isVectorExp())
4046 // ve is not handled but a proper error message is returned
4047 // this is to prevent https://issues.dlang.org/show_bug.cgi?id=20042
4048 lowerbound = 0;
4049 upperbound = ve.dim;
4051 else
4052 assert(0);
4054 aggregate = e1;
4055 firstIndex = lowerbound;
4057 if (upperbound == lowerbound)
4058 return newval;
4060 // For slice assignment, we check that the lengths match.
4061 if (!isBlockAssignment && e1.type.ty != Tpointer)
4063 const srclen = resolveArrayLength(newval);
4064 if (srclen != (upperbound - lowerbound))
4066 error(e.loc, "array length mismatch assigning `[0..%llu]` to `[%llu..%llu]`",
4067 ulong(srclen), ulong(lowerbound), ulong(upperbound));
4068 return CTFEExp.cantexp;
4072 if (auto existingSE = aggregate.isStringExp())
4074 if (existingSE.ownedByCtfe != OwnedBy.ctfe)
4076 error(e.loc, "cannot modify read-only string literal `%s`", existingSE.toChars());
4077 return CTFEExp.cantexp;
4080 if (auto se = newval.isSliceExp())
4082 auto aggr2 = se.e1;
4083 const srclower = se.lwr.toInteger();
4084 const srcupper = se.upr.toInteger();
4086 if (aggregate == aggr2 &&
4087 lowerbound < srcupper && srclower < upperbound)
4089 error(e.loc, "overlapping slice assignment `[%llu..%llu] = [%llu..%llu]`",
4090 ulong(lowerbound), ulong(upperbound), ulong(srclower), ulong(srcupper));
4091 return CTFEExp.cantexp;
4093 version (all) // todo: instead we can directly access to each elements of the slice
4095 Expression orignewval = newval;
4096 newval = resolveSlice(newval);
4097 if (CTFEExp.isCantExp(newval))
4099 error(e.loc, "CTFE internal error: slice `%s`", orignewval.toChars());
4100 return CTFEExp.cantexp;
4103 assert(newval.op != EXP.slice);
4105 if (auto se = newval.isStringExp())
4107 sliceAssignStringFromString(existingSE, se, cast(size_t)firstIndex);
4108 return newval;
4110 if (auto ale = newval.isArrayLiteralExp())
4112 /* Mixed slice: it was initialized as a string literal.
4113 * Now a slice of it is being set with an array literal.
4115 sliceAssignStringFromArrayLiteral(existingSE, ale, cast(size_t)firstIndex);
4116 return newval;
4119 // String literal block slice assign
4120 const value = cast(dchar)newval.toInteger();
4121 foreach (i; 0 .. upperbound - lowerbound)
4123 existingSE.setCodeUnit(cast(size_t)(i + firstIndex), value);
4125 if (goal == CTFEGoal.Nothing)
4126 return null; // avoid creating an unused literal
4127 auto retslice = ctfeEmplaceExp!SliceExp(e.loc, existingSE,
4128 ctfeEmplaceExp!IntegerExp(e.loc, firstIndex, Type.tsize_t),
4129 ctfeEmplaceExp!IntegerExp(e.loc, firstIndex + upperbound - lowerbound, Type.tsize_t));
4130 retslice.type = e.type;
4131 return interpret(pue, retslice, istate);
4133 if (auto existingAE = aggregate.isArrayLiteralExp())
4135 if (existingAE.ownedByCtfe != OwnedBy.ctfe)
4137 error(e.loc, "cannot modify read-only constant `%s`", existingAE.toChars());
4138 return CTFEExp.cantexp;
4141 if (newval.op == EXP.slice && !isBlockAssignment)
4143 auto se = newval.isSliceExp();
4144 auto aggr2 = se.e1;
4145 const srclower = se.lwr.toInteger();
4146 const srcupper = se.upr.toInteger();
4147 const wantCopy = (newval.type.toBasetype().nextOf().baseElemOf().ty == Tstruct);
4149 //printf("oldval = %p %s[%d..%u]\nnewval = %p %s[%llu..%llu] wantCopy = %d\n",
4150 // aggregate, aggregate.toChars(), lowerbound, upperbound,
4151 // aggr2, aggr2.toChars(), srclower, srcupper, wantCopy);
4152 if (wantCopy)
4154 // Currently overlapping for struct array is allowed.
4155 // The order of elements processing depends on the overlapping.
4156 // https://issues.dlang.org/show_bug.cgi?id=14024
4157 assert(aggr2.op == EXP.arrayLiteral);
4158 Expressions* oldelems = existingAE.elements;
4159 Expressions* newelems = aggr2.isArrayLiteralExp().elements;
4161 Type elemtype = aggregate.type.nextOf();
4162 bool needsPostblit = e.e2.isLvalue();
4164 if (aggregate == aggr2 && srclower < lowerbound && lowerbound < srcupper)
4166 // reverse order
4167 for (auto i = upperbound - lowerbound; 0 < i--;)
4169 Expression oldelem = (*oldelems)[cast(size_t)(i + firstIndex)];
4170 Expression newelem = (*newelems)[cast(size_t)(i + srclower)];
4171 newelem = copyLiteral(newelem).copy();
4172 newelem.type = elemtype;
4173 if (needsPostblit)
4175 if (Expression x = evaluatePostblit(istate, newelem))
4176 return x;
4178 if (Expression x = evaluateDtor(istate, oldelem))
4179 return x;
4180 (*oldelems)[cast(size_t)(lowerbound + i)] = newelem;
4183 else
4185 // normal order
4186 for (auto i = 0; i < upperbound - lowerbound; i++)
4188 Expression oldelem = (*oldelems)[cast(size_t)(i + firstIndex)];
4189 Expression newelem = (*newelems)[cast(size_t)(i + srclower)];
4190 newelem = copyLiteral(newelem).copy();
4191 newelem.type = elemtype;
4192 if (needsPostblit)
4194 if (Expression x = evaluatePostblit(istate, newelem))
4195 return x;
4197 if (Expression x = evaluateDtor(istate, oldelem))
4198 return x;
4199 (*oldelems)[cast(size_t)(lowerbound + i)] = newelem;
4203 //assert(0);
4204 return newval; // oldval?
4206 if (aggregate == aggr2 &&
4207 lowerbound < srcupper && srclower < upperbound)
4209 error(e.loc, "overlapping slice assignment `[%llu..%llu] = [%llu..%llu]`",
4210 ulong(lowerbound), ulong(upperbound), ulong(srclower), ulong(srcupper));
4211 return CTFEExp.cantexp;
4213 version (all) // todo: instead we can directly access to each elements of the slice
4215 Expression orignewval = newval;
4216 newval = resolveSlice(newval);
4217 if (CTFEExp.isCantExp(newval))
4219 error(e.loc, "CTFE internal error: slice `%s`", orignewval.toChars());
4220 return CTFEExp.cantexp;
4223 // no overlapping
4224 //length?
4225 assert(newval.op != EXP.slice);
4227 if (newval.op == EXP.string_ && !isBlockAssignment)
4229 /* Mixed slice: it was initialized as an array literal of chars/integers.
4230 * Now a slice of it is being set with a string.
4232 sliceAssignArrayLiteralFromString(existingAE, newval.isStringExp(), cast(size_t)firstIndex);
4233 return newval;
4235 if (newval.op == EXP.arrayLiteral && !isBlockAssignment)
4237 Expressions* oldelems = existingAE.elements;
4238 Expressions* newelems = newval.isArrayLiteralExp().elements;
4239 Type elemtype = existingAE.type.nextOf();
4240 bool needsPostblit = e.op != EXP.blit && e.e2.isLvalue();
4241 foreach (j, newelem; *newelems)
4243 newelem = paintTypeOntoLiteral(elemtype, newelem);
4244 if (needsPostblit)
4246 Expression x = evaluatePostblit(istate, newelem);
4247 if (exceptionOrCantInterpret(x))
4248 return x;
4250 (*oldelems)[cast(size_t)(j + firstIndex)] = newelem;
4252 return newval;
4255 /* Block assignment, initialization of static arrays
4256 * x[] = newval
4257 * x may be a multidimensional static array. (Note that this
4258 * only happens with array literals, never with strings).
4260 struct RecursiveBlock
4262 InterState* istate;
4263 Expression newval;
4264 bool refCopy;
4265 bool needsPostblit;
4266 bool needsDtor;
4268 Expression assignTo(ArrayLiteralExp ae)
4270 return assignTo(ae, 0, ae.elements.length);
4273 Expression assignTo(ArrayLiteralExp ae, size_t lwr, size_t upr)
4275 Expressions* w = ae.elements;
4276 assert(ae.type.ty == Tsarray || ae.type.ty == Tarray || ae.type.ty == Tpointer);
4277 bool directblk = (cast(TypeNext)ae.type).next.equivalent(newval.type);
4278 for (size_t k = lwr; k < upr; k++)
4280 if (!directblk && (*w)[k].op == EXP.arrayLiteral)
4282 // Multidimensional array block assign
4283 if (Expression ex = assignTo((*w)[k].isArrayLiteralExp()))
4284 return ex;
4286 else if (refCopy)
4288 (*w)[k] = newval;
4290 else if (!needsPostblit && !needsDtor)
4292 assignInPlace((*w)[k], newval);
4294 else
4296 Expression oldelem = (*w)[k];
4297 Expression tmpelem = needsDtor ? copyLiteral(oldelem).copy() : null;
4298 assignInPlace(oldelem, newval);
4299 if (needsPostblit)
4301 if (Expression ex = evaluatePostblit(istate, oldelem))
4302 return ex;
4304 if (needsDtor)
4306 // https://issues.dlang.org/show_bug.cgi?id=14860
4307 if (Expression ex = evaluateDtor(istate, tmpelem))
4308 return ex;
4312 return null;
4316 Type tn = newval.type.toBasetype();
4317 bool wantRef = (tn.ty == Tarray || isAssocArray(tn) || tn.ty == Tclass);
4318 bool cow = newval.op != EXP.structLiteral && newval.op != EXP.arrayLiteral && newval.op != EXP.string_;
4319 Type tb = tn.baseElemOf();
4320 StructDeclaration sd = (tb.ty == Tstruct ? (cast(TypeStruct)tb).sym : null);
4322 RecursiveBlock rb;
4323 rb.istate = istate;
4324 rb.newval = newval;
4325 rb.refCopy = wantRef || cow;
4326 rb.needsPostblit = sd && sd.postblit && e.op != EXP.blit && e.e2.isLvalue();
4327 rb.needsDtor = sd && sd.dtor && (e.op == EXP.assign || e.op == EXP.loweredAssignExp);
4328 if (Expression ex = rb.assignTo(existingAE, cast(size_t)lowerbound, cast(size_t)upperbound))
4329 return ex;
4331 if (goal == CTFEGoal.Nothing)
4332 return null; // avoid creating an unused literal
4333 auto retslice = ctfeEmplaceExp!SliceExp(e.loc, existingAE,
4334 ctfeEmplaceExp!IntegerExp(e.loc, firstIndex, Type.tsize_t),
4335 ctfeEmplaceExp!IntegerExp(e.loc, firstIndex + upperbound - lowerbound, Type.tsize_t));
4336 retslice.type = e.type;
4337 return interpret(pue, retslice, istate);
4340 error(e.loc, "slice operation `%s = %s` cannot be evaluated at compile time", e1.toChars(), newval.toChars());
4341 return CTFEExp.cantexp;
4344 override void visit(AssignExp e)
4346 interpretAssignCommon(e, null);
4349 override void visit(BinAssignExp e)
4351 switch (e.op)
4353 case EXP.addAssign:
4354 interpretAssignCommon(e, &Add);
4355 return;
4357 case EXP.minAssign:
4358 interpretAssignCommon(e, &Min);
4359 return;
4361 case EXP.concatenateAssign:
4362 case EXP.concatenateElemAssign:
4363 case EXP.concatenateDcharAssign:
4364 interpretAssignCommon(e, &ctfeCat);
4365 return;
4367 case EXP.mulAssign:
4368 interpretAssignCommon(e, &Mul);
4369 return;
4371 case EXP.divAssign:
4372 interpretAssignCommon(e, &Div);
4373 return;
4375 case EXP.modAssign:
4376 interpretAssignCommon(e, &Mod);
4377 return;
4379 case EXP.leftShiftAssign:
4380 interpretAssignCommon(e, &Shl);
4381 return;
4383 case EXP.rightShiftAssign:
4384 interpretAssignCommon(e, &Shr);
4385 return;
4387 case EXP.unsignedRightShiftAssign:
4388 interpretAssignCommon(e, &Ushr);
4389 return;
4391 case EXP.andAssign:
4392 interpretAssignCommon(e, &And);
4393 return;
4395 case EXP.orAssign:
4396 interpretAssignCommon(e, &Or);
4397 return;
4399 case EXP.xorAssign:
4400 interpretAssignCommon(e, &Xor);
4401 return;
4403 case EXP.powAssign:
4404 interpretAssignCommon(e, &Pow);
4405 return;
4407 default:
4408 assert(0);
4412 override void visit(PostExp e)
4414 debug (LOG)
4416 printf("%s PostExp::interpret() %s\n", e.loc.toChars(), e.toChars());
4418 if (e.op == EXP.plusPlus)
4419 interpretAssignCommon(e, &Add, 1);
4420 else
4421 interpretAssignCommon(e, &Min, 1);
4422 debug (LOG)
4424 if (CTFEExp.isCantExp(result))
4425 printf("PostExp::interpret() CANT\n");
4429 /* Return 1 if e is a p1 > p2 or p1 >= p2 pointer comparison;
4430 * -1 if e is a p1 < p2 or p1 <= p2 pointer comparison;
4431 * 0 otherwise
4433 static int isPointerCmpExp(Expression e, Expression* p1, Expression* p2)
4435 int ret = 1;
4436 while (e.op == EXP.not)
4438 ret *= -1;
4439 e = e.isNotExp().e1;
4441 switch (e.op)
4443 case EXP.lessThan:
4444 case EXP.lessOrEqual:
4445 ret *= -1;
4446 goto case; /+ fall through +/
4447 case EXP.greaterThan:
4448 case EXP.greaterOrEqual:
4449 *p1 = e.isBinExp().e1;
4450 *p2 = e.isBinExp().e2;
4451 if (!(isPointer((*p1).type) && isPointer((*p2).type)))
4452 ret = 0;
4453 break;
4455 default:
4456 ret = 0;
4457 break;
4459 return ret;
4462 /** If this is a four pointer relation, evaluate it, else return NULL.
4464 * This is an expression of the form (p1 > q1 && p2 < q2) or (p1 < q1 || p2 > q2)
4465 * where p1, p2 are expressions yielding pointers to memory block p,
4466 * and q1, q2 are expressions yielding pointers to memory block q.
4467 * This expression is valid even if p and q are independent memory
4468 * blocks and are therefore not normally comparable; the && form returns true
4469 * if [p1..p2] lies inside [q1..q2], and false otherwise; the || form returns
4470 * true if [p1..p2] lies outside [q1..q2], and false otherwise.
4472 * Within the expression, any ordering of p1, p2, q1, q2 is permissible;
4473 * the comparison operators can be any of >, <, <=, >=, provided that
4474 * both directions (p > q and p < q) are checked. Additionally the
4475 * relational sub-expressions can be negated, eg
4476 * (!(q1 < p1) && p2 <= q2) is valid.
4478 private void interpretFourPointerRelation(UnionExp* pue, BinExp e)
4480 assert(e.op == EXP.andAnd || e.op == EXP.orOr);
4482 /* It can only be an isInside expression, if both e1 and e2 are
4483 * directional pointer comparisons.
4484 * Note that this check can be made statically; it does not depends on
4485 * any runtime values. This allows a JIT implementation to compile a
4486 * special AndAndPossiblyInside, keeping the normal AndAnd case efficient.
4489 // Save the pointer expressions and the comparison directions,
4490 // so we can use them later.
4491 Expression p1 = null;
4492 Expression p2 = null;
4493 Expression p3 = null;
4494 Expression p4 = null;
4495 int dir1 = isPointerCmpExp(e.e1, &p1, &p2);
4496 int dir2 = isPointerCmpExp(e.e2, &p3, &p4);
4497 if (dir1 == 0 || dir2 == 0)
4499 result = null;
4500 return;
4503 //printf("FourPointerRelation %s\n", toChars());
4505 UnionExp ue1 = void;
4506 UnionExp ue2 = void;
4507 UnionExp ue3 = void;
4508 UnionExp ue4 = void;
4510 // Evaluate the first two pointers
4511 p1 = interpret(&ue1, p1, istate);
4512 if (exceptionOrCant(p1))
4513 return;
4514 p2 = interpret(&ue2, p2, istate);
4515 if (exceptionOrCant(p2))
4516 return;
4517 dinteger_t ofs1, ofs2;
4518 Expression agg1 = getAggregateFromPointer(p1, &ofs1);
4519 Expression agg2 = getAggregateFromPointer(p2, &ofs2);
4521 if (!pointToSameMemoryBlock(agg1, agg2) && agg1.op != EXP.null_ && agg2.op != EXP.null_)
4523 // Here it is either CANT_INTERPRET,
4524 // or an IsInside comparison returning false.
4525 p3 = interpret(&ue3, p3, istate);
4526 if (CTFEExp.isCantExp(p3))
4527 return;
4528 // Note that it is NOT legal for it to throw an exception!
4529 Expression except = null;
4530 if (exceptionOrCantInterpret(p3))
4531 except = p3;
4532 else
4534 p4 = interpret(&ue4, p4, istate);
4535 if (CTFEExp.isCantExp(p4))
4537 result = p4;
4538 return;
4540 if (exceptionOrCantInterpret(p4))
4541 except = p4;
4543 if (except)
4545 error(e.loc, "comparison `%s` of pointers to unrelated memory blocks remains indeterminate at compile time because exception `%s` was thrown while evaluating `%s`", e.e1.toChars(), except.toChars(), e.e2.toChars());
4546 result = CTFEExp.cantexp;
4547 return;
4549 dinteger_t ofs3, ofs4;
4550 Expression agg3 = getAggregateFromPointer(p3, &ofs3);
4551 Expression agg4 = getAggregateFromPointer(p4, &ofs4);
4552 // The valid cases are:
4553 // p1 > p2 && p3 > p4 (same direction, also for < && <)
4554 // p1 > p2 && p3 < p4 (different direction, also < && >)
4555 // Changing any > into >= doesn't affect the result
4556 if ((dir1 == dir2 && pointToSameMemoryBlock(agg1, agg4) && pointToSameMemoryBlock(agg2, agg3)) ||
4557 (dir1 != dir2 && pointToSameMemoryBlock(agg1, agg3) && pointToSameMemoryBlock(agg2, agg4)))
4559 // it's a legal two-sided comparison
4560 emplaceExp!(IntegerExp)(pue, e.loc, (e.op == EXP.andAnd) ? 0 : 1, e.type);
4561 result = pue.exp();
4562 return;
4564 // It's an invalid four-pointer comparison. Either the second
4565 // comparison is in the same direction as the first, or else
4566 // more than two memory blocks are involved (either two independent
4567 // invalid comparisons are present, or else agg3 == agg4).
4568 error(e.loc, "comparison `%s` of pointers to unrelated memory blocks is indeterminate at compile time, even when combined with `%s`.", e.e1.toChars(), e.e2.toChars());
4569 result = CTFEExp.cantexp;
4570 return;
4572 // The first pointer expression didn't need special treatment, so we
4573 // we need to interpret the entire expression exactly as a normal && or ||.
4574 // This is easy because we haven't evaluated e2 at all yet, and we already
4575 // know it will return a bool.
4576 // But we mustn't evaluate the pointer expressions in e1 again, in case
4577 // they have side-effects.
4578 bool nott = false;
4579 Expression ex = e.e1;
4580 while (1)
4582 if (auto ne = ex.isNotExp())
4584 nott = !nott;
4585 ex = ne.e1;
4587 else
4588 break;
4591 /** Negate relational operator, eg >= becomes <
4592 * Params:
4593 * op = comparison operator to negate
4594 * Returns:
4595 * negate operator
4597 static EXP negateRelation(EXP op) pure
4599 switch (op)
4601 case EXP.greaterOrEqual: op = EXP.lessThan; break;
4602 case EXP.greaterThan: op = EXP.lessOrEqual; break;
4603 case EXP.lessOrEqual: op = EXP.greaterThan; break;
4604 case EXP.lessThan: op = EXP.greaterOrEqual; break;
4605 default: assert(0);
4607 return op;
4610 const EXP cmpop = nott ? negateRelation(ex.op) : ex.op;
4611 const cmp = comparePointers(cmpop, agg1, ofs1, agg2, ofs2);
4612 // We already know this is a valid comparison.
4613 assert(cmp >= 0);
4614 if (e.op == EXP.andAnd && cmp == 1 || e.op == EXP.orOr && cmp == 0)
4616 result = interpret(pue, e.e2, istate);
4617 return;
4619 emplaceExp!(IntegerExp)(pue, e.loc, (e.op == EXP.andAnd) ? 0 : 1, e.type);
4620 result = pue.exp();
4623 override void visit(LogicalExp e)
4625 debug (LOG)
4627 printf("%s LogicalExp::interpret() %s\n", e.loc.toChars(), e.toChars());
4629 // Check for an insidePointer expression, evaluate it if so
4630 interpretFourPointerRelation(pue, e);
4631 if (result)
4632 return;
4634 UnionExp ue1 = void;
4635 result = interpret(&ue1, e.e1, istate);
4636 if (exceptionOrCant(result))
4637 return;
4639 bool res;
4640 const andand = e.op == EXP.andAnd;
4641 if (andand ? result.toBool().hasValue(false) : isTrueBool(result))
4642 res = !andand;
4643 else if (andand ? isTrueBool(result) : result.toBool().hasValue(false))
4645 UnionExp ue2 = void;
4646 result = interpret(&ue2, e.e2, istate);
4647 if (exceptionOrCant(result))
4648 return;
4649 if (result.op == EXP.voidExpression)
4651 assert(e.type.ty == Tvoid);
4652 result = null;
4653 return;
4655 if (result.toBool().hasValue(false))
4656 res = false;
4657 else if (isTrueBool(result))
4658 res = true;
4659 else
4661 error(e.loc, "`%s` does not evaluate to a `bool`", result.toChars());
4662 result = CTFEExp.cantexp;
4663 return;
4666 else
4668 error(e.loc, "`%s` cannot be interpreted as a `bool`", result.toChars());
4669 result = CTFEExp.cantexp;
4670 return;
4672 incUsageCtfe(istate, e.e2.loc);
4674 if (goal != CTFEGoal.Nothing)
4676 if (e.type.equals(Type.tbool))
4677 result = IntegerExp.createBool(res);
4678 else
4680 emplaceExp!(IntegerExp)(pue, e.loc, res, e.type);
4681 result = pue.exp();
4687 // Print a stack trace, starting from callingExp which called fd.
4688 // To shorten the stack trace, try to detect recursion.
4689 private void showCtfeBackTrace(CallExp callingExp, FuncDeclaration fd)
4691 if (ctfeGlobals.stackTraceCallsToSuppress > 0)
4693 --ctfeGlobals.stackTraceCallsToSuppress;
4694 return;
4696 errorSupplemental(callingExp.loc, "called from here: `%s`", callingExp.toChars());
4697 // Quit if it's not worth trying to compress the stack trace
4698 if (ctfeGlobals.callDepth < 6 || global.params.v.verbose)
4699 return;
4700 // Recursion happens if the current function already exists in the call stack.
4701 int numToSuppress = 0;
4702 int recurseCount = 0;
4703 int depthSoFar = 0;
4704 InterState* lastRecurse = istate;
4705 for (InterState* cur = istate; cur; cur = cur.caller)
4707 if (cur.fd == fd)
4709 ++recurseCount;
4710 numToSuppress = depthSoFar;
4711 lastRecurse = cur;
4713 ++depthSoFar;
4715 // We need at least three calls to the same function, to make compression worthwhile
4716 if (recurseCount < 2)
4717 return;
4718 // We found a useful recursion. Print all the calls involved in the recursion
4719 errorSupplemental(fd.loc, "%d recursive calls to function `%s`", recurseCount, fd.toChars());
4720 for (InterState* cur = istate; cur.fd != fd; cur = cur.caller)
4722 errorSupplemental(cur.fd.loc, "recursively called from function `%s`", cur.fd.toChars());
4724 // We probably didn't enter the recursion in this function.
4725 // Go deeper to find the real beginning.
4726 InterState* cur = istate;
4727 while (lastRecurse.caller && cur.fd == lastRecurse.caller.fd)
4729 cur = cur.caller;
4730 lastRecurse = lastRecurse.caller;
4731 ++numToSuppress;
4733 ctfeGlobals.stackTraceCallsToSuppress = numToSuppress;
4736 override void visit(CallExp e)
4738 debug (LOG)
4740 printf("%s CallExp::interpret() %s\n", e.loc.toChars(), e.toChars());
4742 Expression pthis = null;
4743 FuncDeclaration fd = null;
4745 Expression ecall = interpretRegion(e.e1, istate);
4746 if (exceptionOrCant(ecall))
4747 return;
4749 if (auto dve = ecall.isDotVarExp())
4751 // Calling a member function
4752 pthis = dve.e1;
4753 fd = dve.var.isFuncDeclaration();
4754 assert(fd);
4756 if (auto dte = pthis.isDotTypeExp())
4757 pthis = dte.e1;
4759 else if (auto ve = ecall.isVarExp())
4761 fd = ve.var.isFuncDeclaration();
4762 assert(fd);
4764 // If `_d_HookTraceImpl` is found, resolve the underlying hook and replace `e` and `fd` with it.
4765 removeHookTraceImpl(e, fd);
4767 if (fd.ident == Id.__ArrayPostblit || fd.ident == Id.__ArrayDtor)
4769 assert(e.arguments.length == 1);
4770 Expression ea = (*e.arguments)[0];
4771 // printf("1 ea = %s %s\n", ea.type.toChars(), ea.toChars());
4772 if (auto se = ea.isSliceExp())
4773 ea = se.e1;
4774 if (auto ce = ea.isCastExp())
4775 ea = ce.e1;
4777 // printf("2 ea = %s, %s %s\n", ea.type.toChars(), EXPtoString(ea.op).ptr, ea.toChars());
4778 if (ea.op == EXP.variable || ea.op == EXP.symbolOffset)
4779 result = getVarExp(e.loc, istate, (cast(SymbolExp)ea).var, CTFEGoal.RValue);
4780 else if (auto ae = ea.isAddrExp())
4781 result = interpretRegion(ae.e1, istate);
4783 // https://issues.dlang.org/show_bug.cgi?id=18871
4784 // https://issues.dlang.org/show_bug.cgi?id=18819
4785 else if (auto ale = ea.isArrayLiteralExp())
4786 result = interpretRegion(ale, istate);
4788 else
4789 assert(0);
4790 if (CTFEExp.isCantExp(result))
4791 return;
4793 if (fd.ident == Id.__ArrayPostblit)
4794 result = evaluatePostblit(istate, result);
4795 else
4796 result = evaluateDtor(istate, result);
4797 if (!result)
4798 result = CTFEExp.voidexp;
4799 return;
4801 else if (isArrayConstruction(fd.ident))
4803 // In expressionsem.d, `T[x] ea = eb;` was lowered to:
4804 // `_d_array{,set}ctor(ea[], eb[]);`.
4805 // The following code will rewrite it back to `ea = eb` and
4806 // then interpret that expression.
4808 if (fd.ident == Id._d_arrayctor)
4809 assert(e.arguments.length == 3);
4810 else
4811 assert(e.arguments.length == 2);
4813 Expression ea = (*e.arguments)[0];
4814 if (ea.isCastExp)
4815 ea = ea.isCastExp.e1;
4817 Expression eb = (*e.arguments)[1];
4818 if (eb.isCastExp() && fd.ident == Id._d_arrayctor)
4819 eb = eb.isCastExp.e1;
4821 ConstructExp ce = new ConstructExp(e.loc, ea, eb);
4822 ce.type = ea.type;
4824 ce.type = ea.type;
4825 result = interpret(ce, istate);
4827 return;
4829 else if (fd.ident == Id._d_arrayappendT || fd.ident == Id._d_arrayappendTTrace)
4831 // In expressionsem.d `ea ~= eb` was lowered to `_d_arrayappendT{,Trace}({file, line, funcname}, ea, eb);`.
4832 // The following code will rewrite it back to `ea ~= eb` and then interpret that expression.
4833 Expression lhs, rhs;
4835 if (fd.ident == Id._d_arrayappendT)
4837 assert(e.arguments.length == 2);
4838 lhs = (*e.arguments)[0];
4839 rhs = (*e.arguments)[1];
4841 else
4843 assert(e.arguments.length == 5);
4844 lhs = (*e.arguments)[3];
4845 rhs = (*e.arguments)[4];
4848 auto cae = new CatAssignExp(e.loc, lhs, rhs);
4849 cae.type = e.type;
4851 result = interpretRegion(cae, istate, CTFEGoal.LValue);
4852 return;
4854 else if (fd.ident == Id._d_arrayappendcTX)
4855 assert(0, "CTFE cannot interpret _d_arrayappendcTX!");
4857 else if (auto soe = ecall.isSymOffExp())
4859 fd = soe.var.isFuncDeclaration();
4860 assert(fd && soe.offset == 0);
4862 else if (auto de = ecall.isDelegateExp())
4864 // Calling a delegate
4865 fd = de.func;
4866 pthis = de.e1;
4868 // Special handling for: &nestedfunc --> DelegateExp(VarExp(nestedfunc), nestedfunc)
4869 if (auto ve = pthis.isVarExp())
4870 if (ve.var == fd)
4871 pthis = null; // context is not necessary for CTFE
4873 else if (auto fe = ecall.isFuncExp())
4875 // Calling a delegate literal
4876 fd = fe.fd;
4878 else
4880 // delegate.funcptr()
4881 // others
4882 error(e.loc, "cannot call `%s` at compile time", e.toChars());
4883 result = CTFEExp.cantexp;
4884 return;
4886 if (!fd)
4888 error(e.loc, "CTFE internal error: cannot evaluate `%s` at compile time", e.toChars());
4889 result = CTFEExp.cantexp;
4890 return;
4892 if (pthis)
4894 // Member function call
4896 // Currently this is satisfied because closure is not yet supported.
4897 assert(!fd.isNested() || fd.needThis());
4899 if (pthis.op == EXP.typeid_)
4901 error(pthis.loc, "static variable `%s` cannot be read at compile time", pthis.toChars());
4902 result = CTFEExp.cantexp;
4903 return;
4905 assert(pthis);
4907 if (pthis.op == EXP.null_)
4909 assert(pthis.type.toBasetype().ty == Tclass);
4910 error(e.loc, "function call through null class reference `%s`", pthis.toChars());
4911 result = CTFEExp.cantexp;
4912 return;
4915 assert(pthis.op == EXP.structLiteral || pthis.op == EXP.classReference || pthis.op == EXP.type);
4917 if (fd.isVirtual() && !e.directcall)
4919 // Make a virtual function call.
4920 // Get the function from the vtable of the original class
4921 ClassDeclaration cd = pthis.isClassReferenceExp().originalClass();
4923 // We can't just use the vtable index to look it up, because
4924 // vtables for interfaces don't get populated until the glue layer.
4925 fd = cd.findFunc(fd.ident, fd.type.isTypeFunction());
4926 assert(fd);
4930 if (fd && fd.semanticRun >= PASS.semantic3done && fd.hasSemantic3Errors())
4932 error(e.loc, "CTFE failed because of previous errors in `%s`", fd.toChars());
4933 result = CTFEExp.cantexp;
4934 return;
4937 // Check for built-in functions
4938 result = evaluateIfBuiltin(pue, istate, e.loc, fd, e.arguments, pthis);
4939 if (result)
4940 return;
4942 if (!fd.fbody)
4944 error(e.loc, "`%s` cannot be interpreted at compile time, because it has no available source code", fd.toChars());
4945 result = CTFEExp.showcontext;
4946 return;
4949 result = interpretFunction(pue, fd, istate, e.arguments, pthis);
4950 if (result.op == EXP.voidExpression)
4951 return;
4952 if (!exceptionOrCantInterpret(result))
4954 if (goal != CTFEGoal.LValue) // Peel off CTFE reference if it's unnecessary
4956 if (result == pue.exp())
4957 result = pue.copy();
4958 result = interpret(pue, result, istate);
4961 if (!exceptionOrCantInterpret(result))
4963 result = paintTypeOntoLiteral(pue, e.type, result);
4964 result.loc = e.loc;
4966 else if (CTFEExp.isCantExp(result) && !global.gag)
4967 showCtfeBackTrace(e, fd); // Print a stack trace.
4970 override void visit(CommaExp e)
4972 /****************************************
4973 * Find the first non-comma expression.
4974 * Params:
4975 * e = Expressions connected by commas
4976 * Returns:
4977 * left-most non-comma expression
4979 static inout(Expression) firstComma(inout Expression e)
4981 Expression ex = cast()e;
4982 while (ex.op == EXP.comma)
4983 ex = (cast(CommaExp)ex).e1;
4984 return cast(inout)ex;
4988 debug (LOG)
4990 printf("%s CommaExp::interpret() %s\n", e.loc.toChars(), e.toChars());
4993 bool isNewThrowableHook()
4995 auto de = e.e1.isDeclarationExp();
4996 if (de is null)
4997 return false;
4999 auto vd = de.declaration.isVarDeclaration();
5000 if (vd is null)
5001 return false;
5003 auto ei = vd._init.isExpInitializer();
5004 if (ei is null)
5005 return false;
5007 auto ce = ei.exp.isConstructExp();
5008 if (ce is null)
5009 return false;
5011 return isRuntimeHook(ce.e2, Id._d_newThrowable) !is null;
5014 if (auto ce = isRuntimeHook(e.e1, Id._d_arrayappendcTX))
5016 // In expressionsem.d `arr ~= elem` was lowered to
5017 // `_d_arrayappendcTX(arr, elem), arr[arr.length - 1] = elem, elem;`.
5018 // The following code will rewrite it back to `arr ~= elem`
5019 // and then interpret that expression.
5020 assert(ce.arguments.length == 2);
5022 auto arr = (*ce.arguments)[0];
5023 auto elem = e.e2.isConstructExp().e2;
5024 assert(elem);
5026 auto cae = new CatAssignExp(e.loc, arr, elem);
5027 cae.type = arr.type;
5029 result = interpret(cae, istate);
5030 return;
5032 else if (isNewThrowableHook())
5034 // In expressionsem.d `throw new Exception(args)` was lowered to
5035 // `throw (tmp = _d_newThrowable!Exception(), tmp.ctor(args), tmp)`.
5036 // The following code will rewrite it back to `throw new Exception(args)`
5037 // and then interpret this expression instead.
5038 auto ce = e.e2.isCallExp();
5039 assert(ce);
5041 auto ne = new NewExp(e.loc, null, e.type, ce.arguments);
5042 ne.type = e.e1.type;
5044 result = interpret(ne, istate);
5045 return;
5048 // If it creates a variable, and there's no context for
5049 // the variable to be created in, we need to create one now.
5050 InterState istateComma;
5051 if (!istate && firstComma(e.e1).op == EXP.declaration)
5053 ctfeGlobals.stack.startFrame(null);
5054 istate = &istateComma;
5057 void endTempStackFrame()
5059 // If we created a temporary stack frame, end it now.
5060 if (istate == &istateComma)
5061 ctfeGlobals.stack.endFrame();
5064 result = CTFEExp.cantexp;
5066 // If the comma returns a temporary variable, it needs to be an lvalue
5067 // (this is particularly important for struct constructors)
5068 if (e.e1.op == EXP.declaration &&
5069 e.e2.op == EXP.variable &&
5070 e.e1.isDeclarationExp().declaration == e.e2.isVarExp().var &&
5071 e.e2.isVarExp().var.storage_class & STC.ctfe)
5073 VarExp ve = e.e2.isVarExp();
5074 VarDeclaration v = ve.var.isVarDeclaration();
5075 ctfeGlobals.stack.push(v);
5076 if (!v._init && !getValue(v))
5078 setValue(v, copyLiteral(v.type.defaultInitLiteral(e.loc)).copy());
5080 if (!getValue(v))
5082 Expression newval = v._init.initializerToExpression();
5083 // Bug 4027. Copy constructors are a weird case where the
5084 // initializer is a void function (the variable is modified
5085 // through a reference parameter instead).
5086 newval = interpretRegion(newval, istate);
5087 if (exceptionOrCant(newval))
5088 return endTempStackFrame();
5089 if (newval.op != EXP.voidExpression)
5091 // v isn't necessarily null.
5092 setValueWithoutChecking(v, copyLiteral(newval).copy());
5096 else
5098 UnionExp ue = void;
5099 auto e1 = interpret(&ue, e.e1, istate, CTFEGoal.Nothing);
5100 if (exceptionOrCant(e1))
5101 return endTempStackFrame();
5103 result = interpret(pue, e.e2, istate, goal);
5104 return endTempStackFrame();
5107 override void visit(CondExp e)
5109 debug (LOG)
5111 printf("%s CondExp::interpret() %s\n", e.loc.toChars(), e.toChars());
5113 UnionExp uecond = void;
5114 Expression econd;
5115 econd = interpret(&uecond, e.econd, istate);
5116 if (exceptionOrCant(econd))
5117 return;
5119 if (isPointer(e.econd.type))
5121 if (econd.op != EXP.null_)
5123 econd = IntegerExp.createBool(true);
5127 if (isTrueBool(econd))
5129 result = interpret(pue, e.e1, istate, goal);
5130 incUsageCtfe(istate, e.e1.loc);
5132 else if (econd.toBool().hasValue(false))
5134 result = interpret(pue, e.e2, istate, goal);
5135 incUsageCtfe(istate, e.e2.loc);
5137 else
5139 error(e.loc, "`%s` does not evaluate to boolean result at compile time", e.econd.toChars());
5140 result = CTFEExp.cantexp;
5144 override void visit(ArrayLengthExp e)
5146 debug (LOG)
5148 printf("%s ArrayLengthExp::interpret() %s\n", e.loc.toChars(), e.toChars());
5150 UnionExp ue1;
5151 Expression e1 = interpret(&ue1, e.e1, istate);
5152 assert(e1);
5153 if (exceptionOrCant(e1))
5154 return;
5155 if (e1.op != EXP.string_ && e1.op != EXP.arrayLiteral && e1.op != EXP.slice && e1.op != EXP.null_)
5157 error(e.loc, "`%s` cannot be evaluated at compile time", e.toChars());
5158 result = CTFEExp.cantexp;
5159 return;
5161 emplaceExp!(IntegerExp)(pue, e.loc, resolveArrayLength(e1), e.type);
5162 result = pue.exp();
5166 * Interpret the vector expression as an array literal.
5167 * Params:
5168 * pue = non-null pointer to temporary storage that can be used to store the return value
5169 * e = Expression to interpret
5170 * Returns:
5171 * resulting array literal or 'e' if unable to interpret
5173 static Expression interpretVectorToArray(UnionExp* pue, VectorExp e)
5175 if (auto ale = e.e1.isArrayLiteralExp())
5176 return ale; // it's already an array literal
5177 if (e.e1.op == EXP.int64 || e.e1.op == EXP.float64)
5179 // Convert literal __vector(int) -> __vector([array])
5180 auto elements = new Expressions(e.dim);
5181 foreach (ref element; *elements)
5182 element = copyLiteral(e.e1).copy();
5183 auto type = (e.type.ty == Tvector) ? e.type.isTypeVector().basetype : e.type.isTypeSArray();
5184 assert(type);
5185 emplaceExp!(ArrayLiteralExp)(pue, e.loc, type, elements);
5186 auto ale = pue.exp().isArrayLiteralExp();
5187 ale.ownedByCtfe = OwnedBy.ctfe;
5188 return ale;
5190 return e;
5193 override void visit(VectorExp e)
5195 debug (LOG)
5197 printf("%s VectorExp::interpret() %s\n", e.loc.toChars(), e.toChars());
5199 if (e.ownedByCtfe >= OwnedBy.ctfe) // We've already interpreted all the elements
5201 result = e;
5202 return;
5204 Expression e1 = interpret(pue, e.e1, istate);
5205 assert(e1);
5206 if (exceptionOrCant(e1))
5207 return;
5208 if (e1.op != EXP.arrayLiteral && e1.op != EXP.int64 && e1.op != EXP.float64)
5210 error(e.loc, "`%s` cannot be evaluated at compile time", e.toChars());
5211 result = CTFEExp.cantexp;
5212 return;
5214 if (e1 == pue.exp())
5215 e1 = pue.copy();
5216 emplaceExp!(VectorExp)(pue, e.loc, e1, e.to);
5217 auto ve = pue.exp().isVectorExp();
5218 ve.type = e.type;
5219 ve.dim = e.dim;
5220 ve.ownedByCtfe = OwnedBy.ctfe;
5221 result = ve;
5224 override void visit(VectorArrayExp e)
5226 debug (LOG)
5228 printf("%s VectorArrayExp::interpret() %s\n", e.loc.toChars(), e.toChars());
5230 Expression e1 = interpret(pue, e.e1, istate);
5231 assert(e1);
5232 if (exceptionOrCant(e1))
5233 return;
5234 if (auto ve = e1.isVectorExp())
5236 result = interpretVectorToArray(pue, ve);
5237 if (result.op != EXP.vector)
5238 return;
5240 error(e.loc, "`%s` cannot be evaluated at compile time", e.toChars());
5241 result = CTFEExp.cantexp;
5244 override void visit(DelegatePtrExp e)
5246 debug (LOG)
5248 printf("%s DelegatePtrExp::interpret() %s\n", e.loc.toChars(), e.toChars());
5250 Expression e1 = interpret(pue, e.e1, istate);
5251 assert(e1);
5252 if (exceptionOrCant(e1))
5253 return;
5254 error(e.loc, "`%s` cannot be evaluated at compile time", e.toChars());
5255 result = CTFEExp.cantexp;
5258 override void visit(DelegateFuncptrExp e)
5260 debug (LOG)
5262 printf("%s DelegateFuncptrExp::interpret() %s\n", e.loc.toChars(), e.toChars());
5264 Expression e1 = interpret(pue, e.e1, istate);
5265 assert(e1);
5266 if (exceptionOrCant(e1))
5267 return;
5268 error(e.loc, "`%s` cannot be evaluated at compile time", e.toChars());
5269 result = CTFEExp.cantexp;
5272 static bool resolveIndexing(IndexExp e, InterState* istate, Expression* pagg, uinteger_t* pidx, bool modify)
5274 assert(e.e1.type.toBasetype().ty != Taarray);
5276 if (e.e1.type.toBasetype().ty == Tpointer)
5278 // Indexing a pointer. Note that there is no $ in this case.
5279 Expression e1 = interpretRegion(e.e1, istate);
5280 if (exceptionOrCantInterpret(e1))
5281 return false;
5283 Expression e2 = interpretRegion(e.e2, istate);
5284 if (exceptionOrCantInterpret(e2))
5285 return false;
5286 sinteger_t indx = e2.toInteger();
5288 dinteger_t ofs;
5289 Expression agg = getAggregateFromPointer(e1, &ofs);
5291 if (agg.op == EXP.null_)
5293 error(e.loc, "cannot index through null pointer `%s`", e.e1.toChars());
5294 return false;
5296 if (agg.op == EXP.int64)
5298 error(e.loc, "cannot index through invalid pointer `%s` of value `%s`", e.e1.toChars(), e1.toChars());
5299 return false;
5301 // Pointer to a non-array variable
5302 if (agg.op == EXP.symbolOffset)
5304 error(e.loc, "mutable variable `%s` cannot be %s at compile time, even through a pointer", cast(char*)(modify ? "modified" : "read"), agg.isSymOffExp().var.toChars());
5305 return false;
5308 if (agg.op == EXP.arrayLiteral || agg.op == EXP.string_)
5310 dinteger_t len = resolveArrayLength(agg);
5311 if (ofs + indx >= len)
5313 error(e.loc, "pointer index `[%lld]` exceeds allocated memory block `[0..%lld]`", ofs + indx, len);
5314 return false;
5317 else
5319 if (ofs + indx != 0)
5321 error(e.loc, "pointer index `[%lld]` lies outside memory block `[0..1]`", ofs + indx);
5322 return false;
5325 *pagg = agg;
5326 *pidx = ofs + indx;
5327 return true;
5330 Expression e1 = interpretRegion(e.e1, istate);
5331 if (exceptionOrCantInterpret(e1))
5332 return false;
5333 if (e1.op == EXP.null_)
5335 error(e.loc, "cannot index null array `%s`", e.e1.toChars());
5336 return false;
5338 if (auto ve = e1.isVectorExp())
5340 UnionExp ue = void;
5341 e1 = interpretVectorToArray(&ue, ve);
5342 e1 = (e1 == ue.exp()) ? ue.copy() : e1;
5345 // Set the $ variable, and find the array literal to modify
5346 dinteger_t len;
5347 if (e1.op == EXP.variable && e1.type.toBasetype().ty == Tsarray)
5348 len = e1.type.toBasetype().isTypeSArray().dim.toInteger();
5349 else
5351 if (e1.op != EXP.arrayLiteral && e1.op != EXP.string_ && e1.op != EXP.slice && e1.op != EXP.vector)
5353 error(e.loc, "cannot determine length of `%s` at compile time", e.e1.toChars());
5354 return false;
5356 len = resolveArrayLength(e1);
5359 if (e.lengthVar)
5361 Expression dollarExp = ctfeEmplaceExp!IntegerExp(e.loc, len, Type.tsize_t);
5362 ctfeGlobals.stack.push(e.lengthVar);
5363 setValue(e.lengthVar, dollarExp);
5365 Expression e2 = interpretRegion(e.e2, istate);
5366 if (e.lengthVar)
5367 ctfeGlobals.stack.pop(e.lengthVar); // $ is defined only inside []
5368 if (exceptionOrCantInterpret(e2))
5369 return false;
5370 if (e2.op != EXP.int64)
5372 error(e.loc, "CTFE internal error: non-integral index `[%s]`", e.e2.toChars());
5373 return false;
5376 if (auto se = e1.isSliceExp())
5378 // Simplify index of slice: agg[lwr..upr][indx] --> agg[indx']
5379 uinteger_t index = e2.toInteger();
5380 uinteger_t ilwr = se.lwr.toInteger();
5381 uinteger_t iupr = se.upr.toInteger();
5383 if (index > iupr - ilwr)
5385 error(e.loc, "index %llu exceeds array length %llu", index, iupr - ilwr);
5386 return false;
5388 *pagg = e1.isSliceExp().e1;
5389 *pidx = index + ilwr;
5391 else
5393 *pagg = e1;
5394 *pidx = e2.toInteger();
5395 if (len <= *pidx)
5397 error(e.loc, "array index %lld is out of bounds `[0..%lld]`", *pidx, len);
5398 return false;
5401 return true;
5404 override void visit(IndexExp e)
5406 debug (LOG)
5408 printf("%s IndexExp::interpret() %s, goal = %d\n", e.loc.toChars(), e.toChars(), goal);
5410 if (e.e1.type.toBasetype().ty == Tpointer)
5412 Expression agg;
5413 uinteger_t indexToAccess;
5414 if (!resolveIndexing(e, istate, &agg, &indexToAccess, false))
5416 result = CTFEExp.cantexp;
5417 return;
5419 if (agg.op == EXP.arrayLiteral || agg.op == EXP.string_)
5421 if (goal == CTFEGoal.LValue)
5423 // if we need a reference, IndexExp shouldn't be interpreting
5424 // the expression to a value, it should stay as a reference
5425 emplaceExp!(IndexExp)(pue, e.loc, agg, ctfeEmplaceExp!IntegerExp(e.e2.loc, indexToAccess, e.e2.type));
5426 result = pue.exp();
5427 result.type = e.type;
5428 return;
5430 result = ctfeIndex(pue, e.loc, e.type, agg, indexToAccess);
5431 return;
5433 else
5435 assert(indexToAccess == 0);
5436 result = interpretRegion(agg, istate, goal);
5437 if (exceptionOrCant(result))
5438 return;
5439 result = paintTypeOntoLiteral(pue, e.type, result);
5440 return;
5444 if (e.e1.type.toBasetype().ty == Taarray)
5446 Expression e1 = interpretRegion(e.e1, istate);
5447 if (exceptionOrCant(e1))
5448 return;
5449 if (e1.op == EXP.null_)
5451 if (goal == CTFEGoal.LValue && e1.type.ty == Taarray && e.modifiable)
5453 assert(0); // does not reach here?
5455 error(e.loc, "cannot index null array `%s`", e.e1.toChars());
5456 result = CTFEExp.cantexp;
5457 return;
5459 Expression e2 = interpretRegion(e.e2, istate);
5460 if (exceptionOrCant(e2))
5461 return;
5463 if (goal == CTFEGoal.LValue)
5465 // Pointer or reference of a scalar type
5466 if (e1 == e.e1 && e2 == e.e2)
5467 result = e;
5468 else
5470 emplaceExp!(IndexExp)(pue, e.loc, e1, e2);
5471 result = pue.exp();
5472 result.type = e.type;
5474 return;
5477 assert(e1.op == EXP.assocArrayLiteral);
5478 UnionExp e2tmp = void;
5479 e2 = resolveSlice(e2, &e2tmp);
5480 result = findKeyInAA(e.loc, e1.isAssocArrayLiteralExp(), e2);
5481 if (!result)
5483 error(e.loc, "key `%s` not found in associative array `%s`", e2.toChars(), e.e1.toChars());
5484 result = CTFEExp.cantexp;
5486 return;
5489 Expression agg;
5490 uinteger_t indexToAccess;
5491 if (!resolveIndexing(e, istate, &agg, &indexToAccess, false))
5493 result = CTFEExp.cantexp;
5494 return;
5497 if (goal == CTFEGoal.LValue)
5499 Expression e2 = ctfeEmplaceExp!IntegerExp(e.e2.loc, indexToAccess, Type.tsize_t);
5500 emplaceExp!(IndexExp)(pue, e.loc, agg, e2);
5501 result = pue.exp();
5502 result.type = e.type;
5503 return;
5506 result = ctfeIndex(pue, e.loc, e.type, agg, indexToAccess);
5507 if (exceptionOrCant(result))
5508 return;
5509 if (result.op == EXP.void_)
5511 error(e.loc, "`%s` is used before initialized", e.toChars());
5512 errorSupplemental(result.loc, "originally uninitialized here");
5513 result = CTFEExp.cantexp;
5514 return;
5516 if (result == pue.exp())
5517 result = result.copy();
5520 override void visit(SliceExp e)
5522 debug (LOG)
5524 printf("%s SliceExp::interpret() %s\n", e.loc.toChars(), e.toChars());
5526 if (e.e1.type.toBasetype().ty == Tpointer)
5528 // Slicing a pointer. Note that there is no $ in this case.
5529 Expression e1 = interpretRegion(e.e1, istate);
5530 if (exceptionOrCant(e1))
5531 return;
5532 if (e1.op == EXP.int64)
5534 error(e.loc, "cannot slice invalid pointer `%s` of value `%s`", e.e1.toChars(), e1.toChars());
5535 result = CTFEExp.cantexp;
5536 return;
5539 /* Evaluate lower and upper bounds of slice
5541 Expression lwr = interpretRegion(e.lwr, istate);
5542 if (exceptionOrCant(lwr))
5543 return;
5544 Expression upr = interpretRegion(e.upr, istate);
5545 if (exceptionOrCant(upr))
5546 return;
5547 uinteger_t ilwr = lwr.toInteger();
5548 uinteger_t iupr = upr.toInteger();
5550 dinteger_t ofs;
5551 Expression agg = getAggregateFromPointer(e1, &ofs);
5552 ilwr += ofs;
5553 iupr += ofs;
5554 if (agg.op == EXP.null_)
5556 if (iupr == ilwr)
5558 result = ctfeEmplaceExp!NullExp(e.loc);
5559 result.type = e.type;
5560 return;
5562 error(e.loc, "cannot slice null pointer `%s`", e.e1.toChars());
5563 result = CTFEExp.cantexp;
5564 return;
5566 if (agg.op == EXP.symbolOffset)
5568 error(e.loc, "slicing pointers to static variables is not supported in CTFE");
5569 result = CTFEExp.cantexp;
5570 return;
5572 if (agg.op != EXP.arrayLiteral && agg.op != EXP.string_)
5574 error(e.loc, "pointer `%s` cannot be sliced at compile time (it does not point to an array)", e.e1.toChars());
5575 result = CTFEExp.cantexp;
5576 return;
5578 assert(agg.op == EXP.arrayLiteral || agg.op == EXP.string_);
5579 dinteger_t len = ArrayLength(Type.tsize_t, agg).exp().toInteger();
5580 //Type *pointee = ((TypePointer *)agg.type)->next;
5581 if (sliceBoundsCheck(0, len, ilwr, iupr))
5583 error(e.loc, "pointer slice `[%lld..%lld]` exceeds allocated memory block `[0..%lld]`", ilwr, iupr, len);
5584 result = CTFEExp.cantexp;
5585 return;
5587 if (ofs != 0)
5589 lwr = ctfeEmplaceExp!IntegerExp(e.loc, ilwr, lwr.type);
5590 upr = ctfeEmplaceExp!IntegerExp(e.loc, iupr, upr.type);
5592 emplaceExp!(SliceExp)(pue, e.loc, agg, lwr, upr);
5593 result = pue.exp();
5594 result.type = e.type;
5595 return;
5598 CTFEGoal goal1 = CTFEGoal.RValue;
5599 if (goal == CTFEGoal.LValue)
5601 if (e.e1.type.toBasetype().ty == Tsarray)
5602 if (auto ve = e.e1.isVarExp())
5603 if (auto vd = ve.var.isVarDeclaration())
5604 if (vd.storage_class & STC.ref_)
5605 goal1 = CTFEGoal.LValue;
5607 Expression e1 = interpret(e.e1, istate, goal1);
5608 if (exceptionOrCant(e1))
5609 return;
5611 if (!e.lwr)
5613 result = paintTypeOntoLiteral(pue, e.type, e1);
5614 return;
5616 if (auto ve = e1.isVectorExp())
5618 e1 = interpretVectorToArray(pue, ve);
5619 e1 = (e1 == pue.exp()) ? pue.copy() : e1;
5622 /* Set dollar to the length of the array
5624 uinteger_t dollar;
5625 if ((e1.op == EXP.variable || e1.op == EXP.dotVariable) && e1.type.toBasetype().ty == Tsarray)
5626 dollar = e1.type.toBasetype().isTypeSArray().dim.toInteger();
5627 else
5629 if (e1.op != EXP.arrayLiteral && e1.op != EXP.string_ && e1.op != EXP.null_ && e1.op != EXP.slice && e1.op != EXP.vector)
5631 error(e.loc, "cannot determine length of `%s` at compile time", e1.toChars());
5632 result = CTFEExp.cantexp;
5633 return;
5635 dollar = resolveArrayLength(e1);
5638 /* Set the $ variable
5640 if (e.lengthVar)
5642 auto dollarExp = ctfeEmplaceExp!IntegerExp(e.loc, dollar, Type.tsize_t);
5643 ctfeGlobals.stack.push(e.lengthVar);
5644 setValue(e.lengthVar, dollarExp);
5647 /* Evaluate lower and upper bounds of slice
5649 Expression lwr = interpretRegion(e.lwr, istate);
5650 if (exceptionOrCant(lwr))
5652 if (e.lengthVar)
5653 ctfeGlobals.stack.pop(e.lengthVar);
5654 return;
5656 Expression upr = interpretRegion(e.upr, istate);
5657 if (exceptionOrCant(upr))
5659 if (e.lengthVar)
5660 ctfeGlobals.stack.pop(e.lengthVar);
5661 return;
5663 if (e.lengthVar)
5664 ctfeGlobals.stack.pop(e.lengthVar); // $ is defined only inside [L..U]
5666 uinteger_t ilwr = lwr.toInteger();
5667 uinteger_t iupr = upr.toInteger();
5668 if (e1.op == EXP.null_)
5670 if (ilwr == 0 && iupr == 0)
5672 result = e1;
5673 return;
5675 error(e1.loc, "slice `[%llu..%llu]` is out of bounds", ilwr, iupr);
5676 result = CTFEExp.cantexp;
5677 return;
5679 if (auto se = e1.isSliceExp())
5681 // Simplify slice of slice:
5682 // aggregate[lo1..up1][lwr..upr] ---> aggregate[lwr'..upr']
5683 uinteger_t lo1 = se.lwr.toInteger();
5684 uinteger_t up1 = se.upr.toInteger();
5685 if (sliceBoundsCheck(0, up1 - lo1, ilwr, iupr))
5687 error(e.loc, "slice `[%llu..%llu]` exceeds array bounds `[0..%llu]`", ilwr, iupr, up1 - lo1);
5688 result = CTFEExp.cantexp;
5689 return;
5691 ilwr += lo1;
5692 iupr += lo1;
5693 emplaceExp!(SliceExp)(pue, e.loc, se.e1,
5694 ctfeEmplaceExp!IntegerExp(e.loc, ilwr, lwr.type),
5695 ctfeEmplaceExp!IntegerExp(e.loc, iupr, upr.type));
5696 result = pue.exp();
5697 result.type = e.type;
5698 return;
5700 if (e1.op == EXP.arrayLiteral || e1.op == EXP.string_)
5702 if (sliceBoundsCheck(0, dollar, ilwr, iupr))
5704 error(e.loc, "slice `[%lld..%lld]` exceeds array bounds `[0..%lld]`", ilwr, iupr, dollar);
5705 result = CTFEExp.cantexp;
5706 return;
5709 emplaceExp!(SliceExp)(pue, e.loc, e1, lwr, upr);
5710 result = pue.exp();
5711 result.type = e.type;
5714 override void visit(InExp e)
5716 debug (LOG)
5718 printf("%s InExp::interpret() %s\n", e.loc.toChars(), e.toChars());
5720 Expression e1 = interpretRegion(e.e1, istate);
5721 if (exceptionOrCant(e1))
5722 return;
5723 Expression e2 = interpretRegion(e.e2, istate);
5724 if (exceptionOrCant(e2))
5725 return;
5726 if (e2.op == EXP.null_)
5728 emplaceExp!(NullExp)(pue, e.loc, e.type);
5729 result = pue.exp();
5730 return;
5732 if (e2.op != EXP.assocArrayLiteral)
5734 error(e.loc, "`%s` cannot be interpreted at compile time", e.toChars());
5735 result = CTFEExp.cantexp;
5736 return;
5739 e1 = resolveSlice(e1);
5740 result = findKeyInAA(e.loc, e2.isAssocArrayLiteralExp(), e1);
5741 if (exceptionOrCant(result))
5742 return;
5743 if (!result)
5745 emplaceExp!(NullExp)(pue, e.loc, e.type);
5746 result = pue.exp();
5748 else
5750 // Create a CTFE pointer &aa[index]
5751 result = ctfeEmplaceExp!IndexExp(e.loc, e2, e1);
5752 result.type = e.type.nextOf();
5753 emplaceExp!(AddrExp)(pue, e.loc, result, e.type);
5754 result = pue.exp();
5758 override void visit(CatExp e)
5760 debug (LOG)
5762 printf("%s CatExp::interpret() %s\n", e.loc.toChars(), e.toChars());
5765 UnionExp ue1 = void;
5766 Expression e1 = interpret(&ue1, e.e1, istate);
5767 if (exceptionOrCant(e1))
5768 return;
5770 UnionExp ue2 = void;
5771 Expression e2 = interpret(&ue2, e.e2, istate);
5772 if (exceptionOrCant(e2))
5773 return;
5775 UnionExp e1tmp = void;
5776 e1 = resolveSlice(e1, &e1tmp);
5778 UnionExp e2tmp = void;
5779 e2 = resolveSlice(e2, &e2tmp);
5781 /* e1 and e2 can't go on the stack because of x~[y] and [x]~y will
5782 * result in [x,y] and then x or y is on the stack.
5783 * But if they are both strings, we can, because it isn't the x~[y] case.
5785 if (!(e1.op == EXP.string_ && e2.op == EXP.string_))
5787 if (e1 == ue1.exp())
5788 e1 = ue1.copy();
5789 if (e2 == ue2.exp())
5790 e2 = ue2.copy();
5793 Expression prepareCatOperand(Expression exp)
5795 /* Convert `elem ~ array` to `[elem] ~ array` if `elem` is itself an
5796 * array. This is needed because interpreting the `CatExp` calls
5797 * `Cat()`, which cannot handle concatenations between different
5798 * types, except for strings and chars.
5800 auto tb = e.type.toBasetype();
5801 auto tbNext = tb.nextOf();
5802 auto expTb = exp.type.toBasetype();
5804 if (exp.type.implicitConvTo(tbNext) >= MATCH.convert &&
5805 (tb.ty == Tarray || tb.ty == Tsarray) &&
5806 (expTb.ty == Tarray || expTb.ty == Tsarray))
5807 return new ArrayLiteralExp(exp.loc, e.type, exp);
5808 return exp;
5811 *pue = ctfeCat(e.loc, e.type, prepareCatOperand(e1), prepareCatOperand(e2));
5812 result = pue.exp();
5814 if (CTFEExp.isCantExp(result))
5816 error(e.loc, "`%s` cannot be interpreted at compile time", e.toChars());
5817 return;
5819 // We know we still own it, because we interpreted both e1 and e2
5820 if (auto ale = result.isArrayLiteralExp())
5822 ale.ownedByCtfe = OwnedBy.ctfe;
5824 // https://issues.dlang.org/show_bug.cgi?id=14686
5825 foreach (elem; *ale.elements)
5827 Expression ex = evaluatePostblit(istate, elem);
5828 if (exceptionOrCant(ex))
5829 return;
5832 else if (auto se = result.isStringExp())
5833 se.ownedByCtfe = OwnedBy.ctfe;
5836 override void visit(DeleteExp e)
5838 debug (LOG)
5840 printf("%s DeleteExp::interpret() %s\n", e.loc.toChars(), e.toChars());
5842 result = interpretRegion(e.e1, istate);
5843 if (exceptionOrCant(result))
5844 return;
5846 if (result.op == EXP.null_)
5848 result = CTFEExp.voidexp;
5849 return;
5852 auto tb = e.e1.type.toBasetype();
5853 switch (tb.ty)
5855 case Tclass:
5856 if (result.op != EXP.classReference)
5858 error(e.loc, "`delete` on invalid class reference `%s`", result.toChars());
5859 result = CTFEExp.cantexp;
5860 return;
5863 auto cre = result.isClassReferenceExp();
5864 auto cd = cre.originalClass();
5866 // Find dtor(s) in inheritance chain
5869 if (cd.dtor)
5871 result = interpretFunction(pue, cd.dtor, istate, null, cre);
5872 if (exceptionOrCant(result))
5873 return;
5875 // Dtors of Non-extern(D) classes use implicit chaining (like structs)
5876 import dmd.aggregate : ClassKind;
5877 if (cd.classKind != ClassKind.d)
5878 break;
5881 // Emulate manual chaining as done in rt_finalize2
5882 cd = cd.baseClass;
5884 } while (cd); // Stop after Object
5886 break;
5888 default:
5889 assert(0);
5891 result = CTFEExp.voidexp;
5894 override void visit(CastExp e)
5896 debug (LOG)
5898 printf("%s CastExp::interpret() %s\n", e.loc.toChars(), e.toChars());
5900 Expression e1 = interpretRegion(e.e1, istate, goal);
5901 if (exceptionOrCant(e1))
5902 return;
5903 // If the expression has been cast to void, do nothing.
5904 if (e.to.ty == Tvoid)
5906 result = CTFEExp.voidexp;
5907 return;
5909 if (e.to.ty == Tpointer && e1.op != EXP.null_)
5911 Type pointee = (cast(TypePointer)e.type).next;
5912 // Implement special cases of normally-unsafe casts
5913 if (e1.op == EXP.int64)
5915 // Happens with Windows HANDLEs, for example.
5916 result = paintTypeOntoLiteral(pue, e.to, e1);
5917 return;
5920 bool castToSarrayPointer = false;
5921 bool castBackFromVoid = false;
5922 if (e1.type.ty == Tarray || e1.type.ty == Tsarray || e1.type.ty == Tpointer)
5924 // Check for unsupported type painting operations
5925 // For slices, we need the type being sliced,
5926 // since it may have already been type painted
5927 Type elemtype = e1.type.nextOf();
5928 if (auto se = e1.isSliceExp())
5929 elemtype = se.e1.type.nextOf();
5931 // Allow casts from X* to void *, and X** to void** for any X.
5932 // But don't allow cast from X* to void**.
5933 // So, we strip all matching * from source and target to find X.
5934 // Allow casts to X* from void* only if the 'void' was originally an X;
5935 // we check this later on.
5936 Type ultimatePointee = pointee;
5937 Type ultimateSrc = elemtype;
5938 while (ultimatePointee.ty == Tpointer && ultimateSrc.ty == Tpointer)
5940 ultimatePointee = ultimatePointee.nextOf();
5941 ultimateSrc = ultimateSrc.nextOf();
5943 if (ultimatePointee.ty == Tsarray && ultimatePointee.nextOf().equivalent(ultimateSrc))
5945 castToSarrayPointer = true;
5947 else if (ultimatePointee.ty != Tvoid && ultimateSrc.ty != Tvoid && !isSafePointerCast(elemtype, pointee))
5949 error(e.loc, "reinterpreting cast from `%s*` to `%s*` is not supported in CTFE", elemtype.toChars(), pointee.toChars());
5950 result = CTFEExp.cantexp;
5951 return;
5953 if (ultimateSrc.ty == Tvoid)
5954 castBackFromVoid = true;
5957 if (auto se = e1.isSliceExp())
5959 if (se.e1.op == EXP.null_)
5961 result = paintTypeOntoLiteral(pue, e.type, se.e1);
5962 return;
5964 // Create a CTFE pointer &aggregate[1..2]
5965 auto ei = ctfeEmplaceExp!IndexExp(e.loc, se.e1, se.lwr);
5966 ei.type = e.type.nextOf();
5967 emplaceExp!(AddrExp)(pue, e.loc, ei, e.type);
5968 result = pue.exp();
5969 return;
5971 if (e1.op == EXP.arrayLiteral || e1.op == EXP.string_)
5973 // Create a CTFE pointer &[1,2,3][0] or &"abc"[0]
5974 auto ei = ctfeEmplaceExp!IndexExp(e.loc, e1, ctfeEmplaceExp!IntegerExp(e.loc, 0, Type.tsize_t));
5975 ei.type = e.type.nextOf();
5976 emplaceExp!(AddrExp)(pue, e.loc, ei, e.type);
5977 result = pue.exp();
5978 return;
5980 if (e1.op == EXP.index && !e1.isIndexExp().e1.type.equals(e1.type))
5982 // type painting operation
5983 IndexExp ie = e1.isIndexExp();
5984 if (castBackFromVoid)
5986 // get the original type. For strings, it's just the type...
5987 Type origType = ie.e1.type.nextOf();
5988 // ..but for arrays of type void*, it's the type of the element
5989 if (ie.e1.op == EXP.arrayLiteral && ie.e2.op == EXP.int64)
5991 ArrayLiteralExp ale = ie.e1.isArrayLiteralExp();
5992 const indx = cast(size_t)ie.e2.toInteger();
5993 if (indx < ale.elements.length)
5995 if (Expression xx = (*ale.elements)[indx])
5997 if (auto iex = xx.isIndexExp())
5998 origType = iex.e1.type.nextOf();
5999 else if (auto ae = xx.isAddrExp())
6000 origType = ae.e1.type;
6001 else if (auto ve = xx.isVarExp())
6002 origType = ve.var.type;
6006 if (!isSafePointerCast(origType, pointee))
6008 error(e.loc, "using `void*` to reinterpret cast from `%s*` to `%s*` is not supported in CTFE", origType.toChars(), pointee.toChars());
6009 result = CTFEExp.cantexp;
6010 return;
6013 emplaceExp!(IndexExp)(pue, e1.loc, ie.e1, ie.e2);
6014 result = pue.exp();
6015 result.type = e.type;
6016 return;
6019 if (auto ae = e1.isAddrExp())
6021 Type origType = ae.e1.type;
6022 if (isSafePointerCast(origType, pointee))
6024 emplaceExp!(AddrExp)(pue, e.loc, ae.e1, e.type);
6025 result = pue.exp();
6026 return;
6029 if (castToSarrayPointer && pointee.toBasetype().ty == Tsarray && ae.e1.op == EXP.index)
6031 // &val[idx]
6032 dinteger_t dim = (cast(TypeSArray)pointee.toBasetype()).dim.toInteger();
6033 IndexExp ie = ae.e1.isIndexExp();
6034 Expression lwr = ie.e2;
6035 Expression upr = ctfeEmplaceExp!IntegerExp(ie.e2.loc, ie.e2.toInteger() + dim, Type.tsize_t);
6037 // Create a CTFE pointer &val[idx..idx+dim]
6038 auto er = ctfeEmplaceExp!SliceExp(e.loc, ie.e1, lwr, upr);
6039 er.type = pointee;
6040 emplaceExp!(AddrExp)(pue, e.loc, er, e.type);
6041 result = pue.exp();
6042 return;
6046 if (e1.op == EXP.variable || e1.op == EXP.symbolOffset)
6048 // type painting operation
6049 Type origType = (cast(SymbolExp)e1).var.type;
6050 if (castBackFromVoid && !isSafePointerCast(origType, pointee))
6052 error(e.loc, "using `void*` to reinterpret cast from `%s*` to `%s*` is not supported in CTFE", origType.toChars(), pointee.toChars());
6053 result = CTFEExp.cantexp;
6054 return;
6056 if (auto ve = e1.isVarExp())
6057 emplaceExp!(VarExp)(pue, e.loc, ve.var);
6058 else
6059 emplaceExp!(SymOffExp)(pue, e.loc, e1.isSymOffExp().var, e1.isSymOffExp().offset);
6060 result = pue.exp();
6061 result.type = e.to;
6062 return;
6065 // Check if we have a null pointer (eg, inside a struct)
6066 e1 = interpretRegion(e1, istate);
6067 if (e1.op != EXP.null_)
6069 error(e.loc, "pointer cast from `%s` to `%s` is not supported at compile time", e1.type.toChars(), e.to.toChars());
6070 result = CTFEExp.cantexp;
6071 return;
6074 if (e.to.ty == Tsarray && e.e1.type.ty == Tvector)
6076 // Special handling for: cast(float[4])__vector([w, x, y, z])
6077 e1 = interpretRegion(e.e1, istate);
6078 if (exceptionOrCant(e1))
6079 return;
6080 assert(e1.op == EXP.vector);
6081 e1 = interpretVectorToArray(pue, e1.isVectorExp());
6083 if (e.to.ty == Tarray && e1.op == EXP.slice)
6085 // Note that the slice may be void[], so when checking for dangerous
6086 // casts, we need to use the original type, which is se.e1.
6087 SliceExp se = e1.isSliceExp();
6088 if (!isSafePointerCast(se.e1.type.nextOf(), e.to.nextOf()))
6090 error(e.loc, "array cast from `%s` to `%s` is not supported at compile time", se.e1.type.toChars(), e.to.toChars());
6091 result = CTFEExp.cantexp;
6092 return;
6094 emplaceExp!(SliceExp)(pue, e1.loc, se.e1, se.lwr, se.upr);
6095 result = pue.exp();
6096 result.type = e.to;
6097 return;
6099 // Disallow array type painting, except for conversions between built-in
6100 // types of identical size.
6101 if ((e.to.ty == Tsarray || e.to.ty == Tarray) && (e1.type.ty == Tsarray || e1.type.ty == Tarray) && !isSafePointerCast(e1.type.nextOf(), e.to.nextOf()))
6103 error(e.loc, "array cast from `%s` to `%s` is not supported at compile time", e1.type.toChars(), e.to.toChars());
6104 result = CTFEExp.cantexp;
6105 return;
6107 if (e.to.ty == Tsarray)
6108 e1 = resolveSlice(e1);
6110 auto tobt = e.to.toBasetype();
6111 if (tobt.ty == Tbool && e1.type.ty == Tpointer)
6113 emplaceExp!(IntegerExp)(pue, e.loc, e1.op != EXP.null_, e.to);
6114 result = pue.exp();
6115 return;
6117 else if (tobt.isTypeBasic() && e1.op == EXP.null_)
6119 if (tobt.isintegral())
6120 emplaceExp!(IntegerExp)(pue, e.loc, 0, e.to);
6121 else if (tobt.isreal())
6122 emplaceExp!(RealExp)(pue, e.loc, CTFloat.zero, e.to);
6123 result = pue.exp();
6124 return;
6126 result = ctfeCast(pue, e.loc, e.type, e.to, e1, true);
6129 override void visit(AssertExp e)
6131 debug (LOG)
6133 printf("%s AssertExp::interpret() %s\n", e.loc.toChars(), e.toChars());
6135 Expression e1 = interpret(pue, e.e1, istate);
6136 if (exceptionOrCant(e1))
6137 return;
6138 if (isTrueBool(e1))
6141 else if (e1.toBool().hasValue(false))
6143 if (e.msg)
6145 UnionExp ue = void;
6146 result = interpret(&ue, e.msg, istate);
6147 if (exceptionOrCant(result))
6148 return;
6149 result = scrubReturnValue(e.loc, result);
6150 if (StringExp se = result.toStringExp())
6151 error(e.loc, "%s", se.toStringz().ptr);
6152 else
6153 error(e.loc, "%s", result.toChars());
6155 else
6156 error(e.loc, "`%s` failed", e.toChars());
6157 result = CTFEExp.cantexp;
6158 return;
6160 else
6162 error(e.loc, "`%s` is not a compile time boolean expression", e1.toChars());
6163 result = CTFEExp.cantexp;
6164 return;
6166 result = e1;
6167 return;
6170 override void visit(ThrowExp te)
6172 debug (LOG)
6174 printf("%s ThrowExpression::interpret()\n", te.loc.toChars());
6176 interpretThrow(result, te.e1, te.loc, istate);
6179 override void visit(PtrExp e)
6181 // Called for both lvalues and rvalues
6182 const lvalue = goal == CTFEGoal.LValue;
6183 debug (LOG)
6185 printf("%s PtrExp::interpret(%d) %s, %s\n", e.loc.toChars(), lvalue, e.type.toChars(), e.toChars());
6188 // Check for int<->float and long<->double casts.
6189 if (auto soe1 = e.e1.isSymOffExp())
6190 if (soe1.offset == 0 && soe1.var.isVarDeclaration() && isFloatIntPaint(e.type, soe1.var.type))
6192 // *(cast(int*)&v), where v is a float variable
6193 result = paintFloatInt(pue, getVarExp(e.loc, istate, soe1.var, CTFEGoal.RValue), e.type);
6194 return;
6197 if (auto ce1 = e.e1.isCastExp())
6198 if (auto ae11 = ce1.e1.isAddrExp())
6200 // *(cast(int*)&x), where x is a float expression
6201 Expression x = ae11.e1;
6202 if (isFloatIntPaint(e.type, x.type))
6204 result = paintFloatInt(pue, interpretRegion(x, istate), e.type);
6205 return;
6209 // Constant fold *(&structliteral + offset)
6210 if (auto ae = e.e1.isAddExp())
6212 if (ae.e1.op == EXP.address && ae.e2.op == EXP.int64)
6214 AddrExp ade = ae.e1.isAddrExp();
6215 Expression ex = interpretRegion(ade.e1, istate);
6216 if (exceptionOrCant(ex))
6217 return;
6218 if (auto se = ex.isStructLiteralExp())
6220 dinteger_t offset = ae.e2.toInteger();
6221 result = se.getField(e.type, cast(uint)offset);
6222 if (result)
6223 return;
6228 // It's possible we have an array bounds error. We need to make sure it
6229 // errors with this line number, not the one where the pointer was set.
6230 result = interpretRegion(e.e1, istate);
6231 if (exceptionOrCant(result))
6232 return;
6234 if (result.op == EXP.function_)
6235 return;
6236 if (auto soe = result.isSymOffExp())
6238 if (soe.offset == 0 && soe.var.isFuncDeclaration())
6239 return;
6240 error(e.loc, "cannot dereference pointer to static variable `%s` at compile time", soe.var.toChars());
6241 result = CTFEExp.cantexp;
6242 return;
6245 if (!lvalue && result.isArrayLiteralExp() &&
6246 result.type.isTypePointer())
6248 /* A pointer variable can point to an array literal like `[3]`.
6249 * Dereferencing it means accessing the first element value.
6250 * Dereference it only if result should be an rvalue
6252 auto ae = result.isArrayLiteralExp();
6253 if (ae.elements.length == 1)
6255 result = (*ae.elements)[0];
6256 return;
6259 if (result.isStringExp() || result.isArrayLiteralExp())
6260 return;
6262 if (result.op != EXP.address)
6264 if (result.op == EXP.null_)
6265 error(e.loc, "dereference of null pointer `%s`", e.e1.toChars());
6266 else
6267 error(e.loc, "dereference of invalid pointer `%s`", result.toChars());
6268 result = CTFEExp.cantexp;
6269 return;
6272 // *(&x) ==> x
6273 result = result.isAddrExp().e1;
6275 if (result.op == EXP.slice && e.type.toBasetype().ty == Tsarray)
6277 /* aggr[lwr..upr]
6278 * upr may exceed the upper boundary of aggr, but the check is deferred
6279 * until those out-of-bounds elements will be touched.
6281 return;
6283 result = interpret(pue, result, istate, goal);
6284 if (exceptionOrCant(result))
6285 return;
6287 debug (LOG)
6289 if (CTFEExp.isCantExp(result))
6290 printf("PtrExp::interpret() %s = CTFEExp::cantexp\n", e.toChars());
6294 override void visit(DotVarExp e)
6296 void notImplementedYet()
6298 error(e.loc, "`%s.%s` is not yet implemented at compile time", e.e1.toChars(), e.var.toChars());
6299 result = CTFEExp.cantexp;
6300 return;
6303 debug (LOG)
6305 printf("%s DotVarExp::interpret() %s, goal = %d\n", e.loc.toChars(), e.toChars(), goal);
6307 Expression ex = interpretRegion(e.e1, istate);
6308 if (exceptionOrCant(ex))
6309 return;
6311 if (FuncDeclaration f = e.var.isFuncDeclaration())
6313 if (ex == e.e1)
6314 result = e; // optimize: reuse this CTFE reference
6315 else
6317 emplaceExp!(DotVarExp)(pue, e.loc, ex, f, false);
6318 result = pue.exp();
6319 result.type = e.type;
6321 return;
6324 VarDeclaration v = e.var.isVarDeclaration();
6325 if (!v)
6327 error(e.loc, "CTFE internal error: `%s`", e.toChars());
6328 result = CTFEExp.cantexp;
6329 return;
6332 if (ex.op == EXP.null_)
6334 if (ex.type.toBasetype().ty == Tclass)
6335 error(e.loc, "class `%s` is `null` and cannot be dereferenced", e.e1.toChars());
6336 else
6337 error(e.loc, "CTFE internal error: null this `%s`", e.e1.toChars());
6338 result = CTFEExp.cantexp;
6339 return;
6342 StructLiteralExp se;
6343 int i;
6345 if (ex.op != EXP.structLiteral && ex.op != EXP.classReference && ex.op != EXP.typeid_)
6347 return notImplementedYet();
6350 // We can't use getField, because it makes a copy
6351 if (ex.op == EXP.classReference)
6353 se = ex.isClassReferenceExp().value;
6354 i = ex.isClassReferenceExp().findFieldIndexByName(v);
6356 else if (ex.op == EXP.typeid_)
6358 if (v.ident == Identifier.idPool("name"))
6360 if (auto t = isType(ex.isTypeidExp().obj))
6362 auto sym = t.toDsymbol(null);
6363 if (auto ident = (sym ? sym.ident : null))
6365 result = new StringExp(e.loc, ident.toString());
6366 result.expressionSemantic(null);
6367 return ;
6371 return notImplementedYet();
6373 else
6375 se = ex.isStructLiteralExp();
6376 i = findFieldIndexByName(se.sd, v);
6378 if (i == -1)
6380 error(e.loc, "couldn't find field `%s` of type `%s` in `%s`", v.toChars(), e.type.toChars(), se.toChars());
6381 result = CTFEExp.cantexp;
6382 return;
6385 // https://issues.dlang.org/show_bug.cgi?id=19897
6386 // https://issues.dlang.org/show_bug.cgi?id=20710
6387 // Zero-elements fields don't have an initializer. See: scrubArray function
6388 if ((*se.elements)[i] is null)
6389 (*se.elements)[i] = voidInitLiteral(e.type, v).copy();
6391 if (goal == CTFEGoal.LValue)
6393 // just return the (simplified) dotvar expression as a CTFE reference
6394 if (e.e1 == ex)
6395 result = e;
6396 else
6398 emplaceExp!(DotVarExp)(pue, e.loc, ex, v);
6399 result = pue.exp();
6400 result.type = e.type;
6402 return;
6405 result = (*se.elements)[i];
6406 if (!result)
6408 error(e.loc, "internal compiler error: null field `%s`", v.toChars());
6409 result = CTFEExp.cantexp;
6410 return;
6412 if (auto vie = result.isVoidInitExp())
6414 const s = vie.var.toChars();
6415 if (v.overlapped)
6417 error(e.loc, "reinterpretation through overlapped field `%s` is not allowed in CTFE", s);
6418 result = CTFEExp.cantexp;
6419 return;
6421 error(e.loc, "cannot read uninitialized variable `%s` in CTFE", s);
6422 result = CTFEExp.cantexp;
6423 return;
6426 if (v.type.ty != result.type.ty && v.type.ty == Tsarray)
6428 // Block assignment from inside struct literals
6429 auto tsa = cast(TypeSArray)v.type;
6430 auto len = cast(size_t)tsa.dim.toInteger();
6431 UnionExp ue = void;
6432 result = createBlockDuplicatedArrayLiteral(&ue, e.loc, v.type, result, len);
6433 if (result == ue.exp())
6434 result = ue.copy();
6435 (*se.elements)[i] = result;
6437 debug (LOG)
6439 if (CTFEExp.isCantExp(result))
6440 printf("DotVarExp::interpret() %s = CTFEExp::cantexp\n", e.toChars());
6444 override void visit(RemoveExp e)
6446 debug (LOG)
6448 printf("%s RemoveExp::interpret() %s\n", e.loc.toChars(), e.toChars());
6450 Expression agg = interpret(e.e1, istate);
6451 if (exceptionOrCant(agg))
6452 return;
6453 Expression index = interpret(e.e2, istate);
6454 if (exceptionOrCant(index))
6455 return;
6456 if (agg.op == EXP.null_)
6458 result = CTFEExp.voidexp;
6459 return;
6462 AssocArrayLiteralExp aae = agg.isAssocArrayLiteralExp();
6463 Expressions* keysx = aae.keys;
6464 Expressions* valuesx = aae.values;
6465 size_t removed = 0;
6466 foreach (j, evalue; *valuesx)
6468 Expression ekey = (*keysx)[j];
6469 int eq = ctfeEqual(e.loc, EXP.equal, ekey, index);
6470 if (eq)
6471 ++removed;
6472 else if (removed != 0)
6474 (*keysx)[j - removed] = ekey;
6475 (*valuesx)[j - removed] = evalue;
6478 valuesx.length = valuesx.length - removed;
6479 keysx.length = keysx.length - removed;
6480 result = IntegerExp.createBool(removed != 0);
6483 override void visit(ClassReferenceExp e)
6485 //printf("ClassReferenceExp::interpret() %s\n", e.value.toChars());
6486 result = e;
6489 override void visit(VoidInitExp e)
6491 error(e.loc, "CTFE internal error: trying to read uninitialized variable");
6492 assert(0);
6495 override void visit(ThrownExceptionExp e)
6497 assert(0); // This should never be interpreted
6501 /// Interpret `throw <exp>` found at the specified location `loc`
6502 private
6503 void interpretThrow(ref Expression result, Expression exp, const ref Loc loc, InterState* istate)
6505 incUsageCtfe(istate, loc);
6507 Expression e = interpretRegion(exp, istate);
6508 if (exceptionOrCantInterpret(e))
6510 // Make sure e is not pointing to a stack temporary
6511 result = (e.op == EXP.cantExpression) ? CTFEExp.cantexp : e;
6513 else if (e.op == EXP.classReference)
6515 result = ctfeEmplaceExp!ThrownExceptionExp(loc, e.isClassReferenceExp());
6517 else
6519 error(exp.loc, "to be thrown `%s` must be non-null", exp.toChars());
6520 result = ErrorExp.get();
6524 /*********************************************
6525 * Checks if the given expresion is a call to the runtime hook `id`.
6527 * Params:
6528 * e = the expression to check
6529 * id = the identifier of the runtime hook
6530 * Returns:
6531 * `e` cast to `CallExp` if it's the hook, `null` otherwise
6533 public CallExp isRuntimeHook(Expression e, Identifier id)
6535 if (auto ce = e.isCallExp())
6537 if (auto ve = ce.e1.isVarExp())
6539 if (auto fd = ve.var.isFuncDeclaration())
6541 // If `_d_HookTraceImpl` is found, resolve the underlying hook
6542 // and replace `e` and `fd` with it.
6543 removeHookTraceImpl(ce, fd);
6544 return fd.ident == id ? ce : null;
6549 return null;
6552 /********************************************
6553 * Interpret the expression.
6554 * Params:
6555 * pue = non-null pointer to temporary storage that can be used to store the return value
6556 * e = Expression to interpret
6557 * istate = context
6558 * goal = what the result will be used for
6559 * Returns:
6560 * resulting expression
6563 Expression interpret(UnionExp* pue, Expression e, InterState* istate, CTFEGoal goal = CTFEGoal.RValue)
6565 if (!e)
6566 return null;
6567 //printf("+interpret() e : %s, %s\n", e.type.toChars(), e.toChars());
6568 scope Interpreter v = new Interpreter(pue, istate, goal);
6569 e.accept(v);
6570 Expression ex = v.result;
6571 assert(goal == CTFEGoal.Nothing || ex !is null);
6572 //if (ex) printf("-interpret() ex: %s, %s\n", ex.type.toChars(), ex.toChars()); else printf("-interpret()\n");
6573 return ex;
6577 Expression interpret(Expression e, InterState* istate, CTFEGoal goal = CTFEGoal.RValue)
6579 UnionExp ue = void;
6580 auto result = interpret(&ue, e, istate, goal);
6581 if (result == ue.exp())
6582 result = ue.copy();
6583 return result;
6586 /*****************************
6587 * Same as interpret(), but return result allocated in Region.
6588 * Params:
6589 * e = Expression to interpret
6590 * istate = context
6591 * goal = what the result will be used for
6592 * Returns:
6593 * resulting expression
6595 Expression interpretRegion(Expression e, InterState* istate, CTFEGoal goal = CTFEGoal.RValue)
6597 UnionExp ue = void;
6598 auto result = interpret(&ue, e, istate, goal);
6599 auto uexp = ue.exp();
6600 if (result != uexp)
6601 return result;
6602 if (mem.isGCEnabled)
6603 return ue.copy();
6605 // mimicking UnionExp.copy, but with region allocation
6606 switch (uexp.op)
6608 case EXP.cantExpression: return CTFEExp.cantexp;
6609 case EXP.voidExpression: return CTFEExp.voidexp;
6610 case EXP.break_: return CTFEExp.breakexp;
6611 case EXP.continue_: return CTFEExp.continueexp;
6612 case EXP.goto_: return CTFEExp.gotoexp;
6613 default: break;
6615 auto p = ctfeGlobals.region.malloc(uexp.size);
6616 return cast(Expression)memcpy(p, cast(void*)uexp, uexp.size);
6619 private
6620 Expressions* copyArrayOnWrite(Expressions* exps, Expressions* original)
6622 if (exps is original)
6624 if (!original)
6625 exps = new Expressions();
6626 else
6627 exps = original.copy();
6628 ++ctfeGlobals.numArrayAllocs;
6630 return exps;
6634 Given an expression e which is about to be returned from the current
6635 function, generate an error if it contains pointers to local variables.
6637 Only checks expressions passed by value (pointers to local variables
6638 may already be stored in members of classes, arrays, or AAs which
6639 were passed as mutable function parameters).
6640 Returns:
6641 true if it is safe to return, false if an error was generated.
6643 private
6644 bool stopPointersEscaping(const ref Loc loc, Expression e)
6646 if (!e.type.hasPointers())
6647 return true;
6648 if (isPointer(e.type))
6650 Expression x = e;
6651 if (auto eaddr = e.isAddrExp())
6652 x = eaddr.e1;
6653 VarDeclaration v;
6654 while (x.op == EXP.variable && (v = x.isVarExp().var.isVarDeclaration()) !is null)
6656 if (v.storage_class & STC.ref_)
6658 x = getValue(v);
6659 if (auto eaddr = e.isAddrExp())
6660 eaddr.e1 = x;
6661 continue;
6663 if (ctfeGlobals.stack.isInCurrentFrame(v))
6665 error(loc, "returning a pointer to a local stack variable");
6666 return false;
6668 else
6669 break;
6671 // TODO: If it is a EXP.dotVariable or EXP.index, we should check that it is not
6672 // pointing to a local struct or static array.
6674 if (auto se = e.isStructLiteralExp())
6676 return stopPointersEscapingFromArray(loc, se.elements);
6678 if (auto ale = e.isArrayLiteralExp())
6680 return stopPointersEscapingFromArray(loc, ale.elements);
6682 if (auto aae = e.isAssocArrayLiteralExp())
6684 if (!stopPointersEscapingFromArray(loc, aae.keys))
6685 return false;
6686 return stopPointersEscapingFromArray(loc, aae.values);
6688 return true;
6691 // Check all elements of an array for escaping local variables. Return false if error
6692 private
6693 bool stopPointersEscapingFromArray(const ref Loc loc, Expressions* elems)
6695 foreach (e; *elems)
6697 if (e && !stopPointersEscaping(loc, e))
6698 return false;
6700 return true;
6703 private
6704 Statement findGotoTarget(InterState* istate, Identifier ident)
6706 Statement target = null;
6707 if (ident)
6709 LabelDsymbol label = istate.fd.searchLabel(ident);
6710 assert(label && label.statement);
6711 LabelStatement ls = label.statement;
6712 target = ls.gotoTarget ? ls.gotoTarget : ls.statement;
6714 return target;
6717 private
6718 ThrownExceptionExp chainExceptions(ThrownExceptionExp oldest, ThrownExceptionExp newest)
6720 debug (LOG)
6722 printf("Collided exceptions %s %s\n", oldest.thrown.toChars(), newest.thrown.toChars());
6724 // Little sanity check to make sure it's really a Throwable
6725 ClassReferenceExp boss = oldest.thrown;
6726 const next = 5; // index of Throwable.next
6727 assert((*boss.value.elements)[next].type.ty == Tclass); // Throwable.next
6728 ClassReferenceExp collateral = newest.thrown;
6729 if (collateral.originalClass().isErrorException() && !boss.originalClass().isErrorException())
6731 /* Find the index of the Error.bypassException field
6733 auto bypass = next + 1;
6734 if ((*collateral.value.elements)[bypass].type.ty == Tuns32)
6735 bypass += 1; // skip over _refcount field
6736 assert((*collateral.value.elements)[bypass].type.ty == Tclass);
6738 // The new exception bypass the existing chain
6739 (*collateral.value.elements)[bypass] = boss;
6740 return newest;
6742 while ((*boss.value.elements)[next].op == EXP.classReference)
6744 boss = (*boss.value.elements)[next].isClassReferenceExp();
6746 (*boss.value.elements)[next] = collateral;
6747 return oldest;
6751 * All results destined for use outside of CTFE need to have their CTFE-specific
6752 * features removed.
6753 * In particular,
6754 * 1. all slices must be resolved.
6755 * 2. all .ownedByCtfe set to OwnedBy.code
6757 private Expression scrubReturnValue(const ref Loc loc, Expression e)
6759 /* Returns: true if e is void,
6760 * or is an array literal or struct literal of void elements.
6762 static bool isVoid(const Expression e, bool checkArrayType = false) pure
6764 if (e.op == EXP.void_)
6765 return true;
6767 static bool isEntirelyVoid(const Expressions* elems)
6769 foreach (e; *elems)
6771 // It can be NULL for performance reasons,
6772 // see StructLiteralExp::interpret().
6773 if (e && !isVoid(e))
6774 return false;
6776 return true;
6779 if (auto sle = e.isStructLiteralExp())
6780 return isEntirelyVoid(sle.elements);
6782 if (checkArrayType && e.type.ty != Tsarray)
6783 return false;
6785 if (auto ale = e.isArrayLiteralExp())
6786 return isEntirelyVoid(ale.elements);
6788 return false;
6792 /* Scrub all elements of elems[].
6793 * Returns: null for success, error Expression for failure
6795 Expression scrubArray(Expressions* elems, bool structlit = false)
6797 foreach (ref e; *elems)
6799 // It can be NULL for performance reasons,
6800 // see StructLiteralExp::interpret().
6801 if (!e)
6802 continue;
6804 // A struct .init may contain void members.
6805 // Static array members are a weird special case https://issues.dlang.org/show_bug.cgi?id=10994
6806 if (structlit && isVoid(e, true))
6808 e = null;
6810 else
6812 e = scrubReturnValue(loc, e);
6813 if (CTFEExp.isCantExp(e) || e.op == EXP.error)
6814 return e;
6817 return null;
6820 Expression scrubSE(StructLiteralExp sle)
6822 sle.ownedByCtfe = OwnedBy.code;
6823 if (!(sle.stageflags & stageScrub))
6825 const old = sle.stageflags;
6826 sle.stageflags |= stageScrub; // prevent infinite recursion
6827 if (auto ex = scrubArray(sle.elements, true))
6828 return ex;
6829 sle.stageflags = old;
6831 return null;
6834 if (e.op == EXP.classReference)
6836 StructLiteralExp sle = e.isClassReferenceExp().value;
6837 if (auto ex = scrubSE(sle))
6838 return ex;
6840 else if (auto vie = e.isVoidInitExp())
6842 error(loc, "uninitialized variable `%s` cannot be returned from CTFE", vie.var.toChars());
6843 return ErrorExp.get();
6846 e = resolveSlice(e);
6848 if (auto sle = e.isStructLiteralExp())
6850 if (auto ex = scrubSE(sle))
6851 return ex;
6853 else if (auto se = e.isStringExp())
6855 se.ownedByCtfe = OwnedBy.code;
6857 else if (auto ale = e.isArrayLiteralExp())
6859 ale.ownedByCtfe = OwnedBy.code;
6860 if (auto ex = scrubArray(ale.elements))
6861 return ex;
6863 else if (auto aae = e.isAssocArrayLiteralExp())
6865 aae.ownedByCtfe = OwnedBy.code;
6866 if (auto ex = scrubArray(aae.keys))
6867 return ex;
6868 if (auto ex = scrubArray(aae.values))
6869 return ex;
6870 aae.type = toBuiltinAAType(aae.type);
6872 else if (auto ve = e.isVectorExp())
6874 ve.ownedByCtfe = OwnedBy.code;
6875 if (auto ale = ve.e1.isArrayLiteralExp())
6877 ale.ownedByCtfe = OwnedBy.code;
6878 if (auto ex = scrubArray(ale.elements))
6879 return ex;
6882 return e;
6885 /**************************************
6886 * Transitively set all .ownedByCtfe to OwnedBy.cache
6888 private Expression scrubCacheValue(Expression e)
6890 if (!e)
6891 return e;
6893 Expression scrubArrayCache(Expressions* elems)
6895 foreach (ref e; *elems)
6896 e = scrubCacheValue(e);
6897 return null;
6900 Expression scrubSE(StructLiteralExp sle)
6902 sle.ownedByCtfe = OwnedBy.cache;
6903 if (!(sle.stageflags & stageScrub))
6905 const old = sle.stageflags;
6906 sle.stageflags |= stageScrub; // prevent infinite recursion
6907 if (auto ex = scrubArrayCache(sle.elements))
6908 return ex;
6909 sle.stageflags = old;
6911 return null;
6914 if (e.op == EXP.classReference)
6916 if (auto ex = scrubSE(e.isClassReferenceExp().value))
6917 return ex;
6919 else if (auto sle = e.isStructLiteralExp())
6921 if (auto ex = scrubSE(sle))
6922 return ex;
6924 else if (auto se = e.isStringExp())
6926 se.ownedByCtfe = OwnedBy.cache;
6928 else if (auto ale = e.isArrayLiteralExp())
6930 ale.ownedByCtfe = OwnedBy.cache;
6931 if (Expression ex = scrubArrayCache(ale.elements))
6932 return ex;
6934 else if (auto aae = e.isAssocArrayLiteralExp())
6936 aae.ownedByCtfe = OwnedBy.cache;
6937 if (auto ex = scrubArrayCache(aae.keys))
6938 return ex;
6939 if (auto ex = scrubArrayCache(aae.values))
6940 return ex;
6942 else if (auto ve = e.isVectorExp())
6944 ve.ownedByCtfe = OwnedBy.cache;
6945 if (auto ale = ve.e1.isArrayLiteralExp())
6947 ale.ownedByCtfe = OwnedBy.cache;
6948 if (auto ex = scrubArrayCache(ale.elements))
6949 return ex;
6952 return e;
6955 /********************************************
6956 * Transitively replace all Expressions allocated in ctfeGlobals.region
6957 * with Mem owned copies.
6958 * Params:
6959 * e = possible ctfeGlobals.region owned expression
6960 * Returns:
6961 * Mem owned expression
6963 private Expression copyRegionExp(Expression e)
6965 if (!e)
6966 return e;
6968 static void copyArray(Expressions* elems)
6970 foreach (ref e; *elems)
6972 auto ex = e;
6973 e = null;
6974 e = copyRegionExp(ex);
6978 static void copySE(StructLiteralExp sle)
6980 if (1 || !(sle.stageflags & stageScrub))
6982 const old = sle.stageflags;
6983 sle.stageflags |= stageScrub; // prevent infinite recursion
6984 copyArray(sle.elements);
6985 sle.stageflags = old;
6989 switch (e.op)
6991 case EXP.classReference:
6993 auto cre = e.isClassReferenceExp();
6994 cre.value = copyRegionExp(cre.value).isStructLiteralExp();
6995 break;
6998 case EXP.structLiteral:
7000 auto sle = e.isStructLiteralExp();
7002 /* The following is to take care of updating sle.origin correctly,
7003 * which may have multiple objects pointing to it.
7005 if (sle.isOriginal && !ctfeGlobals.region.contains(cast(void*)sle.origin))
7007 /* This means sle has already been moved out of the region,
7008 * and sle.origin is the new location.
7010 return sle.origin;
7012 copySE(sle);
7013 sle.isOriginal = sle is sle.origin;
7015 auto slec = ctfeGlobals.region.contains(cast(void*)e)
7016 ? e.copy().isStructLiteralExp() // move sle out of region to slec
7017 : sle;
7019 if (ctfeGlobals.region.contains(cast(void*)sle.origin))
7021 auto sleo = sle.origin == sle ? slec : sle.origin.copy().isStructLiteralExp();
7022 sle.origin = sleo;
7023 slec.origin = sleo;
7025 return slec;
7028 case EXP.arrayLiteral:
7030 auto ale = e.isArrayLiteralExp();
7031 ale.basis = copyRegionExp(ale.basis);
7032 copyArray(ale.elements);
7033 break;
7036 case EXP.assocArrayLiteral:
7037 copyArray(e.isAssocArrayLiteralExp().keys);
7038 copyArray(e.isAssocArrayLiteralExp().values);
7039 break;
7041 case EXP.slice:
7043 auto se = e.isSliceExp();
7044 se.e1 = copyRegionExp(se.e1);
7045 se.upr = copyRegionExp(se.upr);
7046 se.lwr = copyRegionExp(se.lwr);
7047 break;
7050 case EXP.tuple:
7052 auto te = e.isTupleExp();
7053 te.e0 = copyRegionExp(te.e0);
7054 copyArray(te.exps);
7055 break;
7058 case EXP.address:
7059 case EXP.delegate_:
7060 case EXP.vector:
7061 case EXP.dotVariable:
7063 UnaExp ue = e.isUnaExp();
7064 ue.e1 = copyRegionExp(ue.e1);
7065 break;
7068 case EXP.index:
7070 BinExp be = e.isBinExp();
7071 be.e1 = copyRegionExp(be.e1);
7072 be.e2 = copyRegionExp(be.e2);
7073 break;
7076 case EXP.this_:
7077 case EXP.super_:
7078 case EXP.variable:
7079 case EXP.type:
7080 case EXP.function_:
7081 case EXP.typeid_:
7082 case EXP.string_:
7083 case EXP.int64:
7084 case EXP.error:
7085 case EXP.float64:
7086 case EXP.complex80:
7087 case EXP.null_:
7088 case EXP.void_:
7089 case EXP.symbolOffset:
7090 break;
7092 case EXP.cantExpression:
7093 case EXP.voidExpression:
7094 case EXP.showCtfeContext:
7095 return e;
7097 default:
7098 printf("e: %s, %s\n", EXPtoString(e.op).ptr, e.toChars());
7099 assert(0);
7102 if (ctfeGlobals.region.contains(cast(void*)e))
7104 return e.copy();
7106 return e;
7109 /******************************* Special Functions ***************************/
7111 private Expression interpret_length(UnionExp* pue, InterState* istate, Expression earg)
7113 //printf("interpret_length()\n");
7114 earg = interpret(pue, earg, istate);
7115 if (exceptionOrCantInterpret(earg))
7116 return earg;
7117 dinteger_t len = 0;
7118 if (auto aae = earg.isAssocArrayLiteralExp())
7119 len = aae.keys.length;
7120 else
7121 assert(earg.op == EXP.null_);
7122 emplaceExp!(IntegerExp)(pue, earg.loc, len, Type.tsize_t);
7123 return pue.exp();
7126 private Expression interpret_keys(UnionExp* pue, InterState* istate, Expression earg, Type returnType)
7128 debug (LOG)
7130 printf("interpret_keys()\n");
7132 earg = interpret(pue, earg, istate);
7133 if (exceptionOrCantInterpret(earg))
7134 return earg;
7135 if (earg.op == EXP.null_)
7137 emplaceExp!(NullExp)(pue, earg.loc, earg.type);
7138 return pue.exp();
7140 if (earg.op != EXP.assocArrayLiteral && earg.type.toBasetype().ty != Taarray)
7141 return null;
7142 AssocArrayLiteralExp aae = earg.isAssocArrayLiteralExp();
7143 auto ae = ctfeEmplaceExp!ArrayLiteralExp(aae.loc, returnType, aae.keys);
7144 ae.ownedByCtfe = aae.ownedByCtfe;
7145 *pue = copyLiteral(ae);
7146 return pue.exp();
7149 private Expression interpret_values(UnionExp* pue, InterState* istate, Expression earg, Type returnType)
7151 debug (LOG)
7153 printf("interpret_values()\n");
7155 earg = interpret(pue, earg, istate);
7156 if (exceptionOrCantInterpret(earg))
7157 return earg;
7158 if (earg.op == EXP.null_)
7160 emplaceExp!(NullExp)(pue, earg.loc, earg.type);
7161 return pue.exp();
7163 if (earg.op != EXP.assocArrayLiteral && earg.type.toBasetype().ty != Taarray)
7164 return null;
7165 auto aae = earg.isAssocArrayLiteralExp();
7166 auto ae = ctfeEmplaceExp!ArrayLiteralExp(aae.loc, returnType, aae.values);
7167 ae.ownedByCtfe = aae.ownedByCtfe;
7168 //printf("result is %s\n", e.toChars());
7169 *pue = copyLiteral(ae);
7170 return pue.exp();
7173 private Expression interpret_dup(UnionExp* pue, InterState* istate, Expression earg)
7175 debug (LOG)
7177 printf("interpret_dup()\n");
7179 earg = interpret(pue, earg, istate);
7180 if (exceptionOrCantInterpret(earg))
7181 return earg;
7182 if (earg.op == EXP.null_)
7184 emplaceExp!(NullExp)(pue, earg.loc, earg.type);
7185 return pue.exp();
7187 if (earg.op != EXP.assocArrayLiteral && earg.type.toBasetype().ty != Taarray)
7188 return null;
7189 auto aae = copyLiteral(earg).copy().isAssocArrayLiteralExp();
7190 for (size_t i = 0; i < aae.keys.length; i++)
7192 if (Expression e = evaluatePostblit(istate, (*aae.keys)[i]))
7193 return e;
7194 if (Expression e = evaluatePostblit(istate, (*aae.values)[i]))
7195 return e;
7197 aae.type = earg.type.mutableOf(); // repaint type from const(int[int]) to const(int)[int]
7198 //printf("result is %s\n", aae.toChars());
7199 return aae;
7202 // signature is int delegate(ref Value) OR int delegate(ref Key, ref Value)
7203 private Expression interpret_aaApply(UnionExp* pue, InterState* istate, Expression aa, Expression deleg)
7205 aa = interpret(aa, istate);
7206 if (exceptionOrCantInterpret(aa))
7207 return aa;
7208 if (aa.op != EXP.assocArrayLiteral)
7210 emplaceExp!(IntegerExp)(pue, deleg.loc, 0, Type.tsize_t);
7211 return pue.exp();
7214 FuncDeclaration fd = null;
7215 Expression pthis = null;
7216 if (auto de = deleg.isDelegateExp())
7218 fd = de.func;
7219 pthis = de.e1;
7221 else if (auto fe = deleg.isFuncExp())
7222 fd = fe.fd;
7224 assert(fd && fd.fbody);
7225 assert(fd.parameters);
7226 size_t numParams = fd.parameters.length;
7227 assert(numParams == 1 || numParams == 2);
7229 Parameter fparam = fd.type.isTypeFunction().parameterList[numParams - 1];
7230 const wantRefValue = fparam.isReference();
7232 Expressions args = Expressions(numParams);
7234 AssocArrayLiteralExp ae = aa.isAssocArrayLiteralExp();
7235 if (!ae.keys || ae.keys.length == 0)
7236 return ctfeEmplaceExp!IntegerExp(deleg.loc, 0, Type.tsize_t);
7237 Expression eresult;
7239 for (size_t i = 0; i < ae.keys.length; ++i)
7241 Expression ekey = (*ae.keys)[i];
7242 Expression evalue = (*ae.values)[i];
7243 if (wantRefValue)
7245 Type t = evalue.type;
7246 evalue = ctfeEmplaceExp!IndexExp(deleg.loc, ae, ekey);
7247 evalue.type = t;
7249 args[numParams - 1] = evalue;
7250 if (numParams == 2)
7251 args[0] = ekey;
7253 UnionExp ue = void;
7254 eresult = interpretFunction(&ue, fd, istate, &args, pthis);
7255 if (eresult == ue.exp())
7256 eresult = ue.copy();
7257 if (exceptionOrCantInterpret(eresult))
7258 return eresult;
7260 if (eresult.isIntegerExp().getInteger() != 0)
7261 return eresult;
7263 return eresult;
7266 /* Decoding UTF strings for foreach loops. Duplicates the functionality of
7267 * the twelve _aApplyXXn functions in aApply.d in the runtime.
7269 private Expression foreachApplyUtf(UnionExp* pue, InterState* istate, Expression str, Expression deleg, bool rvs)
7271 debug (LOG)
7273 printf("foreachApplyUtf(%s, %s)\n", str.toChars(), deleg.toChars());
7275 FuncDeclaration fd = null;
7276 Expression pthis = null;
7277 if (auto de = deleg.isDelegateExp())
7279 fd = de.func;
7280 pthis = de.e1;
7282 else if (auto fe = deleg.isFuncExp())
7283 fd = fe.fd;
7285 assert(fd && fd.fbody);
7286 assert(fd.parameters);
7287 size_t numParams = fd.parameters.length;
7288 assert(numParams == 1 || numParams == 2);
7289 Type charType = (*fd.parameters)[numParams - 1].type;
7290 Type indexType = numParams == 2 ? (*fd.parameters)[0].type : Type.tsize_t;
7291 size_t len = cast(size_t)resolveArrayLength(str);
7292 if (len == 0)
7294 emplaceExp!(IntegerExp)(pue, deleg.loc, 0, indexType);
7295 return pue.exp();
7298 UnionExp strTmp = void;
7299 str = resolveSlice(str, &strTmp);
7301 auto se = str.isStringExp();
7302 auto ale = str.isArrayLiteralExp();
7303 if (!se && !ale)
7305 error(str.loc, "CTFE internal error: cannot foreach `%s`", str.toChars());
7306 return CTFEExp.cantexp;
7308 Expressions args = Expressions(numParams);
7310 Expression eresult = null; // ded-store to prevent spurious warning
7312 // Buffers for encoding; also used for decoding array literals
7313 char[4] utf8buf = void;
7314 wchar[2] utf16buf = void;
7316 size_t start = rvs ? len : 0;
7317 size_t end = rvs ? 0 : len;
7318 for (size_t indx = start; indx != end;)
7320 // Step 1: Decode the next dchar from the string.
7322 string errmsg = null; // Used for reporting decoding errors
7323 dchar rawvalue; // Holds the decoded dchar
7324 size_t currentIndex = indx; // The index of the decoded character
7326 if (ale)
7328 // If it is an array literal, copy the code points into the buffer
7329 size_t buflen = 1; // #code points in the buffer
7330 size_t n = 1; // #code points in this char
7331 size_t sz = cast(size_t)ale.type.nextOf().size();
7333 switch (sz)
7335 case 1:
7336 if (rvs)
7338 // find the start of the string
7339 --indx;
7340 buflen = 1;
7341 while (indx > 0 && buflen < 4)
7343 Expression r = (*ale.elements)[indx];
7344 char x = cast(char)r.isIntegerExp().getInteger();
7345 if ((x & 0xC0) != 0x80)
7346 break;
7347 --indx;
7348 ++buflen;
7351 else
7352 buflen = (indx + 4 > len) ? len - indx : 4;
7353 for (size_t i = 0; i < buflen; ++i)
7355 Expression r = (*ale.elements)[indx + i];
7356 utf8buf[i] = cast(char)r.isIntegerExp().getInteger();
7358 n = 0;
7359 errmsg = utf_decodeChar(utf8buf[0 .. buflen], n, rawvalue);
7360 break;
7362 case 2:
7363 if (rvs)
7365 // find the start of the string
7366 --indx;
7367 buflen = 1;
7368 Expression r = (*ale.elements)[indx];
7369 ushort x = cast(ushort)r.isIntegerExp().getInteger();
7370 if (indx > 0 && x >= 0xDC00 && x <= 0xDFFF)
7372 --indx;
7373 ++buflen;
7376 else
7377 buflen = (indx + 2 > len) ? len - indx : 2;
7378 for (size_t i = 0; i < buflen; ++i)
7380 Expression r = (*ale.elements)[indx + i];
7381 utf16buf[i] = cast(ushort)r.isIntegerExp().getInteger();
7383 n = 0;
7384 errmsg = utf_decodeWchar(utf16buf[0 .. buflen], n, rawvalue);
7385 break;
7387 case 4:
7389 if (rvs)
7390 --indx;
7391 Expression r = (*ale.elements)[indx];
7392 rawvalue = cast(dchar)r.isIntegerExp().getInteger();
7393 n = 1;
7395 break;
7397 default:
7398 assert(0);
7400 if (!rvs)
7401 indx += n;
7403 else
7405 // String literals
7406 size_t saveindx; // used for reverse iteration
7408 switch (se.sz)
7410 case 1:
7412 if (rvs)
7414 // find the start of the string
7415 --indx;
7416 while (indx > 0 && ((se.getCodeUnit(indx) & 0xC0) == 0x80))
7417 --indx;
7418 saveindx = indx;
7420 auto slice = se.peekString();
7421 errmsg = utf_decodeChar(slice, indx, rawvalue);
7422 if (rvs)
7423 indx = saveindx;
7424 break;
7427 case 2:
7428 if (rvs)
7430 // find the start
7431 --indx;
7432 auto wc = se.getCodeUnit(indx);
7433 if (wc >= 0xDC00 && wc <= 0xDFFF)
7434 --indx;
7435 saveindx = indx;
7437 const slice = se.peekWstring();
7438 errmsg = utf_decodeWchar(slice, indx, rawvalue);
7439 if (rvs)
7440 indx = saveindx;
7441 break;
7443 case 4:
7444 if (rvs)
7445 --indx;
7446 rawvalue = se.getCodeUnit(indx);
7447 if (!rvs)
7448 ++indx;
7449 break;
7451 default:
7452 assert(0);
7455 if (errmsg)
7457 error(deleg.loc, "`%.*s`", cast(int)errmsg.length, errmsg.ptr);
7458 return CTFEExp.cantexp;
7461 // Step 2: encode the dchar in the target encoding
7463 int charlen = 1; // How many codepoints are involved?
7464 switch (charType.size())
7466 case 1:
7467 charlen = utf_codeLengthChar(rawvalue);
7468 utf_encodeChar(&utf8buf[0], rawvalue);
7469 break;
7470 case 2:
7471 charlen = utf_codeLengthWchar(rawvalue);
7472 utf_encodeWchar(&utf16buf[0], rawvalue);
7473 break;
7474 case 4:
7475 break;
7476 default:
7477 assert(0);
7479 if (rvs)
7480 currentIndex = indx;
7482 // Step 3: call the delegate once for each code point
7484 // The index only needs to be set once
7485 if (numParams == 2)
7486 args[0] = ctfeEmplaceExp!IntegerExp(deleg.loc, currentIndex, indexType);
7488 Expression val = null;
7490 foreach (k; 0 .. charlen)
7492 dchar codepoint;
7493 switch (charType.size())
7495 case 1:
7496 codepoint = utf8buf[k];
7497 break;
7498 case 2:
7499 codepoint = utf16buf[k];
7500 break;
7501 case 4:
7502 codepoint = rawvalue;
7503 break;
7504 default:
7505 assert(0);
7507 val = ctfeEmplaceExp!IntegerExp(str.loc, codepoint, charType);
7509 args[numParams - 1] = val;
7511 UnionExp ue = void;
7512 eresult = interpretFunction(&ue, fd, istate, &args, pthis);
7513 if (eresult == ue.exp())
7514 eresult = ue.copy();
7515 if (exceptionOrCantInterpret(eresult))
7516 return eresult;
7517 if (eresult.isIntegerExp().getInteger() != 0)
7518 return eresult;
7521 return eresult;
7524 /* If this is a built-in function, return the interpreted result,
7525 * Otherwise, return NULL.
7527 private Expression evaluateIfBuiltin(UnionExp* pue, InterState* istate, const ref Loc loc, FuncDeclaration fd, Expressions* arguments, Expression pthis)
7529 Expression e = null;
7530 size_t nargs = arguments ? arguments.length : 0;
7531 if (!pthis)
7533 if (isBuiltin(fd) != BUILTIN.unimp)
7535 Expressions args = Expressions(nargs);
7536 foreach (i, ref arg; args)
7538 Expression earg = (*arguments)[i];
7539 earg = interpret(earg, istate);
7540 if (exceptionOrCantInterpret(earg))
7541 return earg;
7542 arg = earg;
7544 e = eval_builtin(loc, fd, &args);
7545 if (!e)
7547 error(loc, "cannot evaluate unimplemented builtin `%s` at compile time", fd.toChars());
7548 e = CTFEExp.cantexp;
7552 if (!pthis)
7554 if (nargs == 1 || nargs == 3)
7556 Expression firstarg = (*arguments)[0];
7557 if (auto firstAAtype = firstarg.type.toBasetype().isTypeAArray())
7559 const id = fd.ident;
7560 if (nargs == 1)
7562 if (id == Id.aaLen)
7563 return interpret_length(pue, istate, firstarg);
7565 if (fd.toParent2().ident == Id.object)
7567 if (id == Id.keys)
7568 return interpret_keys(pue, istate, firstarg, firstAAtype.index.arrayOf());
7569 if (id == Id.values)
7570 return interpret_values(pue, istate, firstarg, firstAAtype.nextOf().arrayOf());
7571 if (id == Id.rehash)
7572 return interpret(pue, firstarg, istate);
7573 if (id == Id.dup)
7574 return interpret_dup(pue, istate, firstarg);
7577 else // (nargs == 3)
7579 if (id == Id._aaApply)
7580 return interpret_aaApply(pue, istate, firstarg, (*arguments)[2]);
7581 if (id == Id._aaApply2)
7582 return interpret_aaApply(pue, istate, firstarg, (*arguments)[2]);
7587 if (pthis && !fd.fbody && fd.isCtorDeclaration() && fd.parent && fd.parent.parent && fd.parent.parent.ident == Id.object)
7589 if (pthis.op == EXP.classReference && fd.parent.ident == Id.Throwable)
7591 // At present, the constructors just copy their arguments into the struct.
7592 // But we might need some magic if stack tracing gets added to druntime.
7593 StructLiteralExp se = pthis.isClassReferenceExp().value;
7594 assert(arguments.length <= se.elements.length);
7595 foreach (i, arg; *arguments)
7597 auto elem = interpret(arg, istate);
7598 if (exceptionOrCantInterpret(elem))
7599 return elem;
7600 (*se.elements)[i] = elem;
7602 return CTFEExp.voidexp;
7605 if (nargs == 1 && !pthis && (fd.ident == Id.criticalenter || fd.ident == Id.criticalexit))
7607 // Support synchronized{} as a no-op
7608 return CTFEExp.voidexp;
7610 if (!pthis)
7612 const idlen = fd.ident.toString().length;
7613 const id = fd.ident.toChars();
7614 if (nargs == 2 && (idlen == 10 || idlen == 11) && !strncmp(id, "_aApply", 7))
7616 // Functions from aApply.d and aApplyR.d in the runtime
7617 bool rvs = (idlen == 11); // true if foreach_reverse
7618 char c = id[idlen - 3]; // char width: 'c', 'w', or 'd'
7619 char s = id[idlen - 2]; // string width: 'c', 'w', or 'd'
7620 char n = id[idlen - 1]; // numParams: 1 or 2.
7621 // There are 12 combinations
7622 if ((n == '1' || n == '2') &&
7623 (c == 'c' || c == 'w' || c == 'd') &&
7624 (s == 'c' || s == 'w' || s == 'd') &&
7625 c != s)
7627 Expression str = (*arguments)[0];
7628 str = interpret(str, istate);
7629 if (exceptionOrCantInterpret(str))
7630 return str;
7631 return foreachApplyUtf(pue, istate, str, (*arguments)[1], rvs);
7635 return e;
7638 private Expression evaluatePostblit(InterState* istate, Expression e)
7640 auto ts = e.type.baseElemOf().isTypeStruct();
7641 if (!ts)
7642 return null;
7643 StructDeclaration sd = ts.sym;
7644 if (!sd.postblit)
7645 return null;
7647 if (auto ale = e.isArrayLiteralExp())
7649 foreach (elem; *ale.elements)
7651 if (auto ex = evaluatePostblit(istate, elem))
7652 return ex;
7654 return null;
7656 if (e.op == EXP.structLiteral)
7658 // e.__postblit()
7659 UnionExp ue = void;
7660 e = interpretFunction(&ue, sd.postblit, istate, null, e);
7661 if (e == ue.exp())
7662 e = ue.copy();
7663 if (exceptionOrCantInterpret(e))
7664 return e;
7665 return null;
7667 assert(0);
7670 private Expression evaluateDtor(InterState* istate, Expression e)
7672 auto ts = e.type.baseElemOf().isTypeStruct();
7673 if (!ts)
7674 return null;
7675 StructDeclaration sd = ts.sym;
7676 if (!sd.dtor)
7677 return null;
7679 UnionExp ue = void;
7680 if (auto ale = e.isArrayLiteralExp())
7682 foreach_reverse (elem; *ale.elements)
7683 e = evaluateDtor(istate, elem);
7685 else if (e.op == EXP.structLiteral)
7687 // e.__dtor()
7688 e = interpretFunction(&ue, sd.dtor, istate, null, e);
7690 else
7691 assert(0);
7692 if (exceptionOrCantInterpret(e))
7694 if (e == ue.exp())
7695 e = ue.copy();
7696 return e;
7698 return null;
7701 /*************************** CTFE Sanity Checks ***************************/
7702 /* Setter functions for CTFE variable values.
7703 * These functions exist to check for compiler CTFE bugs.
7705 private bool hasValue(VarDeclaration vd)
7707 return vd.ctfeAdrOnStack != VarDeclaration.AdrOnStackNone &&
7708 getValue(vd) !is null;
7711 // Don't check for validity
7712 private void setValueWithoutChecking(VarDeclaration vd, Expression newval)
7714 ctfeGlobals.stack.setValue(vd, newval);
7717 private void setValue(VarDeclaration vd, Expression newval)
7719 //printf("setValue() vd: %s newval: %s\n", vd.toChars(), newval.toChars());
7720 version (none)
7722 if (!((vd.storage_class & (STC.out_ | STC.ref_)) ? isCtfeReferenceValid(newval) : isCtfeValueValid(newval)))
7724 printf("[%s] vd = %s %s, newval = %s\n", vd.loc.toChars(), vd.type.toChars(), vd.toChars(), newval.toChars());
7727 assert((vd.storage_class & (STC.out_ | STC.ref_)) ? isCtfeReferenceValid(newval) : isCtfeValueValid(newval));
7728 ctfeGlobals.stack.setValue(vd, newval);
7732 * Removes `_d_HookTraceImpl` if found from `ce` and `fd`.
7733 * This is needed for the CTFE interception code to be able to find hooks that are called though the hook's `*Trace`
7734 * wrapper.
7736 * This is done by replacing `_d_HookTraceImpl!(T, Hook, errMsg)(..., parameters)` with `Hook(parameters)`.
7737 * Parameters:
7738 * ce = The CallExp that possible will be be replaced
7739 * fd = Fully resolve function declaration that `ce` would call
7741 private void removeHookTraceImpl(ref CallExp ce, ref FuncDeclaration fd)
7743 if (fd.ident != Id._d_HookTraceImpl)
7744 return;
7746 auto oldCE = ce;
7748 // Get the Hook from the second template parameter
7749 TemplateInstance templateInstance = fd.parent.isTemplateInstance;
7750 RootObject hook = (*templateInstance.tiargs)[1];
7751 assert(hook.isDsymbol(), "Expected _d_HookTraceImpl's second template parameter to be an alias to the hook!");
7752 fd = (cast(Dsymbol)hook).isFuncDeclaration;
7754 // Remove the first three trace parameters
7755 auto arguments = new Expressions();
7756 arguments.reserve(ce.arguments.length - 3);
7757 arguments.pushSlice((*ce.arguments)[3 .. $]);
7759 ce = ctfeEmplaceExp!CallExp(ce.loc, ctfeEmplaceExp!VarExp(ce.loc, fd, false), arguments);
7761 if (global.params.v.verbose)
7762 message("strip %s =>\n %s", oldCE.toChars(), ce.toChars());