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

commits at source.squeak.org commits at source.squeak.org
Thu Jan 30 21:33:38 UTC 2020


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

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

Name: VMMaker.oscog-eem.2689
Author: eem
Time: 30 January 2020, 1:33:22.601531 pm
UUID: f47416a6-8fa0-4af1-b9d2-5f46f6e2ea73
Ancestors: VMMaker.oscog-eem.2688

Cogit: DUAL_MAPPED_CODE_ZONE, build on the realization that the original code zone can be mapped shared to the writable zone to revert to the original layout with the code zone housed in the initial alloc of memory at the base.  This requires a new executbale permissions applyer that will also do the dual mapping, sqMakeMemoryExecutableFrom:To:CodeToDataDelta:, whose C code will be written sortly.

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

Item was changed:
  StackInterpreterPrimitives subclass: #CoInterpreter
+ 	instanceVariableNames: 'cogit cogMethodZone gcMode cogCodeSize desiredCogCodeSize heapBase lastCoggableInterpretedBlockMethod deferSmash deferredSmash primTraceLog primTraceLogIndex traceLog traceLogIndex traceSources cogCompiledCodeCompactionCalledFor statCodeCompactionCount statCodeCompactionUsecs lastUncoggableInterpretedBlockMethod flagInterpretedMethods maxLiteralCountForCompile minBackwardJumpCountForCompile CFramePointer CStackPointer'
- 	instanceVariableNames: 'cogit cogMethodZone gcMode cogCodeSize desiredCogCodeSize heapBase lastCoggableInterpretedBlockMethod deferSmash deferredSmash primTraceLog primTraceLogIndex traceLog traceLogIndex traceSources cogCompiledCodeCompactionCalledFor statCodeCompactionCount statCodeCompactionUsecs lastUncoggableInterpretedBlockMethod flagInterpretedMethods maxLiteralCountForCompile minBackwardJumpCountForCompile CFramePointer CStackPointer effectiveCogCodeSize'
  	classVariableNames: 'CSCallbackEnter CSCallbackLeave CSCheckEvents CSEnterCriticalSection CSExitCriticalSection CSOwnVM CSResume CSSignal CSSuspend CSSwitchIfNeccessary CSThreadBind CSThreadSchedulingLoop CSWait CSYield HasBeenReturnedFromMCPC HasBeenReturnedFromMCPCOop MFMethodFlagFrameIsMarkedFlag MinBackwardJumpCountForCompile PrimNumberHashMultiply PrimTraceLogSize RumpCStackSize TraceBlockActivation TraceBlockCreation TraceBufferSize TraceCodeCompaction TraceContextSwitch TraceDisownVM TraceFullGC TraceIncrementalGC TraceIsFromInterpreter TraceIsFromMachineCode TraceOwnVM TracePreemptDisowningThread TracePrimitiveFailure TracePrimitiveRetry TraceSources TraceStackOverflow TraceThreadSwitch TraceVMCallback TraceVMCallbackReturn'
  	poolDictionaries: 'CogMethodConstants VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  
  !CoInterpreter commentStamp: 'eem 10/10/2019 09:08' prior: 0!
  I am a variant of the StackInterpreter that can co-exist with the Cog JIT.  I interpret unjitted methods, either because they have been found for the first time or because they are judged to be too big to JIT.  See CogMethod class's comment for method interoperability.
  
  cogCodeSize
  	- the current size of the machine code zone
  
  cogCompiledCodeCompactionCalledFor
  	- a variable set when the machine code zone runs out of space, causing a machine code zone compaction at the next available opportunity
  
  cogMethodZone
  	- the manager for the machine code zone (instance of CogMethodZone)
  
  cogit
  	- the JIT (co-jit) (instance of SimpleStackBasedCogit, StackToRegisterMappoingCogit, etc)
  
  deferSmash
  	- a flag causing deferral of smashes of the stackLimit around the call of functionSymbol (for assert checks)
  
  deferredSmash
  	- a flag noting deferral of smashes of the stackLimit around the call of functionSymbol (for assert checks)
  
  desiredCogCodeSize
  	- the desred size of the machine code zone, set at startup or via primitiveVMParameter to be written at snapshot time
  
  flagInterpretedMethods
  	- true if methods that are interpreted shoudl have their flag bit set (used to identity methods that are interpreted because they're unjittable for some reason)
  
  gcMode
  	- the variable holding the gcMode, used to inform the cogit of how to scan the machine code zone for oops on GC
  
  heapBase
  	- the address in memory of the base of the objectMemory's heap, which is immediately above the machine code zone
  
  lastCoggableInterpretedBlockMethod
  	- a variable used to invoke the cogit for a block mehtod being invoked repeatedly in the interpreter
  
  lastUncoggableInterpretedBlockMethod
  	- a variable used to avoid invoking the cogit for an unjittable method encountered on block evaluation
  
  maxLiteralCountForCompile
  	- the variable controlling which methods to jit.  methods with a literal count above this value will not be jitted (on the grounds that large methods are typically used for initialization, and take up a lot of space in the code zone)
  
  minBackwardJumpCountForCompile
  	- the variable controlling when to attempt to jit a method being interpreted.  If as many backward jumps as this occur, the current method will be jitted
  
  primTraceLog
  	- a small array implementing a crcular buffer logging the last N primitive invocations, GCs, code compactions, etc used for crash reporting
  
  primTraceLogIndex
  	- the index into primTraceLog of the next entry
  
  reenterInterpreter
  	- the jmpbuf used to jmp back into the interpreter when transitioning from machine code to the interpreter
  
  statCodeCompactionCount
  	- the count of machine code zone compactions
  
  statCodeCompactionUsecs
  	- the total microseconds spent in machine code zone compactions
  
  traceLog
  	- a log of various events, used in debugging
  
  traceLogIndex
  	- the index into traceLog of the next entry
  
  traceSources
  	- the names associated with the codes of events in traceLog
  
  CFramePointer
  	- if in use, the value of the C frame pointer on most recent entry to the interpreter after start-up or a callback.  Used to establish the C stack when calling the run-time from generated machine code.
  
  CStackPointer
  	- the value of the C stack pointer on most recent entry to the interpreter after start-up or a callback.  Used to establish the C stack when calling the run-time from generated machine code.!

Item was changed:
  ----- Method: CoInterpreter>>effectiveCogCodeSize (in category 'accessing') -----
  effectiveCogCodeSize
  	"With the single-mapped regime the effectiveCogCodeSize is cogCodeSize.
+ 	 With the dual-mapped regime then in production effectiveCogCodeSize is
+ 	 cogCodeSize and in simulation it is two times cogCodeSize (meaning we
+ 	 simulate a dual zone by having two copies of the zone at the start of memory)."
+ 	^cogCodeSize!
- 	 With the dual-mapped regime then in production effectiveCogCodeSize is zero
- 	 (meaning that the code zone is outside of memory), and in simulation it is
- 	 two times cogCodeSize (meaning we simulate a dual zone by having two
- 	copies of the zone at the start of memory)."
- 	^effectiveCogCodeSize!

Item was added:
+ ----- Method: CoInterpreter>>initializeCodeGenerator (in category 'initialization') -----
+ initializeCodeGenerator
+ 	cogit
+ 		initializeCodeZoneFrom: (self cCode: [objectMemory memory] inSmalltalk: [Cogit guardPageSize])
+ 		upTo: (self cCode: [objectMemory memory] inSmalltalk: [Cogit guardPageSize]) + cogCodeSize!

Item was changed:
  ----- Method: CoInterpreter>>readImageFromFile:HeapSize:StartingAt: (in category 'image save/restore') -----
  readImageFromFile: f HeapSize: desiredHeapSize StartingAt: imageOffset
  	"Read an image from the given file stream, allocating an amount of memory to its object heap.
  	
  	 V3: desiredHeapSize is the total size of the heap.  Fail if the image has an unknown format or
  	 requires more than the specified amount of memory.
  
  	 Spur: desiredHeapSize is ignored; this routine will attempt to provide at least extraVMMemory's
+ 	 ammount of free space after the image is loaded, taking any free space in the image into account.
- 	 ammount of free space after the image is loaded, taking any free space in teh image into account.
  	 extraVMMemory is stored in the image header and is accessible as vmParameterAt: 23.  If
  	 extraVMMemory is 0, the value defaults to the default grow headroom.  Fail if the image has an
  	 unknown format or if sufficient memory cannot be allocated.
  
  	 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."
  
  	| swapBytes headerStart headerSize dataSize oldBaseAddr
  	  minimumMemory heapSize bytesRead bytesToShift firstSegSize
+ 	  hdrNumStackPages hdrEdenBytes hdrCogCodeSize headerFlags hdrMaxExtSemTabSize allocationReserve |
- 	  hdrNumStackPages hdrEdenBytes hdrCogCodeSize headerFlags hdrMaxExtSemTabSize
- 	  allocationReserve executableZone writableCodeZone |
  	<var: #f type: #sqImageFile>
  	<var: #heapSize type: #usqInt>
  	<var: #dataSize type: #'size_t'>
  	<var: #minimumMemory type: #usqInt>
  	<var: #desiredHeapSize type: #usqInt>
  	<var: #allocationReserve type: #usqInt>
  	<var: #headerStart type: #squeakFileOffsetType>
  	<var: #imageOffset type: #squeakFileOffsetType>
- 	<var: #executableZone type: #'char *'>
- 	<var: #writableCodeZone type: #'char *'>
  
  	metaclassNumSlots := 6.	"guess Metaclass instSize"
  	classNameIndex := 6.		"guess (Class instVarIndexFor: 'name' ifAbsent: []) - 1"
  	swapBytes := self checkImageVersionFrom: f startingAt: imageOffset.
  	headerStart := (self sqImageFilePosition: f) - 4.  "record header start position"
  
  	headerSize			:= self getWord32FromFile: 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 getWord32FromFile: f swap: swapBytes. "N.B.  ignored in V3."
  	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.
  	"This slot holds the size of the native method zone in 1k units. (pad to word boundary)."
  	hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024.
  	cogCodeSize := desiredCogCodeSize ~= 0
  						ifTrue: [desiredCogCodeSize]
  						ifFalse:
  							[hdrCogCodeSize = 0
  									ifTrue: [cogit defaultCogCodeSize]
  									ifFalse: [hdrCogCodeSize]].
  	cogCodeSize > cogit maxCogCodeSize ifTrue:
  		[cogCodeSize := cogit maxCogCodeSize].
  	hdrEdenBytes		:= self getWord32FromFile: 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].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  
