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

commits at source.squeak.org commits at source.squeak.org
Mon Jan 25 20:10:33 UTC 2016


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

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

Name: VMMaker.oscog-eem.1671
Author: eem
Time: 25 January 2016, 12:08:55.31255 pm
UUID: 65ba2e3c-cf26-496b-94e2-9038a49724a7
Ancestors: VMMaker.oscog-eem.1670

IMMUTABILITY: Now that isOopImmutable: is available through the plugin API, merge NewsqueakIA32ABIPlugin into IA32ABIPlugin and nuke NewsqueakIA32ABIPlugin.  Change the Newspeak configurations to not output their own plugins.

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

Item was changed:
  InterpreterPlugin subclass: #IA32ABIPlugin
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: 'VMBasicConstants'
  	category: 'VMMaker-Plugins-Alien'!
  
+ !IA32ABIPlugin commentStamp: 'eem 1/25/2016 11:59' prior: 0!
+ This plugin implements the Alien foreign-function interface, a small elaboration on the Strongtalk FFI.
- !IA32ABIPlugin commentStamp: '<historical>' prior: 0!
- This plugin implements the Alien foreign-function interface, a small elaboration on the Strongtalk FFI.  This version of the plugin differs from the NewsqueakIA32ABIPlugin in not supporting immutability.
  
  Call-outs are performed by a small number of primitives, one each for the four different kinds of return linkage on x86.  The primitives are var-args.  Each primitive has a signature something like:
  primFFICall: functionAddress <Alien> result: result <Alien> with: firstArg <Alien> ... with: lastArg <Alien>
  	<primitive: 'primCallOutIntegralReturn' module: 'IA32ABI'>
  which arranges to call-out supplying the arguments to the function pointed to by functionAddress, copying its return value into result.  The call-out primitives are as follows:
  
  primCallOutIntegralReturn call a function which returns up to 8 bytes in %eax & %edx, taking up to the first 4 bytes from %eax.  i.e. if the sizeof(result) is 4 or less only bytes from %eax will be returned, but if more then the first 4 bytes of result will be assigned with %eax and subsequent bytes with %edx, up to a total of 8 bytes.
  
  primCallOutPointerReturn call a function which returns a pointer in %eax.  Assign sizeof(result) bytes from this pointer into the result.
  
  primCallOutFloatReturn call a function which returns a 4 byte single-precision float in %f0, assigning the 4 bytes of %f0 into result.
  
  primCallOutDoubleReturn call a function which returns an 8 byte double-precision float in %f0, assigning the 8 bytes of %f0 into result.
  
  !

Item was changed:
  ----- Method: IA32ABIPlugin>>primAddressFieldPut (in category 'primitives-accessing') -----
  primAddressFieldPut
  	"Store an unsigned integer into the size field (the second 32/64 bit field; little endian)."
  	"<Alien> addressFieldPut: value <Integer> ^<Integer>
  		<primitive: 'primAddressFieldPut' error: errorCode module: 'IA32ABI'>"
  	| rcvr value valueOop |
  	<export: true>
  	valueOop := interpreterProxy stackValue: 0.
  	rcvr := interpreterProxy stackValue: 1.
  	value := interpreterProxy positiveMachineIntegerValueOf: valueOop.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
+ 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  	self longAt: rcvr + interpreterProxy baseHeaderSize + interpreterProxy bytesPerOop put: value.
  	^interpreterProxy methodReturnValue: valueOop!

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 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 count |
  	<export: true>
  	array := interpreterProxy stackValue: 4.
  	start := interpreterProxy stackIntegerValue: 3.
  	stop := interpreterProxy stackIntegerValue: 2.
  	repl := interpreterProxy stackValue: 1.
  	replStart := interpreterProxy stackIntegerValue: 0.
  
  	(interpreterProxy failed
  	 or: [(interpreterProxy isWordsOrBytes: array) not]) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  
  	(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 isIntegerObject: repl)
  		ifTrue:
  			[(interpreterProxy integerValueOf: repl) <= 0 ifTrue:
  				[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  			src := (interpreterProxy integerValueOf: repl) + replStart - 1]
  		ifFalse:
  			[(interpreterProxy fetchClassOf: repl) ==  interpreterProxy classLargePositiveInteger
  				ifTrue:
  					[src := (interpreterProxy positive32BitValueOf: 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].
+ 
  	count := stop - start + 1.
  	self cCode: 'memmove((void *)dest,(void *)src,count)'
  		inSmalltalk:
  			[count := count + src + dest. "squash unused var compiler warnings"
  			 self error: 'not implemented'].
  
  	interpreterProxy pop: interpreterProxy methodArgumentCount!

Item was changed:
  ----- Method: IA32ABIPlugin>>primDoubleAtPut (in category 'primitives-accessing') -----
  primDoubleAtPut
  	"Store a double into 64 bits starting at the given byte offset (little endian)."
  	"<Alien> doubleAt: index <Integer> put: value <Float | Integer> ^<Float | Integer>
  		<primitive: 'primDoubleAtPut' error: errorCode module: 'IA32ABI'>"
  	| byteOffset rcvr startAddr addr valueOop floatValue |
  	<export: true>
  	<var: #floatValue type: #double>
  
  	valueOop := interpreterProxy stackValue: 0.
  	(interpreterProxy isIntegerObject: valueOop)
  		ifTrue:[floatValue := self cCoerce: (interpreterProxy integerValueOf: valueOop) to: #double]
  		ifFalse:[floatValue := self cCoerce: (interpreterProxy floatValueOf: valueOop) to: #double].
  	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
  	rcvr := interpreterProxy stackObjectValue: 2.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self index: byteOffset length: 8 inRange: rcvr) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
+ 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  	(startAddr := self startOfData: rcvr) = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	addr := startAddr + byteOffset.
  	self cCode:'((int*)addr)[0] = ((int*)(&floatValue))[0]'.
  	self cCode:'((int*)addr)[1] = ((int*)(&floatValue))[1]'.
  	interpreterProxy methodReturnValue: valueOop!

Item was added:
+ ----- Method: IA32ABIPlugin>>primDrainOSEventQueue (in category 'primitives-Windows-VM-specific') -----
+ primDrainOSEventQueue
+ 	<export: true>
+ 	self ioDrainEventQueue!

Item was changed:
  ----- Method: IA32ABIPlugin>>primFloatAtPut (in category 'primitives-accessing') -----
  primFloatAtPut
  	"Store a float into 32 bits starting at the given byte offset (little endian)."
  	"<Alien> floatAt: index <Integer> put: value <Float | Integer> ^<Float | Integer>
  		<primitive: 'primFloatAtPut' error: errorCode module: 'IA32ABI'>"
  	| byteOffset rcvr startAddr addr valueOop floatValue |
  	<export: true>
  	<var: #floatValue type: #float>
  
  	valueOop := interpreterProxy stackValue: 0.
  	(interpreterProxy isIntegerObject: valueOop)
  		ifTrue:[floatValue := self cCoerce: (interpreterProxy integerValueOf: valueOop) to: #double]
  		ifFalse:[floatValue := self cCoerce: (interpreterProxy floatValueOf: valueOop) to: #double].
  	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
  	rcvr := interpreterProxy stackObjectValue: 2.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self index: byteOffset length: 4 inRange: rcvr) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
+ 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  	(startAddr := self startOfData: rcvr) = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	addr := startAddr + byteOffset.
  	self cCode:'((long *)addr)[0] = ((long *)(&floatValue))[0]'.
  	interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: IA32ABIPlugin>>primSignedByteAtPut (in category 'primitives-accessing') -----
  primSignedByteAtPut
  	"Store a signed integer into 8 bits starting at the given byte offset (little endian)."
  	"<Alien> signedByteAt: index <Integer> put: value <Integer> ^<Integer>
  		<primitive: 'primSignedByteAtPut' error: errorCode module: 'IA32ABI'>"
  	| byteOffset rcvr startAddr addr value valueOop |
  	<export: true>
  
  	valueOop := interpreterProxy stackValue: 0.
  	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
  	rcvr := interpreterProxy stackObjectValue: 2.
  	value := interpreterProxy signed32BitValueOf: valueOop.
  	(interpreterProxy failed
  	or: [value < -128
  	or: [value > 127]]) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self index: byteOffset length: 1 inRange: rcvr) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
+ 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  	(startAddr := self startOfData: rcvr) = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	addr := startAddr + byteOffset.
  	self byteAt: addr put: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: IA32ABIPlugin>>primSignedLongAtPut (in category 'primitives-accessing') -----
  primSignedLongAtPut
  	"Store a signed integer into 32 bits starting at the given byte offset (little endian)."
  	"<Alien> signedLongAt: index <Integer> put: value <Integer> ^<Integer>
  		<primitive: 'primSignedLongAtPut' error: errorCode module: 'IA32ABI'>"
  	| byteOffset rcvr startAddr addr value valueOop |
  	<export: true>
  
  	valueOop := interpreterProxy stackValue: 0.
  	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
  	rcvr := interpreterProxy stackObjectValue: 2.
  	value := interpreterProxy signed32BitValueOf: valueOop.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self index: byteOffset length: 4 inRange: rcvr) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
+ 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  	(startAddr := self startOfData: rcvr) = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	addr := startAddr + byteOffset.
  	self long32At: addr put: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: IA32ABIPlugin>>primSignedLongLongAtPut (in category 'primitives-accessing') -----
  primSignedLongLongAtPut
  	"Store a signed integer into 64 bits starting at the given byte offset (little endian)."
  	"<Alien> signedLongLongAt: index <Integer> put: value <Integer> ^<Integer>
  		<primitive: 'primSignedLongLongAtPut' error: errorCode module: 'IA32ABI'>"
  	| byteOffset rcvr startAddr addr valueOop signedlonglongvalue signedlonglongvaluePtr |
  	<export: true>
  	<var: 'signedlonglongvalue' declareC: 'long long signedlonglongvalue'>
  	<var: 'signedlonglongvaluePtr' declareC: 'long long *signedlonglongvaluePtr'>
  
  	signedlonglongvaluePtr := 0.
  	self touch: signedlonglongvaluePtr.
  	valueOop := interpreterProxy stackValue: 0.
  	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
  	rcvr := interpreterProxy stackObjectValue: 2.
  	signedlonglongvalue := interpreterProxy signed64BitValueOf: valueOop.
  	self touch: signedlonglongvalue.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self index: byteOffset length: 8 inRange: rcvr) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
+ 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  	(startAddr := self startOfData: rcvr) = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	addr := startAddr + byteOffset.
  	signedlonglongvaluePtr := self cCoerce: addr to: 'long long*'.
  	self cCode: '*signedlonglongvaluePtr = signedlonglongvalue'.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: IA32ABIPlugin>>primSignedShortAtPut (in category 'primitives-accessing') -----
  primSignedShortAtPut
  	"Store a signed integer into 16 bits starting at the given byte offset (little endian)."
  	"<Alien> signedShortAt: index <Integer> put: value <Integer> ^<Integer>
  		<primitive: 'primSignedShortAtPut' error: errorCode module: 'IA32ABI'>"
  	| byteOffset rcvr startAddr addr value valueOop |
  	<export: true>
  
  	valueOop := interpreterProxy stackValue: 0.
  	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
  	rcvr := interpreterProxy stackObjectValue: 2.
  	value := interpreterProxy signed32BitValueOf: valueOop.
  	(interpreterProxy failed
  	or: [value < -32768
  	or: [value > 32767]]) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self index: byteOffset length: 2 inRange: rcvr) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
+ 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  	(startAddr := self startOfData: rcvr) = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	addr := startAddr + byteOffset.
  	self shortAt: addr put: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: IA32ABIPlugin>>primSignedWordAtPut (in category 'primitives-accessing') -----
  primSignedWordAtPut
  	"Store a signed integer into the word starting at the given byte offset (little endian)."
  	"<Alien> signedWordAt: index <Integer> put: value <Integer> ^<Integer>
  		<primitive: 'primSignedWordAtPut' error: errorCode module: 'IA32ABI'>"
  	| byteOffset rcvr startAddr addr value valueOop |
  	<export: true>
  
  	valueOop := interpreterProxy stackValue: 0.
  	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
  	rcvr := interpreterProxy stackObjectValue: 2.
  	value := interpreterProxy signedMachineIntegerValueOf: valueOop.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self index: byteOffset length: interpreterProxy bytesPerOop inRange: rcvr) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
