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

commits at source.squeak.org commits at source.squeak.org
Sun Apr 5 21:14:19 UTC 2015


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

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

Name: ShoutCore-ul.44
Author: ul
Time: 5 April 2015, 4:22:05.742 pm
UUID: 28aa2d92-85a0-44e3-ab2e-d865bf2c8807
Ancestors: ShoutCore-eem.43

- various speed improvements

=============== Diff against ShoutCore-eem.43 ===============

Item was changed:
  ----- Method: SHParserST80>>parsingBlockArguments (in category 'token testing') -----
  parsingBlockArguments
+ 	^ranges notEmpty and: [ranges last type == #blockPatternArg]!
- 	^ranges notEmpty and: [ranges last type = #blockPatternArg]!

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: [
  					((encodedCharSet isDigit: (nc := self nextChar)) or: [nc == $- and:[(encodedCharSet isDigit: self peekChar)]]) 
  						ifFalse: [sourcePosition := sourcePosition - 1]
  						ifTrue: [self skipDigits]].
+ 			c == $s ifTrue: [
+ 				(encodedCharSet isDigit: (nc := self nextChar))	
+ 					ifTrue: [ self skipDigits ]
+ 					ifFalse: [ 
+ 						(encodedCharSet isLetter: nc) ifTrue: [
+ 							sourcePosition := sourcePosition - 1 ] ] ].
- 			c == $s 
- 				ifTrue: [
- 					(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 == $s 
  		ifTrue: [
  			(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: [
  			(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: [
  			((encodedCharSet isDigit: (nc := self nextChar)) or: [nc == $-  and:[(encodedCharSet isDigit: self peekChar)]]) 
  				ifFalse: [sourcePosition := sourcePosition - 1]
  				ifTrue: [self skipDigits]].
  	c == $s 
  		ifTrue: [
  			(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>>scanWhitespace (in category 'scan') -----
  scanWhitespace
- 	| c |
  	
+ 	(self currentChar ifNil: [ ^self ]) isSeparator ifTrue: [
+ 		sourcePosition := source
+ 			indexOfAnyOf: CharacterSet nonSeparators
+ 			startingAt: sourcePosition + 1
+ 			ifAbsent: [ source size + 1 ] ].
+ 	self currentChar == $" ifTrue: [ self scanComment ]!
- 	[c := self currentChar.
- 	c notNil and: [c isSeparator]] 
- 		whileTrue: [sourcePosition := sourcePosition + 1].
- 	c == $" ifTrue: [self scanComment]!

Item was added:
+ ----- Method: SHRange>>printOn: (in category 'accessing') -----
+ printOn: stream
+ 
+ 	super printOn: stream.
+ 	stream
+ 		nextPut: $(;
+ 		print: type;
+ 		nextPutAll: ', ';
+ 		print: start;
+ 		nextPutAll: ', ';
+ 		print: end;
+ 		nextPut: $)!

Item was changed:
  SHTextStyler subclass: #SHTextStylerST80
+ 	instanceVariableNames: 'classOrMetaClass workspace font parser formatAssignments environment sourceMap processedSourceMap pixelHeight attributesByPixelHeight'
- 	instanceVariableNames: 'classOrMetaClass workspace font parser formatAssignments environment sourceMap processedSourceMap pixelHeight'
  	classVariableNames: 'SubduedSyntaxHighlights SyntaxHighlightingAsYouType SyntaxHighlightingAsYouTypeAnsiAssignment SyntaxHighlightingAsYouTypeLeftArrowAssignment'
  	poolDictionaries: ''
  	category: 'ShoutCore-Styling'!
  SHTextStylerST80 class
  	instanceVariableNames: 'styleTable textAttributesByPixelHeight'!
  
  !SHTextStylerST80 commentStamp: 'tween 8/27/2004 10:55' prior: 0!
  I style Smalltalk methods and expressions.
  
  My 'styleTable' class instance var holds an array ofArrays which control how each token is styled/coloured. See my defaultStyleTable class method for its structure.
  My styleTable can be changed by either modifying the defaultStyleTable class method and then executing SHTextStylerST80 initialize ; or by giving me a new styleTable through my #styleTable: class method.
  
  My 'textAttributesByPixelSize' class instance var contains a dictionary of dictionaries.
  	The key is a pixelSize and the value a Dictionary from token type Symbol to TextAttribute array.
  	It is created/maintained automatically.
  	
  I also install these 3 preferences when my class initialize method is executed....
  	#syntaxHighlightingAsYouType  - controls whether methods are styled in browsers
  	#syntaxHighlightingAsYouTypeAnsiAssignment - controls whether assignments are formatted to be :=
  	#syntaxHighlightingAsYouTypeLeftArrowAssignment - controls whether assignments are formatted to be _
  
  I reimplement #unstyledTextFrom: so that TextActions are preserved in the unstyled text 
  	
  	
  	
  	
  	 
  	
  !
  SHTextStylerST80 class
  	instanceVariableNames: 'styleTable textAttributesByPixelHeight'!

Item was added:
+ ----- Method: SHTextStylerST80 class>>attributesByPixelHeight: (in category 'style table') -----
+ attributesByPixelHeight: aNumber
+ 
+ 	^self textAttributesByPixelHeight 
+ 		at: aNumber 
+ 		ifAbsent: [
+ 			| result |
+ 			result := self initialTextAttributesForPixelHeight: aNumber.
+ 			" thread safety first "
+ 			textAttributesByPixelHeight := textAttributesByPixelHeight copy
+ 				at: aNumber put: result;
+ 				yourself.
+ 			result ]!

Item was changed:
  ----- Method: SHTextStylerST80>>attributesFor: (in category 'private') -----
+ attributesFor: aSymbol
+ 
+ 	^(attributesByPixelHeight ifNil: [
+ 		attributesByPixelHeight := self class attributesByPixelHeight: self pixelHeight ])
+ 		at: aSymbol
+ 		ifAbsent: nil!
- attributesFor: aSymbol 
- 	^self class attributesFor: aSymbol pixelHeight: self pixelHeight
- 	!

Item was changed:
  ----- Method: SHTextStylerST80>>shouldPreserveAttribute: (in category 'private') -----
  shouldPreserveAttribute: aTextAttribute
  	"Answer true if Shout should preserve ALL the attributes in the same run as the argument,
  	false otherwise"
+ 	^aTextAttribute shoutShouldPreserve!
- 	(aTextAttribute respondsTo: #shoutShouldPreserve) 
- 		ifTrue:[^ aTextAttribute shoutShouldPreserve].
- 	^aTextAttribute isMemberOf: TextAction!

Item was added:
+ ----- Method: TextAction>>shoutShouldPreserve (in category '*ShoutCore') -----
+ shoutShouldPreserve
+ 
+ 	^self class == TextAction!

Item was added:
+ ----- Method: TextAttribute>>shoutShouldPreserve (in category '*ShoutCore') -----
+ shoutShouldPreserve
+ 
+ 	^false!



More information about the Packages mailing list