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

commits at source.squeak.org commits at source.squeak.org
Fri Dec 12 23:50:50 UTC 2014


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

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

Name: VMMaker.oscog-eem.982
Author: eem
Time: 12 December 2014, 3:47:55.686 pm
UUID: 067c9e12-04dc-44f6-9888-d38d55e243f5
Ancestors: VMMaker.oscog-eem.981

Provide accessors in InterpreterPlugin to answer
integer objects for positive and signed machine
words.

Use these to make the ALien plugins 64-bit capable.

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

Item was changed:
  ----- Method: IA32ABIPlugin>>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)."
- 	"Answer the unsigned 32-bit integer comprising the address field (the second 32-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.
- 	valueOop := interpreterProxy positive32BitIntegerFor: value.
  	^interpreterProxy methodReturnValue: valueOop!

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)."
- 	"Store an unsigned integer into the size field (the second 32 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.
- 	value := interpreterProxy positive32BitValueOf: valueOop.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	self longAt: rcvr + interpreterProxy baseHeaderSize + interpreterProxy bytesPerOop put: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: IA32ABIPlugin>>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>
- 	<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].
+ 	addr := self cCode: [(self c: 1 alloc: byteSize) asUnsignedInteger] inSmalltalk: [Alien Ccalloc: byteSize].
- 	self cCode: 'addr = (sqInt)calloc(1,byteSize)'
- 		inSmalltalk: [addr := self Ccalloc: byteSize].
  	addr = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrNoCMemory].
+ 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: addr)!
- 	interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: addr)!

Item was changed:
  ----- Method: IA32ABIPlugin>>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 |
- 	| address |
  	<export: true>
+ 	<var: 'inIOProcessEvents' declareC: 'extern int inIOProcessEvents'>
+ 	self cCode: '' inSmalltalk: [inIOProcessEvents = 0].
+ 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: (self addressOf: inIOProcessEvents))!
- 	self
- 		cCode: '{ extern int inIOProcessEvents; address = (sqInt)&inIOProcessEvents; }'
- 		inSmalltalk: [address := 0].
- 	interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: address)!

Item was changed:
  ----- Method: IA32ABIPlugin>>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)!
- 	interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: address asUnsignedInteger)!

Item was changed:
  ----- Method: IA32ABIPlugin>>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)!
- 	interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: libraryHandle asUnsignedInteger)!

Item was changed:
  ----- Method: IA32ABIPlugin>>primMalloc (in category 'primitives-memory management') -----
  primMalloc
  	"Malloc arg bytes."
  	"primMalloc: byteSize <Integer> <^Integer>
  		<primitive: 'primMalloc' error: errorCode module: 'IA32ABI'>"
  	| byteSize addr |
  	<export: true>
- 	<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].
+ 	addr := self cCode: [(self malloc: byteSize) asUnsignedInteger] inSmalltalk: [Alien Cmalloc: byteSize].
- 	addr := self cCode: [self malloc: byteSize] inSmalltalk: [Alien Cmalloc: byteSize].
  	addr = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrNoCMemory].
+ 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: addr)!
- 	interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: addr asUnsignedInteger)!

Item was changed:
  ----- Method: IA32ABIPlugin>>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)."
- 	"Answer the signed 32-bit integer comprising the size field (the first 32-bit field)."
  	"<Alien> primSizeField ^<Integer>
  		<primitive: 'primSizeField' error: errorCode module: 'IA32ABI'>"
  	| rcvr value valueOop |
  	<export: true>
  
  	rcvr := interpreterProxy stackValue: 0.
  	value := (self longAt: rcvr + interpreterProxy baseHeaderSize) signedIntFromLong.
+ 	valueOop := self signedMachineIntegerFor: value.
- 	valueOop := interpreterProxy signed32BitIntegerFor: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: IA32ABIPlugin>>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.
- 	value := interpreterProxy signed32BitValueOf: valueOop.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	self longAt: rcvr + interpreterProxy baseHeaderSize put: value signedIntToLong.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: IA32ABIPlugin>>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)!
- 	address := self cCode: '(sqInt)thunkEntry' inSmalltalk: [0].
- 	interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: address)!

