[Pkg] The Trunk: ShoutCore-ul.47.mcz

commits at source.squeak.org commits at source.squeak.org
Fri May 1 18:01:57 UTC 2015


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

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

Name: ShoutCore-ul.47
Author: ul
Time: 1 May 2015, 1:52:05.9 pm
UUID: a4a03a3c-da8f-4e81-86f5-09b950cfeabe
Ancestors: ShoutCore-ul.46

Removed encodedCharSet from SHParserST80. All methods referencing it are sending the corresponding method to the character again.

=============== Diff against ShoutCore-ul.46 ===============

Item was changed:
  Object subclass: #SHParserST80
+ 	instanceVariableNames: 'classOrMetaClass source workspace arguments sourcePosition currentToken currentTokenFirst temporaries instanceVariables errorBlock currentTokenSourcePosition blockDepth bracketDepth ranges environment allowUnderscoreAssignments allowUnderscoreSelectors'
- 	instanceVariableNames: 'classOrMetaClass source workspace arguments sourcePosition currentToken currentTokenFirst temporaries instanceVariables errorBlock currentTokenSourcePosition blockDepth bracketDepth ranges environment encodedCharSet allowUnderscoreAssignments allowUnderscoreSelectors'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'ShoutCore-Parsing'!
  
  !SHParserST80 commentStamp: 'tween 8/16/2004 15:44' prior: 0!
  I am a Smalltalk method / expression parser.
  
  Rather than creating an Abstract Syntax Tree, I create a sequence of SHRanges (in my 'ranges' instance variable), which represent the tokens within the String I am parsing.
  
  I am used by a SHTextStylerST80 to parse method source strings.
  I am able to parse incomplete / incorrect methods, and so can be used to parse methods that are being edited.
  
  My 'source' instance variable should be set to the string to be parsed.
  
  My 'classOrMetaClass' instance var must be set to the class or metaClass for the method source so that I can correctly resolve identifiers within the source. If this is nil , I parse the source as an expression (i.e. a doIt expression).
  
  My 'workspace' instance variable can be set to a Workspace, so that I can resolve workspace variables.
  
  My 'environment' instance variable is the global namespace (this is initialized to Smalltalk, but can be set to a different environment).
  
  Example 1.
  	ranges := SHParserST80 new
  		classOrMetaClass: Object;
  		source: 'testMethod ^self';
  		parse;
  		ranges
  		
  !

Item was changed:
  ----- Method: SHParserST80>>isKeyword (in category 'token testing') -----
  isKeyword
  	"This method assumes that currentTokenFirst is a non-letter character when currentToken is nil."
  
