[squeak-dev] The Trunk: Compiler-eem.418.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Mar 12 01:58:09 UTC 2020


Eliot Miranda uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-eem.418.mcz

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

Name: Compiler-eem.418
Author: eem
Time: 11 March 2020, 6:58:07.871201 pm
UUID: 2e87ec87-7501-451f-88a5-3049d9cebf02
Ancestors: Compiler-nice.417

Enable read-only literals, and set all literals to be read-only via a paxkage postscript which avoids the recompile step.

=============== Diff against Compiler-nice.417 ===============

Item was changed:
  ----- Method: Encoder>>litIndex: (in category 'encoding') -----
  litIndex: literal
  	| p |
  	p := literalStream position.
  	p = self maxNumLiterals ifTrue:
  		[self notify: 'More than ', self maxNumLiterals printString, ' literals referenced.\You must split or otherwise simplify this method.\The ' withCRs, (self maxNumLiterals + 1) printString, 'th literal is: ', literal printString. ^nil].
+ 	literal isLiteral ifTrue: "filters out BlockClosures, ExternalLibraryFunctions"
+ 		[(literal isReadOnlyObject
+ 		 or: [literal isVariableBinding]) ifFalse:
+ 			[literal setIsReadOnlyObject: true]].
  	"Would like to show where it is in the source code, 
  	 but that info is hard to get."
  	literalStream nextPut: literal.
  	^p!

Item was changed:
  ----- Method: Parser>>externalFunctionDeclaration (in category 'primitives') -----
  externalFunctionDeclaration
  	"Parse the function declaration for a call to an external library."
  	| descriptorClass callType modifier retType externalName args argType module fn |
  	descriptorClass := cue environment
  		valueOf: #ExternalFunction 
  		ifAbsent: [^ false].
  	callType := descriptorClass callingConventionFor: here.
  	callType == nil ifTrue:[^false].
  	[modifier := descriptorClass callingConventionModifierFor: token.
  	 modifier notNil] whileTrue:
  		[self advance.
  		 callType := callType bitOr: modifier].
  	"Parse return type"
  	self advance.
  	retType := self externalType: descriptorClass.
  	retType == nil ifTrue:[^self expected:'return type'].
  	"Parse function name or index"
  	externalName := here.
  	(self match: #string) 
  		ifTrue:[externalName := externalName asSymbol]
  		ifFalse:[(self match:#number) ifFalse:[^self expected:'function name or index']].
  	(self match: #leftParenthesis) ifFalse:[^self expected:'argument list'].
  	args := WriteStream on: Array new.
  	[self match: #rightParenthesis] whileFalse:[
  		argType := self externalType: descriptorClass.
  		argType == nil ifTrue:[^self expected:'argument'].
  		argType isVoid & argType isPointerType not ifFalse:[args nextPut: argType]].
  	(self matchToken: 'module:') ifTrue:[
  		module := here.
  		(self match: #string) ifFalse:[^self expected: 'String'].
  		module := module asSymbol].
  	Smalltalk at: #ExternalLibraryFunction ifPresent:[:xfn|
  		fn := xfn name: externalName 
  				module: module 
  				callType: callType
  				returnType: retType
  				argumentTypes: args contents.
+ 		self litIndex: fn.
+ 		fn beWritableObject. "Undo the read-only setting in litIndex:"].
- 		self allocateLiteral: fn].
  	(self matchToken: 'error:')
  		ifTrue:
  			[| errorCodeVariable |
  			 errorCodeVariable := here.
  			(hereType == #string
  			 or: [hereType == #word]) ifFalse:[^self expected: 'error code (a variable or string)'].
  			 self advance.
  			 self addPragma: (Pragma keyword: #primitive:error: arguments: (Array with: 120 with: errorCodeVariable)).
  			 fn ifNotNil: [fn setErrorCodeName: errorCodeVariable]]
  		ifFalse:
  			[self addPragma: (Pragma keyword: #primitive: arguments: #(120))].
  	^true!

Item was changed:
  ----- Method: Parser>>primitive:module:error: (in category 'primitives') -----
  primitive: aNameString module: aModuleStringOrNil error: errorCodeVariableOrNil
  	"Create named primitive with optional error code."
+ 	| firstLiteral |
- 	
  	(aNameString isString and: [ aModuleStringOrNil isNil or: [ aModuleStringOrNil isString ] ])
  		ifFalse: [ ^ self expected: 'Named primitive' ].
+ 	firstLiteral := {	aModuleStringOrNil ifNotNil: [aModuleStringOrNil asSymbol].
+ 					aNameString asSymbol.
+ 					0.
+ 					0 }.
+ 	(encoder litIndex: firstLiteral) ~= 0 ifTrue:
+ 		[self error: 'parser failed to allocate [primitive binding array as first literal'].
+ 	firstLiteral beWritableObject. "Undo the read-only setting in litIndex:"
- 	self allocateLiteral: (Array 
- 		with: (aModuleStringOrNil isNil 
- 			ifFalse: [ aModuleStringOrNil asSymbol ])
- 		with: aNameString asSymbol
- 		with: 0 with: 0).
  	errorCodeVariableOrNil ifNotNil:
  		[encoder floatTemp: (encoder bindTemp: errorCodeVariableOrNil) nowHasDef].
  	^117!

Item was changed:
  (PackageInfo named: 'Compiler') postscript: '"below, add code to be run after the loading of this package"
+ 
+ "Make all relevant literals read-only, avoiding the recompile step, so as to avoid unbound methods"
+ self systemNavigation allSelect:
+ 	[:m|
+ 	m allLiteralsDo:
+ 		[:l|
+ 		(l isLiteral
+ 		 and: [(l isCollection or: [l isNumber and: [l isReadOnlyObject not]])
+ 		 and: [(l isArray and: [m primitive == 117 and: [l == (m literalAt: 1)]]) not]]) ifTrue:
+ 			[l beReadOnlyObject]].
+ 	false]'!
- "Make sure that all those ``code generation (closures)'''' categoies disappear"
- ParseNode withAllSubclasses do:
- 	[:pnc| pnc organization removeEmptyCategories]'!



More information about the Squeak-dev mailing list