Remove old JK's java parser (which is no longer used) development
authorJan Vrany <jan.vrany@fit.cvut.cz>
Fri, 11 Jan 2013 10:38:06 +0000
branchdevelopment
changeset 1942 ab458da58a25
parent 1941 021634f2b5a2
child 1943 266af0791573
Remove old JK's java parser (which is no longer used)
tools/JavaParser_Old.st
tools/JavaSyntaxHighlighter_Old.st
tools/Make.proto
tools/Make.spec
tools/abbrev.stc
tools/bc.mak
tools/libInit.cc
tools/stx_libjava_tools.st
tools/tools.rc
--- a/tools/JavaParser_Old.st	Fri Jan 11 00:15:21 2013 +0000
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,939 +0,0 @@
-"
- COPYRIGHT (c) 1996-2011 by Claus Gittinger
-
- New code and modifications done at SWING Research Group [1]:
-
- COPYRIGHT (c) 2010-2011 by Jan Vrany, Jan Kurs and Marcel Hlopko
-                            SWING Research Group, Czech Technical University in Prague
-
- 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.
-
- [1] Code written at SWING Research Group contains a signature
-     of one of the above copright owners. For exact set of such code,
-     see the differences between this version and version stx:libjava
-     as of 1.9.2010
-"
-"{ Package: 'stx:libjava/tools' }"
-
-PPCompositeParser subclass:#JavaParser_Old
-	instanceVariableNames:'builder classBody'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Languages-Java-Parser'
-!
-
-PPParser subclass:#SubParser
-	instanceVariableNames:'masterParser'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:JavaParser_Old
-!
-
-JavaParser_Old::SubParser subclass:#MultilineCommentParser
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:JavaParser_Old
-!
-
-PPParser subclass:#LineNumberParser
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:JavaParser_Old
-!
-
-ReadStream subclass:#LineNumberStream
-	instanceVariableNames:'eolPositions lastPosition previousWasCR'
-	classVariableNames:'CR LF'
-	poolDictionaries:''
-	privateIn:JavaParser_Old
-!
-
-JavaParser_Old::MultilineCommentParser subclass:#JavaDocParser
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:JavaParser_Old
-!
-
-JavaParser_Old::SubParser subclass:#SingleLineCommentParser
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:JavaParser_Old
-!
-
-JavaParser_Old::SubParser subclass:#StatementParser
-	instanceVariableNames:'brackets'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:JavaParser_Old
-!
-
-JavaParser_Old::SubParser subclass:#BlockParser
-	instanceVariableNames:'openBlockChar closeBlockChar innerBlockCount'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:JavaParser_Old
-!
-
-!JavaParser_Old class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1996-2011 by Claus Gittinger
-
- New code and modifications done at SWING Research Group [1]:
-
- COPYRIGHT (c) 2010-2011 by Jan Vrany, Jan Kurs and Marcel Hlopko
-                            SWING Research Group, Czech Technical University in Prague
-
- 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.
-
- [1] Code written at SWING Research Group contains a signature
-     of one of the above copright owners. For exact set of such code,
-     see the differences between this version and version stx:libjava
-     as of 1.9.2010
-
-"
-! !
-
-!JavaParser_Old class methodsFor:'parsing'!
-
-methodsIn: sourceCode
-    ^ (self parse: sourceCode) methods.
-
-    "Created: / 08-01-2011 / 15:42:24 / Jan Kurs <kurs.jan@post.cz>"
-!
-
-parse: code
-    ^ JavaParseResult from: (super parse: code).
-
-    "Created: / 08-01-2011 / 16:05:01 / Jan Kurs <kurs.jan@post.cz>"
-    "Modified: / 07-04-2011 / 22:07:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!JavaParser_Old methodsFor:'accessing'!
-
-builder
-    ^ builder
-!
-
-builder:something
-    builder := something.
-!
-
-lineNumber
-    ^ LineNumberParser new.
-
-    "Created: / 29-12-2010 / 22:14:02 / Jan Kurs <kurs.jan@post.cz>"
-    "Modified: / 07-04-2011 / 22:05:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-start
-	^ self javaFile end.
-! !
-
-!JavaParser_Old methodsFor:'grammar'!
-
-annotation
-	^ $@ asParser, self identifier, self annotationBlock optional 
-!
-
-annotationBlock
-        ^ BlockParser new
-                openBlockChar: $(;
-                closeBlockChar: $);
-                yourself;
-        trim
-
-    "Modified: / 07-04-2011 / 21:46:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-argument
-        ^ (
-            self finalKW optional, self type, self threeDotsKW optional, self typeIdentifier, 
-            "JV@2012-03-09: This one is funny, C style array definition seems to be supported.
-            Look at java/lang/String.java"
-            '[]' asParser optional
-
-            ) trim
-
-    "Modified: / 09-03-2012 / 18:47:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-argumentList
-	^ (self argument separatedBy:  ($, asParser trim) ==> [:token | nil]) ==> [: token | token select: [:each | each notNil ]].
-!
-
-block
-        ^ BlockParser new trim
-
-    "Modified: / 07-04-2011 / 21:46:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-classBody
-        ^ (${ asParser trim, self classContents star, $} asParser trim) 
-        foldLeft: [:a :contents :b | contents select: [:each | each notNil ]]
-
-    "Modified: / 30-12-2010 / 11:21:09 / Jan Kurs <kurs.jan@post.cz>"
-!
-
-classContents 
-        ^       self methodDecl trim / 
-                self constructor trim /
-                self staticInitializer trim / 
-                self comment /
-                "Since classes may be nested recursively we have to use this syntax - without self" 
-                self innerClassDecl trim /
-                "TODO JK: This will cause problems - sooner or later"
-                self statement.
-
-    "Modified: / 29-12-2010 / 22:12:11 / Jan Kurs <kurs.jan@post.cz>"
-    "Modified: / 09-03-2012 / 19:29:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-classDecl
-        ^       self classModifiers, 
-                (self classKW / self interfaceKW), 
-                (self identifier, self genericBlock optional) flatten,
-                (self extends optional),
-                (self implements optional),
-                classBody
-
-    "Modified: / 09-03-2012 / 19:32:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-classModifiers
-
-    ^(
-        self publicKW /
-        self privateKW /
-        self abstractKW /
-        self finalKW
-    ) trim star
-
-    "Modified: / 09-03-2012 / 18:09:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-comment
-    ^ (self oneLineComment / self multilineComment)
-
-    "Modified: / 30-12-2010 / 11:20:56 / Jan Kurs <kurs.jan@post.cz>"
-    "Modified (format): / 09-03-2012 / 16:55:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-constructor
-        ^ (     
-                self lineNumber,
-                self javadoc optional, 
-                self methodModifiers optional, 
-                self identifier, 
-                self methodArguments,
-                self throwsStatement optional,
-                self methodBody optional) trim
-                        foldLeft: [:startLine :javadoc :modifiers :name :arguments :throws :body | 
-                                JavaMethodDeclarationNode new
-                                        startLine: startLine;
-                                        javadoc: javadoc;
-                                        modifiers: modifiers;
-                                        retval: nil;
-                                        methodName: name;
-                                        arguments: arguments
-                        ].
-
-    "Modified: / 08-01-2011 / 16:27:25 / Jan Kurs <kurs.jan@post.cz>"
-    "Modified: / 09-03-2012 / 18:55:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-extends
-	^ self extendsKW, self type
-!
-
-fileHeader
-	^ self comment star, self package optional, self imports optional, self comment star
-!
-
-fullIdentifier
-	^ (self identifier separatedBy: $. asParser) trim flatten
-	
-!
-
-genericBlock
-        ^ BlockParser new
-                openBlockChar: $<;
-                closeBlockChar: $>;
-                yourself;
-        trim
-
-    "Modified: / 07-04-2011 / 21:46:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-identifier
-	^ (#letter asParser, #word asParser star) trim flatten
-	
-!
-
-implements
-	^ self implementsKW, (self type separatedBy: $, asParser trim)
-!
-
-import
-    ^ self comment star, self importKW , self statement.
-
-    "Modified (format): / 09-03-2012 / 18:04:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-imports
-	^ self import star
-!
-
-innerClassDecl
-
-    ^   self innerClassModifiers, 
-        (self classKW / self interfaceKW), 
-        (self identifier, self genericBlock optional) flatten,
-        (self extends optional),
-        (self implements optional),
-        classBody
-
-    "Created: / 09-03-2012 / 19:28:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-innerClassModifiers
-
-    ^(
-        self publicKW /
-        self privateKW /
-        self protectedKW /
-        self staticKW /
-        self abstractKW /
-        self finalKW
-    ) trim star
-
-    "Created: / 09-03-2012 / 19:29:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-javaFile
-        ^ (self fileHeader, self classDecl trim) foldLeft: [:header :c | c ]
-
-    "Modified: / 09-03-2012 / 19:31:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-javadoc
-
-    ^ (JavaDocParser for: self) trim
-
-    "Modified: / 09-03-2012 / 16:59:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-methodArguments
-	^ ($( asParser, self argumentList optional, $) asParser) trim foldLeft: [:a :args :b | args].
-!
-
-methodBody
-	^ self block.
-!
-
-methodDecl
-        ^ (    
-                self lineNumber,
-                self javadoc optional, 
-                self methodModifiers optional, 
-                self genericBlock optional,
-                self methodRetval, 
-                self identifier, 
-                self methodArguments,
-                self throwsStatement optional, 
-                self methodBody optional) trim
-                        foldLeft: [:startLine :javadoc :modifiers :generic :retval :name :arguments :throws :body | 
-                                JavaMethodDeclarationNode new
-                                        javadoc: javadoc;
-                                        modifiers: modifiers;
-                                        retval: retval;
-                                        methodName: name;
-                                        arguments: arguments;
-                                        startLine: startLine
-                        ].
-
-    "Modified: / 29-12-2010 / 22:47:53 / Jan Kurs <kurs.jan@post.cz>"
-!
-
-methodModifiers 
-
-    ^(
-        self publicKW /
-        self staticKW /
-        self abstractKW /
-        self privateKW /
-        self protectedKW /
-        self nativeKW /
-        self finalKW /
-        self synchronizedKW /
-        "JV@2012-03-09: Is that correct?"
-        self annotation
-    ) trim star
-
-    "Modified: / 09-03-2012 / 18:32:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-methodRetval
-	^ self type
-!
-
-multilineComment
-    ^ (MultilineCommentParser for: self) trim
-
-    "Modified: / 09-03-2012 / 16:59:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-nameToken
-	^ #word asParser 
-	
-!
-
-oneLineComment
-    ^ (SingleLineCommentParser for: self) trim
-
-    "Modified: / 09-03-2012 / 20:26:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-otherClassContent 
-	^ self statement.
-!
-
-package
-        ^ self packageKW, self statement.
-
-    "Modified: / 09-03-2012 / 19:35:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-primitiveType
-        ^ ( 'int' asParser / 
-            'byte' asParser /
-            'boolean' asParser /
-            'float' asParser /
-            'double' asParser /
-            'char' asParser / 
-            'long' asParser
-        ) trim
-
-    "Modified: / 09-03-2012 / 18:41:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-reference
-	^ self fullIdentifier 
-!
-
-statement
-        ^ StatementParser new trim ==> [: token | nil ].
-
-    "Modified: / 30-12-2010 / 11:20:45 / Jan Kurs <kurs.jan@post.cz>"
-    "Modified: / 07-04-2011 / 22:05:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-staticInitializer 
-        ^ 'static' asParser trim, BlockParser new ==> [:token | nil]
-
-    "Modified: / 07-04-2011 / 21:47:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-throwsStatement 
-	^ self throwsKW, (self identifier separatedBy: $, asParser trim)
-!
-
-type
-	^ 
-	(
-		('void' asParser / self primitiveType / self reference) trim, 
-		 self genericBlock optional,
-		'[]' asParser optional
-	) 
-	flatten 
-!
-
-typeIdentifier 
-	^ self identifier 
-! !
-
-!JavaParser_Old methodsFor:'keywords'!
-
-abstractKW
-
-    ^'abstract' asParser trim
-
-    "Created: / 09-03-2012 / 18:08:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-classKW
-	^ 'class' asParser trim
-!
-
-extendsKW
-	^ 'extends' asParser trim
-!
-
-finalKW
-	^ 'final' asParser trim
-!
-
-implementsKW
-	^ 'implements' asParser trim
-!
-
-importKW
-
-    ^'import' asParser trim
-
-    "Created: / 09-03-2012 / 18:03:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-interfaceKW
-	^ 'interface' asParser trim
-!
-
-nativeKW
-
-    ^'native' asParser trim
-
-    "Created: / 09-03-2012 / 18:07:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-packageKW
-        ^ 'package' asParser trim
-
-    "Created: / 09-03-2012 / 19:35:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-privateKW
-    ^ 'private' asParser
-
-    "Created: / 09-03-2012 / 18:05:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-protectedKW
-    ^ 'protected' asParser
-
-    "Created: / 09-03-2012 / 18:05:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-publicKW
-    ^ 'public' asParser
-
-    "Created: / 09-03-2012 / 18:05:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-staticKW
-
-    ^'static' asParser trim
-
-    "Created: / 09-03-2012 / 18:07:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-synchronizedKW
-
-    ^'synchronized' asParser trim
-
-    "Created: / 09-03-2012 / 18:07:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-threeDotsKW
-	^ '...' asParser trim
-!
-
-throwsKW
-	^ 'throws' asParser trim
-!
-
-voidKW
-	^ 'void' asParser trim
-! !
-
-!JavaParser_Old methodsFor:'parsing'!
-
-parseOn: ppStream
-    ^ super parseOn: (LineNumberStream on: ppStream collection).
-"/    ^ super parseOn: ppStream.
-
-    "Created: / 29-12-2010 / 22:35:30 / Jan Kurs <kurs.jan@post.cz>"
-    "Modified: / 30-12-2010 / 10:01:20 / Jan Kurs <kurs.jan@post.cz>"
-    "Modified: / 07-04-2011 / 22:06:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!JavaParser_Old::SubParser class methodsFor:'instance creation'!
-
-for: masterParser
-
-    ^self new masterParser: masterParser
-
-    "Created: / 09-03-2012 / 16:59:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!JavaParser_Old::SubParser methodsFor:'accessing'!
-
-builder
-    ^masterParser builder
-
-    "Created: / 09-03-2012 / 16:58:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-masterParser
-    ^ masterParser
-!
-
-masterParser:aJavaPetitParser
-    masterParser := aJavaPetitParser.
-! !
-
-!JavaParser_Old::MultilineCommentParser class methodsFor:'documentation'!
-
-version_SVN
-    ^ '§Id§'
-! !
-
-!JavaParser_Old::MultilineCommentParser methodsFor:'parsing'!
-
-buildNodeFrom: start to: end line: line text: text
-
-    ^self builder
-        start: start stop: end line: line;
-        newComment: text.
-
-    "Modified: / 29-12-2010 / 21:29:26 / Jan Kurs <kurs.jan@post.cz>"
-    "Created: / 09-03-2012 / 17:05:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-checkStart: aStream
-	^ (aStream next: self startSequence size) = self startSequence 
-!
-
-parseOn:aStream 
-    | literal  wasStar  line  start  end |
-
-    wasStar := false.
-    line := aStream lineNumber.
-    start := aStream position + 1.
-    (self checkStart:aStream) ifFalse:[
-        ^ PPFailure message:self startSequence , ' expected' at:aStream position.
-    ].
-    [
-        literal := aStream next.
-        aStream atEnd ifTrue:[
-            ^ PPFailure message:'unexpected end of input' at:aStream position.
-        ].
-        wasStar and:[ literal = $/ ]
-    ] whileFalse:[ wasStar := literal = $* ].
-    end := aStream position.
-    ^ self buildNodeFrom: start to: end line: nil text: nil.
-
-    "Modified: / 29-12-2010 / 21:29:26 / Jan Kurs <kurs.jan@post.cz>"
-    "Modified: / 09-03-2012 / 19:37:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-startSequence 
-	^ '/*'
-! !
-
-!JavaParser_Old::LineNumberParser class methodsFor:'documentation'!
-
-version_SVN
-    ^ '§Id§'
-! !
-
-!JavaParser_Old::LineNumberParser methodsFor:'parsing'!
-
-parseOn: aStream
-    ^ aStream lineNumber.
-
-    "Created: / 29-12-2010 / 22:13:22 / Jan Kurs <kurs.jan@post.cz>"
-! !
-
-!JavaParser_Old::LineNumberStream class methodsFor:'documentation'!
-
-version_SVN
-    ^ '§Id§'
-! !
-
-!JavaParser_Old::LineNumberStream class methodsFor:'initialization'!
-
-initialize
-    CR := Character cr.
-    Smalltalk isSmalltalkX ifTrue:[
-        CR := Character return.
-    ].
-    LF := Character nl.
-
-    "Created: / 29-12-2010 / 23:11:17 / Jan Kurs <kurs.jan@post.cz>"
-! !
-
-!JavaParser_Old::LineNumberStream methodsFor:'accessing'!
-
-lineNumber
-        | index start stop pos |
-        pos := position.
-        pos >= eolPositions last ifTrue: [^eolPositions size].
-        start := 1.
-        stop := eolPositions size.
-        [start + 1 < stop] whileTrue: 
-                        [index := (start + stop) // 2.
-                        (eolPositions at: index) <= pos 
-                                ifTrue: [start := index]
-                                ifFalse: [stop := index]].
-        ^start
-
-    "Created: / 30-12-2010 / 10:23:27 / Jan Kurs <kurs.jan@post.cz>"
-!
-
-next
-        | character |
-        character := super next.
-        position - 1 == lastPosition 
-                ifTrue: 
-                        [ 
-"/                        self halt.
-                        lastPosition := lastPosition + 1.
-                        character == CR 
-                                ifTrue: 
-                                        [eolPositions add: position.
-                                        previousWasCR := true]
-                                ifFalse: 
-                                        [(previousWasCR not and: [character == LF]) 
-                                                ifTrue: [eolPositions add: position].
-                                        previousWasCR := false]].
-        ^character
-
-    "Modified: / 30-12-2010 / 10:55:09 / Jan Kurs <kurs.jan@post.cz>"
-!
-
-next: anInteger 
-    "Override for positioning purposes"
-
-    | answer num |
-    num:= readLimit - position min: anInteger.
-    answer := OrderedCollection new: num.
-
-    num timesRepeat: [ 
-        answer add: self next.
-    ].
-    ^ answer asString.
-
-
-"/        | answer endPosition |
-"/        endPosition := position + anInteger min: readLimit.
-"/        answer := collection copyFrom: position + 1 to: endPosition.
-"/        position := endPosition.
-"/        ^ answer
-
-    "Modified: / 30-12-2010 / 10:57:37 / Jan Kurs <kurs.jan@post.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."
-
-	^ collection at: position + 1
-! !
-
-!JavaParser_Old::LineNumberStream methodsFor:'converting'!
-
-asPetitStream
-	^ self
-! !
-
-!JavaParser_Old::LineNumberStream methodsFor:'initialization'!
-
-initialize
-        eolPositions := OrderedCollection with: ZeroPosition.
-        lastPosition := ZeroPosition.
-        previousWasCR := false
-
-    "Created: / 30-12-2010 / 10:22:41 / Jan Kurs <kurs.jan@post.cz>"
-!
-
-on: aCollection
-    super on: aCollection.
-    eolPositions := OrderedCollection with: ZeroPosition.
-    lastPosition := ZeroPosition.
-    previousWasCR := false
-
-    "Created: / 30-12-2010 / 10:26:17 / Jan Kurs <kurs.jan@post.cz>"
-! !
-
-!JavaParser_Old::LineNumberStream methodsFor:'printing'!
-
-printOn: aStream
-	collection isString
-		ifFalse: [ ^ super printOn: aStream ].
-	aStream
-		nextPutAll: (collection copyFrom: 1 to: position);
-		nextPutAll: '·';
-		nextPutAll: (collection copyFrom: position + 1 to: readLimit)
-! !
-
-!JavaParser_Old::JavaDocParser class methodsFor:'documentation'!
-
-version_SVN
-    ^ '§Id§'
-! !
-
-!JavaParser_Old::JavaDocParser methodsFor:'parsing'!
-
-buildNodeFrom: start to: end line: line text: text
-
-    ^self builder
-        start: start stop: end line: line;
-        newJavaDoc: text.
-
-    "Created: / 09-03-2012 / 17:06:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-startSequence 
-	^ '/**'
-! !
-
-!JavaParser_Old::SingleLineCommentParser methodsFor:'parsing'!
-
-parseOn: aStream
-        | literal wasStar start end|
-        wasStar := false.
-        start := aStream position + 1.
-        
-        (aStream next: 2) = '//' ifFalse: [
-                ^ PPFailure message: '// expected' at: aStream position.
-        ].
-        
-        [literal := aStream next.
-                literal = (Character cr) or: [ aStream atEnd ]
-        ] whileFalse.
-        end := aStream position.
-        
-        ^ self builder 
-            start: start stop: end;
-            newComment: '<lost comment, fix in CcmmentParser>>parseOn: >'
-
-    "Modified: / 09-03-2012 / 19:37:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!JavaParser_Old::StatementParser class methodsFor:'documentation'!
-
-version_SVN
-    ^ '§Id§'
-! !
-
-!JavaParser_Old::StatementParser methodsFor:'parsing'!
-
-parseOn: aStream
-	| literal |
-	[literal = $;] whileFalse: [
-		aStream atEnd ifFalse: 
-		[
-			literal := aStream uncheckedPeek.
-			aStream next.
-		]
-		ifTrue: 
-		[
-			^ PPFailure message: 'unexpected end of input' at: aStream position.
-		].
-	
-		"TODO JK: This will cause problems - sooner or later"
-		(literal = $}) ifTrue: [ ^
-			PPFailure message: 'cannot parser $}' at: aStream position.
-		].
-	].
-	^ nil
-! !
-
-!JavaParser_Old::BlockParser class methodsFor:'documentation'!
-
-version_SVN
-    ^ '§Id§'
-! !
-
-!JavaParser_Old::BlockParser methodsFor:'accessing'!
-
-closeBlockChar: anObject
-	closeBlockChar := anObject
-!
-
-openBlockChar: anObject
-	openBlockChar := anObject
-! !
-
-!JavaParser_Old::BlockParser methodsFor:'initialization'!
-
-initialize
-	innerBlockCount := 0.
-	openBlockChar := ${.
-	closeBlockChar := $}.
-! !
-
-!JavaParser_Old::BlockParser methodsFor:'parsing'!
-
-decInnerBlockCount
-	innerBlockCount := innerBlockCount - 1.
-!
-
-incInnerBlockCount
-	innerBlockCount := innerBlockCount + 1.
-!
-
-parseLoop: aStream
-	| literal |
-
-	aStream atEnd ifFalse: 
-	[
-		literal := aStream uncheckedPeek.
-		literal = openBlockChar  ifTrue: [ self incInnerBlockCount].
-		literal = closeBlockChar  ifTrue: [ self decInnerBlockCount].
-		aStream next.
-		^true
-	].
-	^false
-!
-
-parseOn: aStream
-	| literal |
-"	self halt.
-"	
-	(self parseLoop: aStream) ifFalse: 
-	[
-			^ PPFailure message: 'unexpected end of input' at: aStream position
-	].
-
-	self zeroBlockCount ifTrue: [ ^ PPFailure message: ('expected ' copyWith: openBlockChar)  at: aStream position ].
-	
-	[self zeroBlockCount] whileFalse: [
-		(self parseLoop: aStream) ifFalse: 
-		[
-			^ PPFailure message: 'unexpected end of input' at: aStream position
-		]
-	].
-	^ nil.
-!
-
-zeroBlockCount
-	^ innerBlockCount = 0
-! !
-
-!JavaParser_Old class methodsFor:'documentation'!
-
-version_HG
-
-    ^ '$Changeset: <not expanded> $'
-!
-
-version_SVN
-    ^ '§Id§'
-! !
-
-JavaParser_Old::LineNumberStream initialize!
--- a/tools/JavaSyntaxHighlighter_Old.st	Fri Jan 11 00:15:21 2013 +0000
+++ b/tools/JavaSyntaxHighlighter_Old.st	Fri Jan 11 10:38:06 2013 +0000
@@ -35,13 +35,6 @@
 	privateIn:JavaSyntaxHighlighter_Old
 !
 
