Renamed LLVMBuilder to LLVMIRBuilder
authorJan Vrany <jan.vrany@fit.cvut.cz>
Thu, 13 Aug 2015 06:19:28 +0100
changeset 28 97013ae2abae
parent 27 b26354bbff25
child 29 6ea02617c9ab
Renamed LLVMBuilder to LLVMIRBuilder to make naming consistent with coming LLVMDIBuilder
LLVMBasicBlock.st
LLVMBuilder.st
LLVMExamples.st
LLVMIRBuilder.st
LLVMOpcode.st
LLVMType.st
Make.proto
Make.spec
abbrev.stc
bc.mak
jv_llvm_s.st
libInit.cc
--- a/LLVMBasicBlock.st	Fri Aug 14 06:26:02 2015 +0100
+++ b/LLVMBasicBlock.st	Thu Aug 13 06:19:28 2015 +0100
@@ -44,11 +44,11 @@
 
 builder
     "Return a builder positioned at the end of the receiver"
-
+    
     | builder |
 
-    builder := LLVMBuilder new.
-    builder positionAtEnd: self.
+    builder := LLVMIRBuilder new.
+    builder positionAtEnd:self.
     ^ builder
 
     "Created: / 08-08-2015 / 03:25:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
--- a/LLVMBuilder.st	Fri Aug 14 06:26:02 2015 +0100
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,437 +0,0 @@
-"
-    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:#LLVMBuilder
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:'LLVMIntPredicate LLVMRealPredicate LLVMTypeKind'
-	category:'LLVM-S-Core'
-!
-
-!LLVMBuilder 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.
-"
-! !
-
-!LLVMBuilder class methodsFor:'instance creation'!
-
-new
-    ^ LLVM CreateBuilder
-
-    "Created: / 07-07-2015 / 22:38:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!LLVMBuilder 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>"
-! !
-
-!LLVMBuilder 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>"
-! !
-
-!LLVMBuilder methodsFor:'initialization & release'!
-
-dispose
-    ^ LLVM DisposeBuilder: self.
-
-    "Modified (comment): / 08-07-2015 / 22:39:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!LLVMBuilder 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>"
-! !
-
-!LLVMBuilder 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>"
-! !
-
-!LLVMBuilder 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>"
-! !
-
-!LLVMBuilder 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>"
-! !
-
-!LLVMBuilder 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>"
-! !
-
-!LLVMBuilder 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>"
-! !
-
-!LLVMBuilder methodsFor:'positioning'!
-
-positionAtEnd: basicBlock
-    LLVM PositionBuilderAtEnd: self  _: basicBlock
-
-    "Created: / 07-07-2015 / 22:45:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
--- a/LLVMExamples.st	Fri Aug 14 06:26:02 2015 +0100
+++ b/LLVMExamples.st	Thu Aug 13 06:19:28 2015 +0100
@@ -232,27 +232,25 @@
 
 example5_factorial
     "
-    S simple factorial using recursive algorithm.
-    No negative argument or overflow checks
-    "    
-
-    | module 
-      functionType function asm 
-      "Variables" result i 
-      "Blocks"    entry loop loopBody exit
-      jit externalFunction |
+     S simple factorial using recursive algorithm.
+     No negative argument or overflow checks"
+    
+    | module  functionType  function  asm  "Variables"
+    result  i  "Blocks"
+    entry  loop  loopBody  exit  jit  externalFunction |
 
-    module := LLVMModule newWithName: testSelector.
-
-    functionType := LLVMType function: { LLVMType intptr } returning: LLVMType intptr.
-    function := module addFunctionNamed: 'factorial' type: functionType.
-
-    asm := LLVMBuilder new.
+    module := LLVMModule newWithName:testSelector.
+    functionType := LLVMType function:{
+                    LLVMType intptr
+                }
+            returning:LLVMType intptr.
+    function := module addFunctionNamed:'factorial' type:functionType.
+    asm := LLVMIRBuilder new.
     entry := function entry.
