[Vm-dev] VM Maker: VMMaker-oscog-EstebanLorenzano.144.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Feb 18 13:41:50 UTC 2012


Esteban Lorenzano uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker-oscog-EstebanLorenzano.144.mcz

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

Name: VMMaker-oscog-EstebanLorenzano.144
Author: EstebanLorenzano
Time: 18 February 2012, 10:37:50 am
UUID: 5248dc9f-6e7c-499e-a1d6-3e29d9726539
Ancestors: VMMaker-oscog-IgorStasenko.143

-#primitiveGetNextEvent now processing complex evenbts (for touch events)
-#readImageFromFile:HeapSize:StartingAt: now uses sqImageFileReadEntireImage
-IA32ABIPlugin>>#primInIOProcessEventsFlagAddress now has a preprocessor directive, because it is not being used with __APPLE__ platforms

=============== Diff against VMMaker-oscog-IgorStasenko.143 ===============

Item was changed:
  SystemOrganization addCategory: #'VMMaker-Building'!
  SystemOrganization addCategory: #'VMMaker-JIT'!
  SystemOrganization addCategory: #'VMMaker-Interpreter'!
  SystemOrganization addCategory: #'VMMaker-InterpreterSimulation'!
  SystemOrganization addCategory: #'VMMaker-JITSimulation'!
  SystemOrganization addCategory: #'VMMaker-Translation to C'!
  SystemOrganization addCategory: #'VMMaker-Support'!
  SystemOrganization addCategory: #'VMMaker-PostProcessing'!
  SystemOrganization addCategory: #'VMMaker-MemoryManager'!
  SystemOrganization addCategory: #'VMMaker-MemoryManagerSimulation'!
  SystemOrganization addCategory: #'VMMaker-Multithreading'!
  SystemOrganization addCategory: #'VMMaker-Tests'!
  SystemOrganization addCategory: #'VMMaker-Plugins'!
  SystemOrganization addCategory: #'VMMaker-SmartSyntaxPlugins'!
  SystemOrganization addCategory: #'VMMaker-Plugins-Alien'!
+ SystemOrganization addCategory: #'VMMaker-Plugins-Touch'!

Item was changed:
  ----- Method: CCodeGenerator>>emitCHeaderOn: (in category 'C code generator') -----
  emitCHeaderOn: aStream
  	"Emit the initial part of a source file on aStream, comprising the version stamp,
  	 the global struct usage flags, the header files and preamble code."
  
  	| headerClass |
  	headerClass := [vmClass coreInterpreterClass]
  						on: MessageNotUnderstood
  						do: [:ex| vmClass].
  	aStream nextPutAll: (self fileHeaderVersionStampForSourceClass: headerClass); cr; cr.
  	self emitGlobalStructFlagOn: aStream.
  
  	headerFiles addFirst: '"sq.h"'.
  	vmClass isInterpreterClass ifTrue:
  		[headerFiles addLast: '"sqMemoryAccess.h"'].
  	"Additional header files; include C library ones first."
  	self emitHeaderFiles: (headerFiles select: [:hdr| hdr includes: $<]) on: aStream.
  	"Additional header files; include squeak VM ones last"
  	self emitHeaderFiles: (headerFiles reject: [:hdr| hdr includes: $<]) on: aStream.
  
  	vmClass isInterpreterClass ifTrue:
  		[aStream cr; cr; nextPutAll: vmClass preambleCCode].
  
  	aStream cr!

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."
  	| address |
  	<export: true>
  	self
+ 		cCode: '
+ #ifndef __APPLE__ //Apple platform does not use this anymore
+ { extern int inIOProcessEvents; address = (sqInt)&inIOProcessEvents; }
+ #endif'
- 		cCode: '{ extern int inIOProcessEvents; address = (sqInt)&inIOProcessEvents; }'
  		inSmalltalk: [address := 0].
  	interpreterProxy methodReturnValue: (interpreterProxy positive32BitIntegerFor: address)!

Item was added:
+ SmartSyntaxInterpreterPlugin subclass: #IOSPlugin
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: 'VMBasicConstants'
+ 	category: 'VMMaker-Plugins-Touch'!

Item was added:
+ ----- Method: IOSPlugin>>primitiveShowKeyboard: (in category 'primitives') -----
+ primitiveShowKeyboard: showBoolean
+ 	<export: true>
+ 	<var: #showBoolean type: #int>
+ 	
+ 	self sqShowKeyboard: showBoolean.!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveGetNextEvent (in category 'I/O primitives') -----
  primitiveGetNextEvent
  	"Primitive. Return the next input event from the VM event queue."
+ 	| evtBuf arg value eventTypeIs |
- 	| evtBuf arg value |
  	<var: #evtBuf declareC:'int evtBuf[8] = { 0, 0, 0, 0, 0, 0, 0, 0 }'>
  	self cCode:'' inSmalltalk:[evtBuf := CArrayAccessor on: (IntegerArray new: 8)].
  	arg := self stackTop.
  	((objectMemory isArray: arg) and:[(objectMemory slotSizeOf: arg) = 8])  ifFalse:[^self primitiveFail].
  
  	self ioGetNextEvent: (self cCoerce: evtBuf to: 'sqInputEvent*').
  	self successful ifFalse:[^nil].
  
  	"Event type"
+ 	eventTypeIs := evtBuf at: 0.
  	self storeInteger: 0 ofObject: arg withValue: (evtBuf at: 0).
  	self successful ifFalse:[^nil].
  
