Skip to content

Commit

Permalink
Merge pull request scala#5251 from adriaanm/rebase-5177
Browse files Browse the repository at this point in the history
Emit trait method bodies in statics [rebase of scala#5177]
  • Loading branch information
lrytz authored Jun 29, 2016
2 parents 7a7fdac + d8c862b commit 79e24d5
Show file tree
Hide file tree
Showing 39 changed files with 418 additions and 222 deletions.
2 changes: 1 addition & 1 deletion project/ScriptCommands.scala
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ object ScriptCommands {
// Append build.timestamp to Artifactory URL to get consistent build numbers (see https://github.com/sbt/sbt/issues/2088):
publishTo in Global := Some("scala-pr" at url.replaceAll("/$", "") + ";build.timestamp=" + System.currentTimeMillis),
publishArtifact in (Compile, packageDoc) in ThisBuild := false,
scalacOptions in Compile in ThisBuild += "-Yopt:l:classpath",
scalacOptions in Compile in ThisBuild += "-opt:l:classpath",
logLevel in ThisBuild := Level.Info,
logLevel in update in ThisBuild := Level.Warn
), state)
Expand Down
10 changes: 5 additions & 5 deletions scripts/jobs/integrate/bootstrap
Original file line number Diff line number Diff line change
Expand Up @@ -247,7 +247,7 @@ buildPartest() {
else
update scala scala-partest "$PARTEST_REF" && gfxd
doc="$(docTask $PARTEST_BUILT)"
sbtBuild 'set version :="'$PARTEST_VER'"' 'set VersionKeys.scalaXmlVersion := "'$XML_VER'"' 'set VersionKeys.scalaCheckVersion := "'$SCALACHECK_VER'"' $clean "$doc" test "${buildTasks[@]}"
sbtBuild 'set version :="'$PARTEST_VER'"' 'set VersionKeys.scalaXmlVersion := "'$XML_VER'"' $clean "$doc" test "${buildTasks[@]}"
PARTEST_BUILT="yes"
fi
}
Expand Down Expand Up @@ -282,7 +282,7 @@ buildModules() {
buildXML
buildParsers
buildSwing
buildScalacheck
# buildScalacheck
buildPartest
}

