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

commits at source.squeak.org commits at source.squeak.org
Thu Apr 29 09:23:07 UTC 2010


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

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

Name: ShoutCore-ul.16
Author: ul
Time: 28 April 2010, 8:29:31.118 pm
UUID: a8283288-564c-0b40-b752-8e7a6edaac20
Ancestors: ShoutCore-laza.15

- a few minor performance tweaks

=============== Diff against ShoutCore-laza.15 ===============

Item was changed:
  ----- Method: SHParserST80>>parseString (in category 'parse') -----
  parseString
  	| first c answer last |
  	first := sourcePosition.
  	answer := ''.
  	
+ 	[(c := self currentChar)
+ 		ifNil: [
- 	[(c := self currentChar) isNil 
- 		ifTrue: [
  			self rangeType: #unfinishedString start: first - 1 end: source size.
  			self error	": 'unfinished string'"].
+ 	(c == $' 	
+ 		ifFalse: [answer := answer copyWith: c. true] 
+ 		ifTrue: [false]
- 	(c ~~ $' 	
- 		ifTrue: [answer := answer copyWith: c. true] 
- 		ifFalse: [false]
  	) or: [
  		self peekChar == $' 
  			ifTrue: [
  				sourcePosition := sourcePosition + 1.
  				answer := answer copyWith: $'.
  				true]
  			ifFalse: [false]]
  	] whileTrue: [sourcePosition := sourcePosition + 1].
  	last := sourcePosition.
  	self nextChar.
  	self scanPast: #string start: first - 1 end: last.
  	^answer!

Item was changed:
  ----- Method: SHParserST80>>nextChar (in category 'scan') -----
  nextChar
  	sourcePosition := sourcePosition + 1.
+ 	^source at: sourcePosition ifAbsent: $ !
- 	^source at: sourcePosition ifAbsent: [$ ]!

Item was changed:
  ----- Method: SHParserST80>>parseBinary (in category 'parse') -----
  parseBinary 
  	| binary type |
  	self parseUnary.
  	[self isBinary] 
  		whileTrue: [
  			binary := currentToken.
  			type := #binary.
+ 			(binary isEmpty or:[(Symbol lookup: binary) notNil])
- 			(binary isEmpty or:[Symbol hasInterned: binary ifTrue: [:sym | ]])
  				ifFalse:[
+ 					type := (Symbol thatStartsCaseSensitive: binary skipping: nil)
+ 						ifNil: [#undefinedBinary]
+ 						ifNotNil:[#incompleteBinary]].	
- 					type := (Symbol thatStartsCaseSensitive: binary skipping: nil) isNil
- 						ifTrue: [#undefinedBinary]
- 						ifFalse:[#incompleteBinary]].	
  			self scanPast: type. 	
  			self parseTerm.
              	self parseUnary]
  !

Item was changed:
  ----- Method: SHParserST80>>parseKeyword (in category 'parse') -----
  parseKeyword 
      | keyword rangeIndices |
      self parseBinary.
  	keyword := ''.
  	rangeIndices := #().
  	[
      		[self isKeyword]
          		whileTrue: [
  				keyword := keyword, currentToken. 
  				self rangeType: #keyword.
  				"remember where this keyword token is in ranges"
  				rangeIndices := rangeIndices copyWith: ranges size.
  				self scanNext.
  				self parseTerm.
  				self parseBinary ]
  	] ensure: [ | type |
  		"do this in an ensure so that it happens even if the errorBlock evaluates before getting here"
  		"patch up the keyword tokens, so that incomplete and undefined ones look different"
+ 		(keyword isEmpty or:[(Symbol lookup: keyword) notNil])
- 		(keyword isEmpty or:[Symbol hasInterned: keyword ifTrue: [:sym | ]])
  			ifFalse:[
+ 				type := (Symbol thatStartsCaseSensitive: keyword skipping: nil)
+ 					ifNil: [#undefinedKeyword]
+ 					ifNotNil:[#incompleteKeyword].
- 				type := (Symbol thatStartsCaseSensitive: keyword skipping: nil) isNil
- 					ifTrue: [#undefinedKeyword]
- 					ifFalse:[#incompleteKeyword].
  				rangeIndices do: [:i | (ranges at: i) type: type]]]!

Item was changed:
  ----- Method: SHTextStyler>>monitor (in category 'private') -----
  monitor
+ 	^monitor ifNil: [monitor := Monitor new]!
- 	monitor isNil
- 		ifTrue: [monitor := Monitor new].
- 	^monitor!

Item was changed:
  ----- Method: SHParserST80>>parseUnary (in category 'parse') -----
  parseUnary
  	| unary type |
  	
      [self isName]
          whileTrue: [
  			unary := currentToken.
  			type := #unary.
+ 			(unary isEmpty or:[(Symbol lookup: unary) notNil])
- 			(unary isEmpty or:[Symbol hasInterned: unary ifTrue: [:sym | ]])
  				ifFalse:[
+ 					type := (Symbol thatStartsCaseSensitive: unary skipping: nil)
+ 						ifNil: [#undefinedUnary]
+ 						ifNotNil:[#incompleteUnary]].
- 					type := (Symbol thatStartsCaseSensitive: unary skipping: nil) isNil
- 						ifTrue: [#undefinedUnary]
- 						ifFalse:[#incompleteUnary]].
  			self scanPast: type]
  !

Item was changed:
  ----- Method: SHParserST80>>parse: (in category 'parse') -----
  parse: isAMethod 
  	"Parse the receiver's text. If isAMethod is true
      then treat text as a method, if false as an
      expression with no message pattern"
  
  	self initializeInstanceVariables.
  	sourcePosition := 1.
  	arguments := Dictionary new.
  	temporaries := Dictionary new.
  	blockDepth := bracketDepth := 0.
+ 	ranges
+ 		ifNil: [ranges := OrderedCollection new: 100]
+ 		ifNotNil: [ranges reset].
- 	ranges isNil 
- 		ifTrue: [ranges := OrderedCollection new: 100]
- 		ifFalse: [ranges reset].
  	errorBlock := [^false].
  	[self scanNext.
  	isAMethod 
  		ifTrue: [
  			self parseMessagePattern.
  			self parsePragmaSequence].
  	self parseMethodTemporaries.
  	isAMethod ifTrue: [self parsePragmaSequence].
  	self parseStatementList.
  	currentToken ifNotNil: [self error]]
  		ensure:[errorBlock := nil].
  	^true!

Item was changed:
  ----- Method: SHParserST80>>parseSymbolString (in category 'parse') -----
  parseSymbolString
  	| first c last |
  	first := sourcePosition.
  	self nextChar.
+ 	[(c := self currentChar) 
+ 		ifNil: [
- 	[(c := self currentChar) isNil 
- 		ifTrue: [
  			self rangeType: #unfinishedString start: first end: source size.
  			self error	": 'unfinished string'"].
  	c ~~ $' or: [
  		self peekChar == $' 
  			ifTrue: [sourcePosition := sourcePosition + 1.true] 
  			ifFalse: [false]]
  	] whileTrue: [sourcePosition := sourcePosition + 1].
  	last := sourcePosition.
  	self nextChar.
  	self scanPast: #stringSymbol start: first - 1 end: last!

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

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



More information about the Packages mailing list