Proposal: Simplify How Pragmas are stored

MD
Marcus Denker
Wed, Mar 24, 2021 1:11 PM

In Pharo9, we have speed up Pragma access.

https://blog.marcusdenker.de/speeding-up-pragma-access
https://blog.marcusdenker.de/speeding-up-pragma-access-part-ii

I think we further improve things, this time with regard to how Pragmas are stored in the method objects.

Describe the problem
Pragmas are stored mixed with associations in the AdditionalMethodState. I propose to store all Pragmas as one pre-allocated
array as a property #pragmas instead.

This will speedup both pragma access and property access and will radically simplify the code.

Classes involved
CompiledMethod, AdditionalMethodState, Compiler backed

Current Situation

This is how Pragmas are now stored. It is a bit strange:

  • if there is a pragma, we create a method with an AdditionalMethodState object, referenced from the second-last literal.
  • This is a variable subclass, implementing a dictionary, no hashing, just linear search  (that is ok as dicts <10 are faster without hashing most likely)
  • What is very strange: it contains associations (for properties) and Pragmas, mixed.

This means that all code very odd as it has to always check:


 propertyAt: aKey ifAbsent: aBlock
	"Answer the property value associated with aKey or, if aKey isn't found, answer the result of evaluating aBlock."
	1 to: self basicSize do: [:i |
		| propertyOrPragma "<Association|Pragma>" |
		propertyOrPragma := self basicAt: i.
		(propertyOrPragma isAssociation
		 and: [propertyOrPragma key == aKey]) ifTrue:
			[^propertyOrPragma value]].
	^aBlock value

while we have a second api that gives us either a pragma or a property, whatever it finds first:

   at: aKey ifAbsent: aBlock
	"Answer the property value or pragma associated with aKey or,
	 if aKey isnt found, answer the result of evaluating aBlock."

	1 to: self basicSize do:
		[:i |
		| propertyOrPragma "<Association|Pragma>" |
		(propertyOrPragma := self basicAt: i) key == aKey ifTrue:
			[^propertyOrPragma isAssociation
				ifTrue: [propertyOrPragma value]
				ifFalse: [propertyOrPragma]]].
	^aBlock value

and if you ask for #pragmas (which is the main API), it has to create the array, iterating and checking for each entry:

    pragmas
	"Return the Pragma objects. Properties are stored as Associations"
	^ Array new: self basicSize streamContents: [ :pragmaStream | 
		  1 to: self basicSize do: [ :i | 
			  | propertyOrPragma "<Association|Pragma>" |
			  (propertyOrPragma := self basicAt: i) isAssociation ifFalse: [ 
				  pragmaStream nextPut: propertyOrPragma ] ] ]	
