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

commits at source.squeak.org commits at source.squeak.org
Wed Dec 10 23:17:50 UTC 2014


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

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

Name: VMMaker.oscog-eem.974
Author: eem
Time: 10 December 2014, 3:15:09.286 pm
UUID: 7ca9044b-c2d1-4605-b2b6-2b8ffc66c096
Ancestors: VMMaker.oscog-eem.973

Fix 64-bit issues in the AsynchFilePlugin.

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

Item was changed:
  ----- Method: AsynchFilePlugin>>asyncFileValueOf: (in category 'primitives') -----
  asyncFileValueOf: oop
+ 	"Answer a pointer to the first byte of the async file record within the given
+ 	 Smalltalk bytes object, or fail and answer nil if oop is not an async file record."
- 	"Answer a pointer to the first byte of the async file record within the given Smalltalk bytes object, or nil if oop is not an async file record."
  
  	<returnTypeC: 'AsyncFile *'>
+ 	((interpreterProxy isBytes: oop)
+ 	 and: [(interpreterProxy byteSizeOf: oop) = (self sizeof: #AsyncFile)]) ifTrue:
+ 		[^self cCoerceSimple: (interpreterProxy firstIndexableField: oop) to: 'AsyncFile *'].
+ 	interpreterProxy primitiveFailFor: PrimErrBadArgument.
+ 	^nil!
- 	interpreterProxy success:
- 		((interpreterProxy isBytes: oop)
- 		 and: [(interpreterProxy slotSizeOf: oop) = (self cCode: 'sizeof(AsyncFile)')]).
- 	^interpreterProxy failed
- 		ifTrue: [nil]
- 		ifFalse: [self cCoerceSimple: (interpreterProxy firstIndexableField: oop) to: 'AsyncFile *']!

Item was changed:
  ----- Method: AsynchFilePlugin>>primitiveAsyncFileOpen:forWrite:semaIndex: (in category 'primitives') -----
  primitiveAsyncFileOpen: fileName forWrite: writeFlag semaIndex: semaIndex 
  	| fileNameSize fOop f okToOpen |
  	<var: #f type: 'AsyncFile *'>
  	self primitive: 'primitiveAsyncFileOpen' parameters: #(#String #Boolean #SmallInteger ).
+ 	fileNameSize := interpreterProxy byteSizeOf: (fileName asOop: String).
- 	fileNameSize := interpreterProxy slotSizeOf: (fileName asOop: String).
  	"If the security plugin can be loaded, use it to check for permission.
  	If not, assume it's ok"
+ 	sCOAFfn ~= 0 ifTrue:
+ 		[okToOpen := self cCode: '((sqInt (*) (char *, sqInt, sqInt)) sCOAFfn)(fileName, fileNameSize, writeFlag)'
+ 							inSmalltalk: [true].
+ 		 okToOpen ifFalse:
+ 			[^interpreterProxy primitiveFail]].
+ 	fOop := interpreterProxy
+ 				instantiateClass: interpreterProxy classByteArray
+ 				indexableSize: (self sizeof: #AsyncFile).
- 	sCOAFfn ~= 0
- 		ifTrue: [okToOpen := self cCode: ' ((sqInt (*) (char *, sqInt, sqInt)) sCOAFfn)(fileName, fileNameSize, writeFlag)'.
- 			okToOpen ifFalse: [^ interpreterProxy primitiveFail]].
- 	fOop := interpreterProxy instantiateClass: interpreterProxy classByteArray indexableSize: (self cCode: 'sizeof(AsyncFile)').
  	f := self asyncFileValueOf: fOop.
+ 	interpreterProxy failed ifFalse:
+ 		[self cCode: 'asyncFileOpen(f, fileName, fileNameSize, writeFlag, semaIndex)'].
+ 	^fOop!
- 	interpreterProxy failed ifFalse: [self cCode: 'asyncFileOpen(f, (int)fileName, fileNameSize, writeFlag, semaIndex)'].
- 	^ fOop!

Item was changed:
  ----- Method: AsynchFilePlugin>>primitiveAsyncFileReadResult:intoBuffer:at:count: (in category 'primitives') -----
  primitiveAsyncFileReadResult: fhandle intoBuffer: buffer at: start count: num 
  	| bufferSize bufferPtr r f count startIndex |
  	<var: #f type: 'AsyncFile *'>
  	self primitive: 'primitiveAsyncFileReadResult' parameters: #(Oop Oop SmallInteger SmallInteger ).
  
  	f := self asyncFileValueOf: fhandle.
  	count := num.
  	startIndex := start.
  	bufferSize := interpreterProxy slotSizeOf: buffer. "in bytes or words"
  	(interpreterProxy isWords: buffer)
  		ifTrue: ["covert word counts to byte counts"
  			count := count * 4.
  			startIndex := startIndex - 1 * 4 + 1.
  			bufferSize := bufferSize * 4].
  	interpreterProxy success: (startIndex >= 1 and: [startIndex + count - 1 <= bufferSize]).
  
+ 	bufferPtr := (self cCoerce: (interpreterProxy firstIndexableField: buffer) to:#sqInt) + startIndex - 1. 	"adjust for zero-origin indexing"
- 	bufferPtr := (self cCoerce: (interpreterProxy firstIndexableField: buffer) to: 'int') + startIndex - 1. 	"adjust for zero-origin indexing"
  	interpreterProxy failed ifFalse: [r := self cCode: 'asyncFileReadResult(f, bufferPtr, count)'].
  	^ r asOop: SmallInteger!

Item was changed:
  ----- Method: AsynchFilePlugin>>primitiveAsyncFileWriteStart:fPosition:fromBuffer:at:count: (in category 'primitives') -----
  primitiveAsyncFileWriteStart: fHandle fPosition: fPosition fromBuffer: buffer at: start count: num 
  	| f bufferSize bufferPtr count startIndex |
  	<var: #f type: 'AsyncFile *'>
  	self primitive: 'primitiveAsyncFileWriteStart' parameters: #(Oop SmallInteger Oop SmallInteger SmallInteger ).
  	f := self asyncFileValueOf: fHandle.
  	interpreterProxy failed ifTrue: [^ nil].
  
  	count := num.
  	startIndex := start.
  	bufferSize := interpreterProxy slotSizeOf: buffer.	"in bytes or words"
  	(interpreterProxy isWords: buffer)
  		ifTrue: ["covert word counts to byte counts"
  			count := count * 4.
  			startIndex := startIndex - 1 * 4 + 1.
  			bufferSize := bufferSize * 4].
  	interpreterProxy success: (startIndex >= 1 and: [startIndex + count - 1 <= bufferSize]).
+ 	bufferPtr := (self cCoerce: (interpreterProxy firstIndexableField: buffer) to: #sqInt) + startIndex - 1.	"adjust for zero-origin indexing"
- 	bufferPtr := (self cCoerce: (interpreterProxy firstIndexableField: buffer) to: 'int') + startIndex - 1.	"adjust for zero-origin indexing"
  	interpreterProxy failed ifFalse: [self cCode: 'asyncFileWriteStart(f, fPosition, bufferPtr, count)']!

Item was added:
+ ----- Method: AsynchFilePlugin>>sizeof: (in category 'simulation') -----
+ sizeof: objectSymbolOrClass
+ 	<doNotGenerate>
+ 	objectSymbolOrClass isInteger ifTrue:
+ 		[^interpreterProxy wordSize].
+ 	objectSymbolOrClass == #AsyncFile ifTrue:
+ 		[^interpreterProxy wordSize * 2].
+ 	^super sizeof: objectSymbolOrClass!



More information about the Vm-dev mailing list