Eliot Miranda uploaded a new version of VMMaker to project VM Maker: http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2702.mcz ==================== Summary ==================== Name: VMMaker.oscog-eem.2702 Author: eem Time: 3 February 2020, 9:41:20.130225 pm UUID: f1c11cd1-b535-459f-b450-8976cc6f1636 Ancestors: VMMaker.oscog-eem.2701 Cogit: Add support for cache flushing in the dual mapped regime, hence rename maybeGenerateICacheFlush to maybeGenerateCacheFlush. Slang: ease conditional declaration by moving withCRs into variableDeclarationStringsForVariable:. Make cppIf:ifTrue:[ifFalse:] examine InitializationOptions. cFramePointerInUse can't be byte cuz it's global (sigh). Fix some typos. Nuke obsolete code. =============== Diff against VMMaker.oscog-eem.2701 =============== Item was changed: ----- Method: CCodeGenerator>>variableDeclarationStringsForVariable: (in category 'C translation support') ----- variableDeclarationStringsForVariable: variableNameString "We (have to?) abuse declarations for optionality using #if C preprocessor forms. This is ugly, but difficult to avoid. This routine answers either a single string declaration for a variable declared without one of these hacks, or returns the declaration split up into lines." | declString | declString := variableDeclarations at: variableNameString ifAbsent: [^{'sqInt ', variableNameString}]. ^(declString includes: $#) + ifTrue: [declString withCRs findTokens: Character cr] - ifTrue: [declString findTokens: Character cr] ifFalse: [{declString}]! Item was added: + ----- Method: CogAbstractInstruction>>flushDCacheFrom:to: (in category 'inline cacheing') ----- + flushDCacheFrom: startAddress "<Integer>" to: endAddress "<Integer>" + "If there is a dual mapped code zone (the normal zone but marked with read/execute, and a + read/write zone codeToDataDelta bytes away) then flush the data cache for the corresponding + range in the read/write zone and invalidate the data cache for the read/execute zone." + self subclassResponsibility! Item was added: + ----- Method: CogAbstractInstruction>>flushICacheFrom:to: (in category 'inline cacheing') ----- + flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>" + "Flush the instruction cache from (startAddress to endAddress]. + If there is a dual mapped code zone (the normal zone but marked with read/execute, and a + read/write zone codeToDataDelta bytes away) then also flush the data cache for the corresp- + onding range in the read/write zone and invalidate the data cache for the read/execute zone." + self subclassResponsibility! Item was added: + ----- Method: CogAbstractInstruction>>numDCacheFlushOpcodes (in category 'inline cacheing') ----- + numDCacheFlushOpcodes + "If the processor has the ablity to generate code to flush the dcache for the dual mapped + regime then answer the number of opcodes required to compile an accessor for the feature." + ^0! Item was changed: ----- Method: CogIA32Compiler>>flushICacheFrom:to: (in category 'inline cacheing') ----- flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>" + "Flush the instruction cache from (startAddress to endAddress]. + If there is a dual mapped code zone (the normal zone but marked with read/execute, and a + read/write zone codeToDataDelta bytes away) then also flush the data cache for the corresp- + onding range in the read/write zone and invalidate the data cache for the read/execute zone." <cmacro: '(me,startAddress,endAddress) 0'> "On Intel processors where code and data have the same linear address, no special action is required to flush the instruction cache. One only needs to execute a serializing instruction (e.g. CPUID) if code and data are at different virtual addresses (e.g. a debugger using memory-mapping to access a debugee). Using the macro avoids an unnecessary call."! Item was changed: ----- Method: CogICacheFlushingIA32Compiler>>flushICacheFrom:to: (in category 'inline cacheing') ----- flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>" + "Flush the instruction cache from (startAddress to endAddress]. + If there is a dual mapped code zone (the normal zone but marked with read/execute, and a + read/write zone codeToDataDelta bytes away) then also flush the data cache for the corresp- + onding range in the read/write zone and invalidate the data cache for the read/execute zone." <cmacro: '(me,startAddress,endAddress) ceFlushICache(startAddress,endAddress)'> ^cogit simulateCeFlushICacheFrom: startAddress to: endAddress! Item was changed: ----- Method: CogMIPSELCompiler>>flushICacheFrom:to: (in category 'inline cacheing') ----- flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>" + "Flush the instruction cache from (startAddress to endAddress]. + If there is a dual mapped code zone (the normal zone but marked with read/execute, and a + read/write zone codeToDataDelta bytes away) then also flush the data cache for the corresp- + onding range in the read/write zone and invalidate the data cache for the read/execute zone." <cmacro: '(me,startAddress,endAddress) cacheflush((char*) startAddress, endAddress - startAddress, ICACHE)'> "See http://www.linux-mips.org/wiki/Cacheflush_Syscall"! Item was changed: ----- Method: CogMethodZone>>compactCompiledCode (in category 'compaction') ----- compactCompiledCode | objectHeaderValue source dest writableVersion bytes | <var: #source type: #'CogMethod *'> <var: #dest type: #'CogMethod *'> compactionInProgress := true. methodCount := 0. objectHeaderValue := objectMemory nullHeaderForMachineCodeMethod. source := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'. self voidOpenPICList. "The(se) list(s) will be rebuilt with the current live set" self voidUnpairedMethodList. [source < self limitZony and: [source cmType ~= CMFree]] whileTrue: [self assert: (cogit cogMethodDoesntLookKosher: source) = 0. writableVersion := cogit writableMethodFor: source. writableVersion objectHeader: objectHeaderValue. source cmUsageCount > 0 ifTrue: [writableVersion cmUsageCount: source cmUsageCount // 2]. self maybeLinkOnUnpairedMethodList: source. self clearSavedPICUsageCount: writableVersion. source cmType = CMOpenPIC ifTrue: [self addToOpenPICList: writableVersion]. methodCount := methodCount + 1. source := self methodAfter: source]. source >= self limitZony ifTrue: [^self halt: 'no free methods; cannot compact.']. dest := source. [source < self limitZony] whileTrue: [self assert: (cogit maybeFreeCogMethodDoesntLookKosher: source) = 0. bytes := source blockSize. source cmType ~= CMFree ifTrue: [methodCount := methodCount + 1. + cogit + codeMemmove: dest _: source _: bytes; + maybeFlushWritableZoneFrom: dest asUnsignedInteger to: dest asUnsignedInteger + bytes. - cogit codeMemmove: dest _: source _: bytes. (writableVersion := cogit writableMethodFor: dest) objectHeader: objectHeaderValue. dest cmType = CMMethod ifTrue: ["For non-Newspeak there should be a one-to-one mapping between bytecoded and cog methods. For Newspeak not necessarily, but only for anonymous accessors." "Only update the original method's header if it is referring to this CogMethod." (coInterpreter rawHeaderOf: dest methodObject) asInteger = source asInteger ifTrue: [coInterpreter rawHeaderOf: dest methodObject put: dest asInteger] ifFalse: [self assert: (cogit noAssertMethodClassAssociationOf: dest methodObject) = objectMemory nilObject. self linkOnUnpairedMethodList: dest]] ifFalse: [self clearSavedPICUsageCount: writableVersion. dest cmType = CMOpenPIC ifTrue: [self addToOpenPICList: writableVersion]]. dest cmUsageCount > 0 ifTrue: [writableVersion cmUsageCount: dest cmUsageCount // 2]. + cogit maybeFlushWritableZoneFrom: dest asUnsignedInteger to: (dest + 1) asUnsignedInteger. dest := coInterpreter cCoerceSimple: dest asUnsignedInteger + bytes to: #'CogMethod *']. source := coInterpreter cCoerceSimple: source asUnsignedInteger + bytes to: #'CogMethod *']. mzFreeStart := dest asUnsignedInteger. methodBytesFreedSinceLastCompaction := 0. compactionInProgress := false! Item was changed: ----- Method: CogObjectRepresentationForSpur class>>declareCVarsIn: (in category 'translation') ----- declareCVarsIn: aCodeGen "Deal wuth the fact that the number of trampolines depends on IMMUTABILITY and that IMMUTABILITY can be defined at compile time. Yes, this is a mess." | current values | current := InitializationOptions at: #IMMUTABILITY ifAbsent: nil. values := #(true false) collect: [:bool| InitializationOptions at: #IMMUTABILITY put: bool. self cogitClass initializeNumTrampolines. (Cogit classPool at: #NumTrampolines) printString]. current ifNil: [InitializationOptions removeKey: #IMMUTABILITY] ifNotNil: [InitializationOptions at: #IMMUTABILITY put: current]. values first ~= values last ifTrue: [aCodeGen addConstantForBinding: #NumTrampolines -> ('(IMMUTABILITY ? ' , values first , ' : ' , values last , ')')]. aCodeGen var: #ceStoreTrampolines + declareC: '#if IMMUTABILITY\sqInt ceStoreTrampolines[', NumStoreTrampolines printString, '];\#endif'! - declareC: ('#if IMMUTABILITY\sqInt ceStoreTrampolines[', NumStoreTrampolines printString, '];\#endif') withCRs! Item was removed: - ----- Method: CogVMSimulator>>ioAllocateDualMappedCodeZone:OfSize:WritableZone: (in category 'initialization') ----- - ioAllocateDualMappedCodeZone: executableZonePluggableAccessor OfSize: codeSize WritableZone: writableZonePluggableAccessor - "Simulation of ioAllocateDualMappedCodeZoneOfSize:MethodZone:. - If the DUAL_MAPPED_CODE_ZONE preference is set obey it and simulate a dual mapped zone, - causing the system to use the first codeSize * 2 bytes of memory to simulate a dual mapped zone. - Otherwise answer zero, causing the system to work as it used to, using the first codeSize bytes of - memory for the code zone." - (InitializationOptions at: #'DUAL_MAPPED_CODE_ZONE' ifAbsent: [false]) - ifTrue: - [executableZonePluggableAccessor at: 0 put: Cogit guardPageSize. - writableZonePluggableAccessor at: 0 put: codeSize] - ifFalse: - [executableZonePluggableAccessor at: 0 put: 0. - writableZonePluggableAccessor at: 0 put: 0]! 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 | "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_CODE_ZONE ifAbsent: [false]) - effectiveCogCodeSize := (InitializationOptions at: #DUAL_MAPPED_COG_ZONE ifAbsent: [false]) 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! Item was changed: ----- Method: CogX64Compiler>>flushICacheFrom:to: (in category 'inline cacheing') ----- flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>" + "Flush the instruction cache from (startAddress to endAddress]. + If there is a dual mapped code zone (the normal zone but marked with read/execute, and a + read/write zone codeToDataDelta bytes away) then also flush the data cache for the corresp- + onding range in the read/write zone and invalidate the data cache for the read/execute zone." <cmacro: '(me,startAddress,endAddress) 0'> "On Intel processors where code and data have the same linear address, no special action is required to flush the instruciton cache. One only needs to execute a serializing instruction (e.g. CPUID) if code and data are at different virtual addresses (e.g. a debugger using memory-mapping to access a debugee). Using the macro avoids an unnecessary call."! Item was changed: CogClass subclass: #Cogit (excessive size, no diff calculated) Item was changed: ----- Method: Cogit class>>declareCVarsIn: (in category 'translation') ----- declareCVarsIn: aCCodeGenerator | backEnd | backEnd := CogCompilerClass basicNew. #( 'coInterpreter' 'objectMemory' 'methodZone' 'objectRepresentation' 'cogBlockMethodSurrogateClass' 'cogMethodSurrogateClass' 'nsSendCacheSurrogateClass' 'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses' 'simulatedTrampolines' 'simulatedVariableGetters' 'simulatedVariableSetters' 'processorFrameValid' 'printRegisters' 'printInstructions' 'clickConfirm' 'singleStep') do: [:simulationVariableNotNeededForRealVM| aCCodeGenerator removeVariable: simulationVariableNotNeededForRealVM]. NewspeakVM ifFalse: [#( 'selfSendTrampolines' 'dynamicSuperSendTrampolines' 'implicitReceiverSendTrampolines' 'outerSendTrampolines' 'ceEnclosingObjectTrampoline' 'numIRCs' 'indexOfIRC' 'theIRCs') do: [:variableNotNeededInNormalVM| aCCodeGenerator removeVariable: variableNotNeededInNormalVM]]. aCCodeGenerator removeConstant: #COGMTVM. "this should be defined at compile time" aCCodeGenerator addHeaderFile:'<stddef.h>'; "for e.g. offsetof" addHeaderFile:'"sqCogStackAlignment.h"'; addHeaderFile:'"dispdbg.h"'; "must precede cointerp.h & cogit.h otherwise NoDbgRegParms gets screwed up" addHeaderFile:'"cogmethod.h"'. NewspeakVM ifTrue: [aCCodeGenerator addHeaderFile:'"nssendcache.h"']. aCCodeGenerator addHeaderFile:'#if COGMTVM'; addHeaderFile:'"cointerpmt.h"'; addHeaderFile:'#else'; addHeaderFile:'"cointerp.h"'; addHeaderFile:'#endif'; addHeaderFile:'"cogit.h"'. aCCodeGenerator var: #ceGetFP declareC: 'usqIntptr_t (*ceGetFP)(void)'; var: #ceGetSP declareC: 'usqIntptr_t (*ceGetSP)(void)'; var: #ceCaptureCStackPointers declareC: 'void (*ceCaptureCStackPointers)(void)'; var: #ceEnterCogCodePopReceiverReg declareC: 'void (*ceEnterCogCodePopReceiverReg)(void)'; var: #realCEEnterCogCodePopReceiverReg declareC: 'void (*realCEEnterCogCodePopReceiverReg)(void)'; var: #ceCallCogCodePopReceiverReg declareC: 'void (*ceCallCogCodePopReceiverReg)(void)'; var: #realCECallCogCodePopReceiverReg declareC: 'void (*realCECallCogCodePopReceiverReg)(void)'; var: #ceCallCogCodePopReceiverAndClassRegs declareC: 'void (*ceCallCogCodePopReceiverAndClassRegs)(void)'; var: #realCECallCogCodePopReceiverAndClassRegs declareC: 'void (*realCECallCogCodePopReceiverAndClassRegs)(void)'; var: #postCompileHook declareC: 'void (*postCompileHook)(CogMethod *)'; var: #openPICList declareC: 'CogMethod *openPICList = 0'; var: #maxMethodBefore type: #'CogBlockMethod *'; var: 'enumeratingCogMethod' type: #'CogMethod *'. aCCodeGenerator var: #ceTryLockVMOwner + declareC: '#if COGMTVM\usqIntptr_t (*ceTryLockVMOwner)(void)'; - declareC: '#if COGMTVM\usqIntptr_t (*ceTryLockVMOwner)(void)' withCRs; var: #ceUnlockVMOwner + declareC: 'void (*ceUnlockVMOwner)(void)\#endif /* COGMTVM */'. - declareC: 'void (*ceUnlockVMOwner)(void)\#endif /* COGMTVM */' withCRs. backEnd numCheckLZCNTOpcodes > 0 ifTrue: [aCCodeGenerator var: #ceCheckLZCNTFunction declareC: 'static usqIntptr_t (*ceCheckLZCNTFunction)(void)']. backEnd numCheckFeaturesOpcodes > 0 ifTrue: [aCCodeGenerator var: #ceCheckFeaturesFunction declareC: 'static usqIntptr_t (*ceCheckFeaturesFunction)(void)']. backEnd numICacheFlushOpcodes > 0 ifTrue: [aCCodeGenerator var: #ceFlushICache declareC: 'static void (*ceFlushICache)(usqIntptr_t from, usqIntptr_t to)']. + aCCodeGenerator + var: #ceFlushDCache + declareC: '#if DUAL_MAPPED_CODE_ZONE\static void (*ceFlushDCache)(usqIntptr_t from, usqIntptr_t to)\#endif'. aCCodeGenerator declareVar: 'aMethodLabel' type: #'AbstractInstruction'; "Has to come lexicographically before backEnd & methodLabel" var: #backEnd declareC: 'AbstractInstruction * const backEnd = &aMethodLabel'; var: #methodLabel declareC: 'AbstractInstruction * const methodLabel = &aMethodLabel'. self declareC: #(abstractOpcodes stackCheckLabel blockEntryLabel blockEntryNoContextSwitch stackOverflowCall sendMiss entry noCheckEntry selfSendEntry dynSuperEntry fullBlockNoContextSwitchEntry fullBlockEntry picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 cPICEndOfCodeLabel) as: #'AbstractInstruction *' in: aCCodeGenerator. aCCodeGenerator declareVar: #cPICPrototype type: #'CogMethod *'; declareVar: #blockStarts type: #'BlockStart *'; declareVar: #fixups type: #'BytecodeFixup *'; declareVar: #methodZoneBase type: #usqInt. aCCodeGenerator var: #ordinarySendTrampolines declareC: 'sqInt ordinarySendTrampolines[NumSendTrampolines]'; var: #superSendTrampolines declareC: 'sqInt superSendTrampolines[NumSendTrampolines]'. BytecodeSetHasDirectedSuperSend ifTrue: [aCCodeGenerator var: #directedSuperSendTrampolines declareC: 'sqInt directedSuperSendTrampolines[NumSendTrampolines]'; var: #directedSuperBindingSendTrampolines declareC: 'sqInt directedSuperBindingSendTrampolines[NumSendTrampolines]']. NewspeakVM ifTrue: [aCCodeGenerator var: #selfSendTrampolines declareC: 'sqInt selfSendTrampolines[NumSendTrampolines]'; var: #dynamicSuperSendTrampolines declareC: 'sqInt dynamicSuperSendTrampolines[NumSendTrampolines]'; var: #implicitReceiverSendTrampolines declareC: 'sqInt implicitReceiverSendTrampolines[NumSendTrampolines]'; var: #outerSendTrampolines declareC: 'sqInt outerSendTrampolines[NumSendTrampolines]']. aCCodeGenerator var: #trampolineAddresses declareC: 'static char *trampolineAddresses[NumTrampolines*2]'; var: #objectReferencesInRuntime declareC: 'static usqInt objectReferencesInRuntime[NumObjRefsInRuntime+1]'; var: #labelCounter type: #int; var: #traceFlags declareC: 'int traceFlags = 8 /* prim trace log on by default */'; var: #cStackAlignment declareC: 'const int cStackAlignment = STACK_ALIGN_BYTES'. aCCodeGenerator declareVar: #minValidCallAddress type: #'usqIntptr_t'; declareVar: #debugPrimCallStackOffset type: #'usqIntptr_t'. aCCodeGenerator vmClass generatorTable ifNotNil: [:bytecodeGenTable| aCCodeGenerator var: #generatorTable declareC: 'static BytecodeDescriptor generatorTable[', bytecodeGenTable size printString, ']', (self tableInitializerFor: bytecodeGenTable in: aCCodeGenerator)]. "In C the abstract opcode names clash with the Smalltalk generator syntactic sugar. Most of the syntactic sugar is inlined, but alas some remains. Rename the syntactic sugar to avoid the clash." (self organization listAtCategoryNamed: #'abstract instructions') do: [:s| aCCodeGenerator addSelectorTranslation: s to: 'g', (aCCodeGenerator cFunctionNameFor: s)]. aCCodeGenerator addSelectorTranslation: #halt: to: 'haltmsg'. self declareFlagVarsAsByteIn: aCCodeGenerator! Item was changed: ----- Method: Cogit class>>declareFlagVarsAsByteIn: (in category 'translation') ----- declareFlagVarsAsByteIn: aCCodeGenerator CogCompilerClass basicNew byteReadsZeroExtend ifTrue: + [self declareC: #(codeModified deadCode directedSendUsesBinding + hasMovableLiteral hasNativeFrame hasYoungReferent + inBlock needsFrame regArgsHaveBeenPushed useTwoPaths) - [self declareC: #(cFramePointerInUse codeModified deadCode directedSendUsesBinding - hasMovableLiteral hasNativeFrame hasYoungReferent inBlock needsFrame - regArgsHaveBeenPushed traceStores useTwoPaths) as: #'unsigned char' ifPresentIn: aCCodeGenerator]! Item was changed: ----- Method: Cogit class>>mustBeGlobal: (in category 'translation') ----- mustBeGlobal: var + "Answer if a variable must be global and exported. Used for inst vars that are + accessed from VM support code." + ^#('ceBaseFrameReturnTrampoline' 'ceCaptureCStackPointers' 'ceCheckForInterruptTrampoline' - "Answer if a variable must be global and exported. Used for inst vars that are accessed from VM - support code. include cePositive32BitIntegerTrampoline as a hack to prevent it being inlined (it is - only used outside of Cogit by the object representation). Include CFramePointer CStackPointer as - a hack to get them declared at all." - ^#( 'ceBaseFrameReturnTrampoline' #ceCaptureCStackPointers 'ceCheckForInterruptTrampoline' ceEnterCogCodePopReceiverReg realCEEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg realCECallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs realCECallCogCodePopReceiverAndClassRegs 'ceReturnToInterpreterTrampoline' 'ceCannotResumeTrampoline' ceTryLockVMOwner ceUnlockVMOwner 'cmEntryOffset' 'cmNoCheckEntryOffset' 'cmDynSuperEntryOffset' 'cmSelfSendEntryOffset' 'missOffset' 'cbEntryOffset' 'cbNoSwitchEntryOffset' 'blockNoContextSwitchOffset' breakPC + ceGetFP ceGetSP cFramePointerInUse + traceFlags traceStores debugPrimCallStackOffset) - CFramePointer CStackPointer 'cFramePointerInUse' ceGetFP ceGetSP - traceFlags 'traceStores' debugPrimCallStackOffset) includes: var! Item was changed: ----- Method: Cogit>>ceSICMiss: (in category 'in-line cacheing') ----- ceSICMiss: receiver "An in-line cache check in a method has failed. The failing entry check has jumped to the ceMethodAbort abort call at the start of the method which has called this routine. If possible allocate a closed PIC for the current and existing classes. The stack looks like: receiver args sender return address sp=> ceMethodAbort call return address So we can find the method that did the failing entry check at ceMethodAbort call return address - missOffset and we can find the send site from the outer return address." <api> | pic innerReturn outerReturn entryPoint targetMethod newTargetMethodOrNil errorSelectorOrNil cacheTag extent result | <var: #pic type: #'CogMethod *'> <var: #targetMethod type: #'CogMethod *'> "Whether we can relink to a PIC or not we need to pop off the inner return and identify the target method." innerReturn := coInterpreter popStack asUnsignedInteger. targetMethod := self cCoerceSimple: innerReturn - missOffset to: #'CogMethod *'. (objectMemory isOopForwarded: receiver) ifTrue: [^coInterpreter ceSendFromInLineCacheMiss: targetMethod]. outerReturn := coInterpreter stackTop asUnsignedInteger. self assert: (outerReturn between: methodZoneBase and: methodZone freeStart). entryPoint := backEnd callTargetFromReturnAddress: outerReturn. self assert: targetMethod selector ~= objectMemory nilObject. self assert: targetMethod asInteger + cmEntryOffset = entryPoint. self lookup: targetMethod selector for: receiver methodAndErrorSelectorInto: [:method :errsel| newTargetMethodOrNil := method. errorSelectorOrNil := errsel]. "We assume lookupAndCog:for: will *not* reclaim the method zone" self assert: outerReturn = coInterpreter stackTop. cacheTag := objectRepresentation inlineCacheTagForInstance: receiver. ((errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand]) or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag) or: [(backEnd inlineCacheTagAt: outerReturn) = self picAbortDiscriminatorValue or: [newTargetMethodOrNil isNil or: [objectMemory isYoung: newTargetMethodOrNil]]]]) ifTrue: [result := self patchToOpenPICFor: targetMethod selector numArgs: targetMethod cmNumArgs receiver: receiver. self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory" ^coInterpreter ceSendFromInLineCacheMiss: targetMethod]. "See if an Open PIC is already available." pic := methodZone openPICWithSelector: targetMethod selector. (pic isNil or: [self allowEarlyOpenPICPromotion not]) ifTrue: ["otherwise attempt to create a closed PIC for the two cases." pic := self cogPICSelector: targetMethod selector numArgs: targetMethod cmNumArgs Case0Method: targetMethod Case1Method: newTargetMethodOrNil tag: cacheTag isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand. (pic asInteger between: MaxNegativeErrorCode and: -1) ifTrue: ["For some reason the PIC couldn't be generated, most likely a lack of code memory. Continue as if this is an unlinked send." pic asInteger = InsufficientCodeSpace ifTrue: [coInterpreter callForCogCompiledCodeCompaction]. ^coInterpreter ceSendFromInLineCacheMiss: targetMethod]. + "This also implicitly flushes the read/write mapped dual zone to the read/execute zone." backEnd flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize]. "Relink the send site to the pic. If to an open PIC then reset the cache tag to the selector, for the benefit of the cacheTag assert check in checkIfValidOopRef:pc:cogMethod: et al." extent := pic cmType = CMOpenPIC ifTrue: [backEnd rewriteInlineCacheAt: outerReturn tag: (backEnd inlineCacheValueForSelector: targetMethod selector in: coInterpreter mframeHomeMethodExport) target: pic asInteger + cmEntryOffset] ifFalse: [backEnd rewriteCallAt: outerReturn target: pic asInteger + cmEntryOffset]. + "This also implicitly flushes the read/write mapped dual zone to the read/execute zone." backEnd flushICacheFrom: outerReturn asUnsignedInteger - extent to: outerReturn asUnsignedInteger. "Jump back into the pic at its entry in case this is an MNU (newTargetMethodOrNil is nil)" coInterpreter executeCogPIC: pic fromLinkedSendWithReceiver: receiver andCacheTag: (backEnd inlineCacheTagAt: outerReturn). "NOTREACHED" ^nil! Item was changed: ----- Method: Cogit>>codeToDataDelta (in category 'generate machine code - dual mapped zone support') ----- codeToDataDelta "If non-zero this is the delta between the read/execute method zone and the read/write mapping of the method zone. On operating systems where it is entirely disallowed to execute code in a writable region this split is necessary to be able to modify code. In this regime all writes must be made to the read/write mapped zone." + <cmacro: '() codeToDataDelta'> ^codeToDataDelta! Item was changed: ----- Method: Cogit>>cogExtendPIC:CaseNMethod:tag:isMNUCase: (in category 'in-line cacheing') ----- cogExtendPIC: cPIC CaseNMethod: caseNMethod tag: caseNTag isMNUCase: isMNUCase "Extend the cPIC with the supplied case. If caseNMethod is cogged dispatch direct to its unchecked entry-point. If caseNMethod is not cogged, jump to the fast interpreter dispatch, and if isMNUCase then dispatch to fast MNU invocation and mark the cPIC as having the MNU case for cache flushing." <var: #cPIC type: #'CogMethod *'> | operand target address | coInterpreter compilationBreak: cPIC selector point: (objectMemory numBytesOf: cPIC selector) isMNUCase: isMNUCase. self assert: (objectRepresentation inlineCacheTagIsYoung: caseNTag) not. "Caller patches to open pic if caseNMethod is young." self assert: (caseNMethod notNil and: [(objectMemory isYoung: caseNMethod) not]). (isMNUCase not and: [coInterpreter methodHasCogMethod: caseNMethod]) ifTrue: "this isn't an MNU and we have an already cogged method to jump to" [operand := 0. target := (coInterpreter cogMethodOf: caseNMethod) asInteger + cmNoCheckEntryOffset] ifFalse: [operand := caseNMethod. isMNUCase ifTrue: "this is an MNU so tag the CPIC header and setup a jump to the MNUAbort" [cPIC cpicHasMNUCase: true. target := cPIC asInteger + (self sizeof: CogMethod)] ifFalse: "setup a jump to the interpretAborth so we can cog the target method" [target := cPIC asInteger + self picInterpretAbortOffset]]. "find the end address of the new case" address := self addressOfEndOfCase: cPIC cPICNumCases +1 inCPIC: cPIC. self rewriteCPICCaseAt: address tag: caseNTag objRef: operand target: target. "finally, rewrite the jump 3 instr before firstCPICCaseOffset to jump to the beginning of this new case" self rewriteCPIC: cPIC caseJumpTo: address - cPICCaseSize. + "This also implicitly flushes the read/write mapped dual zone to the read/execute zone." backEnd flushICacheFrom: cPIC asUnsignedInteger to: cPIC asUnsignedInteger + closedPICSize. "update the header flag for the number of cases" (self writableMethodFor: cPIC) cPICNumCases: cPIC cPICNumCases + 1. self assertValidDualZoneFrom: cPIC asUnsignedInteger to: cPIC asUnsignedInteger + closedPICSize! Item was changed: ----- Method: Cogit>>cogMNUPICSelector:receiver:methodOperand:numArgs: (in category 'in-line cacheing') ----- cogMNUPICSelector: selector receiver: rcvr methodOperand: methodOperand numArgs: numArgs <api> "Attempt to create a one-case PIC for an MNU. The tag for the case is at the send site and so doesn't need to be generated." <returnTypeC: #'CogMethod *'> | startAddress writablePIC actualPIC | ((objectMemory isYoung: selector) or: [(objectRepresentation inlineCacheTagForInstance: rcvr) = self picAbortDiscriminatorValue]) ifTrue: [^0]. coInterpreter compilationBreak: selector point: (objectMemory numBytesOf: selector) isMNUCase: true. self assert: endCPICCase0 notNil. "get memory in the code zone for the CPIC; if that fails we return an error code for the sender to use to work out how to blow up" startAddress := methodZone allocate: closedPICSize. startAddress = 0 ifTrue: [coInterpreter callForCogCompiledCodeCompaction. ^0]. self maybeBreakGeneratingFrom: startAddress to: startAddress + closedPICSize - 1. writablePIC := self writableMethodFor: startAddress. "memcpy the prototype across to our allocated space; because anything else would be silly" self codeMemcpy: writablePIC _: cPICPrototype _: closedPICSize. self fillInCPICHeader: writablePIC numArgs: numArgs numCases: 1 hasMNUCase: true selector: selector. self configureMNUCPIC: (actualPIC := self cCoerceSimple: startAddress to: #'CogMethod *') methodOperand: methodOperand numArgs: numArgs delta: startAddress - cPICPrototype asUnsignedInteger. + "This also implicitly flushes the read/write mapped dual zone to the read/execute zone." + backEnd flushICacheFrom: startAddress to: startAddress + closedPICSize. + self assert: (backEnd callTargetFromReturnAddress: startAddress + missOffset) = (self picAbortTrampolineFor: numArgs). self assertValidDualZoneFrom: startAddress to: startAddress + closedPICSize. - backEnd flushICacheFrom: startAddress to: startAddress + closedPICSize. ^actualPIC! Item was changed: ----- Method: Cogit>>cogPICSelector:numArgs:Case0Method:Case1Method:tag:isMNUCase: (in category 'in-line cacheing') ----- cogPICSelector: selector numArgs: numArgs Case0Method: case0CogMethod Case1Method: case1MethodOrNil tag: case1Tag isMNUCase: isMNUCase "Attempt to create a two-case PIC for case0CogMethod and case1Method,case1Tag. The tag for case0CogMethod is at the send site and so doesn't need to be generated. case1Method may be any of - a Cog method; link to its unchecked entry-point - a CompiledMethod; link to ceInterpretMethodFromPIC: - a CompiledMethod; link to ceMNUFromPICMNUMethod:receiver:" <var: #case0CogMethod type: #'CogMethod *'> <returnTypeC: #'CogMethod *'> | startAddress writablePIC actualPIC | (objectMemory isYoung: selector) ifTrue: [^self cCoerceSimple: YoungSelectorInPIC to: #'CogMethod *']. coInterpreter compilationBreak: selector point: (objectMemory numBytesOf: selector) isMNUCase: isMNUCase. "get memory in the code zone for the CPIC; if that fails we return an error code for the sender to use to work out how to blow up" startAddress := methodZone allocate: closedPICSize. startAddress = 0 ifTrue: [^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *']. self maybeBreakGeneratingFrom: startAddress to: startAddress + closedPICSize - 1. writablePIC := self writableMethodFor: startAddress. "memcpy the prototype across to our allocated space; because anything else would be silly" self codeMemcpy: writablePIC _: cPICPrototype _: closedPICSize. self fillInCPICHeader: writablePIC numArgs: numArgs numCases: 2 hasMNUCase: isMNUCase selector: selector. self configureCPIC: (actualPIC := self cCoerceSimple: startAddress to: #'CogMethod *') Case0: case0CogMethod Case1Method: case1MethodOrNil tag: case1Tag isMNUCase: isMNUCase numArgs: numArgs delta: startAddress - cPICPrototype asUnsignedInteger. + "This also implicitly flushes the read/write mapped dual zone to the read/execute zone." + backEnd flushICacheFrom: startAddress to: startAddress + closedPICSize. + self assert: (backEnd callTargetFromReturnAddress: startAddress + missOffset) = (self picAbortTrampolineFor: numArgs). self assertValidDualZoneFrom: startAddress to: startAddress + closedPICSize. - backEnd flushICacheFrom: startAddress to: startAddress + closedPICSize. ^actualPIC! Item was changed: ----- Method: Cogit>>fillInMethodHeader:size:selector: (in category 'generate machine code') ----- fillInMethodHeader: method size: size selector: selector "Fill in the header for theCogMehtod method. This may be located at the writable mapping." <var: #method type: #'CogMethod *'> | originalMethod rawHeader actualMethodLocation | <var: #originalMethod type: #'CogMethod *'> actualMethodLocation := method asUnsignedInteger - codeToDataDelta. method cmType: CMMethod. method objectHeader: objectMemory nullHeaderForMachineCodeMethod. method blockSize: size. method methodObject: methodObj. rawHeader := coInterpreter rawHeaderOf: methodObj. "If the method has already been cogged (e.g. Newspeak accessors) then leave the original method attached to its cog method, but get the right header." (coInterpreter isCogMethodReference: rawHeader) ifTrue: [originalMethod := self cCoerceSimple: rawHeader to: #'CogMethod *'. self assert: originalMethod blockSize = size. self assert: methodHeader = originalMethod methodHeader. NewspeakVM ifTrue: [methodZone addToUnpairedMethodList: method]] ifFalse: [coInterpreter rawHeaderOf: methodObj put: actualMethodLocation. NewspeakVM ifTrue: [method nextMethodOrIRCs: theIRCs]]. method methodHeader: methodHeader. method selector: selector. method cmNumArgs: (coInterpreter argumentCountOfMethodHeader: methodHeader). method cmHasMovableLiteral: hasMovableLiteral. (method cmRefersToYoung: hasYoungReferent) ifTrue: [methodZone addToYoungReferrers: method]. method cmUsageCount: self initialMethodUsageCount. method cpicHasMNUCase: false. method cmUsesPenultimateLit: maxLitIndex >= ((objectMemory literalCountOfMethodHeader: methodHeader) - 2). method blockEntryOffset: (blockEntryLabel notNil ifTrue: [blockEntryLabel address - actualMethodLocation] ifFalse: [0]). "This can be an error check since a large stackCheckOffset is caused by compiling a machine-code primitive, and hence depends on the Cogit, not the input method." needsFrame ifTrue: [stackCheckLabel address - actualMethodLocation <= MaxStackCheckOffset ifFalse: [self error: 'too much code for stack check offset']]. method stackCheckOffset: (needsFrame ifTrue: [stackCheckLabel address - actualMethodLocation] ifFalse: [0]). + + "This also implicitly flushes the read/write mapped dual zone to the read/execute zone." + backEnd flushICacheFrom: actualMethodLocation to: actualMethodLocation + size. + self assert: (backEnd callTargetFromReturnAddress: actualMethodLocation + missOffset) = (self methodAbortTrampolineFor: method cmNumArgs). self assert: size = (methodZone roundUpLength: size). - backEnd flushICacheFrom: actualMethodLocation to: actualMethodLocation + size. self assertValidDualZoneFrom: actualMethodLocation to: actualMethodLocation + size. self maybeEnableSingleStep! Item was changed: ----- Method: Cogit>>fillInOPICHeader:numArgs:selector: (in category 'generate machine code') ----- fillInOPICHeader: pic numArgs: numArgs selector: selector "Fill in the header for the OpenPIC pic. This may be located at the writable mapping." <var: #pic type: #'CogMethod *'> <inline: true> pic cmType: CMOpenPIC. pic objectHeader: 0. pic blockSize: openPICSize. "pic methodObject: 0.""This is also the nextOpenPIC link so don't initialize it" methodZone addToOpenPICList: pic. pic methodHeader: 0. pic selector: selector. pic cmNumArgs: numArgs. pic cmHasMovableLiteral: (objectMemory isNonImmediate: selector). (pic cmRefersToYoung: (objectMemory isYoung: selector)) ifTrue: [methodZone addToYoungReferrers: pic]. pic cmUsageCount: self initialOpenPICUsageCount. pic cpicHasMNUCase: false. pic cPICNumCases: 0. pic blockEntryOffset: 0. + + "This also implicitly flushes the read/write mapped dual zone to the read/execute zone." + backEnd flushICacheFrom: pic asUnsignedInteger - codeToDataDelta to: pic asUnsignedInteger - codeToDataDelta + openPICSize. + self assert: pic cmType = CMOpenPIC. self assert: pic selector = selector. self assert: pic cmNumArgs = numArgs. self assert: (backEnd callTargetFromReturnAddress: pic asInteger - codeToDataDelta + missOffset) = (self picAbortTrampolineFor: numArgs). self assert: openPICSize = (methodZone roundUpLength: openPICSize). - backEnd flushICacheFrom: pic asUnsignedInteger - codeToDataDelta to: pic asUnsignedInteger - codeToDataDelta + openPICSize. self assertValidDualZoneFrom: pic asUnsignedInteger - codeToDataDelta to: pic asUnsignedInteger - codeToDataDelta + openPICSize. self maybeEnableSingleStep! Item was changed: ----- Method: Cogit>>generateCaptureCStackPointers: (in category 'initialization') ----- generateCaptureCStackPointers: captureFramePointer "Generate the routine that writes the current values of the C frame and stack pointers into variables. These are used to establish the C stack in trampolines back into the C run-time. This routine assumes the system's frame pointer is the same as that used in generated code." | startAddress callerSavedReg pushedVarBaseReg | <inline: #never> self allocateOpcodes: 32 bytecodes: 0. startAddress := methodZoneBase. "Must happen first; value may be used in accessing any of the following addresses" callerSavedReg := 0. pushedVarBaseReg := false. backEnd hasVarBaseRegister ifTrue: [(self isCallerSavedReg: VarBaseReg) ifFalse: ["VarBaseReg is not caller-saved; must save and restore it, either by using an available caller-saved reg or push/pop." callerSavedReg := self availableRegisterOrNoneIn: (ABICallerSavedRegisterMask bitClear: 1 << TempReg). "TempReg used below" callerSavedReg = NoReg ifTrue: [self NativePushR: VarBaseReg. pushedVarBaseReg := true] ifFalse: [self MoveR: VarBaseReg R: callerSavedReg]]. self MoveCq: self varBaseAddress R: VarBaseReg]. captureFramePointer ifTrue: [self MoveR: FPReg Aw: self cFramePointerAddress]. "Capture the stack pointer prior to the call. If we've pushed VarBaseReg take that into account." (backEnd leafCallStackPointerDelta ~= 0 or: [pushedVarBaseReg]) ifTrue: [self LoadEffectiveAddressMw: (pushedVarBaseReg ifTrue: [backEnd leafCallStackPointerDelta + objectMemory wordSize] ifFalse: [backEnd leafCallStackPointerDelta]) r: NativeSPReg R: TempReg. self MoveR: TempReg Aw: self cStackPointerAddress] ifFalse: [self MoveR: NativeSPReg Aw: self cStackPointerAddress]. backEnd hasVarBaseRegister ifTrue: [(self isCallerSavedReg: VarBaseReg) ifFalse: [pushedVarBaseReg ifTrue: [self NativePopR: VarBaseReg] ifFalse: [self MoveR: callerSavedReg R: VarBaseReg]]]. self NativeRetN: 0. self outputInstructionsForGeneratedRuntimeAt: startAddress. + "This also implicitly flushes the read/write mapped dual zone to the read/execute zone." backEnd flushICacheFrom: startAddress asUnsignedInteger to: methodZoneBase asUnsignedInteger. self recordGeneratedRunTime: 'ceCaptureCStackPointers' address: startAddress. ceCaptureCStackPointers := self cCoerceSimple: startAddress to: #'void (*)(void)'! Item was changed: ----- Method: Cogit>>generateTrampolines (in category 'initialization') ----- generateTrampolines "Generate the run-time entries and exits at the base of the native code zone and update the base. Read the class-side method trampolines for documentation on the various trampolines" | methodZoneStart | methodZoneStart := methodZoneBase. methodLabel address: methodZoneStart. self allocateOpcodes: 80 bytecodes: 0. self setHasYoungReferent: false. objectRepresentation maybeGenerateSelectorIndexDereferenceRoutine. self generateSendTrampolines. self generateMissAbortTrampolines. objectRepresentation generateObjectRepresentationTrampolines. self generateRunTimeTrampolines. NewspeakVM ifTrue: [self generateNewspeakRuntime]. SistaVM ifTrue: [self generateSistaRuntime]. self generateEnilopmarts. self generateTracingTrampolines. "finish up" + self recordGeneratedRunTime: 'methodZoneBase' address: methodZoneBase! - self recordGeneratedRunTime: 'methodZoneBase' address: methodZoneBase. - backEnd flushICacheFrom: methodZoneStart asUnsignedInteger to: methodZoneBase asUnsignedInteger! Item was changed: ----- 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]). + backEnd stopsFrom: startAddress to: endAddress - 1. self cCode: '' inSmalltalk: [self initializeProcessor. backEnd stopsFrom: 0 to: guardPageSize - 1]. codeBase := methodZoneBase := startAddress. minValidCallAddress := (codeBase min: coInterpreter interpretAddress) min: coInterpreter primitiveFailAddress. methodZone manageFrom: methodZoneBase to: endAddress. self assertValidDualZone. self maybeGenerateCheckFeatures. self maybeGenerateCheckLZCNT. + self maybeGenerateCacheFlush. - self maybeGenerateICacheFlush. self generateVMOwnerLockFunctions. self genGetLeafCallStackPointer. self generateStackPointerCapture. self generateTrampolines. self computeEntryOffsets. self computeFullBlockEntryOffsets. self generateClosedPICPrototype. self alignMethodZoneBase. + + "None of the above is executed beyond ceCheckFeatures & ceCheckLZCNTFunction, + so a bulk flush now is the leanest thing to do." + self maybeFlushWritableZoneFrom: startAddress to: methodZoneBase asUnsignedInteger. "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>>maybeFlushWritableZoneFrom:to: (in category 'generate machine code - dual mapped zone support') ----- + maybeFlushWritableZoneFrom: startAddress to: endAddress + "If there is a dual mapped code zone (the normal zone but marked with read/execute, + and a read/write zone codeToDataDelta bytes away) then the data cache for the read/write + zone must be flushed, and the data cache for the read/execute zone must be invalidated, + for the Cogit to see the same values in both zones after a write to the read/write zone." + <var: 'startAddress' type: #usqInt> + <var: 'endAddress' type: #usqInt> + codeToDataDelta > 0 ifTrue: + [backEnd flushDCacheFrom: startAddress to: endAddress]! Item was added: + ----- Method: Cogit>>maybeGenerateCacheFlush (in category 'initialization') ----- + maybeGenerateCacheFlush + | startAddress | + <inline: true> + backEnd numICacheFlushOpcodes > 0 ifTrue: + [self allocateOpcodes: backEnd numICacheFlushOpcodes bytecodes: 0. + startAddress := methodZoneBase. + backEnd generateICacheFlush. + self outputInstructionsForGeneratedRuntimeAt: startAddress. + self recordGeneratedRunTime: 'ceFlushICache' address: startAddress. + ceFlushICache := self cCoerceSimple: startAddress to: #'void (*)(usqIntptr_t,usqIntptr_t)'. + backEnd initialFlushICacheFrom: startAddress to: methodZoneBase]. + self cppIf: #DUAL_MAPPED_CODE_ZONE + ifTrue: + [backEnd numDCacheFlushOpcodes > 0 ifTrue: + [self allocateOpcodes: backEnd numDCacheFlushOpcodes bytecodes: 0. + startAddress := methodZoneBase. + backEnd generateDCacheFlush. + self outputInstructionsForGeneratedRuntimeAt: startAddress. + self recordGeneratedRunTime: 'ceFlushDCache' address: startAddress. + ceFlushDCache := self cCoerceSimple: startAddress to: #'void (*)(usqIntptr_t,usqIntptr_t)'. + backEnd initialFlushICacheFrom: startAddress to: methodZoneBase]]! Item was removed: - ----- Method: Cogit>>maybeGenerateICacheFlush (in category 'initialization') ----- - maybeGenerateICacheFlush - | startAddress | - <inline: true> - backEnd numICacheFlushOpcodes > 0 ifTrue: - [self allocateOpcodes: backEnd numICacheFlushOpcodes bytecodes: 0. - startAddress := methodZoneBase. - backEnd generateICacheFlush. - self outputInstructionsForGeneratedRuntimeAt: startAddress. - self recordGeneratedRunTime: 'ceFlushICache' address: startAddress. - ceFlushICache := self cCoerceSimple: startAddress to: #'void (*)(usqIntptr_t,usqIntptr_t)']! Item was added: + ----- Method: Cogit>>simulateCeFlushDCacheFrom:to: (in category 'simulation only') ----- + simulateCeFlushDCacheFrom: start to: finish + <doNotGenerate> + processor abiMarshallArg0: start arg1: finish. + self simulateLeafCallOf: ceFlushDCache! Item was changed: ----- 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_CODE_ZONE ifAbsent: [false]) ifTrue: - (InitializationOptions at: #DUAL_MAPPED_COG_ZONE ifAbsent: [false]) ifTrue: [codeToDataDeltaPtr at: 0 put: coInterpreter cogCodeSize]! Item was changed: ----- Method: VMClass>>cppIf:ifTrue:ifFalse: (in category 'translation support') ----- cppIf: conditionBlockOrSymbolValue ifTrue: trueExpressionOrBlock ifFalse: falseExpressionOrBlockOrNil "When translated, produces #if (condition) #else #endif CPP directives. Example usage: self cppIf: [BytesPerWord = 8] ifTrue: [self doSomethingFor64Bit] ifFalse: [self doSomethingFor32Bit] self cppIf: BytesPerWord = 8 ifTrue: [self doSomethingFor64Bit] ifFalse: [self doSomethingFor32Bit] self cppIf: #A_GLOBAL ifTrue: [self doSomethingFor64Bit] ifFalse: [self doSomethingFor32Bit]" <doNotGenerate> ^(conditionBlockOrSymbolValue value ifNil: [false] ifNotNil: [:value| value isInteger ifTrue: [value ~= 0] ifFalse: [value isSymbol ifTrue: [(self class bindingOf: value) + ifNil: [InitializationOptions at: value ifAbsent: [false]] - ifNil: [false] ifNotNil: [:binding| binding value]] ifFalse: [value]]]) ifTrue: trueExpressionOrBlock ifFalse: falseExpressionOrBlockOrNil! Item was changed: ----- Method: VMMaker class>>generateAllConfigurationsUnderVersionControl (in category 'configurations') ----- generateAllConfigurationsUnderVersionControl self executeDisplayingProgress: (OrderedDictionary with: 'Generate all newspeak configurations under VCS' -> [ self generateAllNewspeakConfigurationsUnderVersionControl ] + with: 'Generate all squeak configurations under VCS' -> [ self generateAllSqueakConfigurationsUnderVersionControl ] - with: 'Generate all squeak cofigurations under VCS' -> [ self generateAllSqueakConfigurationsUnderVersionControl ] with: 'Generate all spur lowcode configurations' -> [ self generateAllSpurLowcodeConfigurations ] with: 'Generate VM plugins' -> [ self generateVMPlugins ] with: 'Generate spur leak checkers' -> [ self generateSpur32LeakChecker; generateSpur64LeakChecker ])! |
Free forum by Nabble | Edit this page |