C1: Added context setup code.
authorJan Vrany <jan.vrany@fit.cvut.cz>
Wed, 20 Apr 2016 23:36:17 +0100
changeset 18 81ed8ce0852f
parent 17 54798ae989cc
child 26 8eb6716029aa
C1: Added context setup code.
c1/DragonFly__C1Compiler.st
c1/DragonFly__C1CompilerTests.st
c1/DragonFly__C1LLVMMTypes.st
c1/DragonFly__C1LLVMTypes.st
c1/Make.proto
c1/Make.spec
c1/abbrev.stc
c1/bc.mak
c1/bmake.bat
c1/jv_dragonfly_c1.st
c1/libInit.cc
c1/mingwmake.bat
c1/vcmake.bat
--- a/c1/DragonFly__C1Compiler.st	Fri Feb 12 11:51:14 2016 +0000
+++ b/c1/DragonFly__C1Compiler.st	Wed Apr 20 23:36:17 2016 +0100
@@ -3,9 +3,10 @@
 "{ NameSpace: DragonFly }"
 
 Object subclass:#C1Compiler
-	instanceVariableNames:'method module function asm prologue epilogue'
+	instanceVariableNames:'method module function asm prologue epilogue contextSetup context
+		stack'
 	classVariableNames:'SelectorSpecialCharMappingTable'
-	poolDictionaries:'DragonFly::C1LLVMMTypes LLVMIntPredicate VMData VMOffsets'
+	poolDictionaries:'DragonFly::C1LLVMTypes LLVMIntPredicate VMData VMOffsets'
 	category:'DragonFly-C1'
 !
 
@@ -81,6 +82,21 @@
     "Created: / 09-02-2016 / 08:44:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!C1Compiler methodsFor:'accessing'!
+
+functionSEND: nArgs
+    | f |
+
+    self assert: (nArgs between: 0 and:15).
+    f := module getFunctionNamed: '_SEND', nArgs printString.
+    f isNil ifTrue:[ 
+        f := module addFunctionNamed: '_SEND', nArgs printString type: (TyOBJFUNCs at: nArgs + 1).
+    ].
+    ^ f
+
+    "Created: / 20-04-2016 / 21:39:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !C1Compiler methodsFor:'compilation'!
 
 compile: aMethod
@@ -101,17 +117,22 @@
 !C1Compiler methodsFor:'private'!
 
 epilogue
-    self halt.
+    epilogue isNil ifTrue:[ 
+        epilogue := function addBasicBlockNamed: 'epilogue'.
+    ].
+    asm continue: epilogue.
+    asm ret: self loadReceiver
 
     "Created: / 15-04-2016 / 23:38:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-04-2016 / 22:12:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 prologue
     | classOfReceiver classInILC classCheckFailedBlock classCheckPassedBlock classCheck |
     prologue := function addBasicBlockNamed: 'prologue'.
     asm block: prologue.
-    classOfReceiver := self fetchClassOf: (function parameterAt: OBJFUNCArgIndexReceiver ).
-    classInILC := self fetchClassFromILC: (function parameterAt: OBJFUNCArgIndexILC ).
+    classOfReceiver := self loadClassOf:(function parameterAt:OBJFUNCArgIndexReceiver).
+    classInILC := self loadClassFromILC:(function parameterAt:OBJFUNCArgIndexILC).
     classCheckFailedBlock := function addBasicBlockNamed: 'prologue.class-check-failed'. 
     classCheckPassedBlock := function addBasicBlockNamed: 'prologue.class-check-passed'.
     classCheck := asm icmp: (asm ptr: classOfReceiver toInt: LLVMType intptr)
@@ -121,43 +142,98 @@
 
     "/ Class check failed, call _SENDX()"
     asm block: classCheckFailedBlock.
-
-
+    asm ret: (
+        asm call: (self functionSEND:method numArgs) _: { 
+            function parameterAt: OBJFUNCArgIndexReceiver.
+            function parameterAt: OBJFUNCArgIndexSelector.
+            function parameterAt: OBJFUNCArgIndexSearchClass.
+            function parameterAt: OBJFUNCArgIndexILC } , 
+            (1 to: method numArgs collect:[:i | function parameterAt: OBJFUNCArgIndexArgBase + i ])
+    ).
     "/ Classes match, continue.
     asm block: classCheckPassedBlock.
 
+    self contextSetup.
+
     "Created: / 09-02-2016 / 17:07:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 15-04-2016 / 23:45:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-04-2016 / 23:32:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