-    loop  := function addBasicBlockNamed: 'loop'.
-    loopBody  := function addBasicBlockNamed: 'loopBody'.
-    exit  := function addBasicBlockNamed: 'exit'.
-
+    loop := function addBasicBlockNamed:'loop'.
+    loopBody := function addBasicBlockNamed:'loopBody'.
+    exit := function addBasicBlockNamed:'exit'.
+     
     "/ Generate function setup
     "/ 
     "/   function f(v) {
@@ -260,13 +258,14 @@
     "/     var i;
     "/     result = 0;
     "/     i := v;
-    asm block: entry.
-    result := asm alloca: LLVMType intptr as: 'result'.
-    i := asm alloca: LLVMType intptr as: 'i'.
-    asm store: (function parameterAt: 1)   _: i.
-    asm store: (function parameterAt: 1) _: result.
-    asm br: loop.
-
+    
+    asm block:entry.
+    result := asm alloca:LLVMType intptr as:'result'.
+    i := asm alloca:LLVMType intptr as:'i'.
+    asm store:(function parameterAt:1) _:i.
+    asm store:(function parameterAt:1) _:result.
+    asm br:loop.
+     
     "/ Generate loop that computes the factorial
     "/ 
     "/     while ( i > 1 ) {
@@ -278,61 +277,61 @@
     "/ fall-through instruction, so we have to introduce a block 
     "/ loop's body which will become a target for conditional's
     "/ then-branch.
-    asm block: loop.
-    asm if: (asm icmp: (asm load: i) _: (LLVMConstant sintptr:1) cond: LLVMIntSGT) then: loopBody else: exit.
-    asm block: loopBody.
-    asm store: (asm mul: (asm load: result) _: (asm load: i)) _: result.
-    asm store: (asm sub: (asm load: i) _: (LLVMConstant sintptr:1)) _: i.
-    asm br: loop.
-
+    
+    asm block:loop.
+    asm 
+        if:(asm 
+                icmp:(asm load:i)
+                _:(LLVMConstant sintptr:1)
+                cond:LLVMIntSGT)
+        then:loopBody
+        else:exit.
+    asm block:loopBody.
+    asm store:(asm mul:(asm load:result) _:(asm load:i)) _:result.
+    asm store:(asm sub:(asm load:i) _:(LLVMConstant sintptr:1)) _:i.
+    asm br:loop.
+     
     "/ Generate return from function
     "/ 
     "/     return result;
     "/ 
-    asm block: exit.
-    asm ret: (asm load: result).
-
-    jit := LLVMExecutionEngine newForModule: module.
-    externalFunction := jit externalOfFunction: function.
-
-    self assert: (externalFunction callWith: 5) == 120.
-    self assert: (externalFunction callWith: 1) == 1.
+    
+    asm block:exit.
+    asm ret:(asm load:result).
+    jit := LLVMExecutionEngine newForModule:module.
+    externalFunction := jit externalOfFunction:function.
+    self assert:(externalFunction callWith:5) == 120.
+    self assert:(externalFunction callWith:1) == 1.
 
     "
-    LLVMExamples example3_cond
-    "
-
+     LLVMExamples example3_cond"
     "Created: / 10-08-2015 / 09:46:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 example5_factorial_with_overflow
     "
-    Simple factorial using recursive algorithm.
-    This one checks for overflow, if overflow happens,
-    return -1
-    "    
-
-    | module 
-      functionType function asm 
-      "Variables" result i 
-      "Blocks"    entry loop loopBody1 loopBody2 exit overflow
-      smulWithOverflow
-      smulWithOverflowValue
-      jit externalFunction |
+     Simple factorial using recursive algorithm.
+     This one checks for overflow, if overflow happens,
+     return -1"
+    
+    | module  functionType  function  asm  "Variables"
+    result  i  "Blocks"
+    entry  loop  loopBody1  loopBody2  exit  overflow  smulWithOverflow  smulWithOverflowValue  jit  externalFunction |
 