-JavaParser_Old subclass:#Parser
-	instanceVariableNames:'stream'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:JavaSyntaxHighlighter_Old
-!
-
 !JavaSyntaxHighlighter_Old class methodsFor:'documentation'!
 
 copyright
@@ -481,141 +474,6 @@
     "Created: / 09-03-2012 / 17:11:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
-!JavaSyntaxHighlighter_Old::Parser methodsFor:'accessing'!
-
-stream
-    ^ stream
-!
-
-stream:something
-    stream := something.
-! !
-
-!JavaSyntaxHighlighter_Old::Parser methodsFor:'keywords'!
-
-abstractKW
-
-    ^super abstractKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 18:27:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-classKW
-
-    ^super classKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 18:28:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-extendsKW
-
-    ^super extendsKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 18:28:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-finalKW
-
-    ^super finalKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 18:27:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-implementsKW
-
-    ^super implementsKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 18:28:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-importKW
-
-    ^super importKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 18:26:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-interfaceKW
-
-    ^super interfaceKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 18:28:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-markKeyword: keyword
-
-    | start stop |
-
-    stop := stream position.
-    start := stop - keyword size.
-    builder highlighter markKeyword: keyword from:start to:stop
-
-    "Created: / 09-03-2012 / 18:21:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-nativeKW
-
-    ^super nativeKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 18:28:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-packageKW
-
-    ^super packageKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 19:36:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-privateKW
-
-    ^super privateKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 18:28:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-protectedKW
-
-    ^super protectedKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 18:28:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-publicKW
-
-    ^super publicKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 18:10:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-staticKW
-
-    ^super staticKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 18:29:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-synchronizedKW
-
-    ^super synchronizedKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 19:35:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-throwsKW
-
-    ^super throwsKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 18:29:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-voidKW
-
-    ^super voidKW ==> [:token | self markKeyword: token ]
-
-    "Created: / 09-03-2012 / 18:29:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
 !JavaSyntaxHighlighter_Old class methodsFor:'documentation'!
 
 version_HG