- 	"To cope with modern OSs that disallow executing code in writable memory we dual-map
- 	 the code zone, one mapping with read/write permissions and the other with read/execute
- 	 permissions. In such a configuration the code zone has already been alloated and is not
- 	 included in (what is no longer) the initial alloc."
- 	self ioAllocateDualMappedCodeZone: (self addressOf: executableZone) OfSize: cogCodeSize WritableZone: (self addressOf: writableCodeZone).
- 	effectiveCogCodeSize := executableZone > 0 ifTrue: [0] ifFalse: [cogCodeSize].
  	"compare memory requirements with availability"
  	allocationReserve := self interpreterAllocationReserveBytes.
+ 	minimumMemory := cogCodeSize "no need to include the stackZone; this is alloca'ed"
- 	minimumMemory := "no need to include the stackZone; this is alloca'ed"
- 						effectiveCogCodeSize
  						+ dataSize
  						+ objectMemory newSpaceBytes
  						+ allocationReserve.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[| freeOldSpaceInImage headroom |
  			 freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes.
  			 headroom := objectMemory
  							initialHeadroom: extraVMMemory
  							givenFreeOldSpaceInImage: freeOldSpaceInImage.
  			 heapSize := objectMemory roundUpHeapSize:
+ 						   cogCodeSize "no need to include the stackZone; this is alloca'ed"
- 						   effectiveCogCodeSize "no need to include the stackZone; this is alloca'ed"
  						+ dataSize
  						+ headroom
  						+ objectMemory newSpaceBytes
  						+ (headroom > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])]
  		ifFalse:
+ 			[heapSize :=  cogCodeSize "no need to include the stackZone; this is alloca'ed"
- 			[heapSize :=  effectiveCogCodeSize "no need to include the stackZone; this is alloca'ed"
  						+ desiredHeapSize
  						+ objectMemory newSpaceBytes
  						+ (desiredHeapSize - dataSize > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve]).
  			 heapSize < minimumMemory ifTrue:
  				[self insufficientMemorySpecifiedError]].
  
  	"allocate a contiguous block of memory for the Squeak heap and ancilliary data structures"
  	objectMemory memory: (self
  								allocateMemory: heapSize
  								minimum: minimumMemory
  								imageFile: f
  								headerSize: headerSize) asUnsignedInteger.
  	objectMemory memory ifNil:
  		[self insufficientMemoryAvailableError].
  
  	heapBase := objectMemory
+ 					setHeapBase: objectMemory memory + cogCodeSize
- 					setHeapBase: objectMemory memory + effectiveCogCodeSize
  					memoryLimit: objectMemory memory + heapSize
+ 					endOfMemory: objectMemory memory + cogCodeSize + dataSize.
- 					endOfMemory: objectMemory memory + effectiveCogCodeSize + 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 := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  	bytesRead ~= dataSize ifTrue: [self unableToReadImageError].
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	"compute difference between old and new memory base addresses"
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.
  	self initializeInterpreter: bytesToShift.  "adjusts all oops to new location"
