summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAntonio Cunei <antonio.cunei@epfl.ch>2009-12-18 12:41:49 +0000
committerAntonio Cunei <antonio.cunei@epfl.ch>2009-12-18 12:41:49 +0000
commit649b9178954c489a444e2b8ab234072cdd0430e5 (patch)
tree507dbb247cbc9b0ec4dfffad4c4267f05d42eee3
parent4e062472536d8cec91313a315b54560b15893910 (diff)
downloadscala-649b9178954c489a444e2b8ab234072cdd0430e5.tar.gz
scala-649b9178954c489a444e2b8ab234072cdd0430e5.tar.bz2
scala-649b9178954c489a444e2b8ab234072cdd0430e5.zip
Merged revisions 20186,20199,20203,20208-20212,...
Merged revisions 20186,20199,20203,20208-20212,20216-20217 via svnmerge from https://lampsvn.epfl.ch/svn-repos/scala/scala/trunk ........ r20186 | malayeri | 2009-12-17 13:04:55 +0100 (Thu, 17 Dec 2009) | 1 line Fixed #2808. Review by odersky. ........ r20199 | odersky | 2009-12-17 16:50:52 +0100 (Thu, 17 Dec 2009) | 1 line implement new spec for erasure of intersection types. ........ r20203 | odersky | 2009-12-17 18:40:21 +0100 (Thu, 17 Dec 2009) | 1 line Closed #2795. review by dubochet. ........ r20208 | odersky | 2009-12-17 19:06:47 +0100 (Thu, 17 Dec 2009) | 1 line Fixed build problem caused by r20203. Need to maintain old structure for bootstrap. review by dubochet. ........ r20209 | odersky | 2009-12-17 19:16:47 +0100 (Thu, 17 Dec 2009) | 1 line Another fix for the build problem with r20203. Things are trickier than they seemed at first. review by dubochet. ........ r20210 | odersky | 2009-12-17 19:17:10 +0100 (Thu, 17 Dec 2009) | 1 line Closed #2775. Review by moors. ........ r20211 | extempore | 2009-12-17 21:35:44 +0100 (Thu, 17 Dec 2009) | 2 lines Added a method to turn a class name into the pile of bytes which is its classfile on disk. no review. ........ r20212 | extempore | 2009-12-17 21:36:00 +0100 (Thu, 17 Dec 2009) | 4 lines Began the process of consolidating all the code which is painfully duplicated between MarkupParsers and MarkupParser. This motivated by the reappearance of bug #2354 in the exact same form as the one I already fixed. no review. ........ r20216 | rytz | 2009-12-18 11:43:36 +0100 (Fri, 18 Dec 2009) | 1 line read the Exceptions attribute from java classfiles. review by dragos ........ r20217 | cunei | 2009-12-18 12:54:07 +0100 (Fri, 18 Dec 2009) | 3 lines Disabling test for #1801 yet again, still failing on some systems. No review. ........
-rw-r--r--src/compiler/scala/tools/nsc/ast/parser/MarkupParsers.scala33
-rw-r--r--src/compiler/scala/tools/nsc/backend/jvm/GenJVM.scala11
-rw-r--r--src/compiler/scala/tools/nsc/symtab/Definitions.scala1
-rw-r--r--src/compiler/scala/tools/nsc/symtab/classfile/ClassfileParser.scala18
-rw-r--r--src/compiler/scala/tools/nsc/transform/Erasure.scala16
-rw-r--r--src/compiler/scala/tools/nsc/typechecker/Implicits.scala10
-rw-r--r--src/compiler/scala/tools/nsc/typechecker/RefChecks.scala2
-rw-r--r--src/compiler/scala/tools/nsc/util/ScalaClassLoader.scala8
-rw-r--r--src/library/scala/reflect/ClassManifest.scala16
-rw-r--r--src/library/scala/reflect/Manifest.scala16
-rw-r--r--src/library/scala/xml/parsing/MarkupParser.scala234
-rw-r--r--src/library/scala/xml/parsing/MarkupParserCommon.scala51
-rw-r--r--test/files/pos/t2795.scala16
-rw-r--r--test/pending/jvm/t1801.check (renamed from test/files/jvm/t1801.check)0
-rw-r--r--test/pending/jvm/t1801.scala (renamed from test/files/jvm/t1801.scala)0
15 files changed, 220 insertions, 212 deletions
diff --git a/src/compiler/scala/tools/nsc/ast/parser/MarkupParsers.scala b/src/compiler/scala/tools/nsc/ast/parser/MarkupParsers.scala
index 67e1cd8304..bd46d2219d 100644
--- a/src/compiler/scala/tools/nsc/ast/parser/MarkupParsers.scala
+++ b/src/compiler/scala/tools/nsc/ast/parser/MarkupParsers.scala
@@ -50,10 +50,17 @@ trait MarkupParsers
import global._
- class MarkupParser(parser: UnitParser, final val preserveWS: Boolean) {
+ class MarkupParser(parser: UnitParser, final val preserveWS: Boolean) extends scala.xml.parsing.MarkupParserCommon {
import Tokens.{ EMPTY, LBRACE, RBRACE }
+ type PositionType = Position
+ val eof = false
+
+ def xHandleError(that: Char, msg: String) =
+ if (ch == SU) throw TruncatedXML
+ else reportSyntaxError(msg)
+
var input : CharArrayReader = _
import parser.{ symbXMLBuilder => handle, o2p, r2p }
@@ -73,15 +80,6 @@ trait MarkupParsers
finally setter(saved)
}
- /** munch expected XML token, report syntax error for unexpected.
- *
- * @param that ...
- */
- def xToken(that: Char): Unit =
- if (ch == that) nextch
- else if (ch == SU) throw TruncatedXML
- else reportSyntaxError("'%s' expected instead of '%s'".format(that, ch))
-
private var debugLastStartElement = new mutable.Stack[(Int, String)]
private def debugLastPos = debugLastStartElement.top._1
private def debugLastElem = debugLastStartElement.top._2
@@ -421,18 +419,6 @@ trait MarkupParsers
buf.toString.intern
}
- /** scan [S] '=' [S]*/
- def xEQ = { xSpaceOpt; xToken('='); xSpaceOpt }
-
- /** skip optional space S? */
- def xSpaceOpt = { while (isSpace(ch)) { nextch }}
-
- /** scan [3] S ::= (#x20 | #x9 | #xD | #xA)+ */
- def xSpace =
- if (isSpace(ch)) { nextch; xSpaceOpt }
- else if (ch == SU) throw TruncatedXML
- else reportSyntaxError("whitespace expected")
-
/** '<?' ProcInstr ::= Name [S ({Char} - ({Char}'>?' {Char})]'?>'
*
* see [15]
@@ -558,8 +544,9 @@ trait MarkupParsers
*/
def xScalaPatterns: List[Tree] = escapeToScala(parser.patterns(true), "pattern")
+ def reportSyntaxError(pos: Int, str: String) = parser.syntaxError(pos, str)
def reportSyntaxError(str: String) = {
- parser.syntaxError(curOffset, "in XML literal: " + str)
+ reportSyntaxError(curOffset, "in XML literal: " + str)
nextch
}
diff --git a/src/compiler/scala/tools/nsc/backend/jvm/GenJVM.scala b/src/compiler/scala/tools/nsc/backend/jvm/GenJVM.scala
index fef14e940b..50e16dc6b8 100644
--- a/src/compiler/scala/tools/nsc/backend/jvm/GenJVM.scala
+++ b/src/compiler/scala/tools/nsc/backend/jvm/GenJVM.scala
@@ -93,7 +93,6 @@ abstract class GenJVM extends SubComponent {
val TransientAtt = definitions.getClass("scala.transient")
val VolatileAttr = definitions.getClass("scala.volatile")
val RemoteAttr = definitions.getClass("scala.remote")
- val ThrowsAttr = definitions.getClass("scala.throws")
val BeanInfoAttr = definitions.getClass("scala.reflect.BeanInfo")
val BeanInfoSkipAttr = definitions.getClass("scala.reflect.BeanInfoSkip")
val BeanDisplayNameAttr = definitions.getClass("scala.reflect.BeanDisplayName")
@@ -333,7 +332,7 @@ abstract class GenJVM extends SubComponent {
// put some radom value; the actual number is determined at the end
buf.putShort(0xbaba.toShort)
- for (AnnotationInfo(tp, List(exc), _) <- excs.removeDuplicates if tp.typeSymbol == ThrowsAttr) {
+ for (AnnotationInfo(tp, List(exc), _) <- excs.removeDuplicates if tp.typeSymbol == definitions.ThrowsClass) {
val Literal(const) = exc
buf.putShort(
cpool.addClass(
@@ -626,7 +625,7 @@ abstract class GenJVM extends SubComponent {
}
addGenericSignature(jmethod, m.symbol, clasz.symbol)
- val (excs, others) = splitAnnotations(m.symbol.annotations, ThrowsAttr)
+ val (excs, others) = splitAnnotations(m.symbol.annotations, definitions.ThrowsClass)
addExceptionsAttribute(jmethod, excs)
addAnnotations(jmethod, others)
addParamAnnotations(jmethod, m.params.map(_.sym.annotations))
@@ -634,7 +633,7 @@ abstract class GenJVM extends SubComponent {
private def addRemoteException(jmethod: JMethod, meth: Symbol) {
def isRemoteThrows(ainfo: AnnotationInfo) = ainfo match {
- case AnnotationInfo(tp, List(arg), _) if tp.typeSymbol == ThrowsAttr =>
+ case AnnotationInfo(tp, List(arg), _) if tp.typeSymbol == definitions.ThrowsClass =>
arg match {
case Literal(Constant(tpe: Type)) if tpe.typeSymbol == RemoteException.typeSymbol => true
case _ => false
@@ -645,7 +644,7 @@ abstract class GenJVM extends SubComponent {
if (remoteClass ||
(meth.hasAnnotation(RemoteAttr) && jmethod.isPublic())) {
val c = Constant(RemoteException)
- val ainfo = AnnotationInfo(ThrowsAttr.tpe, List(Literal(c).setType(c.tpe)), List())
+ val ainfo = AnnotationInfo(definitions.ThrowsClass.tpe, List(Literal(c).setType(c.tpe)), List())
if (!meth.annotations.exists(isRemoteThrows)) {
meth.addAnnotation(ainfo)
}
@@ -810,7 +809,7 @@ abstract class GenJVM extends SubComponent {
if (!m.hasFlag(Flags.DEFERRED))
addGenericSignature(mirrorMethod, m, module)
- val (throws, others) = splitAnnotations(m.annotations, ThrowsAttr)
+ val (throws, others) = splitAnnotations(m.annotations, definitions.ThrowsClass)
addExceptionsAttribute(mirrorMethod, throws)
addAnnotations(mirrorMethod, others)
addParamAnnotations(mirrorMethod, m.info.params.map(_.annotations))
diff --git a/src/compiler/scala/tools/nsc/symtab/Definitions.scala b/src/compiler/scala/tools/nsc/symtab/Definitions.scala
index 7e346090e0..e1cf7a5a7e 100644
--- a/src/compiler/scala/tools/nsc/symtab/Definitions.scala
+++ b/src/compiler/scala/tools/nsc/symtab/Definitions.scala
@@ -118,6 +118,7 @@ trait Definitions {
lazy val uncheckedStableClass = getClass("scala.annotation.unchecked.uncheckedStable")
lazy val uncheckedVarianceClass = getClass("scala.annotation.unchecked.uncheckedVariance")
lazy val UncheckedClass = getClass("scala.unchecked")
+ lazy val ThrowsClass = getClass("scala.throws")
lazy val TailrecClass = getClass("scala.annotation.tailrec")
lazy val SwitchClass = getClass("scala.annotation.switch")
lazy val ElidableMethodClass = getClass("scala.annotation.elidable")
diff --git a/src/compiler/scala/tools/nsc/symtab/classfile/ClassfileParser.scala b/src/compiler/scala/tools/nsc/symtab/classfile/ClassfileParser.scala
index 6f21e3fee9..da4e0aaa49 100644
--- a/src/compiler/scala/tools/nsc/symtab/classfile/ClassfileParser.scala
+++ b/src/compiler/scala/tools/nsc/symtab/classfile/ClassfileParser.scala
@@ -809,6 +809,10 @@ abstract class ClassfileParser {
// TODO 2: also parse RuntimeInvisibleAnnotation / RuntimeInvisibleParamAnnotation,
// i.e. java annotations with RetentionPolicy.CLASS?
+
+ case nme.ExceptionsATTR if (!isScala) =>
+ parseExceptions(attrLen)
+
case _ =>
in.skip(attrLen)
}
@@ -872,6 +876,20 @@ abstract class ClassfileParser {
None // ignore malformed annotations ==> t1135
}
+ /**
+ * Parse the "Exceptions" attribute which denotes the exceptions
+ * thrown by a method.
+ */
+ def parseExceptions(len: Int) {
+ val nClasses = in.nextChar
+ for (n <- 0 until nClasses) {
+ val cls = pool.getClassSymbol(in.nextChar.toInt)
+ sym.addAnnotation(AnnotationInfo(definitions.ThrowsClass.tpe,
+ Literal(Constant(cls.tpe)) :: Nil,
+ Nil))
+ }
+ }
+
/** Parse a sequence of annotations and attach them to the
* current symbol sym.
*/
diff --git a/src/compiler/scala/tools/nsc/transform/Erasure.scala b/src/compiler/scala/tools/nsc/transform/Erasure.scala
index d58d95cbfe..9db88af6c6 100644
--- a/src/compiler/scala/tools/nsc/transform/Erasure.scala
+++ b/src/compiler/scala/tools/nsc/transform/Erasure.scala
@@ -39,7 +39,7 @@ abstract class Erasure extends AddInterfaces with typechecker.Analyzer with ast.
/** Is `tp` an unbounded generic type (i.e. which could be instantiated
* with primitive as well as class types)?.
*/
- private def genericCore(tp: Type): Type = tp match {
+ private def genericCore(tp: Type): Type = tp.normalize match {
case TypeRef(_, argsym, _) if (argsym.isAbstractType && !(argsym.owner hasFlag JAVA)) =>
tp
case ExistentialType(tparams, restp) =>
@@ -52,7 +52,7 @@ abstract class Erasure extends AddInterfaces with typechecker.Analyzer with ast.
* then Some(N, T) where N is the number of Array constructors enclosing `T`,
* otherwise None. Existentials on any level are ignored.
*/
- def unapply(tp: Type): Option[(Int, Type)] = tp match {
+ def unapply(tp: Type): Option[(Int, Type)] = tp.normalize match {
case TypeRef(_, ArrayClass, List(arg)) =>
genericCore(arg) match {
case NoType =>
@@ -146,7 +146,17 @@ abstract class Erasure extends AddInterfaces with typechecker.Analyzer with ast.
apply(restpe))
case RefinedType(parents, decls) =>
if (parents.isEmpty) erasedTypeRef(ObjectClass)
- else apply(parents.head)
+ else {
+ // implement new spec for erasure of refined types.
+ val psyms = parents map (_.typeSymbol)
+ def isUnshadowed(psym: Symbol) =
+ !(psyms exists (qsym => (psym ne qsym) && (qsym isNonBottomSubClass psym)))
+ val cs = parents.iterator.filter { p => // isUnshadowed is a bit expensive, so try classes first
+ val psym = p.typeSymbol
+ psym.isClass && !psym.isTrait && isUnshadowed(psym)
+ }
+ apply((if (cs.hasNext) cs else parents.iterator.filter(p => isUnshadowed(p.typeSymbol))).next())
+ }
case AnnotatedType(_, atp, _) =>
apply(atp)
case ClassInfoType(parents, decls, clazz) =>
diff --git a/src/compiler/scala/tools/nsc/typechecker/Implicits.scala b/src/compiler/scala/tools/nsc/typechecker/Implicits.scala
index 2bd296b65d..707c91e6ad 100644
--- a/src/compiler/scala/tools/nsc/typechecker/Implicits.scala
+++ b/src/compiler/scala/tools/nsc/typechecker/Implicits.scala
@@ -770,10 +770,16 @@ self: Analyzer =>
EmptyTree // todo: change to existential parameter manifest
else if (sym.isTypeParameterOrSkolem)
EmptyTree // a manifest should have been found by normal searchImplicit
- else
+ else {
+ // the following is tricky! We want to find the parameterized version of
+ // what will become the erasure of the upper bound.
+ var era = erasure.erasure(tp1)
+ if (era.typeSymbol.typeParams.nonEmpty)
+ era = tp1.baseType(era.typeSymbol)
manifestFactoryCall(
"abstractType", tp,
- findSubManifest(pre) :: Literal(sym.name.toString) :: findManifest(tp1.bounds.hi) :: (args map findSubManifest): _*)
+ findSubManifest(pre) :: Literal(sym.name.toString) :: gen.mkClassOf(era) :: (args map findSubManifest): _*)
+ }
} else {
EmptyTree // a manifest should have been found by normal searchImplicit
}
diff --git a/src/compiler/scala/tools/nsc/typechecker/RefChecks.scala b/src/compiler/scala/tools/nsc/typechecker/RefChecks.scala
index 41cf46c8f3..4c919f227a 100644
--- a/src/compiler/scala/tools/nsc/typechecker/RefChecks.scala
+++ b/src/compiler/scala/tools/nsc/typechecker/RefChecks.scala
@@ -316,7 +316,7 @@ abstract class RefChecks extends InfoTransform {
(other hasFlag ACCESSOR) && other.accessed.isVariable && !other.accessed.hasFlag(LAZY)) {
overrideError("cannot override a mutable variable")
} else if ((member hasFlag (OVERRIDE | ABSOVERRIDE)) &&
- !(member.owner isSubClass other.owner) &&
+ !(member.owner.thisType.baseClasses exists (_ isSubClass other.owner)) &&
!member.isDeferred && !other.isDeferred &&
intersectionIsEmpty(member.allOverriddenSymbols, other.allOverriddenSymbols)) {
overrideError("cannot override a concrete member without a third member that's overridden by both "+
diff --git a/src/compiler/scala/tools/nsc/util/ScalaClassLoader.scala b/src/compiler/scala/tools/nsc/util/ScalaClassLoader.scala
index 95396dd95b..95110d6b81 100644
--- a/src/compiler/scala/tools/nsc/util/ScalaClassLoader.scala
+++ b/src/compiler/scala/tools/nsc/util/ScalaClassLoader.scala
@@ -90,4 +90,12 @@ object ScalaClassLoader {
search(getContextLoader())
}
+
+ def findBytesForClassName(s: String): Array[Byte] = {
+ val name = s.replaceAll("""\.""", "/") + ".class"
+ val url = getSystemLoader.getResource(name)
+
+ if (url == null) Array()
+ else new io.Streamable.Bytes { def inputStream() = url.openStream } . toByteArray()
+ }
}
diff --git a/src/library/scala/reflect/ClassManifest.scala b/src/library/scala/reflect/ClassManifest.scala
index 81c36fffcb..58f3c89499 100644
--- a/src/library/scala/reflect/ClassManifest.scala
+++ b/src/library/scala/reflect/ClassManifest.scala
@@ -207,9 +207,21 @@ object ClassManifest {
/** ClassManifest for the abstract type `prefix # name'. `upperBound' is not
* strictly necessary as it could be obtained by reflection. It was
* added so that erasure can be calculated without reflection. */
- def abstractType[T](prefix: OptManifest[_], name: String, upperBound: ClassManifest[_], args: OptManifest[_]*): ClassManifest[T] =
+ def abstractType[T](prefix: OptManifest[_], name: String, clazz: Predef.Class[_], args: OptManifest[_]*): ClassManifest[T] =
new (ClassManifest[T] @serializable) {
- def erasure = upperBound.erasure
+ def erasure = clazz
+ override val typeArguments = args.toList
+ override def toString = prefix.toString+"#"+name+argString
+ }
+
+ /** ClassManifest for the abstract type `prefix # name'. `upperBound' is not
+ * strictly necessary as it could be obtained by reflection. It was
+ * added so that erasure can be calculated without reflection.
+ * todo: remove after next boostrap
+ */
+ def abstractType[T](prefix: OptManifest[_], name: String, upperbound: ClassManifest[_], args: OptManifest[_]*): ClassManifest[T] =
+ new (ClassManifest[T] @serializable) {
+ def erasure = upperbound.erasure
override val typeArguments = args.toList
override def toString = prefix.toString+"#"+name+argString
}
diff --git a/src/library/scala/reflect/Manifest.scala b/src/library/scala/reflect/Manifest.scala
index f425473459..69842e1193 100644
--- a/src/library/scala/reflect/Manifest.scala
+++ b/src/library/scala/reflect/Manifest.scala
@@ -218,9 +218,21 @@ object Manifest {
/** Manifest for the abstract type `prefix # name'. `upperBound' is not
* strictly necessary as it could be obtained by reflection. It was
* added so that erasure can be calculated without reflection. */
- def abstractType[T](prefix: Manifest[_], name: String, upperBound: Manifest[_], args: Manifest[_]*): Manifest[T] =
+ def abstractType[T](prefix: Manifest[_], name: String, clazz: Predef.Class[_], args: Manifest[_]*): Manifest[T] =
new (Manifest[T] @serializable) {
- def erasure = upperBound.erasure
+ def erasure = clazz
+ override val typeArguments = args.toList
+ override def toString = prefix.toString+"#"+name+argString
+ }
+
+ /** Manifest for the abstract type `prefix # name'. `upperBound' is not
+ * strictly necessary as it could be obtained by reflection. It was
+ * added so that erasure can be calculated without reflection.
+ * todo: remove after next bootstrap
+ */
+ def abstractType[T](prefix: Manifest[_], name: String, upperbound: ClassManifest[_], args: Manifest[_]*): Manifest[T] =
+ new (Manifest[T] @serializable) {
+ def erasure = upperbound.erasure
override val typeArguments = args.toList
override def toString = prefix.toString+"#"+name+argString
}
diff --git a/src/library/scala/xml/parsing/MarkupParser.scala b/src/library/scala/xml/parsing/MarkupParser.scala
index 7219051dab..ff19bd3ed5 100644
--- a/src/library/scala/xml/parsing/MarkupParser.scala
+++ b/src/library/scala/xml/parsing/MarkupParser.scala
@@ -6,9 +6,6 @@
** |/ **
\* */
-// $Id$
-
-
package scala.xml
package parsing
@@ -30,10 +27,14 @@ import Utility.Escapes.{ pairs => unescape }
* @author Burak Emir
* @version 1.0
*/
-trait MarkupParser extends AnyRef with TokenTests
+trait MarkupParser extends MarkupParserCommon with TokenTests
{
self: MarkupParser with MarkupHandler =>
+ type PositionType = Int
+
+ def xHandleError(that: Char, msg: String) = reportSyntaxError(msg)
+
val input: Source
/** if true, does not remove surplus whitespace */
@@ -239,8 +240,6 @@ trait MarkupParser extends AnyRef with TokenTests
/** append Unicode character to name buffer*/
protected def putChar(c: Char) = cbuf.append(c)
- //var xEmbeddedBlock = false;
-
/** As the current code requires you to call nextch once manually
* after construction, this method formalizes that suboptimal reality.
*/
@@ -250,7 +249,7 @@ trait MarkupParser extends AnyRef with TokenTests
}
/** this method assign the next character to ch and advances in input */
- def nextch {
+ def nextch = {
if (curInput.hasNext) {
ch = curInput.next
pos = curInput.pos
@@ -265,23 +264,9 @@ trait MarkupParser extends AnyRef with TokenTests
ch = 0.asInstanceOf[Char]
}
}
+ ch
}
- //final val enableEmbeddedExpressions: Boolean = false;
-
- /** munch expected XML token, report syntax error for unexpected
- */
- def xToken(that: Char) {
- if (ch == that)
- nextch
- else {
- reportSyntaxError("'" + that + "' expected instead of '" + ch + "'")
- error("FATAL")
- }
- }
-
- def xToken(that: Seq[Char]): Unit = that foreach xToken
-
/** parse attribute and create namespace scope, metadata
* [41] Attributes ::= { S Name Eq AttValue }
*/
@@ -469,42 +454,32 @@ trait MarkupParser extends AnyRef with TokenTests
def content(pscope: NamespaceBinding): NodeSeq = {
var ts = new NodeBuffer
var exit = eof
- while (! exit) {
- //Console.println("in content, ch = '"+ch+"' line="+scala.io.Position.line(pos));
- /* if( xEmbeddedBlock ) {
- ts.append( xEmbeddedExpr );
- } else {*/
- tmppos = pos;
- exit = eof;
- if(!eof)
- ch match {
- case '<' => // another tag
- //Console.println("before ch = '"+ch+"' line="+scala.io.Position.line(pos)+" pos="+pos);
- nextch;
- //Console.println("after ch = '"+ch+"' line="+scala.io.Position.line(pos)+" pos="+pos);
-
- if('/' ==ch)
- exit = true; // end tag
- else
- content1(pscope, ts)
- //case '{' =>
-/* if( xCheckEmbeddedBlock ) {
- ts.appendAll(xEmbeddedExpr);
- } else {*/
- // val str = new StringBuilder("{");
- // str.append(xText);
- // appendText(tmppos, ts, str.toString());
- /*}*/
- // postcond: xEmbeddedBlock == false!
- case '&' => // EntityRef or CharRef
- nextch;
- if (ch == '#') { // CharacterRef
+ // todo: optimize seq repr.
+ def done = new NodeSeq { val theSeq = ts.toList }
+
+ while (!exit) {
+ tmppos = pos
+ exit = eof
+
+ if (eof)
+ return done
+
+ ch match {
+ case '<' => // another tag
+ nextch match {
+ case '/' => exit = true // end tag
+ case _ => content1(pscope, ts)
+ }
+
+ // postcond: xEmbeddedBlock == false!
+ case '&' => // EntityRef or CharRef
+ nextch match {
+ case '#' => // CharacterRef
nextch
val theChar = handle.text(tmppos, xCharRef(() => ch, () => nextch))
xToken(';');
ts &+ theChar
- }
- else { // EntityRef
+ case _ => // EntityRef
val n = xName
xToken(';')
@@ -512,17 +487,12 @@ trait MarkupParser extends AnyRef with TokenTests
handle.entityRef(tmppos, n)
ts &+ unescape(n)
} else push(n)
- }
- case _ => // text content
- appendText(tmppos, ts, xText);
}
- /*}*/
- }
- val list = ts.toList
- // 2do: optimize seq repr.
- new NodeSeq {
- val theSeq = list
+ case _ => // text content
+ appendText(tmppos, ts, xText);
+ }
}
+ done
} // content(NamespaceBinding)
/** externalID ::= SYSTEM S syslit
@@ -572,47 +542,17 @@ trait MarkupParser extends AnyRef with TokenTests
if ((null != extID) && isValidating) {
pushExternal(extID.systemId)
- //val extSubsetSrc = externalSource( extID.systemId );
-
extIndex = inpStack.length
- /*
- .indexOf(':') != -1) { // assume URI
- Source.fromFile(new java.net.URI(extID.systemLiteral));
- } else {
- Source.fromFile(extID.systemLiteral);
- }
- */
- //Console.println("I'll print it now");
- //val old = curInput;
- //tmppos = curInput.pos;
- //val oldch = ch;
- //curInput = extSubsetSrc;
- //pos = 0;
- //nextch;
extSubset()
-
pop()
-
extIndex = -1
-
- //curInput = old;
- //pos = curInput.pos;
- //ch = curInput.ch;
- //eof = false;
- //while(extSubsetSrc.hasNext)
- //Console.print(extSubsetSrc.next);
-
- //Console.println("returned from external, current ch = "+ch )
}
if ('[' == ch) { // internal subset
nextch
/* TODO */
- //Console.println("hello");
intSubset()
- //while(']' != ch)
- // nextch;
// TODO: do the DTD parsing?? ?!?!?!?!!
xToken(']')
xSpaceOpt
@@ -639,15 +579,14 @@ trait MarkupParser extends AnyRef with TokenTests
*/
def element1(pscope: NamespaceBinding): NodeSeq = {
val pos = this.pos
- val Tuple3(qname, aMap, scope) = xTag(pscope)
- val Tuple2(pre, local) = Utility.prefix(qname) match {
- case Some(p) => (p,qname.substring(p.length+1, qname.length))
- case _ => (null,qname)
+ val (qname, aMap, scope) = xTag(pscope)
+ val (pre, local) = Utility.prefix(qname) match {
+ case Some(p) => (p, qname drop p.length)
+ case _ => (null, qname)
}
val ts = {
if (ch == '/') { // empty element
- xToken('/')
- xToken('>')
+ xToken("/>")
handle.elemStart(pos, pre, local, aMap, scope)
NodeSeq.Empty
}
@@ -685,17 +624,6 @@ trait MarkupParser extends AnyRef with TokenTests
}
}
- /** scan [S] '=' [S]*/
- def xEQ = { xSpaceOpt; xToken('='); xSpaceOpt }
-
- /** skip optional space S? */
- def xSpaceOpt = while (isSpace(ch) && !eof) { nextch; }
-
- /** scan [3] S ::= (#x20 | #x9 | #xD | #xA)+ */
- def xSpace =
- if (isSpace(ch)) { nextch; xSpaceOpt }
- else reportSyntaxError("whitespace expected")
-
/** '&lt;?' ProcInstr ::= Name [S ({Char} - ({Char}'&gt;?' {Char})]'?&gt;'
*
* see [15]
@@ -715,8 +643,7 @@ trait MarkupParser extends AnyRef with TokenTests
nextch
}
};
- xToken('?')
- xToken('>')
+ xToken("?>")
handle.procInstr(tmppos, n, sb.toString)
}
@@ -724,28 +651,17 @@ trait MarkupParser extends AnyRef with TokenTests
* precondition: xEmbeddedBlock == false (we are not in a scala block)
*/
def xText: String = {
- //if( xEmbeddedBlock ) throw FatalError("internal error: encountered embedded block"); // assert
-
- /*if( xCheckEmbeddedBlock )
- return ""
- else {*/
- //Console.println("in xText! ch = '"+ch+"'");
- var exit = false;
- while (! exit) {
- //Console.println("LOOP in xText! ch = '"+ch+"' + pos="+pos);
- putChar(ch);
- val opos = pos;
- nextch;
-
- //Console.println("STILL LOOP in xText! ch = '"+ch+"' + pos="+pos+" opos="+opos);
-
+ var exit = false;
+ while (! exit) {
+ putChar(ch);
+ val opos = pos;
+ nextch;
- exit = eof || /*{ nextch; xCheckEmbeddedBlock }||*/( ch == '<' ) || ( ch == '&' );
- }
- val str = cbuf.toString();
- cbuf.length = 0;
- str
- /*}*/
+ exit = eof || ( ch == '<' ) || ( ch == '&' )
+ }
+ val str = cbuf.toString();
+ cbuf.length = 0;
+ str
}
/** attribute value, terminated by either ' or ". value may not contain &lt;.
@@ -767,7 +683,6 @@ trait MarkupParser extends AnyRef with TokenTests
str
}
-
/* [12] PubidLiteral ::= '"' PubidChar* '"' | "'" (PubidChar - "'")* "'" */
def pubidLiteral(): String = {
val endch = ch
@@ -846,34 +761,16 @@ trait MarkupParser extends AnyRef with TokenTests
val ent = xName
xToken(';')
xSpaceOpt
- /*
- Console.println("hello, pushing!");
- {
- val test = replacementText(ent);
- while(test.hasNext)
- Console.print(test.next);
- } */
+
push(ent)
xSpaceOpt
- //Console.println("hello, getting name");
val stmt = xName
- //Console.println("hello, got name");
xSpaceOpt
- //Console.println("how can we be eof = "+eof);
-
- // eof = true because not external?!
- //if(!eof)
- // error("expected only INCLUDE or IGNORE");
- //pop();
-
- //Console.println("hello, popped");
stmt match {
// parameter entity
- case "INCLUDE" =>
- doInclude()
- case "IGNORE" =>
- doIgnore()
+ case "INCLUDE" => doInclude()
+ case "IGNORE" => doIgnore()
}
case 'I' =>
nextch
@@ -958,11 +855,10 @@ trait MarkupParser extends AnyRef with TokenTests
val n = xName
xSpace
var attList: List[AttrDecl] = Nil
+
// later: find the elemDecl for n
while ('>' != ch) {
val aname = xName
- //Console.println("attribute name: "+aname);
- var defdecl: DefaultDecl = null
xSpace
// could be enumeration (foo,bar) parse this later :-/
while ('"' != ch && '\'' != ch && '#' != ch && '<' != ch) {
@@ -972,29 +868,24 @@ trait MarkupParser extends AnyRef with TokenTests
}
val atpe = cbuf.toString()
cbuf.length = 0
- //Console.println("attr type: "+atpe);
- ch match {
+
+ val defdecl: DefaultDecl = ch match {
case '\'' | '"' =>
- val defValue = xAttributeValue() // default value
- defdecl = DEFAULT(false, defValue)
+ DEFAULT(false, xAttributeValue())
case '#' =>
nextch
xName match {
- case "FIXED" =>
- xSpace
- val defValue = xAttributeValue() // default value
- defdecl = DEFAULT(true, defValue)
- case "IMPLIED" =>
- defdecl = IMPLIED
- case "REQUIRED" =>
- defdecl = REQUIRED
+ case "FIXED" => xSpace ; DEFAULT(true, xAttributeValue())
+ case "IMPLIED" => IMPLIED
+ case "REQUIRED" => REQUIRED
}
case _ =>
+ null
}
xSpaceOpt
- attList = AttrDecl(aname, atpe, defdecl) :: attList
+ attList ::= AttrDecl(aname, atpe, defdecl)
cbuf.length = 0
}
nextch
@@ -1086,9 +977,6 @@ trait MarkupParser extends AnyRef with TokenTests
def reportValidationError(pos: Int, str: String): Unit = reportSyntaxError(pos, str)
def push(entityName: String) {
- //Console.println("BEFORE PUSHING "+ch)
- //Console.println("BEFORE PUSHING "+pos)
- //Console.print("[PUSHING "+entityName+"]")
if (!eof)
inpStack = curInput :: inpStack
diff --git a/src/library/scala/xml/parsing/MarkupParserCommon.scala b/src/library/scala/xml/parsing/MarkupParserCommon.scala
new file mode 100644
index 0000000000..c4ba2ccf15
--- /dev/null
+++ b/src/library/scala/xml/parsing/MarkupParserCommon.scala
@@ -0,0 +1,51 @@
+/* __ *\
+** ________ ___ / / ___ Scala API **
+** / __/ __// _ | / / / _ | (c) 2003-2010, LAMP/EPFL **
+** __\ \/ /__/ __ |/ /__/ __ | http://scala-lang.org/ **
+** /____/\___/_/ |_/____/_/ | | **
+** |/ **
+\* */
+
+package scala.xml
+package parsing
+
+import scala.io.Source
+import scala.xml.dtd._
+import Utility.Escapes.{ pairs => unescape }
+
+/** This is not a public trait - it contains common code shared
+ * between the library level XML parser and the compiler's.
+ * All members should be accessed through those.
+ */
+private[scala] trait MarkupParserCommon extends TokenTests {
+ // type InputType // Source, CharArrayReader
+ // type HandleType // MarkupHandler, SymbolicXMLBuilder
+ // type PositionType // Int, Position
+
+ def ch: Char
+ def nextch: Char
+ def xHandleError(that: Char, msg: String): Unit
+ def reportSyntaxError(str: String): Unit
+ def reportSyntaxError(pos: Int, str: String): Unit
+ def eof: Boolean
+
+ def xToken(that: Char) {
+ if (ch == that) nextch
+ else xHandleError(that, "'%s' expected instead of '%s'".format(that, ch))
+ }
+ def xToken(that: Seq[Char]) { that foreach xToken }
+
+ /** scan [S] '=' [S]*/
+ def xEQ = { xSpaceOpt; xToken('='); xSpaceOpt }
+
+ /** skip optional space S? */
+ def xSpaceOpt = while (isSpace(ch) && !eof) nextch
+
+ /** scan [3] S ::= (#x20 | #x9 | #xD | #xA)+ */
+ def xSpace =
+ if (isSpace(ch)) { nextch; xSpaceOpt }
+ else xHandleError(ch, "whitespace expected")
+
+ //
+ def returning[T](x: T)(f: T => Unit): T = { f(x) ; x }
+}
diff --git a/test/files/pos/t2795.scala b/test/files/pos/t2795.scala
new file mode 100644
index 0000000000..c355a10c54
--- /dev/null
+++ b/test/files/pos/t2795.scala
@@ -0,0 +1,16 @@
+package bug1
+
+trait Element[T] {
+}
+
+trait Config {
+ type T <: Element[T]
+ // XXX Following works fine:
+ // type T <: Element[_]
+}
+
+trait Transform { self: Config =>
+ def processBlock(block: Array[T]): Unit = {
+ var X = new Array[T](1)
+ }
+}
diff --git a/test/files/jvm/t1801.check b/test/pending/jvm/t1801.check
index bf78a99db9..bf78a99db9 100644
--- a/test/files/jvm/t1801.check
+++ b/test/pending/jvm/t1801.check
diff --git a/test/files/jvm/t1801.scala b/test/pending/jvm/t1801.scala
index 6ed7c56336..6ed7c56336 100644
--- a/test/files/jvm/t1801.scala
+++ b/test/pending/jvm/t1801.scala