1 // Copyright (c) 2010, 2011  Per M.A. Bothner.
2 // This is free software; for terms and warranty disclaimer see ../../COPYING.
3 
4 package gnu.expr;
5 import gnu.bytecode.*;
6 import gnu.kawa.reflect.CompileReflect;
7 import gnu.kawa.reflect.LazyType;
8 import gnu.kawa.reflect.Invoke;
9 import gnu.kawa.functions.Convert;
10 import gnu.kawa.util.IdentityHashTable;
11 import gnu.mapping.*;
12 import gnu.math.DFloNum;
13 import gnu.math.IntNum;
14 import gnu.math.BitOps;
15 import gnu.text.Char;
16 
17 import java.lang.reflect.InvocationTargetException;
18 
19 import gnu.kawa.functions.MakePromise;
20 import gnu.kawa.lispexpr.LangPrimType;
21 import gnu.lists.EmptyList;
22 import gnu.lists.PairWithPosition;
23 import gnu.lists.SimpleVector;
24 
25 import java.util.List;
26 import java.util.HashMap;
27 import java.lang.reflect.Proxy;
28 import java.lang.annotation.ElementType;
29 /* #ifdef use:java.lang.invoke */
30 import java.lang.invoke.*;
31 /* #else */
32 // import gnu.mapping.CallContext.MethodHandle;
33 /* #endif */
34 
35 /**
36  * The main Expression re-writing pass.
37  * This pass handles type-checking (work in progress).
38  * Also checks for calls to known Procedures, and may call
39  * a procedure-specific handler, which may do inlining, constant-folding,
40  * error-checking, and general munging.
41  *
42  * Should perhaps rename to something like "Validate" since
43  * we do type-checking and other stuff beyond inlining.
44  */
45 
46 public class InlineCalls extends ExpExpVisitor<Type> {
47 
48     public static ThreadLocal<InlineCalls> currentVisitor
49         = new ThreadLocal<InlineCalls>();
50 
inlineCalls(Expression exp, Compilation comp)51     public static Expression inlineCalls (Expression exp, Compilation comp) {
52         InlineCalls visitor = new InlineCalls(comp);
53         InlineCalls saved = currentVisitor.get(); // normally null
54         try {
55             currentVisitor.set(visitor);
56             return visitor.visit(exp, null);
57         } finally {
58             currentVisitor.set(saved);
59         }
60     }
61 
InlineCalls(Compilation comp)62     public InlineCalls (Compilation comp) {
63         setContext(comp);
64     }
65 
66     VarValueTracker valueTracker = new VarValueTracker(this);
67 
visit(Expression exp, Type required)68     public Expression visit(Expression exp, Type required) {
69         Expression exp0 = exp;
70         if (! exp.getFlag(Expression.VALIDATED)) {
71             exp.setFlag(Expression.VALIDATED); // Protect against cycles.
72             exp = ExpVisitor.visit(this, exp, required);
73             exp.setFlag(Expression.VALIDATED);
74         }
75         if (required == ProcedureInCallContext.INSTANCE)
76           required = null;
77         if (required instanceof ValueNeededType && exp.getType().isVoid()) {
78             if (exp == QuoteExp.voidExp)
79               return QuoteExp.voidObjectExp;
80             if (comp.warnVoidUsed())
81                 comp.error('w', "void-valued expression where value is needed",
82                        exp0);
83             // To avoid cascading warnings.
84             return new BeginExp(exp, QuoteExp.nullExp);
85         }
86         return checkType(exp, required);
87     }
88 
isCompatibleWithValue(Type required, Type expType)89     public static int isCompatibleWithValue(Type required, Type expType) {
90         if (required == null || expType == Type.neverReturnsType
91             || required == Type.neverReturnsType)
92             return 1;
93         if (expType instanceof LazyType && ! LazyType.maybeLazy(required))
94             expType = ((LazyType) expType).getValueType();
95         return required.isCompatibleWithValue(expType);
96     }
97 
checkType(Expression exp, Type required)98     public Expression checkType(Expression exp, Type required) {
99         Type expType = exp.getType();
100         if (expType == Type.toStringType)
101             expType = Type.javalangStringType;
102         int cmp = isCompatibleWithValue(required, expType);
103         if (cmp < 0
104             || (cmp == 0 && required.isInterface()
105                 && (exp instanceof QuoteExp || exp instanceof LambdaExp))) {
106             if (exp instanceof LambdaExp
107                 && (required instanceof ClassType
108                     || required instanceof ParameterizedType)) {
109                 ClassType reqraw = required instanceof ParameterizedType ? ((ParameterizedType) required).getRawType() : (ClassType) required;
110                 Method amethod = reqraw.checkSingleAbstractMethod();
111                 if (amethod != null) {
112                     if (! ModuleExp.compilerAvailable()) {
113                         if (! reqraw.isInterface())
114                             comp.error('e', "cannot convert procedure to abstract class "+reqraw.getClass().getName()+" without bytecode compiler");
115                         Class iface;
116                         try {
117                             iface = reqraw.getReflectClass();
118                         }
119                         catch (Exception ex) {
120                             iface = null;
121                         }
122                         if (iface == null)
123                             comp.error('e', "cannot find interface "+reqraw.getClass().getName());
124                         Method makeProxy =
125                             ClassType.make("gnu.kawa.reflect.ProceduralProxy")
126                             .getDeclaredMethod("makeProxy", 2);
127                         Expression[] args = {QuoteExp.getInstance(iface), exp};
128                         return visit(new ApplyExp(makeProxy, args), required);
129                     }
130                     LambdaExp lexp = (LambdaExp) exp;
131                     ObjectExp oexp = new ObjectExp();
132                     oexp.setLocation(exp);
133                     oexp.supers = new Expression[] { new QuoteExp(required) };
134                     oexp.setTypes(getCompilation());
135                     Object mname = amethod.getName();
136                     oexp.addMethod(lexp, mname);
137                     Declaration mdecl = oexp.addDeclaration(mname, Compilation.typeProcedure);
138                     oexp.firstChild = lexp;
139                     oexp.declareParts(comp);
140                     return visit(oexp, required);
141                 }
142             }
143             if (required instanceof TypeValue) {
144                 Expression converted = ((TypeValue) required).convertValue(exp);
145                 if (converted != null)
146                     return converted;
147             }
148 
149             Language language = comp.getLanguage();
150             comp.error(processingAnnotations() ? 'e' : 'w',
151                        ("type "+language.formatType(expType)
152                         +" is incompatible with required type "
153                         +language.formatType(required)),
154                        exp);
155 
156             // Box if needed to force a run-time ClassCastException.
157             if (required instanceof PrimType)
158                 required = ((PrimType) required).boxedType();
159             // Creating an explicit coercion avoids cascading error messages.
160             ApplyExp expb =
161                 Compilation.makeCoercion(exp, required);
162             expb.setType(required);
163             expb.setFlag(Expression.VALIDATED);
164             return expb;
165         }
166         return exp;
167     }
168 
setCanAccess(LambdaExp exp, Type required)169     private void setCanAccess(LambdaExp exp, Type required) {
170         if (required != ProcedureInCallContext.INSTANCE)
171             exp.setCanRead(true);
172     }
173 
visitApplyExp(ApplyExp exp, Type required)174     protected Expression visitApplyExp(ApplyExp exp, Type required) {
175         Expression func = exp.func;
176         // Replace (apply (lambda (param ...) body ...) arg ...)
177         // by: (let ((param arg) ...) body ...).
178         // Note this should be done *before* we visit the lambda, so we can
179         // visit the body with params bound to the known args.
180         if (func instanceof LambdaExp) {
181             // This optimization in principle should be redundant, but leaving
182             // it out currently causes worse type-inference and code generation.
183             Expression inlined = inlineCall((LambdaExp) func, exp, false);
184             if (inlined != null)
185                 return visit(inlined, required);
186         }
187         func = visit(func, typeForCalledFunction(func));
188         exp.func = func;
189         return func.validateApply(exp, this, required, null);
190     }
191 
192     /** Return a required type for procedure application context.
193      * This is ProcedureInCallContext.INSTANCE or null.
194      * The value ProcedureInCallContext.INSTANCE indicates the expression
195      * is used in application context and setCanCall is appropriate.
196      * This means the function expression must be a lambda or reference.
197      * (Consider a function that is an IfExp:  If the required type is
198      * passed down to two branches that are both lambdas, we might think the
199      * lambdas are called but not read and thus safe for inlining - but that
200      * would be false, since we need the If to yield a procedure value.)
201      */
typeForCalledFunction(Expression exp)202     public static Type typeForCalledFunction(Expression exp) {
203         return  (exp instanceof LambdaExp && ! (exp instanceof ClassExp))
204             || exp instanceof ReferenceExp
205             ? ProcedureInCallContext.INSTANCE
206             : null;
207     }
208 
209     /** Visit an ApplyExp assuming function and arguments have been visited. */
visitApplyOnly(ApplyExp exp, Type required)210     public final Expression visitApplyOnly(ApplyExp exp, Type required) {
211         return exp.func.validateApply(exp, this, required, null);
212     }
213 
checkIntValue(Expression exp)214     public static Integer checkIntValue(Expression exp) {
215         if (exp instanceof QuoteExp) {
216             QuoteExp qarg = (QuoteExp) exp;
217             Object value = qarg.getValue();
218             if (! qarg.isExplicitlyTyped() && value instanceof IntNum) {
219                 IntNum ivalue = (IntNum) value;
220                 if (ivalue.inIntRange())
221                     return Integer.valueOf(ivalue.intValue());
222             }
223         }
224         return null;
225     }
226 
checkLongValue(Expression exp)227     public static Long checkLongValue (Expression exp) {
228         if (exp instanceof QuoteExp) {
229             QuoteExp qarg = (QuoteExp) exp;
230             Object value = qarg.getValue();
231             if (! qarg.isExplicitlyTyped() && value instanceof IntNum) {
232                 IntNum ivalue = (IntNum) value;
233                 if (ivalue.inLongRange())
234                     return Long.valueOf(ivalue.longValue());
235             }
236         }
237         return null;
238     }
239 
fixIntValue(Expression exp)240     public QuoteExp fixIntValue (Expression exp) {
241         Integer ival = InlineCalls.checkIntValue(exp);
242         if (ival != null)
243             return new QuoteExp(ival, comp.getLanguage().getTypeFor(Integer.TYPE));
244         return null;
245     }
246 
fixLongValue(Expression exp)247     public QuoteExp fixLongValue(Expression exp) {
248         Long ival = InlineCalls.checkLongValue(exp);
249         if (ival != null)
250             return new QuoteExp(ival, comp.getLanguage().getTypeFor(Long.TYPE));
251         return null;
252     }
253 
visitQuoteExp(QuoteExp exp, Type required)254     protected Expression visitQuoteExp(QuoteExp exp, Type required) {
255         Object value = exp.getValue();
256         if (exp.getRawType() == null
257                 && ! exp.isSharedConstant() && value != null) {
258             Language language = comp.getLanguage();
259             Type vtype = language.getTypeFor(value.getClass());
260             if (vtype == Type.toStringType)
261                 vtype = Type.javalangStringType;
262             exp.type = vtype;
263             Type primRequired;
264             if (! exp.isExplicitlyTyped()) {
265                 if ((primRequired = PrimType.unboxedType(required)) != null) {
266                     char sig1 = primRequired.getSignature().charAt(0);
267                     if (value instanceof IntNum
268                         && primRequired != LangPrimType.characterType
269                         && primRequired != LangPrimType.characterOrEofType) {
270                         IntNum ivalue = (IntNum) value;
271                         Object ival = null;
272                         switch (sig1) {
273                         case 'B':
274                         case 'S':
275                         case 'I':
276                         case 'J':
277                             ival = LangPrimType.convertIntegerLiteral(ivalue,
278                                     (PrimType) primRequired, false);
279                             break;
280                         case 'F':
281                             ival = Float.valueOf(ivalue.floatValue());
282                             break;
283                         case 'D':
284                             ival = Double.valueOf(ivalue.doubleValue());
285                             break;
286                         default:
287                             ivalue = null;
288                         }
289                         if (ival != null)
290                             exp = new QuoteExp(ival, required);
291                         else if (ivalue != null)
292                             error('w', "integer "+ivalue+" not in range of "+required.getName());
293                     }
294                     if (value instanceof DFloNum) {
295                         DFloNum dvalue = (DFloNum) value;
296                         Object dval;
297                         switch (sig1) {
298                         case 'F':
299                             dval = Float.valueOf(dvalue.floatValue());
300                             break;
301                         case 'D':
302                             dval = Double.valueOf(dvalue.doubleValue());
303                             break;
304                         default:
305                             dval = null;
306                         }
307                         if (dval != null)
308                             exp = new QuoteExp(dval, required);
309                         else
310                             error('w', "saw float where "+required.getName()+" expected");
311                     }
312                     if (value instanceof Char) {
313                         if (sig1 == 'C') {
314                             int ival = ((Char) value).intValue();
315                             if (ival >= 0 && ival <= 0xFFFF)
316                                 exp = new QuoteExp(Character.valueOf((char) ival), required);
317                             else
318                                 error('w', "character scalar value "+ival+" not in range of "+required.getName());
319                         } else
320                             exp.setType(LangPrimType.characterType);
321                     }
322 
323                 } else if ((value instanceof IntNum) && required != null &&
324                            "java.math.BigInteger".equals(required.getName())) {
325                     exp = new QuoteExp(((IntNum)value).asBigInteger(), required);
326                 } else if (value instanceof Char) {
327                     exp.setType(LangPrimType.characterType);
328                 }
329             }
330         }
331         return exp;
332     }
333 
visitReferenceExp(ReferenceExp exp, Type required)334     protected Expression visitReferenceExp (ReferenceExp exp, Type required) {
335         Declaration decl = exp.getBinding();
336         if (decl != null && ! exp.getDontDereference()) {
337             IntNum vals = valueTracker.declValueUsage.get(decl);
338             if (vals != null) {
339                 if (VarValueTracker.maybeUninitialized(vals)
340                     && ! decl.getFlag(Declaration.MAYBE_UNINITIALIZED_ACCESS)) {
341                     if (comp.warnUninitialized())
342                         comp.error('w', "variable '"+exp.getName()+"' may be uninitialized here", exp);
343                     decl.setFlag(Declaration.MAYBE_UNINITIALIZED_ACCESS);
344                 }
345             }
346 
347             LambdaExp lval = decl.getLambdaValue();
348             if (lval != null) {
349                 setCanAccess(lval, required);
350                 valueTracker.checkUninitializedVariables(lval, exp, null);
351             }
352             Expression dval = decl.getValue();
353             if (deferableInit(dval) && ! dval.getFlag(Expression.VALIDATED)) {
354                 visit(dval, required);
355             }
356 
357             // Replace references to a void variable (including one whose value
358             // is the empty sequence in XQuery) by an empty constant.  This is
359             // not so much an optimization as avoiding the complications and
360             // paradoxes of variables and expression that are void.
361             Type type = decl.getType();
362             if (type != null && type.isVoid())
363                 return QuoteExp.voidExp;
364         }
365         if (decl != null && decl.getField() == null && ! decl.getCanWrite()
366             && ! exp.getDontDereference()) {
367             Expression dval = decl.getValue();
368             if (dval instanceof QuoteExp && dval != QuoteExp.undefined_exp)
369                 return visitQuoteExp(new QuoteExp(((QuoteExp) dval).getValue(), decl.getType()), required);
370             // We don't want to visit the body of a named function yet.
371             // Though not doing so does hurt optimization.
372             // See testsuite/inlining-test.scm:constant-propagation3
373             if (dval != null && decl.nvalues == 1 && decl.values[0].kind == Declaration.ValueSource.APPLY_KIND) {
374                 dval = null;
375             }
376             if (dval instanceof ReferenceExp && ! decl.isAlias()) {
377                 ReferenceExp rval = (ReferenceExp) dval;
378                 Declaration rdecl = rval.getBinding();
379                 Type dtype = decl.getType();
380                 if (rdecl != null && ! rdecl.getCanWrite()
381                     && (dtype == null || dtype == Type.objectType
382                         // We could also allow (some) widening conversions.
383                         || dtype == rdecl.getType()))
384                     return visitReferenceExp(new ReferenceExp(rval), required);
385             }
386             if (dval instanceof ClassExp && processingAnnotations()) {
387                 ClassExp cval = (ClassExp) dval;
388                 if (cval.compiledType != null)
389                     return new QuoteExp(cval.compiledType, required);
390             }
391             if (! exp.isProcedureName() && decl.isClassMethod()) {
392                 // FIXME.  This shouldn't be that hard to fix.  For example,
393                 // we could treat a reference to a one-argument method foo as if it
394                 // were (lambda (x) (foo x)).  Or we could treat it as (this):foo.
395                 // However, it's a little tricky handling the general case.
396                 // (What about overloading?  Varargs methods?  Static methods?)
397                 comp.error('e', "unimplemented: reference to method "+decl.getName()+" as variable");
398                 comp.error('e', decl, "here is the definition of ", "");
399             }
400         }
401         decl = Declaration.followAliases(decl);
402         if (decl != null) {
403             if (required != ProcedureInCallContext.INSTANCE)
404                 decl.setCanRead(true);
405             else {
406                 decl.setCanCall(true);
407                 // Avoid tricky optimization if we're interpreting.
408                 if (! comp.mustCompile)
409                     decl.setCanRead();
410             }
411             Declaration ctx = exp.contextDecl();
412             if (ctx != null)
413                 ctx.setCanRead(true);
414         }
415         return super.visitReferenceExp(exp, required);
416     }
417 
visitIfExp(IfExp exp, Type required)418     protected Expression visitIfExp(IfExp exp, Type required) {
419         Expression test = exp.test.visit(this, ValueNeededType.instance);
420         if (test instanceof ReferenceExp) {
421             Declaration decl = ((ReferenceExp) test).getBinding();
422             if (decl != null)
423             {
424                 Expression value = decl.getValue();
425                 if (value instanceof QuoteExp && value != QuoteExp.undefined_exp)
426                     test = value;
427             }
428         }
429         // truth: 1 - test is true; 0: test is false; -1 - test is unknown.
430         int truth = ! (test instanceof QuoteExp) ? -1
431             : comp.getLanguage().isTrue(((QuoteExp) test).getValue()) ? 1 : 0;
432         if (truth == 1 || (truth == 0 && exp.else_clause != null))
433             return visit(exp.select(truth != 0), required);
434         exp.test = test;
435         VarValueTracker.forkPush(this);
436         if (exitValue == null)
437             exp.then_clause = visit(exp.then_clause, required);
438         valueTracker.forkNext();
439         if (exitValue == null && exp.else_clause != null)
440             exp.else_clause = visit(exp.else_clause, required);
441         VarValueTracker.forkPop(this);
442         if (exp.else_clause == null && truth <= 0
443             && required instanceof ValueNeededType) {
444             if (comp.warnVoidUsed())
445                 comp.error('w', "missing else where value is required", exp);
446             if (truth == 0)
447                 return QuoteExp.voidObjectExp;
448         }
449         if (test.getType().isVoid()) {
450             boolean voidTrue = comp.getLanguage().isTrue(Values.empty);
451 
452             if (comp.warnVoidUsed())
453                 comp.error('w', "void-valued condition is always "+(truth!=0));
454             return new BeginExp(test, exp.select(voidTrue));
455         }
456         return exp;
457     }
458 
visitBeginExp(BeginExp exp, Type required)459     protected Expression visitBeginExp(BeginExp exp, Type required) {
460         int last = exp.length - 1;
461         for (int i = 0;  i <= last;  i++) {
462             exp.exps[i] = visit(exp.exps[i], i < last ? null : required);
463         }
464         return exp;
465     }
466 
visitCaseExp(CaseExp exp, Type required)467     protected Expression visitCaseExp(CaseExp exp, Type required) {
468         Expression key = exp.key.visit(this, ValueNeededType.instance);
469 
470         // Inline the key when it is a ReferenceExp bound
471         // to a known value (a QuoteExp).
472         if (key instanceof ReferenceExp) {
473             Declaration decl = ((ReferenceExp) key).getBinding();
474             if (decl != null) {
475                 Expression value = decl.getValue();
476                 if (value instanceof QuoteExp
477                         && value != QuoteExp.undefined_exp)
478                     key = value;
479             }
480         }
481         exp.key = key;
482 
483         // replaces a case containing only the default case
484         if (exp.clauses.length == 0) {
485             return new BeginExp(key, visit(exp.elseClause.exp, required));
486         }
487 
488         // type checking for datums
489         Expression lastIncomp = null;
490         int incomps = 0;
491         for (int i = 0; i < exp.clauses.length; i++) {
492             CaseExp.CaseClause clause = exp.clauses[i];
493             for (int j = 0; j < clause.datums.length; j++) {
494                 clause.datums[j] = this.visit(clause.datums[j], null);
495                 Expression dexp = clause.datums[j];
496                 Object d = ((QuoteExp) dexp).getValue();
497                 if (d instanceof SimpleVector
498                         || (!(d instanceof EmptyList) && d instanceof PairWithPosition)) {
499                     comp.error('w', "List and vectors will never be matched in a case clause", dexp);
500                 } else if (d instanceof CharSequence) {
501                     comp.error('w', "a string in a case clause will never match (except another literal)", dexp);
502                 }
503                 Type keyType = key.getType();
504                 Type dtype = dexp.getType();
505                 if (keyType.isCompatibleWithValue(dtype) == -1){
506                     Language language = comp.getLanguage();
507                     if (incomps < 2)
508                         comp.error('w', "datum type ("+language.formatType(dtype)+") incompatible with the key type ("+language.formatType(keyType)+")", dexp);
509                     else if (incomps == 2)
510                         lastIncomp = dexp;
511                     incomps++;
512                 }
513             }
514         }
515         // if more than 2 datums are incompatible we report a summary
516         if (incomps > 2)
517             comp.error('w', "there are " + (incomps - 2)
518                         + " more datums that are incompatible with the key", lastIncomp);
519 
520         VarValueTracker.forkPush(this);
521         if (exitValue == null) {
522             exp.clauses[0].exp = visit(exp.clauses[0].exp, required);
523             for (int i = 1; i < exp.clauses.length; i++) {
524                 if (exitValue == null) {
525                     valueTracker.forkNext();
526                     exp.clauses[i].exp = visit(exp.clauses[i].exp, required);
527                 }
528             }
529         }
530         if (exitValue == null && exp.elseClause != null) {
531             valueTracker.forkNext();
532             exp.elseClause.exp = visit(exp.elseClause.exp, required);
533         }
534         VarValueTracker.forkPop(this);
535 
536         boolean isKeyKnown = key instanceof QuoteExp;
537 
538         Object keyValue = isKeyKnown ? ((QuoteExp) key).getValue() : null;
539 
540         if (exp.elseClause == null && required instanceof ValueNeededType) {
541             boolean missing = !isKeyKnown || !exp.searchValue(keyValue);
542             if (missing) {
543                 if (comp.warnVoidUsed())
544                     comp.error('w', "missing else where value is required", exp);
545             }
546 
547             if (isKeyKnown && missing) {
548                 return QuoteExp.voidObjectExp;
549             }
550         }
551 
552         // When the key is know at compile time, search a matching
553         // datum and return the corresponding expression.
554         if (isKeyKnown) {
555             Expression e = exp.selectCase(keyValue);
556             return (e != null) ? e : QuoteExp.voidObjectExp;
557         }
558 
559         if (key.getType().isVoid()) {
560             return new BeginExp(key,
561                     exp.selectCase(QuoteExp.voidExp.getValue()));
562         }
563         return exp;
564     }
565 
visitScopeExp(ScopeExp exp, Type required)566     protected Expression visitScopeExp(ScopeExp exp, Type required) {
567         exp.visitChildren(this, null);
568         visitDeclarationTypes(exp);
569         for (Declaration decl = exp.firstDecl();  decl != null;
570              decl = decl.nextDecl()) {
571             if (decl.type == null) {
572                 Expression val = decl.getValue();
573                 decl.type = Type.objectType;
574                 decl.setType(val != null && val != QuoteExp.undefined_exp
575                              ? val.getType()
576                              : Type.objectType);
577             }
578             visitAnnotations(decl);
579         }
580         return exp;
581     }
582 
583     /** Visit any named functions that haven't been visit yet.
584      * This should be called at the end of a LetExp or ModuleExp.
585      */
visitRemainingDeclaredLambdas(ScopeExp exp)586     protected void visitRemainingDeclaredLambdas(ScopeExp exp) {
587         for (Declaration decl = exp.firstDecl(); decl != null;
588              decl = decl.nextDecl()) {
589             Expression value = decl.getValueRaw();
590             if (value instanceof LambdaExp && ! decl.isModuleLocal())
591                 visit(value, null);
592         }
593         for (Declaration decl = exp.firstDecl(); decl != null;
594              decl = decl.nextDecl()) {
595             Expression value = decl.getValueRaw();
596             if (value instanceof LambdaExp
597                 && ! value.getFlag(Expression.VALIDATED)
598                 && decl.isModuleLocal()
599                 && comp.warnUnused())
600                 comp.error('w', decl, "no use of ", "");
601         }
602     }
603 
visitModuleExp(ModuleExp exp, Type required)604     protected Expression visitModuleExp(ModuleExp exp, Type required) {
605         LambdaExp saveLambda = currentLambda;
606         currentLambda = exp;
607         try {
608             super.visitModuleExp(exp, required);
609         } finally {
610             currentLambda = saveLambda;
611         }
612         visitRemainingDeclaredLambdas(exp);
613         return exp;
614     }
615 
visitLetExp(LetExp exp, Type required)616     protected Expression visitLetExp(LetExp exp, Type required) {
617         if (! (exp instanceof CatchClause) && ! (exp instanceof FluidLetExp)) {
618             for (Declaration decl = exp.firstDecl();  decl != null;
619                  decl = decl.nextDecl()) {
620 
621                 // Minor optimization. Even better would be to replace
622                 // the entire LetExp with the Declaration's init expression:
623                 // (let ((x expr)) x) ==> expr
624                 // However, that runs into various complications with
625                 // type-checking, void-value-checking, and correctly setting
626                 // CAN_READ on a LambdaExp. This is simpler and (because
627                 // we have the value-propagation framework) almost as good.
628                 if (exp.body instanceof ReferenceExp) {
629                     ReferenceExp ref = (ReferenceExp) exp.body;
630                     if (ref.getBinding() == decl
631                             && ! ref.getDontDereference()) {
632                         decl.setFlag(Declaration.ALLOCATE_ON_STACK);
633                         ref.setFlag(ReferenceExp.ALLOCATE_ON_STACK_LAST);
634                     }
635                 }
636                 Expression init = decl.getInitValue();
637                 if (init == QuoteExp.undefined_exp
638                     && decl.getValueRaw() instanceof LambdaExp)
639                     valueTracker.noteSet(decl, IntNum.make(~0));
640                 else
641                     valueTracker.noteUnitialized(decl);
642             }
643         }
644 
645         for (Declaration decl = exp.firstDecl(); decl != null;
646              decl = decl.nextDecl()) {
647             Expression init = decl.getInitValue();
648             if (decl.nvalues > 0
649                 && decl.values[0].kind == Declaration.ValueSource.LET_INIT_KIND
650                 && decl.values[0].base == exp) {
651                 valueTracker.noteSet(decl, IntNum.make(~0));
652             }
653             boolean typeSpecified = decl.getFlag(Declaration.TYPE_SPECIFIED);
654             Type dtype = typeSpecified && init != QuoteExp.undefined_exp ? decl.getType() : null;
655             if (deferableInit(init) && decl.getValueRaw() == init)
656                 ; // defer
657             else
658                 init = visit(init, ValueNeededType.make(dtype));
659             decl.setInitValue(init);
660         }
661 
662         if (exitValue == null)
663             exp.body = visit(exp.body, required);
664         visitRemainingDeclaredLambdas(exp);
665         return exp;
666     }
667 
deferableInit(Expression init)668     protected boolean deferableInit(Expression init) {
669         if (init instanceof LambdaExp)
670             return ! (init instanceof ClassExp);
671         if (init instanceof ApplyExp) {
672             Object fun = ((ApplyExp) init).getFunctionValue();
673             if (fun == MakePromise.makeDelay || fun == MakePromise.makeLazy)
674                 return true;
675         }
676         return false;
677     }
678 
visitFluidLetExp(FluidLetExp exp, Type required)679     protected Expression visitFluidLetExp(FluidLetExp exp, Type required) {
680         for (Declaration decl = exp.firstDecl();
681              decl != null; decl = decl.nextDecl()) {
682             decl.setCanRead(true);
683             if (decl.base != null)
684                 decl.base.setCanRead(true);
685         }
686         return super.visitFluidLetExp(exp, required);
687     }
688 
visitLambdaExp(LambdaExp exp, Type required)689     protected Expression visitLambdaExp(LambdaExp exp, Type required) {
690         setCanAccess(exp, required);
691         if (exp.getCallConvention() == Compilation.CALL_WITH_UNSPECIFIED)
692             exp.setCallConvention(getCompilation());
693         Declaration firstDecl = exp.firstDecl();
694         if (firstDecl != null && firstDecl.isThisParameter()
695             && ! exp.isClassMethod() && firstDecl.type == null) {
696             firstDecl.setType(comp.mainClass);
697         }
698         if (exp.getClass() == LambdaExp.class) {
699             if (exp.canFinishCondition != CanFinishMap.CAN_FINISH
700                 && exp.canFinishCondition != null) {
701                 exp.setReturnType(Type.neverReturnsType);
702             }
703             Declaration ldecl = exp.nameDecl;
704             boolean unknownCalls = true;
705             if (ldecl != null && ! exp.isClassMethod() && ldecl.isModuleLocal()) {
706                 int countApply = 0;
707                 for (ApplyExp app = ldecl.firstCall; app != null;
708                      app = app.nextCall)
709                     countApply++;
710                 if (countApply == ldecl.numReferences
711                     // Data-flow from calls to a non-inlined module-level function
712                     // isn't wrong, but it can lead to problems in captured
713                     // variables if the actual argument is an inlined lambda,
714                     // We don't implement the necessary re-writing.
715                     && ! Compilation.avoidInline(exp)) {
716                     // Some preliminary data-flow from a set of known call sites.
717                     // This isn't fully implemented yet.
718                     unknownCalls = false;
719                     for (ApplyExp app = ldecl.firstCall; app != null;
720                          app = app.nextCall) {
721                         Expression func = app.getFunction();
722                         int nargs = app.getArgCount();
723                         Declaration p = firstDecl;
724                         if (p != null && p.isThisParameter())
725                             p = p.nextDecl();
726                         for (int i = 0; p != null && i < exp.min_args;
727                              p = p.nextDecl(), i++) {
728                             if (! p.hasUnknownValue())
729                                 p.noteValueFromApply(app, i);
730                         }
731                     }
732                 }
733             }
734             if (unknownCalls) {
735                 for (Declaration p = firstDecl; p != null;  p = p.nextDecl()) {
736                     if (! p.isThisParameter())
737                         p.noteValueUnknown();
738                 }
739             }
740         }
741         LambdaExp saveLambda = currentLambda;
742         currentLambda = exp;
743         try {
744             visitScopeExp(exp, required);
745         } finally {
746             currentLambda = saveLambda;
747         }
748         if (exp.isClassMethod() && "*init*".equals(exp.getName())) {
749             Expression bodyFirst = exp.getBodyFirstExpression();
750             ClassType calledInit = exp.checkForInitCall(bodyFirst);
751             ClassExp cexp = (ClassExp) exp.getOuter();
752             ClassType superClass = cexp.instanceType.getSuperclass();
753             if (calledInit != null) {
754                 if (calledInit != cexp.instanceType && calledInit != superClass)
755                     comp.error('e', "call to <init> for not this or super class");
756             } else if (superClass != null) {
757                 cexp.checkDefaultSuperConstructor(superClass, comp);
758             }
759         }
760         return exp;
761     }
762 
visitDefaultArgs(LambdaExp exp, Type required)763     public void visitDefaultArgs (LambdaExp exp, Type required) {
764         for (Declaration p = exp.firstDecl(); p != null; p = p.nextDecl()) {
765             Expression init = p.getInitValue();
766             if (init != null)
767                 p.setInitValue(visitAndUpdate(init, p.getType()));
768         }
769     }
770 
visitClassExp(ClassExp exp, Type required)771     protected Expression visitClassExp (ClassExp exp, Type required) {
772         Expression result = super.visitClassExp(exp, required);
773         if (! exp.explicitInit && exp.instanceType != null
774             && ! exp.instanceType.isInterface())
775             exp.checkDefaultSuperConstructor(exp.instanceType.getSuperclass(), comp);
776         return result;
777     }
778 
visitTryExp(TryExp exp, Type required)779     protected Expression visitTryExp (TryExp exp, Type required) {
780         if (exp.getCatchClauses() == null && exp.getFinallyClause() == null)
781             return visit(exp.try_clause, required);
782 
783         VarValueTracker.forkPush(this);
784         exp.try_clause = exp.try_clause.visit(this, required);
785         for (CatchClause clause = exp.catch_clauses;
786              clause != null; clause = clause.getNext())  {
787             valueTracker.forkNext();
788             clause.visit(this, required); // FIXME update?
789         }
790         // It is possible none of the try_clause or catch_clauses are executed
791         // before the finally_clause is executed, so treat as an empty branch.
792         if (exp.finally_clause != null)
793             valueTracker.forkNext();
794         VarValueTracker.forkPop(this);
795         if (exp.finally_clause != null)
796             exp.finally_clause = exp.finally_clause.visit(this, null);
797         if (exp.try_clause instanceof QuoteExp && exp.finally_clause == null)
798             return exp.try_clause;
799         return exp;
800     }
801 
802     boolean processingAnnotations;
803     /** If currently processing an annotation belonging to a declaration.
804      * In this case expressions must resolve to constants,
805      * annotations must resolve to know annotation types.
806      */
processingAnnotations()807     public boolean processingAnnotations () { return processingAnnotations; }
808 
visitAnnotations(Declaration decl)809     protected void visitAnnotations(Declaration decl) {
810         List<Expression> annotations = decl.annotations;
811         if (annotations != null) {
812             boolean saveProcessingAnnotations = processingAnnotations;
813             processingAnnotations = true;
814             try {
815                 int num = annotations.size();
816                 for (int i = 0;  i < num;  i++) {
817                     Expression before = annotations.get(i);
818                     Expression ann = visit(before, null);
819                     Object aval = ann.valueIfConstant();
820                     if (aval instanceof Proxy
821                         && ((aval = Proxy.getInvocationHandler(aval))
822                             instanceof AnnotationEntry)) {
823                         AnnotationEntry ae = (AnnotationEntry) aval;
824                         if (decl.isClassMethod() && !ae.hasTarget(ElementType.METHOD))
825                             comp.error('e', "annotation "+ae.getAnnotationType().getName()+" allowed on methods", before);
826                         if (decl.isClassField() && !ae.hasTarget(ElementType.FIELD))
827                             comp.error('e', "annotation "+ae.getAnnotationType().getName()+" not allowed on fields", before);
828                         if (decl.getValue() instanceof ClassExp
829                             && !ae.hasTarget(ElementType.TYPE)
830                             && !ae.hasTarget(ElementType.FIELD))
831                             comp.error('e', "annotation "+ae.getAnnotationType().getName()+" not allowed on classes", before);
832                     }
833                     annotations.set(i, ann);
834                 }
835             } finally {
836                 processingAnnotations = saveProcessingAnnotations;
837             }
838         }
839     }
840 
visitSetExp(SetExp exp, Type required)841     protected Expression visitSetExp(SetExp exp, Type required) {
842         Declaration decl = exp.getBinding();
843         if (decl != null && decl.getValueRaw() == exp.new_value
844             && deferableInit(exp.new_value))
845             ; // defer
846         else {
847             Type dtype = decl == null || decl.isAlias() ? null : decl.type;
848             exp.new_value = visit(exp.new_value, ValueNeededType.make(dtype));
849         }
850         if (decl != null && decl.values != Declaration.unknownValueValues
851             && exp.valueIndex >= 0) {
852             IntNum setterMask = IntNum.make(~exp.valueIndex);
853             valueTracker.noteSet(decl, setterMask);
854         }
855         if (! exp.isDefining() && decl != null && decl.isClassMethod())
856             comp.error('e', "can't assign to method "+decl.getName(), exp);
857         if (decl != null && decl.getFlag(Declaration.TYPE_SPECIFIED)) {
858             if (CompileReflect.checkKnownClass(decl.getType(), comp) < 0)
859                 decl.setType(Type.errorType);
860         }
861         /*
862         if (decl != null && ! decl.getFlag(Declaration.TYPE_SPECIFIED)) {
863             // This is a kludge to handle the a #!rest parameter that
864            // is implicitly declared to be a Scheme <list>, but may be
865            // assinged some other value, which is a legal Scheme idiom.
866            // We could set implicitly set the parameter type to <list>,
867             // but doing so improves type inference in the common case.
868             Type declType = decl.getType();
869             if (declType != null && ! exp.new_value.getType().isSubtype(declType))
870 	    decl.setType(Type.pointer_type);
871         }
872         */
873         Declaration ctx = exp.contextDecl();
874         if (ctx != null)
875             ctx.setCanRead(true);
876         return exp;
877     }
878 
879     /* #ifdef use:java.lang.invoke */
880     static final MethodType inlinerMethodType =
881         MethodType.methodType(gnu.expr.Expression.class,
882                               gnu.expr.ApplyExp.class,
883                               gnu.expr.InlineCalls.class,
884                               gnu.bytecode.Type.class,
885                               gnu.mapping.Procedure.class);
886     /* #else */
887     // private static final Class[] inlinerMethodType =
888     //     new Class[] { gnu.expr.ApplyExp.class,
889     //                   gnu.expr.InlineCalls.class,
890     //                   gnu.bytecode.Type.class,
891     //                   gnu.mapping.Procedure.class };
892     /* #endif */
893 
894     static
895         /* #ifdef use:java.lang.invoke */
resolveInliner(Procedure proc, String inliner, MethodType mtype)896         MethodHandle resolveInliner(Procedure proc, String inliner,
897                                     MethodType mtype)
898         /* #else */
899         // java.lang.reflect.Method resolveInliner(Procedure proc, String inliner,
900         //                                         Class[] mtype)
901         /* #endif */
902 
903         throws Throwable {
904         int colon = inliner.indexOf(':');
905         if (colon > 0) {
906             String cname = inliner.substring(0, colon);
907             String mname = inliner.substring(colon+1);
908             Class clas = Class.forName(cname, true, proc.getClass().getClassLoader());
909             /* #ifdef use:java.lang.invoke */
910             return MethodHandles.lookup().findStatic(clas, mname, mtype);
911             /* #else */
912             // return clas.getDeclaredMethod(mname, mtype);
913             /* #endif */
914         }
915         return null;
916     }
917 
maybeInline(ApplyExp exp, Type required, Procedure proc)918     public Expression maybeInline(ApplyExp exp, Type required, Procedure proc) {
919         try {
920             Object inliner;
921             synchronized (proc) {
922                 inliner = proc.getProperty(Procedure.validateXApplyKey, null);
923                 if (inliner == null && exp.firstSpliceArg < 0)
924                     inliner = proc.getProperty(Procedure.validateApplyKey, null);
925                 if (inliner == Procedure.inlineIfConstantSymbol) {
926                     Expression e = exp.inlineIfConstant(proc, this);
927                     if (e != exp)
928                         return visit(e, required);
929                 }
930                 if (inliner instanceof CharSequence) {
931                     inliner = resolveInliner(proc, inliner.toString(),
932                                              inlinerMethodType);
933                     if (inliner == null) {
934                         error('e', "inliner property string for "+proc+" is not of the form CLASS:METHOD");
935                         return null;
936                     }
937                 }
938             } /* end synchronized */
939             if (inliner != null) {
940                 /* #ifdef use:java.lang.invoke */
941                 if (inliner instanceof MethodHandle)
942                     return (Expression) ((MethodHandle) inliner).invokeExact(exp, this, required, proc);
943                 /* #endif */
944                 Object[] vargs = new Object[] { exp, this, required, proc };
945                 if (inliner instanceof Procedure)
946                     return (Expression) ((Procedure) inliner).applyN(vargs);
947                 /* #ifndef use:java.lang.invoke */
948                 // else if (inliner instanceof java.lang.reflect.Method)
949                 //   return (Expression) ((java.lang.reflect.Method) inliner)
950                 //     .invoke(null, vargs);
951                 /* #endif */
952             }
953         } catch (Error ex) {
954             throw ex;
955         } catch (Throwable ex) {
956             if (ex instanceof InvocationTargetException)
957                 ex = ((InvocationTargetException) ex).getTargetException();
958             messages.error('e',
959                            "caught exception in inliner for "+proc+" - "+ex, ex);
960         }
961         return null;
962     }
963 
964     /** Attempt to inline a function call.
965      * @param lexp function to inline
966      * @param makeCopy true if the body of lexp should of copied; false
967      *   if we can re-use lexp because it is no longer needed.
968      * @return the inlined expression (a LetExp), or null if we
969      *   weren't able to inline.
970      */
inlineCall(LambdaExp lexp, ApplyExp aexp, boolean makeCopy)971     public static Expression inlineCall(LambdaExp lexp, ApplyExp aexp,
972                                         boolean makeCopy) {
973         if (lexp.keywords != null || ! aexp.isSimple()
974             || lexp.getFlag(LambdaExp.CANNOT_INLINE))
975             return null;
976         Expression[] args = aexp.getArgs();
977         boolean varArgs = lexp.max_args < 0;
978         int fixed = lexp.min_args;
979         if (args.length >= fixed
980             && (varArgs || args.length <= fixed + lexp.opt_args)) {
981             Declaration prev = null;
982             IdentityHashTable mapper;
983             if (makeCopy) {
984                 mapper = new IdentityHashTable();
985                 args = Expression.deepCopy(args, mapper);
986                 if (args == null)
987                     return null;
988             } else {
989                 mapper = null;
990             }
991             int fixed_opt = fixed + lexp.opt_args;
992             int i = 0;
993             LetExp let = new LetExp();
994             for (Declaration param = lexp.firstDecl(); param != null; ) {
995                 Declaration next = param.nextDecl();
996                 if (param.getFlag(Declaration.IS_SUPPLIED_PARAMETER)
997                     && ! param.getFlag(Declaration.IS_PARAMETER)) {
998                     i--;
999                     Object value = Language.getDefaultLanguage()
1000                         .booleanObject(i < args.length);
1001                     param.setInitValue(QuoteExp.getInstance(value));
1002                 } else if (param.getFlag(Declaration.IS_REST_PARAMETER)) {
1003                     int rest_args = args.length - fixed_opt;
1004                     if (rest_args < 0)
1005                         rest_args = 0;
1006                     Expression[] rargs = new Expression[rest_args+1];
1007                     rargs[0] = QuoteExp.getInstance(param.type);
1008                     System.arraycopy(args, args.length-rest_args,
1009                                      rargs, 1, rest_args);
1010                     param.setInitValue(new ApplyExp(Invoke.make, rargs));
1011                 }
1012                 else if (i < fixed_opt && i < args.length
1013                          && ! param.getFlag(Declaration.PATTERN_NESTED))
1014                     param.setInitValue(args[i]);
1015                 i++;
1016                 if (makeCopy) {
1017                     Declaration ldecl =
1018                         let.addDeclaration(param.symbol, param.type);
1019                     if (param.typeExp != null) {
1020                         ldecl.typeExp = Expression.deepCopy(param.typeExp);
1021                         if (ldecl.typeExp == null)
1022                             return null;
1023 
1024                     }
1025                     mapper.put(param, ldecl);
1026                 } else {
1027                     lexp.remove(prev, param);
1028                     let.add(prev, param);
1029                 }
1030                 if ( ! param.getCanWrite()) {
1031                     param.nvalues = 0;
1032                     param.values = null;
1033                 }
1034                 param.noteValueFromLet(let);
1035                 prev = param;
1036                 param = next;
1037             }
1038             Expression body = lexp.body;
1039             if (makeCopy) {
1040                 body = Expression.deepCopy(body, mapper);
1041                 if (body == null && lexp.body != null)
1042                     return null;
1043             }
1044             let.body = body;
1045             lexp.body = null;
1046             lexp.setFlag(Expression.VALIDATED);
1047             lexp.setInlineOnly(true);
1048             return let;
1049         }
1050         /*
1051         if (lambda.min_args == 0 && lambda.max_args == -1)
1052         {
1053             Declaration pargs = lambda.firstDecl();
1054             Expression[] cargs = Expression.deepCopy(args, mapper);
1055             Declaration largs = new Declaration
1056                 IdentityHashTable mapper = new IdentityHashTable();
1057             LetExp let = new LetExp();
1058             return let;
1059         }
1060         if (lambda.min_args != lambda.max_args)
1061         {
1062             // FUTURE
1063         }
1064         */
1065         return null;
1066     }
1067 
1068     /** New helper Type class, used for "lenient" conversions. */
1069     public static class LenientExpectedType extends Type {
1070         Type base;
1071 
make(Type type)1072         public static LenientExpectedType make(Type type) {
1073             return new LenientExpectedType(type);
1074         }
1075 
LenientExpectedType(Type type)1076         LenientExpectedType(Type type) {
1077             super(type);
1078             base = type;
1079         }
1080 
1081         @Override
compare(Type other)1082         public int compare(Type other) {
1083             return this == other ? 0 : -3;
1084         }
1085 
1086         @Override
coerceFromObject(Object obj)1087         public Object coerceFromObject (Object obj) {
1088             return obj;
1089         }
1090 
1091         @Override
isCompatibleWithValue(Type valueType)1092         public int isCompatibleWithValue(Type valueType) {
1093             if (base.getRawType().equals(base.getRawType()))
1094                 return 1;
1095             return base.isCompatibleWithValue(valueType);
1096         }
1097 
1098         @Override
toString()1099         public String toString() {
1100             return "LenientExpectedType["+base+']';
1101         }
1102     }
1103 
1104     public static class ProcedureInCallContext extends ObjectType {
1105         public static final ProcedureInCallContext INSTANCE = new ProcedureInCallContext();
1106 
ProcedureInCallContext()1107         ProcedureInCallContext() {
1108             super("procedure-in-call-context");
1109         }
1110 
getImplementationType()1111         public Type getImplementationType() {
1112             return Compilation.typeProcedure;
1113         }
1114 
compare(Type other)1115         public int compare(Type other) {
1116             return getImplementationType().compare(other.getImplementationType());
1117         }
1118     }
1119 
1120     /** A marker type to indicate that void is invalid.
1121      * Only used as the required type, in e.g. rhs of assignment.
1122      */
1123     public static class ValueNeededType extends ObjectType {
1124         static final ValueNeededType instance
1125             = new ValueNeededType(null);
1126 
1127         Type actualType;
1128 
ValueNeededType(Type actualType)1129         ValueNeededType(Type actualType) {
1130             super("value-needed-type:"+actualType);
1131             this.actualType = actualType;
1132         }
1133 
make(Type type)1134         public static Type make(Type type) {
1135             if (type == null)
1136                 return instance;
1137             if (type instanceof ValueNeededType || type == Type.objectType)
1138                 return type;
1139             /* FUTURE not support by code yet
1140                return new ValueNeededType(type);
1141             */
1142             return type;
1143         }
1144 
getImplementationType()1145         public Type getImplementationType() {
1146             return actualType;
1147         }
1148 
compare(Type other)1149         public int compare(Type other) {
1150             return other.isVoid() ? -1 : 1;
1151         }
1152     }
1153 }
1154