--- a/tools/Make.proto	Fri Jan 11 00:15:21 2013 +0000
+++ b/tools/Make.proto	Fri Jan 11 10:38:06 2013 +0000
@@ -164,10 +164,9 @@
 $(OUTDIR)JavaParseResult.$(O) JavaParseResult.$(H): JavaParseResult.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaParserI.$(O) JavaParserI.$(H): JavaParserI.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)JavaParser_Eclipse.$(O) JavaParser_Eclipse.$(H): JavaParser_Eclipse.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)JavaParser_Old.$(O) JavaParser_Old.$(H): JavaParser_Old.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) $(INCLUDE_TOP)/stx/libbasic/ReadStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PositionableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(STCHDR)
 $(OUTDIR)JavaScannerBase.$(O) JavaScannerBase.$(H): JavaScannerBase.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaSetInspectorView.$(O) JavaSetInspectorView.$(H): JavaSetInspectorView.st $(INCLUDE_TOP)/stx/libtool/SetInspectorView.$(H) $(INCLUDE_TOP)/stx/libtool/InspectorView.$(H) $(INCLUDE_TOP)/stx/libview/SimpleView.$(H) $(INCLUDE_TOP)/stx/libview/DisplaySurface.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsMedium.$(H) $(INCLUDE_TOP)/stx/libview/DeviceGraphicsContext.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsContext.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)JavaSettingsApplication.$(O) JavaSettingsApplication.$(H): JavaSettingsApplication.st $(INCLUDE_TOP)/stx/libtool/AbstractSettingsApplication.$(H) $(INCLUDE_TOP)/stx/libview2/ApplicationModel.$(H) $(INCLUDE_TOP)/stx/libview2/Model.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(INCLUDE_TOP)/stx/libview2/SimpleDialog.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalList.$(H) $(INCLUDE_TOP)/stx/libbasic2/List.$(H) $(INCLUDE_TOP)/stx/libbasic/OrderedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(STCHDR)