+ 	self initializeCodeGenerator.
- 	self initializeCodeGenerator: writableCodeZone executableZone: objectMemory memory.
  	^dataSize!

Item was changed:
  CoInterpreterMT subclass: #CogVMSimulator
+ 	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds lastYieldMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters eventQueue effectiveCogCodeSize expectedSends expecting'
- 	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds lastYieldMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters eventQueue expectedSends expecting'
  	classVariableNames: 'ByteCountsPerMicrosecond ExpectedSends NLRFailures NLRSuccesses'
  	poolDictionaries: ''
  	category: 'VMMaker-JITSimulation'!
  
  !CogVMSimulator commentStamp: 'eem 9/3/2013 11:16' prior: 0!
  This class defines basic memory access and primitive simulation so that the CoInterpreter can run simulated in the Squeak environment.  It also defines a number of handy object viewing methods to facilitate pawing around in the object memory.  Remember that you can test the Cogit using its class-side in-image compilation facilities.
  
  To see the thing actually run, you could (after backing up this image and changes), execute
  
  	(CogVMSimulator new openOn: Smalltalk imageName) test
  
  and be patient both to wait for things to happen, and to accept various things that may go wrong depending on how large or unusual your image may be.  We usually do this with a small and simple benchmark image.
  
  Here's an example to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
  
  (CogVMSimulator newWithOptions: #(Cogit StackToRegisterMappingCogit))
  	desiredNumStackPages: 8;
  	openOn: '/Users/eliot/Cog/startreader.image';
  	openAsMorph;
  	run
  
  Here's a hairier example that I (Eliot) actually use in daily development with some of the breakpoint facilities commented out.
  
  | cos proc opts |
  CoInterpreter initializeWithOptions: (opts := Dictionary newFromPairs: #(Cogit StackToRegisterMappingCogit)).
  CogVMSimulator chooseAndInitCogitClassWithOpts: opts.
  cos := CogVMSimulator new.
  "cos initializeThreadSupport." "to test the multi-threaded VM"
  cos desiredNumStackPages: 8. "to set the size of the stack zone"
  "cos desiredCogCodeSize: 8 * 1024 * 1024." "to set the size of the Cogit's code zone"
  cos openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'. "choose your favourite image"
  "cos setBreakSelector: 'r:degrees:'." "set a breakpoint at a specific selector"
  proc := cos cogit processor.
  "cos cogit sendTrace: 7." "turn on tracing"
  "set a complex breakpoint at a specific point in machine code"
  "cos cogit singleStep: true; breakPC: 16r56af; breakBlock: [:cg|  cos framePointer > 16r101F3C and: [(cos longAt: cos framePointer - 4) = 16r2479A and: [(cos longAt: 16r101F30) = (cos longAt: 16r101F3C) or: [(cos longAt: 16r101F2C) = (cos longAt: 16r101F3C)]]]]; sendTrace: 1".
  "[cos cogit compilationTrace: -1] on: MessageNotUnderstood do: [:ex|]." "turn on compilation tracing in the StackToRegisterMappingCogit"
  "cos cogit setBreakMethod: 16rB38880."
  cos
  	openAsMorph;
  	"toggleTranscript;" "toggleTranscript will send output to the Transcript instead of the morph's rather small window"
  	halt;
  	run!

Item was added:
+ ----- Method: CogVMSimulator>>effectiveCogCodeSize (in category 'accessing') -----
+ effectiveCogCodeSize
+ 	"With the single-mapped regime the effectiveCogCodeSize is cogCodeSize.
+ 	 With the dual-mapped regime then in production effectiveCogCodeSize is
+ 	 cogCodeSize and in simulation it is two times cogCodeSize (meaning we
+ 	 simulate a dual zone by having two copies of the zone at the start of memory)."
+ 	^effectiveCogCodeSize!

Item was changed:
  ----- Method: CogVMSimulator>>openOn:extraMemory: (in category 'initialization') -----
  openOn: fileName extraMemory: extraBytes
  	"CogVMSimulator new openOn: 'clone.im' extraMemory: 100000"
  
  	| f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes
  	  headerFlags firstSegSize heapSize
+ 	  hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize hdrCogCodeSize
+ 	  stackZoneSize methodCacheSize primTraceLogSize allocationReserve |
- 	  hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize
- 	  hdrCogCodeSize stackZoneSize methodCacheSize primTraceLogSize
- 	  allocationReserve executableZone writableCodeZone |
  	"open image file and read the header"
  
  	(f := self openImageFileNamed: fileName) ifNil: [^self].
  
  	"Set the image name and the first argument; there are
  	 no arguments during simulation unless set explicitly."
  	systemAttributes at: 1 put: fileName.
  
  	["begin ensure block..."
  	imageName := f fullName.
  	f binary.
  
  	version := self getWord32FromFile: f swap: false.  "current version: 16r1968 (=6504) vive la revolucion!!"
  	(self readableFormat: version)
  		ifTrue: [swapBytes := false]
  		ifFalse: [(version := version byteSwap32) = self imageFormatVersion
  					ifTrue: [swapBytes := true]
  					ifFalse: [self error: 'incomaptible image format']].
  	headerSize := self getWord32FromFile: f swap: swapBytes.
  	dataSize := self getLongFromFile: f swap: swapBytes.  "length of heap in file"
  	oldBaseAddr := self getLongFromFile: f swap: swapBytes.  "object memory base address of image"
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
  
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getWord32FromFile: 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"
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	stackZoneSize := self computeStackZoneSize.
  	"This slot holds the size of the native method zone in 1k units. (pad to word boundary)."
  	hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024.
  	cogCodeSize := desiredCogCodeSize ~= 0
  						ifTrue: [desiredCogCodeSize]
  						ifFalse:
  							[hdrCogCodeSize = 0
  									ifTrue: [cogit defaultCogCodeSize]
  									ifFalse: [hdrCogCodeSize]].
  	desiredCogCodeSize := hdrCogCodeSize.
  	self assert: f position = (objectMemory wordSize = 4 ifTrue: [40] ifFalse: [64]).
  	hdrEdenBytes	:= self getWord32FromFile: 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].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	self assert: f position = (objectMemory wordSize = 4 ifTrue: [48] ifFalse: [72]).
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  	"For Open PICs to be able to probe the method cache during
  	 simulation the methodCache must be relocated to memory."
  	methodCacheSize := methodCache size * objectMemory wordSize.
  	primTraceLogSize := primTraceLog size * objectMemory wordSize.
  
  	"To cope with modern OSs that disallow executing code in writable memory we dual-map
  	 the code zone, one mapping with read/write permissions and the other with read/execute
+ 	 permissions. In simulation all we can do is use memory, so if we're simulating dual mapping
+ 	 we use double the memory and simulate the memory sharing in the Cogit's backEnd."
+ 	effectiveCogCodeSize := (InitializationOptions at: #DUAL_MAPPED_COG_ZONE ifAbsent: [false])
+ 								ifTrue: [cogCodeSize * 2]
+ 								ifFalse: [cogCodeSize].
- 	 permissions. In such a configuration the code zone has already been alloated and is not
- 	 included in (what is no longer) the initial alloc."
- 	self ioAllocateDualMappedCodeZone: (self addressOf: executableZone put: [:v| executableZone := v])
- 		OfSize: cogCodeSize
- 		WritableZone: (self addressOf: writableCodeZone put: [:v| writableCodeZone := v]).
- 	"In simulation all we can do is use memory, so if we're simulating dual mapping we
- 	 use double the memory and simulate the memory sharing in the Cogit's backEnd."
- 	effectiveCogCodeSize := writableCodeZone > 0 ifTrue: [cogCodeSize * 2] ifFalse: [cogCodeSize].
  
  	"allocate interpreter memory. This list is in address order, low to high.
  	 In the actual VM the stack zone exists on the C stack."
  	heapBase := (Cogit guardPageSize
  				+ effectiveCogCodeSize
  				+ stackZoneSize
  				+ methodCacheSize
  				+ primTraceLogSize
  				+ self rumpCStackSize) roundUpTo: objectMemory allocationUnit.
  	"compare memory requirements with availability"
  	allocationReserve := self interpreterAllocationReserveBytes.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[| freeOldSpaceInImage headroom |
  			 freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes.
  			 headroom := objectMemory
  							initialHeadroom: extraVMMemory
  							givenFreeOldSpaceInImage: freeOldSpaceInImage.
  			 heapSize := objectMemory roundUpHeapSize:
  						   dataSize
  						+ headroom
  						+ objectMemory newSpaceBytes
  						+ (headroom > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])]
  		ifFalse:
  			[heapSize :=  dataSize
  						+ extraBytes
  						+ objectMemory newSpaceBytes
  						+ (extraBytes > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])].
  	heapBase := objectMemory
  					setHeapBase: heapBase
  					memoryLimit:  heapBase + heapSize
  					endOfMemory: heapBase + dataSize.
  
  	self assert: cogCodeSize \\ 4 = 0.
  	self assert: objectMemory memoryLimit \\ 4 = 0.
  	self assert: self rumpCStackSize \\ 4 = 0.
  	objectMemory allocateMemoryOfSize: objectMemory memoryLimit.
  	"read in the image in bulk, then swap the bytes if necessary"
  	f position: headerSize.
  	count := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  	count ~= dataSize ifTrue: [self halt]]
  		ensure: [f close].
  	self moveMethodCacheToMemoryAt: objectMemory cogCodeBase + effectiveCogCodeSize + stackZoneSize.
  	self movePrimTraceLogToMemoryAt: objectMemory cogCodeBase + effectiveCogCodeSize + stackZoneSize + methodCacheSize.
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.  "adjust pointers for zero base address"
  	UIManager default
  		informUser: 'Relocating object pointers...'
  		during: [self initializeInterpreter: bytesToShift].
