[squeak-dev] The Inbox: Compiler-nice.267.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Sep 11 21:58:02 UTC 2013


Nicolas Cellier uploaded a new version of Compiler to project The Inbox:
http://source.squeak.org/inbox/Compiler-nice.267.mcz

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

Name: Compiler-nice.267
Author: nice
Time: 11 September 2013, 11:57:39.343 pm
UUID: 6e7e57b2-1e47-467b-b1ca-63740580515f
Ancestors: Compiler-nice.266

Get rid of last scories of alternate selector syntax experimentations which are quite useless.
This makes Squeak syntax rules a bit more simple and a bit less exotic in the Smalltalk dialect zoo.

This means that literals #: and #:x are not valid syntax anymore.
They must be replaced with universal syntax for invalid selector #':' and #':x' respectively.

Another side effect is that #( :x ) would now be interpreted #( #':' #x ) instead of #( #':x' ) previously.
Once again universal syntax shall be used in this case.

Last usage of this alternate syntax have been expurgated out of Squeak trunk.
But trying to load historical code using those features would pop up a SyntaxError window or silently change a literal array contents.

Using (Scanner prefAllowUnicharSymbol: true) is a known workaround to make #: compile again.
But #:x would then be a message x sent to #':' rather than #':x' literal...
So this preference does not fully solve the compatibility issue.

=============== Diff against Compiler-nice.266 ===============

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 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:
  		[(token == #- 
  		  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 position - (aheadChar == DoItCharacter
  				ifTrue: [hereChar == DoItCharacter
  					ifTrue: [0]
  					ifFalse: [1]]
  				ifFalse: [2])].
  	 (tokenType == #rightParenthesis
  	  or: [tokenType == #doIt]) ifTrue:
  		[^self].
  	tokenType == #leftParenthesis
  		ifTrue: 
  			[self scanToken; scanAllTokenPositionsInto: aBlock]
  		ifFalse: 
+ 			[(tokenType == #word or: [tokenType == #keyword])
- 			[(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]]
  				ifFalse:
  					[(token == #- 
  					  and: [(self typeTableAt: hereChar) == #xDigit])
  						ifTrue: 
  							[self scanToken.
  							 token := token negated]]].
  		self scanToken ] repeat!

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
  			ifTrue: 
  				[self scanToken; scanLitVec]
  			ifFalse: 
+ 				[(tokenType == #word or: [tokenType == #keyword])
- 				[(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]]
  					ifFalse:
  						[(token isCharacter and: [tokenType ~~ #character])
  							ifTrue: [token := token asSymbol]
  							ifFalse: [(token == #- 
  								  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."
  
  	token := (String streamContents: [ :stream |
+ 		[ stream nextPutAll: token.
+ 		 (self typeTableAt: hereChar) == #xLetter ]
+ 			whileTrue: [	self xLetter] ]) asSymbol!
- 		stream nextPutAll: token.
- 		[ (self typeTableAt: hereChar) == #xLetter ] whileTrue: [
- 			self xLetter.
- 			stream nextPutAll: token ] ]) asSymbol!

Item was changed:
  ----- Method: Scanner>>xColon (in category 'multi-character scans') -----
  xColon
  	"Allow := for assignment"
  	
  	aheadChar == $= ifTrue:
  		[self step.
  		tokenType := #leftArrow.
  		self step.
  		^ token := #':='].
  	"Otherwise, just do what normal scan of colon would do"
  	tokenType := #colon.
+ 	^ token := self step!
- 	^ token := self step 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
  		ifTrue: [self scanToken; scanLitVec.
  			mark := start + 1.
  			tokenType == #doIt
  				ifTrue: [self offEnd: 'Unmatched parenthesis']]
  		ifFalse: [tokenType == #leftBracket
  				ifTrue: [self scanToken; scanLitByteVec.
  					mark := start + 1.
  					tokenType == #doIt
  						ifTrue: [self offEnd: 'Unmatched bracket']]
+ 				ifFalse: [(tokenType == #word or: [tokenType == #keyword])
- 				ifFalse: [(tokenType == #word or: [tokenType == #keyword or: [tokenType == #colon]])
  						ifTrue: [self scanLitWord]
  						ifFalse: [(tokenType == #string or: [ tokenType == #verticalBar ])
  							ifTrue: [token := token asSymbol]
  							ifFalse: [tokenType == #binary 
  								ifFalse: [(token isCharacter and: [tokenType ~~ #character and: [self class prefAllowUnicharSymbol]])
  									ifTrue: [token := token asSymbol]
  									ifFalse: [self notify: 'Invalid literal character' at: start + 1]]]]]].
  	mark := start.
  	tokenType := #literal
  
  	"#(Pen)
  	#Pen
  	#'Pen'
  	"!



More information about the Squeak-dev mailing list