+$(OUTDIR)JavaSettingsApplication.$(O) JavaSettingsApplication.$(H): JavaSettingsApplication.st $(INCLUDE_TOP)/stx/libtool/AbstractSettingsApplication.$(H) $(INCLUDE_TOP)/stx/libview2/ApplicationModel.$(H) $(INCLUDE_TOP)/stx/libview2/Model.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libview2/SimpleDialog.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalList.$(H) $(INCLUDE_TOP)/stx/libbasic2/List.$(H) $(INCLUDE_TOP)/stx/libbasic/OrderedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(STCHDR)
 $(OUTDIR)JavaSyntaxHighlighter_Eclipse.$(O) JavaSyntaxHighlighter_Eclipse.$(H): JavaSyntaxHighlighter_Eclipse.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaToken.$(O) JavaToken.$(H): JavaToken.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaTokenParser.$(O) JavaTokenParser.$(H): JavaTokenParser.st $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
@@ -178,7 +177,7 @@
 $(OUTDIR)JavaMethodNode.$(O) JavaMethodNode.$(H): JavaMethodNode.st $(INCLUDE_TOP)/stx/libjava/tools/JavaParseNode.$(H) $(INCLUDE_TOP)/stx/libcomp/ParseNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaParserII.$(O) JavaParserII.$(H): JavaParserII.st $(INCLUDE_TOP)/stx/libjava/tools/JavaParserI.$(H) $(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)JavaScanner.$(O) JavaScanner.$(H): JavaScanner.st $(INCLUDE_TOP)/stx/libjava/tools/JavaScannerBase.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)JavaSyntaxHighlighter_Old.$(O) JavaSyntaxHighlighter_Old.$(H): JavaSyntaxHighlighter_Old.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libjava/tools/JavaParser_Old.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPCompositeParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPDelegateParser.$(H) $(INCLUDE_TOP)/stx/goodies/petitparser/PPParser.$(H) $(INCLUDE_TOP)/stx/libjava/tools/JavaParseNodeBuilder.$(H) $(STCHDR)
