asm/AJx86JumpInstruction.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 12 Feb 2016 11:51:14 +0000
changeset 17 54798ae989cc
parent 3 483729eb4432
child 23 d2d9a2d4d6bf
permissions -rw-r--r--
Initial work on LLVM-based C1 compiler

"{ Package: 'jv:dragonfly/asm' }"

"{ NameSpace: Smalltalk }"

AJJumpInstruction subclass:#AJx86JumpInstruction
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'AsmJit-x86-Instructions'
!


!AJx86JumpInstruction methodsFor:'accessing'!

codeSize 
    machineCode ifNil: [  ^ 2 ].
    ^ machineCode size
!

instructionDesciptions
    ^ AJx86InstructionDescription instructions
!

machineCodeSize

    machineCode ifNil: [ ^ 2 ].
    
    ^ machineCode size
! !

!AJx86JumpInstruction methodsFor:'convenience'!

errorUndefinedLabel: aLabel 

    ^ self error: 'undefined label: ', aLabel name
! !

!AJx86JumpInstruction methodsFor:'emitting code'!

emitCode: asm
    "generate opcodes"

    | delta code nextInstruction target desc |
    
    target := label position.
    target ifNil: [ ^ machineCode := nil ].
    
    nextInstruction := position + 2.
    delta := (target - nextInstruction) asImm.
    desc := self instructionDesciptions at: name.	"can we use 8bit offset?"
    machineCode := delta isInt8
        ifTrue: [ 	self emitShortJump: desc offset: delta ]
        ifFalse: [ self emitLongJump: desc target: target ]
!

emitCodeAtOffset: offset assembler: asm
    
    position := offset.
    [ | labelPos | 
        labelPos := label position.
        labelPos ifNotNil: [ self emitCode: asm ].
        next ifNotNil: [ 
            next emitCodeAtOffset: offset + self machineCodeSize assembler: asm ].
        label position ~= labelPos ] whileTrue.
    
    label position ifNil: [ self errorUndefinedLabel: label  ]
!

emitConditionalJump: addr to: desc
    ^ {16r0F.
    (16r80 + desc opCode1).
    (addr bitAnd: 255).
    (addr >> 8 bitAnd: 255).
    (addr >> 16 bitAnd: 255).
    (addr >> 24 bitAnd: 255)} asByteArray
!

emitLongJump: desc target: target
    | addr sz nextInstruction |
    
    sz := self isConditional
        ifTrue: [ 2 ]
        ifFalse: [ 1 ].
        
    nextInstruction := position + 4 + sz.
    addr := (AJImmediate ivalue: target - nextInstruction) asDWord.
    
    ^ self isConditional
        ifFalse: [ self emitUnconditionalJumpTo: addr ]
        ifTrue: [ 	self emitConditionalJump: addr to: desc ]
!

emitShortJump: desc offset: delta
    "short jump"
    ^ self isConditional
        ifTrue: [ {(16r70 + desc opCode1). (delta asByte)} asByteArray ]
        ifFalse: [ {16rEB. (delta asByte)} asByteArray ]
!

emitUnconditionalJumpTo: addr
    ^ {
    16rE9.
    (addr bitAnd: 255).
    (addr >> 8 bitAnd: 255).
    (addr >> 16 bitAnd: 255).
    (addr >> 24 bitAnd: 255)} asByteArray
! !

!AJx86JumpInstruction methodsFor:'testing'!

isConditional
    ^ name ~~ #jmp
! !

!AJx86JumpInstruction class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !