First shot on #ifTrie:ifFalse: special form
authorJan Vrany <jan.vrany@fit.cvut.cz>
Wed, 16 Sep 2015 05:29:43 +0100
changeset 11 6d39860d0fdb
parent 10 2b9beeac547e
child 12 d716a8181fc1
First shot on #ifTrie:ifFalse: special form
compiler/Make.proto
compiler/Make.spec
compiler/TCompilerExamples.st
compiler/TCompilerPass.st
compiler/TConstantBinding.st
compiler/TDirectoryProvider.st
compiler/TFilesystemProvider.st
compiler/TFunctionBinding.st
compiler/TLLVMCodeGenerator.st
compiler/TMethodBinding.st
compiler/TSemanticAnalyser.st
compiler/TTypechecker.st
compiler/abbrev.stc
compiler/bc.mak
compiler/bmake.bat
compiler/jv_tea_compiler.st
compiler/libInit.cc
compiler/mingwmake.bat
compiler/vcmake.bat
--- a/compiler/Make.proto	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/Make.proto	Wed Sep 16 05:29:43 2015 +0100
@@ -154,7 +154,6 @@
 $(OUTDIR)TBlockType.$(O) TBlockType.$(H): TBlockType.st $(INCLUDE_TOP)/jv/tea/compiler/TType.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)TClassBinding.$(O) TClassBinding.$(H): TClassBinding.st $(INCLUDE_TOP)/jv/tea/compiler/TBinding.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)TCompilerPass.$(O) TCompilerPass.$(H): TCompilerPass.st $(INCLUDE_TOP)/jv/tea/compiler/TProgramNodeVisitor.$(H) $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/parser/RBProgramNodeVisitor.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)TDirectoryProvider.$(O) TDirectoryProvider.$(H): TDirectoryProvider.st $(INCLUDE_TOP)/jv/tea/compiler/TEnvironmentProvider.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)TEnvironment.$(O) TEnvironment.$(H): TEnvironment.st $(INCLUDE_TOP)/jv/tea/compiler/TNamespaceDefinition.$(H) $(INCLUDE_TOP)/stx/goodies/ring/RGAbstractContainer.$(H) $(INCLUDE_TOP)/stx/goodies/ring/RGContainer.$(H) $(INCLUDE_TOP)/stx/goodies/ring/RGDefinition.$(H) $(INCLUDE_TOP)/stx/goodies/ring/RGNamespace.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)TFilesystemProvider.$(O) TFilesystemProvider.$(H): TFilesystemProvider.st $(INCLUDE_TOP)/jv/tea/compiler/TEnvironmentProvider.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)TFunctionBinding.$(O) TFunctionBinding.$(H): TFunctionBinding.st $(INCLUDE_TOP)/jv/tea/compiler/TBinding.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/compiler/Make.spec	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/Make.spec	Wed Sep 16 05:29:43 2015 +0100
@@ -78,7 +78,6 @@
 	TBlockType \
 	TClassBinding \
 	TCompilerPass \
-	TDirectoryProvider \
 	TEnvironment \
 	TFilesystemProvider \
 	TFunctionBinding \
@@ -127,7 +126,6 @@
     $(OUTDIR_SLASH)TBlockType.$(O) \
     $(OUTDIR_SLASH)TClassBinding.$(O) \
     $(OUTDIR_SLASH)TCompilerPass.$(O) \
-    $(OUTDIR_SLASH)TDirectoryProvider.$(O) \
     $(OUTDIR_SLASH)TEnvironment.$(O) \
     $(OUTDIR_SLASH)TFilesystemProvider.$(O) \
     $(OUTDIR_SLASH)TFunctionBinding.$(O) \
--- a/compiler/TCompilerExamples.st	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/TCompilerExamples.st	Wed Sep 16 05:29:43 2015 +0100
@@ -22,29 +22,14 @@
 example_if
     | environment unit compiler|
 
-    environment := TNamespaceDefinition new.
+    environment := TEnvironment new.
     unit := TSourceReader read:'
-nil subclass: #tBoolean
-    category: ''tKernel-Builtins''
-!! 
-
-nil subclass: #tSIntegerW
-    category: ''tKernel-Builtins''
+nil subclass: #If
+    category: ''t-Examples''
 !!