+$(OUTDIR)JavaSyntaxHighlighter_Old.$(O) JavaSyntaxHighlighter_Old.$(H): JavaSyntaxHighlighter_Old.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libjava/tools/JavaParseNodeBuilder.$(H) $(STCHDR)
 $(OUTDIR)JavaTypeNode.$(O) JavaTypeNode.$(H): JavaTypeNode.st $(INCLUDE_TOP)/stx/libjava/tools/JavaParseNode.$(H) $(INCLUDE_TOP)/stx/libcomp/ParseNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaArrayTypeNode.$(O) JavaArrayTypeNode.$(H): JavaArrayTypeNode.st $(INCLUDE_TOP)/stx/libjava/tools/JavaTypeNode.$(H) $(INCLUDE_TOP)/stx/libjava/tools/JavaParseNode.$(H) $(INCLUDE_TOP)/stx/libcomp/ParseNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)JavaBooleanTypeNode.$(O) JavaBooleanTypeNode.$(H): JavaBooleanTypeNode.st $(INCLUDE_TOP)/stx/libjava/tools/JavaTypeNode.$(H) $(INCLUDE_TOP)/stx/libjava/tools/JavaParseNode.$(H) $(INCLUDE_TOP)/stx/libcomp/ParseNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/tools/Make.spec	Fri Jan 11 00:15:21 2013 +0000
