[Newcompiler] [AST] Comments from RBParser

Andrew Tween amtween at hotmail.com
Fri Aug 4 21:03:03 UTC 2006


Hi,
I've had a quick look at the RBParser in VisualWorks and Dolphin Smalltalk, and
the RBParser implementation in AST is a bit different to (behind???) both of
them. I don't think it will take much effort to improve the current AST RBParser
to make it do what you want. Attached is a changeset which might improve things,
although it hasn't been tested properly, and it certainly won't solve all
problems. I think that by fixing things step-by-step eventually we will get the
comment handling correct.

Incidently, Dolphin has a configurable formatter/pretty printer that uses the
RBParser. If you have access to an MS Windows computer, you might want to get
hold of the Dolphin Community edition and take a look at its options.

Cheers,
Andy

----- Original Message ----- 
From: "Mathieu Suen" <mathieusuen at yahoo.fr>
To: "The New Compiler, AST, IRBuilder,Closures..."
<newcompiler at lists.squeakfoundation.org>
Sent: Friday, August 04, 2006 4:04 PM
Subject: Re : [Newcompiler] [AST] Comments from RBParser


> Hi,
>
> It is really strange how RBParse store comments.
> And to write test for the NewCompiler is not unrefined.
>
> Somebody know how it is done?
> I mean,  dose someebody use them (e.g. for pretty print, coloring....) and
have trouble with it or not? And how you use it?
>
> For the time being I follow the way of RBParser to write test.
>
> More information:
>
> zork
>     ["foo" :each | each]
>     ["bar" :each | each]
>     ^self
>
> "foo" are on the  RBMethodNode but "bar" is on the RBVariableNode of the
arguments of the RBBlockNode ??
>
>
> Should I follow this or do it in a better way?
>
> Math
>
>
>
>
>
>
-------------- next part --------------
'From Squeak3.9alpha of 4 July 2005 [latest update: #7051] on 4 August 2006 at 7:10:32 pm'!
Object subclass: #RBParser
	instanceVariableNames: 'scanner currentToken nextToken emptyStatements negatedNumbers errorBlock tags source comments '
	classVariableNames: 'BRAraryNode '
	poolDictionaries: ''
	category: 'AST-RBParser'!
Object subclass: #RBToken
	instanceVariableNames: 'sourcePointer comments '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'AST-Tokens'!

!RBParser methodsFor: 'private' stamp: 'tween 8/4/2006 18:52'!
step
	(currentToken notNil and: [currentToken comments notNil]) 
		ifTrue: [comments addAll: currentToken comments].
	nextToken notNil ifTrue: 
			[currentToken := nextToken.
			nextToken := nil.
			^currentToken].
	currentToken := scanner next! !

!RBParser methodsFor: 'accessing' stamp: 'tween 8/4/2006 18:51'!
initializeParserWith: aString type: aSymbol 
	source := aString.
	comments := OrderedCollection new.
	self scanner: (RBScanner 
				perform: aSymbol
				with: (ReadStream on: aString)
				with: self errorBlock)! !

!RBParser methodsFor: 'private-parsing' stamp: 'tween 8/4/2006 17:26'!
parseStatementList: tagBoolean into: sequenceNode 
	| statements return periods returnPosition node |
	return := false.
	statements := OrderedCollection new.
	periods := OrderedCollection new.
	self addCommentsTo: sequenceNode.
	tagBoolean ifTrue: [self parseResourceTag].
	
	["skip empty statements"
		emptyStatements ifTrue: 
			[[currentToken isSpecial and: [currentToken value == $.]] whileTrue: 
					[periods add: currentToken start.
					self step]].

		"check if we are finished yet"
	 	self atEnd 
			or: [currentToken isSpecial and: ['])}' includes: currentToken value]]] 
			whileFalse: 
				[return ifTrue: [self parserError: 'End of statement list encounted'].
				(currentToken isSpecial and: [currentToken value == $^]) 
					ifTrue: 
						[returnPosition := currentToken start.
						self step.
						node := RBReturnNode return: returnPosition value: self parseAssignment.
						statements add: node.
						return := true]
					ifFalse: 
						[node := self parseAssignment.
						statements add: node].
				(currentToken isSpecial and: [currentToken value == $.]) 
					ifTrue: 
						[periods add: currentToken start.
						self step.
						self addCommentsTo: node]
					ifFalse: [return := true].
				].
	statements notEmpty ifTrue: [self addCommentsTo: statements last].
	sequenceNode
		statements: statements;
		periods: periods.
	^sequenceNode! !


!RBToken methodsFor: 'accessing' stamp: 'tween 8/4/2006 19:01'!
comments
	^comments! !

!RBToken methodsFor: 'accessing' stamp: 'tween 8/4/2006 19:01'!
comments: anOrderedCollection
	comments := anOrderedCollection! !

Object subclass: #RBToken
	instanceVariableNames: 'sourcePointer comments'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'AST-Tokens'!

!RBToken reorganize!
('testing' isAssignment isBinary isIdentifier isKeyword isLiteral isPatternBlock isPatternVariable isRBToken isSpecial)
('accessing' comments comments: length removePositions start stop)
('printing' printOn:)
('initialize-release' start:)
!

Object subclass: #RBParser
	instanceVariableNames: 'scanner currentToken nextToken emptyStatements negatedNumbers errorBlock tags source comments'
	classVariableNames: 'BRAraryNode'
	poolDictionaries: ''
	category: 'AST-RBParser'!


More information about the Newcompiler mailing list