+ 	currentTokenFirst isLetter ifTrue: [
- 	(encodedCharSet isLetter: currentTokenFirst) ifTrue: [
  		^currentToken last == $: ].
  	^allowUnderscoreSelectors
  		and: [ currentTokenFirst == $_ 
  		and: [ currentToken notNil
  		and: [ currentToken size > 1
  		and: [ currentToken last == $: ] ] ] ]!

Item was changed:
  ----- Method: SHParserST80>>isName (in category 'token testing') -----
  isName
  	"This method assumes that currentTokenFirst is a non-letter character when currentToken is nil."
  
+ 	^(currentTokenFirst isLetter
- 	^((encodedCharSet isLetter: currentTokenFirst)
  		or: [ allowUnderscoreSelectors
  			and: [ currentTokenFirst == $_ 
  			and: [ currentToken notNil
  			and: [ currentToken size > 1 ] ] ] ]) 
+ 		and: [ currentToken last isAlphaNumeric
- 		and: [ (encodedCharSet isAlphaNumeric: currentToken last)
  			or: [ allowUnderscoreSelectors
  				and: [ currentToken last == $_ ] ] ] !

Item was changed:
  ----- Method: SHParserST80>>isSelectorCharacter: (in category 'character testing') -----
  isSelectorCharacter: aCharacter
  
  	| asciiValue |
  	('"#$'':().;[]{}^_'  includes: aCharacter) ifTrue: [ ^false ].
  	aCharacter isSeparator ifTrue:[ ^false ].
+ 	aCharacter isAlphaNumeric ifTrue: [ ^false ].
- 	(encodedCharSet isAlphaNumeric: aCharacter) ifTrue: [ ^false ].
  	(asciiValue := aCharacter asciiValue) = 30 ifTrue: [ ^false "the doIt char" ].
  	^asciiValue ~= 0 "Any other char, but 0 is ok as a binary selector char."
  !

Item was changed:
  ----- Method: SHParserST80>>parseByteArray (in category 'parse') -----
  parseByteArray
+ 
  	[currentTokenFirst == $]] whileFalse: [
+ 		currentTokenFirst isDigit
- 		(encodedCharSet isDigit: currentTokenFirst)
  			ifTrue: [
  				"do not parse the number, can be time consuming"
  				self scanPast: #number]
  			ifFalse: [
  				self failWhen: currentTokenFirst == $. .
  				self error]].
  	self scanPast: #byteArrayEnd!

Item was changed:
  ----- Method: SHParserST80>>parseExternalCall (in category 'parse') -----
  parseExternalCall
  	[self scanNext.
  	((Smalltalk at: #ExternalFunction) callingConventionModifierFor: currentToken) notNil]
  		whileTrue.
  	self failUnless: currentToken notNil.
  	self scanPast: #externalCallType.
  	currentToken = '*' 
  		ifTrue: [self scanPast: #externalCallTypePointerIndicator].
+ 	currentTokenFirst isDigit
- 	(encodedCharSet isDigit: currentTokenFirst)
  		ifTrue: [self scanPast: #integer]
  		ifFalse: 	[
  			self failUnless: currentTokenFirst == $'.
  			self parseString].
  	self failUnless: currentTokenFirst == $(.
  	self scanPast: #leftParenthesis.
  	[currentTokenFirst ~= $)] 
  		whileTrue: [
  			self failUnless: currentToken notNil.
  			self scanPast: #externalCallType.
  			currentToken = '*' 
  				ifTrue: [self scanPast: #externalCallTypePointerIndicator]].
  	self scanPast: #rightParenthesis.
  	currentToken = 'module:' 
  		ifTrue: [
  			self scanPast: #module.
  			self parseStringOrSymbol ].
  	currentToken = 'error:' ifTrue: [
  		self scanPast: #primitive. "there's no rangeType for error"
  		self isName
  			ifTrue: [ self scanPast: #patternTempVar ]
  			ifFalse: [ self parseStringOrSymbol ] ].
  	self failUnless: currentToken = '>'.
  	self scanPast: #primitiveOrExternalCallEnd!

Item was changed:
  ----- Method: SHParserST80>>parseLiteral: (in category 'parse') -----
+ parseLiteral: inArray
+ 
- parseLiteral: inArray 
  	currentTokenFirst == $$ 
  		ifTrue: [
  			| pos |
  			self failWhen: self currentChar isNil.
  			self rangeType: #'$'.
  			pos := currentTokenSourcePosition + 1.
  			self nextChar.
  			^self scanPast: #character start: pos end: pos].
+ 	currentTokenFirst isDigit
- 	(encodedCharSet isDigit: currentTokenFirst) 
  		ifTrue: [
  			"do not parse the number, can be time consuming"
  			^self scanPast: #number].
  	currentToken = '-' 
  		ifTrue: [
  			| c |
  			c := self currentChar.
+ 			(inArray and: [c isNil or: [ c isDigit not ]]) 
- 			(inArray and: [c isNil or: [(encodedCharSet isDigit: c) not]]) 
  				ifTrue: [
  					"single - can be a symbol in an Array"
  					^self scanPast: #symbol].
  			self scanPast: #-.
  			self failWhen: currentToken isNil.
  			"token isNil ifTrue: [self error: 'Unexpected End Of Input']."
  			"do not parse the number, can be time consuming"
  			^self scanPast: #number].
  	currentTokenFirst == $' ifTrue: [^self parseString].
  	currentTokenFirst == $# ifTrue: [^self parseSymbol].
  	(inArray and: [currentToken notNil]) ifTrue: [^self scanPast: #symbol].
  	self failWhen: currentTokenFirst == $. .
  	self error	": 'argument missing'"!

Item was changed:
  ----- Method: SHParserST80>>parseLiteralArrayElement (in category 'parse') -----
  parseLiteralArrayElement
+ 
+ 	currentTokenFirst isLetter ifTrue: [
+ 		#true = currentToken ifTrue: [ ^self scanPast: #true ].
+ 		#false = currentToken ifTrue: [ ^self scanPast: #false ].
+ 		#nil = currentToken ifTrue: [ ^self scanPast: #nil ].
+ 		^self scanPast: #symbol ].
+ 	currentTokenFirst == $( ifTrue: [
+ 		self scanPast: #arrayStart.
+ 		^self parseArray ].
- 	(encodedCharSet isLetter: currentTokenFirst)
- 		ifTrue: [
- 			#true = currentToken ifTrue: [ ^self scanPast: #true ].
- 			#false = currentToken ifTrue: [ ^self scanPast: #false ].
- 			#nil = currentToken ifTrue: [ ^self scanPast: #nil ].
- 			^self scanPast: #symbol ].
- 	currentTokenFirst == $( 
- 		ifTrue: [
- 			self scanPast: #arrayStart.
- 			^self parseArray].
  	^self parseLiteral: true!

Item was changed:
  ----- Method: SHParserST80>>parsePrimitive (in category 'parse') -----
  parsePrimitive
  
  	self scanNext.
+ 	currentTokenFirst isDigit
- 	(encodedCharSet isDigit: currentTokenFirst)
  		ifTrue: [ self scanPast: #integer ]
  		ifFalse: [
  			self parseStringOrSymbol.
  			currentToken = 'module:' ifTrue: [
  				self scanPast: #module.
  				self parseStringOrSymbol ] ].
  	currentToken = 'error:' ifTrue: [
  		self scanPast: #primitive. "there's no rangeType for error"
  		self isName
  			ifTrue: [ self scanPast: #patternTempVar ]
  			ifFalse: [ self parseStringOrSymbol ] ].
  	self failUnless: currentToken = '>'.
  	self scanPast: #primitiveOrExternalCallEnd!

Item was changed:
  ----- Method: SHParserST80>>parseSymbol (in category 'parse') -----
  parseSymbol
  	| c |
  	currentToken = '#' 
  		ifTrue: [
  			"if token is just the #, then scan whitespace and comments
  			and then process the next character.
  			Squeak allows space between the # and the start of the symbol 
  			e.g. # (),  #  a, #  'sym' "
  			self rangeType: #symbol.
  			self scanWhitespace].
  	c := self currentChar.
  	self failWhen: (c isNil or: [c isSeparator]).
  	c == $( 
  		ifTrue: [
  			self nextChar.
  			self scanPast: #arrayStart start: currentTokenSourcePosition end: currentTokenSourcePosition + 1.
  			^self parseArray].
  	c == $' ifTrue: [^self parseSymbolString].
  	c == $[ ifTrue: [
  			self nextChar.
  			self scanPast: #byteArrayStart start: currentTokenSourcePosition end: currentTokenSourcePosition + 1.
  			^self parseByteArray].
  	((self isSelectorCharacter: c) or: [c == $-]) 
  		ifTrue: [^self parseSymbolSelector].
+ 	(c isLetter
- 	((encodedCharSet isLetter: c) 
  		or: [ c == $: 
  		or: [ allowUnderscoreSelectors and: [ c == $_ ] ] ]) 
  			ifTrue: [^self parseSymbolIdentifier].
  	^self parseCharSymbol!

Item was changed:
  ----- Method: SHParserST80>>parseSymbolIdentifier (in category 'parse') -----
  parseSymbolIdentifier
  
  	| c start end |
  	c := self currentChar.
  	self failUnless: (
+ 		c isLetter
- 		(encodedCharSet isLetter: c) 
  			or: [ c == $: 
  			or: [ allowUnderscoreSelectors and: [ c == $_ ] ] ]).
  	start := sourcePosition.	
  	[
+ 		(c := self nextChar) isAlphaNumeric
- 		c := self nextChar.
- 		(encodedCharSet isAlphaNumeric: c) 
  			or: [ c == $:
+ 			or: [ allowUnderscoreSelectors and: [ c == $_ ] ] ] ] whileTrue.
- 			or: [ allowUnderscoreSelectors and: [ c == $_] ] ] ] whileTrue.
  	end := sourcePosition - 1.
  	c := source copyFrom: start - 1 to: end.
  	self scanPast: #symbol start: start - 1 end: end.
  	^c!

Item was changed:
  ----- Method: SHParserST80>>scanIdentifier (in category 'scan') -----
  scanIdentifier
  
  	| c start |
  	start := sourcePosition.
  	[
+ 		(c := self nextChar) isAlphaNumeric
- 		(encodedCharSet isAlphaNumeric: (c := self nextChar))
  			or: [ allowUnderscoreSelectors and: [ c == $_ ] ] ] whileTrue.
  	(c == $: and: [ (self isSelectorCharacter: self peekChar) not ]) 
  		ifTrue: [ self nextChar ].
  	currentToken := source copyFrom: start to: sourcePosition - 1.
  	currentTokenSourcePosition := start!

Item was changed:
  ----- Method: SHParserST80>>scanNext (in category 'scan') -----
  scanNext
  
  	self scanWhitespace.
  	currentTokenFirst := self currentChar ifNil: [
  		" end of input "
  		currentTokenFirst := $ .
  		currentTokenSourcePosition := nil.
  		currentToken := nil.
  		^nil ].
+ 	currentTokenFirst isDigit ifTrue: [ ^self scanNumber ].
+ 	(currentTokenFirst isLetter or: [
- 	(encodedCharSet isDigit: currentTokenFirst) ifTrue: [ ^self scanNumber ].
- 	((encodedCharSet isLetter: currentTokenFirst) or: [
  		allowUnderscoreSelectors and: [ currentTokenFirst == $_ ] ])
  			ifTrue: [ ^self scanIdentifier ].
  	^self scanBinary!

Item was changed:
  ----- Method: SHParserST80>>scanNumber (in category 'scan') -----
  scanNumber
  	| start c nc base |
  	start := sourcePosition.
  	self skipDigits.
  	c := self currentChar.
  	c == $r 
  		ifTrue: [
  			base := Integer readFrom: (ReadStream on: (source copyFrom: start to: sourcePosition - 1)).
  			self peekChar == $- ifTrue:[self nextChar].
  			self skipBigDigits: base.
  			c := self currentChar.
  			c == $. 
  				ifTrue: [
  					(self isBigDigit: self nextChar base: base) 
  						ifFalse: [sourcePosition := sourcePosition - 1]
  						ifTrue: [self skipBigDigits: base]].
  			c := self currentChar.
  			('deq'includes: c) 
  				ifTrue: [
+ 					((nc := self nextChar) isDigit or: [nc == $- and: [ self peekChar isDigit ]]) 
- 					((encodedCharSet isDigit: (nc := self nextChar)) or: [nc == $- and:[(encodedCharSet isDigit: self peekChar)]]) 
  						ifFalse: [sourcePosition := sourcePosition - 1]
  						ifTrue: [self skipDigits]].
  			c == $s ifTrue: [
+ 				(nc := self nextChar) isDigit
- 				(encodedCharSet isDigit: (nc := self nextChar))	
  					ifTrue: [ self skipDigits ]
  					ifFalse: [ 
+ 						nc isLetter ifTrue: [
- 						(encodedCharSet isLetter: nc) ifTrue: [
  							sourcePosition := sourcePosition - 1 ] ] ].
  			currentToken := source copyFrom: start to: sourcePosition - 1.
  			^currentTokenSourcePosition := start].
  	c == $s 
  		ifTrue: [
+ 			(nc := self nextChar) isDigit
- 			(encodedCharSet isDigit: (nc := self nextChar))
  				ifFalse: [nc isLetter ifTrue: [sourcePosition := sourcePosition - 1]]
  				ifTrue: [self skipDigits.].
  			currentToken := source copyFrom: start to: sourcePosition - 1.
  			^currentTokenSourcePosition := start].
  	c == $. 
  		ifTrue: [
+ 			self nextChar isDigit
- 			(encodedCharSet isDigit: self nextChar)
  				ifFalse: [
  					sourcePosition := sourcePosition - 1.
  					currentToken := source copyFrom: start to: sourcePosition - 1.
  					^currentTokenSourcePosition := start]
  				ifTrue: [self skipDigits]].
  	c := self currentChar.
  	('deq' includes: c) 
  		ifTrue: [
+ 			((nc := self nextChar) isDigit or: [nc == $-  and:[ self peekChar isDigit ]]) 
- 			((encodedCharSet isDigit: (nc := self nextChar)) or: [nc == $-  and:[(encodedCharSet isDigit: self peekChar)]]) 
  				ifFalse: [sourcePosition := sourcePosition - 1]
  				ifTrue: [self skipDigits]].
  	c == $s 
  		ifTrue: [
+ 			(nc := self nextChar) isDigit
- 			(encodedCharSet isDigit: (nc := self nextChar))
  				ifFalse: [nc isLetter ifTrue: [sourcePosition := sourcePosition - 1]]
  				ifTrue: [self skipDigits]].
  	currentToken := source copyFrom: start to: sourcePosition - 1.
  	^currentTokenSourcePosition := start!

Item was changed:
  ----- Method: SHParserST80>>skipDigits (in category 'scan') -----
  skipDigits
  
+ 	[ self nextChar isDigit ] whileTrue!
- 	[ (encodedCharSet isDigit: self nextChar) ] whileTrue!

Item was changed:
  ----- Method: SHParserST80>>source: (in category 'accessing') -----
  source: aString
  	
+ 	source := aString
- 	source := aString.
- 	encodedCharSet := (source at: 1 ifAbsent: [ $0 ]) encodedCharSet
  	!



More information about the Packages mailing list