-    module := LLVMModule newWithName: testSelector.
-
-    functionType := LLVMType function: { LLVMType intptr } returning: LLVMType intptr.
-    function := module addFunctionNamed: 'factorial' type: functionType.
-
-    asm := LLVMBuilder new.
+    module := LLVMModule newWithName:testSelector.
+    functionType := LLVMType function:{
+                    LLVMType intptr
+                }
+            returning:LLVMType intptr.
+    function := module addFunctionNamed:'factorial' type:functionType.
+    asm := LLVMIRBuilder new.
     entry := function entry.
-    loop  := function addBasicBlockNamed: 'loop'.
-    loopBody1  := function addBasicBlockNamed: 'loopBody1'.
-    loopBody2  := function addBasicBlockNamed: 'loopBody2'.
-    exit  := function addBasicBlockNamed: 'exit'.
-    overflow  := function addBasicBlockNamed: 'overflow'.  
-
+    loop := function addBasicBlockNamed:'loop'.
+    loopBody1 := function addBasicBlockNamed:'loopBody1'.
+    loopBody2 := function addBasicBlockNamed:'loopBody2'.
+    exit := function addBasicBlockNamed:'exit'.
+    overflow := function addBasicBlockNamed:'overflow'.
+     
     "/ Generate function setup
     "/ 
     "/   function f(v) {
@@ -340,13 +339,14 @@
     "/     var i;
     "/     result = 0;
     "/     i := v;
-    asm block: entry.
-    result := asm alloca: LLVMType intptr as: 'result'.
-    i := asm alloca: LLVMType intptr as: 'i'.
-    asm store: (function parameterAt: 1)   _: i.
-    asm store: (function parameterAt: 1) _: result.
-    asm br: loop.
-
+    
+    asm block:entry.
+    result := asm alloca:LLVMType intptr as:'result'.
+    i := asm alloca:LLVMType intptr as:'i'.
+    asm store:(function parameterAt:1) _:i.
+    asm store:(function parameterAt:1) _:result.
+    asm br:loop.
+     
     "/ Generate loop that computes the factorial
     "/ 
     "/     while ( i > 1 ) {
@@ -355,44 +355,59 @@
     "/     }
     "/ 
     "/ First, get the llvm.smul.with.overflow intrinsic:
-    smulWithOverflow := module getIntrinsicNamed: 'llvm.smul.with.overflow' types: {  LLVMType intptr }.
-
+    
+    smulWithOverflow := module getIntrinsicNamed:'llvm.smul.with.overflow'
+            types:{
+                    LLVMType intptr
+                }.
+     
     "/ Now code the loop
-    asm block: loop.
-    asm if: (asm icmp: (asm load: i) _: (LLVMConstant sintptr:1) cond: LLVMIntSGT) then: loopBody1 else: exit.
-    asm block: loopBody1.
-    smulWithOverflowValue := asm call: smulWithOverflow _: { (asm load: result) . (asm load: i) }.
-    asm if: (asm extractvalue: smulWithOverflowValue at: 1) then: overflow else: loopBody2.
-    asm block: loopBody2.
-    asm store: (asm extractvalue: smulWithOverflowValue at: 0) _: result.
-    asm store: (asm sub: (asm load: i) _: (LLVMConstant sintptr:1)) _: i.
-    asm br: loop.
-
+    
+    asm block:loop.
+    asm 
+        if:(asm 
+                icmp:(asm load:i)
+                _:(LLVMConstant sintptr:1)
+                cond:LLVMIntSGT)
+        then:loopBody1
+        else:exit.
+    asm block:loopBody1.
+    smulWithOverflowValue := asm call:smulWithOverflow
+            _:{
+                    (asm load:result).
+                    (asm load:i)
+                }.
+    asm 
+        if:(asm extractvalue:smulWithOverflowValue at:1)
+        then:overflow
+        else:loopBody2.
+    asm block:loopBody2.
+    asm store:(asm extractvalue:smulWithOverflowValue at:0) _:result.
+    asm store:(asm sub:(asm load:i) _:(LLVMConstant sintptr:1)) _:i.
+    asm br:loop.
+     
     "/ Generate return from function
     "/ 
     "/     return result;
     "/ 