-!C1Compiler methodsFor:'private-fetch / store'!
-
-fetchClassFromILC: pIlc
-    self assert: pIlc type = TyInlineCachePtr.
+!C1Compiler methodsFor:'private-context setup'!
 
-    ^ asm load: (asm gep: pIlc at: { 0. TyInlineCacheIndexClass })
+contextSetup
+    contextSetup := function addBasicBlockNamed:'context-setup'.
+    asm continue:contextSetup.
+    context := asm alloca:(C1LLVMTypes 
+                    tyContext:(method numArgs + method numVars + method numTemps))
+            as:'__context'.
+    asm store:self loadReceiver
+        _:(asm gep:context at:{ 0 . TyContextFieldIndexReceiver }).
+    asm store:self loadSelector
+        _:(asm gep:context at:{ 0 . TyContextFieldIndexSelector }).
+    asm store:self loadSearchClass
+        _:(asm gep:context at:{ 0 . TyContextFieldIndexSearchClass }).
 
-    "Created: / 12-02-2016 / 13:19:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 15-04-2016 / 23:18:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 20-04-2016 / 23:12:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!C1Compiler methodsFor:'private-load / store'!
+
+loadClassFromILC:pIlc 
+    self assert:pIlc type = TyInlineCachePtr.
+    ^ asm load:(asm gep:pIlc at:{ 0 . TyInlineCacheIndexClass })
+             "Created: / 12-02-2016 / 13:19:19 / Jan Vrany <jan.vrany@fit.cvut.cz>" "Modified: / 15-04-2016 / 23:18:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-fetchClassOf:obj 
+loadClassOf:obj 
     ^ asm 
         select:(self isSmallIntegerObject:obj)
-        then: self fetchClassSmallInteger
-        else: (asm load: (asm gep:obj at: { 0 . TyInstanceIndexClass })).
+        then:self loadClassSmallInteger
+        else:(asm load:(asm gep:obj at:{ 0 . TyInstanceFieldIndexClass })).
 
     "Created: / 09-02-2016 / 17:25:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 15-04-2016 / 23:19:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-04-2016 / 21:45:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+loadClassSmallInteger
+    | addr |
+
+    addr := asm int:(LLVMConstant uintptr:ADDR_SmallInteger)
+            toPtr:TyOBJ pointer.
+    ^ asm load:addr.
+
+    "Created: / 12-02-2016 / 11:54:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+loadNil
+    ^ asm int: (LLVMConstant uintptr: 0) toPtr:TyOBJ pointer.
+
+    "Created: / 20-04-2016 / 22:08:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-fetchClassSmallInteger
-    | addr |
+loadReceiver
+    ^ context isNil 
+        ifTrue:[ function parameterAt: OBJFUNCArgIndexReceiver ]
+        ifFalse:[ asm load: (asm gep: context at:{ 0 . TyContextFieldIndexReceiver }) ]
+
+    "Created: / 20-04-2016 / 22:09:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-04-2016 / 23:25:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
 
-    addr := asm int: (LLVMConstant uintptr: ADDR_SmallInteger) toPtr: TyOBJ pointer.
-    ^ asm load: addr.
+loadSearchClass
+    ^ context isNil 
+        ifTrue:[ function parameterAt: OBJFUNCArgIndexSearchClass ]
+        ifFalse:[ asm load: (asm gep: context at:{ 0 . TyContextFieldIndexSearchClass }) ]
 
-    "Created: / 12-02-2016 / 11:54:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 20-04-2016 / 23:27:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+loadSelector
+    ^ context isNil 
+        ifTrue:[ function parameterAt: OBJFUNCArgIndexSelector ]
+        ifFalse:[ asm load: (asm gep: context at:{ 0 . TyContextFieldIndexSelector }) ]
+
+    "Created: / 20-04-2016 / 23:24:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !C1Compiler methodsFor:'private-testing'!
--- a/c1/DragonFly__C1CompilerTests.st	Fri Feb 12 11:51:14 2016 +0000
+++ b/c1/DragonFly__C1CompilerTests.st	Wed Apr 20 23:36:17 2016 +0100
@@ -5,60 +5,12 @@
 TestCase subclass:#C1CompilerTests
 	instanceVariableNames:''
 	classVariableNames:''
-	poolDictionaries:'DragonFly::C1LLVMMTypes LLVMIntPredicate VMData VMOffsets'
+	poolDictionaries:'DragonFly::C1LLVMTypes LLVMIntPredicate VMData VMOffsets'
 	category:'DragonFly-C1-Tests'
 !
 
 !C1CompilerTests methodsFor:'tests'!
 
