From 85f320258cbd68c4235cf0cdf2fede9ab6e88c8b Mon Sep 17 00:00:00 2001 From: Eugene Burmako Date: Sun, 25 Nov 2012 12:30:13 +0100 Subject: unifies approaches to call analysis in TreeInfo Instead of a flurry of methods such as `methPart` or `typeArguments` to analyze applications, there is a single access point to related info: `treeInfo.dissectApplied(tree)` Dissection returns an instance of the `Applied` class, which can extract parts of applications and perform other application-specific operations, e.g. `applyCount`. For the sake of convenience, there's also an extractor named `Applied`, which extracts `core`, `targs` and `argss`, where core is everything except targs and argss. Extractor works for both `Tree` and `Applied` (in the former case, it's equivalent to first dissecting and pattern matching). --- .../tools/nsc/typechecker/ContextErrors.scala | 5 +- .../scala/tools/nsc/typechecker/Typers.scala | 21 ++- src/reflect/scala/reflect/internal/TreeInfo.scala | 172 +++++++++++++++------ 3 files changed, 136 insertions(+), 62 deletions(-) diff --git a/src/compiler/scala/tools/nsc/typechecker/ContextErrors.scala b/src/compiler/scala/tools/nsc/typechecker/ContextErrors.scala index faacb60d75..f915f84a32 100644 --- a/src/compiler/scala/tools/nsc/typechecker/ContextErrors.scala +++ b/src/compiler/scala/tools/nsc/typechecker/ContextErrors.scala @@ -1279,7 +1279,10 @@ trait ContextErrors { fail() } - private def implRefError(message: String) = genericError(methPart(macroDdef.rhs), message) + private def implRefError(message: String) = { + val treeInfo.Applied(implRef, _, _) = macroDdef.rhs + genericError(implRef, message) + } private def compatibilityError(message: String) = implRefError( diff --git a/src/compiler/scala/tools/nsc/typechecker/Typers.scala b/src/compiler/scala/tools/nsc/typechecker/Typers.scala index ae506cd6ab..7c76eff9d8 100644 --- a/src/compiler/scala/tools/nsc/typechecker/Typers.scala +++ b/src/compiler/scala/tools/nsc/typechecker/Typers.scala @@ -3891,7 +3891,7 @@ trait Typers extends Modes with Adaptations with Tags { case DynamicApplicationNamed(qual, _) if acceptsApplyDynamic(qual.tpe.widen) => true case _ => false // look deeper? - // val methPart = treeInfo.methPart(fun) + // val treeInfo.Applied(methPart, _, _) = fun // println("methPart of "+ fun +" is "+ methPart) // if (methPart ne fun) isApplyDynamicNamed(methPart) // else false @@ -3927,7 +3927,7 @@ trait Typers extends Modes with Adaptations with Tags { */ def mkInvoke(cxTree: Tree, tree: Tree, qual: Tree, name: Name): Option[Tree] = { log(s"dyna.mkInvoke($cxTree, $tree, $qual, $name)") - val treeSelection = treeInfo.methPart(tree) + val treeInfo.Applied(treeSelection, _, _) = tree def isDesugaredApply = treeSelection match { case Select(`qual`, nme.apply) => true case _ => false @@ -3940,7 +3940,7 @@ trait Typers extends Modes with Adaptations with Tags { // not supported: foo.bar(a1,..., an: _*) def hasStar(args: List[Tree]) = treeInfo.isWildcardStarArgList(args) def applyOp(args: List[Tree]) = if (hasNamed(args)) nme.applyDynamicNamed else nme.applyDynamic - def matches(t: Tree) = isDesugaredApply || treeInfo.methPart(t) == treeSelection + def matches(t: Tree) = isDesugaredApply || treeInfo.dissectApplied(t).core == treeSelection /** Note that the trees which arrive here are potentially some distance from * the trees of direct interest. `cxTree` is some enclosing expression which @@ -3958,9 +3958,8 @@ trait Typers extends Modes with Adaptations with Tags { case _ => t.children flatMap findSelection headOption } findSelection(cxTree) match { - case Some((opName, tapply)) => - val targs = treeInfo.typeArguments(tapply) - val fun = gen.mkTypeApply(Select(qual, opName), targs) + case Some((opName, treeInfo.Applied(_, targs, _))) => + val fun = gen.mkTypeApply(Select(qual, opName), targs) atPos(qual.pos)(Apply(fun, Literal(Constant(name.decode)) :: Nil)) case _ => setError(tree) @@ -4149,8 +4148,8 @@ trait Typers extends Modes with Adaptations with Tags { return fail() if (treeInfo.mayBeVarGetter(varsym)) { - treeInfo.methPart(lhs1) match { - case Select(qual, name) => + lhs1 match { + case treeInfo.Applied(Select(qual, name), _, _) => val sel = Select(qual, nme.getterToSetter(name.toTermName)) setPos lhs.pos val app = Apply(sel, List(rhs)) setPos tree.pos return typed(app, mode, pt) @@ -4568,9 +4567,9 @@ trait Typers extends Modes with Adaptations with Tags { } case Apply(fn, indices) => - treeInfo.methPart(fn) match { - case Select(table, nme.apply) => mkUpdate(table, indices) - case _ => UnexpectedTreeAssignmentConversionError(qual) + fn match { + case treeInfo.Applied(Select(table, nme.apply), _, _) => mkUpdate(table, indices) + case _ => UnexpectedTreeAssignmentConversionError(qual) } } typed1(tree1, mode, pt) diff --git a/src/reflect/scala/reflect/internal/TreeInfo.scala b/src/reflect/scala/reflect/internal/TreeInfo.scala index 8ad15f37e4..7423a2ff57 100644 --- a/src/reflect/scala/reflect/internal/TreeInfo.scala +++ b/src/reflect/scala/reflect/internal/TreeInfo.scala @@ -159,7 +159,7 @@ abstract class TreeInfo { * Also accounts for varargs. */ private def applyMethodParameters(fn: Tree): List[Symbol] = { - val depth = applyDepth(fn) + val depth = dissectApplied(fn).applyDepth // There could be applies which go beyond the parameter list(s), // being applied to the result of the method call. // !!! Note that this still doesn't seem correct, although it should @@ -195,29 +195,26 @@ abstract class TreeInfo { def isGetter = mayBeVarGetter(sym) && sym.owner.info.member(nme.getterToSetter(sym.name.toTermName)) != NoSymbol tree match { - case Ident(_) => isVar - case Select(_, _) => isVar || isGetter - case _ => - methPart(tree) match { - case Select(qual, nme.apply) => qual.tpe.member(nme.update) != NoSymbol - case _ => false - } + case Ident(_) => isVar + case Select(_, _) => isVar || isGetter + case Applied(Select(qual, nme.apply), _, _) => qual.tpe.member(nme.update) != NoSymbol + case _ => false } } /** Is tree a self constructor call this(...)? I.e. a call to a constructor of the * same object? */ - def isSelfConstrCall(tree: Tree): Boolean = methPart(tree) match { - case Ident(nme.CONSTRUCTOR) - | Select(This(_), nme.CONSTRUCTOR) => true + def isSelfConstrCall(tree: Tree): Boolean = tree match { + case Applied(Ident(nme.CONSTRUCTOR), _, _) => true + case Applied(Select(This(_), nme.CONSTRUCTOR), _, _) => true case _ => false } /** Is tree a super constructor call? */ - def isSuperConstrCall(tree: Tree): Boolean = methPart(tree) match { - case Select(Super(_, _), nme.CONSTRUCTOR) => true + def isSuperConstrCall(tree: Tree): Boolean = tree match { + case Applied(Select(Super(_, _), nme.CONSTRUCTOR), _, _) => true case _ => false } @@ -399,22 +396,6 @@ abstract class TreeInfo { case _ => false } - /** If this tree represents a type application (after unwrapping - * any applies) the first type argument. Otherwise, EmptyTree. - */ - def firstTypeArg(tree: Tree): Tree = tree match { - case Apply(fn, _) => firstTypeArg(fn) - case TypeApply(_, targ :: _) => targ - case _ => EmptyTree - } - - /** If this tree represents a type application the type arguments. Otherwise Nil. - */ - def typeArguments(tree: Tree): List[Tree] = tree match { - case TypeApply(_, targs) => targs - case _ => Nil - } - /** If this tree has type parameters, those. Otherwise Nil. */ def typeParameters(tree: Tree): List[TypeDef] = tree match { @@ -514,30 +495,121 @@ abstract class TreeInfo { def hasSynthCaseSymbol(t: Tree) = t.symbol != null && isSynthCaseSymbol(t.symbol) - /** The method part of an application node + /** Applications in Scala can have one of the following shapes: + * + * 1) naked core: Ident(_) or Select(_, _) or basically anything else + * 2) naked core with targs: TypeApply(core, targs) or AppliedTypeTree(core, targs) + * 3) apply or several applies wrapping a core: Apply(core, _), or Apply(Apply(core, _), _), etc + * + * This class provides different ways to decompose applications and simplifies their analysis. + * + * ***Examples*** + * (TypeApply in the examples can be replaced with AppliedTypeTree) + * + * Ident(foo): + * * callee = Ident(foo) + * * core = Ident(foo) + * * targs = Nil + * * argss = Nil + * + * TypeApply(foo, List(targ1, targ2...)) + * * callee = TypeApply(foo, List(targ1, targ2...)) + * * core = foo + * * targs = List(targ1, targ2...) + * * argss = Nil + * + * Apply(foo, List(arg1, arg2...)) + * * callee = foo + * * core = foo + * * targs = Nil + * * argss = List(List(arg1, arg2...)) + * + * Apply(Apply(foo, List(arg21, arg22, ...)), List(arg11, arg12...)) + * * callee = foo + * * core = foo + * * targs = Nil + * * argss = List(List(arg11, arg12...), List(arg21, arg22, ...)) + * + * Apply(Apply(TypeApply(foo, List(targs1, targs2, ...)), List(arg21, arg22, ...)), List(arg11, arg12...)) + * * callee = TypeApply(foo, List(targs1, targs2, ...)) + * * core = foo + * * targs = Nil + * * argss = List(List(arg11, arg12...), List(arg21, arg22, ...)) */ - def methPart(tree: Tree): Tree = tree match { - case Apply(fn, _) => methPart(fn) - case TypeApply(fn, _) => methPart(fn) - case AppliedTypeTree(fn, _) => methPart(fn) - case _ => tree + class Applied(val tree: Tree) { + /** The tree stripped of the possibly nested applications. + * The original tree if it's not an application. + */ + def callee: Tree = { + def loop(tree: Tree): Tree = tree match { + case Apply(fn, _) => loop(fn) + case tree => tree + } + loop(tree) + } + + /** The `callee` unwrapped from type applications. + * The original `callee` if it's not a type application. + */ + def core: Tree = callee match { + case TypeApply(fn, _) => fn + case AppliedTypeTree(fn, _) => fn + case tree => tree + } + + /** The type arguments of the `callee`. + * `Nil` if the `callee` is not a type application. + */ + def targs: List[Tree] = callee match { + case TypeApply(_, args) => args + case AppliedTypeTree(_, args) => args + case _ => Nil + } + + /** (Possibly multiple lists of) value arguments of an application. + * `Nil` if the `callee` is not an application. + */ + def argss: List[List[Tree]] = { + def loop(tree: Tree): List[List[Tree]] = tree match { + case Apply(fn, args) => loop(fn) :+ args + case _ => Nil + } + loop(tree) + } + + /** The depth of the nested applies: e.g. Apply(Apply(Apply(_, _), _), _) + * has depth 3. Continues through type applications (without counting them.) + */ + def applyDepth: Int = { + def loop(tree: Tree): Int = tree match { + case Apply(fn, _) => 1 + loop(fn) + case TypeApply(fn, _) => loop(fn) + case AppliedTypeTree(fn, _) => loop(fn) + case _ => 0 + } + loop(tree) + } } - /** The depth of the nested applies: e.g. Apply(Apply(Apply(_, _), _), _) - * has depth 3. Continues through type applications (without counting them.) + /** Returns a wrapper that knows how to destructure and analyze applications. */ - def applyDepth(tree: Tree): Int = tree match { - case Apply(fn, _) => 1 + applyDepth(fn) - case TypeApply(fn, _) => applyDepth(fn) - case AppliedTypeTree(fn, _) => applyDepth(fn) - case _ => 0 - } - def firstArgument(tree: Tree): Tree = tree match { - case Apply(fn, args) => - val f = firstArgument(fn) - if (f == EmptyTree && !args.isEmpty) args.head else f - case _ => - EmptyTree + def dissectApplied(tree: Tree) = new Applied(tree) + + /** Destructures applications into important subparts described in `Applied` class, + * namely into: core, targs and argss (in the specified order). + * + * Trees which are not applications are also accepted. Their callee and core will + * be equal to the input, while targs and argss will be Nil. + * + * The provided extractors don't expose all the API of the `Applied` class. + * For advanced use, call `dissectApplied` explicitly and use its methods instead of pattern matching. + */ + object Applied { + def unapply(applied: Applied): Option[(Tree, List[Tree], List[List[Tree]])] = + Some((applied.core, applied.targs, applied.argss)) + + def unapply(tree: Tree): Option[(Tree, List[Tree], List[List[Tree]])] = + unapply(dissectApplied(tree)) } /** Does list of trees start with a definition of @@ -634,7 +706,7 @@ abstract class TreeInfo { } def unapply(tree: Tree) = refPart(tree) match { - case ref: RefTree => Some((ref.qualifier.symbol, ref.symbol, typeArguments(tree))) + case ref: RefTree => Some((ref.qualifier.symbol, ref.symbol, dissectApplied(tree).targs)) case _ => None } } -- cgit v1.2.3 From 40063b0009d55ed527bf1625d99a168a8faa4124 Mon Sep 17 00:00:00 2001 From: Eugene Burmako Date: Sat, 24 Nov 2012 22:32:17 +0100 Subject: refactors handling of parent types At the moment parser does too much w.r.t handling of parent types. It checks whether a parent can have value arguments or not and more importantly, it synthesizes constructors and super calls. This approach is fundamentally incompatible with upcoming type macros. Take for example the following two snippets of code: `class C extends A(2)` `class D extends A(2) with B(3)` In the first snippet, `A` might be a type macro, therefore the super call `A.super(2)` eagerly emitted by the parser might be meaningless. In the second snippet parser will report an error despite that `B` might be a type macro which expands into a trait. Unfortunately we cannot simply augment the parser with the `isTypeMacro` check. This is because to find out whether an identifier refers to a type macro, one needs to perform a typecheck, which the parser cannot do. Therefore we need a deep change in how parent types and constructors are processed by the compiler, which is implemented in this commit. --- src/compiler/scala/tools/nsc/ast/Trees.scala | 18 +- .../scala/tools/nsc/ast/parser/Parsers.scala | 62 ++-- .../scala/tools/nsc/ast/parser/TreeBuilder.scala | 20 +- .../scala/tools/nsc/transform/Constructors.scala | 1 - .../scala/tools/nsc/transform/UnCurry.scala | 4 +- .../tools/nsc/typechecker/ContextErrors.scala | 13 +- .../scala/tools/nsc/typechecker/Namers.scala | 9 +- .../tools/nsc/typechecker/StdAttachments.scala | 22 ++ .../scala/tools/nsc/typechecker/Typers.scala | 395 ++++++++++++++------- .../scala/tools/nsc/typechecker/Unapplies.scala | 2 +- .../scala/tools/reflect/ToolBoxFactory.scala | 1 - src/reflect/scala/reflect/internal/TreeInfo.scala | 7 + src/reflect/scala/reflect/internal/Trees.scala | 3 + test/files/neg/anyval-anyref-parent.check | 2 +- test/files/neg/cyclics-import.check | 11 +- test/files/neg/names-defaults-neg.check | 2 +- test/files/neg/protected-constructors.check | 5 +- test/files/neg/t2148.check | 2 +- test/files/neg/t409.check | 4 +- test/files/neg/t5529.check | 5 +- test/files/neg/t5696.check | 2 +- test/files/neg/t667.check | 4 +- test/files/neg/t877.check | 4 +- test/files/run/t5064.check | 6 +- 24 files changed, 388 insertions(+), 216 deletions(-) diff --git a/src/compiler/scala/tools/nsc/ast/Trees.scala b/src/compiler/scala/tools/nsc/ast/Trees.scala index 296d55fec5..b8c59da95c 100644 --- a/src/compiler/scala/tools/nsc/ast/Trees.scala +++ b/src/compiler/scala/tools/nsc/ast/Trees.scala @@ -82,7 +82,7 @@ trait Trees extends scala.reflect.internal.Trees { self: Global => * body * } */ - def Template(parents: List[Tree], self: ValDef, constrMods: Modifiers, vparamss: List[List[ValDef]], argss: List[List[Tree]], body: List[Tree], superPos: Position): Template = { + def Template(parents: List[Tree], self: ValDef, constrMods: Modifiers, vparamss: List[List[ValDef]], body: List[Tree], superPos: Position): Template = { /* Add constructor to template */ // create parameters for as synthetic trees. @@ -117,9 +117,16 @@ trait Trees extends scala.reflect.internal.Trees { self: Global => if (vparamss1.isEmpty || !vparamss1.head.isEmpty && vparamss1.head.head.mods.isImplicit) vparamss1 = List() :: vparamss1; val superRef: Tree = atPos(superPos)(gen.mkSuperSelect) - val superCall = (superRef /: argss) (Apply.apply) + val superCall = Apply(superRef, Nil) // we can't know in advance which of the parents will end up as a superclass + // this requires knowing which of the parents is a type macro and which is not + // and that's something that cannot be found out before typer + // (the type macros aren't in the trunk yet, but there is a plan for them to land there soon) + // this means that we don't know what will be the arguments of the super call + // therefore here we emit a dummy which gets populated when the template is named and typechecked List( - atPos(wrappingPos(superPos, lvdefs ::: argss.flatten)) ( + // TODO: previously this was `wrappingPos(superPos, lvdefs ::: argss.flatten)` + // is it going to be a problem that we can no longer include the `argss`? + atPos(wrappingPos(superPos, lvdefs)) ( DefDef(constrMods, nme.CONSTRUCTOR, List(), vparamss1, TypeTree(), Block(lvdefs ::: List(superCall), Literal(Constant()))))) } } @@ -137,11 +144,10 @@ trait Trees extends scala.reflect.internal.Trees { self: Global => * @param constrMods the modifiers for the class constructor, i.e. as in `class C private (...)` * @param vparamss the value parameters -- if they have symbols they * should be owned by `sym` - * @param argss the supercall arguments * @param body the template statements without primary constructor * and value parameter fields. */ - def ClassDef(sym: Symbol, constrMods: Modifiers, vparamss: List[List[ValDef]], argss: List[List[Tree]], body: List[Tree], superPos: Position): ClassDef = { + def ClassDef(sym: Symbol, constrMods: Modifiers, vparamss: List[List[ValDef]], body: List[Tree], superPos: Position): ClassDef = { // "if they have symbols they should be owned by `sym`" assert( mforall(vparamss)(p => (p.symbol eq NoSymbol) || (p.symbol.owner == sym)), @@ -151,7 +157,7 @@ trait Trees extends scala.reflect.internal.Trees { self: Global => ClassDef(sym, Template(sym.info.parents map TypeTree, if (sym.thisSym == sym || phase.erasedTypes) emptyValDef else ValDef(sym.thisSym), - constrMods, vparamss, argss, body, superPos)) + constrMods, vparamss, body, superPos)) } // --- subcomponents -------------------------------------------------- diff --git a/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala b/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala index 074fcabec8..a929e54601 100644 --- a/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala +++ b/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala @@ -1562,9 +1562,9 @@ self => val nstart = in.skipToken() val npos = r2p(nstart, nstart, in.lastOffset) val tstart = in.offset - val (parents, argss, self, stats) = template(isTrait = false) + val (parents, self, stats) = template() val cpos = r2p(tstart, tstart, in.lastOffset max tstart) - makeNew(parents, self, stats, argss, npos, cpos) + makeNew(parents, self, stats, npos, cpos) case _ => syntaxErrorOrIncomplete("illegal start of simple expression", true) errorTermTree @@ -2742,20 +2742,17 @@ self => * TraitParents ::= AnnotType {with AnnotType} * }}} */ - def templateParents(isTrait: Boolean): (List[Tree], List[List[Tree]]) = { - val parents = new ListBuffer[Tree] += startAnnotType() - val argss = ( - // TODO: the insertion of ListOfNil here is where "new Foo" becomes - // indistinguishable from "new Foo()". - if (in.token == LPAREN && !isTrait) multipleArgumentExprs() - else ListOfNil - ) - - while (in.token == WITH) { - in.nextToken() - parents += startAnnotType() + def templateParents(): List[Tree] = { + val parents = new ListBuffer[Tree] + def readAppliedParent() = { + val start = in.offset + val parent = startAnnotType() + val argss = if (in.token == LPAREN) multipleArgumentExprs() else Nil + parents += atPos(start)((parent /: argss)(Apply.apply)) } - (parents.toList, argss) + readAppliedParent() + while (in.token == WITH) { in.nextToken(); readAppliedParent() } + parents.toList } /** {{{ @@ -2765,7 +2762,7 @@ self => * EarlyDef ::= Annotations Modifiers PatDef * }}} */ - def template(isTrait: Boolean): (List[Tree], List[List[Tree]], ValDef, List[Tree]) = { + def template(): (List[Tree], ValDef, List[Tree]) = { newLineOptWhenFollowedBy(LBRACE) if (in.token == LBRACE) { // @S: pre template body cannot stub like post body can! @@ -2782,16 +2779,16 @@ self => case _ => List() } in.nextToken() - val (parents, argss) = templateParents(isTrait = isTrait) - val (self1, body1) = templateBodyOpt(traitParentSeen = isTrait) - (parents, argss, self1, earlyDefs ::: body1) + val parents = templateParents() + val (self1, body1) = templateBodyOpt(parenMeansSyntaxError = false) + (parents, self1, earlyDefs ::: body1) } else { - (List(), ListOfNil, self, body) + (List(), self, body) } } else { - val (parents, argss) = templateParents(isTrait = isTrait) - val (self, body) = templateBodyOpt(traitParentSeen = isTrait) - (parents, argss, self, body) + val parents = templateParents() + val (self, body) = templateBodyOpt(parenMeansSyntaxError = false) + (parents, self, body) } } @@ -2805,15 +2802,15 @@ self => * }}} */ def templateOpt(mods: Modifiers, name: Name, constrMods: Modifiers, vparamss: List[List[ValDef]], tstart: Int): Template = { - val (parents0, argss, self, body) = ( + val (parents0, self, body) = ( if (in.token == EXTENDS || in.token == SUBTYPE && mods.isTrait) { in.nextToken() - template(isTrait = mods.isTrait) + template() } else { newLineOptWhenFollowedBy(LBRACE) - val (self, body) = templateBodyOpt(traitParentSeen = false) - (List(), ListOfNil, self, body) + val (self, body) = templateBodyOpt(parenMeansSyntaxError = mods.isTrait || name.isTermName) + (List(), self, body) } ) def anyrefParents() = { @@ -2835,7 +2832,7 @@ self => if (inScalaRootPackage && ScalaValueClassNames.contains(name)) Template(parents0, self, anyvalConstructor :: body) else - Template(anyrefParents, self, constrMods, vparamss, argss, body, o2p(tstart)) + Template(anyrefParents, self, constrMods, vparamss, body, o2p(tstart)) } } @@ -2850,14 +2847,15 @@ self => case (self, Nil) => (self, EmptyTree.asList) case result => result } - def templateBodyOpt(traitParentSeen: Boolean): (ValDef, List[Tree]) = { + def templateBodyOpt(parenMeansSyntaxError: Boolean): (ValDef, List[Tree]) = { newLineOptWhenFollowedBy(LBRACE) if (in.token == LBRACE) { templateBody(isPre = false) } else { - if (in.token == LPAREN) - syntaxError((if (traitParentSeen) "parents of traits" else "traits or objects")+ - " may not have parameters", true) + if (in.token == LPAREN) { + if (parenMeansSyntaxError) syntaxError(s"traits or objects may not have parameters", true) + else assert(false, "unexpected opening parenthesis") + } (emptyValDef, List()) } } diff --git a/src/compiler/scala/tools/nsc/ast/parser/TreeBuilder.scala b/src/compiler/scala/tools/nsc/ast/parser/TreeBuilder.scala index 0ac46a18bc..9e9e81aa27 100644 --- a/src/compiler/scala/tools/nsc/ast/parser/TreeBuilder.scala +++ b/src/compiler/scala/tools/nsc/ast/parser/TreeBuilder.scala @@ -205,20 +205,26 @@ abstract class TreeBuilder { */ def makeAnonymousNew(stats: List[Tree]): Tree = { val stats1 = if (stats.isEmpty) List(Literal(Constant(()))) else stats - makeNew(Nil, emptyValDef, stats1, ListOfNil, NoPosition, NoPosition) + makeNew(Nil, emptyValDef, stats1, NoPosition, NoPosition) } /** Create positioned tree representing an object creation + import global._ + + /** Carries information necessary to expand the host tree. + * At times we need to store this info, because macro expansion can be delayed until its targs are inferred. + * After a macro application has been successfully expanded, this attachment is destroyed. + */ type UnaffiliatedMacroContext = scala.reflect.macros.runtime.Context type MacroContext = UnaffiliatedMacroContext { val universe: self.global.type } case class MacroRuntimeAttachment(delayed: Boolean, typerContext: Context, macroContext: Option[MacroContext]) + + /** After being synthesized by the parser, primary constructors aren't fully baked yet. + * A call to super in such constructors is just a fill-me-in-later dummy resolved later + * by `parentTypes`. This attachment coordinates `parentTypes` and `typedTemplate` and + * allows them to complete the synthesis. + */ + case class SuperCallArgsAttachment(argss: List[List[Tree]]) + + /** Extractor for `SuperCallArgsAttachment`. + * Compared with `MacroRuntimeAttachment` this attachment has different a usage pattern, + * so it really benefits from a dedicated extractor. + */ + object CarriesSuperCallArgs { + def unapply(tree: Tree): Option[List[List[Tree]]] = + tree.attachments.get[SuperCallArgsAttachment] collect { case SuperCallArgsAttachment(argss) => argss } + } } \ No newline at end of file diff --git a/src/compiler/scala/tools/nsc/typechecker/Typers.scala b/src/compiler/scala/tools/nsc/typechecker/Typers.scala index 7c76eff9d8..3f5a4036aa 100644 --- a/src/compiler/scala/tools/nsc/typechecker/Typers.scala +++ b/src/compiler/scala/tools/nsc/typechecker/Typers.scala @@ -1378,13 +1378,6 @@ trait Typers extends Modes with Adaptations with Tags { if (member(qual, name) != NoSymbol) qual else adaptToMember(qual, HasMember(name)) - private def typePrimaryConstrBody(clazz : Symbol, cbody: Tree, tparams: List[Symbol], enclTparams: List[Symbol], vparamss: List[List[ValDef]]): Tree = { - // XXX: see about using the class's symbol.... - enclTparams foreach (sym => context.scope.enter(sym)) - namer.enterValueParams(vparamss) - typed(cbody) - } - private def validateNoCaseAncestor(clazz: Symbol) = { if (!phase.erasedTypes) { for (ancestor <- clazz.ancestors find (_.isCase)) { @@ -1486,125 +1479,263 @@ trait Typers extends Modes with Adaptations with Tags { unit.error(tparam.pos, "type parameter of value class may not be specialized") } - def parentTypes(templ: Template): List[Tree] = - if (templ.parents.isEmpty) List(atPos(templ.pos)(TypeTree(AnyRefClass.tpe))) - else try { - val clazz = context.owner - // Normalize supertype and mixins so that supertype is always a class, not a trait. - var supertpt = typedTypeConstructor(templ.parents.head) - val firstParent = supertpt.tpe.typeSymbol - var mixins = templ.parents.tail map typedType - // If first parent is a trait, make it first mixin and add its superclass as first parent - while ((supertpt.tpe.typeSymbol ne null) && supertpt.tpe.typeSymbol.initialize.isTrait) { - val supertpt1 = typedType(supertpt) - if (!supertpt1.isErrorTyped) { - mixins = supertpt1 :: mixins - supertpt = TypeTree(supertpt1.tpe.firstParent) setPos supertpt.pos.focus - } + /** Typechecks a parent type reference. + * + * This typecheck is harder than it might look, because it should honor early + * definitions and also perform type argument inference with the help of super call + * arguments provided in `encodedtpt`. + * + * The method is called in batches (batch = 1 time per each parent type referenced), + * two batches per definition: once from namer, when entering a ClassDef or a ModuleDef + * and once from typer, when typechecking the definition. + * + * ***Arguments*** + * + * `encodedtpt` represents the parent type reference wrapped in an `Apply` node + * which indicates value arguments (i.e. type macro arguments or super constructor call arguments) + * If no value arguments are provided by the user, the `Apply` node is still + * there, but its `args` will be set to `Nil`. + * This argument is synthesized by `tools.nsc.ast.Parsers.templateParents`. + * + * `templ` is an enclosing template, which contains a primary constructor synthesized by the parser. + * Such a constructor is a DefDef which contains early initializers and maybe a super constructor call + * (I wrote "maybe" because trait constructors don't call super constructors). + * This argument is synthesized by `tools.nsc.ast.Trees.Template`. + * + * `inMixinPosition` indicates whether the reference is not the first in the + * list of parents (and therefore cannot be a class) or the opposite. + * + * ***Return value and side effects*** + * + * Returns a `TypeTree` representing a resolved parent type. + * If the typechecked parent reference implies non-nullary and non-empty argument list, + * this argument list is attached to the returned value in SuperCallArgsAttachment. + * The attachment is necessary for the subsequent typecheck to fixup a super constructor call + * in the body of the primary constructor (see `typedTemplate` for details). + * + * This method might invoke `typedPrimaryConstrBody`, hence it might cause the side effects + * described in the docs of that method. It might also attribute the Super(_, _) reference + * (if present) inside the primary constructor of `templ`. + * + * ***Example*** + * + * For the following definition: + * + * class D extends { + * val x = 2 + * val y = 4 + * } with B(x)(3) with C(y) with T + * + * this method will be called six times: + * + * (3 times from the namer) + * typedParentType(Apply(Apply(Ident(B), List(Ident(x))), List(3)), templ, inMixinPosition = false) + * typedParentType(Apply(Ident(C), List(Ident(y))), templ, inMixinPosition = true) + * typedParentType(Apply(Ident(T), List()), templ, inMixinPosition = true) + * + * (3 times from the typer) + * + */ + private def typedParentType(encodedtpt: Tree, templ: Template, inMixinPosition: Boolean): Tree = { + val app = treeInfo.dissectApplied(encodedtpt) + val (treeInfo.Applied(core, targs, argss), decodedtpt) = (app, app.callee) + val argssAreTrivial = argss == Nil || argss == ListOfNil + + // we cannot avoid cyclic references with `initialize` here, because when type macros arrive, + // we'll have to check the probe for isTypeMacro anyways. + // therefore I think it's reasonable to trade a more specific "inherits itself" error + // for a generic, yet understandable "cyclic reference" error + var probe = typedTypeConstructor(core.duplicate).tpe.typeSymbol + if (probe == null) probe = NoSymbol + probe.initialize + + if (probe.isTrait || inMixinPosition) { + if (!argssAreTrivial) { + if (probe.isTrait) ConstrArgsInParentWhichIsTraitError(encodedtpt, probe) + else () // a class in a mixin position - this warrants an error in `validateParentClasses` + // therefore here we do nothing, e.g. don't check that the # of ctor arguments + // matches the # of ctor parameters or stuff like that } - if (supertpt.tpe.typeSymbol == AnyClass && firstParent.isTrait) - supertpt.tpe = AnyRefClass.tpe - - // Determine - // - supertparams: Missing type parameters from supertype - // - supertpe: Given supertype, polymorphic in supertparams - val supertparams = if (supertpt.hasSymbol) supertpt.symbol.typeParams else List() - var supertpe = supertpt.tpe - if (!supertparams.isEmpty) - supertpe = PolyType(supertparams, appliedType(supertpe, supertparams map (_.tpeHK))) - - // A method to replace a super reference by a New in a supercall - def transformSuperCall(scall: Tree): Tree = (scall: @unchecked) match { - case Apply(fn, args) => - treeCopy.Apply(scall, transformSuperCall(fn), args map (_.duplicate)) - case Select(Super(_, _), nme.CONSTRUCTOR) => - treeCopy.Select( - scall, - atPos(supertpt.pos.focus)(New(TypeTree(supertpe)) setType supertpe), - nme.CONSTRUCTOR) + typedType(decodedtpt) + } else { + var supertpt = typedTypeConstructor(decodedtpt) + val supertparams = if (supertpt.hasSymbol) supertpt.symbol.typeParams else Nil + if (supertparams.nonEmpty) { + typedPrimaryConstrBody(templ) { superRef => + val supertpe = PolyType(supertparams, appliedType(supertpt.tpe, supertparams map (_.tpeHK))) + val supercall = New(supertpe, mmap(argss)(_.duplicate)) + val treeInfo.Applied(Select(ctor, nme.CONSTRUCTOR), _, _) = supercall + ctor setType supertpe // this is an essential hack, otherwise it will occasionally fail to typecheck + atPos(supertpt.pos.focus)(supercall) + } match { + case EmptyTree => MissingTypeArgumentsParentTpeError(supertpt) + case tpt => supertpt = TypeTree(tpt.tpe) setPos supertpt.pos.focus + } } + // this is the place where we tell the typer what argss should be used for the super call + // if argss are nullary or empty, then (see the docs for `typedPrimaryConstrBody`) + // the super call dummy is already good enough, so we don't need to do anything + if (argssAreTrivial) supertpt else supertpt updateAttachment SuperCallArgsAttachment(argss) + } + } - treeInfo.firstConstructor(templ.body) match { - case constr @ DefDef(_, _, _, vparamss, _, cbody @ Block(cstats, cunit)) => - // Convert constructor body to block in environment and typecheck it - val (preSuperStats, superCall) = { - val (stats, rest) = cstats span (x => !treeInfo.isSuperConstrCall(x)) - (stats map (_.duplicate), if (rest.isEmpty) EmptyTree else rest.head.duplicate) - } - val cstats1 = if (superCall == EmptyTree) preSuperStats else preSuperStats :+ superCall - val cbody1 = treeCopy.Block(cbody, preSuperStats, superCall match { - case Apply(_, _) if supertparams.nonEmpty => transformSuperCall(superCall) - case _ => cunit.duplicate - }) - val outercontext = context.outer - - assert(clazz != NoSymbol, templ) - val cscope = outercontext.makeNewScope(constr, outercontext.owner) - val cbody2 = newTyper(cscope) // called both during completion AND typing. - .typePrimaryConstrBody(clazz, - cbody1, supertparams, clazz.unsafeTypeParams, vparamss map (_.map(_.duplicate))) - - superCall match { - case Apply(_, _) => - val sarg = treeInfo.firstArgument(superCall) - if (sarg != EmptyTree && supertpe.typeSymbol != firstParent) - ConstrArgsInTraitParentTpeError(sarg, firstParent) - if (!supertparams.isEmpty) - supertpt = TypeTree(cbody2.tpe) setPos supertpt.pos.focus - case _ => - if (!supertparams.isEmpty) - MissingTypeArgumentsParentTpeError(supertpt) - } + /** Typechecks the mishmash of trees that happen to be stuffed into the primary constructor of a given template. + * Before commencing the typecheck applies `superCallTransform` to a super call (if the latter exists). + * The transform can return `EmptyTree`, in which case the super call is replaced with a literal unit. + * + * ***Return value and side effects*** + * + * If a super call is present in the primary constructor and is not erased by the transform, returns it typechecked. + * Otherwise (e.g. if the primary constructor is missing or the super call isn't there) returns `EmptyTree`. + * + * As a side effect, this method attributes the underlying fields of early vals. + * Early vals aren't typechecked anywhere else, so it's essential to call `typedPrimaryConstrBody` + * at least once per definition. It'd be great to disentangle this logic at some point. + * + * ***Example*** + * + * For the following definition: + * + * class D extends { + * val x = 2 + * val y = 4 + * } with B(x)(3) with C(y) with T + * + * the primary constructor of `templ` will be: + * + * Block(List( + * ValDef(NoMods, x, TypeTree(), 2) + * ValDef(NoMods, y, TypeTree(), 4) + * Apply(Select(Super(This(tpnme.EMPTY), tpnme.EMPTY), nme.CONSTRUCTOR)), List()), + * Literal(Constant(()))) + * + * Note the Select(Super(_, _), nme.CONSTRUCTOR) part. This is the representation of + * a fill-me-in-later supercall dummy. The argss are Nil, which encodes the fact + * that supercall argss are unknown during parsing and need to be transplanted from one of the parent types. + * Read more about why the argss are unknown in `tools.nsc.ast.Trees.Template`. + * + * The entire Apply(Select(Super(This(tpnme.EMPTY), tpnme.EMPTY), nme.CONSTRUCTOR)), List()) is a dummy, + * and it's the one and only possible representation that can be emitted by parser. + * + * Despite of being unwieldy, this tree is quite convenient because: + * * It works as is for the case when no processing is required (empty ctor args for the superclass) + * * Stripping off the Apply produces a core that only needs rewrapping with applications of actual argss. + * + * For some time I was thinking of using just Select(Super(This(tpnme.EMPTY), tpnme.EMPTY), nme.CONSTRUCTOR)), + * but that one required wrapping even if the superclass doesn't take any argss. + * + * Another option would be to introduce a singleton tree akin to `emptyValDef` and use it as a dummy. + * Unfortunately this won't work out of the box, because the Super part is supposed to get attributed + * during `typedPrimaryConstrBody`. + * + * We could introduce another attachment for that or change SuperCallArgsAttachment + * to accommodate for the attributed Super, and then using the attached info to adjust the primary constructor + * during typedTemplate. However, given the scope of necessary changes (beyond a few lines) and the fact that, + * according to Martin, the whole thing is to be rewritten soon, I'd say we don't do the follow-up refactoring. + */ + private def typedPrimaryConstrBody(templ: Template)(superCallTransform: Tree => Tree): Tree = + treeInfo.firstConstructor(templ.body) match { + case ctor @ DefDef(_, _, _, vparamss, _, cbody @ Block(cstats, cunit)) => + val (preSuperStats, superCall) = { + val (stats, rest) = cstats span (x => !treeInfo.isSuperConstrCall(x)) + (stats map (_.duplicate), if (rest.isEmpty) EmptyTree else rest.head.duplicate) + } + val superCall1 = (superCall match { + case Apply(superRef @ Select(Super(_, _), nme.CONSTRUCTOR), Nil) => superCallTransform(superRef) + case EmptyTree => EmptyTree + }) orElse cunit + val cbody1 = treeCopy.Block(cbody, preSuperStats, superCall1) + + val clazz = context.owner + assert(clazz != NoSymbol, templ) + val cscope = context.outer.makeNewScope(ctor, context.outer.owner) + val cbody2 = { // called both during completion AND typing. + val typer1 = newTyper(cscope) + // XXX: see about using the class's symbol.... + clazz.unsafeTypeParams foreach (sym => typer1.context.scope.enter(sym)) + typer1.namer.enterValueParams(vparamss map (_.map(_.duplicate))) + typer1.typed(cbody1) + } - val preSuperVals = treeInfo.preSuperFields(templ.body) - if (preSuperVals.isEmpty && preSuperStats.nonEmpty) - debugwarn("Wanted to zip empty presuper val list with " + preSuperStats) - else - map2(preSuperStats, preSuperVals)((ldef, gdef) => gdef.tpt.tpe = ldef.symbol.tpe) + val preSuperVals = treeInfo.preSuperFields(templ.body) + if (preSuperVals.isEmpty && preSuperStats.nonEmpty) + debugwarn("Wanted to zip empty presuper val list with " + preSuperStats) + else + map2(preSuperStats, preSuperVals)((ldef, gdef) => gdef.tpt.tpe = ldef.symbol.tpe) - case _ => - if (!supertparams.isEmpty) - MissingTypeArgumentsParentTpeError(supertpt) - } -/* experimental: early types as type arguments - val hasEarlyTypes = templ.body exists (treeInfo.isEarlyTypeDef) - val earlyMap = new EarlyMap(clazz) - List.mapConserve(supertpt :: mixins){ tpt => - val tpt1 = checkNoEscaping.privates(clazz, tpt) - if (hasEarlyTypes) tpt1 else tpt1 setType earlyMap(tpt1.tpe) + if (superCall1 == cunit) EmptyTree else cbody2 + case _ => + EmptyTree + } + + /** Makes sure that the first type tree in the list of parent types is always a class. + * If the first parent is a trait, prepend its supertype to the list until it's a class. + */ + private def normalizeFirstParent(parents: List[Tree]): List[Tree] = parents match { + case first :: rest if treeInfo.isTraitRef(first) => + def explode(supertpt: Tree, acc: List[Tree]): List[Tree] = { + if (treeInfo.isTraitRef(supertpt)) { + val supertpt1 = typedType(supertpt) + if (!supertpt1.isErrorTyped) { + val supersupertpt = TypeTree(supertpt1.tpe.firstParent) setPos supertpt.pos.focus + return explode(supersupertpt, supertpt1 :: acc) + } + } + if (supertpt.tpe.typeSymbol == AnyClass) supertpt.tpe = AnyRefClass.tpe + supertpt :: acc } -*/ + explode(first, Nil) ++ rest + case _ => parents + } - //Console.println("parents("+clazz") = "+supertpt :: mixins);//DEBUG + /** Certain parents are added in the parser before it is known whether + * that class also declared them as parents. For instance, this is an + * error unless we take corrective action here: + * + * case class Foo() extends Serializable + * + * So we strip the duplicates before typer. + */ + private def fixDuplicateSyntheticParents(parents: List[Tree]): List[Tree] = parents match { + case Nil => Nil + case x :: xs => + val sym = x.symbol + x :: fixDuplicateSyntheticParents( + if (isPossibleSyntheticParent(sym)) xs filterNot (_.symbol == sym) + else xs + ) + } - // Certain parents are added in the parser before it is known whether - // that class also declared them as parents. For instance, this is an - // error unless we take corrective action here: - // - // case class Foo() extends Serializable - // - // So we strip the duplicates before typer. - def fixDuplicates(remaining: List[Tree]): List[Tree] = remaining match { - case Nil => Nil - case x :: xs => - val sym = x.symbol - x :: fixDuplicates( - if (isPossibleSyntheticParent(sym)) xs filterNot (_.symbol == sym) - else xs - ) + def parentTypes(templ: Template): List[Tree] = templ.parents match { + case Nil => List(atPos(templ.pos)(TypeTree(AnyRefClass.tpe))) + case first :: rest => + try { + val supertpts = fixDuplicateSyntheticParents(normalizeFirstParent( + typedParentType(first, templ, inMixinPosition = false) +: + (rest map (typedParentType(_, templ, inMixinPosition = true))))) + + // if that is required to infer the targs of a super call + // typedParentType calls typedPrimaryConstrBody to do the inferring typecheck + // as a side effect, that typecheck also assigns types to the fields underlying early vals + // however if inference is not required, the typecheck doesn't happen + // and therefore early fields have their type trees not assigned + // here we detect this situation and take preventive measures + if (treeInfo.hasUntypedPreSuperFields(templ.body)) + typedPrimaryConstrBody(templ)(superRef => EmptyTree) + + supertpts mapConserve (tpt => checkNoEscaping.privates(context.owner, tpt)) + } catch { + case ex: TypeError => + // fallback in case of cyclic errors + // @H none of the tests enter here but I couldn't rule it out + // upd. @E when a definitions inherits itself, we end up here + // because `typedParentType` triggers `initialize` for parent types symbols + log("Type error calculating parents in template " + templ) + log("Error: " + ex) + ParentTypesError(templ, ex) + List(TypeTree(AnyRefClass.tpe)) } - - fixDuplicates(supertpt :: mixins) mapConserve (tpt => checkNoEscaping.privates(clazz, tpt)) - } - catch { - case ex: TypeError => - // fallback in case of cyclic errors - // @H none of the tests enter here but I couldn't rule it out - log("Type error calculating parents in template " + templ) - log("Error: " + ex) - ParentTypesError(templ, ex) - List(TypeTree(AnyRefClass.tpe)) - } + } /**

Check that

*
    @@ -1844,7 +1975,8 @@ trait Typers extends Modes with Adaptations with Tags { // the following is necessary for templates generated later assert(clazz.info.decls != EmptyScope, clazz) enterSyms(context.outer.make(templ, clazz, clazz.info.decls), templ.body) - validateParentClasses(parents1, selfType) + if (!templ.isErrorTyped) // if `parentTypes` has invalidated the template, don't validate it anymore + validateParentClasses(parents1, selfType) if (clazz.isCase) validateNoCaseAncestor(clazz) @@ -1854,9 +1986,28 @@ trait Typers extends Modes with Adaptations with Tags { if (!phase.erasedTypes && !clazz.info.resultType.isError) // @S: prevent crash for duplicated type members checkFinitary(clazz.info.resultType.asInstanceOf[ClassInfoType]) - val body = - if (isPastTyper || reporter.hasErrors) templ.body - else templ.body flatMap rewrappingWrapperTrees(namer.addDerivedTrees(Typer.this, _)) + val body = { + val body = + if (isPastTyper || reporter.hasErrors) templ.body + else templ.body flatMap rewrappingWrapperTrees(namer.addDerivedTrees(Typer.this, _)) + parents1.head match { + case CarriesSuperCallArgs(argss) => + if (clazz.isTrait) { + ConstrArgsInParentOfTraitError(parents1.head, clazz) + body + } else { + val primaryCtor = treeInfo.firstConstructor(templ.body) + val primaryCtor1 = (deriveDefDef(primaryCtor) { + case block @ Block(earlyVals :+ Apply(superRef, Nil), unit) => + val pos = wrappingPos(parents1.head.pos, argss.flatten) + val superCall = atPos(pos)((superRef /: argss)(Apply.apply)) + Block(earlyVals :+ superCall, unit) setPos pos + }) setPos pos + body map { case `primaryCtor` => primaryCtor1; case stat => stat } + } + case _ => body + } + } val body1 = typedStats(body, templ.symbol) @@ -2603,7 +2754,7 @@ trait Typers extends Modes with Adaptations with Tags { if (members.head eq EmptyTree) setError(tree) else { val typedBlock = typedPos(tree.pos, mode, pt) { - Block(ClassDef(anonClass, NoMods, ListOfNil, ListOfNil, members, tree.pos.focus), atPos(tree.pos.focus)(New(anonClass.tpe))) + Block(ClassDef(anonClass, NoMods, ListOfNil, members, tree.pos.focus), atPos(tree.pos.focus)(New(anonClass.tpe))) } // Don't leak implementation details into the type, see SI-6575 if (isPartial && !typedBlock.isErrorTyped) diff --git a/src/compiler/scala/tools/nsc/typechecker/Unapplies.scala b/src/compiler/scala/tools/nsc/typechecker/Unapplies.scala index bf44b65406..a34d7389bf 100644 --- a/src/compiler/scala/tools/nsc/typechecker/Unapplies.scala +++ b/src/compiler/scala/tools/nsc/typechecker/Unapplies.scala @@ -126,7 +126,7 @@ trait Unapplies extends ast.TreeDSL ModuleDef( Modifiers(cdef.mods.flags & AccessFlags | SYNTHETIC, cdef.mods.privateWithin), cdef.name.toTermName, - Template(parents, emptyValDef, NoMods, Nil, ListOfNil, body, cdef.impl.pos.focus)) + Template(parents, emptyValDef, NoMods, Nil, body, cdef.impl.pos.focus)) } private val caseMods = Modifiers(SYNTHETIC | CASE) diff --git a/src/compiler/scala/tools/reflect/ToolBoxFactory.scala b/src/compiler/scala/tools/reflect/ToolBoxFactory.scala index 95135b84e0..0125f1b189 100644 --- a/src/compiler/scala/tools/reflect/ToolBoxFactory.scala +++ b/src/compiler/scala/tools/reflect/ToolBoxFactory.scala @@ -230,7 +230,6 @@ abstract class ToolBoxFactory[U <: JavaUniverse](val u: U) { factorySelf => emptyValDef, NoMods, List(), - List(List()), List(methdef), NoPosition)) trace("wrapped: ")(showAttributed(moduledef, true, true, settings.Yshowsymkinds.value)) diff --git a/src/reflect/scala/reflect/internal/TreeInfo.scala b/src/reflect/scala/reflect/internal/TreeInfo.scala index 7423a2ff57..8908036442 100644 --- a/src/reflect/scala/reflect/internal/TreeInfo.scala +++ b/src/reflect/scala/reflect/internal/TreeInfo.scala @@ -330,6 +330,9 @@ abstract class TreeInfo { def preSuperFields(stats: List[Tree]): List[ValDef] = stats collect { case vd: ValDef if isEarlyValDef(vd) => vd } + def hasUntypedPreSuperFields(stats: List[Tree]): Boolean = + preSuperFields(stats) exists (_.tpt.isEmpty) + def isEarlyDef(tree: Tree) = tree match { case TypeDef(mods, _, _, _) => mods hasFlag PRESUPER case ValDef(mods, _, _, _) => mods hasFlag PRESUPER @@ -494,6 +497,10 @@ abstract class TreeInfo { def isSynthCaseSymbol(sym: Symbol) = sym hasAllFlags SYNTH_CASE_FLAGS def hasSynthCaseSymbol(t: Tree) = t.symbol != null && isSynthCaseSymbol(t.symbol) + def isTraitRef(tree: Tree): Boolean = { + val sym = if (tree.tpe != null) tree.tpe.typeSymbol else null + ((sym ne null) && sym.initialize.isTrait) + } /** Applications in Scala can have one of the following shapes: * diff --git a/src/reflect/scala/reflect/internal/Trees.scala b/src/reflect/scala/reflect/internal/Trees.scala index 6df4b75a88..0087bb93e7 100644 --- a/src/reflect/scala/reflect/internal/Trees.scala +++ b/src/reflect/scala/reflect/internal/Trees.scala @@ -1034,6 +1034,9 @@ trait Trees extends api.Trees { self: SymbolTable => def New(tpe: Type, args: Tree*): Tree = ApplyConstructor(TypeTree(tpe), args.toList) + def New(tpe: Type, argss: List[List[Tree]]): Tree = + New(TypeTree(tpe), argss) + def New(sym: Symbol, args: Tree*): Tree = New(sym.tpe, args: _*) diff --git a/test/files/neg/anyval-anyref-parent.check b/test/files/neg/anyval-anyref-parent.check index fe20e5de81..8c2aa36583 100644 --- a/test/files/neg/anyval-anyref-parent.check +++ b/test/files/neg/anyval-anyref-parent.check @@ -3,7 +3,7 @@ trait Foo2 extends AnyVal // fail ^ anyval-anyref-parent.scala:5: error: Any does not have a constructor class Bar1 extends Any // fail - ^ + ^ anyval-anyref-parent.scala:6: error: value class needs to have exactly one public val parameter class Bar2(x: Int) extends AnyVal // fail ^ diff --git a/test/files/neg/cyclics-import.check b/test/files/neg/cyclics-import.check index ef355fab0a..be09fca374 100644 --- a/test/files/neg/cyclics-import.check +++ b/test/files/neg/cyclics-import.check @@ -3,13 +3,4 @@ Note: this is often due in part to a class depending on a definition nested with If applicable, you may wish to try moving some members into another object. import User.UserStatus._ ^ -cyclics-import.scala:12: error: not found: type Value - type UserStatus = Value - ^ -cyclics-import.scala:14: error: not found: value Value - val Active = Value("1") - ^ -cyclics-import.scala:15: error: not found: value Value - val Disabled = Value("2") - ^ -four errors found +one error found diff --git a/test/files/neg/names-defaults-neg.check b/test/files/neg/names-defaults-neg.check index f3c45a6aa0..6f9dc7d127 100644 --- a/test/files/neg/names-defaults-neg.check +++ b/test/files/neg/names-defaults-neg.check @@ -100,7 +100,7 @@ Error occurred in an application involving default arguments. ^ names-defaults-neg.scala:86: error: module extending its companion class cannot use default constructor arguments object C extends C() - ^ + ^ names-defaults-neg.scala:90: error: deprecated parameter name x has to be distinct from any other parameter name (deprecated or not). def deprNam1(x: Int, @deprecatedName('x) y: String) = 0 ^ diff --git a/test/files/neg/protected-constructors.check b/test/files/neg/protected-constructors.check index f137158ed6..e295917050 100644 --- a/test/files/neg/protected-constructors.check +++ b/test/files/neg/protected-constructors.check @@ -19,7 +19,4 @@ protected-constructors.scala:15: error: class Foo3 in object Ding cannot be acce object Ding in package dingus where target is defined class Bar3 extends Ding.Foo3("abc") ^ -protected-constructors.scala:15: error: too many arguments for constructor Object: ()Object - class Bar3 extends Ding.Foo3("abc") - ^ -5 errors found +four errors found diff --git a/test/files/neg/t2148.check b/test/files/neg/t2148.check index 5113b48e51..27b5dce507 100644 --- a/test/files/neg/t2148.check +++ b/test/files/neg/t2148.check @@ -1,4 +1,4 @@ -t2148.scala:9: error: type A is not a stable prefix +t2148.scala:9: error: A is not a legal prefix for a constructor val b = new A with A#A1 ^ one error found diff --git a/test/files/neg/t409.check b/test/files/neg/t409.check index 433d64d25d..0edc0d03cd 100644 --- a/test/files/neg/t409.check +++ b/test/files/neg/t409.check @@ -1,4 +1,4 @@ -t409.scala:6: error: traits or objects may not have parameters +t409.scala:6: error: class Case1 needs to be a trait to be mixed in class Toto extends Expr with Case1(12); - ^ + ^ one error found diff --git a/test/files/neg/t5529.check b/test/files/neg/t5529.check index 5d2175fa79..da3f84e1ec 100644 --- a/test/files/neg/t5529.check +++ b/test/files/neg/t5529.check @@ -4,7 +4,4 @@ t5529.scala:12: error: File is already defined as class File t5529.scala:10: error: class type required but test.Test.File found sealed class Dir extends File { } ^ -t5529.scala:10: error: test.Test.File does not have a constructor - sealed class Dir extends File { } - ^ -three errors found +two errors found diff --git a/test/files/neg/t5696.check b/test/files/neg/t5696.check index 72b7781fc4..e0fb61b839 100644 --- a/test/files/neg/t5696.check +++ b/test/files/neg/t5696.check @@ -15,5 +15,5 @@ t5696.scala:38: error: too many argument lists for constructor invocation ^ t5696.scala:46: error: too many argument lists for constructor invocation object x extends G(1)(2) {} - ^ + ^ 6 errors found diff --git a/test/files/neg/t667.check b/test/files/neg/t667.check index d4367bc87b..e68c6dea00 100644 --- a/test/files/neg/t667.check +++ b/test/files/neg/t667.check @@ -1,4 +1,4 @@ -t667.scala:8: error: class Ni inherits itself +t667.scala:8: error: illegal cyclic reference involving class Ni class Ni extends super.Ni with Ni; - ^ + ^ one error found diff --git a/test/files/neg/t877.check b/test/files/neg/t877.check index 5f25bd439c..c3d4ab6584 100644 --- a/test/files/neg/t877.check +++ b/test/files/neg/t877.check @@ -1,7 +1,7 @@ t877.scala:3: error: Invalid literal number trait Foo extends A(22A, Bug!) {} ^ -t877.scala:3: error: parents of traits may not have parameters +t877.scala:3: error: ')' expected but eof found. trait Foo extends A(22A, Bug!) {} - ^ + ^ two errors found diff --git a/test/files/run/t5064.check b/test/files/run/t5064.check index 077006abd9..61ccfd16e7 100644 --- a/test/files/run/t5064.check +++ b/test/files/run/t5064.check @@ -1,6 +1,6 @@ -[12] T5064.super.() -[12] T5064.super. -[12] this +[53] T5064.super.() +[53] T5064.super. +[53] this [16:23] immutable.this.List.apply(scala.this.Predef.wrapIntArray(Array[Int]{1})) [16:20] immutable.this.List.apply <16:20> immutable.this.List -- cgit v1.2.3 From 0ebf72b9498108e67c2133c6522c436af50a18e8 Mon Sep 17 00:00:00 2001 From: Eugene Burmako Date: Sun, 25 Nov 2012 22:00:11 +0100 Subject: introduces global.pendingSuperCall Similarly to global.emptyValDef, which is a dummy that stands for an empty self-type, this commit introduces global.pendingSuperCall, which stands for a yet-to-be-filled-in call to a superclass constructor. pendingSuperCall is emitted by Parsers.template, treated specially by Typers.typedParentType and replaced with a real superclass ctor call by Typers.typedTemplate. To avoid copy/paste, this commit also factors out and unifies dumminess of EmptyTree, emptyValDef and pendingSuperCall - they all don't have a position and actively refuse to gain one, same story for tpe. --- .../scala/reflect/reify/codegen/GenTrees.scala | 4 +- .../scala/reflect/reify/codegen/GenUtils.scala | 3 - src/compiler/scala/tools/nsc/ast/Positions.scala | 2 +- src/compiler/scala/tools/nsc/ast/Trees.scala | 23 +++-- .../tools/nsc/typechecker/StdAttachments.scala | 12 ++- .../scala/tools/nsc/typechecker/Typers.scala | 103 ++++++++------------- src/reflect/scala/reflect/api/BuildUtils.scala | 2 - src/reflect/scala/reflect/api/Trees.scala | 9 ++ .../scala/reflect/internal/BuildUtils.scala | 2 - src/reflect/scala/reflect/internal/Importers.scala | 2 + src/reflect/scala/reflect/internal/Positions.scala | 2 +- src/reflect/scala/reflect/internal/Printers.scala | 4 +- src/reflect/scala/reflect/internal/StdNames.scala | 1 + src/reflect/scala/reflect/internal/Trees.scala | 20 ++-- test/files/run/t5603.check | 4 +- 15 files changed, 95 insertions(+), 98 deletions(-) diff --git a/src/compiler/scala/reflect/reify/codegen/GenTrees.scala b/src/compiler/scala/reflect/reify/codegen/GenTrees.scala index bdcc7383b0..d6bafb6759 100644 --- a/src/compiler/scala/reflect/reify/codegen/GenTrees.scala +++ b/src/compiler/scala/reflect/reify/codegen/GenTrees.scala @@ -45,7 +45,9 @@ trait GenTrees { case global.EmptyTree => reifyMirrorObject(EmptyTree) case global.emptyValDef => - mirrorBuildSelect(nme.emptyValDef) + mirrorSelect(nme.emptyValDef) + case global.pendingSuperCall => + mirrorSelect(nme.pendingSuperCall) case FreeDef(_, _, _, _, _) => reifyNestedFreeDef(tree) case FreeRef(_, _) => diff --git a/src/compiler/scala/reflect/reify/codegen/GenUtils.scala b/src/compiler/scala/reflect/reify/codegen/GenUtils.scala index 49877b4286..21db93d8f5 100644 --- a/src/compiler/scala/reflect/reify/codegen/GenUtils.scala +++ b/src/compiler/scala/reflect/reify/codegen/GenUtils.scala @@ -34,9 +34,6 @@ trait GenUtils { def mirrorSelect(name: String): Tree = termPath(nme.UNIVERSE_PREFIX + name) - def mirrorBuildSelect(name: String): Tree = - termPath(nme.UNIVERSE_BUILD_PREFIX + name) - def mirrorMirrorSelect(name: String): Tree = termPath(nme.MIRROR_PREFIX + name) diff --git a/src/compiler/scala/tools/nsc/ast/Positions.scala b/src/compiler/scala/tools/nsc/ast/Positions.scala index d8fb632f73..0503c5fb10 100644 --- a/src/compiler/scala/tools/nsc/ast/Positions.scala +++ b/src/compiler/scala/tools/nsc/ast/Positions.scala @@ -20,7 +20,7 @@ trait Positions extends scala.reflect.internal.Positions { // When we prune due to encountering a position, traverse the // pruned children so we can warn about those lacking positions. t.children foreach { c => - if ((c eq EmptyTree) || (c eq emptyValDef)) () + if (c.isDummy) () else if (c.pos == NoPosition) { reporter.warning(t.pos, " Positioned tree has unpositioned child in phase " + globalPhase) inform("parent: " + treeSymStatus(t)) diff --git a/src/compiler/scala/tools/nsc/ast/Trees.scala b/src/compiler/scala/tools/nsc/ast/Trees.scala index b8c59da95c..e848fa223b 100644 --- a/src/compiler/scala/tools/nsc/ast/Trees.scala +++ b/src/compiler/scala/tools/nsc/ast/Trees.scala @@ -65,6 +65,13 @@ trait Trees extends scala.reflect.internal.Trees { self: Global => // --- factory methods ---------------------------------------------------------- + /** Factory method for a primary constructor super call `super.(args_1)...(args_n)` + */ + def PrimarySuperCall(argss: List[List[Tree]]): Tree = argss match { + case Nil => Apply(gen.mkSuperSelect, Nil) + case xs :: rest => rest.foldLeft(Apply(gen.mkSuperSelect, xs): Tree)(Apply.apply) + } + /** Generates a template with constructor corresponding to * * constrmods (vparams1_) ... (vparams_n) preSuper { presupers } @@ -117,12 +124,12 @@ trait Trees extends scala.reflect.internal.Trees { self: Global => if (vparamss1.isEmpty || !vparamss1.head.isEmpty && vparamss1.head.head.mods.isImplicit) vparamss1 = List() :: vparamss1; val superRef: Tree = atPos(superPos)(gen.mkSuperSelect) - val superCall = Apply(superRef, Nil) // we can't know in advance which of the parents will end up as a superclass - // this requires knowing which of the parents is a type macro and which is not - // and that's something that cannot be found out before typer - // (the type macros aren't in the trunk yet, but there is a plan for them to land there soon) - // this means that we don't know what will be the arguments of the super call - // therefore here we emit a dummy which gets populated when the template is named and typechecked + val superCall = pendingSuperCall // we can't know in advance which of the parents will end up as a superclass + // this requires knowing which of the parents is a type macro and which is not + // and that's something that cannot be found out before typer + // (the type macros aren't in the trunk yet, but there is a plan for them to land there soon) + // this means that we don't know what will be the arguments of the super call + // therefore here we emit a dummy which gets populated when the template is named and typechecked List( // TODO: previously this was `wrappingPos(superPos, lvdefs ::: argss.flatten)` // is it going to be a problem that we can no longer include the `argss`? @@ -330,6 +337,8 @@ trait Trees extends scala.reflect.internal.Trees { self: Global => else super.transform { tree match { + case tree if tree.isDummy => + tree case tpt: TypeTree => if (tpt.original != null) transform(tpt.original) @@ -343,8 +352,6 @@ trait Trees extends scala.reflect.internal.Trees { self: Global => transform(fn) case This(_) if tree.symbol != null && tree.symbol.isPackageClass => tree - case EmptyTree => - tree case _ => val dupl = tree.duplicate if (tree.hasSymbol && (!localOnly || (locals contains tree.symbol)) && !(keepLabels && tree.symbol.isLabel)) diff --git a/src/compiler/scala/tools/nsc/typechecker/StdAttachments.scala b/src/compiler/scala/tools/nsc/typechecker/StdAttachments.scala index fa2913bee3..0a1d3bfa7a 100644 --- a/src/compiler/scala/tools/nsc/typechecker/StdAttachments.scala +++ b/src/compiler/scala/tools/nsc/typechecker/StdAttachments.scala @@ -21,12 +21,14 @@ trait StdAttachments { */ case class SuperCallArgsAttachment(argss: List[List[Tree]]) - /** Extractor for `SuperCallArgsAttachment`. + /** Convenience method for `SuperCallArgsAttachment`. * Compared with `MacroRuntimeAttachment` this attachment has different a usage pattern, * so it really benefits from a dedicated extractor. */ - object CarriesSuperCallArgs { - def unapply(tree: Tree): Option[List[List[Tree]]] = - tree.attachments.get[SuperCallArgsAttachment] collect { case SuperCallArgsAttachment(argss) => argss } - } + def superCallArgs(tree: Tree): Option[List[List[Tree]]] = + tree.attachments.get[SuperCallArgsAttachment] collect { case SuperCallArgsAttachment(argss) => argss } + + /** Determines whether the given tree has an associated SuperCallArgsAttachment. + */ + def hasSuperArgs(tree: Tree): Boolean = superCallArgs(tree).nonEmpty } \ No newline at end of file diff --git a/src/compiler/scala/tools/nsc/typechecker/Typers.scala b/src/compiler/scala/tools/nsc/typechecker/Typers.scala index 3f5a4036aa..96432f49a7 100644 --- a/src/compiler/scala/tools/nsc/typechecker/Typers.scala +++ b/src/compiler/scala/tools/nsc/typechecker/Typers.scala @@ -52,8 +52,10 @@ trait Typers extends Modes with Adaptations with Tags { object UnTyper extends Traverser { override def traverse(tree: Tree) = { - if (tree != EmptyTree) tree.tpe = null - if (tree.hasSymbol) tree.symbol = NoSymbol + if (!tree.isDummy) { + tree.tpe = null + if (tree.hasSymbol) tree.symbol = NoSymbol + } super.traverse(tree) } } @@ -1561,7 +1563,7 @@ trait Typers extends Modes with Adaptations with Tags { var supertpt = typedTypeConstructor(decodedtpt) val supertparams = if (supertpt.hasSymbol) supertpt.symbol.typeParams else Nil if (supertparams.nonEmpty) { - typedPrimaryConstrBody(templ) { superRef => + typedPrimaryConstrBody(templ) { val supertpe = PolyType(supertparams, appliedType(supertpt.tpe, supertparams map (_.tpeHK))) val supercall = New(supertpe, mmap(argss)(_.duplicate)) val treeInfo.Applied(Select(ctor, nme.CONSTRUCTOR), _, _) = supercall @@ -1580,8 +1582,8 @@ trait Typers extends Modes with Adaptations with Tags { } /** Typechecks the mishmash of trees that happen to be stuffed into the primary constructor of a given template. - * Before commencing the typecheck applies `superCallTransform` to a super call (if the latter exists). - * The transform can return `EmptyTree`, in which case the super call is replaced with a literal unit. + * Before commencing the typecheck, replaces the `pendingSuperCall` dummy with the result of `actualSuperCall`. + * `actualSuperCall` can return `EmptyTree`, in which case the dummy is replaced with a literal unit. * * ***Return value and side effects*** * @@ -1606,34 +1608,14 @@ trait Typers extends Modes with Adaptations with Tags { * Block(List( * ValDef(NoMods, x, TypeTree(), 2) * ValDef(NoMods, y, TypeTree(), 4) - * Apply(Select(Super(This(tpnme.EMPTY), tpnme.EMPTY), nme.CONSTRUCTOR)), List()), + * global.pendingSuperCall, * Literal(Constant(()))) * - * Note the Select(Super(_, _), nme.CONSTRUCTOR) part. This is the representation of - * a fill-me-in-later supercall dummy. The argss are Nil, which encodes the fact - * that supercall argss are unknown during parsing and need to be transplanted from one of the parent types. - * Read more about why the argss are unknown in `tools.nsc.ast.Trees.Template`. - * - * The entire Apply(Select(Super(This(tpnme.EMPTY), tpnme.EMPTY), nme.CONSTRUCTOR)), List()) is a dummy, - * and it's the one and only possible representation that can be emitted by parser. - * - * Despite of being unwieldy, this tree is quite convenient because: - * * It works as is for the case when no processing is required (empty ctor args for the superclass) - * * Stripping off the Apply produces a core that only needs rewrapping with applications of actual argss. - * - * For some time I was thinking of using just Select(Super(This(tpnme.EMPTY), tpnme.EMPTY), nme.CONSTRUCTOR)), - * but that one required wrapping even if the superclass doesn't take any argss. - * - * Another option would be to introduce a singleton tree akin to `emptyValDef` and use it as a dummy. - * Unfortunately this won't work out of the box, because the Super part is supposed to get attributed - * during `typedPrimaryConstrBody`. - * - * We could introduce another attachment for that or change SuperCallArgsAttachment - * to accommodate for the attributed Super, and then using the attached info to adjust the primary constructor - * during typedTemplate. However, given the scope of necessary changes (beyond a few lines) and the fact that, - * according to Martin, the whole thing is to be rewritten soon, I'd say we don't do the follow-up refactoring. + * Note the `pendingSuperCall` part. This is the representation of a fill-me-in-later supercall dummy, + * which encodes the fact that supercall argss are unknown during parsing and need to be transplanted + * from one of the parent types. Read more about why the argss are unknown in `tools.nsc.ast.Trees.Template`. */ - private def typedPrimaryConstrBody(templ: Template)(superCallTransform: Tree => Tree): Tree = + private def typedPrimaryConstrBody(templ: Template)(actualSuperCall: => Tree): Tree = treeInfo.firstConstructor(templ.body) match { case ctor @ DefDef(_, _, _, vparamss, _, cbody @ Block(cstats, cunit)) => val (preSuperStats, superCall) = { @@ -1641,7 +1623,7 @@ trait Typers extends Modes with Adaptations with Tags { (stats map (_.duplicate), if (rest.isEmpty) EmptyTree else rest.head.duplicate) } val superCall1 = (superCall match { - case Apply(superRef @ Select(Super(_, _), nme.CONSTRUCTOR), Nil) => superCallTransform(superRef) + case global.pendingSuperCall => actualSuperCall case EmptyTree => EmptyTree }) orElse cunit val cbody1 = treeCopy.Block(cbody, preSuperStats, superCall1) @@ -1721,7 +1703,7 @@ trait Typers extends Modes with Adaptations with Tags { // and therefore early fields have their type trees not assigned // here we detect this situation and take preventive measures if (treeInfo.hasUntypedPreSuperFields(templ.body)) - typedPrimaryConstrBody(templ)(superRef => EmptyTree) + typedPrimaryConstrBody(templ)(EmptyTree) supertpts mapConserve (tpt => checkNoEscaping.privates(context.owner, tpt)) } catch { @@ -1979,6 +1961,8 @@ trait Typers extends Modes with Adaptations with Tags { validateParentClasses(parents1, selfType) if (clazz.isCase) validateNoCaseAncestor(clazz) + if (clazz.isTrait && hasSuperArgs(parents1.head)) + ConstrArgsInParentOfTraitError(parents1.head, clazz) if ((clazz isSubClass ClassfileAnnotationClass) && !clazz.owner.isPackageClass) unit.error(clazz.pos, "inner classes cannot be classfile annotations") @@ -1990,23 +1974,16 @@ trait Typers extends Modes with Adaptations with Tags { val body = if (isPastTyper || reporter.hasErrors) templ.body else templ.body flatMap rewrappingWrapperTrees(namer.addDerivedTrees(Typer.this, _)) - parents1.head match { - case CarriesSuperCallArgs(argss) => - if (clazz.isTrait) { - ConstrArgsInParentOfTraitError(parents1.head, clazz) - body - } else { - val primaryCtor = treeInfo.firstConstructor(templ.body) - val primaryCtor1 = (deriveDefDef(primaryCtor) { - case block @ Block(earlyVals :+ Apply(superRef, Nil), unit) => - val pos = wrappingPos(parents1.head.pos, argss.flatten) - val superCall = atPos(pos)((superRef /: argss)(Apply.apply)) - Block(earlyVals :+ superCall, unit) setPos pos - }) setPos pos - body map { case `primaryCtor` => primaryCtor1; case stat => stat } - } - case _ => body + val primaryCtor = treeInfo.firstConstructor(body) + val primaryCtor1 = primaryCtor match { + case DefDef(_, _, _, _, _, Block(earlyVals :+ global.pendingSuperCall, unit)) => + val argss = superCallArgs(parents1.head) getOrElse Nil + val pos = wrappingPos(parents1.head.pos, argss.flatten) + val superCall = atPos(pos)(PrimarySuperCall(argss)) + deriveDefDef(primaryCtor)(block => Block(earlyVals :+ superCall, unit) setPos pos) setPos pos + case _ => primaryCtor } + body mapConserve { case `primaryCtor` => primaryCtor1; case stat => stat } } val body1 = typedStats(body, templ.symbol) @@ -5752,21 +5729,21 @@ trait Typers extends Modes with Adaptations with Tags { // enough to see those. See #3938 ConstructorPrefixError(tree, restpe) } else { - //@M fix for #2208 - // if there are no type arguments, normalization does not bypass any checks, so perform it to get rid of AnyRef - if (result.tpe.typeArgs.isEmpty) { - // minimal check: if(result.tpe.typeSymbolDirect eq AnyRefClass) { - // must expand the fake AnyRef type alias, because bootstrapping (init in Definitions) is not - // designed to deal with the cycles in the scala package (ScalaObject extends - // AnyRef, but the AnyRef type alias is entered after the scala package is - // loaded and completed, so that ScalaObject is unpickled while AnyRef is not - // yet defined ) - // !!! TODO - revisit now that ScalaObject is gone. - result setType(restpe) - } else { // must not normalize: type application must be (bounds-)checked (during RefChecks), see #2208 - // during uncurry (after refchecks), all types are normalized - result - } + //@M fix for #2208 + // if there are no type arguments, normalization does not bypass any checks, so perform it to get rid of AnyRef + if (result.tpe.typeArgs.isEmpty) { + // minimal check: if(result.tpe.typeSymbolDirect eq AnyRefClass) { + // must expand the fake AnyRef type alias, because bootstrapping (init in Definitions) is not + // designed to deal with the cycles in the scala package (ScalaObject extends + // AnyRef, but the AnyRef type alias is entered after the scala package is + // loaded and completed, so that ScalaObject is unpickled while AnyRef is not + // yet defined ) + // !!! TODO - revisit now that ScalaObject is gone. + result setType(restpe) + } else { // must not normalize: type application must be (bounds-)checked (during RefChecks), see #2208 + // during uncurry (after refchecks), all types are normalized + result + } } } diff --git a/src/reflect/scala/reflect/api/BuildUtils.scala b/src/reflect/scala/reflect/api/BuildUtils.scala index 0c8e81a220..8f256aa1f5 100644 --- a/src/reflect/scala/reflect/api/BuildUtils.scala +++ b/src/reflect/scala/reflect/api/BuildUtils.scala @@ -59,8 +59,6 @@ private[reflect] trait BuildUtils { self: Universe => def flagsFromBits(bits: Long): FlagSet - def emptyValDef: ValDef - def This(sym: Symbol): Tree def Select(qualifier: Tree, sym: Symbol): Select diff --git a/src/reflect/scala/reflect/api/Trees.scala b/src/reflect/scala/reflect/api/Trees.scala index c98107f9b5..9a65ddaa96 100644 --- a/src/reflect/scala/reflect/api/Trees.scala +++ b/src/reflect/scala/reflect/api/Trees.scala @@ -2366,6 +2366,15 @@ trait Trees { self: Universe => */ val emptyValDef: ValDef + /** An empty superclass constructor call corresponding to: + * super.() + * This is used as a placeholder in the primary constructor body in class templates + * to denote the insertion point of a call to superclass constructor after the typechecker + * figures out the superclass of a given template. + * @group Trees + */ + val pendingSuperCall: Apply + // ---------------------- factories ---------------------------------------------- /** A factory method for `ClassDef` nodes. diff --git a/src/reflect/scala/reflect/internal/BuildUtils.scala b/src/reflect/scala/reflect/internal/BuildUtils.scala index 9f41f0336e..b1b0c5b60b 100644 --- a/src/reflect/scala/reflect/internal/BuildUtils.scala +++ b/src/reflect/scala/reflect/internal/BuildUtils.scala @@ -47,8 +47,6 @@ trait BuildUtils { self: SymbolTable => def flagsFromBits(bits: Long): FlagSet = bits - def emptyValDef: ValDef = self.emptyValDef - def This(sym: Symbol): Tree = self.This(sym) def Select(qualifier: Tree, sym: Symbol): Select = self.Select(qualifier, sym) diff --git a/src/reflect/scala/reflect/internal/Importers.scala b/src/reflect/scala/reflect/internal/Importers.scala index 43902c1930..2f2b02975c 100644 --- a/src/reflect/scala/reflect/internal/Importers.scala +++ b/src/reflect/scala/reflect/internal/Importers.scala @@ -334,6 +334,8 @@ trait Importers extends api.Importers { self: SymbolTable => new ModuleDef(importModifiers(mods), importName(name).toTermName, importTemplate(impl)) case from.emptyValDef => emptyValDef + case from.pendingSuperCall => + pendingSuperCall case from.ValDef(mods, name, tpt, rhs) => new ValDef(importModifiers(mods), importName(name).toTermName, importTree(tpt), importTree(rhs)) case from.DefDef(mods, name, tparams, vparamss, tpt, rhs) => diff --git a/src/reflect/scala/reflect/internal/Positions.scala b/src/reflect/scala/reflect/internal/Positions.scala index faa161d6b1..b65df0e70b 100644 --- a/src/reflect/scala/reflect/internal/Positions.scala +++ b/src/reflect/scala/reflect/internal/Positions.scala @@ -38,7 +38,7 @@ trait Positions extends api.Positions { self: SymbolTable => protected class DefaultPosAssigner extends PosAssigner { var pos: Position = _ override def traverse(t: Tree) { - if (t eq EmptyTree) () + if (t.isDummy) () else if (t.pos == NoPosition) { t.setPos(pos) super.traverse(t) // TODO: bug? shouldn't the traverse be outside of the if? diff --git a/src/reflect/scala/reflect/internal/Printers.scala b/src/reflect/scala/reflect/internal/Printers.scala index 80d247c0ea..6f834803c4 100644 --- a/src/reflect/scala/reflect/internal/Printers.scala +++ b/src/reflect/scala/reflect/internal/Printers.scala @@ -542,8 +542,10 @@ trait Printers extends api.Printers { self: SymbolTable => print(")") case EmptyTree => print("EmptyTree") - case emptyValDef: AnyRef if emptyValDef eq self.emptyValDef => + case self.emptyValDef => print("emptyValDef") + case self.pendingSuperCall => + print("pendingSuperCall") case tree: Tree => val hasSymbol = tree.hasSymbol && tree.symbol != NoSymbol val isError = hasSymbol && tree.symbol.name.toString == nme.ERROR.toString diff --git a/src/reflect/scala/reflect/internal/StdNames.scala b/src/reflect/scala/reflect/internal/StdNames.scala index 5e7f5777b2..c870d8972d 100644 --- a/src/reflect/scala/reflect/internal/StdNames.scala +++ b/src/reflect/scala/reflect/internal/StdNames.scala @@ -730,6 +730,7 @@ trait StdNames { val null_ : NameType = "null" val ofDim: NameType = "ofDim" val origin: NameType = "origin" + val pendingSuperCall: NameType = "pendingSuperCall" val prefix : NameType = "prefix" val productArity: NameType = "productArity" val productElement: NameType = "productElement" diff --git a/src/reflect/scala/reflect/internal/Trees.scala b/src/reflect/scala/reflect/internal/Trees.scala index 0087bb93e7..047298cf82 100644 --- a/src/reflect/scala/reflect/internal/Trees.scala +++ b/src/reflect/scala/reflect/internal/Trees.scala @@ -36,6 +36,7 @@ trait Trees extends api.Trees { self: SymbolTable => def isDef = false def isEmpty = false + def isDummy = false /** The canonical way to test if a Tree represents a term. */ @@ -228,14 +229,6 @@ trait Trees extends api.Trees { self: SymbolTable => override def isDef = true } - case object EmptyTree extends TermTree { - val asList = List(this) - super.tpe_=(NoType) - override def tpe_=(t: Type) = - if (t != NoType) throw new UnsupportedOperationException("tpe_=("+t+") inapplicable for ") - override def isEmpty = true - } - abstract class MemberDef extends DefTree with MemberDefApi { def mods: Modifiers def keyword: String = this match { @@ -599,6 +592,7 @@ trait Trees extends api.Trees { self: SymbolTable => case _: ApplyToImplicitArgs => new ApplyToImplicitArgs(fun, args) case _: ApplyImplicitView => new ApplyImplicitView(fun, args) // TODO: ApplyConstructor ??? + case self.pendingSuperCall => self.pendingSuperCall case _ => new Apply(fun, args) }).copyAttrs(tree) def ApplyDynamic(tree: Tree, qual: Tree, args: List[Tree]) = @@ -961,12 +955,20 @@ trait Trees extends api.Trees { self: SymbolTable => def ValDef(sym: Symbol): ValDef = ValDef(sym, EmptyTree) - object emptyValDef extends ValDef(Modifiers(PRIVATE), nme.WILDCARD, TypeTree(NoType), EmptyTree) { + trait DummyTree extends Tree { override def isEmpty = true + override def isDummy = true super.setPos(NoPosition) override def setPos(pos: Position) = { assert(false); this } + super.setType(NoType) + override def tpe_=(t: Type) = + if (t != NoType) throw new UnsupportedOperationException("tpe_=("+t+") inapplicable for "+self.toString) } + case object EmptyTree extends TermTree with DummyTree { val asList = List(this) } + object emptyValDef extends ValDef(Modifiers(PRIVATE), nme.WILDCARD, TypeTree(NoType), EmptyTree) with DummyTree + object pendingSuperCall extends Apply(Select(Super(This(tpnme.EMPTY), tpnme.EMPTY), nme.CONSTRUCTOR), List()) with DummyTree + def DefDef(sym: Symbol, mods: Modifiers, vparamss: List[List[ValDef]], rhs: Tree): DefDef = atPos(sym.pos) { assert(sym != NoSymbol) diff --git a/test/files/run/t5603.check b/test/files/run/t5603.check index 5127d3c1c7..3b2eb55313 100644 --- a/test/files/run/t5603.check +++ b/test/files/run/t5603.check @@ -12,7 +12,7 @@ [95:101] private[this] val i: [98:101]Int = _; <119:139>def ([95]i: [98]Int) = <119:139>{ <119:139>val nameElse = <134:139>"Bob"; - [94][94][94]super.(); + [NoPosition][NoPosition][NoPosition]super.(); [94]() }; [168:184]val name = [179:184]"avc"; @@ -20,7 +20,7 @@ }; [215:241]object Test extends [227:241][235:238]App { [227]def () = [227]{ - [227][227][227]super.(); + [NoPosition][NoPosition][NoPosition]super.(); [227]() }; [NoPosition] -- cgit v1.2.3 From 7ee299b50ff9d6b99ae3bcfe8d700274b9f0ef44 Mon Sep 17 00:00:00 2001 From: Eugene Burmako Date: Tue, 4 Dec 2012 14:16:01 +0100 Subject: evicts assert(false) from the compiler --- src/compiler/scala/reflect/reify/codegen/GenTrees.scala | 3 ++- src/compiler/scala/tools/nsc/ast/parser/Parsers.scala | 2 +- src/compiler/scala/tools/nsc/backend/icode/GenICode.scala | 5 +++-- src/compiler/scala/tools/nsc/symtab/classfile/Pickler.scala | 2 +- src/compiler/scala/tools/nsc/transform/Constructors.scala | 2 +- src/compiler/scala/tools/nsc/transform/Mixin.scala | 3 +-- src/compiler/scala/tools/nsc/typechecker/Contexts.scala | 4 ++-- src/compiler/scala/tools/nsc/typechecker/Infer.scala | 2 +- src/compiler/scala/tools/nsc/typechecker/RefChecks.scala | 2 +- src/reflect/scala/reflect/internal/BaseTypeSeqs.scala | 2 +- src/reflect/scala/reflect/internal/Symbols.scala | 2 +- src/reflect/scala/reflect/internal/Trees.scala | 10 +++++++--- src/reflect/scala/reflect/internal/Types.scala | 4 ++-- src/reflect/scala/reflect/internal/pickling/UnPickler.scala | 2 +- src/reflect/scala/reflect/internal/transform/UnCurry.scala | 3 +-- src/reflect/scala/reflect/internal/util/Position.scala | 3 ++- src/reflect/scala/reflect/runtime/JavaMirrors.scala | 2 +- 17 files changed, 29 insertions(+), 24 deletions(-) diff --git a/src/compiler/scala/reflect/reify/codegen/GenTrees.scala b/src/compiler/scala/reflect/reify/codegen/GenTrees.scala index d6bafb6759..918aedce51 100644 --- a/src/compiler/scala/reflect/reify/codegen/GenTrees.scala +++ b/src/compiler/scala/reflect/reify/codegen/GenTrees.scala @@ -103,7 +103,8 @@ trait GenTrees { case ReifiedTree(_, _, inlinedSymtab, rtree, _, _, _) => if (reifyDebug) println("inlining the splicee") // all free vars local to the enclosing reifee should've already been inlined by ``Metalevels'' - inlinedSymtab.syms foreach (sym => if (sym.isLocalToReifee) assert(false, inlinedSymtab.symDef(sym))) + for (sym <- inlinedSymtab.syms if sym.isLocalToReifee) + abort("local free var, should have already been inlined by Metalevels: " + inlinedSymtab.symDef(sym)) state.symtab ++= inlinedSymtab rtree case tree => diff --git a/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala b/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala index a929e54601..19f7afd69e 100644 --- a/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala +++ b/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala @@ -2854,7 +2854,7 @@ self => } else { if (in.token == LPAREN) { if (parenMeansSyntaxError) syntaxError(s"traits or objects may not have parameters", true) - else assert(false, "unexpected opening parenthesis") + else abort("unexpected opening parenthesis") } (emptyValDef, List()) } diff --git a/src/compiler/scala/tools/nsc/backend/icode/GenICode.scala b/src/compiler/scala/tools/nsc/backend/icode/GenICode.scala index ea4e8475f9..fd2b11898c 100644 --- a/src/compiler/scala/tools/nsc/backend/icode/GenICode.scala +++ b/src/compiler/scala/tools/nsc/backend/icode/GenICode.scala @@ -753,7 +753,8 @@ abstract class GenICode extends SubComponent { } else ctx1.bb.emit(CONSTANT(Constant(false))) } else if (r.isValueType && cast) { - assert(false, tree) /* Erasure should have added an unboxing operation to prevent that. */ + /* Erasure should have added an unboxing operation to prevent that. */ + abort("should have been unboxed by erasure: " + tree) } else if (r.isValueType) { ctx.bb.emit(IS_INSTANCE(REFERENCE(definitions.boxedClass(r.toType.typeSymbol)))) } else { @@ -1257,7 +1258,7 @@ abstract class GenICode extends SubComponent { val sym = ( if (!tree.symbol.isPackageClass) tree.symbol else tree.symbol.info.member(nme.PACKAGE) match { - case NoSymbol => assert(false, "Cannot use package as value: " + tree) ; NoSymbol + case NoSymbol => abort("Cannot use package as value: " + tree) case s => debugwarn("Bug: found package class where package object expected. Converting.") ; s.moduleClass } ) diff --git a/src/compiler/scala/tools/nsc/symtab/classfile/Pickler.scala b/src/compiler/scala/tools/nsc/symtab/classfile/Pickler.scala index b9eb1ba0cd..25b7813646 100644 --- a/src/compiler/scala/tools/nsc/symtab/classfile/Pickler.scala +++ b/src/compiler/scala/tools/nsc/symtab/classfile/Pickler.scala @@ -198,7 +198,7 @@ abstract class Pickler extends SubComponent { case RefinedType(parents, decls) => val rclazz = tp.typeSymbol for (m <- decls.iterator) - if (m.owner != rclazz) assert(false, "bad refinement member "+m+" of "+tp+", owner = "+m.owner) + if (m.owner != rclazz) abort("bad refinement member "+m+" of "+tp+", owner = "+m.owner) putSymbol(rclazz); putTypes(parents); putSymbols(decls.toList) case ClassInfoType(parents, decls, clazz) => putSymbol(clazz); putTypes(parents); putSymbols(decls.toList) diff --git a/src/compiler/scala/tools/nsc/transform/Constructors.scala b/src/compiler/scala/tools/nsc/transform/Constructors.scala index af43e79a14..ec0797acb5 100644 --- a/src/compiler/scala/tools/nsc/transform/Constructors.scala +++ b/src/compiler/scala/tools/nsc/transform/Constructors.scala @@ -68,7 +68,7 @@ abstract class Constructors extends Transform with ast.TreeDSL { def matchesName(param: Symbol) = param.name == name || param.name.startsWith(name + nme.NAME_JOIN_STRING) (constrParams filter matchesName) match { - case Nil => assert(false, name + " not in " + constrParams) ; null + case Nil => abort(name + " not in " + constrParams) case p :: _ => p } } diff --git a/src/compiler/scala/tools/nsc/transform/Mixin.scala b/src/compiler/scala/tools/nsc/transform/Mixin.scala index 64bb98e2c5..ebbb1d7798 100644 --- a/src/compiler/scala/tools/nsc/transform/Mixin.scala +++ b/src/compiler/scala/tools/nsc/transform/Mixin.scala @@ -871,8 +871,7 @@ abstract class Mixin extends InfoTransform with ast.TreeDSL { val cond = Apply(Select(moduleVarRef, nme.eq), List(NULL)) mkFastPathBody(clazz, moduleSym, cond, List(assign), List(NULL), returnTree, attrThis, args) case _ => - assert(false, "Invalid getter " + rhs + " for module in class " + clazz) - EmptyTree + abort("Invalid getter " + rhs + " for module in class " + clazz) } def mkCheckedAccessor(clazz: Symbol, retVal: Tree, offset: Int, pos: Position, fieldSym: Symbol): Tree = { diff --git a/src/compiler/scala/tools/nsc/typechecker/Contexts.scala b/src/compiler/scala/tools/nsc/typechecker/Contexts.scala index 507825ff15..0907f1088a 100644 --- a/src/compiler/scala/tools/nsc/typechecker/Contexts.scala +++ b/src/compiler/scala/tools/nsc/typechecker/Contexts.scala @@ -510,8 +510,8 @@ trait Contexts { self: Analyzer => /* var c = this while (c != NoContext && c.owner != owner) { - if (c.outer eq null) assert(false, "accessWithin(" + owner + ") " + c);//debug - if (c.outer.enclClass eq null) assert(false, "accessWithin(" + owner + ") " + c);//debug + if (c.outer eq null) abort("accessWithin(" + owner + ") " + c);//debug + if (c.outer.enclClass eq null) abort("accessWithin(" + owner + ") " + c);//debug c = c.outer.enclClass } c != NoContext diff --git a/src/compiler/scala/tools/nsc/typechecker/Infer.scala b/src/compiler/scala/tools/nsc/typechecker/Infer.scala index 5deed4ffee..22daf13e33 100644 --- a/src/compiler/scala/tools/nsc/typechecker/Infer.scala +++ b/src/compiler/scala/tools/nsc/typechecker/Infer.scala @@ -221,7 +221,7 @@ trait Infer extends Checkable { // such as T <: T gets completed. See #360 tvar.constr.inst = ErrorType else - assert(false, tvar.origin+" at "+tvar.origin.typeSymbol.owner) + abort(tvar.origin+" at "+tvar.origin.typeSymbol.owner) } tvars map instantiate } diff --git a/src/compiler/scala/tools/nsc/typechecker/RefChecks.scala b/src/compiler/scala/tools/nsc/typechecker/RefChecks.scala index 78ec6508ed..fbeb401c7d 100644 --- a/src/compiler/scala/tools/nsc/typechecker/RefChecks.scala +++ b/src/compiler/scala/tools/nsc/typechecker/RefChecks.scala @@ -1671,7 +1671,7 @@ abstract class RefChecks extends InfoTransform with scala.reflect.internal.trans checkAnyValSubclass(currentOwner) if (bridges.nonEmpty) deriveTemplate(tree)(_ ::: bridges) else tree - case dc@TypeTreeWithDeferredRefCheck() => assert(false, "adapt should have turned dc: TypeTreeWithDeferredRefCheck into tpt: TypeTree, with tpt.original == dc"); dc + case dc@TypeTreeWithDeferredRefCheck() => abort("adapt should have turned dc: TypeTreeWithDeferredRefCheck into tpt: TypeTree, with tpt.original == dc") case tpt@TypeTree() => if(tpt.original != null) { tpt.original foreach { diff --git a/src/reflect/scala/reflect/internal/BaseTypeSeqs.scala b/src/reflect/scala/reflect/internal/BaseTypeSeqs.scala index d72f08674e..3c2b128c52 100644 --- a/src/reflect/scala/reflect/internal/BaseTypeSeqs.scala +++ b/src/reflect/scala/reflect/internal/BaseTypeSeqs.scala @@ -60,7 +60,7 @@ trait BaseTypeSeqs { elems(i) match { case rtp @ RefinedType(variants, decls) => // can't assert decls.isEmpty; see t0764 - //if (!decls.isEmpty) assert(false, "computing closure of "+this+":"+this.isInstanceOf[RefinedType]+"/"+closureCache(j)) + //if (!decls.isEmpty) abort("computing closure of "+this+":"+this.isInstanceOf[RefinedType]+"/"+closureCache(j)) //Console.println("compute closure of "+this+" => glb("+variants+")") pending += i try { diff --git a/src/reflect/scala/reflect/internal/Symbols.scala b/src/reflect/scala/reflect/internal/Symbols.scala index a27afe9dfd..a4287fb181 100644 --- a/src/reflect/scala/reflect/internal/Symbols.scala +++ b/src/reflect/scala/reflect/internal/Symbols.scala @@ -3090,7 +3090,7 @@ trait Symbols extends api.Symbols { self: SymbolTable => class RefinementClassSymbol protected[Symbols] (owner0: Symbol, pos0: Position) extends ClassSymbol(owner0, pos0, tpnme.REFINE_CLASS_NAME) { override def name_=(name: Name) { - assert(false, "Cannot set name of RefinementClassSymbol to " + name) + abort("Cannot set name of RefinementClassSymbol to " + name) super.name_=(name) } override def isRefinementClass = true diff --git a/src/reflect/scala/reflect/internal/Trees.scala b/src/reflect/scala/reflect/internal/Trees.scala index 047298cf82..5b7afdf5dd 100644 --- a/src/reflect/scala/reflect/internal/Trees.scala +++ b/src/reflect/scala/reflect/internal/Trees.scala @@ -958,11 +958,15 @@ trait Trees extends api.Trees { self: SymbolTable => trait DummyTree extends Tree { override def isEmpty = true override def isDummy = true + + private def unsupported(what: String, args: Any*) = + throw new UnsupportedOperationException(s"$what($args) inapplicable for "+self.toString) + super.setPos(NoPosition) - override def setPos(pos: Position) = { assert(false); this } + override def setPos(pos: Position) = unsupported("setPos", pos) + super.setType(NoType) - override def tpe_=(t: Type) = - if (t != NoType) throw new UnsupportedOperationException("tpe_=("+t+") inapplicable for "+self.toString) + override def tpe_=(t: Type) = if (t != NoType) unsupported("tpe_=", t) } case object EmptyTree extends TermTree with DummyTree { val asList = List(this) } diff --git a/src/reflect/scala/reflect/internal/Types.scala b/src/reflect/scala/reflect/internal/Types.scala index 0c4cda8313..d82692000d 100644 --- a/src/reflect/scala/reflect/internal/Types.scala +++ b/src/reflect/scala/reflect/internal/Types.scala @@ -1401,7 +1401,7 @@ trait Types extends api.Types { self: SymbolTable => if (!sym.isClass) { // SI-6640 allow StubSymbols to reveal what's missing from the classpath before we trip the assertion. sym.failIfStub() - assert(false, sym) + abort(s"ThisType($sym) for sym which is not a class") } //assert(sym.isClass && !sym.isModuleClass || sym.isRoot, sym) @@ -7067,7 +7067,7 @@ trait Types extends api.Types { self: SymbolTable => case ExistentialType(tparams, quantified) :: rest => mergePrefixAndArgs(quantified :: rest, variance, depth) map (existentialAbstraction(tparams, _)) case _ => - assert(false, tps); None + abort(s"mergePrefixAndArgs($tps, $variance, $depth): unsupported tps") } def addMember(thistp: Type, tp: Type, sym: Symbol): Unit = addMember(thistp, tp, sym, AnyDepth) diff --git a/src/reflect/scala/reflect/internal/pickling/UnPickler.scala b/src/reflect/scala/reflect/internal/pickling/UnPickler.scala index f3a5053a91..603fff4f1c 100644 --- a/src/reflect/scala/reflect/internal/pickling/UnPickler.scala +++ b/src/reflect/scala/reflect/internal/pickling/UnPickler.scala @@ -309,7 +309,7 @@ abstract class UnPickler { if (isModuleRoot) moduleRoot setFlag pflags else owner.newLinkedModule(clazz, pflags) case VALsym => - if (isModuleRoot) { assert(false); NoSymbol } + if (isModuleRoot) { abort(s"VALsym at module root: owner = $owner, name = $name") } else owner.newTermSymbol(name.toTermName, NoPosition, pflags) case _ => diff --git a/src/reflect/scala/reflect/internal/transform/UnCurry.scala b/src/reflect/scala/reflect/internal/transform/UnCurry.scala index 0c1640ceb9..6dc6a0f7b8 100644 --- a/src/reflect/scala/reflect/internal/transform/UnCurry.scala +++ b/src/reflect/scala/reflect/internal/transform/UnCurry.scala @@ -19,8 +19,7 @@ trait UnCurry { case MethodType(params, MethodType(params1, restpe)) => apply(MethodType(params ::: params1, restpe)) case MethodType(params, ExistentialType(tparams, restpe @ MethodType(_, _))) => - assert(false, "unexpected curried method types with intervening existential") - tp0 + abort("unexpected curried method types with intervening existential") case MethodType(h :: t, restpe) if h.isImplicit => apply(MethodType(h.cloneSymbol.resetFlag(IMPLICIT) :: t, restpe)) case NullaryMethodType(restpe) => diff --git a/src/reflect/scala/reflect/internal/util/Position.scala b/src/reflect/scala/reflect/internal/util/Position.scala index 0725e9775b..3d10d4c9ce 100644 --- a/src/reflect/scala/reflect/internal/util/Position.scala +++ b/src/reflect/scala/reflect/internal/util/Position.scala @@ -7,6 +7,7 @@ package scala.reflect.internal.util import scala.reflect.ClassTag +import scala.reflect.internal.FatalError import scala.reflect.macros.Attachments object Position { @@ -269,7 +270,7 @@ class OffsetPosition(override val source: SourceFile, override val point: Int) e /** new for position ranges */ class RangePosition(source: SourceFile, override val start: Int, point: Int, override val end: Int) extends OffsetPosition(source, point) { - if (start > end) assert(false, "bad position: "+show) + if (start > end) sys.error("bad position: "+show) override def isRange: Boolean = true override def isOpaqueRange: Boolean = true override def startOrPoint: Int = start diff --git a/src/reflect/scala/reflect/runtime/JavaMirrors.scala b/src/reflect/scala/reflect/runtime/JavaMirrors.scala index ab93d7033a..d110bd4273 100644 --- a/src/reflect/scala/reflect/runtime/JavaMirrors.scala +++ b/src/reflect/scala/reflect/runtime/JavaMirrors.scala @@ -416,7 +416,7 @@ private[reflect] trait JavaMirrors extends internal.SymbolTable with api.JavaUni case sym if sym.owner.isPrimitiveValueClass => invokePrimitiveMethod case sym if sym == Predef_classOf => fail("Predef.classOf is a compile-time function") case sym if sym.isTermMacro => fail(s"${symbol.fullName} is a macro, i.e. a compile-time function") - case _ => assert(false, this) + case _ => abort(s"unsupported symbol $symbol when invoking $this") } } } -- cgit v1.2.3 From 838cbe623c142b7005446793948097f679219fe3 Mon Sep 17 00:00:00 2001 From: Eugene Burmako Date: Tue, 4 Dec 2012 16:06:20 +0100 Subject: DummyTree => CannotHaveAttrs This looks like a much more specific name than a generic "dummy" prefix. CannotHaveAttrs also doesn't imply that an implementing tree should satisfy some bigger contract. EmptyTree and emptyValDef are very unlike each other, so there's no point in trying to unify them. Also DummyTree.isEmpty is no longer automatically true. The notion of trees not having positions and types by design (i.e. EmptyTree + empty TypeTrees + emptyValDef + the new pendingSuperCall) is quite different from the notion of an empty tree in a sense of a tree being a null object (i.e. EmptyTree + empty TypeTrees). --- src/compiler/scala/tools/nsc/ast/Positions.scala | 2 +- src/compiler/scala/tools/nsc/ast/Trees.scala | 2 +- src/compiler/scala/tools/nsc/ast/parser/Parsers.scala | 2 +- .../scala/tools/nsc/interactive/RangePositions.scala | 6 +++--- src/compiler/scala/tools/nsc/typechecker/Typers.scala | 2 +- src/reflect/scala/reflect/api/Trees.scala | 18 +++++++++++++++++- src/reflect/scala/reflect/internal/Positions.scala | 2 +- src/reflect/scala/reflect/internal/Printers.scala | 2 +- src/reflect/scala/reflect/internal/Trees.scala | 15 +++++++-------- 9 files changed, 33 insertions(+), 18 deletions(-) diff --git a/src/compiler/scala/tools/nsc/ast/Positions.scala b/src/compiler/scala/tools/nsc/ast/Positions.scala index 0503c5fb10..49569f5e05 100644 --- a/src/compiler/scala/tools/nsc/ast/Positions.scala +++ b/src/compiler/scala/tools/nsc/ast/Positions.scala @@ -20,7 +20,7 @@ trait Positions extends scala.reflect.internal.Positions { // When we prune due to encountering a position, traverse the // pruned children so we can warn about those lacking positions. t.children foreach { c => - if (c.isDummy) () + if (!c.canHaveAttrs) () else if (c.pos == NoPosition) { reporter.warning(t.pos, " Positioned tree has unpositioned child in phase " + globalPhase) inform("parent: " + treeSymStatus(t)) diff --git a/src/compiler/scala/tools/nsc/ast/Trees.scala b/src/compiler/scala/tools/nsc/ast/Trees.scala index e848fa223b..54402f0903 100644 --- a/src/compiler/scala/tools/nsc/ast/Trees.scala +++ b/src/compiler/scala/tools/nsc/ast/Trees.scala @@ -337,7 +337,7 @@ trait Trees extends scala.reflect.internal.Trees { self: Global => else super.transform { tree match { - case tree if tree.isDummy => + case tree if !tree.canHaveAttrs => tree case tpt: TypeTree => if (tpt.original != null) diff --git a/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala b/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala index 19f7afd69e..d6be1abdd9 100644 --- a/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala +++ b/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala @@ -2767,7 +2767,7 @@ self => if (in.token == LBRACE) { // @S: pre template body cannot stub like post body can! val (self, body) = templateBody(isPre = true) - if (in.token == WITH && self.isEmpty) { + if (in.token == WITH && (self eq emptyValDef)) { val earlyDefs: List[Tree] = body flatMap { case vdef @ ValDef(mods, _, _, _) if !mods.isDeferred => List(copyValDef(vdef)(mods = mods | Flags.PRESUPER)) diff --git a/src/compiler/scala/tools/nsc/interactive/RangePositions.scala b/src/compiler/scala/tools/nsc/interactive/RangePositions.scala index b95f1fa7ca..64117bd8ee 100644 --- a/src/compiler/scala/tools/nsc/interactive/RangePositions.scala +++ b/src/compiler/scala/tools/nsc/interactive/RangePositions.scala @@ -144,7 +144,7 @@ self: scala.tools.nsc.Global => */ private def setChildrenPos(pos: Position, trees: List[Tree]): Unit = try { for (tree <- trees) { - if (!tree.isEmpty && tree.pos == NoPosition) { + if (!tree.isEmpty && tree.canHaveAttrs && tree.pos == NoPosition) { val children = tree.children if (children.isEmpty) { tree setPos pos.focus @@ -165,7 +165,7 @@ self: scala.tools.nsc.Global => */ override def atPos[T <: Tree](pos: Position)(tree: T): T = { if (pos.isOpaqueRange) { - if (!tree.isEmpty && tree.pos == NoPosition) { + if (!tree.isEmpty && tree.canHaveAttrs && tree.pos == NoPosition) { tree.setPos(pos) val children = tree.children if (children.nonEmpty) { @@ -203,7 +203,7 @@ self: scala.tools.nsc.Global => def validate(tree: Tree, encltree: Tree): Unit = { - if (!tree.isEmpty) { + if (!tree.isEmpty && tree.canHaveAttrs) { if (settings.Yposdebug.value && (settings.verbose.value || settings.Yrangepos.value)) println("[%10s] %s".format("validate", treeStatus(tree, encltree))) diff --git a/src/compiler/scala/tools/nsc/typechecker/Typers.scala b/src/compiler/scala/tools/nsc/typechecker/Typers.scala index 96432f49a7..9e07b51b77 100644 --- a/src/compiler/scala/tools/nsc/typechecker/Typers.scala +++ b/src/compiler/scala/tools/nsc/typechecker/Typers.scala @@ -52,7 +52,7 @@ trait Typers extends Modes with Adaptations with Tags { object UnTyper extends Traverser { override def traverse(tree: Tree) = { - if (!tree.isDummy) { + if (tree.canHaveAttrs) { tree.tpe = null if (tree.hasSymbol) tree.symbol = NoSymbol } diff --git a/src/reflect/scala/reflect/api/Trees.scala b/src/reflect/scala/reflect/api/Trees.scala index 9a65ddaa96..3837517a3b 100644 --- a/src/reflect/scala/reflect/api/Trees.scala +++ b/src/reflect/scala/reflect/api/Trees.scala @@ -75,11 +75,26 @@ trait Trees { self: Universe => def isDef: Boolean /** Is this tree one of the empty trees? + * * Empty trees are: the `EmptyTree` null object, `TypeTree` instances that don't carry a type * and the special `emptyValDef` singleton. + * + * In the compiler the `isEmpty` check and the derived `orElse` method are mostly used + * as a check for a tree being a null object (`EmptyTree` for term trees and empty TypeTree for type trees). + * + * Unfortunately `emptyValDef` is also considered to be `isEmpty`, but this is deemed to be + * a conceptual mistake pending a fix in https://issues.scala-lang.org/browse/SI-6762. + * + * @see `canHaveAttrs` */ def isEmpty: Boolean + /** Can this tree carry attributes (i.e. symbols, types or positions)? + * Typically the answer is yes, except for the `EmptyTree` null object and + * two special singletons: `emptyValDef` and `pendingSuperCall`. + */ + def canHaveAttrs: Boolean + /** The canonical way to test if a Tree represents a term. */ def isTerm: Boolean @@ -2852,7 +2867,8 @@ trait Trees { self: Universe => trees mapConserve (tree => transform(tree).asInstanceOf[TypeDef]) /** Transforms a `ValDef`. */ def transformValDef(tree: ValDef): ValDef = - if (tree.isEmpty) tree else transform(tree).asInstanceOf[ValDef] + if (tree eq emptyValDef) tree + else transform(tree).asInstanceOf[ValDef] /** Transforms a list of `ValDef` nodes. */ def transformValDefs(trees: List[ValDef]): List[ValDef] = trees mapConserve (transformValDef(_)) diff --git a/src/reflect/scala/reflect/internal/Positions.scala b/src/reflect/scala/reflect/internal/Positions.scala index b65df0e70b..f8c670827a 100644 --- a/src/reflect/scala/reflect/internal/Positions.scala +++ b/src/reflect/scala/reflect/internal/Positions.scala @@ -38,7 +38,7 @@ trait Positions extends api.Positions { self: SymbolTable => protected class DefaultPosAssigner extends PosAssigner { var pos: Position = _ override def traverse(t: Tree) { - if (t.isDummy) () + if (!t.canHaveAttrs) () else if (t.pos == NoPosition) { t.setPos(pos) super.traverse(t) // TODO: bug? shouldn't the traverse be outside of the if? diff --git a/src/reflect/scala/reflect/internal/Printers.scala b/src/reflect/scala/reflect/internal/Printers.scala index 6f834803c4..a8085a4c58 100644 --- a/src/reflect/scala/reflect/internal/Printers.scala +++ b/src/reflect/scala/reflect/internal/Printers.scala @@ -435,7 +435,7 @@ trait Printers extends api.Printers { self: SymbolTable => case tree => xprintTree(this, tree) } - if (printTypes && tree.isTerm && !tree.isEmpty) { + if (printTypes && tree.isTerm && tree.canHaveAttrs) { print("{", if (tree.tpe eq null) "" else tree.tpe.toString, "}") } } diff --git a/src/reflect/scala/reflect/internal/Trees.scala b/src/reflect/scala/reflect/internal/Trees.scala index 5b7afdf5dd..dceec18e57 100644 --- a/src/reflect/scala/reflect/internal/Trees.scala +++ b/src/reflect/scala/reflect/internal/Trees.scala @@ -36,7 +36,7 @@ trait Trees extends api.Trees { self: SymbolTable => def isDef = false def isEmpty = false - def isDummy = false + def canHaveAttrs = true /** The canonical way to test if a Tree represents a term. */ @@ -955,9 +955,8 @@ trait Trees extends api.Trees { self: SymbolTable => def ValDef(sym: Symbol): ValDef = ValDef(sym, EmptyTree) - trait DummyTree extends Tree { - override def isEmpty = true - override def isDummy = true + trait CannotHaveAttrs extends Tree { + override def canHaveAttrs = false private def unsupported(what: String, args: Any*) = throw new UnsupportedOperationException(s"$what($args) inapplicable for "+self.toString) @@ -969,9 +968,9 @@ trait Trees extends api.Trees { self: SymbolTable => override def tpe_=(t: Type) = if (t != NoType) unsupported("tpe_=", t) } - case object EmptyTree extends TermTree with DummyTree { val asList = List(this) } - object emptyValDef extends ValDef(Modifiers(PRIVATE), nme.WILDCARD, TypeTree(NoType), EmptyTree) with DummyTree - object pendingSuperCall extends Apply(Select(Super(This(tpnme.EMPTY), tpnme.EMPTY), nme.CONSTRUCTOR), List()) with DummyTree + case object EmptyTree extends TermTree with CannotHaveAttrs { override def isEmpty = true; val asList = List(this) } + object emptyValDef extends ValDef(Modifiers(PRIVATE), nme.WILDCARD, TypeTree(NoType), EmptyTree) with CannotHaveAttrs + object pendingSuperCall extends Apply(Select(Super(This(tpnme.EMPTY), tpnme.EMPTY), nme.CONSTRUCTOR), List()) with CannotHaveAttrs def DefDef(sym: Symbol, mods: Modifiers, vparamss: List[List[ValDef]], rhs: Tree): DefDef = atPos(sym.pos) { @@ -1123,7 +1122,7 @@ trait Trees extends api.Trees { self: SymbolTable => traverse(annot); traverse(arg) case Template(parents, self, body) => traverseTrees(parents) - if (!self.isEmpty) traverse(self) + if (self ne emptyValDef) traverse(self) traverseStats(body, tree.symbol) case Block(stats, expr) => traverseTrees(stats); traverse(expr) -- cgit v1.2.3 From bb9adfbd76af0a0281912fcef4bcaca409a7c9a3 Mon Sep 17 00:00:00 2001 From: Eugene Burmako Date: Wed, 5 Dec 2012 07:05:17 +0100 Subject: more ListOfNil => Nil Even more trees (together with Apply nodes produced by templateParents and New nodes produced by New in TreeBuilders) now distinguish nullary argument list from empty argument list. --- src/compiler/scala/tools/nsc/ast/TreeGen.scala | 2 +- src/compiler/scala/tools/nsc/ast/parser/Parsers.scala | 2 +- src/compiler/scala/tools/nsc/ast/parser/TreeBuilder.scala | 2 +- src/compiler/scala/tools/nsc/javac/JavaParsers.scala | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/src/compiler/scala/tools/nsc/ast/TreeGen.scala b/src/compiler/scala/tools/nsc/ast/TreeGen.scala index 53d35791b6..5cb43575b8 100644 --- a/src/compiler/scala/tools/nsc/ast/TreeGen.scala +++ b/src/compiler/scala/tools/nsc/ast/TreeGen.scala @@ -58,7 +58,7 @@ abstract class TreeGen extends scala.reflect.internal.TreeGen with TreeDSL { def mkUnchecked(expr: Tree): Tree = atPos(expr.pos) { // This can't be "Annotated(New(UncheckedClass), expr)" because annotations // are very picky about things and it crashes the compiler with "unexpected new". - Annotated(New(scalaDot(UncheckedClass.name), ListOfNil), expr) + Annotated(New(scalaDot(UncheckedClass.name), Nil), expr) } // if it's a Match, mark the selector unchecked; otherwise nothing. def mkUncheckedMatch(tree: Tree) = tree match { diff --git a/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala b/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala index d6be1abdd9..33db4ee2d5 100644 --- a/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala +++ b/src/compiler/scala/tools/nsc/ast/parser/Parsers.scala @@ -2106,7 +2106,7 @@ self => def annotationExpr(): Tree = atPos(in.offset) { val t = exprSimpleType() if (in.token == LPAREN) New(t, multipleArgumentExprs()) - else New(t, ListOfNil) + else New(t, Nil) } /* -------- PARAMETERS ------------------------------------------- */ diff --git a/src/compiler/scala/tools/nsc/ast/parser/TreeBuilder.scala b/src/compiler/scala/tools/nsc/ast/parser/TreeBuilder.scala index 9e9e81aa27..f94055f666 100644 --- a/src/compiler/scala/tools/nsc/ast/parser/TreeBuilder.scala +++ b/src/compiler/scala/tools/nsc/ast/parser/TreeBuilder.scala @@ -237,7 +237,7 @@ abstract class TreeBuilder { atPos(npos) { New( Ident(x) setPos npos.focus, - ListOfNil) + Nil) } ) } diff --git a/src/compiler/scala/tools/nsc/javac/JavaParsers.scala b/src/compiler/scala/tools/nsc/javac/JavaParsers.scala index 43a8402fc7..050f7a8f95 100644 --- a/src/compiler/scala/tools/nsc/javac/JavaParsers.scala +++ b/src/compiler/scala/tools/nsc/javac/JavaParsers.scala @@ -551,7 +551,7 @@ trait JavaParsers extends ast.parser.ParsersCommon with JavaScanners { if (parentToken == AT && in.token == DEFAULT) { val annot = atPos(pos) { - New(Select(scalaDot(nme.runtime), tpnme.AnnotationDefaultATTR), ListOfNil) + New(Select(scalaDot(nme.runtime), tpnme.AnnotationDefaultATTR), Nil) } mods1 = mods1 withAnnotations List(annot) skipTo(SEMI) -- cgit v1.2.3