Eliot Miranda uploaded a new version of VMMaker to project VM Maker: http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2569.mcz ==================== Summary ==================== Name: VMMaker.oscog-eem.2569 Author: eem Time: 9 October 2019, 8:08:35.66404 pm UUID: e81c138f-13e8-44a4-8ae5-707e996a1881 Ancestors: VMMaker.oscog-eem.2568 Cogit: Fix MoveAwR and MoveRAw for FPReg and SPReg on X64 by avoiding the swap of FPReg/SPReg with RAX prior to the move; i.e. RAX will get smashed. Document this in three relevant places. Note that this situation arises because CFramePointer and CStackPointer are global variables, not private variables in the interpreter's collection, and hence not accessible via VarBaseReg(RBX). Sere we to arrange CFramePointer and CStackPointer were accessible via VarBaseReg(RBX) trampolines would be shorter and perhaps faster. We should do this asap. In the simulator change the regime for CFramePointer & CStackPointer from interpreter local to in-memory to get the simulator to generate code using the same scheme. Have manageFrom:to: inlined. Fix some minor bugs with assembly decoration. Simulator: don;'t wipe out system attribute 2 in openOn:extraMemory: allowing setting of arguments before openOn:extraMemory:. Plugins: fix a typo. =============== Diff against VMMaker.oscog-eem.2568 =============== Item was added: + ----- Method: CogInLineLiteralsX64Compiler>>wantsNearAddressFor: (in category 'simulation') ----- + wantsNearAddressFor: anObject + "A hack hook to allow x64 to address CStackPointer and CFramePointer relative to VarBaseReg. + With this regime we do _not_ want to access via VarBasereg but instead test the + MoveAwR & MoveRAw hack fetch/storing through RAX." + <doNotGenerate> + ^false! Item was changed: ----- Method: CogMethodZone>>manageFrom:to: (in category 'initialization') ----- manageFrom: theStartAddress to: theLimitAddress <returnTypeC: #void> + <inline: true> mzFreeStart := baseAddress := theStartAddress. youngReferrers := limitAddress := theLimitAddress. openPICList := nil. NewspeakVM ifTrue: [unpairedMethodList := nil]. methodBytesFreedSinceLastCompaction := 0. methodCount := 0! Item was changed: ----- Method: CogRTLOpcodes class>>initialize (in category 'class initialization') ----- initialize "Abstract opcodes are a compound of a one word operation specifier and zero or more operand type specifiers. The assembler is in Cogit protocol abstract instructions and uses `at&t' syntax, assigning to the register on the right. e.g. MoveRR is the Move opcode with two register operand specifiers and defines a move register to register instruction from operand 0 to operand 1. The word and register size is assumed to be either 32-bits on a 32-bit architecture or 64-bits on a 64-bit architecture. The abstract machine is mostly a 2 address machine with the odd three address instruction added to better exploit RISCs. (self initialize) The operand specifiers are R - general purpose register Rs - single-precision floating-point register Rd - double-precision floating-point register Cq - a `quick' constant that can be encoded in the minimum space possible. Cw - a constant with word size where word is the default operand size for the Smalltalk VM, 32-bits for a 32-bit VM, 64-bits for a 64-bit VM. The generated constant must occupy the default number of bits. This allows e.g. a garbage collector to update the value without invalidating the code. C32 - a constant with 32 bit size. The generated constant must occupy 32 bits. C64 - a constant with 64 bit size. The generated constant must occupy 64 bits. Aw - memory word (32-bits for a 32-bit VM, 64-bits for a 64-bit VM) at an absolute address + See note about MoveAwR and MoveRAw in the opcodeNames literal array below!!!! Ab - memory byte at an absolute address A32 - memory 32-bit halfword at an absolute address Mwr - memory word whose address is at a constant offset from an address in a register Mbr - memory byte whose address is at a constant offset from an address in a register (zero-extended on read) M16r - memory 16-bit halfword whose address is at a constant offset from an address in a register M32r - memory 32-bit halfword whose address is at a constant offset from an address in a register M64r - memory 64-bit doubleword whose address is at a constant offset from an address in a register Xbr - memory byte whose address is r * byte size away from an address in a register X16r - memory 16-bit halfword whose address is r * (2 bytes size) away from an address in a register X32r - memory 32-bit halfword whose address is r * (4 bytes size) away from an address in a register (64-bit ISAs only) Xwr - memory word whose address is r * word size away from an address in a register Xowr - memory word whose address is o + (r * word size) away from an address in a register (scaled indexed) An alternative would be to decouple opcodes from operands, e.g. Move := 1. Add := 2. Sub := 3... RegisterOperand := 1. ConstantQuickOperand := 2. ConstantWordOperand := 3... But not all combinations make sense and even fewer are used so we stick with the simple compound approach. The assumption is that comparison and arithmetic instructions set condition codes and that move instructions leave the condition codes unaffected. In particular LoadEffectiveAddressMwrR does not set condition codes although it can be used to do arithmetic. On processors such as MIPS this distinction is invalid; there are no condition codes. So the backend is allowed to collapse operation, branch pairs to internal instruction definitions (see senders and implementors of noteFollowingConditionalBranch:). Not all of the definitions in opcodeDefinitions below are implemented. In particular we do not implement the XowrR scaled index addressing mode since it requires 4 operands. Not all instructions make sense on all architectures. MoveRRd and MoveRdR aqre meaningful only on 64-bit machines. Note that there are no generic division instructions defined, but a processor may define some. Branch/Call ranges. Jump[Cond] can be generated as short as possible. Call/Jump[Cond]Long must be generated in the same number of bytes irrespective of displacement since their targets may be updated, but they need only span 16Mb, the maximum size of the code zone. This allows e.g. ARM to use single-word call and jump instructions for most calls and jumps. CallFull/JumpFull must also be generated in the same number of bytes irrespective of displacement for the same reason, but they must be able to span the full (32-bit or 64-bit) address space because they are used to call code in the C runtime, which may be distant from the code zone. CallFull/JumpFull are allowed to use the cResultRegister as a scratch if required (e.g. on x64 where there is no direct 64-bit call or jump). Byte reads. If the concrete compiler class answers true to byteReadsZeroExtend then byte reads must zero-extend the byte read into the destination register. If not, the other bits of the register should be left undisturbed and the Cogit will add an instruction to zero the register as required. Under no circumstances should byte reads sign-extend. 16-bit (and on 64-bits, 32-bit) reads. These /are/ expected to always zero-extend." | opcodeNames refs | opcodeNames := #("Noops & Pseudo Ops" Label Literal "a word-sized literal" AlignmentNops Fill32 "output four byte's worth of bytes with operand 0" Nop "Control" Call "call within the code zone" CallFull "call anywhere within the full address space" CallR RetN JumpR "Not a regular jump, i.e. not pc dependent." Stop "Halt the processor" "N.B. Jumps are contiguous. Long and Full jumps are contiguous within them. See FirstJump et al below" JumpFull "Jump anywhere within the address space" JumpLong "Jump anywhere within the 16mb code zone." JumpLongZero "a.k.a. JumpLongEqual" JumpLongNonZero "a.k.a. JumpLongNotEqual" Jump "short jumps; can be encoded in as few bytes as possible; will not be disturbed by GC or relocation." JumpZero "a.k.a. JumpEqual" JumpNonZero "a.k.a. JumpNotEqual" JumpNegative JumpNonNegative JumpOverflow JumpNoOverflow JumpCarry JumpNoCarry JumpLess "signed" JumpGreaterOrEqual JumpGreater JumpLessOrEqual JumpBelow "unsigned" JumpAboveOrEqual JumpAbove JumpBelowOrEqual JumpFPEqual JumpFPNotEqual JumpFPLess JumpFPLessOrEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPOrdered JumpFPUnordered "Data Movement; destination is always last operand" MoveRR + "N.B. On certain targets (including X64) MoveAwR & MoveRAw may + smash TempReg if the register argument is either FPReg or SPReg!!!!" MoveAwR MoveA32R MoveRAw MoveRA32 MoveAbR MoveRAb MoveMwrR MoveRMwr MoveXwrRR MoveRXwrR "MoveXowrR MoveRXowr""Unused" MoveM8rR MoveMs8rR MoveRM8r MoveM16rR MoveRM16r MoveX16rRR MoveRX16rR MoveM32rR MoveRM32r MoveX32rRR MoveRX32rR MoveMbrR MoveRMbr MoveXbrRR MoveRXbrR MoveCqR MoveCwR MoveC32R "MoveC64R""Not used" MoveRRd MoveRdR MoveRdRd MoveM64rRd MoveRdM64r MoveRsRs MoveM32rRs MoveRsM32r PopR PushR PushCq PushCw PrefetchAw "Arithmetic; destination is always last operand except Cmp; CmpXR is SubRX with no update of result" LoadEffectiveAddressMwrR "LoadEffectiveAddressXowrR" "Variants of add/multiply" NegateR "2's complement negation" NotR ArithmeticShiftRightCqR ArithmeticShiftRightRR LogicalShiftRightCqR LogicalShiftRightRR LogicalShiftLeftCqR LogicalShiftLeftRR RotateLeftCqR RotateRightCqR CmpRR AddRR SubRR AndRR OrRR XorRR CmpCqR AddCqR SubCqR AndCqR OrCqR TstCqR XorCqR CmpCwR CmpC32R AddCwR SubCwR AndCwR OrCwR XorCwR AddcRR AddcCqR SubbRR SubbCqR AndCqRR "Three address ops for RISCs; feel free to add and extend" CmpRdRd AddRdRd SubRdRd MulRdRd DivRdRd SqrtRd XorRdRd CmpRsRs AddRsRs SubRsRs MulRsRs DivRsRs SqrtRs XorRsRs "Conversion" ConvertRRd ConvertRdR ConvertRsRd ConvertRdRs ConvertRsR ConvertRRs SignExtend8RR SignExtend16RR SignExtend32RR ZeroExtend8RR ZeroExtend16RR ZeroExtend32RR "Advanced bit manipulation (aritmetic)" ClzRR LastRTLCode). "Magic auto declaration. Add to the classPool any new variables and nuke any obsolete ones, and assign values" "Find the variables directly referenced by this method" refs := (thisContext method literals select: [:l| l isVariableBinding and: [classPool includesKey: l key]]) collect: [:ea| ea key]. "Move to Undeclared any opcodes in classPool not in opcodes or this method." (classPool keys reject: [:k| (opcodeNames includes: k) or: [refs includes: k]]) do: [:k| Undeclared declare: k from: classPool]. "Declare as class variables and number elements of opcodeArray above" opcodeNames withIndexDo: [:classVarName :value| self classPool declare: classVarName from: Undeclared; at: classVarName put: value]. "For CogAbstractInstruction>>isJump etc..." FirstJump := JumpFull. LastJump := JumpFPUnordered. FirstShortJump := Jump. "And now initialize the backends; they add their own opcodes and hence these must be reinitialized." (Smalltalk classNamed: #CogAbstractInstruction) ifNotNil: [:cogAbstractInstruction| cogAbstractInstruction allSubclasses do: [:sc| sc initialize]]! 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. - systemAttributes at: 1 put: fileName; at: 2 put: nil. ["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. "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 + cogCodeSize + 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 + cogCodeSize + stackZoneSize. self movePrimTraceLogToMemoryAt: objectMemory cogCodeBase + cogCodeSize + 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>>computeMaximumSize (in category 'generate machine code') ----- (excessive size, no diff calculated) Item was changed: ----- Method: CogX64Compiler>>concretizeMoveAwR (in category 'generate machine code') ----- concretizeMoveAwR "Will get inlined into concretizeAt: switch." <inline: true> | addressOperand reg offset save0 save1 | addressOperand := operands at: 0. (self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue: [addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address]. (self isAddressRelativeToVarBase: addressOperand) ifTrue: [save0 := operands at: 0. save1 := operands at: 1. operands at: 0 put: addressOperand - cogit varBaseAddress; at: 1 put: RBX; at: 2 put: save1. self concretizeMoveMwrR. operands at: 0 put: save0; at: 1 put: save1; at: 2 put: 0. ^machineCodeSize]. reg := operands at: 1. + "If fetching RAX, fetch directly, otherwise, because of instruction encoding limitations, the register + _must_ be fetched through RAX. If reg = RBP or RSP simply fetch directly, otherwise swap RAX with + the register before and after the fetch through RAX. We avoid swapping before hand with RBP + and RSP because setting RSP to whatever the contents of RAX is can cause disastrous results if + an interrupt is delivered immediately after that point. See mail threads beginning with + http://lists.squeakfoundation.org/pipermail/vm-dev/2019-September/031428.html + http://lists.squeakfoundation.org/pipermail/vm-dev/2019-October/031499.html" + (reg = RAX or: [reg = RBP or: [reg = RSP]]) - reg = RAX ifTrue: [offset := 0] ifFalse: [machineCode at: 0 put: (self rexR: 0 x: 0 b: reg); at: 1 put: 16r90 + (reg \\ 8). offset := 2]. machineCode at: 0 + offset put: 16r48; at: 1 + offset put: 16rA1; at: 2 + offset put: (addressOperand bitAnd: 16rFF); at: 3 + offset put: (addressOperand >> 8 bitAnd: 16rFF); at: 4 + offset put: (addressOperand >> 16 bitAnd: 16rFF); at: 5 + offset put: (addressOperand >> 24 bitAnd: 16rFF); at: 6 + offset put: (addressOperand >> 32 bitAnd: 16rFF); at: 7 + offset put: (addressOperand >> 40 bitAnd: 16rFF); at: 8 + offset put: (addressOperand >> 48 bitAnd: 16rFF); at: 9 + offset put: (addressOperand >> 56 bitAnd: 16rFF). reg = RAX ifTrue: [^machineCodeSize := 10]. + "Now effect the assignment via xchg, which saves a byte over a move" + (reg = RBP or: [reg = RSP]) ifTrue: + [machineCode + at: 10 put: (self rexR: RAX x: 0 b: reg); + at: 11 put: 16r90 + (reg \\ 8). + ^machineCodeSize := 12]. machineCode at: 12 put: (machineCode at: 0); at: 13 put: (machineCode at: 1). ^machineCodeSize := 14! Item was changed: ----- Method: CogX64Compiler>>concretizeMoveRAw (in category 'generate machine code') ----- concretizeMoveRAw "Will get inlined into concretizeAt: switch." <inline: true> | addressOperand reg offset save1 | reg := operands at: 0. addressOperand := operands at: 1. (self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue: [addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address]. (self isAddressRelativeToVarBase: addressOperand) ifTrue: [save1 := operands at: 1. operands at: 1 put: addressOperand - cogit varBaseAddress; at: 2 put: RBX. self concretizeMoveRMwr. operands at: 1 put: save1; at: 2 put: 0. ^machineCodeSize]. + "If storing RAX, store directly, otherwise, because of instruction encoding limitations, the register + _must_ be stored through RAX. If reg = RBP or RSP simply store directly, otherwise swap RAX with + the register before and after the store through RAX. We avoid sweapping before hand with RBP + and RSP because setting RSP to whatever the contents of RAX is can cause disastrous results if + an interrupt is delivered immediately after that point. See mail threads beginning with + http://lists.squeakfoundation.org/pipermail/vm-dev/2019-September/031428.html + http://lists.squeakfoundation.org/pipermail/vm-dev/2019-October/031499.html" + (reg = RAX or: [reg = RBP or: [reg = RSP]]) - reg = RAX ifTrue: [offset := 0] ifFalse: + [(reg = RBP or: [reg = RSP]) + ifTrue: + [machineCode + at: 0 put: (self rexR: reg x: 0 b: RAX); + at: 1 put: 16r89; + at: 2 put: (self mod: ModReg RM: RAX RO: reg). + offset := 3] + ifFalse: + [machineCode + at: 0 put: (self rexR: RAX x: 0 b: reg); + at: 1 put: 16r90 + (reg \\ 8). + offset := 2]]. - [machineCode - at: 0 put: (self rexR: 0 x: 0 b: reg); - at: 1 put: 16r90 + (reg \\ 8). - offset := 2]. machineCode at: 0 + offset put: 16r48; at: 1 + offset put: 16rA3; at: 2 + offset put: (addressOperand bitAnd: 16rFF); at: 3 + offset put: (addressOperand >> 8 bitAnd: 16rFF); at: 4 + offset put: (addressOperand >> 16 bitAnd: 16rFF); at: 5 + offset put: (addressOperand >> 24 bitAnd: 16rFF); at: 6 + offset put: (addressOperand >> 32 bitAnd: 16rFF); at: 7 + offset put: (addressOperand >> 40 bitAnd: 16rFF); at: 8 + offset put: (addressOperand >> 48 bitAnd: 16rFF); at: 9 + offset put: (addressOperand >> 56 bitAnd: 16rFF). reg = RAX ifTrue: [^machineCodeSize := 10]. + (reg = RBP or: [reg = RSP]) ifTrue: + [^machineCodeSize := 13]. + "Now effect the assignment via xchg, which restores RAX" machineCode at: 12 put: (machineCode at: 0); at: 13 put: (machineCode at: 1). ^machineCodeSize := 14! Item was changed: ----- Method: Cogit>>MoveAw:R: (in category 'abstract instructions') ----- + MoveAw: address R: reg + "N.B. On certain targets (including X64) this instruction may smash TempReg if the target reg is either FPReg or SPReg." - MoveAw: address R: reg <inline: true> <returnTypeC: #'AbstractInstruction *'> ^self gen: MoveAwR literal: address operand: reg! Item was changed: ----- Method: Cogit>>MoveR:Aw: (in category 'abstract instructions') ----- MoveR: reg Aw: address + "N.B. On certain targets (including X64) this instruction may smash TempReg if the source reg is either FPReg or SPReg." <inline: true> <returnTypeC: #'AbstractInstruction *'> ^self gen: MoveRAw operand: reg literal: address! Item was changed: ----- Method: Cogit>>lookupAddress: (in category 'disassembly') ----- lookupAddress: address <doNotGenerate> | cogMethod | address < methodZone freeStart ifTrue: [address >= methodZoneBase ifTrue: [(cogMethod := methodZone methodFor: address) ~= 0 ifTrue: [cogMethod := self cCoerceSimple: cogMethod to: #'CogMethod *'. ^((cogMethod selector ~= objectMemory nilObject and: [objectRepresentation couldBeObject: cogMethod selector]) ifTrue: [coInterpreter stringOf: cogMethod selector] ifFalse: [cogMethod asInteger hex]), '@', ((address - cogMethod asInteger) hex allButFirst: 3)]] ifFalse: [^address = (self codeEntryFor: address) ifTrue: [self codeEntryNameFor: address]]. ^nil]. (simulatedTrampolines includesKey: address) ifTrue: [^self labelForSimulationAccessor: (simulatedTrampolines at: address)]. (simulatedVariableGetters includesKey: address) ifTrue: [^self labelForSimulationAccessor: (simulatedVariableGetters at: address)]. + ^(coInterpreter lookupAddress: address) ifNil: + [address = self cStackPointerAddress + ifTrue: [#CStackPointer] + ifFalse: + [address = self cFramePointerAddress ifTrue: + [#CFramePointer]]]! - ^coInterpreter lookupAddress: address! Item was changed: ----- Method: SocketPluginSimulator>>map:to:type:register:spawning:and:and: (in category 'simulation support') ----- map: hostSocketHandle to: simSockPtr type: socketType register: semaphores spawning: blockOne and: blockTwo and: blockThree | simSocket ourPriority | "SQSocket is typedef struct { int sessionID; int socketType; void *privateSocketPtr; } SQSocket" simSocket := ByteArray new: (self sizeof: #SQSocket). simSocket unsignedLongAt: 1 put: interpreterProxy getThisSessionID; unsignedLongAt: 5 put: socketType. simSocket size = 12 ifTrue: [simSocket unsignedLongAt: 9 put: (fakeAddressCounter := fakeAddressCounter + 64)] ifFalse: [simSocket unsignedLongLongAt: 9 put: (fakeAddressCounter := fakeAddressCounter + 80)]. self assert: ((interpreterProxy isBytes: simSockPtr cPtrAsOop) and: [(interpreterProxy numBytesOf: simSockPtr cPtrAsOop) = simSocket size]). 1 to: simSocket size do: [:i| simSockPtr at: i - 1 put: (simSocket at: i)]. self assert: (self simSocketHandleFrom: simSockPtr) = simSocket. openSocketHandles add: hostSocketHandle. hostSocketToSimSocketMap at: hostSocketHandle put: simSocket. simSocketToHostSocketMap at: simSocket put: hostSocketHandle. externalSemaphores addAll: semaphores. "N.B. These don't need registering. Eventually they will end up waiting on semaphores that have been unregistered, and hence will get garbage collected, along with these processes. But a) run them at one higher than the current priority, and + b) ensure that they all effectively resume at the same time; i.e. ensure this code doesn't get preempted by the first - b) ensure that they all effectively resume at the same time; i.e. ensure this code doesn;t get preempted by the first process to start running." ourPriority := Processor activePriority. [({blockOne. blockTwo. blockThree} collect: [:b| b newProcess priority: ourPriority + 1; yourself]) do: [:each| each resume]] valueAt: ourPriority + 2! Item was changed: ----- Method: StackInterpreterSimulator>>openOn:extraMemory: (in category 'initialization') ----- openOn: fileName extraMemory: extraBytes "StackInterpreterSimulator new openOn: 'clone.im' extraMemory: 100000" | f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes headerFlags heapBase firstSegSize heapSize hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize 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. - systemAttributes at: 1 put: fileName; at: 2 put: nil. ["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 := objectMemory byteSwapped: version) = 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. "pad to word boundary. This slot can be used for anything else that will fit in 16 bits. It is used for the cog code size in Cog. Preserve it to be polite to other VMs." theUnknownShort := self getShortFromFile: f swap: swapBytes. self assert: f position = (objectMemory wordSize = 4 ifTrue: [40] ifFalse: [64]). hdrEdenBytes := self getWord32FromFile: f swap: swapBytes. objectMemory edenBytes: (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. "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])]. "allocate interpreter memory" heapBase := objectMemory startOfMemory. objectMemory setHeapBase: heapBase memoryLimit: heapBase + heapSize endOfMemory: heapBase + dataSize. "bogus for Spur" 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 ensureImageFormatIsUpToDate: swapBytes. bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr. "adjust pointers for zero base address" UIManager default informUser: 'Relocating object pointers...' during: [self initializeInterpreter: bytesToShift]! Item was changed: ----- Method: StackToRegisterMappingCogit>>beginHighLevelCall: (in category 'inline ffi') ----- beginHighLevelCall: alignment <option: #LowcodeVM> | mask actualAlignment | "Store the smalltalk pointers" self ssFlushAll. + backEnd genSaveStackPointers. + backEnd hasLinkRegister ifTrue: + [self MoveAw: coInterpreter instructionPointerAddress R: LinkReg]. - self MoveR: SPReg Aw: coInterpreter stackPointerAddress. - self MoveR: FPReg Aw: coInterpreter framePointerAddress. - backEnd hasLinkRegister ifTrue: [ - self MoveAw: coInterpreter instructionPointerAddress R: LinkReg - ]. - "Load the C pointers" + backEnd genLoadCStackPointer. - self MoveAw: self cStackPointerAddress R: SPReg. "Load the native stack frame pointer" self MoveMw: self frameOffsetOfNativeFramePointer r: FPReg R: FPReg. self SubCq: 1 R: FPReg. actualAlignment := (alignment max: BytesPerWord). + actualAlignment > BytesPerWord ifTrue: + [mask := actualAlignment negated. + self AndCq: mask R: SPReg]. + currentCallCleanUpSize := 0! - actualAlignment > BytesPerWord ifTrue: [ - mask := actualAlignment negated. - self AndCq: mask R: SPReg. - ]. - currentCallCleanUpSize := 0.! |
Free forum by Nabble | Edit this page |