+ 	"Event is Complex, assume evtBuf is populated correctly and return"
+ 	eventTypeIs = 6 
+ 		ifTrue: [ 
+ 			1 to: 7 do: [:i |
+ 				value := evtBuf at: i.
+ 				self storePointer: i ofObject: arg withValue: value]]
+ 	ifFalse: [
+ 		"Event time stamp"
+ 		self storeInteger: 1 ofObject: arg withValue: ((evtBuf at: 1) bitAnd: MillisecondClockMask).
+ 		self successful ifFalse:[^nil].	
- 	"Event time stamp"
- 	self storeInteger: 1 ofObject: arg withValue: ((evtBuf at: 1) bitAnd: MillisecondClockMask).
- 	self successful ifFalse:[^nil].
  
+ 		"Event arguments"
+ 		2 to: 7 do:[:i|
+ 			value := evtBuf at: i.
+ 			(objectMemory isIntegerValue: value)
+ 				ifTrue:[self storeInteger: i ofObject: arg withValue: value]
+ 				ifFalse:[
+ 					value := self positive32BitIntegerFor: value.
+ 					objectMemory storePointer: i ofObject: arg withValue: value] ] ].
- 	"Event arguments"
- 	2 to: 7 do:[:i|
- 		value := evtBuf at: i.
- 		(objectMemory isIntegerValue: value)
- 			ifTrue:[self storeInteger: i ofObject: arg withValue: value]
- 			ifFalse:[value := self positive32BitIntegerFor: value.
- 				objectMemory storePointer: i ofObject: arg withValue: value]].
  
  	self successful ifFalse:[^nil].
  	self pop: 1!

Item was changed:
  ----- Method: StackInterpreter>>readImageFromFile:HeapSize:StartingAt: (in category 'image save/restore') -----
  readImageFromFile: f HeapSize: desiredHeapSize StartingAt: imageOffset
  	"Read an image from the given file stream, allocating the given amount of memory to its object heap. Fail if the image has an unknown format or requires more than the given amount of memory."
  	"Details: This method detects when the image was stored on a machine with the opposite byte ordering from this machine and swaps the bytes automatically. Furthermore, it allows the header information to start 512 bytes into the file, since some file transfer programs for the Macintosh apparently prepend a Mac-specific header of this size. Note that this same 512 bytes of prefix area could also be used to store an exec command on Unix systems, allowing one to launch Smalltalk by invoking the image name as a command."
  	"This code is based on C code by Ian Piumarta and Smalltalk code by Tim Rowledge. Many thanks to both of you!!!!"
  
  	| swapBytes headerStart headerSize dataSize oldBaseAddr hdrNumStackPages
  	  minimumMemory memStart bytesRead bytesToShift heapSize hdrEdenBytes
  	  headerFlags hdrMaxExtSemTabSize |
  	<var: #f type: 'sqImageFile '>
  	<var: #memStart type: 'usqInt'>
  	<var: #desiredHeapSize type: 'usqInt'>
  	<var: #headerStart type: 'squeakFileOffsetType '>
  	<var: #dataSize type: 'size_t '>
  	<var: #imageOffset type: 'squeakFileOffsetType '>
  
  	metaclassSizeBytes := 6 * BytesPerWord.	"guess (Metaclass instSize * BPW)"
  	swapBytes := self checkImageVersionFrom: f startingAt: imageOffset.
  	headerStart := (self sqImageFilePosition: f) - BytesPerWord.  "record header start position"
  
  	headerSize			:= self getLongFromFile: f swap: swapBytes.
  	dataSize			:= self getLongFromFile: f swap: swapBytes.
  	oldBaseAddr		:= self getLongFromFile: f swap: swapBytes.
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes). "N.B.  not used."
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags			:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory		:= self getLongFromFile: f swap: swapBytes.
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default.  Can be changed via vmParameterAt: 43 put: n.
  	 Can be set as a preference (Info.plist, VM.ini, command line etc).
  	 If desiredNumStackPages is already non-zero then it has been
  	 set as a preference.  Ignore (but preserve) the header's default."
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to images run on Cog."
  	theUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	hdrEdenBytes		:= self getLongFromFile: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"decrease Squeak object heap to leave extra memory for the VM"
  	heapSize := self cCode: 'reserveExtraCHeapBytes(desiredHeapSize, extraVMMemory)'.
  
  	"compare memory requirements with availability".
  	minimumMemory := dataSize + objectMemory edenBytes + self interpreterAllocationReserveBytes.
  	heapSize < minimumMemory ifTrue:
  		[self insufficientMemorySpecifiedError].
  
  	"allocate a contiguous block of memory for the Squeak heap"
  	objectMemory memory: (self
  								allocateMemory: heapSize
  								minimum: minimumMemory
  								imageFile: f
  								headerSize: headerSize).
  		
  	objectMemory memory = nil ifTrue: [self insufficientMemoryAvailableError].
  
  	memStart := objectMemory startOfMemory.
  	objectMemory setMemoryLimit: (memStart + heapSize) - 24.  "decrease memoryLimit a tad for safety"
  	objectMemory setEndOfMemory: memStart + dataSize.
  
  	"position file after the header"
  	self sqImageFile: f Seek: headerStart + headerSize.
  
  	"read in the image in bulk, then swap the bytes if necessary"
+ 	bytesRead := self cCode: 'sqImageFileReadEntireImage(pointerForOop(memory), sizeof(unsigned char), dataSize, f)'.
- 	bytesRead := self cCode: 'sqImageFileRead(pointerForOop(memory), sizeof(unsigned char), dataSize, f)'.
  	bytesRead ~= dataSize ifTrue: [self unableToReadImageError].
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	"compute difference between old and new memory base addresses"
  	bytesToShift := memStart - oldBaseAddr.
  	self initializeInterpreter: bytesToShift.  "adjusts all oops to new location"
  	^dataSize
  !



More information about the Vm-dev mailing list