+ 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  	(startAddr := self startOfData: rcvr) = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	addr := startAddr + byteOffset.
  	self longAt: addr put: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: IA32ABIPlugin>>primStrlenFromStartIndex (in category 'primitives-accessing') -----
  primStrlenFromStartIndex
  	"Answer the number of non-null bytes starting at index.  If
  	 there isn't a null byte before the end of the object then the
  	 result will be the number of bytes from index to the end of
  	 the object, i.e. the result will be within the bounds of the object."
  	"<Alien> primStrlenFrom: index <Integer> ^<Integer>
  		<primitive: 'primStrlenFromStartIndex' error: errorCode module: 'IA32ABI'>"
  	| byteOffset rcvr index limit ptr |
  	<export: true>
  	<var: #ptr type: #'char *'>
  
  	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
  	rcvr := interpreterProxy stackObjectValue: 1.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self index: byteOffset length: 1 inRange: rcvr) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
  	limit := self sizeField: rcvr.
+ 	ptr := self cCoerce: ((self startOfData: rcvr withSize: limit) + byteOffset) to: #'char *'.
- 	ptr := self cCoerce: ((self startOfData: rcvr withSize: limit) + byteOffset) to: 'char *'.
  	limit = 0
  		ifTrue: [index := self strlen: ptr]
  		ifFalse:
  			[limit := limit abs.
  			 index := 0.
  			 [index < limit
  			  and: [(self cCode: 'ptr[index]' inSmalltalk: [ptr byteAt: index]) ~= 0]] whileTrue:
  				[index := index + 1]].
  	^interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: index)!

Item was changed:
  ----- Method: IA32ABIPlugin>>primUnsignedByteAtPut (in category 'primitives-accessing') -----
  primUnsignedByteAtPut
  	"Store an unsigned integer into 8 bits starting at the given byte offset (little endian)."
  	"<Alien> unsignedByteAt: index <Integer> put: value <Integer> ^<Integer>
  		<primitive: 'primUnsignedByteAtPut' error: errorCode module: 'IA32ABI'>"
  	| byteOffset rcvr startAddr addr value valueOop |
  	<export: true>
  
  	valueOop := interpreterProxy stackValue: 0.
  	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
  	rcvr := interpreterProxy stackObjectValue: 2.
  	value := interpreterProxy positive32BitValueOf: valueOop.
  	(interpreterProxy failed
  	or: [value > 255]) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self index: byteOffset length: 1 inRange: rcvr) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
+ 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  	(startAddr := self startOfData: rcvr) = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	addr := startAddr + byteOffset.
  	self byteAt: addr put: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: IA32ABIPlugin>>primUnsignedLongAtPut (in category 'primitives-accessing') -----
  primUnsignedLongAtPut
  	"Store an unsigned integer into 32 bits starting at the given byte offset (little endian)."
  	"<Alien> unsignedLongAt: index <Integer> put: value <Integer> ^<Integer>
  		<primitive: 'primUnsignedLongAtPut' error: errorCode module: 'IA32ABI'>"
  	| byteOffset rcvr startAddr addr value valueOop |
  	<export: true>
  
  	valueOop := interpreterProxy stackValue: 0.
  	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
  	rcvr := interpreterProxy stackObjectValue: 2.
  	value := interpreterProxy positive32BitValueOf: valueOop.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self index: byteOffset length: 4 inRange: rcvr) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
+ 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  	(startAddr := self startOfData: rcvr) = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	addr := startAddr + byteOffset.
  	self long32At: addr put: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: IA32ABIPlugin>>primUnsignedLongLongAtPut (in category 'primitives-accessing') -----
  primUnsignedLongLongAtPut
  	"Store a signed integer into 64 bits starting at the given byte offset (little endian)."
  	"<Alien> unsignedLongLongAt: index <Integer> put: value <Integer> ^<Integer>
  		<primitive: 'primUnSignedLongLongAtPut' error: errorCode module: 'IA32ABI'>"
  	| byteOffset rcvr startAddr addr valueOop unsignedlonglongvalue unsignedlonglongvaluePtr |
  	<export: true>
  	<var: 'unsignedlonglongvalue' declareC: 'unsigned long long unsignedlonglongvalue'>
  	<var: 'unsignedlonglongvaluePtr' declareC: 'unsigned long long *unsignedlonglongvaluePtr'>
  
  	unsignedlonglongvaluePtr := 0.
  	self touch: unsignedlonglongvaluePtr.
  
  	valueOop := interpreterProxy stackValue: 0.
  	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
  	rcvr := interpreterProxy stackObjectValue: 2.
  	unsignedlonglongvalue := interpreterProxy positive64BitValueOf: valueOop.
  	self touch: unsignedlonglongvalue.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self index: byteOffset length: 8 inRange: rcvr) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
+ 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  	(startAddr := self startOfData: rcvr) = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	addr := startAddr + byteOffset.
  	unsignedlonglongvaluePtr := self cCoerce: addr to: 'unsigned long long*'.
  	self cCode: '*unsignedlonglongvaluePtr = unsignedlonglongvalue'.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: IA32ABIPlugin>>primUnsignedShortAtPut (in category 'primitives-accessing') -----
  primUnsignedShortAtPut
  	"Store an unsigned integer into 16 bits starting at the given byte offset (little endian)."
  	"<Alien> unsignedShortAt: index <Integer> put: value <Integer> ^<Integer>
  		<primitive: 'primUnsignedShortAtPut' error: errorCode module: 'IA32ABI'>"
  	| byteOffset rcvr startAddr addr value valueOop |
  	<export: true>
  
  	valueOop := interpreterProxy stackValue: 0.
  	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
  	rcvr := interpreterProxy stackObjectValue: 2.
  	value := interpreterProxy positive32BitValueOf: valueOop.
  	(interpreterProxy failed
  	or: [value > 65535]) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self index: byteOffset length: 2 inRange: rcvr) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
+ 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  	(startAddr := self startOfData: rcvr) = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	addr := startAddr + byteOffset.
  	self shortAt: addr put: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: IA32ABIPlugin>>primUnsignedWordAtPut (in category 'primitives-accessing') -----
  primUnsignedWordAtPut
  	"Store an unsigned integer into 32 bits starting at the given byte offset (little endian)."
  	"<Alien> unsignedWordAt: index <Integer> put: value <Integer> ^<Integer>
  		<primitive: 'primUnsignedWordAtPut' error: errorCode module: 'IA32ABI'>"
  	| byteOffset rcvr startAddr addr value valueOop |
  	<export: true>
  
  	valueOop := interpreterProxy stackValue: 0.
  	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
  	rcvr := interpreterProxy stackObjectValue: 2.
  	value := interpreterProxy positiveMachineIntegerValueOf: valueOop.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self index: byteOffset length: interpreterProxy bytesPerOop inRange: rcvr) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