+ 	self initializeCodeGenerator!
- 	writableCodeZone ~= 0
- 		ifTrue:
- 			[self initializeCodeGenerator: cogCodeSize + (Cogit guardPageSize * 2)
- 				executableZone: Cogit guardPageSize]
- 		ifFalse:
- 			[self initializeCodeGenerator: 0
- 				executableZone: Cogit guardPageSize]!

Item was added:
+ ----- Method: Cogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
+ initializeCodeZoneFrom: startAddress upTo: endAddress
+ 	<api>
+ 	self initializeBackend.
+ 	backEnd stopsFrom: startAddress to: endAddress - 1.
+ 	self sqMakeMemoryExecutableFrom: startAddress
+ 		To: endAddress
+ 		CodeToDataDelta: (self addressOf: codeToDataDelta put: [:v| codeToDataDelta := v]).
+ 	self cCode: '' inSmalltalk:
+ 		[backEnd stopsFrom: 0 to: guardPageSize - 1.
+ 		 self initializeProcessor].
+ 	codeBase := methodZoneBase := startAddress.
+ 	minValidCallAddress := (codeBase min: coInterpreter interpretAddress)
+ 								min: coInterpreter primitiveFailAddress.
+ 	methodZone manageFrom: methodZoneBase to: endAddress.
+ 	self assertValidDualZone.
+ 	self maybeGenerateCheckFeatures.
+ 	self maybeGenerateCheckLZCNT.
+ 	self maybeGenerateICacheFlush.
+ 	self generateVMOwnerLockFunctions.
+ 	self genGetLeafCallStackPointer.
+ 	self generateStackPointerCapture.
+ 	self generateTrampolines.
+ 	self computeEntryOffsets.
+ 	self computeFullBlockEntryOffsets.
+ 	self generateClosedPICPrototype.
+ 	self alignMethodZoneBase.
+ 	"repeat so that now the methodZone ignores the generated run-time"
+ 	methodZone manageFrom: methodZoneBase to: endAddress.
+ 	"N.B. this is assumed to be the last thing done in initialization; see Cogit>>initialized"
+ 	self generateOpenPICPrototype!

