LLVMIRBuilder.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 06 Jul 2016 22:40:59 +0100
changeset 71 ab03b0a6d037
parent 70 ced2a5c16e70
child 72 2c876bd46960
permissions -rw-r--r--
Implemented LLVMType>>sizeInBits/sizeInBytes for all data types ...i.e., also for structures, vectors and arrays.

"
    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:'block'
	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
    "Returns  the 'current' basic block as `anLLVMBasicBlock`"

    block isNil ifTrue:[  
        block := LLVM GetInsertBlock: self
    ].
    ^ block

    "Created: / 15-09-2015 / 11:49:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-09-2015 / 21:49:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

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

continue: anLLVMBasicBlock
    "Like block, but if current block has no terminator,
     add an unconditional jump to `anLLVMBasicBlock1` so
     exection continues there"

    | last |

    last := self block lastInstruction.
    (last isNil or:[ last isTerminatorInst not ]) ifTrue:[ 
        self br: anLLVMBasicBlock.
    ].
    ^ self positionAtEnd: anLLVMBasicBlock

    "Created: / 20-04-2016 / 22:00:27 / 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 assertIsIntegerOrIntegerVectorValue: value1.
    self assertIsValueOfSameType: value2 as: value1 .
    self assertIsString: name.  

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

    "Created: / 07-08-2015 / 17:56:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-09-2015 / 19:34:40 / 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 assertIsIntegerOrIntegerVectorValue: value1.
    self assertIsValueOfSameType: value2 as: value1 .
    self assertIsString: name.  

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

    "Created: / 11-07-2015 / 16:46:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-09-2015 / 19:34:48 / 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 assertIsIntegerOrIntegerVectorValue: value1.
    self assertIsValueOfSameType: value2 as: value1 .
    self assertIsString: name.  
    ^ LLVM 
        BuildLShr:self
        _:value1
        _:value2
        _:name

    "Created: / 11-07-2015 / 14:49:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-09-2015 / 19:34:52 / 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 assertIsIntegerOrIntegerVectorValue: value1.
    self assertIsValueOfSameType: value2 as: value1 .
    self assertIsString: name.  
    ^ LLVM 
        BuildOr:self
        _:value1
        _:value2
        _:name

    "Created: / 11-07-2015 / 17:16:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-09-2015 / 19:34:56 / 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 assertIsIntegerOrIntegerVectorValue: value1.
    self assertIsValueOfSameType: value2 as: value1 .
    self assertIsString: name.  
    ^ LLVM 
        BuildShl:self
        _:value1
        _:value2
        _:name

    "Created: / 11-07-2015 / 16:37:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-09-2015 / 19:35:01 / 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 - conversion'!

bitcast: value to: type
    ^ self bitcast: value to: type as: ''

    "Created: / 12-10-2015 / 18:37:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

bitcast: value to: type as: name
    self assertIsValue: value.
    self assertIsType: type.
    self assertIsString: name.
    ^ LLVM BuildBitCast: self  _: value _: type _: name.

    "Created: / 12-10-2015 / 18:36:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

int: value toPtr: type
    ^ self int: value toPtr: type as: ''

    "Created: / 11-02-2016 / 20:35:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

int: value toPtr: type as: name
    self assertIsIntegerValue: value.
    self assertIsType: type.
    self assert: type isPointerType description: 'Type is not an pointer type'.
    self assertIsString: name.    

    ^ LLVM BuildIntToPtr: self  _: value _: type _: name.

    "Created: / 11-02-2016 / 20:39:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

ptr: value toInt: type
    ^ self ptr: value toInt: type as: ''

    "Created: / 11-02-2016 / 20:40:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

ptr: value toInt: type as: name
    self assertIsValue: value.
    self assert: value type isPointerType description: 'Value is not of an pointer type'.
    self assertIsType: type.
    self assert: type isIntegerType description: 'Type is not an integer type'.
    self assertIsString: name.    

    ^ LLVM BuildPtrToInt: self  _: value _: type _: name.

    "Created: / 11-02-2016 / 20:40:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 12-02-2016 / 11:55:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMIRBuilder methodsFor:'instructions - intrinsics'!

memcpy: dst _: src _: size _: align _: volatile
    self assertIsValue: dst ofKind: LLVMPointerTypeKind.
    self assertIsValue: src ofKind: LLVMPointerTypeKind.
    self assertIsValue: size ofType: LLVMType int64.
    self assertIsInteger32Unsigned: align.
    self assertIsBoolean: volatile.

    ^ LLVMCEXT BuildMemCpy: self _: dst _: src _: size _: align _: volatile

    "Created: / 06-07-2016 / 09:45:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

memmove: ptr _: val _: size _: align _: volatile
    self assertIsValue: ptr ofKind: LLVMPointerTypeKind.
    self assertIsValue: val ofKind: LLVMIntegerTypeKind.
    self assertIsValue: size ofType: LLVMType int64.
    self assertIsInteger32Unsigned: align.
    self assertIsBoolean: volatile.

    ^ LLVMCEXT BuildMemMove: self _: ptr _: val _: size _: align _: volatile

    "Created: / 06-07-2016 / 09:45:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

