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

commits at source.squeak.org commits at source.squeak.org
Fri Jan 30 20:39:06 UTC 2015


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

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

Name: VMMaker.oscog-eem.1030
Author: eem
Time: 30 January 2015, 12:37:44.348 pm
UUID: 714f922a-8349-4094-b2e2-359fd5140db9
Ancestors: VMMaker.oscog-eem.1029

Fix 64-bit warnings in AsynchFilePlugin and in
#Array parameters in the SmartSyntaxInterpreterPlugins.

Fix a warning in the Alien plgins.

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

Item was changed:
  ----- Method: Array class>>ccg:prolog:expr:index: (in category '*VMMaker-plugin generation') -----
  ccg: cg prolog: aBlock expr: aString index: anInteger
  
  	^cg 
  		ccgLoad: aBlock 
  		expr: aString 
+ 		asOopPtrFrom: anInteger
- 		asIntPtrFrom: anInteger
  		andThen: (cg ccgValBlock: 'isIndexable')!

Item was changed:
  ----- Method: AsynchFilePlugin>>primitiveAsyncFileClose: (in category 'primitives') -----
  primitiveAsyncFileClose: fh 
  	| f |
  	<var: #f type: 'AsyncFile *'>
  	self primitive: 'primitiveAsyncFileClose' parameters: #(Oop ).
  	f := self asyncFileValueOf: fh.
+ 	interpreterProxy failed ifFalse:
+ 		[self asyncFileClose: f]!
- 	self asyncFileClose: f!

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 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]).
  
+ 	interpreterProxy failed ifFalse:
+ 		["adjust for zero-origin indexing"
+ 		 bufferPtr := (self cCoerce: (interpreterProxy firstIndexableField: buffer) to:#sqInt) + startIndex - 1.
+ 		 r := self asyncFile: f Read: bufferPtr asVoidPointer Result: count].
- 	bufferPtr := (self cCoerce: (interpreterProxy firstIndexableField: buffer) to:#sqInt) + 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>>primitiveAsyncFileReadStart:fPosition:count: (in category 'primitives') -----
  primitiveAsyncFileReadStart: fHandle fPosition: fPosition count: count
  	| f |
  	<var: #f type: 'AsyncFile *'>
  	self primitive: 'primitiveAsyncFileReadStart' parameters: #(Oop SmallInteger SmallInteger).
  	f := self asyncFileValueOf: fHandle.
+ 	interpreterProxy failed ifFalse:
+ 		[self asyncFile: f Read: fPosition Start: count]
- 	self cCode: 'asyncFileReadStart(f, fPosition, count)'
  !

Item was changed:
  ----- Method: AsynchFilePlugin>>primitiveAsyncFileWriteResult: (in category 'primitives') -----
  primitiveAsyncFileWriteResult: fHandle
- 
  	| f r |
  	<var: #f type: 'AsyncFile *'>
  	self primitive: 'primitiveAsyncFileWriteResult' parameters:#(Oop).
  
  	f := self asyncFileValueOf: fHandle.
+ 	interpreterProxy failed ifFalse:
+ 		[r := self asyncFileWriteResult: f.
+ 		 ^r asOop: SmallInteger]!
- 	r := self cCode:' asyncFileWriteResult(f)'.
- 	^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 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]).
+ 
+ 	interpreterProxy failed ifFalse:
+ 		["adjust for zero-origin indexing"
+ 		 bufferPtr := (self cCoerce: (interpreterProxy firstIndexableField: buffer) to: #sqInt) + startIndex - 1.
+ 		 self async: f File: fPosition Write: bufferPtr asVoidPointer Start: count]!
- 	bufferPtr := (self cCoerce: (interpreterProxy firstIndexableField: buffer) to: #sqInt) + startIndex - 1.	"adjust for zero-origin indexing"
- 	interpreterProxy failed ifFalse: [self cCode: 'asyncFileWriteStart(f, fPosition, bufferPtr, count)']!

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 |
  	<export: true>
  	<var: 'inIOProcessEvents' declareC: 'extern int inIOProcessEvents'>
  	self cCode: '' inSmalltalk: [inIOProcessEvents = 0].
+ 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: (self addressOf: inIOProcessEvents) asUnsignedInteger)!
- 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: (self addressOf: inIOProcessEvents))!

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 |
  	<export: true>
  	<var: 'inIOProcessEvents' declareC: 'extern int inIOProcessEvents'>
  	self cCode: '' inSmalltalk: [inIOProcessEvents = 0].
+ 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: (self addressOf: inIOProcessEvents) asUnsignedInteger)!
- 	interpreterProxy methodReturnValue: (self positiveMachineIntegerFor: (self addressOf: inIOProcessEvents))!

Item was added:
+ ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asOopPtrFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asOopPtrFrom: anInteger
+ 	"Answer codestring for integer pointer to first indexable field of object (without validating side-effect), as described in comment to ccgLoad:expr:asRawOopFrom:"
+ 
+ 	^aBlock value: (String streamContents:
+ 		[:aStream |
+ 		 aStream
+ 			nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
+ 			crtab: 4;
+ 			nextPutAll: '(interpreterProxy stackValue:';
+ 			print: anInteger;
+ 			nextPutAll:	'))';
+ 			crtab: 3;
+ 			nextPutAll: 'to: ''sqInt *'''])!

Item was added:
+ ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asOopPtrFrom:andThen: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asOopPtrFrom: anInteger andThen: valBlock
+ 	"Answer codestring for integer pointer to first indexable field of object (without validating side-effect unless specified in valBlock), as described in comment to ccgLoad:expr:asRawOopFrom:"
+ 
+ 	^(valBlock value: anInteger), '.',
+ 	 (aBlock value: (String streamContents:
+ 		[:aStream |
+ 		aStream
+ 			nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
+ 			crtab: 4;
+ 			nextPutAll: '(interpreterProxy stackValue:';
+ 			print: anInteger;
+ 			nextPutAll:	'))';
+ 			crtab: 3;
+ 			nextPutAll: 'to: ''sqInt *''']))!



More information about the Vm-dev mailing list