-test_fetchClassOf
-    | compiler module function asm jit test |
-
-    compiler := C1Compiler new.
-    module := LLVMModule newWithName: testSelector.
-    function := module addFunctionNamed: 'test'
-                                   type: (LLVMType function: { TyOBJ } returning: TyOBJ).
-    asm := function builder.
-    compiler 
-        instVarNamed: #module put: module;
-        instVarNamed: #function put: function;
-        instVarNamed: #asm put: asm.
-
-    asm ret: (compiler fetchClassOf: (function parameterAt: 1)).
-
-    jit := LLVMExecutionEngine newForModule: module.  
-    test := jit externalOfFunction: function. 
-
-    self assert: (test callOWith: 1) == SmallInteger.
-    self assert: (test callOWith: self) == self class.
-    self assert: (test callOWith: 1.0) == 1.0 class.
-
-    "Created: / 12-02-2016 / 12:27:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-test_fetchClassSmallInteger
-    | compiler module function asm jit test |
-
-    compiler := C1Compiler new.
-    module := LLVMModule newWithName: testSelector.
-    function := module addFunctionNamed: 'test'
-                                   type: (LLVMType function: { } returning: TyOBJ).
-    asm := function builder.
-    compiler 
-        instVarNamed: #module put: module;
-        instVarNamed: #function put: function;
-        instVarNamed: #asm put: asm.
-
-    asm ret: (compiler fetchClassSmallInteger).
-
-    jit := LLVMExecutionEngine newForModule: module.  
-    test := jit externalOfFunction: function. 
-
-    self assert: (test callO) == SmallInteger.
-
-    "Created: / 12-02-2016 / 12:26:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
 test_isSmallIntegerObject
     | compiler module function asm jit test |
 
@@ -81,5 +33,49 @@
     self assert: (test callWith: self) == 0.
 
     "Created: / 12-02-2016 / 12:17:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+test_loadClassOf
+    | compiler  module  function  asm  jit  test |
+
+    compiler := C1Compiler new.
+    module := LLVMModule newWithName:testSelector.
+    function := module addFunctionNamed:'test'
+            type:(LLVMType function:{ TyOBJ } returning:TyOBJ).
+    asm := function builder.
+    compiler
+        instVarNamed:#module put:module;
+        instVarNamed:#function put:function;
+        instVarNamed:#asm put:asm.
+    asm ret:(compiler loadClassOf: compiler loadReceiver).
+    jit := LLVMExecutionEngine newForModule:module.
+    test := jit externalOfFunction:function.
+    self assert:(test callOWith:1) == SmallInteger.
+    self assert:(test callOWith:self) == self class.
+    self assert:(test callOWith:1.0) == 1.0 class.
+
+    "Created: / 12-02-2016 / 12:27:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-04-2016 / 22:23:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+test_loadClassSmallInteger
+    | compiler  module  function  asm  jit  test |
+
+    compiler := C1Compiler new.
+    module := LLVMModule newWithName:testSelector.
+    function := module addFunctionNamed:'test'
+            type:(LLVMType function:{} returning:TyOBJ).
+    asm := function builder.
+    compiler
+        instVarNamed:#module put:module;
+        instVarNamed:#function put:function;
+        instVarNamed:#asm put:asm.
+    asm ret:(compiler loadClassSmallInteger).
+    jit := LLVMExecutionEngine newForModule:module.
+    test := jit externalOfFunction:function.
+    self assert:(test callO) == SmallInteger.
+
+    "Created: / 12-02-2016 / 12:26:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-04-2016 / 22:20:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/c1/DragonFly__C1LLVMMTypes.st	Fri Feb 12 11:51:14 2016 +0000
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,206 +0,0 @@
-"{ Package: 'jv:dragonfly/c1' }"
-
-"{ NameSpace: DragonFly }"
-
-SharedPool subclass:#C1LLVMMTypes
-	instanceVariableNames:''
-	classVariableNames:'TyInstance TyInstanceFieldIndexClass TyInstanceFieldIndexSize
-		TyInstanceFieldIndexSpace TyInstanceFieldIndexFlags
-		TyInstanceFieldIndexAge TyInstanceFieldIndexHashLow TyOBJ
-		TyInlineCache TyInlineCacheIndexFunc TyInlineCacheIndexClass
-		TyInlineCacheIndexLineNo TyInlineCachePtr TyOBJFUNC TyOBJFUNCs'
-	poolDictionaries:''
-	category:'DragonFly-C1'
-!
-
-
-!C1LLVMMTypes class methodsFor:'initialization'!
-
-initialize
-    "Invoked at system start or when the class is dynamically loaded."
-
-    "/ please change as required (and remove this comment)
-
-    TyInstance := LLVMType named: '__instance'.
-    TyOBJ := TyInstance pointer.
-    TyInstance elementTypes: {
-        TyOBJ.                      "/ o_class
-        LLVMType int32.             "/ o_size
-        LLVMType int8.              "/ o_space
-        LLVMType int8.              "/ o_flags
-        LLVMType int8.              "/ o_age
-        LLVMType int8.              "/ o_hashLow
-    }.
-    TyInstanceFieldIndexClass := 0.
-    TyInstanceFieldIndexSize := 1.
-    TyInstanceFieldIndexSpace := 2.
-    TyInstanceFieldIndexFlags := 3.
-    TyInstanceFieldIndexAge := 4.
-    TyInstanceFieldIndexHashLow := 5.
-
-    TyInlineCache := LLVMType named: 'inlineCache'.
-    TyInlineCachePtr := TyInlineCache pointer.
-    TyOBJFUNC := LLVMType function: {
-        TyOBJ.                      "/ self
-        TyOBJ.                      "/ selector
-        TyOBJ.                      "/ searchClass or nil
-        TyInlineCachePtr .          "/ pIlc
-    } varargs: true returning: TyOBJ.
-
-    TyInlineCache elementTypes: {
-        TyOBJFUNC pointer .         "/ ilc_func
-        TyOBJ.                      "/ ilc_class
-        TyInlineCachePtr .          "/ ilc_link
-        TyOBJ .                     "/ ilc_lineNo
-        LLVMType char pointer .     "/ ilc_poly
-    }.
-    TyInlineCacheIndexFunc := 0.
-    TyInlineCacheIndexClass := 1.
-    TyInlineCacheIndexLineNo := 3.
-
-    TyOBJFUNCs := {
-        "/ 0 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-        } returning: TyOBJ .
-        "/ 1 args 
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ .
-        } returning: TyOBJ .
-        "/ 2 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ . TyOBJ .
-        } returning: TyOBJ .
-        "/ 3 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ . TyOBJ . TyOBJ .
-        } returning: TyOBJ .
-        "/ 4 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ . TyOBJ . TyOBJ . TyOBJ .
-        } returning: TyOBJ .
-        "/ 5 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
-        } returning: TyOBJ .
-        "/ 6 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
-        } returning: TyOBJ .
-        "/ 7 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
-        } returning: TyOBJ .
-        "/ 8 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . 
-        } returning: TyOBJ .
-        "/ 9 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . 
-        } returning: TyOBJ .
-        "/ 10 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . 
-        } returning: TyOBJ .
-        "/ 11 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . 
-        } returning: TyOBJ .
-        "/ 12 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . 
-        } returning: TyOBJ .
-        "/ 13 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . 
-        } returning: TyOBJ .
-        "/ 14 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
-        } returning: TyOBJ .
-        "/ 16 args
-        LLVMType function: {
-            TyOBJ.                      "/ self
-            TyOBJ.                      "/ selector
-            TyOBJ.                      "/ searchClass or nil
-            TyInlineCachePtr .          "/ pIlc
-            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . 
-        } returning: TyOBJ .
-    }
-
-    "Modified: / 20-04-2016 / 19:57:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!C1LLVMMTypes class methodsFor:'documentation'!
-
-version_HG
-
-    ^ '$Changeset: <not expanded> $'
-! !
-
-
-
-! !
-
-
-C1LLVMMTypes initialize!
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/c1/DragonFly__C1LLVMTypes.st	Wed Apr 20 23:36:17 2016 +0100
@@ -0,0 +1,261 @@
+"{ Package: 'jv:dragonfly/c1' }"
+
+"{ NameSpace: DragonFly }"
+
+SharedPool subclass:#C1LLVMTypes
+	instanceVariableNames:''
+	classVariableNames:'TyInstance TyInstanceFields TyInstanceFieldIndexClass
+		TyInstanceFieldIndexSize TyInstanceFieldIndexSpace
+		TyInstanceFieldIndexFlags TyInstanceFieldIndexAge
+		TyInstanceFieldIndexHashLow TyOBJ TyInlineCache
+		TyInlineCacheIndexFunc TyInlineCacheIndexClass
+		TyInlineCacheIndexLineNo TyInlineCachePtr TyOBJFUNC TyOBJFUNCs
+		TyContextFields TyContextFieldIndexStack TyContexts
+		TyContextFieldIndexFlags TyContextFieldIndexSenderS
+		TyContextFieldIndexHome TyContextFieldIndexReceiver
+		TyContextFieldIndexSelector TyContextFieldIndexSearchClass
+		TyContextFieldIndexMethod TyContextFieldIndexLineNr
+		TyContextFieldIndexRetvalTemp TyContextFieldIndexHandleS'
+	poolDictionaries:''
+	category:'DragonFly-C1'
+!
+
+
+!C1LLVMTypes class methodsFor:'initialization'!
+
+initialize
+    "Invoked at system start or when the class is dynamically loaded."
+
+    "/ please change as required (and remove this comment)
+
+    TyInstance := LLVMType named: '__instance'.
+    TyOBJ := TyInstance pointer.
+    TyInstanceFields := {
+        TyOBJ.                      "/ o_class
+        LLVMType int32.             "/ o_size
+        LLVMType int8.              "/ o_space
+        LLVMType int8.              "/ o_flags
+        LLVMType int8.              "/ o_age
+        LLVMType int8.              "/ o_hashLow
+    }.
+    TyInstance elementTypes: TyInstanceFields.
+
+    TyInstanceFieldIndexClass := 0.
+    TyInstanceFieldIndexSize := 1.
+    TyInstanceFieldIndexSpace := 2.
+    TyInstanceFieldIndexFlags := 3.
+    TyInstanceFieldIndexAge := 4.
+    TyInstanceFieldIndexHashLow := 5.
+
+    TyContextFields := TyInstanceFields , (Context instVarNames collect: [ :nm | nm last == $* ifTrue:[ LLVMType intptr pointer ] ifFalse:[ TyOBJ ] ]).
+    TyContextFieldIndexFlags := TyInstanceFields size - 1 + (Context instVarIndexFor: #flags).
+    TyContextFieldIndexSenderS  := TyInstanceFields size - 1 + (Context instVarIndexFor: #'sender*').   
+    TyContextFieldIndexHome  := TyInstanceFields size - 1 + (Context instVarIndexFor: #home).   
+    TyContextFieldIndexReceiver  := TyInstanceFields size - 1 + (Context instVarIndexFor: #receiver).   
+    TyContextFieldIndexSelector  := TyInstanceFields size - 1 + (Context instVarIndexFor: #selector).   
+    TyContextFieldIndexSearchClass  := TyInstanceFields size - 1 + (Context instVarIndexFor: #searchClass).   
+    TyContextFieldIndexMethod  := TyInstanceFields size - 1 + (Context instVarIndexFor: #method).   
+    TyContextFieldIndexLineNr  := TyInstanceFields size - 1 + (Context instVarIndexFor: #lineNr).   
+    TyContextFieldIndexRetvalTemp  := TyInstanceFields size - 1 + (Context instVarIndexFor: #retvalTemp).   
+    TyContextFieldIndexHandleS := TyInstanceFields size - 1 + (Context instVarIndexFor: #'handle*').   
+    TyContextFieldIndexStack := TyInstanceFields size + Context instSize.
+ 
+    TyContexts := #().
+
+    TyInlineCache := LLVMType named: 'inlineCache'.
+    TyInlineCachePtr := TyInlineCache pointer.
+    TyOBJFUNC := LLVMType function: {
+        TyOBJ.                      "/ self
+        TyOBJ.                      "/ selector
+        TyOBJ.                      "/ searchClass or nil
+        TyInlineCachePtr .          "/ pIlc
+    } varargs: true returning: TyOBJ.
+
+    TyInlineCache elementTypes: {
+        TyOBJFUNC pointer .         "/ ilc_func
+        TyOBJ.                      "/ ilc_class
+        TyInlineCachePtr .          "/ ilc_link
+        TyOBJ .                     "/ ilc_lineNo
+        LLVMType char pointer .     "/ ilc_poly
+    }.
+    TyInlineCacheIndexFunc := 0.
+    TyInlineCacheIndexClass := 1.
+    TyInlineCacheIndexLineNo := 3.
+
+    TyOBJFUNCs := {
+        "/ 0 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+        } returning: TyOBJ .
+        "/ 1 args 
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ .
+        } returning: TyOBJ .
+        "/ 2 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ . TyOBJ .
+        } returning: TyOBJ .
+        "/ 3 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ . TyOBJ . TyOBJ .
+        } returning: TyOBJ .
+        "/ 4 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ . TyOBJ . TyOBJ . TyOBJ .
+        } returning: TyOBJ .
+        "/ 5 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
+        } returning: TyOBJ .
+        "/ 6 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
+        } returning: TyOBJ .
+        "/ 7 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
+        } returning: TyOBJ .
+        "/ 8 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . 
+        } returning: TyOBJ .
+        "/ 9 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . 
+        } returning: TyOBJ .
+        "/ 10 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . 
+        } returning: TyOBJ .
+        "/ 11 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . 
+        } returning: TyOBJ .
+        "/ 12 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . 
+        } returning: TyOBJ .
+        "/ 13 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . 
+        } returning: TyOBJ .
+        "/ 14 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
+        } returning: TyOBJ .
+        "/ 16 args
+        LLVMType function: {
+            TyOBJ.                      "/ self
+            TyOBJ.                      "/ selector
+            TyOBJ.                      "/ searchClass or nil
+            TyInlineCachePtr .          "/ pIlc
+            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . 
+        } returning: TyOBJ .
+    }
+
+    "Modified: / 21-04-2016 / 08:34:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!C1LLVMTypes class methodsFor:'accessing'!
+
+tyContext: size
+    "Return a type for context with given `size`. Size should
+     be numArgs + numVars + numTemps"
+
+    | tyContext |
+
+    TyContexts size < (size + 1) ifTrue:[ 
+        | tmp |
+
+        tmp := Array new: size + 1.
+        tmp replaceFrom: 1 to: TyContexts size with: TyContexts.
+        TyContexts := tmp.
+    ].
+    tyContext := TyContexts at: size + 1.
+    tyContext isNil ifTrue:[ 
+        tyContext := LLVMType named: '__context' , size printString.
+        size == 0 ifTrue:[
+            tyContext elementTypes: TyContextFields
+        ] ifFalse:[    
+            tyContext elementTypes: (TyContextFields copyWith: (LLVMType arrayOf: TyOBJ size: size))
+        ].
+        TyContexts at: size + 1 put: tyContext.
+    ].
+    ^ tyContext
+
+    "
+    DragonFly::C1LLVMTypes tyContext: 3
+    "
+
+    "Created: / 20-04-2016 / 23:06:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (comment): / 21-04-2016 / 08:41:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!C1LLVMTypes class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
+
+C1LLVMTypes initialize!
--- a/c1/Make.proto	Fri Feb 12 11:51:14 2016 +0000
+++ b/c1/Make.proto	Wed Apr 20 23:36:17 2016 +0100
@@ -124,9 +124,9 @@
 
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
 $(OUTDIR)DragonFly__C1LLVMMCJITMemoryManager.$(O) DragonFly__C1LLVMMCJITMemoryManager.$(C) DragonFly__C1LLVMMCJITMemoryManager.$(H): DragonFly__C1LLVMMCJITMemoryManager.st $(INCLUDE_TOP)/jv/llvm_s/LLVMDisposableObject.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMMCJITMemoryManager.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMObject.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalAddress.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)DragonFly__C1LLVMMTypes.$(O) DragonFly__C1LLVMMTypes.$(C) DragonFly__C1LLVMMTypes.$(H): DragonFly__C1LLVMMTypes.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SharedPool.$(H) $(STCHDR)