+++ b/tools/Make.spec	Fri Jan 11 10:38:06 2013 +0000
@@ -56,7 +56,6 @@
 	JavaParseNodeBuilder \
 	JavaParseResult \
 	JavaParser_Eclipse \
-	JavaParser_Old \
 	JavaSetInspectorView \
 	JavaSyntaxHighlighter_Eclipse \
 	stx_libjava_tools \
@@ -100,7 +99,6 @@
     $(OUTDIR)JavaParseNodeBuilder.$(O) \
     $(OUTDIR)JavaParseResult.$(O) \
     $(OUTDIR)JavaParser_Eclipse.$(O) \
-    $(OUTDIR)JavaParser_Old.$(O) \
     $(OUTDIR)JavaSetInspectorView.$(O) \
     $(OUTDIR)JavaSyntaxHighlighter_Eclipse.$(O) \
     $(OUTDIR)stx_libjava_tools.$(O) \
--- a/tools/abbrev.stc	Fri Jan 11 00:15:21 2013 +0000
+++ b/tools/abbrev.stc	Fri Jan 11 10:38:06 2013 +0000
@@ -10,7 +10,6 @@
 JavaParserITests JavaParserITests stx:libjava/tools 'Languages-Java-Tests-Parser' 1
 JavaParserTestCase JavaParserTestCase stx:libjava/tools 'Languages-Java-Tests-Parser' 1
 JavaParser_Eclipse JavaParser_Eclipse stx:libjava/tools 'Languages-Java-Tools' 0
