aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorodersky <odersky@gmail.com>2016-04-01 12:14:26 +0200
committerodersky <odersky@gmail.com>2016-04-01 12:14:26 +0200
commitd1ffa3e34610422cc8ec8a90c330cae548fa2ba6 (patch)
tree079042638eba8f81a73582c3a95cd733af1f2412
parent6ae7051cdd83ebbd4ea5b93da771f39ad1dbf438 (diff)
parent98a69cae13db04741e99a7abd45f9e2a9845e5f7 (diff)
downloaddotty-d1ffa3e34610422cc8ec8a90c330cae548fa2ba6.tar.gz
dotty-d1ffa3e34610422cc8ec8a90c330cae548fa2ba6.tar.bz2
dotty-d1ffa3e34610422cc8ec8a90c330cae548fa2ba6.zip
Merge pull request #1172 from dotty-staging/compiler-docs
First of a series of compiler design documents
-rw-r--r--docs/dotc-internals/overall-structure.md174
-rw-r--r--docs/dotc-internals/periods.md94
-rw-r--r--src/dotty/tools/dotc/Bench.scala4
-rw-r--r--src/dotty/tools/dotc/Compiler.scala102
-rw-r--r--src/dotty/tools/dotc/Main.scala3
-rw-r--r--src/dotty/tools/dotc/Resident.scala4
-rw-r--r--src/dotty/tools/dotc/Run.scala1
-rw-r--r--src/dotty/tools/dotc/ast/Desugar.scala1
-rw-r--r--src/dotty/tools/dotc/ast/tpd.scala1
-rw-r--r--src/dotty/tools/dotc/core/Annotations.scala1
-rw-r--r--src/dotty/tools/dotc/core/Contexts.scala2
-rw-r--r--src/dotty/tools/dotc/core/Decorators.scala1
-rw-r--r--src/dotty/tools/dotc/core/Denotations.scala1
-rw-r--r--src/dotty/tools/dotc/core/Mode.scala (renamed from src/dotty/tools/dotc/typer/Mode.scala)5
-rw-r--r--src/dotty/tools/dotc/core/SymDenotations.scala1
-rw-r--r--src/dotty/tools/dotc/core/TypeApplications.scala1
-rw-r--r--src/dotty/tools/dotc/core/TypeComparer.scala1
-rw-r--r--src/dotty/tools/dotc/core/TypeErasure.scala1
-rw-r--r--src/dotty/tools/dotc/core/Types.scala3
-rw-r--r--src/dotty/tools/dotc/core/classfile/ClassfileParser.scala1
-rw-r--r--src/dotty/tools/dotc/core/tasty/TreeUnpickler.scala1
-rw-r--r--src/dotty/tools/dotc/core/unpickleScala2/Scala2Unpickler.scala1
-rw-r--r--src/dotty/tools/dotc/printing/PlainPrinter.scala1
-rw-r--r--src/dotty/tools/dotc/reporting/Reporter.scala2
-rw-r--r--src/dotty/tools/dotc/transform/ElimStaticThis.scala2
-rw-r--r--src/dotty/tools/dotc/transform/Erasure.scala2
-rw-r--r--src/dotty/tools/dotc/transform/GetClass.scala3
-rw-r--r--src/dotty/tools/dotc/transform/LazyVals.scala1
-rw-r--r--src/dotty/tools/dotc/transform/PatternMatcher.scala2
-rw-r--r--src/dotty/tools/dotc/transform/RestoreScopes.scala1
-rw-r--r--src/dotty/tools/dotc/transform/TreeChecker.scala1
-rw-r--r--src/dotty/tools/dotc/transform/TreeTransform.scala2
-rw-r--r--test/dotc/tests.scala2
-rw-r--r--test/test/DeSugarTest.scala2
-rw-r--r--test/test/showTree.scala2
35 files changed, 345 insertions, 82 deletions
diff --git a/docs/dotc-internals/overall-structure.md b/docs/dotc-internals/overall-structure.md
new file mode 100644
index 000000000..a80c35b4c
--- /dev/null
+++ b/docs/dotc-internals/overall-structure.md
@@ -0,0 +1,174 @@
+# Dotc's Overall Structure
+
+The compiler code is found in package [dotty.tools](https://github.com/lampepfl/dotty/tree/master/src/dotty/tools). It spans the
+following three sub-packages:
+
+ backend Compiler backends (currently for JVM and JS)
+ dotc The main compiler
+ io Helper modules for file access and classpath handling.
+
+The [dotc](https://github.com/lampepfl/dotty/tree/master/src/dotty/tools/dotc)
+package contains some main classes that can be run as separate
+programs. The most important one is class
+[Main](https://github.com/lampepfl/dotty/blob/master/src/dotty/tools/dotc/Main.scala).
+`Main` inherits from
+[Driver](https://github.com/lampepfl/dotty/blob/master/src/dotty/tools/dotc/Driver.scala) which
+contains the highest level functions for starting a compiler and processing some sources.
+`Driver` in turn is based on two other high-level classes,
+[Compiler](https://github.com/lampepfl/dotty/blob/master/src/dotty/tools/dotc/Compiler.scala) and
+[Run](https://github.com/lampepfl/dotty/blob/master/src/dotty/tools/dotc/Run.scala).
+
+## Package Structure
+
+Most functionality of `dotc` is implemented in subpackages of `dotc`. Here's a list of sub-packages
+and their focus.
+
+ ast Abstract syntax trees,
+ config Compiler configuration, settings, platform specific definitions.
+ core Core data structures and operations, with specific subpackages for:
+
+ core.classfile Reading of Java classfiles into core data structures
+ core.tasty Reading and writing of TASTY files to/from core data structures
+ core.unpickleScala2 Reading of Scala2 symbol information into core data structures
+
+ parsing Scanner and parser
+ printing Pretty-printing trees, types and other data
+ repl The interactive REPL
+ reporting Reporting of error messages, warnings and other info.
+ rewrite Helpers for rewriting Scala 2's constructs into dotty's.
+ transform Miniphases and helpers for tree transformations.
+ typer Type-checking and other frontend phases
+ util General purpose utility classes and modules.
+
+## Contexts
+
+`dotc` has almost no global state (the only significant bit of global state is the name table,
+which is used to hash strings into unique names). Instead, all essential bits of information that
+can vary over a compiler run are collected in a
+[Context](https://github.com/lampepfl/dotty/blob/master/src/dotty/tools/dotc/core/Contexts.scala).
+Most methods in `dotc` take a Context value as an implicit parameter.
+
+Contexts give a convenient way to customize values in some part of the
+call-graph. To run, e.g. some compiler function `f` at a given
+phase `phase`, we invoke `f` with an explicit context parameter, like
+this
+
+ f(/*normal args*/)(ctx.withPhase(phase))
+
+This assumes that `f` is defined in the way most compiler functions are:
+
+ def f(/*normal parameters*/)(implicit ctx: Context) ...
+
+Compiler code follows the convention that all implicit `Context`
+parameters are named `ctx`. This is important to avoid implicit
+ambiguities in the case where nested methods contain each a Context
+parameters. The common name ensures then that the implicit parameters
+properly shadow each other.
+
+Sometimes we want to make sure that implicit contexts are not captured
+in closures or other long-lived objects, be it because we want to
+enforce that nested methods each get their own implicit context, or
+because we want to avoid a space leak in the case where a closure can
+survive several compiler runs. A typical case is a completer for a
+symbol representing an external class, which produces the attributes
+of the symbol on demand, and which might never be invoked. In that
+case we follow the convention that any context parameter is explicit,
+not implicit, so we can track where it is used, and that it has a name
+different from `ctx`. Commonly used is `ictx` for "initialization
+context".
+
+With these two conventions in place, it has turned out that implicit
+contexts work amazingly well as a device for dependency injection and
+bulk parameterization. There is of course always the danger that
+an unexpected implicit will be passed, but in practice this has not turned out to
+be much of a problem.
+
+## Compiler Phases
+
+Seen from a temporal perspective, the `dotc` compiler consists of a list of phases.
+The current list of phases is specified in class [Compiler](https://github.com/lampepfl/dotty/blob/master/src/dotty/tools/dotc/Compiler.scala) as follows:
+
+```scala
+ def phases: List[List[Phase]] = List(
+ List(new FrontEnd), // Compiler frontend: scanner, parser, namer, typer
+ List(new PostTyper), // Additional checks and cleanups after type checking
+ List(new Pickler), // Generate TASTY info
+ List(new FirstTransform, // Some transformations to put trees into a canonical form
+ new CheckReentrant), // Internal use only: Check that compiled program has no data races involving global vars
+ List(new RefChecks, // Various checks mostly related to abstract members and overriding
+ new CheckStatic, // Check restrictions that apply to @static members
+ new ElimRepeated, // Rewrite vararg parameters and arguments
+ new NormalizeFlags, // Rewrite some definition flags
+ new ExtensionMethods, // Expand methods of value classes with extension methods
+ new ExpandSAMs, // Expand single abstract method closures to anonymous classes
+ new TailRec, // Rewrite tail recursion to loops
+ new LiftTry, // Put try expressions that might execute on non-empty stacks into their own methods
+ new ClassOf), // Expand `Predef.classOf` calls.
+ List(new PatternMatcher, // Compile pattern matches
+ new ExplicitOuter, // Add accessors to outer classes from nested ones.
+ new ExplicitSelf, // Make references to non-trivial self types explicit as casts
+ new CrossCastAnd, // Normalize selections involving intersection types.
+ new Splitter), // Expand selections involving union types into conditionals
+ List(new VCInlineMethods, // Inlines calls to value class methods
+ new SeqLiterals, // Express vararg arguments as arrays
+ new InterceptedMethods, // Special handling of `==`, `|=`, `getClass` methods
+ new Getters, // Replace non-private vals and vars with getter defs (fields are added later)
+ new ElimByName, // Expand by-name parameters and arguments
+ new AugmentScala2Traits, // Expand traits defined in Scala 2.11 to simulate old-style rewritings
+ new ResolveSuper), // Implement super accessors and add forwarders to trait methods
+ List(new Erasure), // Rewrite types to JVM model, erasing all type parameters, abstract types and refinements.
+ List(new ElimErasedValueType, // Expand erased value types to their underlying implementation types
+ new VCElideAllocations, // Peep-hole optimization to eliminate unnecessary value class allocations
+ new Mixin, // Expand trait fields and trait initializers
+ new LazyVals, // Expand lazy vals
+ new Memoize, // Add private fields to getters and setters
+ new LinkScala2ImplClasses, // Forward calls to the implementation classes of traits defined by Scala 2.11
+ new NonLocalReturns, // Expand non-local returns
+ new CapturedVars, // Represent vars captured by closures as heap objects
+ new Constructors, // Collect initialization code in primary constructors
+ // Note: constructors changes decls in transformTemplate, no InfoTransformers should be added after it
+ new FunctionalInterfaces,// Rewrites closures to implement @specialized types of Functions.
+ new GetClass), // Rewrites getClass calls on primitive types.
+ List(new LambdaLift, // Lifts out nested functions to class scope, storing free variables in environments
+ // Note: in this mini-phase block scopes are incorrect. No phases that rely on scopes should be here
+ new ElimStaticThis, // Replace `this` references to static objects by global identifiers
+ new Flatten, // Lift all inner classes to package scope
+ new RestoreScopes), // Repair scopes rendered invalid by moving definitions in prior phases of the group
+ List(new ExpandPrivate, // Widen private definitions accessed from nested classes
+ new CollectEntryPoints, // Find classes with main methods
+ new LabelDefs), // Converts calls to labels to jumps
+ List(new GenSJSIR), // Generate .js code
+ List(new GenBCode) // Generate JVM bytecode
+ )
+```
+
+Note that phases are grouped, so the `phases` method is of type
+`List[List[Phase]]`. The idea is that all phases in a group are
+*fused* into a single tree traversal. That way, phases can be kept
+small (most phases perform a single function) without requiring an
+excessive number of tree traversals (which are costly, because they
+have generally bad cache locality).
+
+Phases fall into four categories:
+
+ - Frontend phases: `Frontend`, `PostTyper` and `Pickler`. `FrontEnd` parses the source programs and generates
+ untyped abstract syntax trees, which are then typechecked and transformed into typed abstract syntax trees.
+ `PostTyper` performs checks and cleanups that require a fully typed program. In particular, it
+
+ - creates super accessors representing `super` calls in traits
+ - creates implementations of synthetic (compiler-implemented) methods
+ - avoids storing parameters passed unchanged from subclass to superclass in duplicate fields.
+
+ Finally `Pickler` serializes the typed syntax trees produced by the frontend as TASTY data structures.
+
+ - High-level transformations: All phases from `FirstTransform` to `Erasure`. Most of these phases transform
+ syntax trees, expanding high-level constructs to more primitive ones. The last phase in the group, `Erasure`
+ translates all types into types supported directly by the JVM. To do this, it performs another type checking
+ pass, but using the rules of the JVM's type system instead of Scala's.
+
+ - Low-level transformations: All phases from `ElimErasedValueType` to `LabelDefs`. These
+ further transform trees until they are essentially a structured version of Java bytecode.
+
+ - Code generators: These map the transformed trees to Java classfiles or Javascript files.
+
+
diff --git a/docs/dotc-internals/periods.md b/docs/dotc-internals/periods.md
new file mode 100644
index 000000000..a616ba8a8
--- /dev/null
+++ b/docs/dotc-internals/periods.md
@@ -0,0 +1,94 @@
+# Dotc's concept of time
+
+Conceptually, the `dotc` compiler's job is to maintain views of
+various artifacts associated with source code at all points in time.
+But what is *time* for `dotc`? In fact, it is a combination of
+compiler runs and compiler phases.
+
+The *hours* of the compiler's clocks are measured in compiler
+[runs](https://github.com/lampepfl/dotty/blob/master/src/dotty/tools/dotc/Run.scala). Every
+run creates a new hour, which follows all the compiler runs (hours) that
+happened before. `dotc` is designed to be used as an incremental
+compiler that can support incremental builds, as well as interactions
+in an IDE and a REPL. This means that new runs can occur quite
+frequently. At the extreme, every keystroke in an editor or REPL can
+potentially launch a new compiler run, so potentially an "hour" of
+compiler time might take only a fraction of a second in real time.
+
+The *minutes* of the compiler's clocks are measured in phases. At every
+compiler run, the compiler cycles through a number of
+[phases](https://github.com/lampepfl/dotty/blob/master/src/dotty/tools/dotc/core/Phases.scala).
+The list of phases is defined in the [Compiler]object
+There are currently about 60 phases per run, so the minutes/hours
+analogy works out roughly. After every phase the view the compiler has
+of the world changes: trees are transformed, types are gradually simplified
+from Scala types to JVM types, definitions are rearranged, and so on.
+
+Many pieces in the information compiler are time-dependent. For
+instance, a Scala symbol representing a definition has a type, but
+that type will usually change as one goes from the higher-level Scala
+view of things to the lower-level JVM view. There are different ways
+to deal with this. Many compilers change the type of a symbol
+destructively according to the "current phase". Another, more
+functional approach might be to have different symbols representing
+the same definition at different phases, which each symbol carrying a
+different immutable type. `dotc` employs yet another scheme, which is
+inspired by functional reactive programming (FRP): Symbols carry not a
+single type, but a function from compiler phase to type. So the type
+of a symbol is a time-indexed function, where time ranges over
+compiler phases.
+
+Typically, the definition of a symbol or other quantity remains stable
+for a number of phases. This leads us to the concept of a
+[period](https://github.com/lampepfl/dotty/blob/master/src/dotty/tools/dotc/core/Periods.scala).
+Conceptually, period is an interval of some given phases in a given
+compiler run. Periods are conceptually represented by three pieces of
+information
+
+ - the ID of the current run,
+ - the ID of the phase starting the period
+ - the number of phases in the period
+
+All three pieces of information are encoded in a value class over a 32 bit integer.
+Here's the API for class `Period`:
+
+```scala
+ class Period(val code: Int) extends AnyVal {
+ def runId: RunId // The run identifier of this period.
+ def firstPhaseId: PhaseId // The first phase of this period
+ def lastPhaseId: PhaseId // The last phase of this period
+ def phaseId: PhaseId // The phase identifier of this single-phase period.
+
+ def containsPhaseId(id: PhaseId): Boolean
+ def contains(that: Period): Boolean
+ def overlaps(that: Period): Boolean
+
+ def & (that: Period): Period
+ def | (that: Period): Period
+ }
+```
+
+We can access the parts of a period using `runId`, `firstPhaseId`,
+`lastPhaseId`, or using `phaseId` for periods consisting only of a
+single phase. They return `RunId` or `PhaseId` values, which are
+aliases of `Int`. `containsPhaseId`, `contains` and `overlaps` test
+whether a period contains a phase or a period as a sub-interval, or
+whether the interval overlaps with another period. Finally, `&` and
+`|` produce the intersection and the union of two period intervals
+(the union operation `|` takes as `runId` the `runId` of its left
+operand, as periods spanning different `runId`s cannot be constructed.
+
+Periods are constructed using two `apply` methods:
+
+```scala
+ object Period {
+
+ /** The single-phase period consisting of given run id and phase id */
+ def apply(rid: RunId, pid: PhaseId): Period }
+
+ /** The period consisting of given run id, and lo/hi phase ids */
+ def apply(rid: RunId, loPid: PhaseId, hiPid: PhaseId): Period
+ }
+```
+
+As a sentinel value there's `Nowhere`, a period that is empty.
diff --git a/src/dotty/tools/dotc/Bench.scala b/src/dotty/tools/dotc/Bench.scala
index 2fc38d78c..56b6dabbe 100644
--- a/src/dotty/tools/dotc/Bench.scala
+++ b/src/dotty/tools/dotc/Bench.scala
@@ -8,6 +8,10 @@ package dotc
import core.Contexts.Context
import reporting.Reporter
+/** A main class for running compiler benchmarks. Can instantiate a given
+ * number of compilers and run each (sequentially) a given number of times
+ * on the same sources.
+ */
object Bench extends Driver {
@sharable private var numRuns = 1
diff --git a/src/dotty/tools/dotc/Compiler.scala b/src/dotty/tools/dotc/Compiler.scala
index fe16243bb..fe48ac30e 100644
--- a/src/dotty/tools/dotc/Compiler.scala
+++ b/src/dotty/tools/dotc/Compiler.scala
@@ -7,7 +7,7 @@ import Periods._
import Symbols._
import Types._
import Scopes._
-import typer.{FrontEnd, Typer, Mode, ImportInfo, RefChecks}
+import typer.{FrontEnd, Typer, ImportInfo, RefChecks}
import reporting.{Reporter, ConsoleReporter}
import Phases.Phase
import transform._
@@ -18,6 +18,9 @@ import core.Denotations.SingleDenotation
import dotty.tools.backend.jvm.{LabelDefs, GenBCode}
import dotty.tools.backend.sjs.GenSJSIR
+/** The central class of the dotc compiler. The job of a compiler is to create
+ * runs, which process given `phases` in a given `rootContext`.
+ */
class Compiler {
/** Meta-ordering constraint:
@@ -38,54 +41,55 @@ class Compiler {
*/
def phases: List[List[Phase]] =
List(
- List(new FrontEnd),
- List(new PostTyper),
- List(new Pickler),
- List(new FirstTransform,
- new CheckReentrant),
- List(new RefChecks,
- new CheckStatic,
- new ElimRepeated,
- new NormalizeFlags,
- new ExtensionMethods,
- new ExpandSAMs,
- new TailRec,
- new LiftTry,
- new ClassOf),
- List(new PatternMatcher,
- new ExplicitOuter,
- new ExplicitSelf,
- new CrossCastAnd,
- new Splitter),
- List(new VCInlineMethods,
- new SeqLiterals,
- new InterceptedMethods,
- new Getters,
- new ElimByName,
- new AugmentScala2Traits,
- new ResolveSuper),
- List(new Erasure),
- List(new ElimErasedValueType,
- new VCElideAllocations,
- new Mixin,
- new LazyVals,
- new Memoize,
- new LinkScala2ImplClasses,
- new NonLocalReturns,
- new CapturedVars, // capturedVars has a transformUnit: no phases should introduce local mutable vars here
- new Constructors, // constructors changes decls in transformTemplate, no InfoTransformers should be added after it
- new FunctionalInterfaces,
- new GetClass), // getClass transformation should be applied to specialized methods
- List(new LambdaLift, // in this mini-phase block scopes are incorrect. No phases that rely on scopes should be here
- new ElimStaticThis,
- new Flatten,
- // new DropEmptyCompanions,
- new RestoreScopes),
- List(new ExpandPrivate,
- new CollectEntryPoints,
- new LabelDefs),
- List(new GenSJSIR),
- List(new GenBCode)
+ List(new FrontEnd), // Compiler frontend: scanner, parser, namer, typer
+ List(new PostTyper), // Additional checks and cleanups after type checking
+ List(new Pickler), // Generate TASTY info
+ List(new FirstTransform, // Some transformations to put trees into a canonical form
+ new CheckReentrant), // Internal use only: Check that compiled program has no data races involving global vars
+ List(new RefChecks, // Various checks mostly related to abstract members and overriding
+ new CheckStatic, // Check restrictions that apply to @static members
+ new ElimRepeated, // Rewrite vararg parameters and arguments
+ new NormalizeFlags, // Rewrite some definition flags
+ new ExtensionMethods, // Expand methods of value classes with extension methods
+ new ExpandSAMs, // Expand single abstract method closures to anonymous classes
+ new TailRec, // Rewrite tail recursion to loops
+ new LiftTry, // Put try expressions that might execute on non-empty stacks into their own methods
+ new ClassOf), // Expand `Predef.classOf` calls.
+ List(new PatternMatcher, // Compile pattern matches
+ new ExplicitOuter, // Add accessors to outer classes from nested ones.
+ new ExplicitSelf, // Make references to non-trivial self types explicit as casts
+ new CrossCastAnd, // Normalize selections involving intersection types.
+ new Splitter), // Expand selections involving union types into conditionals
+ List(new VCInlineMethods, // Inlines calls to value class methods
+ new SeqLiterals, // Express vararg arguments as arrays
+ new InterceptedMethods, // Special handling of `==`, `|=`, `getClass` methods
+ new Getters, // Replace non-private vals and vars with getter defs (fields are added later)
+ new ElimByName, // Expand by-name parameters and arguments
+ new AugmentScala2Traits, // Expand traits defined in Scala 2.11 to simulate old-style rewritings
+ new ResolveSuper), // Implement super accessors and add forwarders to trait methods
+ List(new Erasure), // Rewrite types to JVM model, erasing all type parameters, abstract types and refinements.
+ List(new ElimErasedValueType, // Expand erased value types to their underlying implmementation types
+ new VCElideAllocations, // Peep-hole optimization to eliminate unnecessary value class allocations
+ new Mixin, // Expand trait fields and trait initializers
+ new LazyVals, // Expand lazy vals
+ new Memoize, // Add private fields to getters and setters
+ new LinkScala2ImplClasses, // Forward calls to the implementation classes of traits defined by Scala 2.11
+ new NonLocalReturns, // Expand non-local returns
+ new CapturedVars, // Represent vars captured by closures as heap objects
+ new Constructors, // Collect initialization code in primary constructors
+ // Note: constructors changes decls in transformTemplate, no InfoTransformers should be added after it
+ new FunctionalInterfaces,// Rewrites closures to implement @specialized types of Functions.
+ new GetClass), // Rewrites getClass calls on primitive types.
+ List(new LambdaLift, // Lifts out nested functions to class scope, storing free variables in environments
+ // Note: in this mini-phase block scopes are incorrect. No phases that rely on scopes should be here
+ new ElimStaticThis, // Replace `this` references to static objects by global identifiers
+ new Flatten, // Lift all inner classes to package scope
+ new RestoreScopes), // Repair scopes rendered invalid by moving definitions in prior phases of the group
+ List(new ExpandPrivate, // Widen private definitions accessed from nested classes
+ new CollectEntryPoints, // Find classes with main methods
+ new LabelDefs), // Converts calls to labels to jumps
+ List(new GenSJSIR), // Generate .js code
+ List(new GenBCode) // Generate JVM bytecode
)
var runId = 1
diff --git a/src/dotty/tools/dotc/Main.scala b/src/dotty/tools/dotc/Main.scala
index 6c473d8bb..a6844fbbc 100644
--- a/src/dotty/tools/dotc/Main.scala
+++ b/src/dotty/tools/dotc/Main.scala
@@ -3,8 +3,7 @@ package dotc
import core.Contexts.Context
-/* To do:
- */
+/** Main class of the `dotc` batch compiler. */
object Main extends Driver {
override def newCompiler(implicit ctx: Context): Compiler = new Compiler
}
diff --git a/src/dotty/tools/dotc/Resident.scala b/src/dotty/tools/dotc/Resident.scala
index e1b62e4d0..56f6684d0 100644
--- a/src/dotty/tools/dotc/Resident.scala
+++ b/src/dotty/tools/dotc/Resident.scala
@@ -6,7 +6,9 @@ import reporting.Reporter
import java.io.EOFException
import scala.annotation.tailrec
-/** A compiler which stays resident between runs.
+/** A compiler which stays resident between runs. This is more of a PoC than
+ * something that's expected to be used often
+ *
* Usage:
*
* > scala dotty.tools.dotc.Resident <options> <initial files>
diff --git a/src/dotty/tools/dotc/Run.scala b/src/dotty/tools/dotc/Run.scala
index ee808323a..7a0e555e4 100644
--- a/src/dotty/tools/dotc/Run.scala
+++ b/src/dotty/tools/dotc/Run.scala
@@ -13,6 +13,7 @@ import java.io.{BufferedWriter, OutputStreamWriter}
import scala.reflect.io.VirtualFile
import scala.util.control.NonFatal
+/** A compiler run. Exports various methods to compile source files */
class Run(comp: Compiler)(implicit ctx: Context) {
assert(comp.phases.last.last.id <= Periods.MaxPossiblePhaseId)
diff --git a/src/dotty/tools/dotc/ast/Desugar.scala b/src/dotty/tools/dotc/ast/Desugar.scala
index 2ab33a120..719f3d036 100644
--- a/src/dotty/tools/dotc/ast/Desugar.scala
+++ b/src/dotty/tools/dotc/ast/Desugar.scala
@@ -9,7 +9,6 @@ import Decorators._
import language.higherKinds
import collection.mutable.ListBuffer
import config.Printers._
-import typer.Mode
object desugar {
diff --git a/src/dotty/tools/dotc/ast/tpd.scala b/src/dotty/tools/dotc/ast/tpd.scala
index a6d97478b..8d21953ae 100644
--- a/src/dotty/tools/dotc/ast/tpd.scala
+++ b/src/dotty/tools/dotc/ast/tpd.scala
@@ -10,7 +10,6 @@ import util.Positions._, Types._, Contexts._, Constants._, Names._, Flags._
import SymDenotations._, Symbols._, StdNames._, Annotations._, Trees._, Symbols._
import Denotations._, Decorators._, DenotTransformers._
import config.Printers._
-import typer.Mode
import collection.mutable
import typer.ErrorReporting._
diff --git a/src/dotty/tools/dotc/core/Annotations.scala b/src/dotty/tools/dotc/core/Annotations.scala
index 2b27b5e01..dc4897233 100644
--- a/src/dotty/tools/dotc/core/Annotations.scala
+++ b/src/dotty/tools/dotc/core/Annotations.scala
@@ -5,7 +5,6 @@ import Symbols._, Types._, util.Positions._, Contexts._, Constants._, ast.tpd._
import config.ScalaVersion
import StdNames._
import dotty.tools.dotc.ast.{tpd, untpd}
-import dotty.tools.dotc.typer.ProtoTypes.FunProtoTyped
object Annotations {
diff --git a/src/dotty/tools/dotc/core/Contexts.scala b/src/dotty/tools/dotc/core/Contexts.scala
index fd0cff94e..a0bb03e50 100644
--- a/src/dotty/tools/dotc/core/Contexts.scala
+++ b/src/dotty/tools/dotc/core/Contexts.scala
@@ -18,7 +18,7 @@ import util.Positions._
import ast.Trees._
import ast.untpd
import util.{FreshNameCreator, SimpleMap, SourceFile, NoSource}
-import typer._
+import typer.{Implicits, ImplicitRunInfo, ImportInfo, NamerContextOps, SearchHistory, TypeAssigner, Typer}
import Implicits.ContextualImplicits
import config.Settings._
import config.Config
diff --git a/src/dotty/tools/dotc/core/Decorators.scala b/src/dotty/tools/dotc/core/Decorators.scala
index 60c019bce..7d108a459 100644
--- a/src/dotty/tools/dotc/core/Decorators.scala
+++ b/src/dotty/tools/dotc/core/Decorators.scala
@@ -7,7 +7,6 @@ import Contexts._, Names._, Phases._, printing.Texts._, printing.Printer, printi
import util.Positions.Position, util.SourcePosition
import collection.mutable.ListBuffer
import dotty.tools.dotc.transform.TreeTransforms._
-import typer.Mode
import scala.language.implicitConversions
/** This object provides useful implicit decorators for types defined elsewhere */
diff --git a/src/dotty/tools/dotc/core/Denotations.scala b/src/dotty/tools/dotc/core/Denotations.scala
index b52c11201..218fb8561 100644
--- a/src/dotty/tools/dotc/core/Denotations.scala
+++ b/src/dotty/tools/dotc/core/Denotations.scala
@@ -18,7 +18,6 @@ import printing.Texts._
import printing.Printer
import io.AbstractFile
import config.Config
-import typer.Mode
import util.common._
import collection.mutable.ListBuffer
import Decorators.SymbolIteratorDecorator
diff --git a/src/dotty/tools/dotc/typer/Mode.scala b/src/dotty/tools/dotc/core/Mode.scala
index 55d44ad7a..5b3dbc872 100644
--- a/src/dotty/tools/dotc/typer/Mode.scala
+++ b/src/dotty/tools/dotc/core/Mode.scala
@@ -1,7 +1,6 @@
-package dotty.tools.dotc.typer
-
-import collection.mutable
+package dotty.tools.dotc.core
+/** A collection of mode bits that are part of a context */
case class Mode(val bits: Int) extends AnyVal {
import Mode._
def | (that: Mode) = Mode(bits | that.bits)
diff --git a/src/dotty/tools/dotc/core/SymDenotations.scala b/src/dotty/tools/dotc/core/SymDenotations.scala
index a83e7726a..28932b691 100644
--- a/src/dotty/tools/dotc/core/SymDenotations.scala
+++ b/src/dotty/tools/dotc/core/SymDenotations.scala
@@ -13,7 +13,6 @@ import Decorators.SymbolIteratorDecorator
import ast._
import annotation.tailrec
import CheckRealizable._
-import typer.Mode
import util.SimpleMap
import util.Stats
import config.Config
diff --git a/src/dotty/tools/dotc/core/TypeApplications.scala b/src/dotty/tools/dotc/core/TypeApplications.scala
index 8f8a7dbdd..26ffefec4 100644
--- a/src/dotty/tools/dotc/core/TypeApplications.scala
+++ b/src/dotty/tools/dotc/core/TypeApplications.scala
@@ -12,7 +12,6 @@ import Names._
import NameOps._
import Flags._
import StdNames.tpnme
-import typer.Mode
import util.Positions.Position
import config.Printers._
import collection.mutable
diff --git a/src/dotty/tools/dotc/core/TypeComparer.scala b/src/dotty/tools/dotc/core/TypeComparer.scala
index 4e7a4a75d..c846737b6 100644
--- a/src/dotty/tools/dotc/core/TypeComparer.scala
+++ b/src/dotty/tools/dotc/core/TypeComparer.scala
@@ -3,7 +3,6 @@ package dotc
package core
import Types._, Contexts._, Symbols._, Flags._, Names._, NameOps._, Denotations._
-import typer.Mode
import Decorators._
import StdNames.{nme, tpnme}
import collection.mutable
diff --git a/src/dotty/tools/dotc/core/TypeErasure.scala b/src/dotty/tools/dotc/core/TypeErasure.scala
index 26cac4f72..a7d825131 100644
--- a/src/dotty/tools/dotc/core/TypeErasure.scala
+++ b/src/dotty/tools/dotc/core/TypeErasure.scala
@@ -6,7 +6,6 @@ import Symbols._, Types._, Contexts._, Flags._, Names._, StdNames._, Decorators.
import Uniques.unique
import dotc.transform.ExplicitOuter._
import dotc.transform.ValueClasses._
-import typer.Mode
import util.DotClass
/** Erased types are:
diff --git a/src/dotty/tools/dotc/core/Types.scala b/src/dotty/tools/dotc/core/Types.scala
index 3801f1914..5dfe3a4f1 100644
--- a/src/dotty/tools/dotc/core/Types.scala
+++ b/src/dotty/tools/dotc/core/Types.scala
@@ -31,7 +31,6 @@ import config.Config
import config.Printers._
import annotation.tailrec
import Flags.FlagSet
-import typer.Mode
import language.implicitConversions
import scala.util.hashing.{ MurmurHash3 => hashing }
@@ -3446,7 +3445,7 @@ object Types {
object CyclicReference {
def apply(denot: SymDenotation)(implicit ctx: Context): CyclicReference = {
val ex = new CyclicReference(denot)
- if (!(ctx.mode is typer.Mode.CheckCyclic)) {
+ if (!(ctx.mode is Mode.CheckCyclic)) {
cyclicErrors.println(ex.getMessage)
for (elem <- ex.getStackTrace take 200)
cyclicErrors.println(elem.toString)
diff --git a/src/dotty/tools/dotc/core/classfile/ClassfileParser.scala b/src/dotty/tools/dotc/core/classfile/ClassfileParser.scala
index 25558a79a..f7a69aa53 100644
--- a/src/dotty/tools/dotc/core/classfile/ClassfileParser.scala
+++ b/src/dotty/tools/dotc/core/classfile/ClassfileParser.scala
@@ -12,7 +12,6 @@ import scala.collection.{ mutable, immutable }
import scala.collection.mutable.{ ListBuffer, ArrayBuffer }
import scala.annotation.switch
import typer.Checking.checkNonCyclic
-import typer.Mode
import io.AbstractFile
import scala.util.control.NonFatal
diff --git a/src/dotty/tools/dotc/core/tasty/TreeUnpickler.scala b/src/dotty/tools/dotc/core/tasty/TreeUnpickler.scala
index eb3369184..b547862b4 100644
--- a/src/dotty/tools/dotc/core/tasty/TreeUnpickler.scala
+++ b/src/dotty/tools/dotc/core/tasty/TreeUnpickler.scala
@@ -13,7 +13,6 @@ import TastyUnpickler._, TastyBuffer._, PositionPickler._
import scala.annotation.{tailrec, switch}
import scala.collection.mutable.ListBuffer
import scala.collection.{ mutable, immutable }
-import typer.Mode
import config.Printers.pickling
/** Unpickler for typed trees
diff --git a/src/dotty/tools/dotc/core/unpickleScala2/Scala2Unpickler.scala b/src/dotty/tools/dotc/core/unpickleScala2/Scala2Unpickler.scala
index 3f58a9e0f..83d427a8f 100644
--- a/src/dotty/tools/dotc/core/unpickleScala2/Scala2Unpickler.scala
+++ b/src/dotty/tools/dotc/core/unpickleScala2/Scala2Unpickler.scala
@@ -17,7 +17,6 @@ import printing.Printer
import io.AbstractFile
import util.common._
import typer.Checking.checkNonCyclic
-import typer.Mode
import PickleBuffer._
import scala.reflect.internal.pickling.PickleFormat._
import Decorators._
diff --git a/src/dotty/tools/dotc/printing/PlainPrinter.scala b/src/dotty/tools/dotc/printing/PlainPrinter.scala
index 6d026dde7..3fb220afe 100644
--- a/src/dotty/tools/dotc/printing/PlainPrinter.scala
+++ b/src/dotty/tools/dotc/printing/PlainPrinter.scala
@@ -8,7 +8,6 @@ import StdNames.{nme, tpnme}
import ast.Trees._, ast._
import java.lang.Integer.toOctalString
import config.Config.summarizeDepth
-import typer.Mode
import scala.annotation.switch
class PlainPrinter(_ctx: Context) extends Printer {
diff --git a/src/dotty/tools/dotc/reporting/Reporter.scala b/src/dotty/tools/dotc/reporting/Reporter.scala
index 8236f93ef..44defa6b1 100644
--- a/src/dotty/tools/dotc/reporting/Reporter.scala
+++ b/src/dotty/tools/dotc/reporting/Reporter.scala
@@ -10,7 +10,7 @@ import collection.mutable
import config.Settings.Setting
import config.Printers
import java.lang.System.currentTimeMillis
-import typer.Mode
+import core.Mode
import interfaces.Diagnostic.{ERROR, WARNING, INFO}
object Reporter {
diff --git a/src/dotty/tools/dotc/transform/ElimStaticThis.scala b/src/dotty/tools/dotc/transform/ElimStaticThis.scala
index 7df29b0b0..70a610188 100644
--- a/src/dotty/tools/dotc/transform/ElimStaticThis.scala
+++ b/src/dotty/tools/dotc/transform/ElimStaticThis.scala
@@ -10,7 +10,7 @@ import dotty.tools.dotc.core.SymDenotations.SymDenotation
import TreeTransforms.{MiniPhaseTransform, TransformerInfo}
import dotty.tools.dotc.core.Types.{ThisType, TermRef}
-/** Replace This references to module classes in static methods by global identifiers to the
+/** Replace This references to module classes in static methods by global identifiers to the
* corresponding modules.
*/
class ElimStaticThis extends MiniPhaseTransform {
diff --git a/src/dotty/tools/dotc/transform/Erasure.scala b/src/dotty/tools/dotc/transform/Erasure.scala
index 8d890902e..b4beaab88 100644
--- a/src/dotty/tools/dotc/transform/Erasure.scala
+++ b/src/dotty/tools/dotc/transform/Erasure.scala
@@ -25,7 +25,7 @@ import dotty.tools.dotc.core.Flags
import ValueClasses._
import TypeUtils._
import ExplicitOuter._
-import typer.Mode
+import core.Mode
class Erasure extends Phase with DenotTransformer { thisTransformer =>
diff --git a/src/dotty/tools/dotc/transform/GetClass.scala b/src/dotty/tools/dotc/transform/GetClass.scala
index f25fd6f64..6a9a5fda2 100644
--- a/src/dotty/tools/dotc/transform/GetClass.scala
+++ b/src/dotty/tools/dotc/transform/GetClass.scala
@@ -20,7 +20,8 @@ class GetClass extends MiniPhaseTransform {
override def phaseName: String = "getClass"
- override def runsAfter: Set[Class[_ <: Phase]] = Set(classOf[Erasure])
+ // getClass transformation should be applied to specialized methods
+ override def runsAfter: Set[Class[_ <: Phase]] = Set(classOf[Erasure], classOf[FunctionalInterfaces])
override def transformApply(tree: Apply)(implicit ctx: Context, info: TransformerInfo): Tree = {
import ast.Trees._
diff --git a/src/dotty/tools/dotc/transform/LazyVals.scala b/src/dotty/tools/dotc/transform/LazyVals.scala
index fc02e68cc..e42c7bae9 100644
--- a/src/dotty/tools/dotc/transform/LazyVals.scala
+++ b/src/dotty/tools/dotc/transform/LazyVals.scala
@@ -3,7 +3,6 @@ package transform
import dotty.tools.dotc.core.Annotations.Annotation
import dotty.tools.dotc.core.Phases.NeedsCompanions
-import dotty.tools.dotc.typer.Mode
import scala.collection.mutable
import core._
diff --git a/src/dotty/tools/dotc/transform/PatternMatcher.scala b/src/dotty/tools/dotc/transform/PatternMatcher.scala
index a7f654780..35e772cd1 100644
--- a/src/dotty/tools/dotc/transform/PatternMatcher.scala
+++ b/src/dotty/tools/dotc/transform/PatternMatcher.scala
@@ -21,7 +21,7 @@ import ast.Trees._
import Applications._
import TypeApplications._
import SymUtils._, core.NameOps._
-import typer.Mode
+import core.Mode
import dotty.tools.dotc.util.Positions.Position
import dotty.tools.dotc.core.Decorators._
diff --git a/src/dotty/tools/dotc/transform/RestoreScopes.scala b/src/dotty/tools/dotc/transform/RestoreScopes.scala
index 41da05691..8b9d2be0d 100644
--- a/src/dotty/tools/dotc/transform/RestoreScopes.scala
+++ b/src/dotty/tools/dotc/transform/RestoreScopes.scala
@@ -11,7 +11,6 @@ import TreeTransforms.MiniPhaseTransform
import SymDenotations._
import ast.Trees._
import NameOps._
-import typer.Mode
import TreeTransforms.TransformerInfo
import StdNames._
diff --git a/src/dotty/tools/dotc/transform/TreeChecker.scala b/src/dotty/tools/dotc/transform/TreeChecker.scala
index a260963e9..dadaf52e2 100644
--- a/src/dotty/tools/dotc/transform/TreeChecker.scala
+++ b/src/dotty/tools/dotc/transform/TreeChecker.scala
@@ -15,6 +15,7 @@ import core.StdNames._
import core.Decorators._
import core.TypeErasure.isErasedType
import core.Phases.Phase
+import core.Mode
import typer._
import typer.ErrorReporting._
import reporting.ThrowingReporter
diff --git a/src/dotty/tools/dotc/transform/TreeTransform.scala b/src/dotty/tools/dotc/transform/TreeTransform.scala
index 7fe003388..67bd2f160 100644
--- a/src/dotty/tools/dotc/transform/TreeTransform.scala
+++ b/src/dotty/tools/dotc/transform/TreeTransform.scala
@@ -11,7 +11,7 @@ import dotty.tools.dotc.core.Phases.Phase
import dotty.tools.dotc.core.SymDenotations.SymDenotation
import dotty.tools.dotc.core.Symbols.Symbol
import dotty.tools.dotc.core.Flags.PackageVal
-import dotty.tools.dotc.typer.Mode
+import dotty.tools.dotc.core.Mode
import dotty.tools.dotc.ast.Trees._
import dotty.tools.dotc.core.Decorators._
import dotty.tools.dotc.util.DotClass
diff --git a/test/dotc/tests.scala b/test/dotc/tests.scala
index 084f13a90..51b8b3dc5 100644
--- a/test/dotc/tests.scala
+++ b/test/dotc/tests.scala
@@ -280,7 +280,7 @@ class tests extends CompilerTest {
@Test def tasty_typer = compileList("tasty_typer", List(
"Applications.scala", "Checking.scala", "ConstFold.scala", "ErrorReporting.scala",
"EtaExpansion.scala", "FrontEnd.scala", "Implicits.scala", "ImportInfo.scala",
- "Inferencing.scala", "Mode.scala", "ProtoTypes.scala", "ReTyper.scala", "RefChecks.scala",
+ "Inferencing.scala", "ProtoTypes.scala", "ReTyper.scala", "RefChecks.scala",
"TypeAssigner.scala", "Typer.scala", "VarianceChecker.scala", "Variances.scala"
) map (typerDir + _), testPickling)
diff --git a/test/test/DeSugarTest.scala b/test/test/DeSugarTest.scala
index 77aa293d5..1365f3222 100644
--- a/test/test/DeSugarTest.scala
+++ b/test/test/DeSugarTest.scala
@@ -9,7 +9,7 @@ import dotty.tools.dotc._
import ast.Trees._
import ast.desugar
import ast.desugar._
-import typer.Mode
+import core.Mode
import Contexts.Context
import scala.collection.mutable.ListBuffer
diff --git a/test/test/showTree.scala b/test/test/showTree.scala
index 2c3316ac9..8d5a5ad7c 100644
--- a/test/test/showTree.scala
+++ b/test/test/showTree.scala
@@ -3,7 +3,7 @@ import dotty.tools.dotc._
import ast.Trees._
import ast.desugar
import ast.desugar._
-import typer.Mode
+import core.Mode
object showTree extends DeSugarTest {