+$(OUTDIR)DragonFly__C1LLVMTypes.$(O) DragonFly__C1LLVMTypes.$(C) DragonFly__C1LLVMTypes.$(H): DragonFly__C1LLVMTypes.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SharedPool.$(H) $(STCHDR)
 $(OUTDIR)jv_dragonfly_c1.$(O) jv_dragonfly_c1.$(C) jv_dragonfly_c1.$(H): jv_dragonfly_c1.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(STCHDR)
-$(OUTDIR)DragonFly__C1Compiler.$(O) DragonFly__C1Compiler.$(C) DragonFly__C1Compiler.$(H): DragonFly__C1Compiler.st $(INCLUDE_TOP)/jv/dragonfly/VMData.$(H) $(INCLUDE_TOP)/jv/dragonfly/VMOffsets.$(H) $(INCLUDE_TOP)/jv/dragonfly/c1/DragonFly__C1LLVMMTypes.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMIntPredicate.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)DragonFly__C1Compiler.$(O) DragonFly__C1Compiler.$(C) DragonFly__C1Compiler.$(H): DragonFly__C1Compiler.st $(INCLUDE_TOP)/jv/dragonfly/VMData.$(H) $(INCLUDE_TOP)/jv/dragonfly/VMOffsets.$(H) $(INCLUDE_TOP)/jv/dragonfly/c1/DragonFly__C1LLVMTypes.$(H) $(INCLUDE_TOP)/jv/llvm_s/LLVMIntPredicate.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
 