-!!tSIntegerW methodsFor:''testing''!!
-= another <tSIntegerW> <^ tBoolean> 
-    %[:asm | 
-        asm ret: (asm add: self _: another)
-    %].
-    "Following code is actually used only in hosted environment"
-    ^ self + another
-!! !!
-
-!!tSIntegerW class methodsFor:''test''!!
-threePlusFour <^ tSIntegerW> 
-        ^ 3 + 4
-
-!! !!
+!!If class methodsFor:''examples''!!
+if <^ tSIntegerW> 
+        true ifTrue:[ ^ 1 ] ifFalse:[ ^ 0 ]
     '.
 
     compiler := TCompiler new.
@@ -55,7 +40,7 @@
     "
 
     "Created: / 14-09-2015 / 12:14:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 14-09-2015 / 14:27:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-09-2015 / 12:22:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 example_three_plus_four
--- a/compiler/TCompilerPass.st	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/TCompilerPass.st	Wed Sep 16 05:29:43 2015 +0100
@@ -118,9 +118,10 @@
 !
 
 acceptIfTrueIfFalseNode: node 
-    self acceptMessageNode: node
+    ^ self acceptMessageNode: node.
 
     "Created: / 14-09-2015 / 14:09:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-09-2015 / 11:59:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 acceptIfTrueNode: node
--- a/compiler/TConstantBinding.st	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/TConstantBinding.st	Wed Sep 16 05:29:43 2015 +0100
@@ -12,10 +12,10 @@
 
 !TConstantBinding class methodsFor:'instance creation'!
 
-value: anObject
-    ^ self new initializeWithValue: anObject
+value: anObject type: aTType
+    ^ self new initializeWithValue: anObject type: aTType
 
-    "Created: / 25-08-2015 / 23:14:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 15-09-2015 / 08:19:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !TConstantBinding methodsFor:'accessing'!
@@ -37,16 +37,11 @@
 
 !TConstantBinding methodsFor:'initialization'!
 
-initializeWithValue: anObject
+initializeWithValue: anObject type: aTType
     value := anObject.
-    value class == SmallInteger ifTrue:[ 
-        type := TSimpleType named: 'tSIntegerW'.
-        ^ self.
-    ].
-    self error: 'Unsupported constant'
+    type := aTType.
 
-    "Created: / 25-08-2015 / 23:15:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 14-09-2015 / 15:18:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 15-09-2015 / 08:19:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !TConstantBinding methodsFor:'testing'!
--- a/compiler/TDirectoryProvider.st	Mon Sep 14 16:27:00 2015 +0100
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,11 +0,0 @@
-"{ Package: 'jv:tea/compiler' }"
-
-"{ NameSpace: Smalltalk }"
-
-TEnvironmentProvider subclass:#TDirectoryProvider
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Languages-Tea-Compiler-Model-Provider'
-!
-
--- a/compiler/TFilesystemProvider.st	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/TFilesystemProvider.st	Wed Sep 16 05:29:43 2015 +0100
@@ -9,6 +9,7 @@
 	category:'Languages-Tea-Compiler-Model-Provider'
 !
 
+
 !TFilesystemProvider class methodsFor:'instance creation'!
 
 new
@@ -58,3 +59,10 @@
     "Modified: / 14-09-2015 / 15:06:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!TFilesystemProvider class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/TFunctionBinding.st	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/TFunctionBinding.st	Wed Sep 16 05:29:43 2015 +0100
@@ -26,6 +26,14 @@
     "Modified: / 02-09-2015 / 17:02:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!TFunctionBinding methodsFor:'converting'!
+
+asLLVMValueInModule: aLLVMModule
+    self subclassResponsibility
+
+    "Created: / 15-09-2015 / 07:03:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !TFunctionBinding methodsFor:'initialization'!
 
 parameterTypes: aCollection
--- a/compiler/TLLVMCodeGenerator.st	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/TLLVMCodeGenerator.st	Wed Sep 16 05:29:43 2015 +0100
@@ -117,6 +117,40 @@
     "Created: / 31-08-2015 / 10:14:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+acceptIfTrueIfFalseNode: node 
+    | condition thenBody thenBlock thenResult elseBody elseBlock elseResult joinBlock result |
+
+    condition := self visitNode: node receiver.  
+    thenBody  := node arguments first body.
+    thenBlock := function addBasicBlock.
+
+    elseBody  := node arguments second body.
+    elseBlock := function addBasicBlock.
+
+    asm if: condition then: thenBlock else: elseBlock.
+    "/ Code true-branch
+    asm block: thenBlock.
+    thenResult := self visitNode: thenBody.
+    thenResult isReturnInst ifFalse:[  
+        joinBlock notNil ifTrue:[ joinBlock function addBasicBlock ].
+        asm br: joinBlock.
+    ].
+
+    "/ Code false-branch
+    asm block: elseBlock.
+    elseResult := self visitNode: elseBody.
+    elseResult isReturnInst ifFalse:[  
+        joinBlock notNil ifTrue:[ joinBlock function addBasicBlock ].
+        asm br: joinBlock.
+    ].
+    joinBlock notNil ifTrue:[ 
+        asm block: joinBlock.
+    ].
+
+    "Created: / 15-09-2015 / 11:59:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 16-09-2015 / 05:28:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 acceptInlineAssemblyNode: aTInlineAssemblyNode
     | emitMethodNode emitMethod|
 
@@ -146,45 +180,26 @@
 !
 
 acceptMessageNode: aMessageNode
-    | receiver arguments methodName methodFunction |
+    | receiver arguments methodFunction |
 
     receiver := self visitNode: aMessageNode receiver.
-    receiver := self visitNode: aMessageNode receiver.
     arguments := aMessageNode arguments collect: [:argument | self visitNode: argument ].
-
-    methodName := self class llvmFunctionNameForClass: aMessageNode binding mclass clazz selector: aMessageNode selector.
-    methodFunction := context module getFunctionNamed: methodName.
+    methodFunction := aMessageNode binding asLLVMValueInModule: context module.  
 
     ^ asm call: methodFunction _: { receiver } , arguments
 
     "Created: / 31-08-2015 / 10:13:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 03-09-2015 / 07:13:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (format): / 15-09-2015 / 07:14:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 acceptMethodNode: aMethodNode 
-    | binding |
-
-    binding := aMethodNode binding.
-    binding mclass isMetaclass ifTrue:[
-        function := context module 
-                        addFunctionNamed: (self class llvmFunctionNameForClass: currentClass selector: currentMethod selector)
-                        type: (LLVMType 
-                                function:  (binding parameterTypes collect:[:t|t asLLVMTypeInModule: context module])
-                                returning: (binding returnType asLLVMTypeInModule: context module)).
-    ] ifFalse:[ 
-        function := context module 
-                        addFunctionNamed: (self class llvmFunctionNameForClass: currentClass selector: currentMethod selector)      
-                        type: (LLVMType 
-                                function:  {binding receiverType asLLVMTypeInModule: context module } ,
-                                           (binding parameterTypes collect:[:t|t asLLVMTypeInModule: context module])
-                                returning: (binding returnType asLLVMTypeInModule: context module)).
-        (function parameterAt: 1) name: 'self'.
-    ].
+    function := aMethodNode binding asLLVMValueInModule: context module.
     asm := function builder.
     super acceptMethodNode: aMethodNode
 
     "Created: / 31-08-2015 / 09:42:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 14-09-2015 / 15:37:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-09-2015 / 07:17:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (format): / 15-09-2015 / 08:17:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 acceptOptimizedNode: anOptimizedNode 
--- a/compiler/TMethodBinding.st	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/TMethodBinding.st	Wed Sep 16 05:29:43 2015 +0100
@@ -36,6 +36,36 @@
     ^ selector
 ! !
 