Expand Down Expand Up @@ -424,7 +424,7 @@ deriveModuleVersions() {
echo "Module versions (versioning strategy: $moduleVersioning):"
echo "PARSERS = $PARSERS_VER at $PARSERS_REF"
echo "PARTEST = $PARTEST_VER at $PARTEST_REF"
echo "SCALACHECK = $SCALACHECK_VER at $SCALACHECK_REF"
# echo "SCALACHECK = $SCALACHECK_VER at $SCALACHECK_REF"
echo "SWING = $SWING_VER at $SWING_REF"
echo "XML = $XML_VER at $XML_REF"

Expand All @@ -444,7 +444,7 @@ removeExistingBuilds() {
local storageApiUrl=`echo $releaseTempRepoUrl | sed 's/\(scala-release-temp\)/api\/storage\/\1/'`
local scalaLangModules=`curl -s $storageApiUrl/org/scala-lang | jq -r '.children | .[] | "org/scala-lang" + .uri' | grep -v actors-migration`

for module in "org/scalacheck" $scalaLangModules; do
for module in $scalaLangModules; do
local artifacts=`curl -s $storageApiUrl/$module | jq -r ".children | .[] | select(.uri | contains(\"$SCALA_VER\")) | .uri"`
for artifact in $artifacts; do
echo "Deleting $releaseTempRepoUrl$module$artifact"
Expand All @@ -464,7 +464,7 @@ constructUpdatedModuleVersions() {
updatedModuleVersions=("${updatedModuleVersions[@]}" "-Dscala-xml.version.number=$XML_VER")

updatedModuleVersions=("${updatedModuleVersions[@]}" "-Dpartest.version.number=$PARTEST_VER")
updatedModuleVersions=("${updatedModuleVersions[@]}" "-Dscalacheck.version.number=$SCALACHECK_VER")
# updatedModuleVersions=("${updatedModuleVersions[@]}" "-Dscalacheck.version.number=$SCALACHECK_VER")

# allow overriding the jline version using a jenkins build parameter
if [ ! -z "$JLINE_VER" ] ; then updatedModuleVersions=("${updatedModuleVersions[@]}" "-Djline.version=$JLINE_VER"); fi
Expand Down
3 changes: 2 additions & 1 deletion src/compiler/scala/tools/nsc/ast/TreeGen.scala
Original file line number Diff line number Diff line change
Expand Up @@ -336,12 +336,13 @@ abstract class TreeGen extends scala.reflect.internal.TreeGen with TreeDSL {
* - are associating the RHS with a cloned symbol, but intend for the original
* method to remain and for recursive calls to target it.
*/
final def mkStatic(orig: DefDef, maybeClone: Symbol => Symbol): DefDef = {
final def mkStatic(orig: DefDef, newName: Name, maybeClone: Symbol => Symbol): DefDef = {
assert(phase.erasedTypes, phase)
assert(!orig.symbol.hasFlag(SYNCHRONIZED), orig.symbol.defString)
val origSym = orig.symbol
val origParams = orig.symbol.info.params
val newSym = maybeClone(orig.symbol)
newSym.setName(newName)
newSym.setFlag(STATIC)
// Add an explicit self parameter
val selfParamSym = newSym.newSyntheticValueParam(newSym.owner.typeConstructor, nme.SELF).setFlag(ARTIFACT)
Expand Down
49 changes: 29 additions & 20 deletions src/compiler/scala/tools/nsc/backend/jvm/BCodeBodyBuilder.scala
Original file line number Diff line number Diff line change
Expand Up @@ -11,10 +11,10 @@ package jvm

import scala.annotation.switch
import scala.reflect.internal.Flags

import scala.tools.asm
import GenBCode._
import BackendReporting._
import scala.tools.asm.Opcodes
import scala.tools.asm.tree.MethodInsnNode
import scala.tools.nsc.backend.jvm.BCodeHelpers.{InvokeStyle, TestOp}

Expand Down Expand Up @@ -637,15 +637,15 @@ abstract class BCodeBodyBuilder extends BCodeSkelBuilder {
val nativeKind = tpeTK(expr)
genLoad(expr, nativeKind)
val MethodNameAndType(mname, methodType) = srBoxesRuntimeBoxToMethods(nativeKind)
bc.invokestatic(srBoxesRunTimeRef.internalName, mname, methodType.descriptor, app.pos)
bc.invokestatic(srBoxesRunTimeRef.internalName, mname, methodType.descriptor, itf = false, app.pos)
generatedType = boxResultType(fun.symbol)

case Apply(fun, List(expr)) if currentRun.runDefinitions.isUnbox(fun.symbol) =>
genLoad(expr)
val boxType = unboxResultType(fun.symbol)
generatedType = boxType
val MethodNameAndType(mname, methodType) = srBoxesRuntimeUnboxToMethods(boxType)
bc.invokestatic(srBoxesRunTimeRef.internalName, mname, methodType.descriptor, app.pos)
bc.invokestatic(srBoxesRunTimeRef.internalName, mname, methodType.descriptor, itf = false, app.pos)

case app @ Apply(fun, args) =>
val sym = fun.symbol
Expand Down Expand Up @@ -1058,31 +1058,40 @@ abstract class BCodeBodyBuilder extends BCodeSkelBuilder {
}

receiverClass.info // ensure types the type is up to date; erasure may add lateINTERFACE to traits
val receiverName = internalName(receiverClass)

// super calls are only allowed to direct parents
if (style.isSuper && receiverClass.isTraitOrInterface && !cnode.interfaces.contains(receiverName)) {
thisBType.info.get.inlineInfo.lateInterfaces += receiverName
cnode.interfaces.add(receiverName)
}
val receiverBType = classBTypeFromSymbol(receiverClass)
val receiverName = receiverBType.internalName

def needsInterfaceCall(sym: Symbol) = {
sym.isTraitOrInterface ||
sym.isJavaDefined && sym.isNonBottomSubClass(definitions.ClassfileAnnotationClass)
}

val jname = method.javaSimpleName.toString
val bmType = methodBTypeFromSymbol(method)
val mdescr = bmType.descriptor
val jname = method.javaSimpleName.toString
val bmType = methodBTypeFromSymbol(method)
val mdescr = bmType.descriptor

val isInterface = receiverBType.isInterface.get
import InvokeStyle._
style match {
case Static => bc.invokestatic (receiverName, jname, mdescr, pos)
case Special => bc.invokespecial (receiverName, jname, mdescr, pos)
case Virtual =>
if (needsInterfaceCall(receiverClass)) bc.invokeinterface(receiverName, jname, mdescr, pos)
else bc.invokevirtual (receiverName, jname, mdescr, pos)
case Super => bc.invokespecial (receiverName, jname, mdescr, pos)
if (style == Super) {
assert(receiverClass == methodOwner, s"for super call, expecting $receiverClass == $methodOwner")
if (receiverClass.isTrait && !receiverClass.isJavaDefined) {
val staticDesc = MethodBType(typeToBType(method.owner.info) :: bmType.argumentTypes, bmType.returnType).descriptor
val staticName = traitImplMethodName(method).toString
bc.invokestatic(receiverName, staticName, staticDesc, isInterface, pos)
} else {
if (receiverClass.isTraitOrInterface) {
// An earlier check in Mixin reports an error in this case, so it doesn't reach the backend
assert(cnode.interfaces.contains(receiverName), s"cannot invokespecial $receiverName.$jname, the interface is not a direct parent.")
}
bc.invokespecial(receiverName, jname, mdescr, isInterface, pos)
}
} else {
val opc = style match {
case Static => Opcodes.INVOKESTATIC
case Special => Opcodes.INVOKESPECIAL
case Virtual => if (isInterface) Opcodes.INVOKEINTERFACE else Opcodes.INVOKEVIRTUAL
}
bc.emitInvoke(opc, receiverName, jname, mdescr, isInterface, pos)
}

bmType.returnType
Expand Down
71 changes: 10 additions & 61 deletions src/compiler/scala/tools/nsc/backend/jvm/BCodeHelpers.scala
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ import scala.tools.asm
import scala.tools.nsc.io.AbstractFile
import GenBCode._
import BackendReporting._
import scala.reflect.internal.Flags

/*
* Traits encapsulating functionality to convert Scala AST Trees into ASM ClassNodes.
Expand Down Expand Up @@ -49,6 +50,14 @@ abstract class BCodeHelpers extends BCodeIdiomatic with BytecodeWriters {
}
}

def needsStaticImplMethod(sym: Symbol) = sym.hasAttachment[global.mixer.NeedStaticImpl.type]

final def traitImplMethodName(sym: Symbol): Name = {
val name = sym.javaSimpleName
if (sym.isMixinConstructor) name
else name.append(nme.NAME_JOIN_STRING)
}

/**
* True if `classSym` is an anonymous class or a local class. I.e., false if `classSym` is a
* member class. This method is used to decide if we should emit an EnclosingMethod attribute.
Expand Down Expand Up @@ -230,58 +239,6 @@ abstract class BCodeHelpers extends BCodeIdiomatic with BytecodeWriters {
sym.isErroneous
}

/**
* Build the [[InlineInfo]] for a class symbol.
*/
def buildInlineInfoFromClassSymbol(classSym: Symbol, classSymToInternalName: Symbol => InternalName, methodSymToDescriptor: Symbol => String): InlineInfo = {
val isEffectivelyFinal = classSym.isEffectivelyFinal

val sam = {
if (classSym.isEffectivelyFinal) None
else {
// Phase travel necessary. For example, nullary methods (getter of an abstract val) get an
// empty parameter list in later phases and would therefore be picked as SAM.
val samSym = exitingPickler(definitions.samOf(classSym.tpe))
if (samSym == NoSymbol) None
else Some(samSym.javaSimpleName.toString + methodSymToDescriptor(samSym))
}
}

var warning = Option.empty[ClassSymbolInfoFailureSI9111]

// Primitive methods cannot be inlined, so there's no point in building a MethodInlineInfo. Also, some
// primitive methods (e.g., `isInstanceOf`) have non-erased types, which confuses [[typeToBType]].
val methodInlineInfos = classSym.info.decls.iterator.filter(m => m.isMethod && !scalaPrimitives.isPrimitive(m)).flatMap({
case methodSym =>
if (completeSilentlyAndCheckErroneous(methodSym)) {
// Happens due to SI-9111. Just don't provide any MethodInlineInfo for that method, we don't need fail the compiler.
if (!classSym.isJavaDefined) devWarning("SI-9111 should only be possible for Java classes")
warning = Some(ClassSymbolInfoFailureSI9111(classSym.fullName))
None
} else {
val name = methodSym.javaSimpleName.toString // same as in genDefDef
val signature = name + methodSymToDescriptor(methodSym)

// In `trait T { object O }`, `oSym.isEffectivelyFinalOrNotOverridden` is true, but the
// method is abstract in bytecode, `defDef.rhs.isEmpty`. Abstract methods are excluded
// so they are not marked final in the InlineInfo attribute.
//
// However, due to https://github.com/scala/scala-dev/issues/126, this currently does not
// work, the abstract accessor for O will be marked effectivelyFinal.
val effectivelyFinal = methodSym.isEffectivelyFinalOrNotOverridden && !methodSym.isDeferred

val info = MethodInlineInfo(
effectivelyFinal = effectivelyFinal,
annotatedInline = methodSym.hasAnnotation(ScalaInlineClass),
annotatedNoInline = methodSym.hasAnnotation(ScalaNoInlineClass)
)
Some((signature, info))
}
}).toMap

InlineInfo(isEffectivelyFinal, sam, methodInlineInfos, warning)
}

/*
* must-single-thread
*/
Expand Down Expand Up @@ -568,15 +525,7 @@ abstract class BCodeHelpers extends BCodeIdiomatic with BytecodeWriters {
/**
* The class internal name for a given class symbol.
*/
final def internalName(sym: Symbol): String = {
// For each java class, the scala compiler creates a class and a module (thus a module class).
// If the `sym` is a java module class, we use the java class instead. This ensures that the
// ClassBType is created from the main class (instead of the module class).
// The two symbols have the same name, so the resulting internalName is the same.
// Phase travel (exitingPickler) required for SI-6613 - linkedCoC is only reliable in early phases (nesting)
val classSym = if (sym.isJavaDefined && sym.isModuleClass) exitingPickler(sym.linkedClassOfClass) else sym
classBTypeFromSymbol(classSym).internalName
}
final def internalName(sym: Symbol): String = classBTypeFromSymbol(sym).internalName
} // end of trait BCInnerClassGen

trait BCAnnotGen extends BCInnerClassGen {
Expand Down
22 changes: 10 additions & 12 deletions src/compiler/scala/tools/nsc/backend/jvm/BCodeIdiomatic.scala
Original file line number Diff line number Diff line change
Expand Up @@ -190,6 +190,7 @@ abstract class BCodeIdiomatic extends SubComponent {
JavaStringBuilderClassName,
INSTANCE_CONSTRUCTOR_NAME,
"()V",
itf = false,
pos
)
}
Expand Down Expand Up @@ -373,30 +374,27 @@ abstract class BCodeIdiomatic extends SubComponent {
final def rem(tk: BType) { emitPrimitive(JCodeMethodN.remOpcodes, tk) } // can-multi-thread

// can-multi-thread
final def invokespecial(owner: String, name: String, desc: String, pos: Position) {
addInvoke(Opcodes.INVOKESPECIAL, owner, name, desc, false, pos)
final def invokespecial(owner: String, name: String, desc: String, itf: Boolean, pos: Position): Unit = {
emitInvoke(Opcodes.INVOKESPECIAL, owner, name, desc, itf, pos)
}
// can-multi-thread
final def invokestatic(owner: String, name: String, desc: String, pos: Position) {
addInvoke(Opcodes.INVOKESTATIC, owner, name, desc, false, pos)
final def invokestatic(owner: String, name: String, desc: String, itf: Boolean, pos: Position): Unit = {
emitInvoke(Opcodes.INVOKESTATIC, owner, name, desc, itf, pos)
}
// can-multi-thread
final def invokeinterface(owner: String, name: String, desc: String, pos: Position) {
addInvoke(Opcodes.INVOKEINTERFACE, owner, name, desc, true, pos)
final def invokeinterface(owner: String, name: String, desc: String, pos: Position): Unit = {
emitInvoke(Opcodes.INVOKEINTERFACE, owner, name, desc, itf = true, pos)
}
// can-multi-thread
final def invokevirtual(owner: String, name: String, desc: String, pos: Position) {
addInvoke(Opcodes.INVOKEVIRTUAL, owner, name, desc, false, pos)
final def invokevirtual(owner: String, name: String, desc: String, pos: Position): Unit = {
emitInvoke(Opcodes.INVOKEVIRTUAL, owner, name, desc, itf = false, pos)
}

private def addInvoke(opcode: Int, owner: String, name: String, desc: String, itf: Boolean, pos: Position) = {
def emitInvoke(opcode: Int, owner: String, name: String, desc: String, itf: Boolean, pos: Position): Unit = {
val node = new MethodInsnNode(opcode, owner, name, desc, itf)
jmethod.instructions.add(node)
if (settings.optInlinerEnabled) callsitePositions(node) = pos
}
final def invokedynamic(owner: String, name: String, desc: String) {
jmethod.visitMethodInsn(Opcodes.INVOKEDYNAMIC, owner, name, desc)
}

// can-multi-thread
final def goTo(label: asm.Label) { jmethod.visitJumpInsn(Opcodes.GOTO, label) }
Expand Down
17 changes: 16 additions & 1 deletion src/compiler/scala/tools/nsc/backend/jvm/BCodeSkelBuilder.scala
Original file line number Diff line number Diff line change
Expand Up @@ -488,7 +488,22 @@ abstract class BCodeSkelBuilder extends BCodeHelpers {

case ValDef(mods, name, tpt, rhs) => () // fields are added in `genPlainClass()`, via `addClassFields()`

case dd : DefDef => genDefDef(dd)
case dd : DefDef =>
val sym = dd.symbol
if (needsStaticImplMethod(sym)) {
val staticDefDef = global.gen.mkStatic(dd, traitImplMethodName(sym), _.cloneSymbol)
val forwarderDefDef = {
val forwarderBody = Apply(global.gen.mkAttributedRef(staticDefDef.symbol), This(sym.owner).setType(sym.owner.typeConstructor) :: dd.vparamss.head.map(p => global.gen.mkAttributedIdent(p.symbol))).setType(sym.info.resultType)
// we don't want to the optimizer to inline the static method into the forwarder. Instead,
// the backend has a special case to transitively inline into a callsite of the forwarder
// when the forwarder itself is inlined.
forwarderBody.updateAttachment(NoInlineCallsiteAttachment)
deriveDefDef(dd)(_ => global.atPos(dd.pos)(forwarderBody))
}
genDefDef(staticDefDef)
if (!sym.isMixinConstructor)
genDefDef(forwarderDefDef)
} else genDefDef(dd)

case Template(_, _, body) => body foreach gen

Expand Down
22 changes: 1 addition & 21 deletions src/compiler/scala/tools/nsc/backend/jvm/BTypes.scala
Original file line number Diff line number Diff line change
Expand Up @@ -225,8 +225,7 @@ abstract class BTypes {

val inlineInfo = inlineInfoFromClassfile(classNode)

val classfileInterfaces: List[ClassBType] = classNode.interfaces.asScala.map(classBTypeFromParsedClassfile)(collection.breakOut)
val interfaces = classfileInterfaces.filterNot(i => inlineInfo.lateInterfaces.contains(i.internalName))
val interfaces: List[ClassBType] = classNode.interfaces.asScala.map(classBTypeFromParsedClassfile)(collection.breakOut)

classBType.info = Right(ClassInfo(superClass, interfaces, flags, nestedClasses, nestedInfo, inlineInfo))
classBType
Expand Down Expand Up @@ -1147,25 +1146,6 @@ object BTypes {
sam: Option[String],
methodInfos: Map[String, MethodInlineInfo],
warning: Option[ClassInlineInfoWarning]) {
/**
* A super call (invokespecial) to a default method T.m is only allowed if the interface T is
* a direct parent of the class. Super calls are introduced for example in Mixin when generating
* forwarder methods:
*
* trait T { override def clone(): Object = "hi" }
* trait U extends T
* class C extends U
*
* The class C gets a forwarder that invokes T.clone(). During code generation the interface T
* is added as direct parent to class C. Note that T is not a (direct) parent in the frontend
* type of class C.
*
* All interfaces that are added to a class during code generation are added to this buffer and
* stored in the InlineInfo classfile attribute. This ensures that the ClassBTypes for a
* specific class is the same no matter if it's constructed from a Symbol or from a classfile.
* This is tested in BTypesFromClassfileTest.
*/
val lateInterfaces: ListBuffer[InternalName] = ListBuffer.empty
}

val EmptyInlineInfo = InlineInfo(false, None, Map.empty, None)
Expand Down
Loading

0 comments on commit 79e24d5

Please sign in to comment.