+ 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  	(startAddr := self startOfData: rcvr) = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	addr := startAddr + byteOffset.
  	self longAt: addr put: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- InterpreterPlugin subclass: #NewsqueakIA32ABIPlugin
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: 'VMBasicConstants'
- 	category: 'VMMaker-Plugins-Alien'!
- 
- !NewsqueakIA32ABIPlugin commentStamp: 'eem 10/31/2007 18:04' prior: 0!
- This plugin implements the Newsqueak foreign-function interface, a small elaboration on the Strongtalk FFI.
- 
- Call-outs are performed by a small number of primitives, one each for the four different kinds of return linkage on x86.  The primitives are var-args.  Each primitive has a signature something like:
- primFFICall: functionAddress <Alien> result: result <Alien> with: firstArg <Alien> ... with: lastArg <Alien>
- 	<primitive: 'primCallOutIntegralReturn' module: 'IA32ABI'>
- which arranges to call-out supplying the arguments to the function pointed to by functionAddress, copying its return value into result.  The call-out primitives are as follows:
- 
- primCallOutIntegralReturn call a function which returns up to 8 bytes in %eax & %edx, taking up to the first 4 bytes from %eax.  i.e. if the sizeof(result) is 4 or less only bytes from %eax will be returned, but if more then the first 4 bytes of result will be assigned with %eax and subsequent bytes with %edx, up to a total of 8 bytes.
- 
- primCallOutPointerReturn call a function which returns a pointer in %eax.  Assign sizeof(result) bytes from this pointer into the result.
- 
- primCallOutFloatReturn call a function which returns a 4 byte single-precision float in %f0, assigning the 4 bytes of %f0 into result.
- 
- primCallOutDoubleReturn call a function which returns an 8 byte double-precision float in %f0, assigning the 8 bytes of %f0 into result.
- 
- !

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin class>>ancilliaryClasses: (in category 'translation') -----
- ancilliaryClasses: options
- 	^{ VMCallbackContext. VMCallbackReturnValue }!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin class>>declareCVarsIn: (in category 'translation to C') -----
- declareCVarsIn: aCCodeGen
- 	aCCodeGen
- 		addHeaderFile: '<setjmp.h>';
- 		addHeaderFile: '"vmCallback.h"';
- 		addHeaderFile: '"ia32abi.h"'!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin class>>hasHeaderFile (in category 'accessing') -----
- hasHeaderFile
- 	^true!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin class>>moduleName (in category 'translation') -----
- moduleName
- 	^'IA32ABI'!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin class>>simulatorClass (in category 'simulation only') -----
- simulatorClass
- 	^NewspeakVM ifTrue: [NewsqueakIA32ABIPluginSimulator]!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>index:length:inRange: (in category 'private-support') -----
- index: byteIndex length: length inRange: rcvr
- 	"Answer if the indices byteIndex to byteIndex + length - 1 are valid zero-relative indices into the rcvr.
- 	 Beware!!  There be dragons here.  The form below (byteIndex <= (dataSize abs - length)) is used
- 	 because byteIndex + length could overflow, whereas (dataSize abs - length) can't.  We *don't* use the
- 	 obvious optimization
- 		^dataSize = 0 or: [byteIndex asUnsignedInteger <= (dataSize abs - length)]
- 	 because with C's Usual Arithmetic Conversions
- 		5. Otherwise, both operands are converted to the unsigned integer type corresponding to the type of the operand with signed integer type.
- 	 means that the comparison will be unsigned, and if length > dataSize abs then dataSize abs - length is large and positive."
- 	| dataSize |
- 	<inline: true>
- 	dataSize := self sizeField: rcvr.
- 	^dataSize = 0 or: [byteIndex >= 0 and: [byteIndex <= (dataSize abs - length)]]!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>isAlien: (in category 'private-support') -----
- isAlien: anOop
- 	<export: true>
- 	^interpreterProxy
- 		includesBehavior: (interpreterProxy fetchClassOf: anOop)
- 		ThatOf: interpreterProxy classAlien!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primAddressField (in category 'primitives-accessing') -----
- primAddressField
- 	"Answer the unsigned 32-bit (or 64-bit) integer comprising the address field (the second 32-bit or 64-bit field)."
- 	"<Alien> primAddressField ^<Integer>
- 		<primitive: 'primAddressField' error: errorCode module: 'IA32ABI'>"
- 	| rcvr value valueOop |
- 	<export: true>
- 	rcvr := interpreterProxy stackValue: 0.
- 	value := self longAt: rcvr + interpreterProxy baseHeaderSize + interpreterProxy bytesPerOop.
- 	valueOop := self positiveMachineIntegerFor: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primAddressFieldPut (in category 'primitives-accessing') -----
- primAddressFieldPut
- 	"Store an unsigned integer into the size field (the second 32/64 bit field; little endian)."
- 	"<Alien> addressFieldPut: value <Integer> ^<Integer>
- 		<primitive: 'primAddressFieldPut' error: errorCode module: 'IA32ABI'>"
- 	| rcvr value valueOop |
- 	<export: true>
- 	valueOop := interpreterProxy stackValue: 0.
- 	rcvr := interpreterProxy stackValue: 1.
- 	value := interpreterProxy positiveMachineIntegerValueOf: valueOop.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
- 	self longAt: rcvr + interpreterProxy baseHeaderSize + interpreterProxy bytesPerOop put: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>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 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 count |
- 	<export: true>
- 	array := interpreterProxy stackValue: 4.
- 	start := interpreterProxy stackIntegerValue: 3.
- 	stop := interpreterProxy stackIntegerValue: 2.
- 	repl := interpreterProxy stackValue: 1.
- 	replStart := interpreterProxy stackIntegerValue: 0.
- 
- 	(interpreterProxy failed
- 	 or: [(interpreterProxy isWordsOrBytes: array) not]) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 
- 	(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 isIntegerObject: repl)
- 		ifTrue:
- 			[(interpreterProxy integerValueOf: repl) <= 0 ifTrue:
- 				[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 			src := (interpreterProxy integerValueOf: repl) + replStart - 1]
- 		ifFalse:
- 			[(interpreterProxy fetchClassOf: repl) ==  interpreterProxy classLargePositiveInteger
- 				ifTrue:
- 					[src := (interpreterProxy positive32BitValueOf: 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].
- 
- 	count := stop - start + 1.
- 	self cCode: 'memmove((void *)dest,(void *)src,count)'
- 		inSmalltalk:
- 			[count := count + src + dest. "squash unused var compiler warnings"
- 			 self error: 'not implemented'].
- 
- 	interpreterProxy pop: interpreterProxy methodArgumentCount!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primAllocateExecutablePage (in category 'primitives-memory management') -----
- primAllocateExecutablePage
- 	"Answer an Alien for an executable page; for thunks"
- 	"primAllocateExecutablePage ^<Alien>
- 		<primitive: 'primAllocateExecutablePage' error: errorCode module: 'IA32ABI'>"
- 	| byteSize ptr mem alien |
- 	<export: true>
- 	<var: #byteSize type: 'long'>
- 	<var: #ptr type: 'long *'>
- 	<var: #mem type: 'void *'>
- 
- 	self cCode: 'mem = allocateExecutablePage(&byteSize)'
- 		inSmalltalk: [self error: 'not yet implemented'. mem := 0. byteSize := 0].
- 	mem = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoCMemory].
- 	alien := interpreterProxy
- 				instantiateClass: interpreterProxy classAlien
- 				indexableSize: 2 * interpreterProxy bytesPerOop.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
- 	ptr := interpreterProxy firstIndexableField: alien.
- 	ptr at: 0 put: 0 - byteSize. "indirect mem indicated by negative size. Slang doesn't grok negated"
- 	ptr at: 1 put: (self cCoerce: mem to: 'long').
- 	interpreterProxy methodReturnValue: alien!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primBoxedFree (in category 'primitives-memory management') -----
- primBoxedFree
- 	"Free the memory referenced by the receiver, an Alien."
- 	"proxy <Alien> primFree ^<Alien>
- 		<primitive: 'primBoxedFree' error: errorCode module: 'IA32ABI'>"
- 	| addr rcvr ptr sizeField |
- 	<export: true>
- 	<var: #ptr type: 'sqInt *'>
- 	<var: #sizeField type: 'long'>
- 
- 	rcvr := interpreterProxy stackObjectValue: 0.
- 	(interpreterProxy byteSizeOf: rcvr) >= (2 * interpreterProxy bytesPerOop) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	ptr := interpreterProxy firstIndexableField: rcvr.
- 	sizeField := ptr at: 0.
- 	addr := ptr at: 1.
- 	"Don't you dare to free Squeak's memory!!"
- 	(sizeField >= 0 or: [addr = 0 or: [interpreterProxy isInMemory: addr]]) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
- 	self cCode: 'free((void *)addr)'
- 		inSmalltalk: [self Cfree: addr].
- 	ptr
- 		at: 0 put: 0;
- 		at: 1 put: 0 "cleanup"!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primCallOutDoubleReturn (in category 'primitives-callouts') -----
- primCallOutDoubleReturn
- 	"Call a foreign function that answers a double-precision floating-point result in %f0
- 	 according to IA32-ish ABI rules. The primitive will have a signature of the form
- 	functionAddress <Alien> primFFICallResult: result <Alien|Object> with: firstArg <Alien | Integer> ... with: lastArg <Alien | Integer> ^<Alien>
- 		<primitive: 'primCallOutDoubleReturn' error: errorCode module: 'IA32ABI'>.
- 	Answer result. If result is an Alien the value answered by the call will be assigned to result."
- 	| errCode mac result |
- 	<export: true>
- 	mac := interpreterProxy methodArgumentCount.
- 	self cppIf: STACKVM
- 		ifTrue: "In the STACKVM stacks grow down"
- 			[errCode := self call: interpreterProxy getStackPointer + mac - 2 "ptr to 0th arg"
- 							IA32: 1 - mac	"nargs negated to imply stack direction"
- 							Double: mac	"funcOffset"
- 							Return: mac - 1	"resultOffset"]
- 		ifFalse:
- 			[errCode := self call: interpreterProxy getStackPointer - mac + 2 "ptr to 0th arg"
- 							IA32: mac - 1	"nargs"
- 							Double: mac	"funcOffset"
- 							Return: mac - 1	"resultOffset"].
- 	errCode ~= 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: errCode].
- 	result := interpreterProxy stackValue: mac - 1.
- 	interpreterProxy pop: mac + 1 thenPush: result!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primCallOutFloatReturn (in category 'primitives-callouts') -----
- primCallOutFloatReturn
- 	"Call a foreign function that answers a single-precision floating-point result in %f0
- 	 according to IA32-ish ABI rules. The primitive will have a signature of the form
- 	functionAddress <Alien> primFFICallResult: result <Alien|Object> with: firstArg <Alien | Integer> ... with: lastArg <Alien | Integer> ^<Alien>
- 		<primitive: 'primCallOutFloatReturn' error: errorCode module: 'IA32ABI'>.
- 	Answer result. If result is an Alien the value answered by the call will be assigned to result."
- 	| errCode mac result |
- 	<export: true>
- 	mac := interpreterProxy methodArgumentCount.
- 	self cppIf: STACKVM
- 		ifTrue: "In the STACKVM stacks grow down"
- 			[errCode := self call: interpreterProxy getStackPointer + mac - 2 "ptr to 0th arg"
- 							IA32: 1 - mac	"nargs negated to imply stack direction"
- 							Float: mac		"funcOffset"
- 							Return: mac - 1	"resultOffset"]
- 		ifFalse:
- 			[errCode := self call: interpreterProxy getStackPointer - mac + 2 "ptr to 0th arg"
- 							IA32: mac - 1	"nargs"
- 							Float: mac		"funcOffset"
- 							Return: mac - 1	"resultOffset"].
- 	errCode ~= 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: errCode].
- 	result := interpreterProxy stackValue: mac - 1.
- 	interpreterProxy pop: mac + 1 thenPush: result!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primCallOutIntegralReturn (in category 'primitives-callouts') -----
- primCallOutIntegralReturn
- 	"Call a foreign function that answers an integral result in %eax (and possibly %edx)
- 	 according to IA32-ish ABI rules. The primitive will have a signature of the form
- 	functionAddress <Alien> primFFICallResult: result <Alien|Object> with: firstArg <Alien | Integer> ... with: lastArg <Alien | Integer> ^<Alien>
- 		<primitive: 'primCallOutIntegralReturn' error: errorCode module: 'IA32ABI'>.
- 	Answer result. If result is an Alien the value answered by the call will be assigned to result."
- 	| errCode mac result |
- 	<export: true>
- 	mac := interpreterProxy methodArgumentCount.
- 	self cppIf: STACKVM
- 		ifTrue: "In the STACKVM stacks grow down"
- 			[errCode := self call: interpreterProxy getStackPointer + mac - 2 "ptr to 0th arg"
- 							IA32: 1 - mac	"nargs negated to imply stack direction"
- 							Integral: mac	"funcOffset"
- 							Return: mac - 1	"resultOffset"]
- 		ifFalse:
- 			[errCode := self call: interpreterProxy getStackPointer - mac + 2 "ptr to 0th arg"
- 							IA32: mac - 1	"nargs"
- 							Integral: mac	"funcOffset"
- 							Return: mac - 1	"resultOffset"].
- 	errCode ~= 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: errCode].
- 	result := interpreterProxy stackValue: mac - 1.
- 	interpreterProxy pop: mac + 1 thenPush: result!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primCalloc (in category 'primitives-memory management') -----
- primCalloc
- 	"calloc (malloc + zero-fill) arg bytes."
- 	"primCalloc: byteSize <Integer> ^<Integer>
- 		<primitive: 'primCalloc' error: errorCode module: 'IA32ABI'>"
- 	| byteSize addr |
- 	<export: true>
- 
- 	byteSize := interpreterProxy stackIntegerValue: 0.
- 	(interpreterProxy failed
- 	 or: [byteSize <= 0 "some mallocs can't deal with malloc(0) bytes"]) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	addr := self cCode: [(self c: 1 alloc: byteSize) asUnsignedInteger] inSmalltalk: [Alien Ccalloc: byteSize].
- 	addr = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoCMemory].
- 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: addr)!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primDoubleAt (in category 'primitives-accessing') -----
- primDoubleAt
- 	"Answer the 64-bit double starting at the given byte offset (little endian)."
- 	"<Alien> doubleAt: index <Integer> ^<Float>
- 		<primitive: 'primDoubleAt' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr floatValue |
- 	<export: true>
- 	<var: #floatValue type:'double '>
- 
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 1.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 8 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	self cCode:'((long *)(&floatValue))[0] = ((long *)addr)[0]; ((long *)(&floatValue))[1] = ((long *)addr)[1]'
- 		inSmalltalk: [floatValue := rcvr doubleAt: byteOffset].
- 	interpreterProxy pop: 2.
- 	^interpreterProxy pushFloat: floatValue!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primDoubleAtPut (in category 'primitives-accessing') -----
- primDoubleAtPut
- 	"Store a double into 64 bits starting at the given byte offset (little endian)."
- 	"<Alien> doubleAt: index <Integer> put: value <Float | Integer> ^<Float | Integer>
- 		<primitive: 'primDoubleAtPut' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr valueOop floatValue |
- 	<export: true>
- 	<var: #floatValue type: #double>
- 
- 	valueOop := interpreterProxy stackValue: 0.
- 	(interpreterProxy isIntegerObject: valueOop)
- 		ifTrue:[floatValue := self cCoerce: (interpreterProxy integerValueOf: valueOop) to: #double]
- 		ifFalse:[floatValue := self cCoerce: (interpreterProxy floatValueOf: valueOop) to: #double].
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 2.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 8 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	self cCode:'((int*)addr)[0] = ((int*)(&floatValue))[0]'.
- 	self cCode:'((int*)addr)[1] = ((int*)(&floatValue))[1]'.
- 	interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primDrainOSEventQueue (in category 'primitives-Windows-VM-specific') -----
- primDrainOSEventQueue
- 	<export: true>
- 	self ioDrainEventQueue!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primFloatAt (in category 'primitives-accessing') -----
- primFloatAt
- 	"Answer the 32-bit float starting at the given byte offset (little endian)."
- 	"<Alien> floatAt: index <Integer> ^<Float>
- 		<primitive: 'primFloatAt' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr floatValue |
- 	<export: true>
- 	<var: #floatValue type: 'float '>
- 
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 1.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 4 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	self cCode:'((long *)(&floatValue))[0] = ((long *)addr)[0]'
- 		inSmalltalk: [floatValue := rcvr floatAt: byteOffset].
- 	interpreterProxy pop: 2.
- 	^interpreterProxy pushFloat: floatValue!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primFloatAtPut (in category 'primitives-accessing') -----
- primFloatAtPut
- 	"Store a float into 32 bits starting at the given byte offset (little endian)."
- 	"<Alien> floatAt: index <Integer> put: value <Float | Integer> ^<Float | Integer>
- 		<primitive: 'primFloatAtPut' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr valueOop floatValue |
- 	<export: true>
- 	<var: #floatValue type: #float>
- 
- 	valueOop := interpreterProxy stackValue: 0.
- 	(interpreterProxy isIntegerObject: valueOop)
- 		ifTrue:[floatValue := self cCoerce: (interpreterProxy integerValueOf: valueOop) to: #double]
- 		ifFalse:[floatValue := self cCoerce: (interpreterProxy floatValueOf: valueOop) to: #double].
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 2.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 4 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	self cCode:'((long *)addr)[0] = ((long *)(&floatValue))[0]'.
- 	interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primFree (in category 'primitives-memory management') -----
- primFree
- 	"Free the memory referenced by the argument, an integer."
- 	"<Anywhere> primFree: address <Integer>
- 		<primitive: 'primFree' error: errorCode module: 'IA32ABI'>"
- 	| addr |
- 	<export: true>
- 	addr := interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 0).
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	"Don't you dare to free Squeak's memory!!"
- 	(addr = 0 or: [interpreterProxy isInMemory: addr]) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
- 	self cCode: 'free((void *)addr)'
- 		inSmalltalk: [self Cfree: addr].
- 	interpreterProxy pop: 1!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primInIOProcessEventsFlagAddress (in category 'primitives-Windows-VM-specific') -----
- primInIOProcessEventsFlagAddress
- 	"Answer the address of the int inIOProcessEvents flag.  This can be used to
- 	 disable invocation of ioProcessEvents and is for backward-compatibility.
- 	 Please use the core VM primitiveEventProcessingControl in new code."
- 	| inIOProcessEvents |
- 	<export: true>
- 	<var: 'inIOProcessEvents' declareC: 'extern int inIOProcessEvents'>
- 	self cCode: '' inSmalltalk: [inIOProcessEvents = 0].
- 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: (self addressOf: inIOProcessEvents) asUnsignedInteger)!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primInLibraryFindSymbol (in category 'primitives-library loading') -----
- primInLibraryFindSymbol
- 	"Attempt to find the address of a symbol in a loaded library.
- 	 The primitive can have a signature  either of the form:
- 		<Anywhere> primInLibrary: libraryHandle <Alien> findSymbol: symbolName <String> ^<Integer>
- 			<primitive: 'primInLibraryFindSymbol' error: errorCode module: 'IA32ABI'>
- 	 or:
- 		libraryHandle <Alien>  primFindSymbol: symbolName <String> ^<Integer>
- 			<primitive: 'primInLibraryFindSymbol' error: errorCode module: 'IA32ABI'>"
- 	<export: true>
- 	| functionName libraryProxy address |
- 	<var: #address type: #'void *'>
- 	functionName := interpreterProxy stackValue: 0.
- 	libraryProxy := interpreterProxy stackValue: 1.
- 	((self isAlien: libraryProxy)
- 	 and: [(interpreterProxy byteSizeOf: libraryProxy) >= (2 * interpreterProxy bytesPerOop)
- 	 and: [interpreterProxy isBytes: functionName]]) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	address := interpreterProxy
- 					ioLoadSymbol: (self cCoerce: (interpreterProxy firstIndexableField: functionName)
- 										to: #sqInt)
- 					OfLength: (interpreterProxy byteSizeOf: functionName)
- 					FromModule: (self longAt: libraryProxy + interpreterProxy baseHeaderSize + interpreterProxy bytesPerOop).
- 	(interpreterProxy failed
- 	 or: [address = 0]) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNotFound].
- 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: address asUnsignedInteger)!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primLoadLibrary (in category 'primitives-library loading') -----
- primLoadLibrary
- 	"Attempt to load a library of the given name.  The primitive will have a signature
- 	 of the form:
- 		<Anywhere>  primLoadLibrary: libraryName <String> ^<Integer>
- 			<primitive: 'primLoadLibrary' error: errorCode module: 'IA32ABI'>"
- 	<export: true>
- 	| libraryName libraryHandle |
- 	<var: #libraryHandle type: #'void *'>
- 	libraryName := interpreterProxy stackValue: 0.
- 	(interpreterProxy isBytes: libraryName)
- 		ifFalse: [^ interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	libraryHandle := interpreterProxy
- 					ioLoadModule: (self cCoerce: (interpreterProxy firstIndexableField: libraryName) to: 'sqInt')
- 					OfLength: (interpreterProxy byteSizeOf: libraryName).
- 	libraryHandle = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNotFound].
- 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: libraryHandle asUnsignedInteger)!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primMalloc (in category 'primitives-memory management') -----
- primMalloc
- 	"Malloc arg bytes."
- 	"primMalloc: byteSize <Integer> <^Integer>
- 		<primitive: 'primMalloc' error: errorCode module: 'IA32ABI'>"
- 	| byteSize addr |
- 	<export: true>
- 
- 	byteSize := interpreterProxy stackIntegerValue: 0.
- 	(interpreterProxy failed
- 	 or: [byteSize <= 0 "some mallocs can't deal with malloc(0) bytes"]) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	addr := self cCode: [(self malloc: byteSize) asUnsignedInteger] inSmalltalk: [Alien Cmalloc: byteSize].
- 	addr = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoCMemory].
- 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: addr)!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primReturnAsFromContextThrough (in category 'primitives-callbacks') -----
- primReturnAsFromContextThrough
- 	"Return a result from a callback to the callback's callee.  The primitive
- 	 has a signature of either of the forms:
- 		result <VMCallbackContext32/64>
- 				primReturnAs: returnTypeCode <Integer>
- 				FromContext: callbackContext <Context>
- 		result <VMCallbackContext32/64>
- 				primSignal: aSemaphore <Semaphore>
- 				andReturnAs: returnTypeCode <Integer>
- 				FromContext: callbackContext <Context>
- 			<primitive: 'primReturnAsFromContextThrough' error: errorCode module: 'IA32ABI'>.
- 	 If of the second form answer false if this is not the most recent callback, and signal aSemaphore
- 	 if it is, so as to implement LIFO ordering of callbacks."
- 	<export: true>
- 	| vmCallbackContext isMostRecent |
- 	<var: #vmCallbackContext type: #'VMCallbackContext *'>
- 	interpreterProxy methodArgumentCount = 3
- 		ifTrue:
- 			[vmCallbackContext := self cCoerceSimple: (self startOfData: (interpreterProxy stackValue: 3))
- 										to: #'VMCallbackContext *'.
- 			 isMostRecent := vmCallbackContext = self getMostRecentCallbackContext.
- 			 isMostRecent ifFalse:
- 				[^interpreterProxy methodReturnValue: interpreterProxy falseObject].
- 			(interpreterProxy fetchClassOf: (interpreterProxy stackValue: 2)) = interpreterProxy classSemaphore ifFalse:
- 				[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 			[interpreterProxy signalNoResume: (interpreterProxy stackValue: 2)] whileFalse]
- 		ifFalse:
- 			[vmCallbackContext := self cCoerceSimple: (self startOfData: (interpreterProxy stackValue: 2))
- 										to: #'VMCallbackContext *'].
- 	(interpreterProxy
- 		returnAs: (interpreterProxy stackValue: 1)
- 		ThroughCallback: vmCallbackContext
- 		Context: (interpreterProxy stackValue: 0)) ifFalse:
- 			[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	"NOTREACHED"!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primReturnFromContextThrough (in category 'primitives-callbacks') -----
- primReturnFromContextThrough
- 	"Return a result from a callback to the callback's callee.  The primitive
- 	 has a signature of either of the forms:
- 		result <FFICallbackResult> primReturnFromContext: callbackContext <MethodContext> through: jmpBuf <Integer>
- 		result <FFICallbackResult> primSignal: aSemaphore <Semaphore> andReturnFromContext: callbackContext <MethodContext> through: jmpBuf <Integer>
- 			<primitive: 'primReturnFromContextThrough' error: errorCode module: 'IA32ABI'>.
- 	 If of the second form answer true if this is not the most recent callback, and signal aSemaphore
- 	 if it is, so as to implement LIFO ordering of callbacks."
- 	<export: true>
- 	<legacy>
- 	| mac vmCallbackContext vmCallbackReturnValue isMostRecent |
- 	<var: #vmCallbackContext type: #'VMCallbackContext *'>
- 	<var: #vmCallbackReturnValue type: #'VMCallbackReturnValue *'>
- 	vmCallbackContext := self cCoerceSimple: (interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 0))
- 								to: #'VMCallbackContext *'.
- 	(interpreterProxy failed or: [vmCallbackContext = 0]) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 
- 	(mac := interpreterProxy methodArgumentCount) = 3 ifTrue:
- 		[isMostRecent := vmCallbackContext = self getMostRecentCallbackContext.
- 		isMostRecent ifFalse:
- 			[interpreterProxy methodReturnValue: interpreterProxy trueObject.
- 			^nil].
- 		(interpreterProxy fetchClassOf: (interpreterProxy stackValue: 2)) = interpreterProxy classSemaphore
- 			ifFalse: [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 		[interpreterProxy signalNoResume: (interpreterProxy stackValue: 2)] whileFalse].
- 	vmCallbackReturnValue := self cCoerceSimple: (self startOfData: (interpreterProxy stackValue: mac))
- 									to: #'VMCallbackReturnValue *'.
- 	self cCode: "C needs a typedef for structs to be assigned, but that implies a struct class for just one assignment."
- 		[self mem: (self addressOf: vmCallbackContext rvs)
- 			cp: (self addressOf: vmCallbackReturnValue crvrvs)
- 			y: (self sizeof: vmCallbackContext rvs)]
- 		inSmalltalk: [vmCallbackContext rvs: vmCallbackReturnValue crvrvs].
- 	(interpreterProxy
- 		returnAs: (interpreterProxy integerObjectOf: vmCallbackReturnValue type + 1)
- 		ThroughCallback: vmCallbackContext
- 		Context: (interpreterProxy stackValue: 1)) ifFalse:
- 			[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	"NOTREACHED"!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primSignedByteAt (in category 'primitives-accessing') -----
- primSignedByteAt
- 	"Answer the signed 8-bit integer starting at the given byte offset (little endian)."
- 	"<Alien> unsignedByteAt: index <Integer> ^<Integer>
- 		<primitive: 'primSignedByteAt' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 	<var: #value type: 'signed char '>
- 
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 1.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 1 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	value := self byteAt: addr.
- 	valueOop := interpreterProxy signed32BitIntegerFor: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primSignedByteAtPut (in category 'primitives-accessing') -----
- primSignedByteAtPut
- 	"Store a signed integer into 8 bits starting at the given byte offset (little endian)."
- 	"<Alien> signedByteAt: index <Integer> put: value <Integer> ^<Integer>
- 		<primitive: 'primSignedByteAtPut' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 
- 	valueOop := interpreterProxy stackValue: 0.
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 2.
- 	value := interpreterProxy signed32BitValueOf: valueOop.
- 	(interpreterProxy failed
- 	or: [value < -128
- 	or: [value > 127]]) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 1 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	self byteAt: addr put: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primSignedLongAt (in category 'primitives-accessing') -----
- primSignedLongAt
- 	"Answer the signed 32-bit integer starting at the given byte offset (little endian)."
- 	"<Alien> signedLongAt: index <Integer> ^<Integer>
- 		<primitive: 'primSignedLongAt' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 1.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 4 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	value := self long32At: addr.
- 	valueOop := interpreterProxy signed32BitIntegerFor: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primSignedLongAtPut (in category 'primitives-accessing') -----
- primSignedLongAtPut
- 	"Store a signed integer into 32 bits starting at the given byte offset (little endian)."
- 	"<Alien> signedLongAt: index <Integer> put: value <Integer> ^<Integer>
- 		<primitive: 'primSignedLongAtPut' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 
- 	valueOop := interpreterProxy stackValue: 0.
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 2.
- 	value := interpreterProxy signed32BitValueOf: valueOop.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 4 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	self long32At: addr put: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primSignedLongLongAt (in category 'primitives-accessing') -----
- primSignedLongLongAt
- 	"Answer the signed 64-bit integer starting at the given byte offset (little endian)."
- 	"<Alien> signedLongLongAt: index <Integer> ^<Integer>
- 		<primitive: 'primSignedLongLongAt' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr valueOop signedlonglongvaluePtr signedlonglongvalue |
- 	<export: true>
- 	<var: 'signedlonglongvalue' declareC: 'long long signedlonglongvalue'>
- 	<var: 'signedlonglongvaluePtr' declareC: 'long long *signedlonglongvaluePtr'>
- 
- 	signedlonglongvaluePtr := 0.
- 	self touch: signedlonglongvaluePtr.
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 1.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 8 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	signedlonglongvaluePtr := self cCoerce: addr to: 'long long*'.
- 	signedlonglongvalue := self cCode: '*signedlonglongvaluePtr'.
- 	valueOop := interpreterProxy signed64BitIntegerFor: signedlonglongvalue.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primSignedLongLongAtPut (in category 'primitives-accessing') -----
- primSignedLongLongAtPut
- 	"Store a signed integer into 64 bits starting at the given byte offset (little endian)."
- 	"<Alien> signedLongLongAt: index <Integer> put: value <Integer> ^<Integer>
- 		<primitive: 'primSignedLongLongAtPut' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr valueOop signedlonglongvalue signedlonglongvaluePtr |
- 	<export: true>
- 	<var: 'signedlonglongvalue' declareC: 'long long signedlonglongvalue'>
- 	<var: 'signedlonglongvaluePtr' declareC: 'long long *signedlonglongvaluePtr'>
- 
- 	signedlonglongvaluePtr := 0.
- 	self touch: signedlonglongvaluePtr.
- 	valueOop := interpreterProxy stackValue: 0.
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 2.
- 	signedlonglongvalue := interpreterProxy signed64BitValueOf: valueOop.
- 	self touch: signedlonglongvalue.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 8 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	signedlonglongvaluePtr := self cCoerce: addr to: 'long long*'.
- 	self cCode: '*signedlonglongvaluePtr = signedlonglongvalue'.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primSignedShortAt (in category 'primitives-accessing') -----
- primSignedShortAt
- 	"Answer the signed 32-bit integer starting at the given byte offset (little endian)."
- 	"<Alien> signedShortAt: index <Integer> ^<Integer>
- 		<primitive: 'primSignedShortAt' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 	<var: #value type: 'short '>
- 
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 1.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 2 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	value := self shortAt: addr.
- 	valueOop := interpreterProxy signed32BitIntegerFor: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primSignedShortAtPut (in category 'primitives-accessing') -----
- primSignedShortAtPut
- 	"Store a signed integer into 16 bits starting at the given byte offset (little endian)."
- 	"<Alien> signedShortAt: index <Integer> put: value <Integer> ^<Integer>
- 		<primitive: 'primSignedShortAtPut' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 
- 	valueOop := interpreterProxy stackValue: 0.
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 2.
- 	value := interpreterProxy signed32BitValueOf: valueOop.
- 	(interpreterProxy failed
- 	or: [value < -32768
- 	or: [value > 32767]]) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 2 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	self shortAt: addr put: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primSignedWordAt (in category 'primitives-accessing') -----
- primSignedWordAt
- 	"Answer the signed word starting at the given byte offset (little endian)."
- 	"<Alien> signedWordAt: index <Integer> ^<Integer>
- 		<primitive: 'primSignedWordAt' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 1.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: interpreterProxy bytesPerOop inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	value := self longAt: addr.
- 	valueOop := interpreterProxy signedMachineIntegerValueOf: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primSignedWordAtPut (in category 'primitives-accessing') -----
- primSignedWordAtPut
- 	"Store a signed integer into the word starting at the given byte offset (little endian)."
- 	"<Alien> signedWordAt: index <Integer> put: value <Integer> ^<Integer>
- 		<primitive: 'primSignedWordAtPut' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 
- 	valueOop := interpreterProxy stackValue: 0.
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 2.
- 	value := interpreterProxy signedMachineIntegerValueOf: valueOop.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: interpreterProxy bytesPerOop inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	self longAt: addr put: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primSizeField (in category 'primitives-accessing') -----
- primSizeField
- 	"Answer the signed 32- or 64-bit integer comprising the size field (the first 32- or 64-bit field)."
- 	"<Alien> primSizeField ^<Integer>
- 		<primitive: 'primSizeField' error: errorCode module: 'IA32ABI'>"
- 	| rcvr value valueOop |
- 	<export: true>
- 
- 	rcvr := interpreterProxy stackValue: 0.
- 	value := self cppIf: interpreterProxy bytesPerOop = 8
- 				ifTrue: [(self longAt: rcvr + interpreterProxy baseHeaderSize) signedIntFromLong64]
- 				ifFalse: [(self longAt: rcvr + interpreterProxy baseHeaderSize) signedIntFromLong].
- 	valueOop := self signedMachineIntegerFor: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primSizeFieldPut (in category 'primitives-accessing') -----
- primSizeFieldPut
- 	"Store a signed integer into the size field (the first 32 bit field; little endian)."
- 	"<Alien> sizeFieldPut: value <Integer> ^<Integer>
- 		<primitive: 'primSizeFieldPut' error: errorCode module: 'IA32ABI'>"
- 	| rcvr value valueOop |
- 	<export: true>
- 
- 	valueOop := interpreterProxy stackValue: 0.
- 	rcvr := interpreterProxy stackValue: 1.
- 	value := interpreterProxy signedMachineIntegerValueOf: valueOop.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self cppIf: interpreterProxy bytesPerOop = 8
- 		ifTrue: [self longAt: rcvr + interpreterProxy baseHeaderSize put: value signedIntToLong64]
- 		ifFalse: [self longAt: rcvr + interpreterProxy baseHeaderSize put: value signedIntToLong]).
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primStrlenFromStartIndex (in category 'primitives-accessing') -----
- primStrlenFromStartIndex
- 	"Answer the number of non-null bytes starting at index.  If
- 	 there isn't a null byte before the end of the object then the
- 	 result will be the number of bytes from index to the end of
- 	 the object, i.e. the result will be within the bounds of the object."
- 	"<Alien> primStrlenFrom: index <Integer> ^<Integer>
- 		<primitive: 'primStrlenFromStartIndex' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr index limit ptr |
- 	<export: true>
- 	<var: #ptr type: #'char *'>
- 
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 1.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 1 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	limit := self sizeField: rcvr.
- 	ptr := self cCoerce: ((self startOfData: rcvr withSize: limit) + byteOffset) to: #'char *'.
- 	limit = 0
- 		ifTrue: [index := self strlen: ptr]
- 		ifFalse:
- 			[limit := limit abs.
- 			 index := 0.
- 			 [index < limit
- 			  and: [(self cCode: 'ptr[index]' inSmalltalk: [ptr byteAt: index]) ~= 0]] whileTrue:
- 				[index := index + 1]].
- 	^interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: index)!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primStrlenThroughPointerAtIndex (in category 'primitives-accessing') -----
- primStrlenThroughPointerAtIndex
- 	"Answer the number of non-null bytes starting at the byte addressed by
- 	 the 4-byte pointer at index."
- 	"<Alien> strlenThroughPointerAt: index <Integer> ^<Integer>
- 		<primitive: 'primStrlenThroughPointerAtIndex' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr ptr addr |
- 	<export: true>
- 	<var: #ptr type: #'char *'>
- 
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 1.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: interpreterProxy bytesPerOop inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	addr := (self startOfData: rcvr) + byteOffset.
- 	ptr := self cCoerce: (self longAt: addr) to: #'char *'.
- 	^interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: (self strlen: ptr))!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primThunkEntryAddress (in category 'primitives-callbacks') -----
- primThunkEntryAddress
- 	"Answer the address of the entry-point for thunk callbacks:
- 		long thunkEntry(void *thunkp, long *stackp);
- 	 This could be derived via loadModule: findSymbol: etc but that would
- 	preclude making the plugin internal."
- 	| address |
- 	<export: true>
- 	address := self cCode: [#thunkEntry asInteger] inSmalltalk: [0].
- 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: address)!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primUnsignedByteAt (in category 'primitives-accessing') -----
- primUnsignedByteAt
- 	"Answer the unsigned 8-bit integer starting at the given byte offset (little endian)."
- 	"<Alien> unsignedByteAt: index <Integer> ^<Integer>
- 		<primitive: 'primUnsignedByteAt' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 	<var: #value type: 'unsigned char '>
- 
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 1.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 1 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	value := self byteAt: addr.
- 	valueOop := interpreterProxy positive32BitIntegerFor: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primUnsignedByteAtPut (in category 'primitives-accessing') -----
- primUnsignedByteAtPut
- 	"Store an unsigned integer into 8 bits starting at the given byte offset (little endian)."
- 	"<Alien> unsignedByteAt: index <Integer> put: value <Integer> ^<Integer>
- 		<primitive: 'primUnsignedByteAtPut' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 
- 	valueOop := interpreterProxy stackValue: 0.
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 2.
- 	value := interpreterProxy positive32BitValueOf: valueOop.
- 	(interpreterProxy failed
- 	or: [value > 255]) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 1 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	self byteAt: addr put: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primUnsignedLongAt (in category 'primitives-accessing') -----
- primUnsignedLongAt
- 	"Answer the unsigned 32-bit integer starting at the given byte offset (little endian)."
- 	"<Alien> unsignedLongAt: index <Integer> ^<Integer>
- 		<primitive: 'primUnsignedLongAt' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 1.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 4 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	value := self long32At: addr.
- 	valueOop := interpreterProxy positive32BitIntegerFor: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primUnsignedLongAtPut (in category 'primitives-accessing') -----
- primUnsignedLongAtPut
- 	"Store an unsigned integer into 32 bits starting at the given byte offset (little endian)."
- 	"<Alien> unsignedLongAt: index <Integer> put: value <Integer> ^<Integer>
- 		<primitive: 'primUnsignedLongAtPut' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 
- 	valueOop := interpreterProxy stackValue: 0.
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 2.
- 	value := interpreterProxy positive32BitValueOf: valueOop.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 4 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	self long32At: addr put: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primUnsignedLongLongAt (in category 'primitives-accessing') -----
- primUnsignedLongLongAt
- 	"Answer the unsigned 64-bit integer starting at the given byte offset (little endian)."
- 	"<Alien>unsignedLongLongAt: index <Integer> ^<Integer>
- 		<primitive: 'primUnsignedLongLongAt' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr valueOop unsignedlonglongvaluePtr unsignedlonglongvalue |
- 	<export: true>
- 	<var: 'unsignedlonglongvalue' declareC: 'unsigned long long unsignedlonglongvalue'>
- 	<var: 'unsignedlonglongvaluePtr' declareC: 'unsigned long long *unsignedlonglongvaluePtr'>
- 
- 	unsignedlonglongvaluePtr := 0.
- 	self touch: unsignedlonglongvaluePtr.
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 1.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 8 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	unsignedlonglongvaluePtr := self cCoerce: addr to: 'unsigned long long*'.
- 	unsignedlonglongvalue := self cCode: '*unsignedlonglongvaluePtr'.
- 	valueOop := interpreterProxy positive64BitIntegerFor: unsignedlonglongvalue.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primUnsignedLongLongAtPut (in category 'primitives-accessing') -----
- primUnsignedLongLongAtPut
- 	"Store a signed integer into 64 bits starting at the given byte offset (little endian)."
- 	"<Alien> unsignedLongLongAt: index <Integer> put: value <Integer> ^<Integer>
- 		<primitive: 'primUnSignedLongLongAtPut' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr valueOop unsignedlonglongvalue unsignedlonglongvaluePtr |
- 	<export: true>
- 	<var: 'unsignedlonglongvalue' declareC: 'unsigned long long unsignedlonglongvalue'>
- 	<var: 'unsignedlonglongvaluePtr' declareC: 'unsigned long long *unsignedlonglongvaluePtr'>
- 
- 	unsignedlonglongvaluePtr := 0.
- 	self touch: unsignedlonglongvaluePtr.
- 
- 	valueOop := interpreterProxy stackValue: 0.
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 2.
- 	unsignedlonglongvalue := interpreterProxy positive64BitValueOf: valueOop.
- 	self touch: unsignedlonglongvalue.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 8 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	unsignedlonglongvaluePtr := self cCoerce: addr to: 'unsigned long long*'.
- 	self cCode: '*unsignedlonglongvaluePtr = unsignedlonglongvalue'.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primUnsignedShortAt (in category 'primitives-accessing') -----
- primUnsignedShortAt
- 	"Answer the unsigned 16-bit integer starting at the given byte offset (little endian)."
- 	"<Alien> unsignedShortAt: index <Integer> ^<Integer>
- 		<primitive: 'primUnsignedShortAt' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 	<var: #value type: 'unsigned short'>
- 
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 1.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 2 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	value := self shortAt: addr.
- 	valueOop := interpreterProxy positive32BitIntegerFor: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primUnsignedShortAtPut (in category 'primitives-accessing') -----
- primUnsignedShortAtPut
- 	"Store an unsigned integer into 16 bits starting at the given byte offset (little endian)."
- 	"<Alien> unsignedShortAt: index <Integer> put: value <Integer> ^<Integer>
- 		<primitive: 'primUnsignedShortAtPut' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 
- 	valueOop := interpreterProxy stackValue: 0.
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 2.
- 	value := interpreterProxy positive32BitValueOf: valueOop.
- 	(interpreterProxy failed
- 	or: [value > 65535]) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: 2 inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	self shortAt: addr put: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primUnsignedWordAt (in category 'primitives-accessing') -----
- primUnsignedWordAt
- 	"Answer the unsigned word starting at the given byte offset (little endian)."
- 	"<Alien> unsignedWordAt: index <Integer> ^<Integer>
- 		<primitive: 'primUnsignedWordAt' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 1.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: interpreterProxy bytesPerOop inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	value := self longAt: addr.
- 	valueOop := interpreterProxy positiveMachineIntegerFor: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primUnsignedWordAtPut (in category 'primitives-accessing') -----
- primUnsignedWordAtPut
- 	"Store an unsigned integer into 32 bits starting at the given byte offset (little endian)."
- 	"<Alien> unsignedWordAt: index <Integer> put: value <Integer> ^<Integer>
- 		<primitive: 'primUnsignedWordAtPut' error: errorCode module: 'IA32ABI'>"
- 	| byteOffset rcvr startAddr addr value valueOop |
- 	<export: true>
- 
- 	valueOop := interpreterProxy stackValue: 0.
- 	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.
- 	rcvr := interpreterProxy stackObjectValue: 2.
- 	value := interpreterProxy positiveMachineIntegerValueOf: valueOop.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	(self index: byteOffset length: interpreterProxy bytesPerOop inRange: rcvr) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
- 	(interpreterProxy isOopImmutable: rcvr) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
- 	(startAddr := self startOfData: rcvr) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	addr := startAddr + byteOffset.
- 	self longAt: addr put: value.
- 	^interpreterProxy methodReturnValue: valueOop!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primVarArgsCallOutDoubleReturn (in category 'primitives-callouts') -----
- primVarArgsCallOutDoubleReturn
- 	"Call a foreign function that answers a double-precision floating-point result in %f0
- 	 according to IA32-ish ABI rules. The primitive will have a signature of the form
- 	functionAddress <Alien> primFFICallResult: result <Alien|Object> withArguments: args <Array of: Alien | Integer> ^<Alien>
- 		<primitive: 'primVarArgsCallOutDoubleReturn' error: errorCode module: 'IA32ABI'>.
- 	Answer result. If result is an Alien the value answered by the call will be assigned to result."
- 	| array mac errCode result |
- 	<export: true>
- 	array := interpreterProxy stackValue: 0.
- 	(interpreterProxy isArray: array) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	mac := interpreterProxy methodArgumentCount.
- 	errCode := self call: (interpreterProxy firstIndexableField: array)	"ptr to 0th arg"
- 					IA32: (interpreterProxy stSizeOf: array)				"nargs"
- 					Double: 2											"func stackValue"
- 					Return: 1.											"result stackValue"
- 	errCode ~= 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: errCode].
- 	result := interpreterProxy stackValue: 1.
- 	interpreterProxy pop: mac + 1 thenPush: result!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primVarArgsCallOutFloatReturn (in category 'primitives-callouts') -----
- primVarArgsCallOutFloatReturn
- 	"Call a foreign function that answers a single-precision floating-point result in %f0
- 	 according to IA32-ish ABI rules. The primitive will have a signature of the form
- 	functionAddress <Alien> primFFICallResult: result <Alien|Object> withArguments: args <Array of: Alien | Integer> ^<Alien>
- 		<primitive: 'primVarArgsCallOutFloatReturn' error: errorCode module: 'IA32ABI'>.
- 	Answer result. If result is an Alien the value answered by the call will be assigned to result."
- 	| array mac errCode result |
- 	<export: true>
- 	array := interpreterProxy stackValue: 0.
- 	(interpreterProxy isArray: array) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	mac := interpreterProxy methodArgumentCount.
- 	errCode := self call: (interpreterProxy firstIndexableField: array)	"ptr to 0th arg"
- 					IA32: (interpreterProxy stSizeOf: array)				"nargs"
- 					Float: 2												"func stackValue"
- 					Return: 1.											"result stackValue"
- 	errCode ~= 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: errCode].
- 	result := interpreterProxy stackValue: 1.
- 	interpreterProxy pop: mac + 1 thenPush: result!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>primVarArgsCallOutIntegralReturn (in category 'primitives-callouts') -----
- primVarArgsCallOutIntegralReturn
- 	"Call a foreign function that answers an integral result in %eax (and possibly %edx)
- 	 according to IA32-ish ABI rules. The primitive will have a signature of the form
- 	functionAddress <Alien> primFFICallResult: result <Alien|Object> withArguments: args <Array of: Alien | Integer> ^<Alien>
- 		<primitive: 'primVarArgsCallOutIntegralReturn' error: errorCode module: 'IA32ABI'>.
- 	Answer result. If result is an Alien the value answered by the call will be assigned to result."
- 	| array mac errCode result |
- 	<export: true>
- 	array := interpreterProxy stackValue: 0.
- 	(interpreterProxy isArray: array) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	mac := interpreterProxy methodArgumentCount.
- 	errCode := self call: (interpreterProxy firstIndexableField: array)	"ptr to 0th arg"
- 					IA32: (interpreterProxy stSizeOf: array)				"nargs"
- 					Integral: 2											"func stackValue"
- 					Return: 1.											"result stackValue"
- 	errCode ~= 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: errCode].
- 	result := interpreterProxy stackValue: 1.
- 	interpreterProxy pop: mac + 1 thenPush: result!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>setInterpreter: (in category 'initialize') -----
- setInterpreter: anInterpreter 
- 	"Note: This is coded so that is can be run from Squeak."
- 	| ok |
- 	<export: true>
- 	<var: #anInterpreter type: #'struct VirtualMachine*'>
- 	interpreterProxy := anInterpreter.
- 	ok := interpreterProxy majorVersion = 1
- 			and: [interpreterProxy minorVersion >= 12].
- 	ok ifTrue:
- 		[self expandDereferenceInterpreterProxyFunctionTable].
- 	^ok!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>sizeField: (in category 'private-support') -----
- sizeField: rcvr
- 	"Answer the first field of rcvr which is assumed to be an Alien of at least 8 bytes"
- 	<inline: true>
- 	^self longAt: rcvr + interpreterProxy baseHeaderSize!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>startOfByteData: (in category 'private-support') -----
- startOfByteData: rcvr "<byte indexable oop> ^<Integer>"
- 	"Answer the start of rcvr's data, given that it is not an alien."
- 	<inline: true>
- 	^rcvr + interpreterProxy baseHeaderSize!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>startOfData: (in category 'private-support') -----
- startOfData: rcvr "<Alien oop> ^<Integer>"
- 	"Answer the start of rcvr's data.  For direct aliens this is the address of
- 	 the second field.  For indirect and pointer aliens it is what the second field points to."
- 	<inline: true>
- 	^(self sizeField: rcvr) > 0
- 	 	ifTrue: [rcvr + interpreterProxy baseHeaderSize + interpreterProxy bytesPerOop]
- 		ifFalse: [self longAt: rcvr + interpreterProxy baseHeaderSize + interpreterProxy bytesPerOop]!