--- a/c1/Make.spec	Fri Feb 12 11:51:14 2016 +0000
+++ b/c1/Make.spec	Wed Apr 20 23:36:17 2016 +0100
@@ -52,7 +52,7 @@
 
 COMMON_CLASSES= \
 	DragonFly::C1LLVMMCJITMemoryManager \
-	DragonFly::C1LLVMMTypes \
+	DragonFly::C1LLVMTypes \
 	jv_dragonfly_c1 \
 	DragonFly::C1Compiler \
 
@@ -61,7 +61,7 @@
 
 COMMON_OBJS= \
     $(OUTDIR_SLASH)DragonFly__C1LLVMMCJITMemoryManager.$(O) \
-    $(OUTDIR_SLASH)DragonFly__C1LLVMMTypes.$(O) \
+    $(OUTDIR_SLASH)DragonFly__C1LLVMTypes.$(O) \
     $(OUTDIR_SLASH)jv_dragonfly_c1.$(O) \
     $(OUTDIR_SLASH)DragonFly__C1Compiler.$(O) \
 
--- a/c1/abbrev.stc	Fri Feb 12 11:51:14 2016 +0000
+++ b/c1/abbrev.stc	Wed Apr 20 23:36:17 2016 +0100
@@ -2,7 +2,7 @@
 # this file is needed for stc to be able to compile modules independently.
 # it provides information about a classes filename, category and especially namespace.
 DragonFly::C1LLVMMCJITMemoryManager DragonFly__C1LLVMMCJITMemoryManager jv:dragonfly/c1 'DragonFly-C1' 0