-    asm block: exit.
-    asm ret: (asm load: result).
-
+    
+    asm block:exit.
+    asm ret:(asm load:result).
+     
     "/ Generate overflow handler
     "/     overflow:
     "/     return -1;
     "/ 
-    asm block: overflow.
-    asm ret: (LLVMConstant sintptr: -1).  
     
-
-    jit := LLVMExecutionEngine newForModule: module.
-    externalFunction := jit externalOfFunction: function.
+    asm block:overflow.
+    asm ret:(LLVMConstant sintptr:-1).
+    jit := LLVMExecutionEngine newForModule:module.
+    externalFunction := jit externalOfFunction:function.
+    self assert:(externalFunction callWith:5) == 120.
+    self assert:(externalFunction callWith:1) == 1.
+    self assert:(externalFunction callWith:120) == -1.
 
-    self assert: (externalFunction callWith: 5)   ==  120.
-    self assert: (externalFunction callWith: 1)   ==  1.
-    self assert: (externalFunction callWith: 120) == -1.
-
-    "sly    LLVMExamples example3_cond
-    "
-
+    "sly    LLVMExamples example3_cond"
     "Created: / 10-08-2015 / 17:12:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 10-08-2015 / 18:58:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/LLVMIRBuilder.st	Thu Aug 13 06:19:28 2015 +0100
@@ -0,0 +1,437 @@
+"
+    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>"
+! !
+
+!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>"
+! !
+
--- a/LLVMOpcode.st	Fri Aug 14 06:26:02 2015 +0100
+++ b/LLVMOpcode.st	Thu Aug 13 06:19:28 2015 +0100
@@ -412,5 +412,12 @@
     ^LLVMZExt
 ! !
 
+!LLVMOpcode class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
 
 LLVMOpcode initialize!
--- a/LLVMType.st	Fri Aug 14 06:26:02 2015 +0100
+++ b/LLVMType.st	Thu Aug 13 06:19:28 2015 +0100
@@ -46,6 +46,7 @@
 initialize
     "Invoked at system start or when the class is dynamically loaded."
 
+    LLVMTypeKind initialize.
     KindToClassMapping := Dictionary withKeysAndValues: {
         LLVMHalfTypeKind .      LLVMTypeHalt .
         LLVMFloatTypeKind .     LLVMTypeFloat .
--- a/Make.proto	Fri Aug 14 06:26:02 2015 +0100
+++ b/Make.proto	Thu Aug 13 06:19:28 2015 +0100
@@ -166,10 +166,10 @@
 $(OUTDIR)LLVMTypeMismatchError.$(O) LLVMTypeMismatchError.$(H): LLVMTypeMismatchError.st $(INCLUDE_TOP)/jv/llvm_s/LLVMError.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMTypeError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMUse.$(O) LLVMUse.$(H): LLVMUse.st $(INCLUDE_TOP)/jv/llvm_s/LLVMObject.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalAddress.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMValue.$(O) LLVMValue.$(H): LLVMValue.st $(INCLUDE_TOP)/jv/llvm_s/LLVMObject.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalAddress.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)LLVMBuilder.$(O) LLVMBuilder.$(H): LLVMBuilder.st $(INCLUDE_TOP)/jv/llvm_s/LLVMDisposableObject.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMIntPredicate.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMObject.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMRealPredicate.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMTypeKind.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalAddress.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMExecutionEngine.$(O) LLVMExecutionEngine.$(H): LLVMExecutionEngine.st $(INCLUDE_TOP)/jv/llvm_s/LLVMDisposableObject.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMObject.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalAddress.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMFunction.$(O) LLVMFunction.$(H): LLVMFunction.st $(INCLUDE_TOP)/jv/llvm_s/LLVMObject.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMValue.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalAddress.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMGenericValue.$(O) LLVMGenericValue.$(H): LLVMGenericValue.st $(INCLUDE_TOP)/jv/llvm_s/LLVMDisposableObject.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMObject.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalAddress.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)LLVMIRBuilder.$(O) LLVMIRBuilder.$(H): LLVMIRBuilder.st $(INCLUDE_TOP)/jv/llvm_s/LLVMDisposableObject.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMIntPredicate.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMObject.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMRealPredicate.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMTypeKind.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalAddress.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMMCJITMemoryManager.$(O) LLVMMCJITMemoryManager.$(H): LLVMMCJITMemoryManager.st $(INCLUDE_TOP)/jv/llvm_s/LLVMDisposableObject.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMObject.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalAddress.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMModule.$(O) LLVMModule.$(H): LLVMModule.st $(INCLUDE_TOP)/jv/llvm_s/LLVMDisposableObject.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMObject.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMTypeKind.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalAddress.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMModuleProvider.$(O) LLVMModuleProvider.$(H): LLVMModuleProvider.st $(INCLUDE_TOP)/jv/llvm_s/LLVMDisposableObject.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMObject.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalAddress.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/Make.spec	Fri Aug 14 06:26:02 2015 +0100