Item was removed:
- ----- Method: NewsqueakIA32ABIPlugin>>startOfData:withSize: (in category 'private-support') -----
- startOfData: rcvr "<Alien oop>" withSize: sizeField "<Integer> ^<Integer>"
- 	"Answer the start of rcvr's data.  For direct aliens this is the address of
- 	 the second field.  For indirect and pointer aliens it is what the second field points to."
- 	<inline: true>
- 	^sizeField > 0
- 	 	ifTrue: [rcvr + interpreterProxy baseHeaderSize + interpreterProxy bytesPerOop]
- 		ifFalse: [self longAt: rcvr + interpreterProxy baseHeaderSize + interpreterProxy bytesPerOop]!

Item was removed:
- NewsqueakIA32ABIPlugin subclass: #NewsqueakIA32ABIPluginAttic
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-Plugins-Alien'!

Item was removed:
- ----- Method: NewsqueakIA32ABIPluginAttic class>>declareCVarsIn: (in category 'translation to C') -----
- declareCVarsIn: aCCodeGen
- 	^self  "on purpose as a sub class of existing plugin"!

Item was removed:
- ----- Method: NewsqueakIA32ABIPluginAttic>>primBoxedCalloc (in category 'primitives-memory management') -----
- primBoxedCalloc
- 	"This version boxes the result."
- 	"calloc (malloc + zero-fill) arg bytes."
- 	"primBoxedCalloc: byteSize <Integer>
- 		<primitive: 'primBoxedCalloc' module: 'IA32ABI'>"
- 	| byteSize addr oop ptr |
- 	<export: true>
- 	<inline: false>
- 	<var: #ptr type: 'long *'>
- 	<var: #byteSize type: 'long'>
- 	byteSize := interpreterProxy stackIntegerValue: 0.
- 	(interpreterProxy failed
- 	 or: [byteSize <= 0 "some mallocs can't deal with malloc(0) bytes"]) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	self cCode: 'addr = (sqInt)calloc(1,byteSize)'
- 		inSmalltalk: [addr := self Ccalloc: byteSize].
- 	addr = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoCMemory].
- 	oop := interpreterProxy 
- 			instantiateClass: interpreterProxy classAlien
- 			indexableSize: 2 * interpreterProxy bytesPerOop.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
- 	ptr := interpreterProxy firstIndexableField: oop.
- 	ptr at: 0 put: 0 - byteSize. "indirect args indicated by negative size. Slang doesn't grok negated"
- 	ptr at: 1 put: addr.
- 	interpreterProxy pop: 2 thenPush: oop.
- !