```	

This is slow for pragmas, the array is created on demand. This is slow for properties, as we need to check an skip pragmas when searching.

For speed, the code for pragmas on CompiledMethod has to do that:

```smalltalk
  pragmas
	| selectorOrProperties |
	^(selectorOrProperties := self penultimateLiteral) isMethodProperties
		ifTrue: [selectorOrProperties pragmas]
		ifFalse: [#()]

Just to avoid creating an empty array via the streamContents: method. Which, if you ask for pragmas of all methods, does matter. And this is what "Senders Of" does...

And this is very, very strange. In the past this lead to very odd things like "sender of" for #isFFIMethod giving all method that had the property #isFFIMethod set. (I fixed that already)

I propose to clean this up.

Proposal

I want to have a clear layer: properties are there to add state to CompiledMethods, the Pragma implementation just uses
this lower level layer.

AdditionalMethodState should have no code related to Pragmas.

So instead of putting pragmas into the AdditionalMethodState directly, we just add one property #pragmas for those methods
where pragmas are used. The compiler then pre-allocates the array and puts it there. (Pragmas are statically known, properties
can be set and removed at runtime).

Which means that on CompiledMethod, we just have:

pragmas
	^ self propertyAt: #pragmas ifAbsent: [ #() ]

pragmas and pragmasDo: on AdditionalMethodState can be removed, we can remove the propertyAt* API there and just use
the Dictionary API (which makes sense, as AdditionalMethodState is just a property dictionary with a backpointer)

The only thing we need to do for this to work is to change the code in the compiler backend to be:

addPragma: aPragma

	properties ifNil: [ properties := AdditionalMethodState new ].
	properties
		at: #pragmas
		ifAbsent: [ properties := properties copyWith: #pragmas -> #(  ) ].
	properties
		at: #pragmas
		put: ((properties at: #pragmas) copyWith: aPragma)

(bit ugly... need to use copyWith: as the high level API needs the compiledMethod set in the AdditionalMethodState)

And some smaller changes here and there (e.g. setting the backpointer in pragmas after the compiledMethod is created).

I did first implementation, It seems to work but this showed that we have to take care with the bootrap.
(see here for the closed PR)

In Pharo9, we have speed up Pragma access. https://blog.marcusdenker.de/speeding-up-pragma-access https://blog.marcusdenker.de/speeding-up-pragma-access-part-ii I think we further improve things, this time with regard to how Pragmas are stored in the method objects. **Describe the problem** Pragmas are stored mixed with associations in the AdditionalMethodState. I propose to store all Pragmas as one pre-allocated array as a property #pragmas instead. This will speedup both pragma access and property access and will radically simplify the code. **Classes involved** CompiledMethod, AdditionalMethodState, Compiler backed **Current Situation** This is how Pragmas are now stored. It is a bit strange: - if there is a pragma, we create a method with an AdditionalMethodState object, referenced from the second-last literal. - This is a variable subclass, implementing a dictionary, no hashing, just linear search (that is ok as dicts <10 are faster without hashing most likely) - What is *very* strange: it contains associations (for properties) and Pragmas, mixed. This means that all code very odd as it has to always check: ```smalltalk propertyAt: aKey ifAbsent: aBlock "Answer the property value associated with aKey or, if aKey isn't found, answer the result of evaluating aBlock." 1 to: self basicSize do: [:i | | propertyOrPragma "<Association|Pragma>" | propertyOrPragma := self basicAt: i. (propertyOrPragma isAssociation and: [propertyOrPragma key == aKey]) ifTrue: [^propertyOrPragma value]]. ^aBlock value ``` while we have a second api that gives us either a pragma or a property, whatever it finds first: ```smalltalk at: aKey ifAbsent: aBlock "Answer the property value or pragma associated with aKey or, if aKey isnt found, answer the result of evaluating aBlock." 1 to: self basicSize do: [:i | | propertyOrPragma "<Association|Pragma>" | (propertyOrPragma := self basicAt: i) key == aKey ifTrue: [^propertyOrPragma isAssociation ifTrue: [propertyOrPragma value] ifFalse: [propertyOrPragma]]]. ^aBlock value ``` and if you ask for #pragmas (which is the main API), it has to create the array, iterating and checking for each entry: ```smalltalk pragmas "Return the Pragma objects. Properties are stored as Associations" ^ Array new: self basicSize streamContents: [ :pragmaStream | 1 to: self basicSize do: [ :i | | propertyOrPragma "<Association|Pragma>" | (propertyOrPragma := self basicAt: i) isAssociation ifFalse: [ pragmaStream nextPut: propertyOrPragma ] ] ] ``` This is slow for pragmas, the array is created on demand. This is slow for properties, as we need to check an skip pragmas when searching. For speed, the code for pragmas on CompiledMethod has to do that: ```smalltalk pragmas | selectorOrProperties | ^(selectorOrProperties := self penultimateLiteral) isMethodProperties ifTrue: [selectorOrProperties pragmas] ifFalse: [#()] ``` Just to avoid creating an empty array via the streamContents: method. Which, if you ask for pragmas of all methods, does matter. And this is what "Senders Of" does... And this is very, very strange. In the past this lead to very odd things like "sender of" for #isFFIMethod giving all method that had the property #isFFIMethod set. (I fixed that already) I propose to clean this up. **Proposal** I want to have a clear layer: properties are there to add state to CompiledMethods, the Pragma implementation just uses this lower level layer. AdditionalMethodState should have *no* code related to Pragmas. So instead of putting pragmas into the AdditionalMethodState directly, we just add one property #pragmas for those methods where pragmas are used. The compiler then pre-allocates the array and puts it there. (Pragmas are statically known, properties can be set and removed at runtime). Which means that on CompiledMethod, we just have: ```smalltalk pragmas ^ self propertyAt: #pragmas ifAbsent: [ #() ] ``` pragmas and pragmasDo: on AdditionalMethodState can be removed, we can remove the propertyAt* API there and just use the Dictionary API (which makes sense, as AdditionalMethodState is just a property dictionary with a backpointer) The only thing we need to do for this to work is to change the code in the compiler backend to be: ```smalltalk addPragma: aPragma properties ifNil: [ properties := AdditionalMethodState new ]. properties at: #pragmas ifAbsent: [ properties := properties copyWith: #pragmas -> #( ) ]. properties at: #pragmas put: ((properties at: #pragmas) copyWith: aPragma) ``` (bit ugly... need to use copyWith: as the high level API needs the compiledMethod set in the AdditionalMethodState) And some smaller changes here and there (e.g. setting the backpointer in pragmas after the compiledMethod is created). I did first implementation, It seems to work but this showed that we have to take care with the bootrap. (see [here](https://github.com/pharo-project/pharo/pull/7930/files) for the closed PR)
SP
Sean P. DeNigris
Mon, Apr 5, 2021 2:58 PM

Marcus Denker-4 wrote

This will speedup both pragma access and property access and will
radically simplify the code.

A little over my head, but sounds great!


Cheers,
Sean

Sent from: http://forum.world.st/Pharo-Smalltalk-Developers-f1294837.html

Marcus Denker-4 wrote > This will speedup both pragma access and property access and will > radically simplify the code. A little over my head, but sounds great! ----- Cheers, Sean -- Sent from: http://forum.world.st/Pharo-Smalltalk-Developers-f1294837.html