-JavaParser_Old JavaParser_Old stx:libjava/tools 'Languages-Java-Parser' 0
 JavaSetInspectorView JavaSetInspectorView stx:libjava/tools 'Languages-Java-Tools-Inspectors' 2
 JavaSyntaxHighlighter_Eclipse JavaSyntaxHighlighter_Eclipse stx:libjava/tools 'Languages-Java-Tools-Eclipse' 0
 stx_libjava_tools stx_libjava_tools stx:libjava/tools '* Projects & Packages *' 3
--- a/tools/bc.mak	Fri Jan 11 00:15:21 2013 +0000
+++ b/tools/bc.mak	Fri Jan 11 10:38:06 2013 +0000
@@ -89,10 +89,9 @@
 $(OUTDIR)JavaParseResult.$(O) JavaParseResult.$(H): JavaParseResult.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaParserI.$(O) JavaParserI.$(H): JavaParserI.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)JavaParser_Eclipse.$(O) JavaParser_Eclipse.$(H): JavaParser_Eclipse.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)JavaParser_Old.$(O) JavaParser_Old.$(H): JavaParser_Old.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) $(INCLUDE_TOP)\stx\libbasic\ReadStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PositionableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(STCHDR)
 $(OUTDIR)JavaScannerBase.$(O) JavaScannerBase.$(H): JavaScannerBase.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaSetInspectorView.$(O) JavaSetInspectorView.$(H): JavaSetInspectorView.st $(INCLUDE_TOP)\stx\libtool\SetInspectorView.$(H) $(INCLUDE_TOP)\stx\libtool\InspectorView.$(H) $(INCLUDE_TOP)\stx\libview\SimpleView.$(H) $(INCLUDE_TOP)\stx\libview\DisplaySurface.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsMedium.$(H) $(INCLUDE_TOP)\stx\libview\DeviceGraphicsContext.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsContext.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)JavaSettingsApplication.$(O) JavaSettingsApplication.$(H): JavaSettingsApplication.st $(INCLUDE_TOP)\stx\libtool\AbstractSettingsApplication.$(H) $(INCLUDE_TOP)\stx\libview2\ApplicationModel.$(H) $(INCLUDE_TOP)\stx\libview2\Model.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(INCLUDE_TOP)\stx\libview2\SimpleDialog.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalList.$(H) $(INCLUDE_TOP)\stx\libbasic2\List.$(H) $(INCLUDE_TOP)\stx\libbasic\OrderedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(STCHDR)