+!TMethodBinding methodsFor:'converting'!
+
+asLLVMValueInModule: aLLVMModule
+    | name function |
+
+    name := TLLVMCodeGenerator llvmFunctionNameForClass: mclass clazz selector: selector.
+    function := aLLVMModule getFunctionNamed: name.
+    function isNil ifTrue:[ 
+        | type |
+
+        mclass isMetaclass ifTrue:[
+            type := LLVMType 
+                        function:  (parameterTypes collect:[:t|t asLLVMTypeInModule: aLLVMModule ])
+                        returning: (returnType asLLVMTypeInModule: aLLVMModule).                 
+        ] ifFalse:[ 
+            type := LLVMType
+                    function:  {mclass type asLLVMTypeInModule:  aLLVMModule } ,
+                               (parameterTypes collect:[:t|t asLLVMTypeInModule: aLLVMModule])
+                    returning: (returnType asLLVMTypeInModule: aLLVMModule).
+        ].
+        function := aLLVMModule addFunctionNamed: name type: type.
+        mclass isMetaclass ifFalse:[
+            (function parameterAt: 1) name: 'self'.
+        ]
+    ].
+    ^ function
+
+    "Created: / 15-09-2015 / 07:04:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !TMethodBinding methodsFor:'initialization'!
 
 initializeWithClass: aTClassBinding selector: aSymbol
--- a/compiler/TSemanticAnalyser.st	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/TSemanticAnalyser.st	Wed Sep 16 05:29:43 2015 +0100
@@ -67,11 +67,22 @@
 !
 
 acceptLiteralNode: aRBLiteralNode
+    | value |
+
     super acceptLiteralNode: aRBLiteralNode.
-    aRBLiteralNode binding: (TConstantBinding value: aRBLiteralNode value).
+    value := aRBLiteralNode value.
+    value isInteger ifTrue:[ 
+        aRBLiteralNode binding: (TConstantBinding value: value type: (context environment binding lookupClassSIntegerW) type).
+        ^ self.
+    ].
+    value isBoolean ifTrue:[ 
+        aRBLiteralNode binding: (TConstantBinding value: (value ifTrue:[1] ifFalse:[0]) type: (context environment binding lookupClassBoolean) type).
+        ^ self.
+    ].
+    self erorr: 'Unsupported constant'.
 
     "Created: / 25-08-2015 / 23:17:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 02-09-2015 / 10:34:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-09-2015 / 08:27:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 acceptMethodNode: aMethodNode
--- a/compiler/TTypechecker.st	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/TTypechecker.st	Wed Sep 16 05:29:43 2015 +0100
@@ -14,14 +14,15 @@
 acceptIfTrueIfFalseNode: node
     | receiverType booleanType |
 
-    receiverType := node binding type.
-    booleanType := context environment binding lookupClassBoolean.
+    receiverType := node receiver binding type.
+    booleanType := context environment binding lookupClassBoolean type.
 
     receiverType = booleanType ifFalse:[ 
         context reportTypeError: 'receiver of ifTrue:ifFalse: special form must be of type tBoolean (is ' , receiverType printString.
     ].
 
     "Created: / 14-09-2015 / 14:24:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-09-2015 / 08:29:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 acceptIfTrueNode: node
--- a/compiler/abbrev.stc	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/abbrev.stc	Wed Sep 16 05:29:43 2015 +0100
@@ -15,26 +15,20 @@
 TInlineAssemblyNode TInlineAssemblyNode jv:tea/compiler 'Languages-Tea-Compiler-AST' 0
 TMetaDefinition TMetaDefinition jv:tea/compiler 'Languages-Tea-Compiler-Model' 0
 TMethodDefinition TMethodDefinition jv:tea/compiler 'Languages-Tea-Compiler-Model' 0
-TMethodDefinitionTests TMethodDefinitionTests jv:tea/compiler 'Languages-Tea-Compiler-Model-Tests' 1
 TNamespaceDefinition TNamespaceDefinition jv:tea/compiler 'Languages-Tea-Compiler-Model' 0
 TParser TParser jv:tea/compiler 'Languages-Tea-Compiler-AST' 0
-TParserTests TParserTests jv:tea/compiler 'Languages-Tea-Compiler-AST-Tests' 1
 TProgramNodeVisitor TProgramNodeVisitor jv:tea/compiler 'Languages-Tea-Compiler-AST' 0
 TScanner TScanner jv:tea/compiler 'Languages-Tea-Compiler-AST' 0
 TScope TScope jv:tea/compiler 'Languages-Tea-Compiler-Bindings' 0