+++ b/Make.spec	Thu Aug 13 06:19:28 2015 +0100
@@ -87,10 +87,10 @@
 	LLVMTypeMismatchError \
 	LLVMUse \
 	LLVMValue \
-	LLVMBuilder \
 	LLVMExecutionEngine \
 	LLVMFunction \
 	LLVMGenericValue \
+	LLVMIRBuilder \
 	LLVMMCJITMemoryManager \
 	LLVMModule \
 	LLVMModuleProvider \
@@ -155,10 +155,10 @@
     $(OUTDIR_SLASH)LLVMTypeMismatchError.$(O) \
     $(OUTDIR_SLASH)LLVMUse.$(O) \
     $(OUTDIR_SLASH)LLVMValue.$(O) \
-    $(OUTDIR_SLASH)LLVMBuilder.$(O) \
     $(OUTDIR_SLASH)LLVMExecutionEngine.$(O) \
     $(OUTDIR_SLASH)LLVMFunction.$(O) \
     $(OUTDIR_SLASH)LLVMGenericValue.$(O) \
+    $(OUTDIR_SLASH)LLVMIRBuilder.$(O) \
     $(OUTDIR_SLASH)LLVMMCJITMemoryManager.$(O) \
     $(OUTDIR_SLASH)LLVMModule.$(O) \
     $(OUTDIR_SLASH)LLVMModuleProvider.$(O) \
--- a/abbrev.stc	Fri Aug 14 06:26:02 2015 +0100
+++ b/abbrev.stc	Thu Aug 13 06:19:28 2015 +0100
@@ -38,7 +38,7 @@
 LLVMTypeMismatchError LLVMTypeMismatchError jv:llvm_s 'LLVM-S-Core-Exceptions' 1
 LLVMUse LLVMUse jv:llvm_s 'LLVM-S-Core' 0
 LLVMValue LLVMValue jv:llvm_s 'LLVM-S-Core' 0
-LLVMBuilder LLVMBuilder jv:llvm_s 'LLVM-S-Core' 0
+LLVMIRBuilder LLVMIRBuilder jv:llvm_s 'LLVM-S-Core' 0
 LLVMExecutionEngine LLVMExecutionEngine jv:llvm_s 'LLVM-S-Core' 0
 LLVMFunction LLVMFunction jv:llvm_s 'LLVM-S-Core' 0
 LLVMGenericValue LLVMGenericValue jv:llvm_s 'LLVM-S-Core' 0
--- a/bc.mak	Fri Aug 14 06:26:02 2015 +0100
+++ b/bc.mak	Thu Aug 13 06:19:28 2015 +0100
@@ -108,10 +108,10 @@
 $(OUTDIR)LLVMTypeMismatchError.$(O) LLVMTypeMismatchError.$(H): LLVMTypeMismatchError.st $(INCLUDE_TOP)\jv\llvm_s\LLVMError.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMTypeError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMUse.$(O) LLVMUse.$(H): LLVMUse.st $(INCLUDE_TOP)\jv\llvm_s\LLVMObject.$(H) $(INCLUDE_TOP)\stx\libbasic\ExternalAddress.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMValue.$(O) LLVMValue.$(H): LLVMValue.st $(INCLUDE_TOP)\jv\llvm_s\LLVMObject.$(H) $(INCLUDE_TOP)\stx\libbasic\ExternalAddress.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)LLVMBuilder.$(O) LLVMBuilder.$(H): LLVMBuilder.st $(INCLUDE_TOP)\jv\llvm_s\LLVMDisposableObject.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMIntPredicate.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMObject.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMRealPredicate.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMTypeKind.$(H) $(INCLUDE_TOP)\stx\libbasic\ExternalAddress.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMExecutionEngine.$(O) LLVMExecutionEngine.$(H): LLVMExecutionEngine.st $(INCLUDE_TOP)\jv\llvm_s\LLVMDisposableObject.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMObject.$(H) $(INCLUDE_TOP)\stx\libbasic\ExternalAddress.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMFunction.$(O) LLVMFunction.$(H): LLVMFunction.st $(INCLUDE_TOP)\jv\llvm_s\LLVMObject.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMValue.$(H) $(INCLUDE_TOP)\stx\libbasic\ExternalAddress.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMGenericValue.$(O) LLVMGenericValue.$(H): LLVMGenericValue.st $(INCLUDE_TOP)\jv\llvm_s\LLVMDisposableObject.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMObject.$(H) $(INCLUDE_TOP)\stx\libbasic\ExternalAddress.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)LLVMIRBuilder.$(O) LLVMIRBuilder.$(H): LLVMIRBuilder.st $(INCLUDE_TOP)\jv\llvm_s\LLVMDisposableObject.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMIntPredicate.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMObject.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMRealPredicate.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMTypeKind.$(H) $(INCLUDE_TOP)\stx\libbasic\ExternalAddress.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMMCJITMemoryManager.$(O) LLVMMCJITMemoryManager.$(H): LLVMMCJITMemoryManager.st $(INCLUDE_TOP)\jv\llvm_s\LLVMDisposableObject.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMObject.$(H) $(INCLUDE_TOP)\stx\libbasic\ExternalAddress.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMModule.$(O) LLVMModule.$(H): LLVMModule.st $(INCLUDE_TOP)\jv\llvm_s\LLVMDisposableObject.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMObject.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMTypeKind.$(H) $(INCLUDE_TOP)\stx\libbasic\ExternalAddress.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)LLVMModuleProvider.$(O) LLVMModuleProvider.$(H): LLVMModuleProvider.st $(INCLUDE_TOP)\jv\llvm_s\LLVMDisposableObject.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMObject.$(H) $(INCLUDE_TOP)\stx\libbasic\ExternalAddress.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
--- a/jv_llvm_s.st	Fri Aug 14 06:26:02 2015 +0100
+++ b/jv_llvm_s.st	Thu Aug 13 06:19:28 2015 +0100
@@ -135,55 +135,16 @@
      Each entry in the list may be: a single class-name (symbol),
      or an array-literal consisting of class name and attributes.
      Attributes are: #autoload or #<os> where os is one of win32, unix,..."