Item was added:
+ ----- Method: InterpreterPlugin>>positiveMachineIntegerFor: (in category 'API access') -----
+ positiveMachineIntegerFor: value
+ 	<var: #value type: #'unsigned long'>
+ 	<inline: true>
+ 	^interpreterProxy bytesPerWord = 8
+ 		ifTrue: [interpreterProxy positive64BitIntegerFor: value]
+ 		ifFalse: [interpreterProxy positive32BitIntegerFor: value]!

Item was added:
+ ----- Method: InterpreterPlugin>>signedMachineIntegerFor: (in category 'API access') -----
+ signedMachineIntegerFor: value
+ 	<var: #value type: #'unsigned long'>
+ 	<inline: true>
+ 	^interpreterProxy bytesPerWord = 8
+ 		ifTrue: [interpreterProxy signed64BitIntegerFor: value]
+ 		ifFalse: [interpreterProxy signed32BitIntegerFor: value]!

Item was changed:
  ----- 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)."
- 	"Answer the unsigned 32-bit integer comprising the address field (the second 32-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.
- 	valueOop := interpreterProxy positive32BitIntegerFor: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- Method: NewsqueakIA32ABIPlugin>>primAddressFieldPut (in category 'primitives-accessing') -----
  primAddressFieldPut
+ 	"Store an unsigned integer into the size field (the second 32/64 bit field; little endian)."
- 	"Store an unsigned integer into the size field (the second 32 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.
- 	value := interpreterProxy positive32BitValueOf: 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: 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>
- 	<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].
+ 	addr := self cCode: [(self c: 1 alloc: byteSize) asUnsignedInteger] inSmalltalk: [Alien Ccalloc: byteSize].
- 	self cCode: 'addr = (sqInt)calloc(1,byteSize)'
- 		inSmalltalk: [addr := self Ccalloc: byteSize].
  	addr = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrNoCMemory].
+ 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: addr)!
- 	interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: addr)!

Item was changed:
  ----- 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 |
- 	| address |
  	<export: true>
+ 	<var: 'inIOProcessEvents' declareC: 'extern int inIOProcessEvents'>
+ 	self cCode: '' inSmalltalk: [inIOProcessEvents = 0].
+ 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: (self addressOf: inIOProcessEvents))!
- 	self
- 		cCode: '{ extern int inIOProcessEvents; address = (sqInt)&inIOProcessEvents; }'
- 		inSmalltalk: [address := 0].
- 	interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: address)!

Item was changed:
  ----- 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)!
- 	interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: address asUnsignedInteger)!

Item was changed:
  ----- 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)!
- 	interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: libraryHandle asUnsignedInteger)!

Item was changed:
  ----- 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>
- 	<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].
+ 	addr := self cCode: [(self malloc: byteSize) asUnsignedInteger] inSmalltalk: [Alien Cmalloc: byteSize].
- 	addr := self cCode: [self malloc: byteSize] inSmalltalk: [Alien Cmalloc: byteSize].
  	addr = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrNoCMemory].
+ 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: addr)!
- 	interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: addr asUnsignedInteger)!

Item was changed:
  ----- 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)."
- 	"Answer the signed 32-bit integer comprising the size field (the first 32-bit field)."
  	"<Alien> primSizeField ^<Integer>
  		<primitive: 'primSizeField' error: errorCode module: 'IA32ABI'>"
  	| rcvr value valueOop |
  	<export: true>
  
  	rcvr := interpreterProxy stackValue: 0.
  	value := (self longAt: rcvr + interpreterProxy baseHeaderSize) signedIntFromLong.
+ 	valueOop := self signedMachineIntegerFor: value.
- 	valueOop := interpreterProxy signed32BitIntegerFor: value.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- 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.
- 	value := interpreterProxy signed32BitValueOf: valueOop.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(interpreterProxy isOopImmutable: rcvr) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrNoModification].
  	self longAt: rcvr + interpreterProxy baseHeaderSize put: value signedIntToLong.
  	^interpreterProxy methodReturnValue: valueOop!

Item was changed:
  ----- 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)!
- 	address := self cCode: '(sqInt)thunkEntry' inSmalltalk: [0].
- 	interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: address)!



More information about the Vm-dev mailing list