-TSemanticAnalyserTests TSemanticAnalyserTests jv:tea/compiler 'Languages-Tea-Compiler-Internals-Tests' 1
 TSourceReader TSourceReader jv:tea/compiler 'Languages-Tea-Compiler-Model' 0
-TSourceReaderTests TSourceReaderTests jv:tea/compiler 'Languages-Tea-Compiler-Model-Tests' 1
 TSpecialFormNode TSpecialFormNode jv:tea/compiler 'Languages-Tea-Compiler-AST' 0
 TType TType jv:tea/compiler 'Languages-Tea-Compiler-Types' 0
 TTypeNode TTypeNode jv:tea/compiler 'Languages-Tea-Compiler-AST' 0
 TTypeSpecNode TTypeSpecNode jv:tea/compiler 'Languages-Tea-Compiler-AST' 0
-TTypecheckerTests TTypecheckerTests jv:tea/compiler 'Languages-Tea-Compiler-Internals-Tests' 1
 jv_tea_compiler jv_tea_compiler jv:tea/compiler '* Projects & Packages *' 3
 TBlockType TBlockType jv:tea/compiler 'Languages-Tea-Compiler-Types' 0
 TClassBinding TClassBinding jv:tea/compiler 'Languages-Tea-Compiler-Bindings' 0
 TCompilerPass TCompilerPass jv:tea/compiler 'Languages-Tea-Compiler-Internals' 0
-TDirectoryProvider TDirectoryProvider jv:tea/compiler 'Languages-Tea-Compiler-Model-Provider' 0
 TEnvironment TEnvironment jv:tea/compiler 'Languages-Tea-Compiler-Model' 0
 TFilesystemProvider TFilesystemProvider jv:tea/compiler 'Languages-Tea-Compiler-Model-Provider' 0
 TFunctionBinding TFunctionBinding jv:tea/compiler 'Languages-Tea-Compiler-Bindings' 0
@@ -51,3 +45,8 @@
 TVariableBinding TVariableBinding jv:tea/compiler 'Languages-Tea-Compiler-Bindings' 0
 TArgumentBinding TArgumentBinding jv:tea/compiler 'Languages-Tea-Compiler-Bindings' 0
 TLocalBinding TLocalBinding jv:tea/compiler 'Languages-Tea-Compiler-Bindings' 0
+TMethodDefinitionTests TMethodDefinitionTests jv:tea/compiler 'Languages-Tea-Compiler-Model-Tests' 1
+TParserTests TParserTests jv:tea/compiler 'Languages-Tea-Compiler-AST-Tests' 1
+TSemanticAnalyserTests TSemanticAnalyserTests jv:tea/compiler 'Languages-Tea-Compiler-Internals-Tests' 1
+TSourceReaderTests TSourceReaderTests jv:tea/compiler 'Languages-Tea-Compiler-Model-Tests' 1
+TTypecheckerTests TTypecheckerTests jv:tea/compiler 'Languages-Tea-Compiler-Internals-Tests' 1
--- a/compiler/bc.mak	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/bc.mak	Wed Sep 16 05:29:43 2015 +0100
@@ -101,7 +101,6 @@
 $(OUTDIR)TBlockType.$(O) TBlockType.$(H): TBlockType.st $(INCLUDE_TOP)\jv\tea\compiler\TType.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)TClassBinding.$(O) TClassBinding.$(H): TClassBinding.st $(INCLUDE_TOP)\jv\tea\compiler\TBinding.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)TCompilerPass.$(O) TCompilerPass.$(H): TCompilerPass.st $(INCLUDE_TOP)\jv\tea\compiler\TProgramNodeVisitor.$(H) $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\parser\RBProgramNodeVisitor.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)TDirectoryProvider.$(O) TDirectoryProvider.$(H): TDirectoryProvider.st $(INCLUDE_TOP)\jv\tea\compiler\TEnvironmentProvider.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)TEnvironment.$(O) TEnvironment.$(H): TEnvironment.st $(INCLUDE_TOP)\jv\tea\compiler\TNamespaceDefinition.$(H) $(INCLUDE_TOP)\stx\goodies\ring\RGAbstractContainer.$(H) $(INCLUDE_TOP)\stx\goodies\ring\RGContainer.$(H) $(INCLUDE_TOP)\stx\goodies\ring\RGDefinition.$(H) $(INCLUDE_TOP)\stx\goodies\ring\RGNamespace.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)TFilesystemProvider.$(O) TFilesystemProvider.$(H): TFilesystemProvider.st $(INCLUDE_TOP)\jv\tea\compiler\TEnvironmentProvider.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)TFunctionBinding.$(O) TFunctionBinding.$(H): TFunctionBinding.st $(INCLUDE_TOP)\jv\tea\compiler\TBinding.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
