LLVMIRBuilder.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 17 Aug 2015 08:53:26 +0100
changeset 33 feabf14b6c1d
parent 28 97013ae2abae
child 38 52be9bfdf7e1
permissions -rw-r--r--
Initial support for generating (DWARF) debug info. The current API is really horrible and clumsy, but it's more or less 1-to-1 mapping to LLVM API. LLVMExamples>>example7_factorial_with_debug_info shows how to use it. The debug info API (at the Smalltalk level) will be refactored to provide easier-to-use interface.

"
    Copyright (C) 2015-now Jan Vrany

    This code is not an open-source (yet). You may use this code
    for your own experiments and projects, given that:

    * all modification to the code will be sent to the
      original author for inclusion in future releases
    * this is not used in any commercial software

    This license is provisional and may (will) change in
    a future.
"
"{ Package: 'jv:llvm_s' }"

"{ NameSpace: Smalltalk }"

LLVMDisposableObject subclass:#LLVMIRBuilder
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:'LLVMIntPredicate LLVMRealPredicate LLVMTypeKind'
	category:'LLVM-S-Core'
!

!LLVMIRBuilder class methodsFor:'documentation'!

copyright
"
    Copyright (C) 2015-now Jan Vrany

    This code is not an open-source (yet). You may use this code
    for your own experiments and projects, given that:

    * all modification to the code will be sent to the
      original author for inclusion in future releases
    * this is not used in any commercial software

    This license is provisional and may (will) change in
    a future.
"
! !

!LLVMIRBuilder class methodsFor:'instance creation'!

new
    ^ LLVM CreateBuilder

    "Created: / 07-07-2015 / 22:38:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMIRBuilder class methodsFor:'generators'!

instructions
    ^ #(
        add:to: (isIntegerOrVector isIntegerOrVector)
        lsrh:by: (isIntegerOrVector isIntegerOrVector)
    )

    "Created: / 11-07-2015 / 13:05:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMIRBuilder methodsFor:'accessing'!

block: anLLVMBasicBlock
    "Sets the 'current' basic block to `anLLVMBasicBlock` and
     position to it's end so that instructions will be generated
     at the end of the block."

    ^ self positionAtEnd: anLLVMBasicBlock

    "Created: / 10-08-2015 / 09:03:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

line: line column: column scope: scope
    "Sets the current location in original source (i.e., on source being
     translated to LLVM IR). This information is used generate debug information."

    ^ self line: line column: column scope: scope inlinedAt: nil

    "Created: / 15-08-2015 / 21:26:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

line: line column: column scope: scope inlinedAt: inlinedScope
    "Sets the current location in original source (i.e., on source being
     translated to LLVM IR). This information is used generate debug information."

    self assertIsIntegerUnsigned: line.
    self assertIsIntegerUnsigned: column.
    self assertIsMetadata: scope. 
    inlinedScope notNil ifTrue:[  
    self assertIsMetadata: inlinedScope.  
    ].

    LLVMCEXT SetCurrentDebugLocation2: self  _: line _: column _: scope _: inlinedScope

    "Created: / 15-08-2015 / 21:26:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

location
    "Return current location as LLVMMetadata."

    ^ LLVMCEXT GetCurrentDebugLocation2: self

    "Created: / 15-08-2015 / 23:52:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMIRBuilder methodsFor:'initialization & release'!

dispose
    ^ LLVM DisposeBuilder: self.

    "Modified (comment): / 08-07-2015 / 22:39:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMIRBuilder methodsFor:'instructions - aggregates'!

extractvalue: value at: index
    ^ self extractvalue: value at: index as: ''

    "Created: / 10-08-2015 / 17:38:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

extractvalue: value at: index as: name


    self assertIsValue: value.
    self assert: ((value type kind == LLVMStructTypeKind) or:[ value type kind == LLVMArrayTypeKind ]) message: 'value is not a struct or an array'.
    self assert: index isInteger message: 'index is not an integer'.

    ^ LLVM BuildExtractValue: self _: value _: index _: name.


    "Created: / 10-08-2015 / 17:39:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMIRBuilder methodsFor:'instructions - binary'!

add:value1 _:value2 
    ^ self add:value1 _:value2 as:''

    "Created: / 07-07-2015 / 22:52:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 10-08-2015 / 09:42:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

add:value1 _:value2 as:name 
    self assertIsIntegerOrIntegerVectorValue: value1.  
    self assertIsIntegerOrIntegerVectorValue: value2.
    self assertIsValueOfSameType: value1  as: value2. 
    self assertIsString: name.  

    ^ LLVM BuildAdd:self _:value1 _:value2 _:name

    "Created: / 07-07-2015 / 22:52:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 10-08-2015 / 09:41:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

