BUG? RBParser looses some comments

Andrew Tween amtween at hotmail.com
Thu Jun 29 18:15:54 UTC 2006


If you assign to a workspace var ...

x := RBParser
     parseExpression: 'aReceiver aMessage "foo" do: [Transcript show: 42]'
     onError: [:s :p|^nil].

then you can find the comment in ...

x arguments first body comments

which seems like the wrong place for it to be :(

I had a brief look at the RBParser implementation in VisualWorks, and it seems a
bit better. The RBParser>>addCommentsTo: method is called from more places in
the code.
If you file in the attached changeset and re-run the above then the comment will
now be found in ...

x receiver receiver comments

which seems more appropriate.

The second example will also work in a consistent manner...

y := RBParser
     parseExpression: 'aReceiver aMessage "foo" anotherMessage'
     onError: [:s :p|^nil].
y receiver receiver comments

rather than "y comments", as before.

Hope that helps,
Cheers,
Andy

----- Original Message ----- 
From: "Damien Pollet" <damien.pollet at gmail.com>
To: "The general-purpose Squeak developers list"
<squeak-dev at lists.squeakfoundation.org>
Sent: Thursday, June 29, 2006 4:08 PM
Subject: BUG? RBParser looses some comments


> I can't find the comment when exploring the result of this:
> RBParser
>     parseExpression: 'aReceiver aMessage "foo" do: [Transcript show: 42]'
>     onError: [:s :p|^nil].
>
> But for this it's OK:
> RBParser
>     parseExpression: 'aReceiver aMessage "foo" anotherMessage'
>     onError: [:s :p|^nil].
>
> (I'm porting a pretty printer from VW: package Gutenberg on SqueakSource)
> -- 
>  Damien Pollet
>  type less, do more
>
>
-------------- next part --------------
'From Squeak3.9alpha of 4 July 2005 [latest update: #7035] on 29 June 2006 at 7:06:21 pm'!

!RBParser methodsFor: 'private' stamp: 'tween 6/29/2006 18:42'!
addCommentsTo: aNode
	| existingComments newComments allComments |
	
	existingComments := aNode comments ifNil:[OrderedCollection new].
	newComments := scanner getComments ifNil:[OrderedCollection new].
	allComments := existingComments, newComments.
	allComments isEmpty ifTrue:[allComments := nil].
	aNode comments: allComments! !

!RBParser methodsFor: 'private-parsing' stamp: 'tween 6/29/2006 18:15'!
parsePrimitiveIdentifier
	| token answer |
	token := currentToken.
	self step.
	answer := RBVariableNode identifierToken: token.
	self addCommentsTo: answer.
	^answer! !

!RBParser methodsFor: 'private-parsing' stamp: 'tween 6/29/2006 18:30'!
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.
						self addCommentsTo: node.
						statements add: node.
						return := true]
					ifFalse: 
						[node := self parseAssignment.
						self addCommentsTo: node.
						statements add: node].
				(currentToken isSpecial and: [currentToken value == $.]) 
					ifTrue: 
						[periods add: currentToken start.
						self step]
					ifFalse: [return := true].
				].
	statements notEmpty ifTrue: [self addCommentsTo: statements last].
	sequenceNode
		statements: statements;
		periods: periods.
	^sequenceNode! !

!RBParser methodsFor: 'private-parsing' stamp: 'tween 6/29/2006 18:30'!
parseUnaryMessage
	| node |

	node := self parsePrimitiveObject.
	self addCommentsTo: node.
	[currentToken isLiteral ifTrue: [self patchLiteralMessage].
	currentToken isIdentifier] 
			whileTrue: [node := self parseUnaryMessageWith: node].
	self addCommentsTo: node.
	^node! !



More information about the Squeak-dev mailing list