The Inbox: ShoutCore-mt.78.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
6 messages Options
Reply | Threaded
Open this post in threaded view
|

The Inbox: ShoutCore-mt.78.mcz

commits-2
A new version of ShoutCore was added to project The Inbox:
http://source.squeak.org/inbox/ShoutCore-mt.78.mcz

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

Name: ShoutCore-mt.78
Author: mt
Time: 12 June 2020, 5:28:15.527851 pm
UUID: 7decada5-8996-304c-ba9c-a93b00f0cc33
Ancestors: ShoutCore-mt.77

Complements Compiler-mt.436 (inbox).

Adds a (extension) method-based hook to install custom pragma-parsing methods. Use it to move FFI-specific pragma-parsing, i.e. <apicall: ...> and <cdecl: ...>, into FFI packages.

=============== Diff against ShoutCore-mt.77 ===============

Item was removed:
- ----- Method: SHParserST80>>isTokenExternalFunctionCallingConvention (in category 'token testing') -----
- isTokenExternalFunctionCallingConvention
-
- currentToken ifNil: [ ^false ].
- ^(Smalltalk classNamed: #ExternalFunction)
- ifNil: [ false ]
- ifNotNil: [ :descriptorClass |
- (descriptorClass callingConventionFor: currentToken) notNil ]!

Item was removed:
- ----- 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
- 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 currentTokenType == #name
- ifTrue: [ self parseTemporary: #patternTempVar ]
- ifFalse: [ self parseStringOrSymbol ] ].
- self failUnless: currentToken = '>'.
- self scanPast: #primitiveOrExternalCallEnd!

Item was changed:
+ ----- Method: SHParserST80>>parsePragmaBinary (in category 'parse pragma') -----
- ----- Method: SHParserST80>>parsePragmaBinary (in category 'parse') -----
  parsePragmaBinary
 
  self scanPast: #pragmaBinary.
  self currentTokenType == #name
  ifTrue:[self scanPast: (self resolvePragmaArgument: currentToken)]
  ifFalse:[ self parseLiteral: false].
  self failUnless: currentToken = '>'.
  self scanPast: #primitiveOrExternalCallEnd!

Item was changed:
+ ----- Method: SHParserST80>>parsePragmaKeyword (in category 'parse pragma') -----
- ----- Method: SHParserST80>>parsePragmaKeyword (in category 'parse') -----
  parsePragmaKeyword
 
  [self currentTokenType == #keyword]
  whileTrue:[
  self scanPast: #pragmaKeyword.
  self currentTokenType == #name
  ifTrue:[self scanPast: (self resolvePragmaArgument: currentToken)]
  ifFalse:[ self parseLiteral: false]].
  self failUnless: currentToken = '>'.
  self scanPast: #primitiveOrExternalCallEnd!

Item was changed:
+ ----- Method: SHParserST80>>parsePragmaSequence (in category 'parse pragma') -----
- ----- Method: SHParserST80>>parsePragmaSequence (in category 'parse') -----
  parsePragmaSequence
+
  [currentToken = '<' ]
+ whileTrue: [
- whileTrue:[
  self scanPast: #primitiveOrExternalCallStart.
+ self parsePragmaStatement].!
- currentToken = 'primitive:'
- ifTrue: [
- self addRangeType: #primitive.
- self parsePrimitive]
- ifFalse:[
- self isTokenExternalFunctionCallingConvention
- ifTrue: [
- self addRangeType: #externalFunctionCallingConvention.
- self parseExternalCall]
- ifFalse:[
- self currentTokenType
- caseOf: {
- [ #name ] -> [
- self scanPast: #pragmaUnary.
- self failUnless: currentToken = '>'.
- self scanPast: #primitiveOrExternalCallEnd ].
- [ #binary ] -> [ self parsePragmaBinary ].
- [ #keyword ] -> [ self parsePragmaKeyword ] }
- otherwise: [ self fail ": 'Invalid External Function Calling convention'" ] ] ] ]!

Item was added:
+ ----- Method: SHParserST80>>parsePragmaStatement (in category 'parse pragma') -----
+ parsePragmaStatement
+
+ | parserSelector parserMethod |
+ currentToken last == $: ifFalse: [
+ "Quick exit to not break one-word pragmas such as <primitive> or <foobar>."
+ ^ self parsePragmaStatementKeywords].
+
+ (self class includesSelector: (parserSelector := currentToken asSimpleGetter)) ifTrue: [
+ ((parserMethod := self class compiledMethodAt: parserSelector) pragmas
+ anySatisfy: [:pragma | pragma keyword == #pragmaParser])
+ ifTrue: [^ self executeMethod: parserMethod]].
+
+ ^ self parsePragmaStatementKeywords!

Item was added:
+ ----- Method: SHParserST80>>parsePragmaStatementKeywords (in category 'parse pragma') -----
+ parsePragmaStatementKeywords
+
+ self currentTokenType
+ caseOf: {
+ [ #name ] -> [
+ self scanPast: #pragmaUnary.
+ self failUnless: currentToken = '>'.
+ self scanPast: #primitiveOrExternalCallEnd ].
+ [ #binary ] -> [ self parsePragmaBinary ].
+ [ #keyword ] -> [ self parsePragmaKeyword ] }
+ otherwise: [ self fail ": 'Invalid External Function Calling convention'" ]. !

Item was removed:
- ----- Method: SHParserST80>>parsePrimitive (in category 'parse') -----
- parsePrimitive
-
- self scanNext.
- currentTokenFirst isDigit
- 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 currentTokenType == #name
- ifTrue: [ self parseTemporary: #patternTempVar ]
- ifFalse: [ self parseStringOrSymbol ] ].
- self failUnless: currentToken = '>'.
- self scanPast: #primitiveOrExternalCallEnd!

Item was added:
+ ----- Method: SHParserST80>>primitive (in category 'parse pragma') -----
+ primitive
+ "Parse keywords and literals of primitive pragmas differently to emit different range tokens for different UI styling. This hook exists so that packages do not break primitive-pragma parsing by accident. Instead, this method needs to be replaced intentionally."
+ <pragmaParser>
+
+ self addRangeType: #primitive.
+
+ self scanNext.
+ currentTokenFirst isDigit
+ 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 currentTokenType == #name
+ ifTrue: [ self parseTemporary: #patternTempVar ]
+ ifFalse: [ self parseStringOrSymbol ] ].
+ self failUnless: currentToken = '>'.
+ self scanPast: #primitiveOrExternalCallEnd!


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: ShoutCore-mt.78.mcz

marcel.taeumel
@Levente: Would this be okay-ish from a performance-perspective? :-)

Best,
Marcel

Am 12.06.2020 17:28:25 schrieb [hidden email] <[hidden email]>:

A new version of ShoutCore was added to project The Inbox:
http://source.squeak.org/inbox/ShoutCore-mt.78.mcz

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

Name: ShoutCore-mt.78
Author: mt
Time: 12 June 2020, 5:28:15.527851 pm
UUID: 7decada5-8996-304c-ba9c-a93b00f0cc33
Ancestors: ShoutCore-mt.77

Complements Compiler-mt.436 (inbox).

Adds a (extension) method-based hook to install custom pragma-parsing methods. Use it to move FFI-specific pragma-parsing, i.e. and , into FFI packages.

=============== Diff against ShoutCore-mt.77 ===============

Item was removed:
- ----- Method: SHParserST80>>isTokenExternalFunctionCallingConvention (in category 'token testing') -----
- isTokenExternalFunctionCallingConvention
-
- currentToken ifNil: [ ^false ].
- ^(Smalltalk classNamed: #ExternalFunction)
- ifNil: [ false ]
- ifNotNil: [ :descriptorClass |
- (descriptorClass callingConventionFor: currentToken) notNil ]!

Item was removed:
- ----- 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
- 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 currentTokenType == #name
- ifTrue: [ self parseTemporary: #patternTempVar ]
- ifFalse: [ self parseStringOrSymbol ] ].
- self failUnless: currentToken = '>'.
- self scanPast: #primitiveOrExternalCallEnd!

Item was changed:
+ ----- Method: SHParserST80>>parsePragmaBinary (in category 'parse pragma') -----
- ----- Method: SHParserST80>>parsePragmaBinary (in category 'parse') -----
parsePragmaBinary

self scanPast: #pragmaBinary.
self currentTokenType == #name
ifTrue:[self scanPast: (self resolvePragmaArgument: currentToken)]
ifFalse:[ self parseLiteral: false].
self failUnless: currentToken = '>'.
self scanPast: #primitiveOrExternalCallEnd!

Item was changed:
+ ----- Method: SHParserST80>>parsePragmaKeyword (in category 'parse pragma') -----
- ----- Method: SHParserST80>>parsePragmaKeyword (in category 'parse') -----
parsePragmaKeyword

[self currentTokenType == #keyword]
whileTrue:[
self scanPast: #pragmaKeyword.
self currentTokenType == #name
ifTrue:[self scanPast: (self resolvePragmaArgument: currentToken)]
ifFalse:[ self parseLiteral: false]].
self failUnless: currentToken = '>'.
self scanPast: #primitiveOrExternalCallEnd!

Item was changed:
+ ----- Method: SHParserST80>>parsePragmaSequence (in category 'parse pragma') -----
- ----- Method: SHParserST80>>parsePragmaSequence (in category 'parse') -----
parsePragmaSequence
+
[currentToken = '<'>
+ whileTrue: [
- whileTrue:[
self scanPast: #primitiveOrExternalCallStart.
+ self parsePragmaStatement].!
- currentToken = 'primitive:'
- ifTrue: [
- self addRangeType: #primitive.
- self parsePrimitive]
- ifFalse:[
- self isTokenExternalFunctionCallingConvention
- ifTrue: [
- self addRangeType: #externalFunctionCallingConvention.
- self parseExternalCall]
- ifFalse:[
- self currentTokenType
- caseOf: {
- [ #name ] -> [
- self scanPast: #pragmaUnary.
- self failUnless: currentToken = '>'.
- self scanPast: #primitiveOrExternalCallEnd ].
- [ #binary ] -> [ self parsePragmaBinary ].
- [ #keyword ] -> [ self parsePragmaKeyword ] }
- otherwise: [ self fail ": 'Invalid External Function Calling convention'" ] ] ] ]!

Item was added:
+ ----- Method: SHParserST80>>parsePragmaStatement (in category 'parse pragma') -----
+ parsePragmaStatement
+
+ | parserSelector parserMethod |
+ currentToken last == $: ifFalse: [
+ "Quick exit to not break one-word pragmas such as or ."
+ ^ self parsePragmaStatementKeywords].
+
+ (self class includesSelector: (parserSelector := currentToken asSimpleGetter)) ifTrue: [
+ ((parserMethod := self class compiledMethodAt: parserSelector) pragmas
+ anySatisfy: [:pragma | pragma keyword == #pragmaParser])
+ ifTrue: [^ self executeMethod: parserMethod]].
+
+ ^ self parsePragmaStatementKeywords!

Item was added:
+ ----- Method: SHParserST80>>parsePragmaStatementKeywords (in category 'parse pragma') -----
+ parsePragmaStatementKeywords
+
+ self currentTokenType
+ caseOf: {
+ [ #name ] -> [
+ self scanPast: #pragmaUnary.
+ self failUnless: currentToken = '>'.
+ self scanPast: #primitiveOrExternalCallEnd ].
+ [ #binary ] -> [ self parsePragmaBinary ].
+ [ #keyword ] -> [ self parsePragmaKeyword ] }
+ otherwise: [ self fail ": 'Invalid External Function Calling convention'" ]. !

Item was removed:
- ----- Method: SHParserST80>>parsePrimitive (in category 'parse') -----
- parsePrimitive
-
- self scanNext.
- currentTokenFirst isDigit
- 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 currentTokenType == #name
- ifTrue: [ self parseTemporary: #patternTempVar ]
- ifFalse: [ self parseStringOrSymbol ] ].
- self failUnless: currentToken = '>'.
- self scanPast: #primitiveOrExternalCallEnd!

Item was added:
+ ----- Method: SHParserST80>>primitive (in category 'parse pragma') -----
+ primitive
+ "Parse keywords and literals of primitive pragmas differently to emit different range tokens for different UI styling. This hook exists so that packages do not break primitive-pragma parsing by accident. Instead, this method needs to be replaced intentionally."
+
+
+ self addRangeType: #primitive.
+
+ self scanNext.
+ currentTokenFirst isDigit
+ 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 currentTokenType == #name
+ ifTrue: [ self parseTemporary: #patternTempVar ]
+ ifFalse: [ self parseStringOrSymbol ] ].
+ self failUnless: currentToken = '>'.
+ self scanPast: #primitiveOrExternalCallEnd!




Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: ShoutCore-mt.78.mcz

marcel.taeumel
Hi all!

I made some benchmarks. While I haven't got the slowest machine here, it gives a rough impression of the performance impact of this extension hook I proposed.

What is currently a simple message send, will be replaced by a lookup mechanism that dispatches the method dictionary manually. Here are the extra operations in a nutshell from SHParserST80 >> #parsePragmaStatement

currentToken last == $:
currentToken asSimpleGetter
self class includesSelector:
self class compiledMethodAt:
CompiledMethod >> #pragmas ... anySatisfy:
self executeMethod:

So, there is one linear search for the pragma <pragmaParser> to avoid calling an arbitrary method in Parser. :-) I suppose that #asSimpleGetter could be reduced to #allButLast and maybe Symbol class >> #lookup: can further speed things up.

Here is the benchmark code:

({
   FFITestLibrary >> #ffiPrintString:. "<cdecl...>"
   BitBlt >> #copyBits. "<primitive: ...>"
   ExternalPoolReadWriter >> #fetchFromFile. "1 simple pragma"
   Win32Pool class >> #winver. "9 simple pragmas"
} collect: [:method |
   | source styler |
   source := method getSource.
   styler := SHTextStylerST80 new
      classOrMetaClass: method methodClass.
   (method methodClass name, '>>', method selector)
      -> ((1 to: 3) collect: [:e | [styler styledTextFor: source] bench])]
   as: OrderedDictionary) asJsonString.

Here are the results:

=== BEFORE ===

{
   "FFITestLibrary>>ffiPrintString:":[
      "77,700 per second. 12.9 microseconds per run. 3.0194 % GC time.",
      "77,100 per second. 13 microseconds per run. 3.11938 % GC time.",
      "77,300 per second. 12.9 microseconds per run. 3.35933 % GC time."
   ],
   "BitBlt>>copyBits":[
      "8,020 per second. 125 microseconds per run. 3.15937 % GC time.",
      "7,990 per second. 125 microseconds per run. 3.32 % GC time.",
      "8,030 per second. 125 microseconds per run. 3.24 % GC time."
   ],
   "ExternalPoolReadWriter>>fetchFromFile":[
      "39,200 per second. 25.5 microseconds per run. 2.63947 % GC time.",
      "38,600 per second. 25.9 microseconds per run. 3.28 % GC time.",
      "38,200 per second. 26.2 microseconds per run. 3.04 % GC time."
   ],
   "Win32Pool class>>winver":[
      "23,400 per second. 42.7 microseconds per run. 2.96 % GC time.",
      "23,500 per second. 42.5 microseconds per run. 2.95941 % GC time.",
      "23,600 per second. 42.5 microseconds per run. 2.73945 % GC time."
   ]
}

=== AFTER ===

{
   "FFITestLibrary>>ffiPrintString:":[
      "66,400 per second. 15.1 microseconds per run. 2.85943 % GC time.",
      "66,900 per second. 14.9 microseconds per run. 2.66 % GC time.",
      "69,100 per second. 14.5 microseconds per run. 2.44 % GC time."
   ],
   "BitBlt>>copyBits":[
      "7,610 per second. 131 microseconds per run. 2.81944 % GC time.",
      "7,520 per second. 133 microseconds per run. 2.77944 % GC time.",
      "7,640 per second. 131 microseconds per run. 2.62 % GC time."
   ],
   "ExternalPoolReadWriter>>fetchFromFile":[
      "37,100 per second. 26.9 microseconds per run. 2.03959 % GC time.",
      "36,600 per second. 27.3 microseconds per run. 2.44049 % GC time.",
      "36,800 per second. 27.2 microseconds per run. 2.45951 % GC time."
   ],
   "Win32Pool class>>winver":[
      "19,200 per second. 52.1 microseconds per run. 2.05959 % GC time.",
      "18,900 per second. 52.9 microseconds per run. 1.9796 % GC time.",
      "19,000 per second. 52.6 microseconds per run. 2.2 % GC time."
   ]
}

Best,
Marcel

Am 12.06.2020 17:31:18 schrieb Marcel Taeumel <[hidden email]>:

@Levente: Would this be okay-ish from a performance-perspective? :-)

Best,
Marcel

Am 12.06.2020 17:28:25 schrieb [hidden email] <[hidden email]>:

A new version of ShoutCore was added to project The Inbox:
http://source.squeak.org/inbox/ShoutCore-mt.78.mcz

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

Name: ShoutCore-mt.78
Author: mt
Time: 12 June 2020, 5:28:15.527851 pm
UUID: 7decada5-8996-304c-ba9c-a93b00f0cc33
Ancestors: ShoutCore-mt.77

Complements Compiler-mt.436 (inbox).

Adds a (extension) method-based hook to install custom pragma-parsing methods. Use it to move FFI-specific pragma-parsing, i.e. and , into FFI packages.

=============== Diff against ShoutCore-mt.77 ===============

Item was removed:
- ----- Method: SHParserST80>>isTokenExternalFunctionCallingConvention (in category 'token testing') -----
- isTokenExternalFunctionCallingConvention
-
- currentToken ifNil: [ ^false ].
- ^(Smalltalk classNamed: #ExternalFunction)
- ifNil: [ false ]
- ifNotNil: [ :descriptorClass |
- (descriptorClass callingConventionFor: currentToken) notNil ]!

Item was removed:
- ----- 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
- 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 currentTokenType == #name
- ifTrue: [ self parseTemporary: #patternTempVar ]
- ifFalse: [ self parseStringOrSymbol ] ].
- self failUnless: currentToken = '>'.
- self scanPast: #primitiveOrExternalCallEnd!

Item was changed:
+ ----- Method: SHParserST80>>parsePragmaBinary (in category 'parse pragma') -----
- ----- Method: SHParserST80>>parsePragmaBinary (in category 'parse') -----
parsePragmaBinary

self scanPast: #pragmaBinary.
self currentTokenType == #name
ifTrue:[self scanPast: (self resolvePragmaArgument: currentToken)]
ifFalse:[ self parseLiteral: false].
self failUnless: currentToken = '>'.
self scanPast: #primitiveOrExternalCallEnd!

Item was changed:
+ ----- Method: SHParserST80>>parsePragmaKeyword (in category 'parse pragma') -----
- ----- Method: SHParserST80>>parsePragmaKeyword (in category 'parse') -----
parsePragmaKeyword

[self currentTokenType == #keyword]
whileTrue:[
self scanPast: #pragmaKeyword.
self currentTokenType == #name
ifTrue:[self scanPast: (self resolvePragmaArgument: currentToken)]
ifFalse:[ self parseLiteral: false]].
self failUnless: currentToken = '>'.
self scanPast: #primitiveOrExternalCallEnd!

Item was changed:
+ ----- Method: SHParserST80>>parsePragmaSequence (in category 'parse pragma') -----
- ----- Method: SHParserST80>>parsePragmaSequence (in category 'parse') -----
parsePragmaSequence
+
[currentToken = '<'>
+ whileTrue: [
- whileTrue:[
self scanPast: #primitiveOrExternalCallStart.
+ self parsePragmaStatement].!
- currentToken = 'primitive:'
- ifTrue: [
- self addRangeType: #primitive.
- self parsePrimitive]
- ifFalse:[
- self isTokenExternalFunctionCallingConvention
- ifTrue: [
- self addRangeType: #externalFunctionCallingConvention.
- self parseExternalCall]
- ifFalse:[
- self currentTokenType
- caseOf: {
- [ #name ] -> [
- self scanPast: #pragmaUnary.
- self failUnless: currentToken = '>'.
- self scanPast: #primitiveOrExternalCallEnd ].
- [ #binary ] -> [ self parsePragmaBinary ].
- [ #keyword ] -> [ self parsePragmaKeyword ] }
- otherwise: [ self fail ": 'Invalid External Function Calling convention'" ] ] ] ]!

Item was added:
+ ----- Method: SHParserST80>>parsePragmaStatement (in category 'parse pragma') -----
+ parsePragmaStatement
+
+ | parserSelector parserMethod |
+ currentToken last == $: ifFalse: [
+ "Quick exit to not break one-word pragmas such as or ."
+ ^ self parsePragmaStatementKeywords].
+
+ (self class includesSelector: (parserSelector := currentToken asSimpleGetter)) ifTrue: [
+ ((parserMethod := self class compiledMethodAt: parserSelector) pragmas
+ anySatisfy: [:pragma | pragma keyword == #pragmaParser])
+ ifTrue: [^ self executeMethod: parserMethod]].
+
+ ^ self parsePragmaStatementKeywords!

Item was added:
+ ----- Method: SHParserST80>>parsePragmaStatementKeywords (in category 'parse pragma') -----
+ parsePragmaStatementKeywords
+
+ self currentTokenType
+ caseOf: {
+ [ #name ] -> [
+ self scanPast: #pragmaUnary.
+ self failUnless: currentToken = '>'.
+ self scanPast: #primitiveOrExternalCallEnd ].
+ [ #binary ] -> [ self parsePragmaBinary ].
+ [ #keyword ] -> [ self parsePragmaKeyword ] }
+ otherwise: [ self fail ": 'Invalid External Function Calling convention'" ]. !

Item was removed:
- ----- Method: SHParserST80>>parsePrimitive (in category 'parse') -----
- parsePrimitive
-
- self scanNext.
- currentTokenFirst isDigit
- 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 currentTokenType == #name
- ifTrue: [ self parseTemporary: #patternTempVar ]
- ifFalse: [ self parseStringOrSymbol ] ].
- self failUnless: currentToken = '>'.
- self scanPast: #primitiveOrExternalCallEnd!

Item was added:
+ ----- Method: SHParserST80>>primitive (in category 'parse pragma') -----
+ primitive
+ "Parse keywords and literals of primitive pragmas differently to emit different range tokens for different UI styling. This hook exists so that packages do not break primitive-pragma parsing by accident. Instead, this method needs to be replaced intentionally."
+
+
+ self addRangeType: #primitive.
+
+ self scanNext.
+ currentTokenFirst isDigit
+ 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 currentTokenType == #name
+ ifTrue: [ self parseTemporary: #patternTempVar ]
+ ifFalse: [ self parseStringOrSymbol ] ].
+ self failUnless: currentToken = '>'.
+ self scanPast: #primitiveOrExternalCallEnd!




Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: ShoutCore-mt.78.mcz

marcel.taeumel
Hi all!

I made some tweaks to further speed-up the manual method lookup. The extra operations are now as follows:

currentToken last == $:
Symbol lookup: currentToken allButLast
self class methodDict at: ifPresent:
method pragmas anySatisfy ...
self executeMethod:

As it is now, it is a fairly generic way to re-direct method dispatch based on two information: (1) string token that is already interned as symbol and (2) a pragma that is in a method with that symbol as selector. I suppose there are other places in the system that could be modularized with such a mechanism. Not sure whether it is worthwhile outside a string-parsing context.

Anyway, here are the results for the Shout parser:

=== AFTER (optmized) ===

{
   "FFITestLibrary>>ffiPrintString:":[
      "73,500 per second. 13.6 microseconds per run. 2.78 % GC time.",
      "73,800 per second. 13.6 microseconds per run. 2.46 % GC time.",
      "74,000 per second. 13.5 microseconds per run. 2.43951 % GC time."
   ],
   "BitBlt>>copyBits":[
      "8,050 per second. 124 microseconds per run. 2.42 % GC time.",
      "7,990 per second. 125 microseconds per run. 2.73945 % GC time.",
      "8,040 per second. 124 microseconds per run. 2.65947 % GC time."
   ],
   "ExternalPoolReadWriter>>fetchFromFile":[
      "39,700 per second. 25.2 microseconds per run. 2.18 % GC time.",
      "39,600 per second. 25.3 microseconds per run. 2.52 % GC time.",
      "39,400 per second. 25.4 microseconds per run. 2.08 % GC time."
   ],
   "Win32Pool class>>winver":[
      "21,600 per second. 46.3 microseconds per run. 2.29954 % GC time.",
      "21,700 per second. 46.2 microseconds per run. 2.3 % GC time.",
      "21,800 per second. 45.9 microseconds per run. 2.28 % GC time."
   ]
}

Best,
Marcel

Am 13.06.2020 10:03:41 schrieb Marcel Taeumel <[hidden email]>:

Hi all!

I made some benchmarks. While I haven't got the slowest machine here, it gives a rough impression of the performance impact of this extension hook I proposed.

What is currently a simple message send, will be replaced by a lookup mechanism that dispatches the method dictionary manually. Here are the extra operations in a nutshell from SHParserST80 >> #parsePragmaStatement

currentToken last == $:
currentToken asSimpleGetter
self class includesSelector:
self class compiledMethodAt:
CompiledMethod >> #pragmas ... anySatisfy:
self executeMethod:

So, there is one linear search for the pragma <pragmaParser> to avoid calling an arbitrary method in Parser. :-) I suppose that #asSimpleGetter could be reduced to #allButLast and maybe Symbol class >> #lookup: can further speed things up.

Here is the benchmark code:

({
   FFITestLibrary >> #ffiPrintString:. "<cdecl...>"
   BitBlt >> #copyBits. "<primitive: ...>"
   ExternalPoolReadWriter >> #fetchFromFile. "1 simple pragma"
   Win32Pool class >> #winver. "9 simple pragmas"
} collect: [:method |
   | source styler |
   source := method getSource.
   styler := SHTextStylerST80 new
      classOrMetaClass: method methodClass.
   (method methodClass name, '>>', method selector)
      -> ((1 to: 3) collect: [:e | [styler styledTextFor: source] bench])]
   as: OrderedDictionary) asJsonString.

Here are the results:

=== BEFORE ===

{
   "FFITestLibrary>>ffiPrintString:":[
      "77,700 per second. 12.9 microseconds per run. 3.0194 % GC time.",
      "77,100 per second. 13 microseconds per run. 3.11938 % GC time.",
      "77,300 per second. 12.9 microseconds per run. 3.35933 % GC time."
   ],
   "BitBlt>>copyBits":[
      "8,020 per second. 125 microseconds per run. 3.15937 % GC time.",
      "7,990 per second. 125 microseconds per run. 3.32 % GC time.",
      "8,030 per second. 125 microseconds per run. 3.24 % GC time."
   ],
   "ExternalPoolReadWriter>>fetchFromFile":[
      "39,200 per second. 25.5 microseconds per run. 2.63947 % GC time.",
      "38,600 per second. 25.9 microseconds per run. 3.28 % GC time.",
      "38,200 per second. 26.2 microseconds per run. 3.04 % GC time."
   ],
   "Win32Pool class>>winver":[
      "23,400 per second. 42.7 microseconds per run. 2.96 % GC time.",
      "23,500 per second. 42.5 microseconds per run. 2.95941 % GC time.",
      "23,600 per second. 42.5 microseconds per run. 2.73945 % GC time."
   ]
}

=== AFTER ===

{
   "FFITestLibrary>>ffiPrintString:":[
      "66,400 per second. 15.1 microseconds per run. 2.85943 % GC time.",
      "66,900 per second. 14.9 microseconds per run. 2.66 % GC time.",
      "69,100 per second. 14.5 microseconds per run. 2.44 % GC time."
   ],
   "BitBlt>>copyBits":[
      "7,610 per second. 131 microseconds per run. 2.81944 % GC time.",
      "7,520 per second. 133 microseconds per run. 2.77944 % GC time.",
      "7,640 per second. 131 microseconds per run. 2.62 % GC time."
   ],
   "ExternalPoolReadWriter>>fetchFromFile":[
      "37,100 per second. 26.9 microseconds per run. 2.03959 % GC time.",
      "36,600 per second. 27.3 microseconds per run. 2.44049 % GC time.",
      "36,800 per second. 27.2 microseconds per run. 2.45951 % GC time."
   ],
   "Win32Pool class>>winver":[
      "19,200 per second. 52.1 microseconds per run. 2.05959 % GC time.",
      "18,900 per second. 52.9 microseconds per run. 1.9796 % GC time.",
      "19,000 per second. 52.6 microseconds per run. 2.2 % GC time."
   ]
}

Best,
Marcel

Am 12.06.2020 17:31:18 schrieb Marcel Taeumel <[hidden email]>:

@Levente: Would this be okay-ish from a performance-perspective? :-)

Best,
Marcel

Am 12.06.2020 17:28:25 schrieb [hidden email] <[hidden email]>:

A new version of ShoutCore was added to project The Inbox:
http://source.squeak.org/inbox/ShoutCore-mt.78.mcz

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

Name: ShoutCore-mt.78
Author: mt
Time: 12 June 2020, 5:28:15.527851 pm
UUID: 7decada5-8996-304c-ba9c-a93b00f0cc33
Ancestors: ShoutCore-mt.77

Complements Compiler-mt.436 (inbox).

Adds a (extension) method-based hook to install custom pragma-parsing methods. Use it to move FFI-specific pragma-parsing, i.e. and , into FFI packages.

=============== Diff against ShoutCore-mt.77 ===============

Item was removed:
- ----- Method: SHParserST80>>isTokenExternalFunctionCallingConvention (in category 'token testing') -----
- isTokenExternalFunctionCallingConvention
-
- currentToken ifNil: [ ^false ].
- ^(Smalltalk classNamed: #ExternalFunction)
- ifNil: [ false ]
- ifNotNil: [ :descriptorClass |
- (descriptorClass callingConventionFor: currentToken) notNil ]!

Item was removed:
- ----- 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
- 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 currentTokenType == #name
- ifTrue: [ self parseTemporary: #patternTempVar ]
- ifFalse: [ self parseStringOrSymbol ] ].
- self failUnless: currentToken = '>'.
- self scanPast: #primitiveOrExternalCallEnd!

Item was changed:
+ ----- Method: SHParserST80>>parsePragmaBinary (in category 'parse pragma') -----
- ----- Method: SHParserST80>>parsePragmaBinary (in category 'parse') -----
parsePragmaBinary

self scanPast: #pragmaBinary.
self currentTokenType == #name
ifTrue:[self scanPast: (self resolvePragmaArgument: currentToken)]
ifFalse:[ self parseLiteral: false].
self failUnless: currentToken = '>'.
self scanPast: #primitiveOrExternalCallEnd!

Item was changed:
+ ----- Method: SHParserST80>>parsePragmaKeyword (in category 'parse pragma') -----
- ----- Method: SHParserST80>>parsePragmaKeyword (in category 'parse') -----
parsePragmaKeyword

[self currentTokenType == #keyword]
whileTrue:[
self scanPast: #pragmaKeyword.
self currentTokenType == #name
ifTrue:[self scanPast: (self resolvePragmaArgument: currentToken)]
ifFalse:[ self parseLiteral: false]].
self failUnless: currentToken = '>'.
self scanPast: #primitiveOrExternalCallEnd!

Item was changed:
+ ----- Method: SHParserST80>>parsePragmaSequence (in category 'parse pragma') -----
- ----- Method: SHParserST80>>parsePragmaSequence (in category 'parse') -----
parsePragmaSequence
+
[currentToken = '<'>
+ whileTrue: [
- whileTrue:[
self scanPast: #primitiveOrExternalCallStart.
+ self parsePragmaStatement].!
- currentToken = 'primitive:'
- ifTrue: [
- self addRangeType: #primitive.
- self parsePrimitive]
- ifFalse:[
- self isTokenExternalFunctionCallingConvention
- ifTrue: [
- self addRangeType: #externalFunctionCallingConvention.
- self parseExternalCall]
- ifFalse:[
- self currentTokenType
- caseOf: {
- [ #name ] -> [
- self scanPast: #pragmaUnary.
- self failUnless: currentToken = '>'.
- self scanPast: #primitiveOrExternalCallEnd ].
- [ #binary ] -> [ self parsePragmaBinary ].
- [ #keyword ] -> [ self parsePragmaKeyword ] }
- otherwise: [ self fail ": 'Invalid External Function Calling convention'" ] ] ] ]!

Item was added:
+ ----- Method: SHParserST80>>parsePragmaStatement (in category 'parse pragma') -----
+ parsePragmaStatement
+
+ | parserSelector parserMethod |
+ currentToken last == $: ifFalse: [
+ "Quick exit to not break one-word pragmas such as or ."
+ ^ self parsePragmaStatementKeywords].
+
+ (self class includesSelector: (parserSelector := currentToken asSimpleGetter)) ifTrue: [
+ ((parserMethod := self class compiledMethodAt: parserSelector) pragmas
+ anySatisfy: [:pragma | pragma keyword == #pragmaParser])
+ ifTrue: [^ self executeMethod: parserMethod]].
+
+ ^ self parsePragmaStatementKeywords!

Item was added:
+ ----- Method: SHParserST80>>parsePragmaStatementKeywords (in category 'parse pragma') -----
+ parsePragmaStatementKeywords
+
+ self currentTokenType
+ caseOf: {
+ [ #name ] -> [
+ self scanPast: #pragmaUnary.
+ self failUnless: currentToken = '>'.
+ self scanPast: #primitiveOrExternalCallEnd ].
+ [ #binary ] -> [ self parsePragmaBinary ].
+ [ #keyword ] -> [ self parsePragmaKeyword ] }
+ otherwise: [ self fail ": 'Invalid External Function Calling convention'" ]. !

Item was removed:
- ----- Method: SHParserST80>>parsePrimitive (in category 'parse') -----
- parsePrimitive
-
- self scanNext.
- currentTokenFirst isDigit
- 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 currentTokenType == #name
- ifTrue: [ self parseTemporary: #patternTempVar ]
- ifFalse: [ self parseStringOrSymbol ] ].
- self failUnless: currentToken = '>'.
- self scanPast: #primitiveOrExternalCallEnd!

Item was added:
+ ----- Method: SHParserST80>>primitive (in category 'parse pragma') -----
+ primitive
+ "Parse keywords and literals of primitive pragmas differently to emit different range tokens for different UI styling. This hook exists so that packages do not break primitive-pragma parsing by accident. Instead, this method needs to be replaced intentionally."
+
+
+ self addRangeType: #primitive.
+
+ self scanNext.
+ currentTokenFirst isDigit
+ 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 currentTokenType == #name
+ ifTrue: [ self parseTemporary: #patternTempVar ]
+ ifFalse: [ self parseStringOrSymbol ] ].
+ self failUnless: currentToken = '>'.
+ self scanPast: #primitiveOrExternalCallEnd!




Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: ShoutCore-mt.78.mcz

Levente Uzonyi
Hi Marcel,

The numbers look good to me and the code too.


Levente

On Sat, 13 Jun 2020, Marcel Taeumel wrote:

> Hi all!
>
> I made some tweaks to further speed-up the manual method lookup. The extra operations are now as follows:
>
> currentToken last == $:
> Symbol lookup: currentToken allButLast
> self class methodDict at: ifPresent:
> method pragmas anySatisfy ...
> self executeMethod:
>
> As it is now, it is a fairly generic way to re-direct method dispatch based on two information: (1) string token that is already interned as symbol and (2) a pragma that is in a method with that symbol as selector. I suppose
> there are other places in the system that could be modularized with such a mechanism. Not sure whether it is worthwhile outside a string-parsing context.
>
> Anyway, here are the results for the Shout parser:
>
> === AFTER (optmized) ===
>
> {
>    "FFITestLibrary>>ffiPrintString:":[
>       "73,500 per second. 13.6 microseconds per run. 2.78 % GC time.",
>       "73,800 per second. 13.6 microseconds per run. 2.46 % GC time.",
>       "74,000 per second. 13.5 microseconds per run. 2.43951 % GC time."
>    ],
>    "BitBlt>>copyBits":[
>       "8,050 per second. 124 microseconds per run. 2.42 % GC time.",
>       "7,990 per second. 125 microseconds per run. 2.73945 % GC time.",
>       "8,040 per second. 124 microseconds per run. 2.65947 % GC time."
>    ],
>    "ExternalPoolReadWriter>>fetchFromFile":[
>       "39,700 per second. 25.2 microseconds per run. 2.18 % GC time.",
>       "39,600 per second. 25.3 microseconds per run. 2.52 % GC time.",
>       "39,400 per second. 25.4 microseconds per run. 2.08 % GC time."
>    ],
>    "Win32Pool class>>winver":[
>       "21,600 per second. 46.3 microseconds per run. 2.29954 % GC time.",
>       "21,700 per second. 46.2 microseconds per run. 2.3 % GC time.",
>       "21,800 per second. 45.9 microseconds per run. 2.28 % GC time."
>    ]
> }
>
> Best,
> Marcel
>
>       Am 13.06.2020 10:03:41 schrieb Marcel Taeumel <[hidden email]>:
>
>       Hi all!
>
> I made some benchmarks. While I haven't got the slowest machine here, it gives a rough impression of the performance impact of this extension hook I proposed.
>
> What is currently a simple message send, will be replaced by a lookup mechanism that dispatches the method dictionary manually. Here are the extra operations in a nutshell from SHParserST80 >> #parsePragmaStatement
>
> currentToken last == $:
> currentToken asSimpleGetter
> self class includesSelector:
> self class compiledMethodAt:
> CompiledMethod >> #pragmas ... anySatisfy:
> self executeMethod:
>
> So, there is one linear search for the pragma <pragmaParser> to avoid calling an arbitrary method in Parser. :-) I suppose that #asSimpleGetter could be reduced to #allButLast and maybe Symbol class >> #lookup: can
> further speed things up.
>
> Here is the benchmark code:
>
> ({
>    FFITestLibrary >> #ffiPrintString:. "<cdecl...>"
>    BitBlt >> #copyBits. "<primitive: ...>"
>    ExternalPoolReadWriter >> #fetchFromFile. "1 simple pragma"
>    Win32Pool class >> #winver. "9 simple pragmas"
> } collect: [:method |
>    | source styler |
>    source := method getSource.
>    styler := SHTextStylerST80 new
>       classOrMetaClass: method methodClass.
>    (method methodClass name, '>>', method selector)
>       -> ((1 to: 3) collect: [:e | [styler styledTextFor: source] bench])]
>    as: OrderedDictionary) asJsonString.
>
> Here are the results:
>
> === BEFORE ===
>
> {
>    "FFITestLibrary>>ffiPrintString:":[
>       "77,700 per second. 12.9 microseconds per run. 3.0194 % GC time.",
>       "77,100 per second. 13 microseconds per run. 3.11938 % GC time.",
>       "77,300 per second. 12.9 microseconds per run. 3.35933 % GC time."
>    ],
>    "BitBlt>>copyBits":[
>       "8,020 per second. 125 microseconds per run. 3.15937 % GC time.",
>       "7,990 per second. 125 microseconds per run. 3.32 % GC time.",
>       "8,030 per second. 125 microseconds per run. 3.24 % GC time."
>    ],
>    "ExternalPoolReadWriter>>fetchFromFile":[
>       "39,200 per second. 25.5 microseconds per run. 2.63947 % GC time.",
>       "38,600 per second. 25.9 microseconds per run. 3.28 % GC time.",
>       "38,200 per second. 26.2 microseconds per run. 3.04 % GC time."
>    ],
>    "Win32Pool class>>winver":[
>       "23,400 per second. 42.7 microseconds per run. 2.96 % GC time.",
>       "23,500 per second. 42.5 microseconds per run. 2.95941 % GC time.",
>       "23,600 per second. 42.5 microseconds per run. 2.73945 % GC time."
>    ]
> }
>
> === AFTER ===
>
> {
>    "FFITestLibrary>>ffiPrintString:":[
>       "66,400 per second. 15.1 microseconds per run. 2.85943 % GC time.",
>       "66,900 per second. 14.9 microseconds per run. 2.66 % GC time.",
>       "69,100 per second. 14.5 microseconds per run. 2.44 % GC time."
>    ],
>    "BitBlt>>copyBits":[
>       "7,610 per second. 131 microseconds per run. 2.81944 % GC time.",
>       "7,520 per second. 133 microseconds per run. 2.77944 % GC time.",
>       "7,640 per second. 131 microseconds per run. 2.62 % GC time."
>    ],
>    "ExternalPoolReadWriter>>fetchFromFile":[
>       "37,100 per second. 26.9 microseconds per run. 2.03959 % GC time.",
>       "36,600 per second. 27.3 microseconds per run. 2.44049 % GC time.",
>       "36,800 per second. 27.2 microseconds per run. 2.45951 % GC time."
>    ],
>    "Win32Pool class>>winver":[
>       "19,200 per second. 52.1 microseconds per run. 2.05959 % GC time.",
>       "18,900 per second. 52.9 microseconds per run. 1.9796 % GC time.",
>       "19,000 per second. 52.6 microseconds per run. 2.2 % GC time."
>    ]
> }
>
> Best,
> Marcel
>
>       Am 12.06.2020 17:31:18 schrieb Marcel Taeumel <[hidden email]>:
>
>       @Levente: Would this be okay-ish from a performance-perspective? :-)
> Best,
> Marcel
>
>       Am 12.06.2020 17:28:25 schrieb [hidden email] <[hidden email]>:
>
>       A new version of ShoutCore was added to project The Inbox:
>       http://source.squeak.org/inbox/ShoutCore-mt.78.mcz
>
>       ==================== Summary ====================
>
>       Name: ShoutCore-mt.78
>       Author: mt
>       Time: 12 June 2020, 5:28:15.527851 pm
>       UUID: 7decada5-8996-304c-ba9c-a93b00f0cc33
>       Ancestors: ShoutCore-mt.77
>
>       Complements Compiler-mt.436 (inbox).
>
>       Adds a (extension) method-based hook to install custom pragma-parsing methods. Use it to move FFI-specific pragma-parsing, i.e. and , into FFI packages.
>
>       =============== Diff against ShoutCore-mt.77 ===============
>
>       Item was removed:
>       - ----- Method: SHParserST80>>isTokenExternalFunctionCallingConvention (in category 'token testing') -----
>       - isTokenExternalFunctionCallingConvention
>       -
>       - currentToken ifNil: [ ^false ].
>       - ^(Smalltalk classNamed: #ExternalFunction)
>       - ifNil: [ false ]
>       - ifNotNil: [ :descriptorClass |
>       - (descriptorClass callingConventionFor: currentToken) notNil ]!
>
>       Item was removed:
>       - ----- 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
>       - 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 currentTokenType == #name
>       - ifTrue: [ self parseTemporary: #patternTempVar ]
>       - ifFalse: [ self parseStringOrSymbol ] ].
>       - self failUnless: currentToken = '>'.
>       - self scanPast: #primitiveOrExternalCallEnd!
>
>       Item was changed:
>       + ----- Method: SHParserST80>>parsePragmaBinary (in category 'parse pragma') -----
>       - ----- Method: SHParserST80>>parsePragmaBinary (in category 'parse') -----
>       parsePragmaBinary
>
>       self scanPast: #pragmaBinary.
>       self currentTokenType == #name
>       ifTrue:[self scanPast: (self resolvePragmaArgument: currentToken)]
>       ifFalse:[ self parseLiteral: false].
>       self failUnless: currentToken = '>'.
>       self scanPast: #primitiveOrExternalCallEnd!
>
>       Item was changed:
>       + ----- Method: SHParserST80>>parsePragmaKeyword (in category 'parse pragma') -----
>       - ----- Method: SHParserST80>>parsePragmaKeyword (in category 'parse') -----
>       parsePragmaKeyword
>
>       [self currentTokenType == #keyword]
>       whileTrue:[
>       self scanPast: #pragmaKeyword.
>       self currentTokenType == #name
>       ifTrue:[self scanPast: (self resolvePragmaArgument: currentToken)]
>       ifFalse:[ self parseLiteral: false]].
>       self failUnless: currentToken = '>'.
>       self scanPast: #primitiveOrExternalCallEnd!
>
>       Item was changed:
>       + ----- Method: SHParserST80>>parsePragmaSequence (in category 'parse pragma') -----
>       - ----- Method: SHParserST80>>parsePragmaSequence (in category 'parse') -----
>       parsePragmaSequence
>       +
>       [currentToken = '<'><'>
>       + whileTrue: [
>       - whileTrue:[
>       self scanPast: #primitiveOrExternalCallStart.
>       + self parsePragmaStatement].!
>       - currentToken = 'primitive:'
>       - ifTrue: [
>       - self addRangeType: #primitive.
>       - self parsePrimitive]
>       - ifFalse:[
>       - self isTokenExternalFunctionCallingConvention
>       - ifTrue: [
>       - self addRangeType: #externalFunctionCallingConvention.
>       - self parseExternalCall]
>       - ifFalse:[
>       - self currentTokenType
>       - caseOf: {
>       - [ #name ] -> [
>       - self scanPast: #pragmaUnary.
>       - self failUnless: currentToken = '>'.
>       - self scanPast: #primitiveOrExternalCallEnd ].
>       - [ #binary ] -> [ self parsePragmaBinary ].
>       - [ #keyword ] -> [ self parsePragmaKeyword ] }
>       - otherwise: [ self fail ": 'Invalid External Function Calling convention'" ] ] ] ]!
>
>       Item was added:
>       + ----- Method: SHParserST80>>parsePragmaStatement (in category 'parse pragma') -----
>       + parsePragmaStatement
>       +
>       + | parserSelector parserMethod |
>       + currentToken last == $: ifFalse: [
>       + "Quick exit to not break one-word pragmas such as or ."
>       + ^ self parsePragmaStatementKeywords].
>       +
>       + (self class includesSelector: (parserSelector := currentToken asSimpleGetter)) ifTrue: [
>       + ((parserMethod := self class compiledMethodAt: parserSelector) pragmas
>       + anySatisfy: [:pragma | pragma keyword == #pragmaParser])
>       + ifTrue: [^ self executeMethod: parserMethod]].
>       +
>       + ^ self parsePragmaStatementKeywords!
>
>       Item was added:
>       + ----- Method: SHParserST80>>parsePragmaStatementKeywords (in category 'parse pragma') -----
>       + parsePragmaStatementKeywords
>       +
>       + self currentTokenType
>       + caseOf: {
>       + [ #name ] -> [
>       + self scanPast: #pragmaUnary.
>       + self failUnless: currentToken = '>'.
>       + self scanPast: #primitiveOrExternalCallEnd ].
>       + [ #binary ] -> [ self parsePragmaBinary ].
>       + [ #keyword ] -> [ self parsePragmaKeyword ] }
>       + otherwise: [ self fail ": 'Invalid External Function Calling convention'" ]. !
>
>       Item was removed:
>       - ----- Method: SHParserST80>>parsePrimitive (in category 'parse') -----
>       - parsePrimitive
>       -
>       - self scanNext.
>       - currentTokenFirst isDigit
>       - 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 currentTokenType == #name
>       - ifTrue: [ self parseTemporary: #patternTempVar ]
>       - ifFalse: [ self parseStringOrSymbol ] ].
>       - self failUnless: currentToken = '>'.
>       - self scanPast: #primitiveOrExternalCallEnd!
>
>       Item was added:
>       + ----- Method: SHParserST80>>primitive (in category 'parse pragma') -----
>       + primitive
>       + "Parse keywords and literals of primitive pragmas differently to emit different range tokens for different UI styling. This hook exists so that packages do not break primitive-pragma parsing by
>       accident. Instead, this method needs to be replaced intentionally."
>       +
>       +
>       + self addRangeType: #primitive.
>       +
>       + self scanNext.
>       + currentTokenFirst isDigit
>       + 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 currentTokenType == #name
>       + ifTrue: [ self parseTemporary: #patternTempVar ]
>       + ifFalse: [ self parseStringOrSymbol ] ].
>       + self failUnless: currentToken = '>'.
>       + self scanPast: #primitiveOrExternalCallEnd!
>
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: ShoutCore-mt.78.mcz

marcel.taeumel
Hi Levente,

thanks for taking a look at it. :-)

Best,
Marcel

Am 14.06.2020 00:13:05 schrieb Levente Uzonyi <[hidden email]>:

Hi Marcel,

The numbers look good to me and the code too.


Levente

On Sat, 13 Jun 2020, Marcel Taeumel wrote:

> Hi all!
>
> I made some tweaks to further speed-up the manual method lookup. The extra operations are now as follows:
>
> currentToken last == $:
> Symbol lookup: currentToken allButLast
> self class methodDict at: ifPresent:
> method pragmas anySatisfy ...
> self executeMethod:
>
> As it is now, it is a fairly generic way to re-direct method dispatch based on two information: (1) string token that is already interned as symbol and (2) a pragma that is in a method with that symbol as selector. I suppose
> there are other places in the system that could be modularized with such a mechanism. Not sure whether it is worthwhile outside a string-parsing context.
>
> Anyway, here are the results for the Shout parser:
>
> === AFTER (optmized) ===
>
> {
>    "FFITestLibrary>>ffiPrintString:":[
>       "73,500 per second. 13.6 microseconds per run. 2.78 % GC time.",
>       "73,800 per second. 13.6 microseconds per run. 2.46 % GC time.",
>       "74,000 per second. 13.5 microseconds per run. 2.43951 % GC time."
>    ],
>    "BitBlt>>copyBits":[
>       "8,050 per second. 124 microseconds per run. 2.42 % GC time.",
>       "7,990 per second. 125 microseconds per run. 2.73945 % GC time.",
>       "8,040 per second. 124 microseconds per run. 2.65947 % GC time."
>    ],
>    "ExternalPoolReadWriter>>fetchFromFile":[
>       "39,700 per second. 25.2 microseconds per run. 2.18 % GC time.",
>       "39,600 per second. 25.3 microseconds per run. 2.52 % GC time.",
>       "39,400 per second. 25.4 microseconds per run. 2.08 % GC time."
>    ],
>    "Win32Pool class>>winver":[
>       "21,600 per second. 46.3 microseconds per run. 2.29954 % GC time.",
>       "21,700 per second. 46.2 microseconds per run. 2.3 % GC time.",
>       "21,800 per second. 45.9 microseconds per run. 2.28 % GC time."
>    ]
> }
>
> Best,
> Marcel
>
> Am 13.06.2020 10:03:41 schrieb Marcel Taeumel :
>
> Hi all!
>
> I made some benchmarks. While I haven't got the slowest machine here, it gives a rough impression of the performance impact of this extension hook I proposed.
>
> What is currently a simple message send, will be replaced by a lookup mechanism that dispatches the method dictionary manually. Here are the extra operations in a nutshell from SHParserST80 >> #parsePragmaStatement
>
> currentToken last == $:
> currentToken asSimpleGetter
> self class includesSelector:
> self class compiledMethodAt:
> CompiledMethod >> #pragmas ... anySatisfy:
> self executeMethod:
>
> So, there is one linear search for the pragma to avoid calling an arbitrary method in Parser. :-) I suppose that #asSimpleGetter could be reduced to #allButLast and maybe Symbol class >> #lookup: can
> further speed things up.
>
> Here is the benchmark code:
>
> ({
>    FFITestLibrary >> #ffiPrintString:. ""
>    BitBlt >> #copyBits. ""
>    ExternalPoolReadWriter >> #fetchFromFile. "1 simple pragma"
>    Win32Pool class >> #winver. "9 simple pragmas"
> } collect: [:method |
>    | source styler |
>    source := method getSource.
>    styler := SHTextStylerST80 new
>       classOrMetaClass: method methodClass.
>    (method methodClass name, '>>', method selector)
>       -> ((1 to: 3) collect: [:e | [styler styledTextFor: source] bench])]
>    as: OrderedDictionary) asJsonString.
>
> Here are the results:
>
> === BEFORE ===
>
> {
>    "FFITestLibrary>>ffiPrintString:":[
>       "77,700 per second. 12.9 microseconds per run. 3.0194 % GC time.",
>       "77,100 per second. 13 microseconds per run. 3.11938 % GC time.",
>       "77,300 per second. 12.9 microseconds per run. 3.35933 % GC time."
>    ],
>    "BitBlt>>copyBits":[
>       "8,020 per second. 125 microseconds per run. 3.15937 % GC time.",
>       "7,990 per second. 125 microseconds per run. 3.32 % GC time.",
>       "8,030 per second. 125 microseconds per run. 3.24 % GC time."
>    ],
>    "ExternalPoolReadWriter>>fetchFromFile":[
>       "39,200 per second. 25.5 microseconds per run. 2.63947 % GC time.",
>       "38,600 per second. 25.9 microseconds per run. 3.28 % GC time.",
>       "38,200 per second. 26.2 microseconds per run. 3.04 % GC time."
>    ],
>    "Win32Pool class>>winver":[
>       "23,400 per second. 42.7 microseconds per run. 2.96 % GC time.",
>       "23,500 per second. 42.5 microseconds per run. 2.95941 % GC time.",
>       "23,600 per second. 42.5 microseconds per run. 2.73945 % GC time."
>    ]
> }
>
> === AFTER ===
>
> {
>    "FFITestLibrary>>ffiPrintString:":[
>       "66,400 per second. 15.1 microseconds per run. 2.85943 % GC time.",
>       "66,900 per second. 14.9 microseconds per run. 2.66 % GC time.",
>       "69,100 per second. 14.5 microseconds per run. 2.44 % GC time."
>    ],
>    "BitBlt>>copyBits":[
>       "7,610 per second. 131 microseconds per run. 2.81944 % GC time.",
>       "7,520 per second. 133 microseconds per run. 2.77944 % GC time.",
>       "7,640 per second. 131 microseconds per run. 2.62 % GC time."
>    ],
>    "ExternalPoolReadWriter>>fetchFromFile":[
>       "37,100 per second. 26.9 microseconds per run. 2.03959 % GC time.",
>       "36,600 per second. 27.3 microseconds per run. 2.44049 % GC time.",
>       "36,800 per second. 27.2 microseconds per run. 2.45951 % GC time."
>    ],
>    "Win32Pool class>>winver":[
>       "19,200 per second. 52.1 microseconds per run. 2.05959 % GC time.",
>       "18,900 per second. 52.9 microseconds per run. 1.9796 % GC time.",
>       "19,000 per second. 52.6 microseconds per run. 2.2 % GC time."
>    ]
> }
>
> Best,
> Marcel
>
> Am 12.06.2020 17:31:18 schrieb Marcel Taeumel :
>
> @Levente: Would this be okay-ish from a performance-perspective? :-)
> Best,
> Marcel
>
> Am 12.06.2020 17:28:25 schrieb [hidden email] :
>
> A new version of ShoutCore was added to project The Inbox:
> http://source.squeak.org/inbox/ShoutCore-mt.78.mcz
>
> ==================== Summary ====================
>
> Name: ShoutCore-mt.78
> Author: mt
> Time: 12 June 2020, 5:28:15.527851 pm
> UUID: 7decada5-8996-304c-ba9c-a93b00f0cc33
> Ancestors: ShoutCore-mt.77
>
> Complements Compiler-mt.436 (inbox).
>
> Adds a (extension) method-based hook to install custom pragma-parsing methods. Use it to move FFI-specific pragma-parsing, i.e. and , into FFI packages.
>
> =============== Diff against ShoutCore-mt.77 ===============
>
> Item was removed:
> - ----- Method: SHParserST80>>isTokenExternalFunctionCallingConvention (in category 'token testing') -----
> - isTokenExternalFunctionCallingConvention
> -
> - currentToken ifNil: [ ^false ].
> - ^(Smalltalk classNamed: #ExternalFunction)
> - ifNil: [ false ]
> - ifNotNil: [ :descriptorClass |
> - (descriptorClass callingConventionFor: currentToken) notNil ]!
>
> Item was removed:
> - ----- 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
> - 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 currentTokenType == #name
> - ifTrue: [ self parseTemporary: #patternTempVar ]
> - ifFalse: [ self parseStringOrSymbol ] ].
> - self failUnless: currentToken = '>'.
> - self scanPast: #primitiveOrExternalCallEnd!
>
> Item was changed:
> + ----- Method: SHParserST80>>parsePragmaBinary (in category 'parse pragma') -----
> - ----- Method: SHParserST80>>parsePragmaBinary (in category 'parse') -----
> parsePragmaBinary
>
> self scanPast: #pragmaBinary.
> self currentTokenType == #name
> ifTrue:[self scanPast: (self resolvePragmaArgument: currentToken)]
> ifFalse:[ self parseLiteral: false].
> self failUnless: currentToken = '>'.
> self scanPast: #primitiveOrExternalCallEnd!
>
> Item was changed:
> + ----- Method: SHParserST80>>parsePragmaKeyword (in category 'parse pragma') -----
> - ----- Method: SHParserST80>>parsePragmaKeyword (in category 'parse') -----
> parsePragmaKeyword
>
> [self currentTokenType == #keyword]
> whileTrue:[
> self scanPast: #pragmaKeyword.
> self currentTokenType == #name
> ifTrue:[self scanPast: (self resolvePragmaArgument: currentToken)]
> ifFalse:[ self parseLiteral: false]].
> self failUnless: currentToken = '>'.
> self scanPast: #primitiveOrExternalCallEnd!
>
> Item was changed:
> + ----- Method: SHParserST80>>parsePragmaSequence (in category 'parse pragma') -----
> - ----- Method: SHParserST80>>parsePragmaSequence (in category 'parse') -----
> parsePragmaSequence
> +
> [currentToken = '<'><'>
> + whileTrue: [
> - whileTrue:[
> self scanPast: #primitiveOrExternalCallStart.
> + self parsePragmaStatement].!
> - currentToken = 'primitive:'
> - ifTrue: [
> - self addRangeType: #primitive.
> - self parsePrimitive]
> - ifFalse:[
> - self isTokenExternalFunctionCallingConvention
> - ifTrue: [
> - self addRangeType: #externalFunctionCallingConvention.
> - self parseExternalCall]
> - ifFalse:[
> - self currentTokenType
> - caseOf: {
> - [ #name ] -> [
> - self scanPast: #pragmaUnary.
> - self failUnless: currentToken = '>'.
> - self scanPast: #primitiveOrExternalCallEnd ].
> - [ #binary ] -> [ self parsePragmaBinary ].
> - [ #keyword ] -> [ self parsePragmaKeyword ] }
> - otherwise: [ self fail ": 'Invalid External Function Calling convention'" ] ] ] ]!
>
> Item was added:
> + ----- Method: SHParserST80>>parsePragmaStatement (in category 'parse pragma') -----
> + parsePragmaStatement
> +
> + | parserSelector parserMethod |
> + currentToken last == $: ifFalse: [
> + "Quick exit to not break one-word pragmas such as or ."
> + ^ self parsePragmaStatementKeywords].
> +
> + (self class includesSelector: (parserSelector := currentToken asSimpleGetter)) ifTrue: [
> + ((parserMethod := self class compiledMethodAt: parserSelector) pragmas
> + anySatisfy: [:pragma | pragma keyword == #pragmaParser])
> + ifTrue: [^ self executeMethod: parserMethod]].
> +
> + ^ self parsePragmaStatementKeywords!
>
> Item was added:
> + ----- Method: SHParserST80>>parsePragmaStatementKeywords (in category 'parse pragma') -----
> + parsePragmaStatementKeywords
> +
> + self currentTokenType
> + caseOf: {
> + [ #name ] -> [
> + self scanPast: #pragmaUnary.
> + self failUnless: currentToken = '>'.
> + self scanPast: #primitiveOrExternalCallEnd ].
> + [ #binary ] -> [ self parsePragmaBinary ].
> + [ #keyword ] -> [ self parsePragmaKeyword ] }
> + otherwise: [ self fail ": 'Invalid External Function Calling convention'" ]. !
>
> Item was removed:
> - ----- Method: SHParserST80>>parsePrimitive (in category 'parse') -----
> - parsePrimitive
> -
> - self scanNext.
> - currentTokenFirst isDigit
> - 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 currentTokenType == #name
> - ifTrue: [ self parseTemporary: #patternTempVar ]
> - ifFalse: [ self parseStringOrSymbol ] ].
> - self failUnless: currentToken = '>'.
> - self scanPast: #primitiveOrExternalCallEnd!
>
> Item was added:
> + ----- Method: SHParserST80>>primitive (in category 'parse pragma') -----
> + primitive
> + "Parse keywords and literals of primitive pragmas differently to emit different range tokens for different UI styling. This hook exists so that packages do not break primitive-pragma parsing by
> accident. Instead, this method needs to be replaced intentionally."
> +
> +
> + self addRangeType: #primitive.
> +
> + self scanNext.
> + currentTokenFirst isDigit
> + 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 currentTokenType == #name
> + ifTrue: [ self parseTemporary: #patternTempVar ]
> + ifFalse: [ self parseStringOrSymbol ] ].
> + self failUnless: currentToken = '>'.
> + self scanPast: #primitiveOrExternalCallEnd!
>
>
>
>