-
-    ^ #(
-        "<className> or (<className> attributes...) in load order"
-        LLVM
-        LLVMAtomicOrdering
-        LLVMAtomicRMWBinOp
-        LLVMAttribute
-        LLVMByteOrdering
-        LLVMCEXT
-        LLVMCallConv
-        LLVMConfig
-        LLVMConstant
-        LLVMDLLStorageClass
-        LLVMDiagnosticSeverity
+    
+    ^ "<className> or (<className> attributes...) in load order" 
+     #(
+     #LLVM #LLVMAtomicOrdering #LLVMAtomicRMWBinOp #LLVMAttribute #LLVMByteOrdering #LLVMCEXT #LLVMCallConv #LLVMConfig #LLVMConstant #LLVMDLLStorageClass #LLVMDiagnosticSeverity #LLVMIntPredicate #LLVMLandingPadClauseTy #LLVMLinkage #LLVMObjectArray #LLVMOpcode #LLVMRealPredicate #LLVMThreadLocalMode #LLVMTypeKind #LLVMVerifierFailureAction #LLVMVisibility
         LLVMError
-        LLVMIntPredicate
-        LLVMLandingPadClauseTy
-        LLVMLinkage
-        LLVMObjectArray
-        LLVMOpcode
-        LLVMRealPredicate
-        LLVMThreadLocalMode
-        LLVMTypeKind
-        LLVMVerifierFailureAction
-        LLVMVisibility
-        #'jv_llvm_s'
-        (LLVMExamples autoload)
-        LLVMObject
+     #'jv_llvm_s'
+     #(LLVMExamples autoload)
+     #LLVMObject #LLVMBasicBlock #LLVMContext #LLVMDiagnosticInfo #LLVMDisposableObject #LLVMMCJITCompilerOptions #LLVMPassRegistry #LLVMTargetLibraryInfo #LLVMType #LLVMUse #LLVMValue #LLVMIRBuilder #LLVMExecutionEngine #LLVMFunction #LLVMGenericValue #LLVMMCJITMemoryManager #LLVMModule #LLVMModuleProvider #LLVMPassManager #LLVMTargetData #LLVMStXMethod
         LLVMTypeError
-        LLVMBasicBlock
-        LLVMContext
-        LLVMDiagnosticInfo
-        LLVMDisposableObject
-        LLVMMCJITCompilerOptions
-        LLVMPassRegistry
-        LLVMTargetLibraryInfo
-        LLVMType
         LLVMTypeMismatchError
-        LLVMUse
-        LLVMValue
-        LLVMBuilder
-        LLVMExecutionEngine
-        LLVMFunction
-        LLVMGenericValue
-        LLVMMCJITMemoryManager
-        LLVMModule
-        LLVMModuleProvider
-        LLVMPassManager
-        LLVMTargetData
         LLVMTypeDouble
         LLVMTypeFP128
         LLVMTypeFloat
@@ -198,7 +159,6 @@
         LLVMTypeVoid
         #'LLVMTypeX86_FP80'
         #'LLVMTypeX86_MMX'
-        LLVMStXMethod
         LLVMTypeArray
         LLVMTypePointer
         LLVMTypeVector
--- a/libInit.cc	Fri Aug 14 06:26:02 2015 +0100
+++ b/libInit.cc	Thu Aug 13 06:19:28 2015 +0100
@@ -63,10 +63,10 @@
 _LLVMTypeMismatchError_Init(pass,__pRT__,snd);
 _LLVMUse_Init(pass,__pRT__,snd);
 _LLVMValue_Init(pass,__pRT__,snd);
-_LLVMBuilder_Init(pass,__pRT__,snd);
 _LLVMExecutionEngine_Init(pass,__pRT__,snd);
 _LLVMFunction_Init(pass,__pRT__,snd);
 _LLVMGenericValue_Init(pass,__pRT__,snd);
+_LLVMIRBuilder_Init(pass,__pRT__,snd);
 _LLVMMCJITMemoryManager_Init(pass,__pRT__,snd);
 _LLVMModule_Init(pass,__pRT__,snd);
 _LLVMModuleProvider_Init(pass,__pRT__,snd);