asm/AJImmediate.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 17 Jun 2016 17:25:15 +0100
changeset 26 8eb6716029aa
parent 23 d2d9a2d4d6bf
permissions -rw-r--r--
Merge

"
    Copyright (c) 2012-2016 Igor Stasenko
                            Martin McClure
                            Damien Pollet
                            Camillo Bruni
                            Guido Chari
                   2016-now Jan Vrany <jan.vrany [at] fit . cvut . cz>

    Permission is hereby granted, free of charge, to any person obtaining a copy
    of this software and associated documentation files (the 'Software'), to deal
    in the Software without restriction, including without limitation the rights
    to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
    copies of the Software, and to permit persons to whom the Software is
    furnished to do so, subject to the following conditions:

    The above copyright notice and this permission notice shall be included in all
    copies or substantial portions of the Software.

    THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
    IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
    FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
    AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
    LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
    OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
    SOFTWARE.
"
"{ Package: 'jv:dragonfly/asm' }"

"{ NameSpace: Smalltalk }"

AJOperand subclass:#AJImmediate
	instanceVariableNames:'label size isUnsigned relocMode value'
	classVariableNames:''
	poolDictionaries:''
	category:'AsmJit-Operands'
!

AJImmediate comment:'I am an immediate (constant integer) operand used by the assembler.

Example:
	"create an immediate from an integer"
	1 asImm.
	"implicitely use an immediate in an assembly instrution"
	asm := AJx64Assembler new.
	asm add: 1 to: asm RAX.
	'
!

!AJImmediate class methodsFor:'documentation'!

copyright
"
    Copyright (c) 2012-2016 Igor Stasenko
                            Martin McClure
                            Damien Pollet
                            Camillo Bruni
                            Guido Chari
                   2016-now Jan Vrany <jan.vrany [at] fit . cvut . cz>

    Permission is hereby granted, free of charge, to any person obtaining a copy
    of this software and associated documentation files (the 'Software'), to deal
    in the Software without restriction, including without limitation the rights
    to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
    copies of the Software, and to permit persons to whom the Software is
    furnished to do so, subject to the following conditions:

    The above copyright notice and this permission notice shall be included in all
    copies or substantial portions of the Software.

    THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
    IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
    FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
    AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
    LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
    OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
    SOFTWARE.

"
! !

!AJImmediate class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!AJImmediate class methodsFor:'as yet unclassified'!

ivalue: aValue
    ^ self new
        ivalue: aValue
!

uvalue: aValue
    ^ self new uvalue: aValue

    "Created: / 11-01-2016 / 21:05:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!AJImmediate methodsFor:'accessing'!

extractLabels: aBlock

    label ifNotNil: [ label extractLabels: aBlock ]    
!

ivalue: aValue
    "signed integer value"
    value := aValue.
    isUnsigned := false.
!

label: aLabelName

    label := aLabelName
!

relocMode
    ^ relocMode ifNil: [#RelocNone ]
!

size
    ^ size
!

size: aSize
    size := aSize
!

sizeFor: anOperand
    "Check if I am a valid size to be used together with anOperand
    If so, I will use as much size as it"
    self assert: (self fitsInSize: anOperand size).
    ^anOperand size
!

uvalue: aValue
    "unsigned value"
    self assert: (aValue >=0).
    value := aValue.
    isUnsigned := true.
!

value
    ^ value
! !

!AJImmediate methodsFor:'converting'!

asByte
    "answer the byte representing a value"
    (self fitsInSize: 1)
        ifFalse: [ Error signal: self asString, ' exceeds byte (8bit) range' ].

    (self isSigned and: [ value < 0 ]) ifTrue: [ ^ (1<<8) + value ].
    
    ^ value
!

asDWord
    "answer the 32bit word representing a value"
    (self fitsInSize: 4)
        ifFalse: [ Error signal: self asString, ' exceeds doubleword (32bit) range' ].

    (self isSigned and: [ value < 0 ]) ifTrue: [ ^ (1<<32) + value ].
    
    ^ value
!

asQWord
    "answer the 64bit word representing a value"
    (self fitsInSize: 8)
        ifFalse: [ Error signal: self asString, ' exceeds quadword (64bit) range' ].

    (self isSigned and: [ value < 0 ]) ifTrue: [ ^ (1<<64) + value ].
    
    ^ value
!

asWord
    "answer the 16bit word representing a value"
    (self fitsInSize: 2)
        ifFalse: [ Error signal: self asString, ' value exceeds word (16bit) range' ].

    (self isSigned and: [ value < 0 ]) ifTrue: [ ^ (1<<16) + value ].
    
    ^ value
!

ptr

    "turn receiver into a memory operand with absolute address == receiver"
    
    ^ AJMem new displacement: self
! !

!AJImmediate methodsFor:'emitting code'!

emitUsing: emitter size: aSize

    label ifNotNil: [
        "this will set the label offset"
        emitter setLabelPosition: label. 
    ].

    aSize = 1 ifTrue: [ ^ emitter emitByte: self asByte ].
    aSize = 2 ifTrue: [ ^ emitter emitWord: self asWord ].
    aSize = 4 ifTrue: [ ^ emitter emitDWord: self asDWord ].
    aSize = 8 ifTrue: [ ^ emitter emitQWord: self asQWord ].
    
    self error: aSize asString, 'bytes is an invalid immediate value size'
! !

!AJImmediate methodsFor:'initialize-release'!

initialize
    value := 0.
    isUnsigned := false.
! !

!AJImmediate methodsFor:'printing'!

printOn: aStream
    aStream nextPut: $(.

    self printAnnotationOn: aStream.
      
    value > 1000000 
        ifTrue: [ aStream nextPutAll: value hex]
        ifFalse: [ aStream print: value].

    aStream space.
        
    aStream nextPut: (
        self isSigned ifTrue: [ $i ] ifFalse: [ $u ]).

    size ifNotNil: [ aStream print: size].
    
    aStream nextPut: $).

    
! !

!AJImmediate methodsFor:'testing'!

fitsInSize: aSize
    | maxSize |
    maxSize := 1 << (aSize * 8).

    self isUnsigned 
        ifTrue: [ ^ maxSize > value ].

    value < 0 
        ifTrue: [ ^ 0 - value <= (maxSize >> 1) ].
        
    ^ value < (maxSize>>1)
!

isImm
    ^ true
!

isInt32
      ^ value >= -2147483648 and: [ value <= 2147483647 ]
!

isInt8
    ^ size ifNil:  [ self fitsInSize: 1 ]
        ifNotNil: [ size = 1 ]
!

isSigned 
    ^ isUnsigned not
!

isUnsigned 
    ^ isUnsigned
!

isZero
    ^ value = 0
!

prohibitsRex 
    "Answer true if use of this operand requires that the instruction *not* have a REX prefix."

    ^ false
!

requiresRex
    "Answer true if use of this operand requires that the instruction have a REX prefix."

    ^ false
! !