[squeak-dev] The Trunk: Compiler-ul.196.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Mar 15 13:40:39 UTC 2011


Levente Uzonyi uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-ul.196.mcz

==================== Summary ====================

Name: Compiler-ul.196
Author: ul
Time: 15 March 2011, 1:46:35.738 pm
UUID: c6499e3d-db6c-704f-b00e-243584dd2543
Ancestors: Compiler-ul.195

- minor tweaks

=============== Diff against Compiler-ul.195 ===============

Item was changed:
  ----- Method: Scanner>>scanAllTokenPositionsInto: (in category 'expression types') -----
  scanAllTokenPositionsInto: aBlock
  	"Evaluate aBlock with the start and end positions of all separate non-white-space tokens, including comments."
  
  	| lastMark |
  	lastMark := 1.
+ 	[currentComment ifNotNil:
- 	[currentComment notNil ifTrue:
  		[currentComment do:
  			[:cmnt| | idx |
  			 idx := source originalContents indexOfSubCollection: cmnt startingAt: lastMark.
  			 (idx > 0 and: [idx < mark]) ifTrue:
  				[aBlock value: idx - 1 value: (lastMark := idx + cmnt size)]].
  		 currentComment := nil].
+ 	mark ifNotNil:
- 	mark notNil ifTrue:
  		[(token == #- 
+ 		  and: [(self typeTableAt: hereChar) == #xDigit]) ifTrue:
- 		  and: [(self typeTableAt: hereChar) = #xDigit]) ifTrue:
  			[| savedMark |
  			 savedMark := mark.
  			 self scanToken.
  			 token := token negated.
  			 mark := savedMark].
  		"Compensate for the fact that the parser uses two character lookahead.  Normally we must
  		  remove the extra two characters.  But this mustn't happen for the last token at the end of stream."
  		 aBlock
  			value: mark
  			value: (source atEnd
  					ifTrue: [tokenType := #doIt. "to cause an immediate ^self" source position]
  					ifFalse: [source position - 2])].
+ 	 (tokenType == #rightParenthesis
- 	 (tokenType = #rightParenthesis
  	  or: [tokenType == #doIt]) ifTrue:
  		[^self].
+ 	tokenType == #leftParenthesis
- 	tokenType = #leftParenthesis
  		ifTrue: 
  			[self scanToken; scanAllTokenPositionsInto: aBlock]
  		ifFalse: 
+ 			[(tokenType == #word or: [tokenType == #keyword or: [tokenType = #colon]])
- 			[(tokenType = #word or: [tokenType = #keyword or: [tokenType = #colon]])
  				ifTrue: 
  					[self scanLitWord.
+ 					 token == #true ifTrue: [token := true].
+ 					 token == #false ifTrue: [token := false].
+ 					 token == #nil ifTrue: [token := nil]]
- 					 token = #true ifTrue: [token := true].
- 					 token = #false ifTrue: [token := false].
- 					 token = #nil ifTrue: [token := nil]]
  				ifFalse:
  					[(token == #- 
+ 					  and: [(self typeTableAt: hereChar) == #xDigit])
- 					  and: [(self typeTableAt: hereChar) = #xDigit])
  						ifTrue: 
  							[self scanToken.
  							 token := token negated]]].
  		self scanToken.
  	true] whileTrue!

Item was changed:
  ----- Method: Scanner>>scanLitByteVec (in category 'expression types') -----
  scanLitByteVec
  	| stream |
  	stream := (ByteArray new: 16) writeStream.
+ 	[ tokenType == #rightBracket or: [ tokenType == #doIt ] ] whileFalse: [
+ 		tokenType == #word
- 	[ tokenType = #rightBracket or: [ tokenType = #doIt ] ] whileFalse: [
- 		tokenType = #word
  			ifTrue: [ self scanLitWord ].
  		(token isInteger and: [ token between: 0 and: 255 ])
  			ifFalse: [ ^ self offEnd: '8-bit integer or right bracket expected' ].
  		stream nextPut: token.
  		self scanToken ].
  	token := stream contents!

Item was changed:
  ----- Method: Scanner>>scanLitVec (in category 'expression types') -----
  scanLitVec
  	| s |
  	s := WriteStream on: (Array new: 16).
+ 	[tokenType == #rightParenthesis or: [tokenType == #doIt]] whileFalse:
+ 		[tokenType == #leftParenthesis
- 	[tokenType = #rightParenthesis or: [tokenType = #doIt]] whileFalse:
- 		[tokenType = #leftParenthesis
  			ifTrue: 
  				[self scanToken; scanLitVec]
  			ifFalse: 
+ 				[(tokenType == #word or: [tokenType == #keyword or: [tokenType == #colon]])
- 				[(tokenType = #word or: [tokenType = #keyword or: [tokenType = #colon]])
  					ifTrue: 
  						[self scanLitWord.
+ 						token == #true ifTrue: [token := true].
+ 						token == #false ifTrue: [token := false].
+ 						token == #nil ifTrue: [token := nil]]
- 						token = #true ifTrue: [token := true].
- 						token = #false ifTrue: [token := false].
- 						token = #nil ifTrue: [token := nil]]
  					ifFalse:
  						[(token == #- 
+ 						  and: [(self typeTableAt: hereChar) == #xDigit]) ifTrue: 
- 						  and: [(self typeTableAt: hereChar) = #xDigit]) ifTrue: 
  							[self scanToken.
  							 token := token negated]]].
  		s nextPut: token.
  		self scanToken].
  	token := s contents!

Item was changed:
  ----- Method: Scanner>>scanLitWord (in category 'expression types') -----
  scanLitWord
  	"Accumulate keywords and asSymbol the result."
  
  	| t |
+ 	[(self typeTableAt: hereChar) == #xLetter]
- 	[(self typeTableAt: hereChar) = #xLetter]
  		whileTrue: 
  			[t := token.
  			self xLetter.
  			token := t , token].
  	token := token asSymbol!

Item was changed:
  ----- Method: Scanner>>xLitQuote (in category 'multi-character scans') -----
  xLitQuote
  	"Symbols and vectors: #(1 (4 5) 2 3) #ifTrue:ifFalse: #'abc'."
  	| start |
  	start := mark.
  	self step. "litQuote"
  	self scanToken.
+ 	tokenType == #leftParenthesis
- 	tokenType = #leftParenthesis
  		ifTrue: [self scanToken; scanLitVec.
  			mark := start + 1.
  			tokenType == #doIt
  				ifTrue: [self offEnd: 'Unmatched parenthesis']]
+ 		ifFalse: [tokenType == #leftBracket
- 		ifFalse: [tokenType = #leftBracket
  				ifTrue: [self scanToken; scanLitByteVec.
  					mark := start + 1.
  					tokenType == #doIt
  						ifTrue: [self offEnd: 'Unmatched bracket']]
+ 				ifFalse: [(tokenType == #word or: [tokenType == #keyword or: [tokenType == #colon]])
- 				ifFalse: [(#(#word #keyword #colon ) includes: tokenType)
  						ifTrue: [self scanLitWord]
+ 						ifFalse: ["tokenType == #literal
- 						ifFalse: [tokenType == #literal
  								ifTrue: [token isSymbol
+ 										ifTrue: [""##word""
- 										ifTrue: ["##word"
  											token := token
+ 											""May want to move toward ANSI
+ 											here ""]]
+ 								ifFalse: ["tokenType == #string
+ 										ifTrue: [token := token asSymbol]"]"]]].
- 											"May want to move toward ANSI
- 											here "]]
- 								ifFalse: [tokenType == #string
- 										ifTrue: [token := token asSymbol]]]]].
  	mark := start.
  	tokenType := #literal
  
  	"#(Pen)
  	#Pen
  	#'Pen'
  	##Pen
  	###Pen
  	"!




More information about the Squeak-dev mailing list