Item was changed:
  ----- Method: Cogit>>initializeCodeZoneFrom:upTo:writableCodeZone: (in category 'initialization') -----
  initializeCodeZoneFrom: startAddress upTo: endAddress writableCodeZone: writableCodeZone
  	<api>
+ 	<var: 'startAddress' type: #usqInt>
+ 	<var: 'endAddress' type: #usqInt>
+ 	<var: 'writableCodeZone' type: #usqInt>
  	"If the OS platform requires dual mapping to achieve a writable code zone
  	 then startAddress will be the non-zero address of the read/write zone and
  	 executableCodeZone will be the non-zero address of the read/execute zone.
  	 If the OS platform does not require dual mapping then startAddress will be
  	 the first address of the read/write/executable zone and executableCodeZone
  	 will be zero."
  	self initializeBackend.
  	codeToDataDelta := writableCodeZone = 0 ifTrue: [0] ifFalse: [writableCodeZone - startAddress].
  	backEnd stopsFrom: startAddress to: endAddress - 1.
  	self cCode:
  			[writableCodeZone = 0 ifTrue:
  				[self sqMakeMemoryExecutableFrom: startAddress To: endAddress]]
  		inSmalltalk:
  			[startAddress = self class guardPageSize ifTrue:
  				[backEnd stopsFrom: 0 to: endAddress - 1].
  			 self initializeProcessor].
  
  	codeBase := methodZoneBase := startAddress.
  	minValidCallAddress := (codeBase min: coInterpreter interpretAddress) min: coInterpreter primitiveFailAddress.
  	methodZone manageFrom: methodZoneBase to: endAddress.
  	self assertValidDualZone.
  	self maybeGenerateCheckFeatures.
  	self maybeGenerateCheckLZCNT.
  	self maybeGenerateICacheFlush.
  	self generateVMOwnerLockFunctions.
  	self genGetLeafCallStackPointer.
  	self generateStackPointerCapture.
  	self generateTrampolines.
  	self computeEntryOffsets.
  	self computeFullBlockEntryOffsets.
  	self generateClosedPICPrototype.
  	self alignMethodZoneBase.
  	"repeat so that now the methodZone ignores the generated run-time"
  	methodZone manageFrom: methodZoneBase to: endAddress.
  	"N.B. this is assumed to be the last thing done in initialization; see Cogit>>initialized"
  	self generateOpenPICPrototype!