and:value1 _:value2 
    ^ self and:value1 _:value2 as:''

    "Created: / 07-08-2015 / 16:51:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 07-08-2015 / 17:56:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

and:value1 _:value2 as: name
    self assert: (value1 isKindOf: LLVMValue).
    self assert: value1 isIntegerOrIntegerVectorValue.
    self assert: (value2 isKindOf: LLVMValue).
    self assert: value2 isIntegerOrIntegerVectorValue.
    self assert: (name isSingleByteString).
    ^LLVM BuildAnd: self  _: value1 _: value2 _: name

    "Created: / 07-08-2015 / 17:56:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

ashr:value1 _:value2 
    ^ self 
            ashr:value1
            _:value2
            as:''

    "Created: / 11-07-2015 / 16:46:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

ashr:value1 _:value2 as:name 
    self assert:(value1 isKindOf:LLVMValue).
    self assert:value1 isIntegerOrIntegerVectorValue.
    self assert:(value2 isKindOf:LLVMValue).
    self assert:value2 isIntegerOrIntegerVectorValue.
    self assert:(name isSingleByteString).
    ^ LLVM 
        BuildAShr:self
        _:value1
        _:value2
        _:name

    "Created: / 11-07-2015 / 16:46:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

lshr:value1 _:value2 
    ^ self 
            lshr:value1
            _:value2
            as:''

    "Created: / 11-07-2015 / 13:02:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

lshr:value1 _:value2 as:name 
    self assert:(value1 isKindOf:LLVMValue).
    self assert:value1 isIntegerOrIntegerVectorValue.
    self assert:(value2 isKindOf:LLVMValue).
    self assert:value2 isIntegerOrIntegerVectorValue.
    self assert:(name isSingleByteString).
    ^ LLVM 
        BuildLShr:self
        _:value1
        _:value2
        _:name

    "Created: / 11-07-2015 / 14:49:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

mul:value1 _:value2 
    ^ self mul:value1 _:value2 as:''

    "Created: / 10-08-2015 / 09:42:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

mul:value1 _:value2 as:name 
    self assertIsIntegerOrIntegerVectorValue: value1.  
    self assertIsIntegerOrIntegerVectorValue: value2.
    self assertIsValueOfSameType: value1  as: value2. 
    self assertIsString: name.  

    ^ LLVM BuildMul:self _:value1 _:value2 _:name

    "Created: / 10-08-2015 / 09:41:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

or:value1 _:value2 
    ^ self 
            or:value1
            _:value2
            as:''

    "Created: / 11-07-2015 / 17:17:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

or:value1 _:value2 as:name 
    self assert:(value1 isKindOf:LLVMValue).
    self assert:value1 isIntegerOrIntegerVectorValue.
    self assert:(value2 isKindOf:LLVMValue).
    self assert:value2 isIntegerOrIntegerVectorValue.
    self assert:(name isSingleByteString).
    ^ LLVM 
        BuildOr:self
        _:value1
        _:value2
        _:name

    "Created: / 11-07-2015 / 17:16:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

shl:value1 _:value2
    ^ self shl:value1 _:value2 as:''

    "Created: / 11-07-2015 / 16:37:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 07-08-2015 / 17:58:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

shl:value1 _:value2 as:name 
    self assert:(value1 isKindOf:LLVMValue).
    self assert:value1 isIntegerOrIntegerVectorValue.
    self assert:(value2 isKindOf:LLVMValue).
    self assert:value2 isIntegerOrIntegerVectorValue.
    self assert:(name isSingleByteString).
    ^ LLVM 
        BuildShl:self
        _:value1
        _:value2
        _:name

    "Created: / 11-07-2015 / 16:37:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

sub:value1 _:value2 
    ^ self sub:value1 _:value2 as:''

    "Created: / 10-08-2015 / 09:42:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

sub:value1 _:value2 as:name 
    self assertIsIntegerOrIntegerVectorValue: value1.  
    self assertIsIntegerOrIntegerVectorValue: value2.
    self assertIsValueOfSameType: value1  as: value2. 
    self assertIsString: name.  

    ^ LLVM BuildSub:self _:value1 _:value2 _:name

    "Created: / 10-08-2015 / 09:42:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMIRBuilder methodsFor:'instructions - binary - compare'!

icmp:value1 _:value2 cond: cond
    ^ self icmp:value1 _:value2 cond: cond as: ''

    "Created: / 07-08-2015 / 18:39:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

