VM Maker: VMMaker.oscog-eem.2601.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: VMMaker.oscog-eem.2601.mcz

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

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

Name: VMMaker.oscog-eem.2601
Author: eem
Time: 9 December 2019, 6:11:14.195782 pm
UUID: f68a6ed3-c868-4802-a358-4e5667d22982
Ancestors: VMMaker.oscog-eem.2600

Cogit:
Add an assert to check that non-pc-dependent instructions compute identical maxSize and machineCodeSize.  Fix the two ARM32 and four X64 instructions that violated this stringent assert.

Fix addressIsInCurrentCompilation: for simulation when there are negative addresses (possible that a MoveCwR or PushCw would have negative values, so even though this was only run afoul of by ARMv8 instructions that shouldn't have asked the question, this is goodness).

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

Item was changed:
  ----- Method: CogARMCompiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  "Because we don't use Thumb, each ARM instruction has 4 bytes. Many
  abstract opcodes need more than one instruction. Instructions that refer
  to constants and/or literals depend on literals being stored in-line or out-of-line.
 
  N.B.  The ^N forms are to get around the bytecode compiler's long branch
  limits which are exceeded when each case jumps around the otherwise."
 
  opcode
  caseOf: {
  "Noops & Pseudo Ops"
  [Label] -> [^0].
  [Literal] -> [^4].
  [AlignmentNops] -> [^(operands at: 0) - 4].
  [Fill32] -> [^4].
  [Nop] -> [^4].
  "Control"
  [Call] -> [^4].
  [CallFull] -> [^self literalLoadInstructionBytes + 4].
  [JumpR] -> [^4].
  [Jump] -> [^4].
  [JumpFull] -> [^self literalLoadInstructionBytes + 4].
  [JumpLong] -> [^4].
  [JumpZero] -> [^4].
  [JumpNonZero] -> [^4].
  [JumpNegative] -> [^4].
  [JumpNonNegative] -> [^4].
  [JumpOverflow] -> [^4].
  [JumpNoOverflow] -> [^4].
  [JumpCarry] -> [^4].
  [JumpNoCarry] -> [^4].
  [JumpLess] -> [^4].
  [JumpGreaterOrEqual] -> [^4].
  [JumpGreater] -> [^4].
  [JumpLessOrEqual] -> [^4].
  [JumpBelow] -> [^4].
  [JumpAboveOrEqual] -> [^4].
  [JumpAbove] -> [^4].
  [JumpBelowOrEqual] -> [^4].
  [JumpLongZero] -> [^4].
  [JumpLongNonZero] -> [^4].
  [JumpFPEqual] -> [^8].
  [JumpFPNotEqual] -> [^8].
  [JumpFPLess] -> [^8].
  [JumpFPGreaterOrEqual]-> [^8].
  [JumpFPGreater] -> [^8].
  [JumpFPLessOrEqual] -> [^8].
  [JumpFPOrdered] -> [^8].
  [JumpFPUnordered] -> [^8].
  [RetN] -> [^(operands at: 0) = 0 ifTrue: [4] ifFalse: [8]].
  [Stop] -> [^4].
 
  "Arithmetic"
  [AddCqR] -> [^self rotateable8bitSignedImmediate: (operands at: 0)
  ifTrue: [:r :i :n| 4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
  [AndCqR] -> [^self rotateable8bitBitwiseImmediate: (operands at: 0)
  ifTrue: [:r :i :n| 4]
  ifFalse:
  [self literalLoadInstructionBytes = 4
  ifTrue: [8]
  ifFalse:
  [1 << (operands at: 0) highBit = ((operands at: 0) + 1)
  ifTrue: [8]
  ifFalse: [self literalLoadInstructionBytes + 4]]]].
  [AndCqRR] -> [^self rotateable8bitBitwiseImmediate: (operands at: 0)
  ifTrue: [:r :i :n| 4]
  ifFalse:
  [self literalLoadInstructionBytes = 4
  ifTrue: [8]
  ifFalse:
  [1 << (operands at: 0) highBit = ((operands at: 0) + 1)
  ifTrue: [8]
  ifFalse: [self literalLoadInstructionBytes + 4]]]].
  [CmpCqR] -> [^self rotateable8bitSignedImmediate: (operands at: 0)
  ifTrue: [:r :i :n| 4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
  [OrCqR] -> [^self rotateable8bitImmediate: (operands at: 0)
  ifTrue: [:r :i| 4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
  [SubCqR] -> [^self rotateable8bitSignedImmediate: (operands at: 0)
  ifTrue: [:r :i :n| 4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
  [TstCqR] -> [^self rotateable8bitImmediate: (operands at: 0)
  ifTrue: [:r :i| 4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
  [XorCqR] -> [^self rotateable8bitBitwiseImmediate: (operands at: 0)
  ifTrue: [:r :i :n| 4]
  ifFalse:
  [self literalLoadInstructionBytes = 4
  ifTrue: [8]
  ifFalse:
  [1 << (operands at: 0) highBit = ((operands at: 0) + 1)
  ifTrue: [8]
  ifFalse: [self literalLoadInstructionBytes + 4]]]].
  [AddCwR] -> [^self literalLoadInstructionBytes + 4].
  [AndCwR] -> [^self literalLoadInstructionBytes + 4].
  [CmpCwR] -> [^self literalLoadInstructionBytes + 4].
  [OrCwR] -> [^self literalLoadInstructionBytes + 4].
  [SubCwR] -> [^self literalLoadInstructionBytes + 4].
  [XorCwR] -> [^self literalLoadInstructionBytes + 4].
  [AddRR] -> [^4].
  [AndRR] -> [^4].
  [CmpRR] -> [^4].
  [OrRR] -> [^4].
  [XorRR] -> [^4].
  [SubRR] -> [^4].
  [NegateR] -> [^4].
  [LoadEffectiveAddressMwrR]
  -> [^self rotateable8bitImmediate: (operands at: 0)
  ifTrue: [:r :i| 4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
 
  [LogicalShiftLeftCqR] -> [^4].
  [LogicalShiftRightCqR] -> [^4].
  [ArithmeticShiftRightCqR] -> [^4].
  [LogicalShiftLeftRR] -> [^4].
  [LogicalShiftRightRR] -> [^4].
  [ArithmeticShiftRightRR] -> [^4].
  [AddRdRd] -> [^4].
  [CmpRdRd] -> [^4].
  [SubRdRd] -> [^4].
  [MulRdRd] -> [^4].
  [DivRdRd] -> [^4].
  [SqrtRd] -> [^4].
  [ClzRR] -> [^4].
  "ARM Specific Arithmetic"
  [SMULL] -> [^4].
  [MSR] -> [^4].
  [CMPSMULL] -> [^4]. "special compare for genMulR:R: usage"
  "ARM Specific Data Movement"
  [PopLDM] -> [^4].
  [PushSTM] -> [^4].
  "Data Movement"
  [MoveCqR] -> [^self literalLoadInstructionBytes = 4
  ifTrue: [self literalLoadInstructionBytes]
  ifFalse:
  [self rotateable8bitBitwiseImmediate: (operands at: 0)
  ifTrue: [:r :i :n| 4]
  ifFalse: [self literalLoadInstructionBytes]]].
  [MoveCwR] -> [^self literalLoadInstructionBytes = 4
  ifTrue: [self literalLoadInstructionBytes]
  ifFalse:
  [(self inCurrentCompilation: (operands at: 0))
  ifTrue: [4]
  ifFalse: [self literalLoadInstructionBytes]]].
  [MoveRR] -> [^4].
  [MoveRdRd] -> [^4].
  [MoveAwR] -> [^(self isAddressRelativeToVarBase: (operands at: 0))
  ifTrue: [4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
  [MoveRAw] -> [^(self isAddressRelativeToVarBase: (operands at: 1))
  ifTrue: [4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
  [MoveAbR] -> [^(self isAddressRelativeToVarBase: (operands at: 0))
  ifTrue: [4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
  [MoveRAb] -> [^(self isAddressRelativeToVarBase: (operands at: 1))
  ifTrue: [4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
  [MoveRMwr] -> [^self is12BitValue: (operands at: 1)
  ifTrue: [:u :i| 4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
+ [MoveRdM64r] -> [^4].
- [MoveRdM64r] -> [^self literalLoadInstructionBytes + 4].
  [MoveMbrR] -> [^self is12BitValue: (operands at: 0)
  ifTrue: [:u :i| 4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
  [MoveRMbr] -> [^self is12BitValue: (operands at: 1)
  ifTrue: [:u :i| 4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
  [MoveRM16r] -> [^self is12BitValue: (operands at: 1)
  ifTrue: [:u :i| 4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
  [MoveM16rR] -> [^self rotateable8bitImmediate: (operands at: 0)
  ifTrue: [:r :i| 4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
+ [MoveM64rRd] -> [^4].
- [MoveM64rRd] -> [^self literalLoadInstructionBytes + 4].
  [MoveMwrR] -> [^self is12BitValue: (operands at: 0)
  ifTrue: [:u :i| 4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
  [MoveXbrRR] -> [^4].
  [MoveRXbrR] -> [^4].
  [MoveXwrRR] -> [^4].
  [MoveRXwrR] -> [^4].
  [PopR] -> [^4].
  [PushR] -> [^4].
  [PushCw] -> [^self literalLoadInstructionBytes = 4
  ifTrue: [self literalLoadInstructionBytes + 4]
  ifFalse:
  [(self inCurrentCompilation: (operands at: 0))
  ifTrue: [8]
  ifFalse:
  [self rotateable8bitBitwiseImmediate: (operands at: 0)
  ifTrue: [:r :i :n| 8]
  ifFalse: [self literalLoadInstructionBytes + 4]]]].
  [PushCq] -> [^self literalLoadInstructionBytes = 4
  ifTrue: [self literalLoadInstructionBytes + 4]
  ifFalse:
  [self rotateable8bitBitwiseImmediate: (operands at: 0)
  ifTrue: [:r :i :n| 8]
  ifFalse: [self literalLoadInstructionBytes + 4]]].
  [PrefetchAw] -> [^(self isAddressRelativeToVarBase: (operands at: 0))
  ifTrue: [4]
  ifFalse: [self literalLoadInstructionBytes + 4]].
  "Conversion"
  [ConvertRRd] -> [^8].
  }.
  ^0 "to keep C compiler quiet"
  !

Item was changed:
  ----- Method: CogX64Compiler>>computeMaximumSize (in category 'generate machine code') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: Cogit>>addressIsInCurrentCompilation: (in category 'testing') -----
  addressIsInCurrentCompilation: address
  <inline: true>
+ self cCode: [] inSmalltalk: [address < 0 ifTrue: [^false]].
  ^address asUnsignedInteger >= methodLabel address
   and: [address asUnsignedInteger < (methodZone youngReferrers min: methodLabel address + MaxMethodSize)]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>generateInstructionsAt: (in category 'generate machine code') -----
  generateInstructionsAt: eventualAbsoluteAddress
  "Size pc-dependent instructions and assign eventual addresses to all instructions.
  Answer the size of the code.
  Compute forward branches based on virtual address (abstract code starts at 0),
  assuming that any branches branched over are long.
  Compute backward branches based on actual address.
  Reuse the fixups array to record the pc-dependent instructions that need to have
  their code generation postponed until after the others.
 
  Override to andd handling for null branches (branches to the immediately following
  instruction) occasioned by StackToRegisterMapping's following of jumps."
  | absoluteAddress pcDependentIndex abstractInstruction fixup |
  <var: #abstractInstruction type: #'AbstractInstruction *'>
  <var: #fixup type: #'BytecodeFixup *'>
  absoluteAddress := eventualAbsoluteAddress.
  pcDependentIndex := 0.
  0 to: opcodeIndex - 1 do:
  [:i|
  self maybeBreakGeneratingAt: absoluteAddress.
  abstractInstruction := self abstractInstructionAt: i.
  abstractInstruction isPCDependent
  ifTrue:
  [abstractInstruction sizePCDependentInstructionAt: absoluteAddress.
  (abstractInstruction isJump
   and: [(i + 1 < opcodeIndex
    and: [abstractInstruction getJmpTarget == (self abstractInstructionAt: i + 1)])
  or: [i + 2 < opcodeIndex
  and: [abstractInstruction getJmpTarget == (self abstractInstructionAt: i + 2)
  and: [(self abstractInstructionAt: i + 1) opcode = Nop]]]])
  ifTrue:
  [abstractInstruction
  opcode: Nop;
  concretizeAt: absoluteAddress]
  ifFalse:
  [fixup := self fixupAtIndex: pcDependentIndex.
  pcDependentIndex := pcDependentIndex + 1.
  fixup instructionIndex: i].
  absoluteAddress := absoluteAddress + abstractInstruction machineCodeSize]
  ifFalse:
+ [absoluteAddress := abstractInstruction concretizeAt: absoluteAddress.
+ self assert: abstractInstruction machineCodeSize = abstractInstruction maxSize]].
- [absoluteAddress := abstractInstruction concretizeAt: absoluteAddress]].
  0 to: pcDependentIndex - 1 do:
  [:j|
  fixup := self fixupAtIndex: j.
  abstractInstruction := self abstractInstructionAt: fixup instructionIndex.
  self maybeBreakGeneratingAt: abstractInstruction address.
  abstractInstruction concretizeAt: abstractInstruction address].
  ^absoluteAddress - eventualAbsoluteAddress!