Item was removed:
- ----- Method: NewsqueakIA32ABIPluginAttic>>primBoxedMalloc (in category 'primitives-memory management') -----
- primBoxedMalloc
- 	"This version boxes the result."
- 	"Malloc arg bytes."
- 	"primBoxedMalloc: byteSize <Integer>
- 		<primitive: 'primBoxedMalloc' module: 'IA32ABI'>"
- 	| byteSize addr oop ptr |
- 	<export: true>
- 	<inline: false>
- 	<var: #ptr type: 'long *'>
- 	<var: #byteSize type: 'long'>
- 	byteSize := interpreterProxy stackIntegerValue: 0.
- 	(interpreterProxy failed
- 	 or: [byteSize <= 0 "some mallocs can't deal with malloc(0) bytes"]) ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	self cCode: 'addr = (sqInt)malloc(byteSize)'
- 		inSmalltalk: [addr := self Cmalloc: byteSize].
- 	addr = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoCMemory].
- 	oop := interpreterProxy 
- 			instantiateClass: interpreterProxy classAlien
- 			indexableSize: 2 * interpreterProxy bytesPerOop.
- 	interpreterProxy failed ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
- 	ptr := interpreterProxy firstIndexableField: oop.
- 	ptr at: 0 put: 0 - byteSize. "indirect args indicated by negative size. Slang doesn't grok negated"
- 	ptr at: 1 put: addr.
- 	interpreterProxy pop: 2 thenPush: oop.
- !