-DragonFly::C1LLVMMTypes DragonFly__C1LLVMMTypes jv:dragonfly/c1 'DragonFly-C1' 0
+DragonFly::C1LLVMTypes DragonFly__C1LLVMTypes jv:dragonfly/c1 'DragonFly-C1' 0
 jv_dragonfly_c1 jv_dragonfly_c1 jv:dragonfly/c1 '* Projects & Packages *' 3
 DragonFly::C1Compiler DragonFly__C1Compiler jv:dragonfly/c1 'DragonFly-C1' 0
 DragonFly::C1CompilerTests DragonFly__C1CompilerTests jv:dragonfly/c1 'DragonFly-C1-Tests' 1
--- a/c1/bc.mak	Fri Feb 12 11:51:14 2016 +0000
+++ b/c1/bc.mak	Wed Apr 20 23:36:17 2016 +0100
@@ -71,9 +71,9 @@
 
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
 $(OUTDIR)DragonFly__C1LLVMMCJITMemoryManager.$(O) DragonFly__C1LLVMMCJITMemoryManager.$(C) DragonFly__C1LLVMMCJITMemoryManager.$(H): DragonFly__C1LLVMMCJITMemoryManager.st $(INCLUDE_TOP)\jv\llvm_s\LLVMDisposableObject.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMMCJITMemoryManager.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMObject.$(H) $(INCLUDE_TOP)\stx\libbasic\ExternalAddress.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)DragonFly__C1LLVMMTypes.$(O) DragonFly__C1LLVMMTypes.$(C) DragonFly__C1LLVMMTypes.$(H): DragonFly__C1LLVMMTypes.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SharedPool.$(H) $(STCHDR)
+$(OUTDIR)DragonFly__C1LLVMTypes.$(O) DragonFly__C1LLVMTypes.$(C) DragonFly__C1LLVMTypes.$(H): DragonFly__C1LLVMTypes.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SharedPool.$(H) $(STCHDR)
 $(OUTDIR)jv_dragonfly_c1.$(O) jv_dragonfly_c1.$(C) jv_dragonfly_c1.$(H): jv_dragonfly_c1.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(STCHDR)
-$(OUTDIR)DragonFly__C1Compiler.$(O) DragonFly__C1Compiler.$(C) DragonFly__C1Compiler.$(H): DragonFly__C1Compiler.st $(INCLUDE_TOP)\jv\dragonfly\VMData.$(H) $(INCLUDE_TOP)\jv\dragonfly\VMOffsets.$(H) $(INCLUDE_TOP)\jv\dragonfly\c1\DragonFly__C1LLVMMTypes.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMIntPredicate.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)DragonFly__C1Compiler.$(O) DragonFly__C1Compiler.$(C) DragonFly__C1Compiler.$(H): DragonFly__C1Compiler.st $(INCLUDE_TOP)\jv\dragonfly\VMData.$(H) $(INCLUDE_TOP)\jv\dragonfly\VMOffsets.$(H) $(INCLUDE_TOP)\jv\dragonfly\c1\DragonFly__C1LLVMTypes.$(H) $(INCLUDE_TOP)\jv\llvm_s\LLVMIntPredicate.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
 
