Initial outline of Dart parser
authorJan Vrany <jan.vrany@fit.cvut.cz>
Thu, 10 Jan 2013 13:21:04 +0000
changeset 1 46dd2b3b6974
parent 0 947ac083e76c
child 2 8fedb5e096fc
Initial outline of Dart parser
compiler/Dart__Parser.st
compiler/Dart__Scanner.st
compiler/Dart__ScannerBase.st
compiler/Make.proto
compiler/Make.spec
compiler/Makefile
compiler/abbrev.stc
compiler/bc.mak
compiler/bmake.bat
compiler/compiler.rc
compiler/jv_dart_compiler.st
compiler/lccmake.bat
compiler/libInit.cc
compiler/mingwmake.bat
compiler/vcmake.bat
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/Dart__Parser.st	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,65 @@
+"{ Package: 'jv:dart/compiler' }"
+
+"{ NameSpace: Dart }"
+
+PPCompositeParser subclass:#Parser
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Languages-Dart-Parser'
+!
+
+PPParser subclass:#TokenParser
+	instanceVariableNames:'tokenType'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Parser
+!
+
+
+!Parser::TokenParser class methodsFor:'instance creation'!
+
+for: tokenType
+
+    ^self new tokenType: tokenType
+
+    "Created: / 14-03-2012 / 23:10:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!Parser::TokenParser methodsFor:'accessing'!
+
+tokenType
+    ^ tokenType
+!
+
+tokenType:aSymbol
+    tokenType := aSymbol.
+! !
+
+!Parser::TokenParser methodsFor:'parsing'!
+
+parseOn:aJavaScanner
+    "Parse aStream with the receiving parser and answer the parse-result or an instance of PPFailure. 
+    Override this method in subclasses to specify custom parse behavior. Do not call this method from outside, 
+    instead use #parse:."
+
+    | pos |
+
+    pos := aJavaScanner position.
+
+    ^(aJavaScanner nextToken = tokenType) ifTrue:[
+        aJavaScanner token
+    ] ifFalse:[
+        aJavaScanner position: pos.
+        PPFailure message: (tokenType printString , ' token expected (got ', aJavaScanner tokenType , ' {',(aJavaScanner tokenValue ? '<nil>') printString,'})') at: aJavaScanner position
+    ]
+
+    "Modified: / 17-03-2012 / 13:34:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!Parser class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/Dart__Scanner.st	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,1083 @@
+"
+ COPYRIGHT (c) 2003 by Claus Gittinger
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+"{ Package: 'jv:dart/compiler' }"
+
+"{ NameSpace: Dart }"
+
+ScannerBase subclass:#Scanner
+	instanceVariableNames:'allowDegeneratedMantissa keywordTable'
+	classVariableNames:'Verbose'
+	poolDictionaries:''
+	category:'Languages-Dart-Parser'
+!
+
+Object subclass:#Token
+	instanceVariableNames:'type value startPosition endPosition'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Scanner
+!
+
+!Scanner class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by Claus Gittinger
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+examples
+"
+    |s in|
+
+    in := '
+function scalefactor(value) {
+    scalevector[0]=value;
+    scalevector[1]=1.;
+    scalevector[2]=1.;
+}
+'.
+
+    s := JavaScanner for:in readStream.
+    s nextToken
+
+
+    |s in|
+
+    in := '
+function scalefactor(value) {
+    scalevector[0]=value;
+    scalevector[1]=1.;
+    scalevector[2]=1.;
+}
+'.
+    s := JavaScanner new.
+    s scanTokens:(in readStream).
+
+
+    |s in|
+
+    in := '
+function scalefactor(value) {
+    scalevector[0]=value;
+    scalevector[1]=1.;
+    scalevector[2]=1.;
+}
+'.
+    in := in readStream.
+    s := JavaScanner for:in.
+    [in atEnd] whileFalse:[
+	Transcript showCR:s nextToken
+    ]
+
+"
+
+    "Created: / 13.5.1998 / 14:54:06 / cg"
+! !
+
+!Scanner class methodsFor:'initialization'!
+
+setupActions
+    "initialize the scanners actionTables - these are used to dispatch
+     into scanner methods as characters are read"
+
+    |block|
+
+    self setupKeywordTable.
+
+    ActionArray := Array new:256.
+    TypeArray := Array new:256.
+
+    block := [:s :char | s nextNumber].
+    ($0 asciiValue) to:($9 asciiValue) do:[:index |
+        ActionArray at:index put:block
+    ].
+
+    block := [:s :char | s nextSingleCharacterToken:char].
+    #( $: $; $, ${ $} $( $) $[ $] $_ $? $@) do:[:ch |
+        ActionArray at:(ch asciiValue) put:block
+    ].
+
+    block := [:s :char | s nextIdentifier].
+    ($a asciiValue) to:($z asciiValue) do:[:index |
+        ActionArray at:index put:block
+    ].
+    ($A asciiValue) to:($Z asciiValue) do:[:index |
+        ActionArray at:index put:block
+    ].
+    ActionArray at:$_ asciiValue put:block.
+
+    ActionArray at:$$ asciiValue put:block.
+
+    ActionArray at:($. asciiValue) put:[:s :char | s nextDotOrFloatOrEllipsis].
+
+    ActionArray at:($' asciiValue) put:[:s :char | s nextString:$' character:true].
+    ActionArray at:($" asciiValue) put:[:s :char | s nextString:$" character:false].
+    ActionArray at:($!! asciiValue) put:[:s :char | s nextMulti:#(($= #'!!=')) after:char].
+    ActionArray at:($= asciiValue) put:[:s :char | s nextMulti:#(($= #'==')) after:char].
+    ActionArray at:($< asciiValue) put:[:s :char | s nextMulti:#(($= #'<=') ($< #'<<')) after:char].
+    ActionArray at:($> asciiValue) put:[:s :char | s nextMulti:#(($= #'>=') ($> #'>>' $> #'>>>' $= #'>>>=')) after:char].
+
+    ActionArray at:($- asciiValue) put:[:s :char | s nextMulti:#(($- #'--') ($= #'-=')) after:char].
+    ActionArray at:($+ asciiValue) put:[:s :char | s nextMulti:#(($+ #'++') ($= #'+=')) after:char].
+    ActionArray at:($* asciiValue) put:[:s :char | s nextMulti:#(($= #'*=')) after:char].
+    ActionArray at:($/ asciiValue) put:[:s :char | s nextMulti:#(($= #'/=') ($/ nil #skipEOLComment) ($* nil #skipComment)) after:char].
+    ActionArray at:($% asciiValue) put:[:s :char | s nextMulti:#(($= #'%=')) after:char].
+    ActionArray at:($& asciiValue) put:[:s :char | s nextMulti:#(($= #'&=') ($& #'&&')) after:char].
+    ActionArray at:($^ asciiValue) put:[:s :char | s nextMulti:#(($= #'^=')) after:char].
+    ActionArray at:($~ asciiValue) put:[:s :char | s nextMulti:#(($= #'~=')) after:char].
+    ActionArray at:($| asciiValue) put:[:s :char | s nextMulti:#(($= #'|=') ($| #'||')) after:char].
+
+    "
+     self setupActions
+    "
+
+    "Created: / 14-05-1998 / 15:48:03 / cg"
+    "Modified: / 17-05-1998 / 21:03:37 / cg"
+    "Modified: / 16-03-2012 / 23:49:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+setupKeywordTable
+    "initialize the scanners actionTables - these are used to dispatch
+     into scanner methods as characters are read"
+
+    KeywordTable := Dictionary new.
+
+    #(
+        'abstract'              abstract
+        'assert'                assert
+        'class'                 class
+        'extends'               extends
+        'factory'               factory
+        'get'                   get
+        'implements'            implements
+        'import'                import
+        'interface'             interface
+        'is'                    is
+        'library'               library
+        'native'                native
+        'negate'                negate
+        'operator'              operator
+        'set'                   set
+        'source'                source
+        'static'                static
+        'typedef'               typedef
+        'this'                  this
+        'super'                 super
+        'null'                  null
+        'true'                  #true
+        'false'                 #false
+        'const'                 const
+        'new'                   new
+        'void'                  void
+        'final'                 final
+        'var'                   var
+        'while'                 while
+        'do'                    do
+        'for'                   for
+        'in'                    in
+        'if'                    if
+        'else'                  else
+        'switch'                switch
+        'case'                  case
+        'default'               default
+        'try'                   try
+        'catch'                 catch
+        'finally'               finally
+        'break'                 break
+        'continue'              continue
+        'return'                return
+        'throw'                 throw
+    ) pairWiseDo:[:s :kw |
+        KeywordTable at:s put:kw
+    ].
+
+    "
+     NewJavaScanner setupKeywordTable
+    "
+
+    "Created: / 14-05-1998 / 15:48:03 / cg"
+    "Modified: / 17-05-1998 / 21:03:37 / cg"
+    "Modified: / 10-01-2013 / 10:51:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!Scanner methodsFor:'accessing'!
+
+token
+    "the previously scanned token"
+
+    ^Token new
+        type: tokenType;
+        value: tokenValue;
+        startPosition: tokenStartPosition;
+        endPosition: tokenEndPosition;
+        yourself
+
+    "Created: / 17-03-2012 / 13:32:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 10-01-2013 / 11:20:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!Scanner methodsFor:'converting'!
+
+asPetitStream
+
+    ^self
+
+    "Created: / 14-03-2012 / 22:51:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!Scanner methodsFor:'error handling'!
+
+errorMessagePrefix
+    ^ 'Dart Error:'
+
+    "Modified: / 10-01-2013 / 11:21:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+warningMessagePrefix
+    ^ 'Dart Warning:'
+
+    "Modified: / 10-01-2013 / 11:21:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!Scanner methodsFor:'initialization'!
+
+initialize
+    "initialize the scanner"
+
+    super initialize.
+
+    allowDegeneratedMantissa := true.     "/ something like 123.
+    keywordTable := self class keywordTable.
+! !
+
+!Scanner methodsFor:'private'!
+
+checkForKeyword:string
+    "check if string is a keyword (as opposed to an identifier)."
+
+    |tok|
+
+    (tok := keywordTable at:string ifAbsent:nil) notNil ifTrue:[
+	tokenType := tok.
+	^ true
+    ].
+    ^ false
+!
+
+isCommentCharacter:ch
+    "return true, if ch is the comment-start character"
+
+    ^ false
+
+    "Created: / 14.5.1998 / 20:53:33 / cg"
+!
+
+rememberTokenStartPosition
+    self rememberTokenStartPosition:0
+
+    "Created: / 17-03-2012 / 00:19:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+rememberTokenStartPosition: offset
+    tokenStartPosition := source position - offset
+
+    "Created: / 17-03-2012 / 17:39:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!Scanner methodsFor:'reading next token'!
+
+characterEscape:char
+    |ascii c |
+
+    char == $" ifTrue:[
+        ^ $".
+    ].
+
+    char == $b ifTrue:[
+        ^ Character backspace
+    ].
+    char == $t ifTrue:[
+        ^ Character tab
+    ].
+    char == $n ifTrue:[
+        ^ Character cr
+    ].
+    char == $r ifTrue:[
+        ^ Character return
+    ].
+    char == $f ifTrue:[
+        ^ Character newPage
+    ].
+
+    char == $u ifTrue:[
+        ascii := 0.
+        c := source peekOrNil.
+        4 timesRepeat:[
+            (c isDigitRadix:16) ifFalse:[
+                self syntaxError:'invalid hex character constant'
+                        position:source position-2 to:(source position - 1).
+                ^ Character value:ascii
+            ].
+            ascii := (ascii bitShift:4).
+            ascii := ascii + c digitValue.
+            source next. c := source peekOrNil.
+        ].
+        ^ Character value:ascii
+    ].
+"/    char == $x ifTrue:[
+"/        ascii := 0.
+"/        c := source peekOrNil.
+"/        2 timesRepeat:[
+"/            (c isDigitRadix:16) ifFalse:[
+"/                self syntaxError:'invalid hex character constant'
+"/                        position:source position-2 to:(source position - 1).
+"/                ^ Character value:ascii
+"/            ].
+"/            ascii := (ascii bitShift:4).
+"/            ascii := ascii + c digitValue.
+"/            source next. c := source peekOrNil.
+"/        ].
+"/        ^ Character value:ascii
+"/    ].
+    "OctalEscape ::= \ OctalDigit |
+                     \ OctalDigit OctalDigit
+                     \ ZeroToThree OctalDigit OctalDigit"
+
+    (char between:$0 and:$3) ifTrue:[
+        ascii := char digitValue.
+        c := source peekOrNil.
+        (c between: $0 and: $7) ifTrue:[
+            source next.
+            ascii := (ascii bitShift:3).
+            ascii := ascii + c digitValue.
+        ].
+        c := source peekOrNil.
+        (c between: $0 and: $7) ifTrue:[
+            source next.
+            ascii := (ascii bitShift:3).
+            ascii := ascii + c digitValue.
+        ].
+        ^ Character value:ascii
+    ].
+    (char between:$4 and: $7) ifTrue:[
+        ascii := char digitValue.            
+        c := source peekOrNil.
+        (c between: $0 and: $7) ifTrue:[
+            source next.
+            ascii := (ascii bitShift:3).
+            ascii := ascii + c digitValue.
+        ].
+        ^ Character value:ascii
+    ].
+
+    ^ char
+
+    "Modified: / 16-03-2012 / 10:07:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+exponentPart:initialValue
+    |nextChar value s|
+
+    value := initialValue.
+    nextChar := source peekOrNil.
+
+    ((nextChar == $e) or:[nextChar == $E]) ifTrue:[
+	nextChar := source nextPeek.
+	(nextChar notNil and:[(nextChar isDigitRadix:10) or:['+-' includes:nextChar]]) ifTrue:[
+	    s := 1.
+	    (nextChar == $+) ifTrue:[
+		nextChar := source nextPeek
+	    ] ifFalse:[
+		(nextChar == $-) ifTrue:[
+		    nextChar := source nextPeek.
+		    s := s negated
+		]
+	    ].
+	    value := value asFloat
+		     * (10.0 raisedToInteger:((Integer readFrom:source radix:10) * s))
+	]
+    ].
+    ^ value
+!
+
+hexponentPart:initialValue
+    |nextChar value s|
+
+    value := initialValue.
+    nextChar := source peekOrNil.
+
+    ((nextChar == $p) or:[nextChar == $P]) ifTrue:[
+        nextChar := source nextPeek.
+        (nextChar notNil and:[(nextChar isDigitRadix:16) or:['+-' includes:nextChar]]) ifTrue:[
+            s := 1.
+            (nextChar == $+) ifTrue:[
+                nextChar := source nextPeek
+            ] ifFalse:[
+                (nextChar == $-) ifTrue:[
+                    nextChar := source nextPeek.
+                    s := s negated
+                ]
+            ].
+            value := value asFloat
+                     * (16.0 raisedToInteger:((Integer readFrom:source radix:16) * s))
+        ]
+    ].
+    ^ value
+
+    "Created: / 16-03-2012 / 00:00:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+nextDotOrFloat
+    |nextChar|
+
+    nextChar := source nextPeek.
+    nextChar isDigit ifTrue:[
+	^ self nextFractionalPart:0.
+    ].
+    tokenType := tokenValue := $. .
+    ^ tokenType
+!
+
+nextDotOrFloatOrEllipsis
+    |nextChar nextChar2|
+
+    nextChar := source nextPeek.
+    nextChar isDigit ifTrue:[
+        ^ self nextFractionalPart:0.
+    ].
+    nextChar == $. ifTrue:[
+        nextChar2 := source nextPeek.
+        nextChar2 == $. ifTrue:[
+            source next.
+            tokenType := #Ellipsis.
+            tokenValue := '...'.
+            ^tokenType.
+        ] ifFalse:[
+            source skip: -1.
+        ].
+    ].
+    tokenType := tokenValue := $. .
+    ^ tokenType
+
+    "Created: / 15-03-2012 / 10:08:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+nextFractionalPart:intValue
+    |nextChar value|
+
+    value := intValue.
+    nextChar := source peekOrNil.
+
+    (nextChar notNil and:[nextChar isDigitRadix:10]) ifTrue:[
+        value := value asFloat + (self nextMantissa:10).
+        nextChar := source peekOrNil
+    ] ifFalse:[
+        allowDegeneratedMantissa == true ifTrue:[
+            self warning:'degenerated float constant: ' , value printString , '.' .
+            tokenValue := value asFloat.
+            tokenType := #Float.
+            ^ tokenType
+        ].
+        nextChar := peekChar := $..
+    ].
+
+    ((nextChar == $e) or:[nextChar == $E]) ifTrue:[
+        value := self exponentPart:value.
+        nextChar := source peekOrNil
+    ] ifFalse:[
+        ((nextChar == $p) or:[nextChar == $P]) ifTrue:[
+            value := self hexponentPart:value.
+            nextChar := source peekOrNil
+        ].
+    ].
+
+    tokenValue := value.
+
+    (nextChar == $d or:[nextChar == $D]) ifTrue:[
+        source next.
+        tokenType := #Double.
+    ] ifFalse:[
+        (nextChar == $f or:[nextChar == $F]) ifTrue:[
+            source next.
+        ].
+        tokenType := #Float.
+    ].
+
+    ^ tokenType
+
+    "Created: / 14-05-1998 / 20:00:25 / cg"
+    "Modified: / 16-05-1998 / 15:51:46 / cg"
+    "Modified: / 16-03-2012 / 00:00:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+nextHexFractionalPart:intValue
+    |nextChar value|
+
+    value := intValue.
+    nextChar := source peekOrNil.
+
+    (nextChar notNil and:[nextChar isDigitRadix:16]) ifTrue:[
+        value := value asFloat + (self nextMantissa:16).
+        nextChar := source peekOrNil
+    ] ifFalse:[
+        allowDegeneratedMantissa == true ifTrue:[
+            self warning:'degenerated float constant: ' , value printString , '.' .
+            tokenValue := value asFloat.
+            tokenType := #Float.
+            ^ tokenType
+        ].
+        nextChar := peekChar := $..
+    ].
+
+    ((nextChar == $e) or:[nextChar == $E]) ifTrue:[
+        value := self exponentPart:value.
+        nextChar := source peekOrNil
+    ] ifFalse:[
+        ((nextChar == $p) or:[nextChar == $P]) ifTrue:[
+            value := self hexponentPart:value.
+            nextChar := source peekOrNil
+        ].
+    ].
+
+    tokenValue := value.
+
+    (nextChar == $d or:[nextChar == $D]) ifTrue:[
+        source next.
+        tokenType := #Double.
+    ] ifFalse:[
+        (nextChar == $f or:[nextChar == $F]) ifTrue:[
+            source next.
+        ].
+        tokenType := #Float.
+    ].
+
+    ^ tokenType
+
+    "Created: / 14-05-1998 / 20:00:25 / cg"
+    "Modified: / 16-05-1998 / 15:51:46 / cg"
+    "Created: / 16-03-2012 / 00:16:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+nextIdentifier
+    "an alpha character (or underscore) has been read.
+     Return the next identifier."
+
+    |nextChar string ok pos|
+
+    hereChar == $_ ifTrue:[
+        nextChar := source nextPeek.
+        string := '_'.
+        [nextChar == $_] whileTrue:[
+            string := string copyWith:$_.
+            nextChar := source nextPeek.
+        ].
+        nextChar isAlphaNumeric ifTrue:[
+            string := string , source nextAlphaNumericWord.
+        ]
+    ] ifFalse:[
+        string := source nextAlphaNumericWord "self nextId".
+    ].
+    nextChar := source peekOrNil.
+
+    (nextChar == $_ or:[nextChar == $$]) ifTrue:[
+        pos := source position.
+        ok := true.
+        [ok] whileTrue:[
+            string := string copyWith:nextChar.
+            nextChar := source nextPeek.
+            nextChar isNil ifTrue:[
+                ok := false
+            ] ifFalse:[
+                (nextChar isAlphaNumeric) ifTrue:[
+                    string := string , source nextAlphaNumericWord.
+                    nextChar := source peekOrNil.
+                ].
+                (nextChar == $_ or:[nextChar == $$]) ifFalse:[
+                    ok := false
+                ]
+            ]
+        ].
+    ].
+
+"/    (nextChar == $: and:[scanColonAsLabel]) ifTrue:[
+"/        source next.
+"/        ch2 := source peekOrNil.
+"/        "/ colon follows - care for '::' (nameSpace separator) or ':=' (assignment)
+"/        (ch2 == $=) ifFalse:[
+"/            (ch2 == $:) ifFalse:[
+"/                tokenEndPosition := source position - 1.
+"/                token := string copyWith:nextChar.
+"/                tokenType := #Keyword.
+"/                ^ tokenType
+"/            ].
+"/            peekChar := $:.
+"/            peekChar2 := $:.
+"/        ] ifTrue:[
+"/            peekChar := $:.
+"/            peekChar2 := $=.
+"/        ]
+"/    ].
+
+    tokenValue := string.
+    (self checkForKeyword:string) ifFalse:[
+        tokenType := #Identifier.
+    ].
+    tokenEndPosition := source position - 1.
+    peekChar2 notNil ifTrue:[
+        tokenEndPosition := tokenEndPosition - 1
+    ].
+    ^ tokenType
+
+    "Modified: / 15-03-2012 / 20:53:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+nextMulti:list after:firstChar
+    "a char has been read - peek ahead in list"
+
+    |pc|
+
+    peekChar isNil ifTrue:[
+	source next.
+    ] ifFalse:[
+	peekChar := nil.
+    ].
+    pc := source peek.
+
+    list do:[:spec |
+	|ch tok idx|
+
+	ch := spec at:1.
+	tok := spec at:2.
+	idx := 3.
+
+	pc == ch ifTrue:[
+	    peekChar isNil ifTrue:[
+		source next.
+	    ] ifFalse:[
+		peekChar := nil.
+	    ].
+
+	    spec size > 2 ifTrue:[
+		ch := spec at:3.
+		source peek == ch ifTrue:[
+		    source next.
+		    tok := spec at:4.
+		    idx := 5.
+		]
+	    ].
+
+	    tok isNil ifTrue:[
+		^ self perform:(spec at:idx).
+	    ].
+
+	    tokenType := tokenValue := tok.
+	    ^ tokenType
+	]
+    ].
+
+    tokenType := tokenValue := firstChar.
+    ^ tokenType
+
+    "Created: / 14.5.1998 / 19:19:34 / cg"
+    "Modified: / 16.5.1998 / 19:09:59 / cg"
+!
+
+nextNumber
+    |nextChar value|
+
+    value := 0.
+    nextChar := source peekOrNil.
+    nextChar == $0 ifTrue:[
+        source next.
+        nextChar := source peekOrNil.
+        (nextChar == $x or:[nextChar == $X]) ifTrue:[
+            source next.
+            value := Integer readFrom:source radix:16.
+
+            tokenValue := value.
+            numberRadix := 16.
+
+            nextChar := source peekOrNil.
+
+            source peekOrNil isNil ifTrue:[
+                tokenType := #Integer.
+                tokenValue := 0.
+                ^tokenType
+            ].
+
+            (nextChar == $L or:[nextChar == $l]) ifTrue:[
+                source next.
+                tokenType := #LongInteger.
+            ].
+            nextChar == $. ifTrue:[
+                source next.
+                ^self nextHexFractionalPart: tokenValue.
+            ].
+            tokenType := #Integer.
+            ^ tokenType.
+
+        ].
+        (nextChar notNil and:[nextChar between:$0 and:$7]) ifTrue:[
+            value := Integer readFrom:source radix:8.
+            tokenValue := value.
+            numberRadix := 8.
+
+            nextChar := source peekOrNil.
+            (nextChar == $L or:[nextChar == $l]) ifTrue:[
+                source next.
+                tokenType := #LongInteger.
+            ] ifFalse:[
+                tokenType := #Integer.
+            ].
+            ^ tokenType
+        ].
+    ].
+    (nextChar == $L or:[nextChar == $l]) ifTrue:[
+        source next.
+        tokenValue := value.
+        tokenType := #LongInteger.
+        ^ tokenType
+    ].
+    (nextChar == $D or:[nextChar == $d]) ifTrue:[
+        source next.
+        tokenValue := 0.0.
+        tokenType := #Double.
+        ^ tokenType
+    ].
+
+
+
+    numberRadix := 10.
+    nextChar isDigit ifTrue:[
+        value := Integer readFrom:source radix:10.
+        nextChar := source peekOrNil.
+
+        (nextChar == $L or:[nextChar == $l]) ifTrue:[
+            source next.
+            tokenValue := value.
+            tokenType := #LongInteger.
+            ^ tokenType
+        ].
+    ].
+
+    (nextChar == $.) ifTrue:[
+        nextChar := source nextPeek.
+        (nextChar notNil and:[nextChar isDigitRadix:10]) ifTrue:[
+            value := value asFloat + (self nextMantissa:10).
+            nextChar := source peekOrNil
+        ] ifFalse:[
+            allowDegeneratedMantissa == true ifTrue:[
+                self warning:'degenerated float constant: ' , value printString , '.' .
+                tokenValue := value asFloat.
+                tokenType := #Float.
+                ^ tokenType
+            ].
+
+"/            nextChar == (Character cr) ifTrue:[
+"/                lineNr := lineNr + 1.
+"/            ].
+            nextChar := peekChar := $..
+        ]
+    ].
+    ((nextChar == $e) or:[nextChar == $E]) ifTrue:[
+        value := self exponentPart:value.
+        nextChar := source peekOrNil
+    ] ifFalse:[
+        ((nextChar == $p) or:[nextChar == $P]) ifTrue:[
+            value := self hexponentPart:value.
+            nextChar := source peekOrNil
+        ]
+    ].
+
+    nextChar == $- ifTrue:[
+        self
+            warnPossibleIncompatibility:'add a space before ''-'' for compatibility with other systems'
+            position:(source position) to:source position.
+    ].
+
+    (nextChar == $d or:[nextChar == $D]) ifTrue:[
+        source next.
+        tokenType := #Double.
+        value := value asFloat.
+    ] ifFalse:[
+        (nextChar == $f or:[nextChar == $F]) ifTrue:[
+            source next.
+            tokenType := #Float.
+            value := value asFloat.
+        ] ifFalse:[
+            (value isMemberOf:Float) ifTrue:[
+                tokenType := #Float.
+            ] ifFalse:[
+                tokenType := #Integer.
+            ]
+        ]
+    ].
+    tokenValue := value.
+    ^ tokenType
+
+    "Created: / 14-05-1998 / 20:00:25 / cg"
+    "Modified: / 16-05-1998 / 15:51:46 / cg"
+    "Modified: / 16-03-2012 / 23:34:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+nextString:delimiter character:isCharacter
+    |s pos nextChar inString|
+
+    s := (String new:20) writeStream.
+
+    pos := source position.
+    source next.
+    nextChar := source next.
+    inString := true.
+
+    [inString] whileTrue:[
+	nextChar isNil ifTrue:[
+	    self syntaxError:'unexpected end-of-input in String'
+		    position:pos to:(source position - 1).
+	    tokenValue := nil.
+	    tokenType := #EOF.
+	    ^ tokenType
+	].
+	nextChar == $\ ifTrue:[
+	    nextChar := source next.
+	    nextChar := self characterEscape:nextChar.
+	] ifFalse:[
+	    (nextChar == Character cr) ifTrue:[
+		lineNr := lineNr + 1
+	    ] ifFalse:[
+		(nextChar == delimiter) ifTrue:[
+		    (source peekOrNil == delimiter) ifTrue:[
+			source next
+		    ] ifFalse:[
+			inString := false
+		    ]
+		].
+	    ].
+	].
+	inString ifTrue:[
+	    s nextPut:nextChar.
+	    nextChar := source next
+	]
+    ].
+
+    tokenValue := s contents.
+    isCharacter ifTrue:[
+	tokenValue size ~~ 1 ifTrue:[
+	    self syntaxError:'bad (multi-)character constant'
+		    position:pos to:(source position - 1).
+	].
+	tokenValue := tokenValue at:1.
+	tokenType := #Character.
+    ] ifFalse:[
+	tokenType := #String.
+    ].
+    ^ tokenType
+
+    "Created: / 16.5.1998 / 19:53:05 / cg"
+    "Modified: / 16.5.1998 / 19:57:16 / cg"
+!
+
+nextToken
+    |t|
+
+    [
+        t := super nextToken.
+        tokenEndPosition := source position - 1.
+        t isNil
+    ] whileTrue.
+    Verbose == true ifTrue:[
+        Transcript 
+            show:'JavaScanner nextToken => ';
+            show: t storeString;
+            show: ' | ';
+            showCR: tokenValue.
+    ].
+    ^ t
+
+    "Created: / 14-05-1998 / 15:48:04 / cg"
+    "Modified: / 16-05-1998 / 19:12:29 / cg"
+    "Modified: / 17-03-2012 / 17:35:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+skipComment
+    |commentStream commentType startPos|
+
+    startPos := source position.
+    source next.
+    hereChar := source peekOrNil.
+
+    [
+	[hereChar notNil and:[hereChar ~~ $*]] whileTrue:[
+	    hereChar == (Character cr) ifTrue:[
+		lineNr := lineNr + 1.
+	    ].
+	    hereChar := source nextPeek
+	].
+    ] doUntil:[
+	hereChar := source nextPeek.
+	hereChar isNil or:[hereChar == $/].
+    ].
+
+    "skip final /"
+    source next.
+
+    hereChar isNil ifTrue:[
+	self warning:'unclosed comment' position:startPos to:(source position)
+    ].
+
+"/    saveComments ifTrue:[
+"/        self endComment:(commentStream contents) type:commentType.
+"/    ].
+    ^ nil. "/ force nextToken again
+
+    "Modified: / 31.3.1998 / 23:45:26 / cg"
+!
+
+skipEOLComment
+    hereChar := source peek.
+    [hereChar notNil and:[hereChar ~~ Character cr]] whileTrue:[
+	hereChar := source nextPeek.
+    ].
+    lineNr := lineNr + 1.
+
+    ^ nil.
+
+    "Created: / 16.5.1998 / 19:11:05 / cg"
+    "Modified: / 16.5.1998 / 19:15:42 / cg"
+! !
+
+!Scanner methodsFor:'stream api'!
+
+atEnd
+    ^ source atEnd
+
+    "Created: / 14-03-2012 / 22:53:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+next
+    ^ source next
+
+    "Created: / 14-03-2012 / 22:53:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+next: anInteger 
+    "Answer up to anInteger elements of my collection. Overridden for efficiency."
+
+    ^ source nextAvailable: anInteger
+
+    "Modified: / 14-03-2012 / 22:55:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+peek
+    "An improved version of peek, that is slightly faster than the built in version."
+
+    ^source peek
+
+    "Modified: / 14-03-2012 / 22:46:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+position
+    ^source position
+
+    "Created: / 14-03-2012 / 22:52:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+position: anInteger
+    "The receiver does not check for invalid arguments passed to this method, as it is solely used with valid indexes for backtracking."
+
+"/    anInteger = 16 ifTrue:[self halt].
+
+    ^source position: anInteger
+
+    "Modified: / 15-03-2012 / 10:59:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+skipSeparators
+
+    source skipSeparators
+
+    "Created: / 15-03-2012 / 10:35:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+uncheckedPeek
+    "An unchecked version of peek that throws an error if we try to peek over the end of the stream, even faster than #peek."
+
+    ^ self peek
+
+    "Modified: / 14-03-2012 / 22:46:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!Scanner::Token methodsFor:'accessing'!
+
+endPosition
+    ^ endPosition
+!
+
+endPosition:something
+    endPosition := something.
+!
+
+startPosition
+    ^ startPosition
+!
+
+startPosition:something
+    startPosition := something.
+!
+
+type
+    ^ type
+!
+
+type:something
+    type := something.
+!
+
+value
+    ^ value
+!
+
+value:something
+    value := something.
+! !
+
+!Scanner::Token methodsFor:'printing & storing'!
+
+printOn:aStream
+    "append a printed representation if the receiver to the argument, aStream"
+
+    super printOn:aStream.
+    aStream nextPutAll:'type: '.
+    type printOn:aStream.
+    aStream nextPutAll:'value: '.
+    value printOn:aStream.
+    aStream nextPutAll:'startPosition: '.
+    startPosition printOn:aStream.
+    aStream nextPutAll:'endPosition: '.
+    endPosition printOn:aStream.
+! !
+
+!Scanner class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/Dart__ScannerBase.st	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,804 @@
+"
+ COPYRIGHT (c) 2003 by Claus Gittinger
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+"{ Package: 'jv:dart/compiler' }"
+
+"{ NameSpace: Dart }"
+
+Object subclass:#ScannerBase
+	instanceVariableNames:'typeArray actionArray source lineNr tokenType tokenStartPosition
+		tokenEndPosition tokenLineNr numberRadix numberScale hereChar
+		peekChar peekChar2 requestor saveComments currentComments
+		tokenValue scaledMantissaValue parserFlags'
+	classVariableNames:'Warnings'
+	poolDictionaries:''
+	category:'Languages-Dart-Parser'
+!
+
+ScannerBase class instanceVariableNames:'TypeArray ActionArray KeywordTable'
+
+"
+ No other class instance variables are inherited by this class.
+"
+!
+
+!ScannerBase class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2003 by Claus Gittinger
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!ScannerBase class methodsFor:'initialization'!
+
+initialize
+    "initialize the classes defaults. Typically, these are changed
+     later in the 'private.rc' file."
+
+"/    ScannerError isLoaded ifFalse:[
+"/        ScannerError autoload
+"/    ].
+"/    EmptySourceNotification notifierString:'empty source given to evaluate'.
+
+    Warnings := false.
+
+    "ActionArray := nil.
+     TypeArray := nil.
+     self initialize
+    "
+
+    "Modified: / 15-03-2012 / 00:05:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+setupActions
+    "initialize the scanners tables - these are used to dispatch
+     into scanner methods as characters are read"
+
+    self subclassResponsibility
+
+"/    |block|
+"/
+"/    ActionArray := Array new:256.
+"/    TypeArray := Array new:256.
+"/
+"/    block := [:s :char | s nextNumber].
+"/    ($0 asciiValue) to:($9 asciiValue) do:[:index |
+"/        ActionArray at:index put:block
+"/    ].
+"/
+"/    block := [:s :char | s nextIdentifier].
+"/    ($a asciiValue) to:($z asciiValue) do:[:index |
+"/        ActionArray at:index put:block
+"/    ].
+"/    ($A asciiValue) to:($Z asciiValue) do:[:index |
+"/        ActionArray at:index put:block
+"/    ].
+"/    ActionArray at:$_ asciiValue put:block
+"/
+! !
+
+!ScannerBase class methodsFor:'instance creation'!
+
+for:aStringOrStream
+    "create & return a new scanner reading from aStringOrStream"
+
+    ^ (super new) initializeFor:aStringOrStream
+
+    "Modified: 23.5.1997 / 12:08:42 / cg"
+!
+
+new
+    "create & return a new scanner"
+
+    ^ self basicNew initialize.
+
+    "Modified: / 23.5.1997 / 12:08:42 / cg"
+    "Created: / 26.5.1999 / 12:02:16 / stefan"
+! !
+
+!ScannerBase class methodsFor:'Signal constants'!
+
+emptySourceNotificationSignal
+    ^ EmptySourceNotification
+
+    "Created: / 16.5.1998 / 15:55:14 / cg"
+!
+
+errorSignal
+    ^ ScannerError
+
+    "Created: / 16.5.1998 / 15:55:14 / cg"
+!
+
+scannerErrorSignal
+    ^ ScannerError
+
+    "Created: / 16.5.1998 / 15:55:14 / cg"
+!
+
+warningSignal
+    ^ ScannerWarning
+
+    "Created: / 16.5.1998 / 15:55:14 / cg"
+! !
+
+!ScannerBase class methodsFor:'defaults'!
+
+warnings
+    "return true, if any warnings are to be shown"
+
+    ^ Warnings
+!
+
+warnings:aBoolean
+    "this allows turning on/off all warnings; the default is on.
+     You can turn off warnings in your 'private.rc' file with
+	 Compiler warnings:false
+    "
+
+    Warnings := aBoolean
+
+    "Modified: 23.5.1997 / 12:03:05 / cg"
+! !
+
+!ScannerBase class methodsFor:'private accessing'!
+
+actionArray
+    ^ ActionArray
+!
+
+keywordTable
+    ^ KeywordTable
+!
+
+typeArray
+    ^ TypeArray
+! !
+
+!ScannerBase class methodsFor:'utility scanning'!
+
+scanNumberFrom:aStream
+    "utility - helper for Number>>readSmalltalkSyntaxFrom:"
+
+    ^ self basicNew scanNumberFrom:aStream
+
+    "
+     |s|
+
+     s := '12345abcd' readStream.
+     Transcript showCR:(self scanNumberFrom:s).
+     Transcript showCR:(s upToEnd).
+    "
+    "
+     |s|
+
+     s := '16rffffxabcd' readStream.
+     Transcript showCR:(self scanNumberFrom:s).
+     Transcript showCR:(s upToEnd).
+    "
+    "
+     |s|
+
+     s := '1.2345abcd' readStream.
+     Transcript showCR:(self scanNumberFrom:s).
+     Transcript showCR:(s upToEnd).
+    "
+    "
+     |s|
+
+     s := '1.abcd' readStream.
+     Transcript showCR:(self scanNumberFrom:s).
+     Transcript showCR:(s upToEnd).
+    "
+
+    "Modified: / 18.6.1998 / 23:10:39 / cg"
+! !
+
+!ScannerBase methodsFor:'Compatibility - ST80'!
+
+endOfLastToken
+    "return the position of the token which was just read.
+     This method was required by some PD program.
+     It is not maintained and may be removed without notice."
+
+    ^ source position
+
+    "Modified: 23.5.1997 / 12:14:27 / cg"
+!
+
+scan:aStringOrStream
+    "initialize the scanner: set the source-stream and
+     preread the first token"
+
+    self initializeFor:aStringOrStream.
+    self nextToken
+
+    "Created: / 30.10.1997 / 16:59:39 / cg"
+!
+
+scanToken
+    "read the next token from my input stream"
+
+    ^ self nextToken
+
+    "Created: / 30.10.1997 / 17:00:16 / cg"
+!
+
+scanTokens:aStringOrStream
+    "return a collection of symbolic tokens from the passed input"
+
+    |tokens|
+
+    self initializeFor:aStringOrStream.
+    tokens := OrderedCollection new.
+    self nextToken.
+    [tokenValue notNil] whileTrue:[
+	tokens add:tokenValue.
+	self nextToken
+    ].
+    ^ tokens
+
+    "
+     Scanner new
+	scanTokens:'Boolean subclass:#True
+				instanceVariableNames:''''
+				classVariableNames:''''
+				poolDictionaries:''''
+				category:''Kernel-Objects''
+	'
+    "
+
+    "Modified: 20.6.1997 / 18:22:58 / cg"
+! !
+
+!ScannerBase methodsFor:'accessing'!
+
+actionArray
+    ^ actionArray
+!
+
+actionArray:something
+    actionArray := something.
+!
+
+comments
+    "if saveComments is on:
+      returns the collection of collected comments (so far)
+      clears the internal collection for the next access"
+
+    |ret|
+
+    ret := currentComments ? #().
+    currentComments := nil.
+    ^ ret
+
+    "Created: 20.4.1996 / 20:07:01 / cg"
+    "Modified: 23.5.1997 / 12:14:45 / cg"
+!
+
+lineNumber
+    "the current line number (in the stream)"
+
+    ^ lineNr
+!
+
+newSourceStream:aStream
+    source := aStream.
+    self nextToken.
+
+    "Created: / 29.10.1998 / 21:59:33 / cg"
+!
+
+numberRadix
+    "the radix of the previously scanned number"
+
+    ^ numberRadix
+!
+
+parserFlags:something
+    parserFlags := something.
+!
+
+saveComments:aBoolean
+    "toggle to turn on/off comment remembering"
+
+    saveComments := aBoolean
+
+    "Created: 20.4.1996 / 20:03:56 / cg"
+    "Modified: 23.5.1997 / 12:14:49 / cg"
+!
+
+sourceStream
+    ^ source
+
+    "Created: 20.4.1996 / 19:59:58 / cg"
+!
+
+token
+    "the previously scanned token"
+
+    "/ generated lazily ...
+    self halt.
+!
+
+tokenEndPosition
+    "the previously scanned tokens last character position"
+
+    ^ tokenEndPosition
+!
+
+tokenLineNumber
+    "the previously scanned tokens line number"
+
+    ^ tokenLineNr
+!
+
+tokenStartPosition
+    "the previously scanned tokens first character position"
+
+    ^ tokenStartPosition
+!
+
+tokenType
+    "the type (symbolic) of the previously scanned token"
+
+    ^ tokenType
+!
+
+tokenValue
+    "the value (string or number) of the previously scanned token"
+
+    ^ tokenValue
+!
+
+typeArray
+    ^ typeArray
+!
+
+typeArray:something
+    typeArray := something.
+! !
+
+!ScannerBase methodsFor:'error handling'!
+
+correctableError:message position:pos1 to:pos2
+    "report an error which can be corrected by compiler -
+     return non-false, if correction is wanted (there is more than
+     true/false returned here)"
+
+    |correctIt|
+
+    requestor isNil ifTrue:[
+"/        self showErrorMessage:message position:pos1.
+	correctIt := false
+    ] ifFalse:[
+	correctIt := requestor correctableError:message position:pos1 to:pos2 from:self
+    ].
+    ^ correctIt
+
+    "Created: / 13.5.1998 / 16:45:56 / cg"
+!
+
+errorMessagePrefix
+    ^ 'Error:'
+!
+
+ignoreWarnings
+    ^ Warnings == false
+
+    "Modified: / 14-03-2012 / 22:36:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+lastTokenLineNumber
+    "return the line number of the token which was just read."
+
+    ^ tokenLineNr
+
+    "Created: 8.11.1996 / 18:46:36 / cg"
+    "Modified: 23.5.1997 / 12:16:12 / cg"
+!
+
+notifyError:aMessage position:position to:endPos
+    "notify requestor of an error - if there is no requestor
+     put it on the transcript. Requestor is typically the CodeView
+     in which the accept/doIt was triggered, or the PositionableStream
+     which does the fileIn. The requestor may decide how to highlight the
+     error (and/or to abort the compile).
+     Return the result passed back by the requestor."
+
+    requestor isNil ifTrue:[
+	self showErrorMessage:aMessage position:position.
+	^ false
+    ].
+    ^ requestor error:aMessage position:position to:endPos from:self
+!
+
+notifyWarning:aMessage position:position to:endPos
+    "notify requestor of an warning - if there is no requestor
+     put it on the transcript.
+     Return the result passed back by the requestor."
+
+    |warn|
+
+    self ignoreWarnings ifFalse:[
+	requestor isNil ifTrue:[
+	    warn := ScannerWarning new.
+	    warn startPosition:position.
+	    warn endPosition:endPos.
+	    warn lineNumber:tokenLineNr.
+	    warn errorString:((self warningMessagePrefix) , ' ' , aMessage).
+	    warn raiseRequest.
+	    ^ false
+	].
+	^ requestor warning:aMessage position:position to:endPos from:self
+    ].
+    ^ false
+!
+
+parseError:aMessage
+    "report an error"
+
+    ^ self parseError:aMessage position:tokenStartPosition to:nil
+
+    "Created: / 13.5.1998 / 16:45:13 / cg"
+!
+
+parseError:aMessage position:position
+    "report an error"
+
+    ^ self parseError:aMessage position:position to:nil
+
+    "Created: / 13.5.1998 / 16:45:05 / cg"
+!
+
+parseError:aMessage position:position to:endPos
+    "report an error"
+
+    |m|
+
+    m := (self errorMessagePrefix) , ' ' , (aMessage ? '???').
+    self notifyError:m position:position to:endPos.
+    ^ false
+
+    "Created: / 13.5.1998 / 16:44:55 / cg"
+    "Modified: / 28.9.1998 / 19:29:27 / cg"
+!
+
+showErrorMessage:aMessage position:pos
+    "show an errormessage on the Transcript"
+
+    Transcript showCR:(pos printString , ' [line: ' , tokenLineNr printString , '] ' , aMessage)
+!
+
+syntaxError:aMessage
+    "a syntax error happened - position is not known"
+
+    ^ self syntaxError:aMessage position:tokenStartPosition
+!
+
+syntaxError:aMessage position:position
+    "a syntax error happened - only start position is known"
+
+    ^ self syntaxError:aMessage position:position to:nil
+!
+
+syntaxError:aMessage position:position to:endPos
+    "a syntax error happened"
+
+    |err|
+
+    err := ScannerError new.
+    err startPosition:tokenStartPosition.
+    err endPosition:tokenEndPosition.
+    err lineNumber:tokenLineNr.
+    err errorString:((self errorMessagePrefix) , ' ' , aMessage).
+    err raiseRequest
+!
+
+warning:aMessage
+    "a warning - position is not known"
+
+    ^ self warning:aMessage position:tokenStartPosition
+!
+
+warning:aMessage position:position
+    "a warning - only start position is known"
+
+    ^ self warning:aMessage position:position to:nil
+!
+
+warning:aMessage position:position to:endPos
+    "a warning"
+
+    ^ self notifyWarning:((self warningMessagePrefix) , ' ' , aMessage) position:position to:endPos
+!
+
+warningMessagePrefix
+    ^ 'Warning:'
+! !
+
+!ScannerBase methodsFor:'general scanning'!
+
+scanPositionsFor:aTokenString inString:aSourceString
+    "scan aSourceString for occurrances of aTokenString.
+     Return a collection of start positions.
+     Added for VW compatibility (to support syntax-highlight)."
+
+    |searchType searchToken positions t|
+
+    "
+     first, look what kind of token we have to search for
+    "
+    self initializeFor:(ReadStream on:aTokenString).
+    self nextToken.
+    searchType := tokenType.
+    searchToken := tokenValue.
+
+    "
+     start the real work ...
+    "
+    self initializeFor:(ReadStream on:aSourceString).
+    positions := OrderedCollection new.
+
+    [(t := self nextToken) ~~ #EOF] whileTrue:[
+	searchType == t ifTrue:[
+	    (searchToken isNil or:[tokenValue = searchToken]) ifTrue:[
+		positions add:tokenStartPosition.
+	    ]
+	]
+    ].
+
+    ^ positions
+
+    "
+     Scanner new scanPositionsFor:'hello' inString:'foo bar hello baz hello helloWorld'
+     Scanner new scanPositionsFor:'3.14' inString:'foo 3.145 bar hello 3.14 baz hello 3.14 ''3.14'''
+     Scanner new scanPositionsFor:'''3.14''' inString:'foo 3.145 bar hello 3.14 baz hello 3.14 ''3.14'' aaa'
+     Scanner new scanPositionsFor:'16' inString:'foo 16 bar hello 16r10 baz hello 2r10000'
+    "
+! !
+
+!ScannerBase methodsFor:'initialization'!
+
+initialize
+    "initialize the scanner"
+
+    "/actionArray notNil ifTrue:[ self halt ].
+
+    saveComments := false.
+    parserFlags := ParserFlags new.
+
+    (actionArray := self class actionArray) isNil ifTrue:[
+        self class setupActions.
+        actionArray := self class actionArray
+    ].
+    typeArray := self class typeArray.
+
+    "Modified: / 14-03-2012 / 22:35:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+initializeFor:aStringOrStream
+    "initialize the new scanner & prepare for reading from aStringOrStream"
+
+    self initialize.
+    self source:aStringOrStream.
+!
+
+source:aStringOrStream
+    "prepare for reading from aStringOrStream"
+
+    tokenStartPosition := 1.
+    tokenLineNr := lineNr := 1.
+    currentComments := nil.
+
+    aStringOrStream isStream ifFalse:[
+	source := ReadStream on:aStringOrStream
+    ] ifTrue:[
+	source := aStringOrStream.
+    ].
+
+    "Modified: / 26.5.1999 / 12:02:16 / stefan"
+! !
+
+!ScannerBase methodsFor:'private'!
+
+addComment:comment
+    saveComments ifTrue:[
+	currentComments isNil ifTrue:[
+	    currentComments := OrderedCollection with:comment
+	] ifFalse:[
+	    currentComments add:comment
+	]
+    ].
+!
+
+backupPosition
+    "if reading from a stream, at the end we might have read
+     one token too many"
+
+    (tokenType == #EOF) ifFalse:[
+	source position:tokenStartPosition
+    ]
+!
+
+beginComment
+    ^ self
+!
+
+requestor:anObject
+    "set the requestor to be notified about errors"
+
+    requestor := anObject
+! !
+
+!ScannerBase methodsFor:'reading next token'!
+
+atEnd
+    "true if at the end"
+
+    ^ tokenType == #EOF.
+
+    "Created: / 30-04-2011 / 11:24:13 / cg"
+!
+
+isCommentCharacter:aCharacter
+    self subclassResponsibility
+!
+
+nextSingleCharacterToken:aCharacter
+    "return a character token"
+
+    tokenEndPosition := tokenStartPosition.
+    tokenType := tokenValue := aCharacter.
+    hereChar notNil ifTrue:[source next].
+    ^ tokenType
+
+    "Modified: / 13.5.1998 / 15:10:23 / cg"
+!
+
+nextToken
+    "scan the next token from the source-stream;
+     as a side effect, leave info in:
+        tokenType          - a symbol describing the kind of token
+        token              - its value as string or number
+        tokenStartPosition - the tokens first characters position in the input stream
+        tokenEndPosition   - the tokens last characters position in the input stream
+        tokenLineNr        - the tokens first characters lineNumber in the input stream
+     returns the tokenType.
+    "
+
+    |skipping actionBlock v ch tok|
+
+    [true] whileTrue:[
+        peekChar notNil ifTrue:[
+            "/ kludge - should be called peekSym.
+            "/ used when xlating Foo.Bar into Foo::Bar
+            peekChar isSymbol ifTrue:[
+                tokenValue := nil.
+                tokenType := peekChar.
+                peekChar := nil.
+                ^ tokenType
+            ].
+
+            peekChar isSeparator ifTrue:[
+                peekChar == (Character cr) ifTrue:[
+                    lineNr := lineNr + 1.
+                ].
+                peekChar := peekChar2.
+                peekChar2 := nil.
+            ].
+        ].
+        peekChar notNil ifTrue:[
+            ch := peekChar.
+            peekChar := peekChar2.
+            peekChar2 := nil.
+            hereChar := nil.
+            tokenStartPosition := source position - 1.
+        ] ifFalse:[
+            skipping := true.
+            [skipping] whileTrue:[
+                hereChar := source skipSeparatorsExceptCR.
+                hereChar == (Character cr) ifTrue:[
+                    lineNr := lineNr + 1.
+                    source next.
+                ] ifFalse:[
+                    hereChar == (Character return) ifTrue:[
+                        source next.
+                    ] ifFalse:[
+                        (self isCommentCharacter:hereChar) ifTrue:[
+                            "start of a comment"
+
+                            self skipComment.
+                            hereChar := source peekOrNil.
+                        ] ifFalse:[
+                            skipping := false
+                        ]
+                    ]
+                ]
+            ].
+            hereChar isNil ifTrue:[
+                tokenValue := nil.
+                tokenType := #EOF.
+                ^ tokenType
+            ].
+            ch := hereChar.
+            tokenStartPosition := source position.
+        ].
+        tokenLineNr := lineNr.
+
+        (v := ch asciiValue) == 0 ifTrue:[
+            v := Character space codePoint
+        ].
+        actionBlock := actionArray at:v.
+        actionBlock notNil ifTrue:[
+            tok := actionBlock value:self value:ch.
+            tok notNil ifTrue:[
+                ^ tok
+            ].
+        ] ifFalse:[
+            self syntaxError:('invalid character: ''' , ch asString , ''' ',
+                              '(' , v printString , ')')
+                    position:tokenStartPosition to:tokenStartPosition.
+            source next.
+            tokenValue := nil.
+            tokenType := #Error.
+            ^ #Error
+        ]
+    ].
+!
+
+skipComment
+    self subclassResponsibility
+! !
+
+!ScannerBase methodsFor:'reading next token - private'!
+
+nextMantissa:radix
+    "read the mantissa of a radix number.
+     Return post-decimal value (i.e. 0.xxxx); leave number of post-decimal
+     digits in numberScale; scaled post-decimal value in scaledMantissaValue (xxx)."
+
+    |nextChar value factor|
+
+    value := scaledMantissaValue := 0.
+    factor := 1.0 / radix.
+    nextChar := source peekOrNil.
+    numberScale := 0.
+
+    [(nextChar notNil and:[nextChar isDigitRadix:radix])] whileTrue:[
+	scaledMantissaValue := (scaledMantissaValue * radix) + (nextChar digitValue).
+	value := value + (nextChar digitValue * factor).
+	factor := factor / radix.
+	numberScale := numberScale + 1.
+	nextChar := source nextPeek
+    ].
+    ^ value
+
+    "Modified: / 5.3.1998 / 02:54:11 / cg"
+! !
+
+!ScannerBase class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
+ScannerBase initialize!
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/Make.proto	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,125 @@
+# $Header$
+#
+# DO NOT EDIT
+# automagically generated from the projectDefinition: jv_dart_compiler.
+#
+# Warning: once you modify this file, do not rerun
+# stmkmp or projectDefinition-build again - otherwise, your changes are lost.
+#
+# The Makefile as generated by this Make.proto supports the following targets:
+#    make         - compile all st-files to a classLib
+#    make clean   - clean all temp files
+#    make clobber - clean all
+#
+# This file contains definitions for Unix based platforms.
+# It shares common definitions with the win32-make in Make.spec.
+
+#
+# position (of this package) in directory hierarchy:
+# (must point to ST/X top directory, for tools and includes)
+TOP=../../../stx
+INCLUDE_TOP=$(TOP)/..
+
+# subdirectories where targets are to be made:
+SUBDIRS=
+
+
+# subdirectories where Makefiles are to be made:
+# (only define if different from SUBDIRS)
+# ALLSUBDIRS=
+
+REQUIRED_SUPPORT_DIRS=
+
+# if your embedded C code requires any system includes,
+# add the path(es) here:,
+# ********** OPTIONAL: MODIFY the next lines ***
+# LOCALINCLUDES=-Ifoo -Ibar
+LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/libbasic -I$(INCLUDE_TOP)/stx/goodies/petitparser
+
+
+# if you need any additional defines for embedded C code,
+# add them here:,
+# ********** OPTIONAL: MODIFY the next lines ***
+# LOCALDEFINES=-Dfoo -Dbar -DDEBUG
+LOCALDEFINES=
+
+LIBNAME=libjv_dart_compiler
+STCLOCALOPT='-package=$(PACKAGE)' -I. $(LOCALINCLUDES) $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES) -headerDir=.  -varPrefix=$(LIBNAME)
+
+
+# ********** OPTIONAL: MODIFY the next line ***
+# additional C-libraries that should be pre-linked with the class-objects
+LD_OBJ_LIBS=
+LOCAL_SHARED_LIBS=
+
+
+# ********** OPTIONAL: MODIFY the next line ***
+# additional C targets or libraries should be added below
+LOCAL_EXTRA_TARGETS=
+
+OBJS= $(COMMON_OBJS) $(UNIX_OBJS)
+
+
+
+all:: preMake classLibRule postMake
+
+pre_objs::  
+
+
+
+
+
+
+# Enforce recompilation of package definition class if Mercurial working
+# copy state changes. Together with --guessVersion it ensures that package
+# definition class always contains correct binary revision string.
+ifneq (**NOHG**, $(shell hg root 2> /dev/null || echo -n '**NOHG**'))
+jv_dart_compiler.$(O): $(shell hg root)/.hg/dirstate
+endif
+
+
+
+
+# run default testsuite for this package
+test: $(TOP)/goodies/builder/reports
+	$(MAKE) -C $(TOP)/goodies/builder/reports
+	$(TOP)/goodies/builder/reports/report-runner.sh -D . -r Builder::TestReport -p $(PACKAGE)
+
+
+
+# add more install actions here
+install::
+
+# add more install actions for aux-files (resources) here
+installAux::
+
+# add more preMake actions here
+preMake::
+
+# add more postMake actions here
+postMake:: cleanjunk
+
+prereq: $(REQUIRED_SUPPORT_DIRS)
+	cd $(TOP)/libbasic && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+	cd $(TOP)/librun && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
+
+
+
+cleanjunk::
+	-rm -f *.s *.s2
+
+clean::
+	-rm -f *.o *.H
+
+clobber:: clean
+	-rm -f *.so *.dll
+
+
+# BEGINMAKEDEPEND --- do not remove this line; make depend needs it
+$(OUTDIR)Dart__Parser.$(O) Dart__Parser.$(H): Dart__Parser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPCompositeParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPDelegateParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)Dart__ScannerBase.$(O) Dart__ScannerBase.$(H): Dart__ScannerBase.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)jv_dart_compiler.$(O) jv_dart_compiler.$(H): jv_dart_compiler.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)Dart__Scanner.$(O) Dart__Scanner.$(H): Dart__Scanner.st $(INCLUDE_TOP)/jv/dart/compiler/Dart__ScannerBase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+
+# ENDMAKEDEPEND --- do not remove this line
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/Make.spec	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,68 @@
+# $Header$
+#
+# DO NOT EDIT
+# automagically generated from the projectDefinition: jv_dart_compiler.
+#
+# Warning: once you modify this file, do not rerun
+# stmkmp or projectDefinition-build again - otherwise, your changes are lost.
+#
+# This file contains specifications which are common to all platforms.
+#
+
+# Do NOT CHANGE THESE DEFINITIONS
+# (otherwise, ST/X will have a hard time to find out the packages location from its packageID,
+#  to find the source code of a class and to find the library for a package)
+MODULE=jv
+MODULE_DIR=dart/compiler
+PACKAGE=$(MODULE):$(MODULE_DIR)
+
+
+# Argument(s) to the stc compiler (stc --usage).
+#  -headerDir=. : create header files locally
+#                (if removed, they will be created as common
+#  -Pxxx       : defines the package
+#  -Zxxx       : a prefix for variables within the classLib
+#  -Dxxx       : defines passed to to CC for inline C-code
+#  -Ixxx       : include path passed to CC for inline C-code
+#  +optspace   : optimized for space
+#  +optspace2  : optimized more for space
+#  +optspace3  : optimized even more for space
+#  +optinline  : generate inline code for some ST constructs
+#  +inlineNew  : additionally inline new
+#  +inlineMath : additionally inline some floatPnt math stuff
+#
+# ********** OPTIONAL: MODIFY the next line(s) ***
+# STCLOCALOPTIMIZATIONS=+optinline +inlineNew
+# STCLOCALOPTIMIZATIONS=+optspace3
+STCLOCALOPTIMIZATIONS=+optspace3
+
+
+# Argument(s) to the stc compiler (stc --usage).
+#  -warn            : no warnings
+#  -warnNonStandard : no warnings about ST/X extensions
+#  -warnEOLComments : no warnings about EOL comment extension
+#  -warnPrivacy     : no warnings about privateClass extension
+#
+# ********** OPTIONAL: MODIFY the next line(s) ***
+# STCWARNINGS=-warn
+# STCWARNINGS=-warnNonStandard
+# STCWARNINGS=-warnEOLComments
+STCWARNINGS=-warnNonStandard
+
+COMMON_CLASSES= \
+	jv_dart_compiler \
+	Dart::ScannerBase \
+	Dart::Parser \
+	Dart::Scanner \
+
+
+
+
+COMMON_OBJS= \
+    $(OUTDIR)jv_dart_compiler.$(O) \
+    $(OUTDIR)Dart__ScannerBase.$(O) \
+    $(OUTDIR)Dart__Parser.$(O) \
+    $(OUTDIR)Dart__Scanner.$(O) \
+
+
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/Makefile	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,19 @@
+#
+# DO NOT EDIT
+#
+# make uses this file (Makefile) only, if there is no
+# file named "makefile" (lower-case m) in the same directory.
+# My only task is to generate the real makefile and call make again.
+# Thereafter, I am no longer used and needed.
+#
+
+.PHONY: run
+
+run: makefile
+	$(MAKE) -f makefile
+
+#only needed for the definition of $(TOP)
+include Make.proto
+
+makefile:
+	$(TOP)/rules/stmkmf
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/abbrev.stc	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,7 @@
+# automagically generated by the project definition
+# this file is needed for stc to be able to compile modules independently.
+# it provides information about a classes filename, category and especially namespace.
+jv_dart_compiler jv_dart_compiler jv:dart/compiler '* Projects & Packages *' 3
+Dart::ScannerBase Dart__ScannerBase jv:dart/compiler 'Languages-Dart-Parser' 3
+Dart::Parser Dart__Parser jv:dart/compiler 'Languages-Dart-Parser' 0
+Dart::Scanner Dart__Scanner jv:dart/compiler 'Languages-Dart-Parser' 3
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/bc.mak	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,80 @@
+# $Header$
+#
+# DO NOT EDIT
+# automagically generated from the projectDefinition: jv_dart_compiler.
+#
+# Warning: once you modify this file, do not rerun
+# stmkmp or projectDefinition-build again - otherwise, your changes are lost.
+#
+# Notice, that the name bc.mak is historical (from times, when only borland c was supported).
+# This file contains make rules for the win32 platform using either borland-bcc or visual-c.
+# It shares common definitions with the unix-make in Make.spec.
+# The bc.mak supports the following targets:
+#    bmake         - compile all st-files to a classLib (dll)
+#    bmake clean   - clean all temp files
+#    bmake clobber - clean all
+#
+# Historic Note:
+#  this used to contain only rules to make with borland
+#    (called via bmake, by "make.exe -f bc.mak")
+#  this has changed; it is now also possible to build using microsoft visual c
+#    (called via vcmake, by "make.exe -f bc.mak -DUSEVC")
+#
+TOP=..\..\..\stx
+INCLUDE_TOP=$(TOP)\..
+
+
+
+!INCLUDE $(TOP)\rules\stdHeader_bc
+
+!INCLUDE Make.spec
+
+LIBNAME=libjv_dart_compiler
+RESFILES=compiler.res
+
+
+
+LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\libbasic -I$(INCLUDE_TOP)\stx\goodies\petitparser
+LOCALDEFINES=
+
+STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES)  -varPrefix=$(LIBNAME)
+LOCALLIBS=
+
+OBJS= $(COMMON_OBJS) $(WIN32_OBJS)
+
+ALL::  classLibRule
+
+classLibRule: $(OUTDIR) $(OUTDIR)$(LIBNAME).dll
+
+!INCLUDE $(TOP)\rules\stdRules_bc
+
+# build all prerequisite packages for this package
+prereq:
+	pushd ..\..\..\stx\libbasic & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+	pushd ..\..\..\stx\librun & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+
+
+
+
+
+
+test: $(TOP)\goodies\builder\reports\NUL
+	pushd $(TOP)\goodies\builder\reports & $(MAKE_BAT)
+	$(TOP)\goodies\builder\reports\report-runner.bat -D . -r Builder::TestReport -p $(PACKAGE)
+
+# BEGINMAKEDEPEND --- do not remove this line; make depend needs it
+$(OUTDIR)Dart__Parser.$(O) Dart__Parser.$(H): Dart__Parser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPCompositeParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPDelegateParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)Dart__ScannerBase.$(O) Dart__ScannerBase.$(H): Dart__ScannerBase.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)jv_dart_compiler.$(O) jv_dart_compiler.$(H): jv_dart_compiler.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)Dart__Scanner.$(O) Dart__Scanner.$(H): Dart__Scanner.st $(INCLUDE_TOP)\jv\dart\compiler\Dart__ScannerBase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+
+# ENDMAKEDEPEND --- do not remove this line
+
+# **Must be at end**
+
+# Enforce recompilation of package definition class if Mercurial working
+# copy state changes. Together with --guessVersion it ensures that package
+# definition class always contains correct binary revision string.
+!IFDEF HGROOT
+$(OUTDIR)jv_dart_compiler.$(O): $(HGROOT)\.hg\dirstate
+!ENDIF
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/bmake.bat	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,12 @@
+@REM -------
+@REM make using Borland bcc32
+@REM type bmake, and wait...
+@REM do not edit - automatically generated from ProjectDefinition
+@REM -------
+@SET DEFINES=
+@REM Kludge got Mercurial, cannot be implemented in Borland make
+@FOR /F "tokens=*" %%i in ('hg root') do SET HGROOT=%%i
+@IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
+make.exe -N -f bc.mak  %DEFINES% %*
+
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/compiler.rc	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,37 @@
+//
+// DO NOT EDIT
+// automagically generated from the projectDefinition: jv_dart_compiler.
+//
+VS_VERSION_INFO VERSIONINFO
+  FILEVERSION     6,2,32767,32767
+  PRODUCTVERSION  6,2,3,0
+#if (__BORLANDC__)
+  FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
+  FILEFLAGS       VS_FF_PRERELEASE | VS_FF_SPECIALBUILD
+  FILEOS          VOS_NT_WINDOWS32
+  FILETYPE        VFT_DLL
+  FILESUBTYPE     VS_USER_DEFINED
+#endif
+
+BEGIN
+  BLOCK "StringFileInfo"
+  BEGIN
+    BLOCK "040904E4"
+    BEGIN
+      VALUE "CompanyName", "My Company\0"
+      VALUE "FileDescription", "Class Library (LIB)\0"
+      VALUE "FileVersion", "6.2.32767.32767\0"
+      VALUE "InternalName", "jv:dart/compiler\0"
+      VALUE "LegalCopyright", "My CopyRight or CopyLeft\0"
+      VALUE "ProductName", "ProductName\0"
+      VALUE "ProductVersion", "6.2.3.0\0"
+      VALUE "ProductDate", "Thu, 10 Jan 2013 13:20:39 GMT\0"
+    END
+
+  END
+
+  BLOCK "VarFileInfo"
+  BEGIN                               //  Language   |    Translation
+    VALUE "Translation", 0x409, 0x4E4 // U.S. English, Windows Multilingual
+  END
+END
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/jv_dart_compiler.st	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,106 @@
+"{ Package: 'jv:dart/compiler' }"
+
+LibraryDefinition subclass:#jv_dart_compiler
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'* Projects & Packages *'
+!
+
+
+!jv_dart_compiler class methodsFor:'description'!
+
+excludedFromPreRequisites
+    "list all packages which should be ignored in the automatic
+     preRequisites scan. See #preRequisites for more."
+
+    ^ #(
+    )
+!
+
+preRequisites
+    "list all required packages.
+     This list can be maintained manually or (better) generated and
+     updated by scanning the superclass hierarchies and looking for
+     global variable accesses. (the browser has a menu function for that)
+     Howevery, often too much is found, and you may want to explicitely
+     exclude individual packages in the #excludedFromPrerequisites method."
+
+    ^ #(
+        #'stx:libbasic'    "LibraryDefinition - superclass of jv_dart "
+    )
+! !
+
+!jv_dart_compiler class methodsFor:'description - contents'!
+
+classNamesAndAttributes
+    "lists the classes which are to be included in the project.
+     Each entry in the list may be: a single class-name (symbol),
+     or an array-literal consisting of class name and attributes.
+     Attributes are: #autoload or #<os> where os is one of win32, unix,..."
+
+    ^ #(
+        "<className> or (<className> attributes...) in load order"
+        #'jv_dart_compiler'
+        #'Dart::ScannerBase'
+        #'Dart::Parser'
+        #'Dart::Scanner'
+    )
+
+    "Modified: / 10-01-2013 / 13:15:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+extensionMethodNames
+    "lists the extension methods which are to be included in the project.
+     Entries are 2-element array literals, consisting of class-name and selector."
+
+    ^ #(
+    )
+! !
+
+!jv_dart_compiler class methodsFor:'description - project information'!
+
+applicationIconFileName
+    "Return the name (without suffix) of an icon-file (the app's icon); will be included in the rc-resource file"
+
+    ^ nil
+    "/ ^ self applicationName
+!
+
+companyName
+    "Return a companyname which will appear in <lib>.rc"
+
+    ^ 'My Company'
+!
+
+description
+    "Return a description string which will appear in vc.def / bc.def"
+
+    ^ 'Class Library'
+!
+
+legalCopyright
+    "Return a copyright string which will appear in <lib>.rc"
+
+    ^ 'My CopyRight or CopyLeft'
+!
+
+productInstallDirBaseName
+    "Returns a default installDir which will appear in <app>.nsi.
+     This is usually not the one you want to keep"
+
+    ^ (self package asCollectionOfSubstringsSeparatedByAny:':/') last
+!
+
+productName
+    "Return a product name which will appear in <lib>.rc"
+
+    ^ 'ProductName'
+! !
+
+!jv_dart_compiler class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/lccmake.bat	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,8 @@
+@REM -------
+@REM make using lcc compiler
+@REM type lccmake, and wait...
+@REM do not edit - automatically generated from ProjectDefinition
+@REM -------
+make.exe -N -f bc.mak -DUSELCC=1 %*
+
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/libInit.cc	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,37 @@
+/*
+ * $Header$
+ *
+ * DO NOT EDIT
+ * automagically generated from the projectDefinition: jv_dart_compiler.
+ */
+#define __INDIRECTVMINITCALLS__
+#include <stc.h>
+
+#ifdef WIN32
+# pragma codeseg INITCODE "INITCODE"
+#endif
+
+#if defined(INIT_TEXT_SECTION) || defined(DLL_EXPORT)
+DLL_EXPORT void _libjv_dart_compiler_Init() INIT_TEXT_SECTION;
+// DLL_EXPORT void _libjv_dart_compiler_InitDefinition() INIT_TEXT_SECTION;
+#endif
+
+// void _libjv_dart_compiler_InitDefinition(pass, __pRT__, snd)
+// OBJ snd; struct __vmData__ *__pRT__; {
+// __BEGIN_PACKAGE2__("libjv_dart_compiler__DFN", _libjv_dart_compiler_InitDefinition, "jv:dart/compiler");
+// _jv_137dart_137compiler_Init(pass,__pRT__,snd);
+
+// __END_PACKAGE__();
+// }
+
+void _libjv_dart_compiler_Init(pass, __pRT__, snd)
+OBJ snd; struct __vmData__ *__pRT__; {
+__BEGIN_PACKAGE2__("libjv_dart_compiler", _libjv_dart_compiler_Init, "jv:dart/compiler");
+_Dart__Parser_Init(pass,__pRT__,snd);
+_Dart__ScannerBase_Init(pass,__pRT__,snd);
+_jv_137dart_137compiler_Init(pass,__pRT__,snd);
+_Dart__Scanner_Init(pass,__pRT__,snd);
+
+
+__END_PACKAGE__();
+}
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/mingwmake.bat	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,12 @@
+@REM -------
+@REM make using mingw gnu compiler
+@REM type mingwmake, and wait...
+@REM do not edit - automatically generated from ProjectDefinition
+@REM -------
+@SET DEFINES=
+@REM Kludge got Mercurial, cannot be implemented in Borland make
+@FOR /F "tokens=*" %%i in ('hg root') do SET HGROOT=%%i
+@IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
+make.exe -N -f bc.mak -DUSEMINGW=1 %DEFINES% %*
+
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/vcmake.bat	Thu Jan 10 13:21:04 2013 +0000
@@ -0,0 +1,18 @@
+@REM -------
+@REM make using Microsoft Visual C compiler
+@REM type vcmake, and wait...
+@REM do not edit - automatically generated from ProjectDefinition
+@REM -------
+
+@if not defined VSINSTALLDIR (
+    call ..\..\..\stx\rules\vcsetup.bat
+)
+@SET DEFINES=
+@REM Kludge got Mercurial, cannot be implemented in Borland make
+@FOR /F "tokens=*" %%i in ('hg root') do SET HGROOT=%%i
+@IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
+make.exe -N -f bc.mak -DUSEVC=1 %DEFINES% %*
+
+
+
+