[Vm-dev] VM Maker: VMMaker.oscog-eem.2988.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Jul 19 22:07:15 UTC 2021


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2988.mcz

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

Name: VMMaker.oscog-eem.2988
Author: eem
Time: 19 July 2021, 3:07:06.232474 pm
UUID: 9e67581e-33d5-403f-bc83-f4af6a2e1c70
Ancestors: VMMaker.oscog-eem.2987

Add hook to primAlienReplace for Apple Silicon to flip executable pages into writability around a write to the page via primAlienReplace.

=============== Diff against VMMaker.oscog-eem.2987 ===============

Item was changed:
  ----- Method: IA32ABIPlugin>>primAlienCopyInto (in category 'primitives-accessing') -----
  primAlienCopyInto
  	"Copy some number of bytes from the receiver starting at the first index into some destination
  	 object starting at the second index.  The  destination may be an Aliens or a bit-indexable object.
  	 The primitive will have the following signature:
  	<Alien>
  		primCopyFrom: start <Integer>
  		to: stop <Integer>
  		into: destination <Alien | indexableByteSubclass et al>
  		startingAt: destStart <Integer> ^<self>
  		<primitive: 'primitiveAlienReplace' error: errorCode module: 'IA32ABI'>
  	"
  	<export: true>
  	| alien start stop dest destStart src totalLength destAddr myLength |
+ 	alien		:= interpreterProxy stackValue: 4.  "Unchecked!!"
+ 	start		:= interpreterProxy stackValue: 3.
+ 	stop		:= interpreterProxy stackValue: 2.
+ 	dest		:= interpreterProxy stackValue: 1.
+ 	destStart	:= interpreterProxy stackValue: 0.
- 	alien := interpreterProxy stackValue: 4.  "Unchecked!!"
- 	start := interpreterProxy stackIntegerValue: 3.
- 	stop := interpreterProxy stackIntegerValue: 2.
- 	dest := interpreterProxy stackValue: 1.
- 	destStart := interpreterProxy stackIntegerValue: 0.
  
+ 	((interpreterProxy isIntegerObject: start)
+ 	 and: [(interpreterProxy isIntegerObject: stop)
+ 	 and: [(interpreterProxy isIntegerObject: destStart)
+ 	 and: [interpreterProxy isWordsOrBytes: dest]]]) ifFalse:
- 	(interpreterProxy failed
- 	 or: [(interpreterProxy isWordsOrBytes: dest) not]) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  
+ 	start		:= interpreterProxy integerValueOf: start.
+ 	stop		:= interpreterProxy integerValueOf: stop.
+ 	destStart	:= interpreterProxy integerValueOf: destStart.
+ 
  	myLength := self sizeField: alien.
  	src := (self startOfData: alien withSize: myLength) + start - 1.
  
  	(self isAlien: dest)
  		ifTrue:
  			[totalLength := self sizeField: dest.
  			 destAddr := (self startOfData: dest withSize: totalLength) + destStart - 1.
  			 totalLength = 0 "no bounds checks for zero-sized (pointer) Aliens"
  				ifTrue: [totalLength := stop]
  				ifFalse: [totalLength := totalLength abs]]
  		ifFalse:
  			[totalLength := interpreterProxy byteSizeOf: dest.
  			 destAddr := (self startOfByteData: dest) + destStart - 1].
  
  	((start >= 1 and: [start - 1 <= stop and: [stop <= myLength abs]])
  	 and: [stop - start + 1 <= totalLength]) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
  
  	(interpreterProxy isOopImmutable: dest) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  
+ 	"Use memmove to allow source and destination to overlap"
- 	"Use memmove to allow source and desition to overlap"
  	self memmove: destAddr asVoidPointer _: src asVoidPointer _: stop - start + 1.
  
  	interpreterProxy methodReturnReceiver!

Item was changed:
  ----- Method: IA32ABIPlugin>>primAlienReplace (in category 'primitives-accessing') -----
  primAlienReplace
  	"Copy some number of bytes from some source object starting at the index
  	 into the receiver destination object from startIndex to stopIndex.  The  source