--- a/c1/bmake.bat	Fri Feb 12 11:51:14 2016 +0000
+++ b/c1/bmake.bat	Wed Apr 20 23:36:17 2016 +0100
@@ -10,6 +10,7 @@
 
 make.exe -N -f bc.mak  %DEFINES% %*
 
+@IF "%1" EQU "test" exit /b 0
 @IF "%1" EQU "exe" exit /b 0
 @IF "%1" EQU "setup" exit /b 0
 @IF "%1" EQU "pluginSetup" exit /b 0
--- a/c1/jv_dragonfly_c1.st	Fri Feb 12 11:51:14 2016 +0000
+++ b/c1/jv_dragonfly_c1.st	Wed Apr 20 23:36:17 2016 +0100
@@ -48,7 +48,7 @@
 
     ^ #(
     )
-!
+! !
 
 !jv_dragonfly_c1 class methodsFor:'description - contents'!
 
@@ -57,15 +57,12 @@
      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"
-        #'DragonFly::C1LLVMMCJITMemoryManager'
-        #'DragonFly::C1LLVMMTypes'
-        #'jv_dragonfly_c1'
-        #'DragonFly::C1Compiler'
-        (#'DragonFly::C1CompilerTests' autoload)
-    )
+    
+    ^ "<className> or (<className> attributes...) in load order" #( #'DragonFly::C1LLVMMCJITMemoryManager'
+     #'DragonFly::C1LLVMTypes'
+     #'jv_dragonfly_c1'
+     #'DragonFly::C1Compiler'
+     #(#'DragonFly::C1CompilerTests' autoload) )
 !
 
 extensionMethodNames
@@ -76,4 +73,9 @@
     )
 ! !
 
+!jv_dragonfly_c1 class methodsFor:'documentation'!
 
+version_HG
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/c1/libInit.cc	Fri Feb 12 11:51:14 2016 +0000
+++ b/c1/libInit.cc	Wed Apr 20 23:36:17 2016 +0100
@@ -17,7 +17,7 @@
 #endif
 
 extern void _DragonFly__C1LLVMMCJITMemoryManager_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _DragonFly__C1LLVMMTypes_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _DragonFly__C1LLVMTypes_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _jv_137dragonfly_137c1_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _DragonFly__C1Compiler_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 
@@ -34,7 +34,7 @@
 {
   __BEGIN_PACKAGE2__("libjv_dragonfly_c1", _libjv_dragonfly_c1_Init, "jv:dragonfly/c1");
     _DragonFly__C1LLVMMCJITMemoryManager_Init(pass,__pRT__,snd);
-    _DragonFly__C1LLVMMTypes_Init(pass,__pRT__,snd);
+    _DragonFly__C1LLVMTypes_Init(pass,__pRT__,snd);
     _jv_137dragonfly_137c1_Init(pass,__pRT__,snd);
     _DragonFly__C1Compiler_Init(pass,__pRT__,snd);
 
--- a/c1/mingwmake.bat	Fri Feb 12 11:51:14 2016 +0000
+++ b/c1/mingwmake.bat	Wed Apr 20 23:36:17 2016 +0100
@@ -13,6 +13,7 @@
 @popd
 make.exe -N -f bc.mak %DEFINES% %USEMINGW_ARG% %*
 
+@IF "%1" EQU "test" exit /b 0
 @IF "%1" EQU "exe" exit /b 0
 @IF "%1" EQU "setup" exit /b 0
 @IF "%1" EQU "pluginSetup" exit /b 0
--- a/c1/vcmake.bat	Fri Feb 12 11:51:14 2016 +0000
+++ b/c1/vcmake.bat	Wed Apr 20 23:36:17 2016 +0100
@@ -17,6 +17,7 @@
 
 make.exe -N -f bc.mak -DUSEVC=1 %DEFINES% %*
 
+@IF "%1" EQU "test" exit /b 0
 @IF "%1" EQU "exe" exit /b 0
 @IF "%1" EQU "setup" exit /b 0
 @IF "%1" EQU "pluginSetup" exit /b 0