Nicolas Cellier uploaded a new version of VMMaker to project VM Maker: http://source.squeak.org/VMMaker/VMMaker.oscog-nice.2914.mcz ==================== Summary ==================== Name: VMMaker.oscog-nice.2914 Author: nice Time: 31 December 2020, 10:06:40.613299 am UUID: 0e1f0f1f-96ba-41ec-8f4f-c0d2fb618a21 Ancestors: VMMaker.oscog-nice.2913 A few fixes for the VM tests - enable using a WordArray as simulation memory - concretizeAt: does not answer the instruction size but the next address =============== Diff against VMMaker.oscog-nice.2913 =============== Item was changed: ----- Method: AbstractInstructionTests>>generateInstructions (in category 'generating machine code') ----- generateInstructions "See Cogit>>computeMaximumSizes, generateInstructionsAt: & outputInstructionsAt:. This is a pure Smalltalk (non-Slang) version of that trio of methods." | address pcDependentInstructions instructions | address := 0. pcDependentInstructions := OrderedCollection new. opcodes do: [:abstractInstruction| abstractInstruction address: address; maxSize: abstractInstruction computeMaximumSize. address := address + abstractInstruction maxSize]. address := 0. opcodes do: [:abstractInstruction| abstractInstruction isPCDependent ifTrue: [abstractInstruction sizePCDependentInstructionAt: address. pcDependentInstructions addLast: abstractInstruction. address := address + abstractInstruction machineCodeSize] ifFalse: [address := abstractInstruction concretizeAt: address]]. pcDependentInstructions do: [:abstractInstruction| abstractInstruction concretizeAt: abstractInstruction address]. instructions := ByteArray new: address. address := 0. opcodes do: [:abstractInstruction| | machineCodeBytes | self assert: abstractInstruction address = address. machineCodeBytes := self memoryAsBytes: abstractInstruction machineCode object. 1 to: abstractInstruction machineCodeSize do: [:j| + instructions at: address + 1 put: (machineCodeBytes byteAt: j). - instructions at: address + 1 put: (machineCodeBytes at: j). address := address + 1]]. ^instructions! Item was changed: ----- Method: AbstractInstructionTests>>runAddCwR: (in category 'running') ----- runAddCwR: assertPrintBar "self defaultTester runAddCwR: false" self concreteCompilerClass dataRegistersWithAccessorsDo: [:reg :rgetter :rsetter| self pairs: (-2 to: 2) do: [:a :b| | inst len bogus memory | inst := self gen: AddCwR operand: a operand: reg. len := inst concretizeAt: 0. memory := self memoryAsBytes: inst machineCode. self processor reset; perform: rsetter with: (self processor convertIntegerToInternal: b). [[processor pc < len] whileTrue: + [processor singleStepIn: memory]] - [self processor singleStepIn: memory]] on: Error do: [:ex| ]. "self processor printRegistersOn: Transcript. Transcript show: (self processor disassembleInstructionAt: 0 In: memory); cr" assertPrintBar ifTrue: [self assert: processor pc = inst machineCodeSize. self assertCheckLongArithOpCodeSize: inst machineCodeSize] ifFalse: [bogus := processor pc ~= inst machineCodeSize]. self concreteCompilerClass dataRegistersWithAccessorsDo: [:ireg :getter :setter| | expected | (self concreteCompilerClass isRISCTempRegister: ireg) ifFalse: [expected := getter == rgetter ifTrue: [b + a] ifFalse: [0]. assertPrintBar ifTrue: [self assert: (self processor convertInternalToInteger: (self processor perform: getter)) equals: expected] ifFalse: [(self processor convertInternalToInteger: (self processor perform: getter)) ~= expected ifTrue: [bogus := true]]]. assertPrintBar ifFalse: [Transcript nextPutAll: rgetter; nextPut: $(; print: b; nextPutAll: ') + '; print: a; nextPutAll: ' = '; print: (self processor convertInternalToInteger: (self processor perform: rgetter)); cr; flush. bogus ifTrue: [self processor printRegistersOn: Transcript. Transcript show: (self processor disassembleInstructionAt: 0 In: memory); cr]]]]]! Item was changed: ----- Method: AbstractInstructionTests>>testNegateR (in category 'running') ----- testNegateR "self defaultTester testNegateR" self concreteCompilerClass dataRegistersWithAccessorsDo: [:reg :rgetter :rsetter| -2 to: 2 do: [:a| | inst len memory | inst := self gen: NegateR operand: reg. len := inst concretizeAt: 0. memory := self memoryAsBytes: inst machineCode. self processor reset; perform: rsetter with: (processor convertIntegerToInternal: a). [[processor pc < len] whileTrue: + [processor singleStepIn: memory]] - [self processor singleStepIn: memory]] on: Error do: [:ex| ]. "self processor printRegistersOn: Transcript. Transcript show: (self processor disassembleInstructionAt: 0 In: memory); cr" self assert: processor pc equals: inst machineCodeSize. self concreteCompilerClass dataRegistersWithAccessorsDo: [:ireg :getter :setter| | expected | expected := getter == rgetter ifTrue: [ a negated ] ifFalse: [0]. self assert: (processor convertInternalToInteger: (processor perform: getter)) equals: expected]]]! Item was changed: ----- Method: CogARMCompilerForTests>>concretizeAt: (in category 'generate machine code') ----- concretizeAt: actualAddress "Override to check maxSize and machineCodeSize" + | maxAddress nextAddress | - | size | maxSize ifNil: [maxSize := self computeMaximumSize]. + maxAddress := actualAddress + maxSize. + nextAddress := super concretizeAt: actualAddress. - size := super concretizeAt: actualAddress. self assert: (maxSize notNil and: [self isPCDependent + ifTrue: [maxAddress >= nextAddress] + ifFalse: [maxAddress = nextAddress]]). + ^nextAddress! - ifTrue: [maxSize >= size] - ifFalse: [maxSize = size]]). - ^size! Item was changed: ----- Method: CogIA32CompilerForTests>>concretizeAt: (in category 'generate machine code') ----- concretizeAt: actualAddress "Override to check maxSize and machineCodeSize" + | maxAddress nextAddress | - | size | maxSize ifNil: [maxSize := self computeMaximumSize]. + maxAddress := actualAddress + maxSize. + nextAddress := super concretizeAt: actualAddress. - size := super concretizeAt: actualAddress. self assert: (maxSize notNil and: [self isPCDependent + ifTrue: [maxAddress >= nextAddress] + ifFalse: [maxAddress = nextAddress]]). + ^nextAddress! - ifTrue: [maxSize >= size] - ifFalse: [maxSize = size]]). - ^size! Item was changed: ----- Method: CogX64CompilerForTests>>concretizeAt: (in category 'generate machine code') ----- concretizeAt: actualAddress "Override to check maxSize and machineCodeSize" + | maxAddress nextAddress | - | size | maxSize ifNil: [maxSize := self computeMaximumSize]. + maxAddress := actualAddress + maxSize. + nextAddress := super concretizeAt: actualAddress. - size := super concretizeAt: actualAddress. self assert: (maxSize notNil and: [self isPCDependent + ifTrue: [maxAddress >= nextAddress] + ifFalse: [maxAddress = nextAddress]]). + ^nextAddress! - ifTrue: [maxSize >= size] - ifFalse: [maxSize = size]]). - ^size! Item was changed: VMClass subclass: #OutOfLineLiteralsManager instanceVariableNames: 'cogit objectMemory objectRepresentation firstOpcodeIndex nextLiteralIndex lastDumpedLiteralIndex literals literalsSize savedFirstOpcodeIndex savedNextLiteralIndex savedLastDumpedLiteralIndex' classVariableNames: '' poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogRTLOpcodes' category: 'VMMaker-JIT'! + !OutOfLineLiteralsManager commentStamp: 'nice 12/31/2020 09:14' prior: 0! + An OutOfLineLiteralsManager manages the dumping of literals for backends that want to keep literals out-of-line, accessed by pc-relative addressing. - !OutOfLineLiteralsManager commentStamp: 'eem 6/7/2015 12:10' prior: 0! - An OutOfLineLiteralsManager manages the dumping of literals for backends that wat to keep literals out-of-line, accessed by pc-relative addressing. Instance Variables cogit: <Cogit>! Item was added: + ----- Method: RawBitsArray>>byteAt: (in category '*VMMaker-simulation') ----- + byteAt: anInteger + "emulate an access to raw (unsigned) bytes, as if the receiver was a ByteArray" + + | element p | + p := self bytesPerBasicElement. + p = 1 ifTrue: [^self basicAt: 1]. + element := self basicAt: anInteger + p - 1 // p. + ^Smalltalk isLittleEndian + ifTrue: [element digitAt: anInteger - 1 \\ p + 1] + ifFalse: [element digitAt: p - (anInteger \\ p)] + ! Item was added: + ----- Method: WordArray>>unsignedLongAt:bigEndian: (in category '*VMMaker-JITsimulation') ----- + unsignedLongAt: byteIndex bigEndian: bigEndian + "Compatiblity with the ByteArray & Alien methods of the same name." + | wordIndex lowBits word hiWord | + wordIndex := byteIndex - 1 // 4 + 1. + lowBits := byteIndex - 1 bitAnd: 3. + word := self at: wordIndex. + lowBits > 0 ifTrue: "access straddles two words" + [hiWord := self at: wordIndex + 1. + word := (word bitShift: lowBits * -8) + (hiWord bitShift: 4 - lowBits * 8)]. + word := word bitAnd: 16rFFFFFFFF. + bigEndian + ifTrue: + [word := ((word bitShift: -24) bitAnd: 16rFF) + + ((word bitShift: -8) bitAnd: 16rFF00) + + ((word bitAnd: 16rFF00) bitShift: 8) + + ((word bitAnd: 16rFF) bitShift: 24)]. + ^word! |
Free forum by Nabble | Edit this page |