+ 	 and destination may be Aliens or byte-indexable objects.  The primitive will have
- 	 and destination may be Aliens or byte-indexable objects.  The primitive wll have
  	 either of the following signatures:
  	<Alien | indexableByteSubclass | indexableWordSubclass>
  		primReplaceFrom: start <Integer>
  		to: stop <Integer>
  		with: replacement <Alien | indexableByteSubclass | indexableWordSubclass | Integer>
  		startingAt: repStart <Integer> ^<self>
  		<primitive: 'primitiveAlienReplace' error: errorCode module: 'IA32ABI'>
  	<Anywhere>
  		primReplaceIn: dest <Alien | indexableByteSubclass | indexableWordSubclass>
  		from: start <Integer>
  		to: stop <Integer>
  		with: replacement <Alien | indexableByteSubclass | indexableWordSubclass | Integer>
  		startingAt: repStart <Integer> ^<self>
  		<primitive: 'primitiveAlienReplace' error: errorCode module: 'IA32ABI'>
  	"
+ 	| array start stop repl replStart dest src totalLength isOnExecutablePage |
- 	| array start stop repl replStart dest src totalLength |
  	<export: true>
+ 	array		:= interpreterProxy stackValue: 4.  "Unchecked!!"
+ 	start		:= interpreterProxy stackValue: 3.
+ 	stop		:= interpreterProxy stackValue: 2.
+ 	repl			:= interpreterProxy stackValue: 1.
+ 	replStart	:= interpreterProxy stackValue: 0.
- 	array := interpreterProxy stackValue: 4.
- 	start := interpreterProxy stackIntegerValue: 3.
- 	stop := interpreterProxy stackIntegerValue: 2.
- 	repl := interpreterProxy stackValue: 1.
- 	replStart := interpreterProxy stackIntegerValue: 0.
  
+ 	((interpreterProxy isIntegerObject: start)
+ 	 and: [(interpreterProxy isIntegerObject: stop)
+ 	 and: [(interpreterProxy isIntegerObject: replStart)
+ 	 and: [interpreterProxy isWordsOrBytes: repl]]]) ifFalse:
- 	(interpreterProxy failed
- 	 or: [(interpreterProxy isWordsOrBytes: array) not]) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  
+ 	start		:= interpreterProxy integerValueOf: start.
+ 	stop		:= interpreterProxy integerValueOf: stop.
+ 	replStart	:= interpreterProxy integerValueOf: replStart.
+ 
  	(self isAlien: array)
  		ifTrue:
  			[totalLength := self sizeField: array.
  			 dest := (self startOfData: array withSize: totalLength) + start - 1.
  			 totalLength = 0 "no bounds checks for zero-sized (pointer) Aliens"
  				ifTrue: [totalLength := stop]
  				ifFalse: [totalLength := totalLength abs]]
  		ifFalse:
  			[totalLength := interpreterProxy byteSizeOf: array.
  			 dest := (self startOfByteData: array) + start - 1].
  	(start >= 1 and: [start - 1 <= stop and: [stop <= totalLength]]) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
  
  	(interpreterProxy isKindOfInteger: repl)
  		ifTrue:
  			[src := (interpreterProxy positiveMachineIntegerValueOf: repl) + replStart - 1.
  			 interpreterProxy failed ifTrue:
  				[^interpreterProxy primitiveFailFor: PrimErrBadArgument]]
  		ifFalse:
  			[(self isAlien: repl)
  				ifTrue:
  					[totalLength := self sizeField: repl.
  					 src := (self startOfData: repl withSize: totalLength) + replStart - 1.
  					 totalLength = 0 "no bounds checks for zero-sized (pointer) Aliens"
  						ifTrue: [totalLength := stop - start + replStart]
  						ifFalse: [totalLength := totalLength abs]]
  				ifFalse:
  					[(interpreterProxy isWordsOrBytes: repl) ifFalse:
  						[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  					 totalLength := interpreterProxy byteSizeOf: repl.
  					 src := (self startOfByteData: repl) + replStart - 1].
  			(replStart >= 1 and: [stop - start + replStart <= totalLength]) ifFalse:
  				[^interpreterProxy primitiveFailFor: PrimErrBadIndex]].
  
  	(interpreterProxy isOopImmutable: array) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  
+ 	isOnExecutablePage := self ifIsWithinExecutablePageMakePageWritable: dest asVoidPointer.
+ 	"Use memmove to allow source and destination to overlap"
- 	"Use memmove to allow source and desition to overlap"
  	self memmove: dest asVoidPointer _: src asVoidPointer _: stop - start + 1.
+ 	isOnExecutablePage ifTrue: [self makePageExecutableAgain: dest asVoidPointer].
  
  	interpreterProxy methodReturnReceiver!

Item was added:
+ ----- Method: IA32ABIPluginSimulator>>ifIsWithinExecutablePageMakePageWritable: (in category 'simulation support') -----
+ ifIsWithinExecutablePageMakePageWritable: anAddress
+ 	^false!



More information about the Vm-dev mailing list