icmp:value1 _:value2 cond: cond as: name

    self assertIsIntegerOrIntegerVectorValue:value1.      
    self assertIsIntegerOrIntegerVectorValue:value2.      
    self assertIsValueOfSameType:value1 as:value2.
    self assertIsString:name.      
    ^ LLVM BuildICmp: self  _: cond _:  value1 _: value2 _: name

    "Created: / 07-08-2015 / 18:18:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMIRBuilder methodsFor:'instructions - memory'!

alloca: type
    ^ self alloca: type as: ''

    "Created: / 10-08-2015 / 06:33:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

alloca: type as: name
    self assertIsType: type.
    self assertIsString: name.

    ^ LLVM BuildAlloca: self _: type _: name

    "Created: / 10-08-2015 / 06:26:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

gep: pointer at: integerOrArrayOfIntegers
    ^ self gep: pointer at: integerOrArrayOfIntegers as: ''

    "Created: / 05-08-2015 / 20:58:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

gep: pointer at: integerOrArrayOfIntegers as: name
    | indices |

    self assertIsValue: pointer ofKind: LLVMPointerTypeKind.  
    self assert: (integerOrArrayOfIntegers isInteger 
                    or:[ integerOrArrayOfIntegers isSequenceable and:[ integerOrArrayOfIntegers allSatisfy:[:e|e isInteger] ] ]).
    self assertIsString: name.  
    integerOrArrayOfIntegers isInteger ifTrue:[ 
        indices := LLVMObjectArray with: (LLVMConstant uint32: integerOrArrayOfIntegers)
    ] ifFalse:[ 
        indices := LLVMObjectArray new: integerOrArrayOfIntegers size.
        1 to: indices size do:[:i |
            indices at: i put: (LLVMConstant uint32: (integerOrArrayOfIntegers at: i)).
        ].
    ].
    ^ LLVM BuildGEP: self _: pointer _: indices _: indices size _: name.

    "Created: / 05-08-2015 / 20:58:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 10-08-2015 / 17:41:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

load: pointer
    ^ self load: pointer as: ''

    "Created: / 10-08-2015 / 06:45:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

load: pointer as: name
    self assertIsValue: pointer.
    self assertIsString: name.

    ^ LLVM BuildLoad: self _: pointer _: name

    "Created: / 10-08-2015 / 06:45:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

store: value _: pointer
    self assertIsValue: value.
    self assertIsValue: pointer.

    ^ LLVM BuildStore: self  _: value _: pointer

    "Created: / 10-08-2015 / 06:45:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMIRBuilder methodsFor:'instructions - other'!

call: function _: args
    ^ self call: function _: args as: ''.

    "Created: / 10-08-2015 / 18:53:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

call: function _: arguments as: name
    | argumentsArray argumentsSize |

    self assertIsFunctionValue: function.
    self assertIsValueArray: arguments.  
    self assertIsString: name.

    argumentsSize := arguments size.
    argumentsArray := arguments asLLVMObjectArray.
    ^ LLVM BuildCall: self _: function _: argumentsArray _: argumentsSize _: name

    "Created: / 10-08-2015 / 18:53:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMIRBuilder methodsFor:'instructions - terminators'!

br: target
    | targetAsValue  |

    targetAsValue := target asLLVMValue.

    self assertIsBasicBlockValue: targetAsValue.

    ^ LLVM BuildBr: self _: targetAsValue

    "Created: / 08-08-2015 / 02:59:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

if: cond then: then else: else
    ^ self if: cond then: then else: else as: ''

    "Created: / 08-08-2015 / 04:15:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

if: cond then: then else: else as: name
    | thenAsValue elseAsValue |

    thenAsValue := then asLLVMValue.
    elseAsValue := else asLLVMValue.

    self assertIsBasicBlockValue: thenAsValue.
    self assertIsBasicBlockValue: elseAsValue.
    self assertIsValue: cond ofType: LLVMType int1.

    ^ LLVM BuildCondBr: self _: cond _: thenAsValue _: elseAsValue

    "Created: / 07-08-2015 / 18:42:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-08-2015 / 02:58:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

ret
    ^ LLVM BuildRetVoid: self

    "Created: / 07-08-2015 / 18:14:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

ret:value1

    self assertIsValue: value1.
    ^ LLVM BuildRet: self _: value1

    "Created: / 07-07-2015 / 22:55:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-08-2015 / 03:11:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMIRBuilder methodsFor:'positioning'!

positionAtEnd: basicBlock
    LLVM PositionBuilderAtEnd: self  _: basicBlock

    "Created: / 07-07-2015 / 22:45:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMIRBuilder class methodsFor:'documentation'!

version_HG

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