asm/AJInstruction.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 15 Jun 2016 23:46:29 +0100
changeset 23 d2d9a2d4d6bf
parent 17 54798ae989cc
permissions -rw-r--r--
Added README, licenses and copyright notices.

"
    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 }"

Object subclass:#AJInstruction
	instanceVariableNames:'name operands machineCode position next annotation level'
	classVariableNames:''
	poolDictionaries:''
	category:'AsmJit-Instructions'
!

!AJInstruction 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.

"
! !

!AJInstruction class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!AJInstruction methodsFor:'accessing'!

annotation
    ^ annotation
!

annotation: anObject
    annotation := anObject
!

extractLabels: aBlock

    operands ifNotNil: [ operands do: [:each | each extractLabels: aBlock ]]
!

increaseLevel: num
    level := level + num
!

insert: anInstructions

    | n |
    self halt.
    n := next.
    next := anInstructions.
    anInstructions do: [:each | each increaseLevel: level ].
    anInstructions last next: n
!

instructionName 
    ^ name
!

level
    ^ level
!

level: aLevel
    level := aLevel 
!

machineCodeSize
    ^ machineCode ifNil: [ 0 ] ifNotNil: [ machineCode size ]
!

name
    ^ name
        ifNil: ['undefined']
!

name: anObject
    name := anObject
!

next
    ^ next
!

next: anObject
    next := anObject
!

operands
    ^ operands
!

operands: anObject
    operands := anObject
!

position
    ^ position
!

position: anObject
    position := anObject
! !

!AJInstruction methodsFor:'emitting code'!

emitCode: asm
    machineCode := #[]
!

emitCodeAtOffset: offset assembler: asm

    position := offset.
    self emitCode: asm.
    next ifNotNil: [ next emitCodeAtOffset: offset + self machineCodeSize assembler: asm ].
! !

!AJInstruction methodsFor:'function calls'!

prepareCallAlignments
    "do nothing"
! !

!AJInstruction methodsFor:'helpers'!

checkOperandsForConflict
    "Subclasses may signal an error here."
!

find: aByteString 
    self shouldBeImplemented.
! !

!AJInstruction methodsFor:'initialize-release'!

initialize
    level := 0
! !

!AJInstruction methodsFor:'iterating'!

do: aBlock
    "evaluate all instructions for the list"
    | nn |
    nn := self.
    [ nn notNil ] whileTrue: [
        aBlock value: nn.
        nn := nn next.
    ].
!

last
    "answer the last instruction in the list"
    | nn l |
    nn := self.
    [ (l := nn next) notNil ] whileTrue: [ nn := l ].
    ^ nn
! !

!AJInstruction methodsFor:'manipulating'!

insert: newInstruction before: anInstruction
    
    "replace a single instruction with one or more other instructions"
    | instr  anext |
    
    anInstruction == self ifTrue: [
        newInstruction last next: self.
        ^ newInstruction ].
    
    instr := self.
    [ (anext := instr next) notNil and: [ anext ~~ anInstruction ]] whileTrue: [ instr := anext ].

    instr next ifNotNil: [
        newInstruction do: [:each | 
            each increaseLevel: instr level  
            ].
        newInstruction last next: instr next.
        instr next: newInstruction ].  
!

replace: anInstruction with: otherInstructions
    
    "replace a single instruction with one or more other instructions"
    | instr |
    
    anInstruction == self ifTrue: [
        otherInstructions last next: self next.
        ^ otherInstructions ].
    
    instr := self.
    [ instr notNil and: [instr next ~~ anInstruction ]] whileTrue: [ instr := instr next ].
    instr notNil ifTrue: [
        otherInstructions last next: instr next next.
        instr next: otherInstructions 
        ].  
! !

!AJInstruction methodsFor:'printing'!

printAnnotationOn: aStream 
    annotation
        ifNil: [^ self].
    aStream nextPut: $";
         nextPutAll: annotation asString;
         nextPut: $";
         cr.
    self printIndentOn: aStream
!

printIndentOn: aStream 
    level ifNil: [ ^ self ].
    level timesRepeat: [ aStream nextPutAll: '|   ']
!

printListOn: aStream
    
    self printIndentOn: aStream.
    self printSelfOn: aStream.
    
    next ifNotNil: [
        aStream cr.
        next printListOn: aStream 
        ]
!

printMachineCodeOn: aStream 
    (machineCode isNil
            or: [machineCode isEmpty])
        ifTrue: [^ self].
    aStream padColumn: 65;
         nextPutAll: '#['.
    machineCode 
        do: [ :byte | 
            byte printOn: aStream base: 16 length: 2 padded: true ]
        separatedBy: [ aStream space ].
    aStream nextPut: $]
!

printOn: aStream  
"[ ^self ] value."

    self printListOn: aStream asLineStream
!

printOperandsOn: aStream 
    (operands notNil
            and: [operands isEmpty not])
        ifTrue: [aStream space; nextPut: $(.
            operands
                do: [ :operand | operand printAsOperandOn: aStream]
                separatedBy: [aStream space].
            aStream nextPut: $)]
!

printSelfOn: aStream 
    self printAnnotationOn: aStream.
    aStream nextPutAll: (self name ). "padRightTo: 4)."
    self printOperandsOn: aStream.
    self printMachineCodeOn: aStream
!

printStringLimitedTo: aNumber
    ^ String streamContents: [:s | self printOn: s] 
!

storeOn: aStream
    "store machine code to binary stream"
    machineCode ifNotNil: [
        aStream nextPutAll: machineCode   
        ]
! !

!AJInstruction methodsFor:'testing'!

hasLabel
    self shouldBeImplemented.
!

isLabelUsed: anAJJumpLabel
    ^ false
! !

!AJInstruction methodsFor:'visitor'!

accept: anObject
    self subclassResponsibility
!

processTempsWith: anObject
    "do nothing"
!

setPrologue: anInstrucitons
    "do nothing"
! !