Item was removed:
- ----- Method: NewsqueakIA32ABIPluginAttic>>primCallOutDoubleReturnAnywhere (in category 'primitives-callouts') -----
- primCallOutDoubleReturnAnywhere
- 	"Call a foreign function that answers a double-precision floating-point result in %f0
- 	 according to IA32-ish ABI rules. The primitive will have a signature of the form
- 	<Anywhere> primFFICall: functionAddress <Alien> result: result <Alien|Object> with: firstArg <Alien> ... with: lastArg <Alien>
- 		<primitive: 'primCallOutDoubleReturnAnywhere' error: errorCode module: 'IA32ABI'>.
- 	Answer result. If result is an Alien the value answered by the call will be assigned to result."
- 	| errCode mac result |
- 	<export: true>
- 	mac := interpreterProxy methodArgumentCount.
- 	(self isAlien:  (interpreterProxy stackValue: mac - 2)) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	self cppIf: STACKVM
- 		ifTrue: "In the STACKVM stacks grow down"
- 			[self cCode: 'errCode = callIA32DoubleReturn(interpreterProxy->getStackPointer() + mac - 3, /* arg vec */
- 															2 - mac	/* nargs */,
- 															mac	/* funcOffset*/,
- 															mac - 2	/* resultOffset */)'
- 				inSmalltalk: [errCode := PrimErrUnsupported]]
- 		ifFalse:
- 			[self cCode: 'errCode = callIA32DoubleReturn(interpreterProxy->getStackPointer() - mac + 3, /* arg vec */
- 															mac - 2	/* nargs */,
- 															mac	/* funcOffset*/,
- 															mac - 2	/* resultOffset */)'
- 				inSmalltalk: [errCode := PrimErrUnsupported]].
- 	errCode ~= 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: errCode].
- 	result := interpreterProxy stackValue: mac - 2.
- 	interpreterProxy pop: mac + 1 thenPush: result!