--- a/compiler/bmake.bat	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/bmake.bat	Wed Sep 16 05:29:43 2015 +0100
@@ -5,7 +5,7 @@
 @REM -------
 @SET DEFINES=
 @REM Kludge got Mercurial, cannot be implemented in Borland make
-@FOR /F "tokens=*" %i in ('hg root') do SET HGROOT=%i
+@FOR /F "tokens=*" %%i in ('hg root') do SET HGROOT=%%i
 @IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
 
 make.exe -N -f bc.mak  %DEFINES% %*
--- a/compiler/jv_tea_compiler.st	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/jv_tea_compiler.st	Wed Sep 16 05:29:43 2015 +0100
@@ -87,26 +87,20 @@
         TInlineAssemblyNode
         TMetaDefinition
         TMethodDefinition
-        (TMethodDefinitionTests autoload)
         TNamespaceDefinition
         TParser
-        (TParserTests autoload)
         TProgramNodeVisitor
         TScanner
         TScope
-        (TSemanticAnalyserTests autoload)
         TSourceReader
-        (TSourceReaderTests autoload)
         TSpecialFormNode
         TType
         TTypeNode
         TTypeSpecNode
-        (TTypecheckerTests autoload)
         #'jv_tea_compiler'
         TBlockType
         TClassBinding
         TCompilerPass
-        TDirectoryProvider
         TEnvironment
         TFilesystemProvider
         TFunctionBinding
@@ -123,6 +117,11 @@
         TVariableBinding
         TArgumentBinding
         TLocalBinding
+        (TMethodDefinitionTests autoload)
+        (TParserTests autoload)
+        (TSemanticAnalyserTests autoload)
+        (TSourceReaderTests autoload)
+        (TTypecheckerTests autoload)
     )
 !
 
--- a/compiler/libInit.cc	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/libInit.cc	Wed Sep 16 05:29:43 2015 +0100
@@ -54,7 +54,6 @@
 _TBlockType_Init(pass,__pRT__,snd);
 _TClassBinding_Init(pass,__pRT__,snd);
 _TCompilerPass_Init(pass,__pRT__,snd);
-_TDirectoryProvider_Init(pass,__pRT__,snd);
 _TEnvironment_Init(pass,__pRT__,snd);
 _TFilesystemProvider_Init(pass,__pRT__,snd);
 _TFunctionBinding_Init(pass,__pRT__,snd);
--- a/compiler/mingwmake.bat	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/mingwmake.bat	Wed Sep 16 05:29:43 2015 +0100
@@ -5,7 +5,7 @@
 @REM -------
 @SET DEFINES=
 @REM Kludge got Mercurial, cannot be implemented in Borland make
-@FOR /F "tokens=*" %i in ('hg root') do SET HGROOT=%i
+@FOR /F "tokens=*" %%i in ('hg root') do SET HGROOT=%%i
 @IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
 
 @pushd ..\..\..\stx\rules
--- a/compiler/vcmake.bat	Mon Sep 14 16:27:00 2015 +0100
+++ b/compiler/vcmake.bat	Wed Sep 16 05:29:43 2015 +0100
@@ -10,6 +10,10 @@
     popd
 )
 @SET DEFINES=
+@REM Kludge got Mercurial, cannot be implemented in Borland make
+@FOR /F "tokens=*" %%i in ('hg root') do SET HGROOT=%%i
+@IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
+
 
 make.exe -N -f bc.mak -DUSEVC=1 %DEFINES% %*