memset: ptr _: val _: size _: align _: volatile
    self assertIsValue: ptr ofKind: LLVMPointerTypeKind.
    self assertIsValue: val ofKind: LLVMIntegerTypeKind.
    self assertIsValue: size ofType: LLVMType int64.
    self assertIsInteger32Unsigned: align.
    self assertIsBoolean: volatile.

    ^ LLVMCEXT BuildMemSet: self _: ptr _: val _: size _: align _: volatile

    "Created: / 06-07-2016 / 00:11:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 06-07-2016 / 09:41:35 / 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 at: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>"
!

phi: incoming
    ^ self phi: incoming as: ''

    "Created: / 21-04-2016 / 22:14:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

phi: incoming as: name
    "Create a PHI code from `incoming` values. An incoming value (i.e., an element
     of `incomming` array) must be either an instruction (i.e., a LLVMValue for an
     instruction) or an association LLVMBasicBlock -> LLVMValue."

    | insn type values blocks |
    self assert: (incoming isSequenceable and:[incoming isString not]) message: 'Incoming is not a sequenceable collection'.
    incoming do:[:assocOrValue |
        | t |
        assocOrValue isAssociation ifTrue:[ 
            self assert: assocOrValue key isLLVMBasicBlock message: 'Invalid incoming value - association key is not an LLVMBasicBlock'.
            self assert: assocOrValue value isLLVMValue message: 'Invalid incoming value - association value is not an LLVMValue'.
            t := assocOrValue value type.
        ] ifFalse:[ 
            self assert: assocOrValue isLLVMValue message: 'Invalid incoming value - value is not an LLVMValue'.
            self assert: assocOrValue isInstruction message: 'Invalid incoming value - value is not an instruction'.
            t := assocOrValue type.
        ].
        type isNil ifTrue:[ 
            type := t
        ] ifFalse:[ 
            self assert: type = t message: 'Invalid incoming values - types differ'.
        ].
    ].
    self assertIsString: name.

    values := (incoming collect:[ :assocOrValue | assocOrValue value]) asLLVMObjectArray.
    blocks := (incoming collect:[ :assocOrValue | assocOrValue isAssociation ifTrue:[assocOrValue key] ifFalse:[assocOrValue parent]]) asLLVMObjectArray.
    insn := LLVM BuildPhi: self _: incoming first value type _: name.
    LLVM AddIncoming: insn _: values _: blocks _: incoming size.
    ^ insn.

    "Created: / 21-04-2016 / 21:30:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-04-2016 / 09:08:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

select: condition then: then else: else
    ^ self select: condition then: then else: else as: ''

    "Created: / 09-02-2016 / 20:39:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

select: cond then: then else: else as: name

    self assertIsValue: cond ofType: LLVMType int1.
    self assertIsValueOfSameType: then  as: else. 
    self assertIsString: name.

    ^ LLVM BuildSelect: self  _: cond _: then _: else _: name.

    "Created: / 09-02-2016 / 20:40:11 / 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 
    ^ self if: cond then: then as: ''

    "Created: / 09-06-2016 / 01:13:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

if: cond then: then as: name
    ^ self if: cond then: then else: nil as: name

    "Created: / 09-06-2016 / 01:14:04 / 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 blockForm insn |

    self assertIsValue: cond ofType: LLVMType int1.
    blockForm := then isBlock and:[ else isNil or:[else isBlock] ].

    blockForm ifTrue: [
        | thenBlock  elseBlock joinBlock |

        thenBlock := block function addBasicBlock.
        elseBlock := block function addBasicBlock.
        thenAsValue := thenBlock asLLVMValue.
        elseAsValue := elseBlock asLLVMValue.
        insn := LLVM BuildCondBr: self _: cond _: thenAsValue _: elseAsValue.

        self block: thenBlock.
        then value.
        "/ Refetch thenBlock. It could be that the then-branch branched again
        "/ (nested ifs, loops) so the end of the then-branch is not the same
        "/ basic block as the beggining.
        thenBlock := self block.
        thenBlock isTerminated ifFalse:[ 
            joinBlock := block function addBasicBlock. 
            self br: joinBlock 
        ].

        self block: elseBlock.
        else value.
        "/ Refetch elseBlock. See above.
        elseBlock := self block.
        elseBlock isTerminated ifFalse:[ 
            joinBlock isNil ifTrue:[
                joinBlock := block function addBasicBlock. 
            ].
            self br: joinBlock 
        ].

        joinBlock notNil ifTrue:[
            self block: joinBlock.
        ].
    ] ifFalse:[
        thenAsValue := then asLLVMValue.
        elseAsValue := else asLLVMValue.
        self assertIsBasicBlockValue: thenAsValue.
        self assertIsBasicBlockValue: elseAsValue.
        insn := LLVM BuildCondBr: self _: cond _: thenAsValue _: elseAsValue.
    ].
    ^ insn.

    "Created: / 07-08-2015 / 18:42:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-06-2016 / 16:51:18 / 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: aLLVMBasicBlock
    self assertIsBasicBlock: aLLVMBasicBlock.
    LLVM PositionBuilderAtEnd: self  _: aLLVMBasicBlock.
    block := aLLVMBasicBlock

    "Created: / 07-07-2015 / 22:45:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 15-09-2015 / 18:16:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

positionBefore: anLLVMValue
    self assertIsInstruction: anLLVMValue.
    LLVM PositionBuilderBefore: self  _: anLLVMValue.
    block := nil.

    "Created: / 23-09-2015 / 21:28:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMIRBuilder class methodsFor:'documentation'!

version_HG

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