Item was removed:
- ----- Method: NewsqueakIA32ABIPluginAttic>>primCallOutFloatReturnAnywhere (in category 'primitives-callouts') -----
- primCallOutFloatReturnAnywhere
- 	"Call a foreign function that answers a single-precision floating-point result in %f0
- 	 according to IA32-ish ABI rules. The primitive will have a signature of the form
- 	<Anywhere> primFFICall: functionAddress <Alien> result: result <Alien|Object> with: firstArg <Alien> ... with: lastArg <Alien>
- 		<primitive: 'primCallOutFloatReturnAnywhere' error: errorCode module: 'IA32ABI'>.
- 	Answer result. If result is an Alien the value answered by the call will be assigned to result."
- 	| errCode mac result |
- 	<export: true>
- 	mac := interpreterProxy methodArgumentCount.
- 	(self isAlien: (interpreterProxy stackValue: mac - 2)) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	self cppIf: STACKVM
- 		ifTrue: "In the STACKVM stacks grow down"
- 			[self cCode: 'errCode = callIA32FloatReturn(interpreterProxy->getStackPointer() + mac - 3, /* arg vec */
- 															2 - mac	/* nargs */,
- 															mac	/* funcOffset*/,
- 															mac - 2	/* resultOffset */)'
- 				inSmalltalk: [errCode := PrimErrUnsupported]]
- 		ifFalse:
- 			[self cCode: 'errCode = callIA32FloatReturn(interpreterProxy->getStackPointer() - mac + 3, /* arg vec */
- 															mac - 2	/* nargs */,
- 															mac	/* funcOffset*/,
- 															mac - 2	/* resultOffset */)'
- 				inSmalltalk: [errCode := PrimErrUnsupported]].
- 	errCode ~= 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: errCode].
- 	result := interpreterProxy stackValue: mac - 2.
- 	interpreterProxy pop: mac + 1 thenPush: result!