Item was added:
+ ----- Method: Cogit>>sqMakeMemoryExecutableFrom:To:CodeToDataDelta: (in category 'initialization') -----
+ sqMakeMemoryExecutableFrom: startAddress To: endAddress CodeToDataDelta: codeToDataDeltaPtr
+ 	<doNotGenerate>
+ 	"Simulate setting executable permissions on the code zone.  In production this will apply execute permission
+ 	 to startAddress throguh endAddress - 1.  If starting up in the DUAL_MAPPED_CODE_ZONE regime then it
+ 	 will also create a writable mapping for the code zone and assign the distance from executable zone to the
+ 	 writable zone throguh codeToDataDeltaPtr.  If in this regime when simulating, the CogVMSimulator will
+ 	 have allocated twice as much code memory as asked for (see CogVMSimulator openOn:extraMemory:) and
+ 	 so simply set the delta to the code size."
+ 	(InitializationOptions at: #DUAL_MAPPED_COG_ZONE ifAbsent: [false]) ifTrue:
+ 		[codeToDataDeltaPtr at: 0 put: coInterpreter cogCodeSize]!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
+ initializeCodeZoneFrom: startAddress upTo: endAddress
+ 	scratchSimStack := self cCode: [self malloc: self simStackSlots * (self sizeof: CogSimStackEntry)]
+ 							inSmalltalk: [CArrayAccessor on: ((1 to: self simStackSlots) collect: [:ign| CogRegisterAllocatingSimStackEntry new])].
+ 	super initializeCodeZoneFrom: startAddress upTo: endAddress!

Item was removed:
- ----- Method: RegisterAllocatingCogit>>initializeCodeZoneFrom:upTo:writableCodeZone: (in category 'initialization') -----
- initializeCodeZoneFrom: startAddress upTo: endAddress writableCodeZone: writableCodeZone
- 	scratchSimStack := self cCode: [self malloc: self simStackSlots * (self sizeof: CogSimStackEntry)]
- 							inSmalltalk: [CArrayAccessor on: ((1 to: self simStackSlots) collect: [:ign| CogRegisterAllocatingSimStackEntry new])].
- 	super initializeCodeZoneFrom: startAddress upTo: endAddress writableCodeZone: writableCodeZone!

Item was added:
+ ----- Method: SistaCogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
+ initializeCodeZoneFrom: startAddress upTo: endAddress
+ 	initialCounterValue := MaxCounterValue.
+ 	super initializeCodeZoneFrom: startAddress upTo: endAddress!

Item was removed:
- ----- Method: SistaCogit>>initializeCodeZoneFrom:upTo:writableCodeZone: (in category 'initialization') -----
- initializeCodeZoneFrom: startAddress upTo: endAddress writableCodeZone: writableCodeZone
- 	initialCounterValue := MaxCounterValue.
- 	super initializeCodeZoneFrom: startAddress upTo: endAddress writableCodeZone: writableCodeZone!

Item was added:
+ ----- Method: SistaCogitClone>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
+ initializeCodeZoneFrom: startAddress upTo: endAddress
+ 	initialCounterValue := MaxCounterValue.
+ 	super initializeCodeZoneFrom: startAddress upTo: endAddress!

Item was removed:
- ----- Method: SistaCogitClone>>initializeCodeZoneFrom:upTo:writableCodeZone: (in category 'initialization') -----
- initializeCodeZoneFrom: startAddress upTo: endAddress writableCodeZone: writableCodeZone
- 	initialCounterValue := MaxCounterValue.
- 	super initializeCodeZoneFrom: startAddress upTo: endAddress writableCodeZone: writableCodeZone!



More information about the Vm-dev mailing list