+$(OUTDIR)JavaSettingsApplication.$(O) JavaSettingsApplication.$(H): JavaSettingsApplication.st $(INCLUDE_TOP)\stx\libtool\AbstractSettingsApplication.$(H) $(INCLUDE_TOP)\stx\libview2\ApplicationModel.$(H) $(INCLUDE_TOP)\stx\libview2\Model.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libview2\SimpleDialog.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalList.$(H) $(INCLUDE_TOP)\stx\libbasic2\List.$(H) $(INCLUDE_TOP)\stx\libbasic\OrderedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(STCHDR)
 $(OUTDIR)JavaSyntaxHighlighter_Eclipse.$(O) JavaSyntaxHighlighter_Eclipse.$(H): JavaSyntaxHighlighter_Eclipse.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaToken.$(O) JavaToken.$(H): JavaToken.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaTokenParser.$(O) JavaTokenParser.$(H): JavaTokenParser.st $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
@@ -103,7 +102,7 @@
 $(OUTDIR)JavaMethodNode.$(O) JavaMethodNode.$(H): JavaMethodNode.st $(INCLUDE_TOP)\stx\libjava\tools\JavaParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaParserII.$(O) JavaParserII.$(H): JavaParserII.st $(INCLUDE_TOP)\stx\libjava\tools\JavaParserI.$(H) $(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)JavaScanner.$(O) JavaScanner.$(H): JavaScanner.st $(INCLUDE_TOP)\stx\libjava\tools\JavaScannerBase.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)JavaSyntaxHighlighter_Old.$(O) JavaSyntaxHighlighter_Old.$(H): JavaSyntaxHighlighter_Old.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libjava\tools\JavaParser_Old.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPCompositeParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPDelegateParser.$(H) $(INCLUDE_TOP)\stx\goodies\petitparser\PPParser.$(H) $(INCLUDE_TOP)\stx\libjava\tools\JavaParseNodeBuilder.$(H) $(STCHDR)
+$(OUTDIR)JavaSyntaxHighlighter_Old.$(O) JavaSyntaxHighlighter_Old.$(H): JavaSyntaxHighlighter_Old.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libjava\tools\JavaParseNodeBuilder.$(H) $(STCHDR)
 $(OUTDIR)JavaTypeNode.$(O) JavaTypeNode.$(H): JavaTypeNode.st $(INCLUDE_TOP)\stx\libjava\tools\JavaParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaArrayTypeNode.$(O) JavaArrayTypeNode.$(H): JavaArrayTypeNode.st $(INCLUDE_TOP)\stx\libjava\tools\JavaTypeNode.$(H) $(INCLUDE_TOP)\stx\libjava\tools\JavaParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)JavaBooleanTypeNode.$(O) JavaBooleanTypeNode.$(H): JavaBooleanTypeNode.st $(INCLUDE_TOP)\stx\libjava\tools\JavaTypeNode.$(H) $(INCLUDE_TOP)\stx\libjava\tools\JavaParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
--- a/tools/libInit.cc	Fri Jan 11 00:15:21 2013 +0000
+++ b/tools/libInit.cc	Fri Jan 11 10:38:06 2013 +0000
@@ -35,7 +35,6 @@
 _JavaParseResult_Init(pass,__pRT__,snd);
 _JavaParserI_Init(pass,__pRT__,snd);
 _JavaParser_137Eclipse_Init(pass,__pRT__,snd);
-_JavaParser_137Old_Init(pass,__pRT__,snd);
 _JavaScannerBase_Init(pass,__pRT__,snd);
 _JavaSetInspectorView_Init(pass,__pRT__,snd);
 _JavaSettingsApplication_Init(pass,__pRT__,snd);
--- a/tools/stx_libjava_tools.st	Fri Jan 11 00:15:21 2013 +0000
+++ b/tools/stx_libjava_tools.st	Fri Jan 11 10:38:06 2013 +0000
@@ -65,7 +65,6 @@
         (JavaParserITests autoload)
         (JavaParserTestCase autoload)
         #'JavaParser_Eclipse'
-        #'JavaParser_Old'
         JavaSetInspectorView
         #'JavaSyntaxHighlighter_Eclipse'
         #'stx_libjava_tools'
--- a/tools/tools.rc	Fri Jan 11 00:15:21 2013 +0000
+++ b/tools/tools.rc	Fri Jan 11 10:38:06 2013 +0000
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2011\nCopyright eXept Software AG 1998-2011\0"
       VALUE "ProductName", "Smalltalk/X\0"
       VALUE "ProductVersion", "6.2.3.0\0"
-      VALUE "ProductDate", "Sun, 16 Dec 2012 16:42:56 GMT\0"
+      VALUE "ProductDate", "Fri, 11 Jan 2013 10:37:01 GMT\0"
     END
 
   END