Item was removed:
- ----- Method: NewsqueakIA32ABIPluginAttic>>primCallOutIntegralReturnAnywhere (in category 'primitives-callouts') -----
- primCallOutIntegralReturnAnywhere
- 	"Call a foreign function that answers an integral result in %eax (and possibly %edx)
- 	 according to IA32-ish ABI rules. The primitive will have a signature of the form
- 	<Anywhere> primFFICall: functionAddress <Alien> result: result <Alien|Object> with: firstArg <Alien> ... with: lastArg <Alien>
- 		<primitive: 'primCallOutIntegralReturnAnywhere' error: errorCode module: 'IA32ABI'>.
- 	Answer result. If result is an Alien the value answered by the call will be assigned to result."
- 	| errCode mac result |
- 	<export: true>
- 	mac := interpreterProxy methodArgumentCount.
- 	(self isAlien:  (interpreterProxy stackValue: mac - 2)) ifFalse:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
- 	self cppIf: STACKVM
- 		ifTrue: "In the STACKVM stacks grow down"
- 			[self cCode: 'errCode = callIA32IntegralReturn(interpreterProxy->getStackPointer() + mac - 3, /* arg vec */
- 															2 - mac	/* nargs */,
- 															mac	/* funcOffset*/,
- 															mac - 2	/* resultOffset */)'
- 				inSmalltalk: [errCode := PrimErrUnsupported]]
- 		ifFalse:
- 			[self cCode: 'errCode = callIA32IntegralReturn(interpreterProxy->getStackPointer() - mac + 3, /* arg vec */
- 															mac - 2	/* nargs */,
- 															mac	/* funcOffset*/,
- 															mac - 2	/* resultOffset */)'
- 				inSmalltalk: [errCode := PrimErrUnsupported]].
- 	errCode ~= 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: errCode].
- 	result := interpreterProxy stackValue: mac - 2.
- 	interpreterProxy pop: mac + 1 thenPush: result!

Item was removed:
- NewsqueakIA32ABIPlugin subclass: #NewsqueakIA32ABIPluginSimulator
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-Plugins-Alien'!

Item was removed:
- ----- Method: NewsqueakIA32ABIPluginSimulator class>>shouldBeTranslated (in category 'translation') -----
- shouldBeTranslated
- 	^false!

Item was removed:
- ----- Method: NewsqueakIA32ABIPluginSimulator>>longAt: (in category 'memory access') -----
- longAt: byteAddress
- 	^interpreterProxy longAt: byteAddress!

Item was removed:
- ----- Method: NewsqueakIA32ABIPluginSimulator>>longAt:put: (in category 'memory access') -----
- longAt: byteAddress put: a32BitValue
- 	^interpreterProxy longAt: byteAddress put: a32BitValue!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurCog64VM (in category 'configurations') -----
  generateNewspeakSpurCog64VM
+ 	"No primitives since we can use those for the Cog VM"
- 	"No primitives since we can use those for the Spur Cog Newspeak VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
  		with: #(	ObjectMemory Spur64BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
  				NewspeakVM true)
  		to: (FileDirectory default directoryNamed: self sourceTree, '/nsspur64src') fullName
  		platformDir: (FileDirectory default directoryNamed: self sourceTree, '/platforms') fullName
  		including:#()
  !

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurCogVM (in category 'configurations') -----
  generateNewspeakSpurCogVM
+ 	"No primitives since we can use those for the Cog VM"
- 	"This tree also includes the Newspeak plugins.  But once the Alien plugins are harmonised
- 	 (which can be done now immutability support is being added to Spur) all VMs can share a
- 	 single set of plugin sources."
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
  		with: #(	ObjectMemory Spur32BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
  				NewspeakVM true)
  		to: (FileDirectory default pathFromURI: self sourceTree, '/nsspursrc')
  		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
+ 		including:#()
- 		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation
- 					DeflatePlugin DSAPlugin DropPlugin FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin
- 					ImmX11Plugin JPEGReadWriter2Plugin JPEGReaderPlugin LargeIntegersPlugin
- 					Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin RePlugin
- 					SecurityPlugin SocketPlugin SoundPlugin SqueakSSLPlugin SurfacePlugin
- 					UUIDPlugin UnixOSProcessPlugin UnixAioPlugin
- 					VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)
  !

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurStack64VM (in category 'configurations') -----
  generateNewspeakSpurStack64VM
+ 	"No primitives since we can use those for the Cog VM"
- 	"No primitives since we can use those from the Spur Cog Newspeak VM"
  	^VMMaker
  		generate: StackInterpreter
  		with: #( ObjectMemory Spur64BitMemoryManager
  				MULTIPLEBYTECODESETS true
  				NewspeakVM true
  				FailImbalancedPrimitives false)
  		to: (FileDirectory default directoryNamed: self sourceTree, '/nsspurstack64src') fullName
  		platformDir: (FileDirectory default directoryNamed: self sourceTree, '/platforms') fullName
  		including: #()!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurStackVM (in category 'configurations') -----
  generateNewspeakSpurStackVM
+ 	"No primitives since we can use those for the Cog VM"
- 	"No primitives since we can use those from the Spur Cog Newspeak VM"
  	^VMMaker
  		generate: StackInterpreter
  		with: #(	ObjectMemory Spur32BitMemoryManager
  				MULTIPLEBYTECODESETS true
  				NewspeakVM true
  				FailImbalancedPrimitives false)
  		to: (FileDirectory default directoryNamed: self sourceTree, '/nsspurstacksrc') fullName
  		platformDir: (FileDirectory default directoryNamed: self sourceTree, '/platforms') fullName
  		including: #()!



More information about the Vm-dev mailing list