Merge jv
authorMerge Script
Sat, 24 Sep 2016 06:43:04 +0200
branchjv
changeset 3988 dc67db6ea87b
parent 3986 5dadef06fe27 (diff)
parent 3987 ed1e194ec458 (current diff)
child 3990 ee6b0bd566bd
Merge
Parser.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/.hgignore	Sat Sep 24 06:43:04 2016 +0200
@@ -0,0 +1,16 @@
+
+syntax: glob
+*Init.c   
+makefile
+*.so
+*.H
+*.o
+*.STH
+*.sc
+objbc
+objvc
+*.class
+java/libs/*.jar
+java/libs-src/*.jar
+*-Test.xml
+st.chg
--- a/AbstractSyntaxHighlighter.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/AbstractSyntaxHighlighter.st	Sat Sep 24 06:43:04 2016 +0200
@@ -257,6 +257,40 @@
     ^ self formatMethod:nil source:aString in:aClass using:preferencesOrNil
 
     "Modified: / 28-04-2010 / 13:02:11 / cg"
+!
+
+formatStatements:aString in:aClass
+    "Format (recolor) a list of statements with optional temporaries in a given class.
+     Return the text containing font changes and color information."
+
+    |parser tree text|
+
+    aString isNil ifTrue:[^ nil].
+
+    parser := self for:(ReadStream on:aString string) in:aClass.
+    parser ignoreErrors:true.
+    parser ignoreWarnings:true.
+    parser sourceText:(text := aString string asText).
+    "/ use an array here - this can be changed much faster using #at:put:
+    text emphasisCollection:(Array new:aString size).
+
+    parser nextToken.
+    tree := parser parseMethodBody.
+    "/ now, convert the emphasis-array to a runArray
+    text emphasisCollection:(text emphasis asRunArray).
+
+    tree == #Error ifTrue:[
+        ^ self colorize:text forErrorAtPosition:parser sourceStream position withOriginal:aString.
+    ].
+    ^ text
+
+    "
+     SyntaxHighlighter
+        formatStatements:'| a b | a error: b'
+        in:UndefinedObject
+    "
+
+    "Created: / 22-02-2016 / 20:50:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !AbstractSyntaxHighlighter class methodsFor:'highlighting'!
@@ -683,6 +717,11 @@
     ^ '$Header$'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$ Id $'
 ! !
--- a/BlockNode.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/BlockNode.st	Sat Sep 24 06:43:04 2016 +0200
@@ -287,21 +287,25 @@
      the code is compiled by stc, otherwise assume the code is
      compiled by bytecode compiler"
 
-    | myBlocks |
+    | myBlocks myInlinedBlocks |
 
     myBlocks := OrderedCollection new.
     self collectBlocksInto: myBlocks.
-    myBlocks := myBlocks select:[:block | block isInlinedInto: self assumeStcCompiled: forStcCompiledCode. ].
-    ^ myBlocks notEmpty ifTrue:[
+    myInlinedBlocks := myBlocks select:[:block | block isInlinedInto: self assumeStcCompiled: forStcCompiledCode. ].
+    ^ myInlinedBlocks notEmpty ifTrue:[
         OrderedCollection streamContents:[:s|
             s nextPutAll: blockVars ? #().
-            myBlocks do:[:block | s nextPutAll: block variables ? #() ].
+            myInlinedBlocks do:[:block | 
+                s nextPutAll: block arguments ? #().   
+                s nextPutAll: block variables ? #() 
+            ].
         ]
     ] ifFalse:[
         blockVars
     ].
 
     "Created: / 19-08-2013 / 11:37:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 22-12-2015 / 12:51:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !BlockNode methodsFor:'block messages'!
@@ -407,7 +411,7 @@
                     numArgs:(blockArgs size)
                     numVars:0
                     numStack:stackSize
-                    sourcePosition:nil 
+                    sourcePosition:startPosition
                     initialPC:nil 
                     literals:nil.
         ^ ConstantNode type:#Block value:cheapy.
@@ -559,10 +563,17 @@
 
     "cheap block detection filters out blocks with no statements"
 
+    "/ Do not encode source position if not available.
+    "/ Note, that JavaScriptCompiler has no sourceposX pseudo instruction
+    "/ support, so in this case, do not emit it.
+    (startPosition notNil and:[ (aCompiler isKindOf: (Smalltalk at:#JavaScriptCompiler)) not]) ifTrue:[ 
+        self codeSourcePosition: startPosition on: aStream for: aCompiler.
+    ].
+
     pos := aStream position.
 
     aStream nextPut:#makeBlock.                                 "+0"
-    aStream nextPut:0.                                          "+1"
+    aStream nextPut:0."/block's bytecode end index,patched later"+1"
     aStream nextPut:(blockVars size + (maxNumTemp?0)).          "+2"
     aStream nextPut:(blockArgs size).                           "+3"
                                                                 "+4"
@@ -593,7 +604,8 @@
     "set the end of the block's code"
     code at:pos+2 put:(aStream position + 1)
 
-    "Modified: 26.6.1997 / 10:48:56 / cg"
+    "Modified: / 26-06-1997 / 10:48:56 / cg"
+    "Modified: / 05-05-2016 / 00:13:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !BlockNode methodsFor:'code generation helpers'!
@@ -1035,6 +1047,17 @@
     "Created: 23.10.1996 / 16:17:07 / cg"
 !
 
+numVarsIncludingInlined: forStcCompiledCode
+    "Returns number of local variables including those of blocks inlined into
+     the receiver. If `forStcCompiledCode` is true then assume
+     the code is compiled by stc, otherwise assume the code is
+     compiled by bytecode compiler"
+
+    ^ (self variablesIncludingInlined: forStcCompiledCode) size.
+
+    "Created: / 22-12-2015 / 12:38:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 simpleSendBlockExpression
     blockVars notNil ifTrue:[^ nil].
     statements isNil ifTrue:[^ nil].
@@ -1088,8 +1111,9 @@
 
     self parent isMessage ifFalse:[ ^ false ].
     selector := self parent selector.
-    ^ assumeStc ifTrue:[
-        #(
+    "/ Following control-flow selectors are inlined by both, 
+    "/ stc and bytecode/jit compiler...
+    (#(
             ifTrue:
             ifTrue:ifFalse:
             ifFalse:
@@ -1097,22 +1121,21 @@
             whileTrue:
             whileFalse
             whileFalse:
+            to:do:   
             "/ Add more here...
+    ) includes: selector) ifTrue:[ ^ true ].
+    ^ assumeStc ifTrue:[
+        #(
+            "/ Add more selectors inlined only by STC here...
         ) includes: selector
     ] ifFalse:[
         #(
-            ifTrue:
-            ifTrue:ifFalse:
-            ifFalse:
-            whileTrue
-            whileTrue:
-            whileFalse
-            whileFalse:
-            "/ Add more here...
+            "/ Add more selector inline only by bytecode compiler here...
         ) includes: selector
     ]
 
     "Created: / 19-08-2013 / 12:00:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 22-12-2015 / 12:56:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 isJavaScriptBlock
@@ -1146,6 +1169,11 @@
     ^ '$Header$'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$ Id $'
 ! !
--- a/BreakpointAnalyzer.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/BreakpointAnalyzer.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1,5 +1,18 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libcomp' }"
 
+"{ NameSpace: Smalltalk }"
+
 Parser variableSubclass:#BreakpointAnalyzer
 	instanceVariableNames:'messageSendMap'
 	classVariableNames:''
@@ -7,6 +20,21 @@
 	category:'System-Compiler-Debugging'
 !
 
+!BreakpointAnalyzer class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
 
 !BreakpointAnalyzer methodsFor:'accessing'!
 
--- a/BreakpointDescription.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/BreakpointDescription.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1,3 +1,14 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libcomp' }"
 
 "{ NameSpace: Smalltalk }"
@@ -11,6 +22,20 @@
 
 !BreakpointDescription class methodsFor:'documentation'!
 
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
 documentation
 "
     I describe a breakpoint: its state (enabled/disabled),
--- a/BreakpointQuery.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/BreakpointQuery.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1,5 +1,18 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libcomp' }"
 
+"{ NameSpace: Smalltalk }"
+
 Query subclass:#BreakpointQuery
 	instanceVariableNames:''
 	classVariableNames:''
@@ -9,6 +22,20 @@
 
 !BreakpointQuery class methodsFor:'documentation'!
 
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
 documentation
 "
     BreakpointQuery is a query used to pass list of breakpoints
--- a/ByteCodeCompiler.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/ByteCodeCompiler.st	Sat Sep 24 06:43:04 2016 +0200
@@ -351,9 +351,9 @@
         F2          STORE_OUTBLOCK_LVAR store local variable in outer context 0..numArgs-1 for args; numArgs..numArgs+nLocal-1 for bVars
         F3          SWAP            swap TOS with NOS
 
-        F4          UNUSED_244
-        F5          UNUSED_245
-        F6          UNUSED_246
+        F4          SOURCEPOS8 uu   source position information (offset in source, dummy) 
+        F5          SOURCEPOS16 uuuu  source position information (offset in source, dummy) 
+        F6          SOURCEPOS32 uuuuuuuu source position information (offset in source, dummy) 
         F7          UNUSED_247
         F8          UNUSED_248
         F9          UNUSED_249
@@ -1178,6 +1178,10 @@
     (aSymbol == #lineno) ifTrue:[lineno := true. ^ 8].
     (aSymbol == #lineno16) ifTrue:[lineno := true. ^ 9].
 
+    (aSymbol == #sourcepos8)  ifTrue:[extra := #index.      ^ 244].
+    (aSymbol == #sourcepos16) ifTrue:[extra := #unsigned16. ^ 245].
+    (aSymbol == #sourcepos32) ifTrue:[extra := #unsigned32. ^ 246].
+
     (aSymbol == #send) ifTrue:[lineno := true. extra := #special. ^ 19].
     (aSymbol == #superSend) ifTrue:[lineno := true. extra := #special. ^ 20].
     (aSymbol == #sendSelf) ifTrue:[lineno := true. extra := #special. ^ 13].
@@ -1437,6 +1441,7 @@
     "Modified: / 03-09-1995 / 12:58:47 / claus"
     "Modified: / 25-10-2011 / 21:56:43 / cg"
     "Modified (comment): / 31-10-2011 / 11:34:37 / cg"
+    "Modified (format): / 31-05-2015 / 03:55:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 checkForCommonCode:symbolicCodeArray
@@ -2046,6 +2051,40 @@
     ].
 !
 
+codeSourcePosition:nr on:codeStream
+    "generate source position information"
+
+    "/ caveat: (currently) there is no separate line number, position or symbol table;
+    "/ the source positions are coded right into the instruction stream.
+    "/ This might change in the future.
+    "/ (It is not a problem speed wise: the Jitter just skips them.)
+
+    nr <= 255 ifTrue:[
+        codeStream 
+            nextPut:#sourcepos8;
+            nextPut:nr.
+    ] ifFalse:[
+        nr <= 16rFFFF ifTrue:[
+            codeStream 
+                nextPut:#sourcepos16;
+                nextPut:nr;
+                nextPut:nil.
+
+        ] ifFalse:[ 
+            nr <= 16rFFFFFFFF ifTrue:[ 
+                codeStream 
+                    nextPut:#sourcepos32;
+                    nextPut:nr;
+                    nextPut:nil;
+                    nextPut:nil;
+                    nextPut:nil.
+            ].
+        ].
+    ].
+
+    "Created: / 31-05-2015 / 03:43:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 createMethod
     |newMethod|
 
--- a/CompilationErrorHandlerQuery.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/CompilationErrorHandlerQuery.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1,3 +1,14 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libcomp' }"
 
 "{ NameSpace: Smalltalk }"
@@ -9,6 +20,21 @@
 	category:'System-Compiler'
 !
 
+!CompilationErrorHandlerQuery class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
 
 !CompilationErrorHandlerQuery class methodsFor:'documentation'!
 
--- a/Decompiler.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/Decompiler.st	Sat Sep 24 06:43:04 2016 +0200
@@ -518,6 +518,20 @@
     "Modified: 16.4.1996 / 20:28:58 / cg"
 !
 
+showUnsigned16:byte
+    listStream show:(bytes wordAt:index MSB:false) printString.
+    index := index + 2
+
+    "Created: / 17-08-2015 / 14:51:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+showUnsigned32:byte
+    listStream show:(bytes doubleWordAt:index MSB:false) printString.
+    index := index + 2
+
+    "Created: / 17-08-2015 / 14:53:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 showVeryLongOffset:byte
     |offs|
 
@@ -788,6 +802,9 @@
                 storeBlockLocal       " 241 "
                 storeOuterBlockLocal  " 242 "
                 swap                  " 243 "
+                SOURCEPOS8            " 244 "
+                SOURCEPOS16           " 245 "
+                SOURCEPOS32           " 246 "
               ).
 
     lnos := #(  false          " 0  "
@@ -1034,6 +1051,9 @@
                 false           " 241 "
                 false           " 242 "
                 false           " 243 "
+                false           " 244 "
+                false           " 245 "
+                false           " 246 "
               ).
 
     extras := #(nil             " 0  "
@@ -1280,6 +1300,9 @@
                 index           " 241 "
                 levelIndex      " 242 "
                 nil             " 243 "
+                index           " 244 "
+                unsigned16      " 245 "
+                unsigned32      " 246 "
              ).
 
     sym := syms at:(aByte + 1).
@@ -1294,7 +1317,7 @@
 
     "Modified: / 02-09-1995 / 00:12:11 / claus"
     "Modified: / 25-10-2011 / 21:58:24 / cg"
-    "Modified: / 12-04-2013 / 01:31:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 31-05-2015 / 04:05:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !Decompiler class methodsFor:'documentation'!
@@ -1305,5 +1328,10 @@
 
 version_CVS
     ^ '$Header$'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
--- a/Explainer.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/Explainer.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1047,7 +1047,7 @@
                 "/ TODO: generate a short documentation string (comment plus interface)
                 "/ and return { #html->htmlText . #text->regularText}
                 "/ so caller can extract what he wants to see...
-                ^ (HTMLDocGenerator htmlDocOf:val).
+                ^ ((Smalltalk at:#HTMLDocGenerator) htmlDocOf:val).
             ].
             explanation := varName , ' is '.
             explanation := explanation , (val isLoaded ifTrue:['a'] ifFalse:['an autoloaded']).
@@ -1089,6 +1089,7 @@
     "Created: / 14-10-2010 / 11:33:04 / cg"
     "Modified: / 14-02-2012 / 15:31:28 / cg"
     "Modified (comment): / 28-02-2012 / 10:45:48 / cg"
+    "Modified: / 05-05-2016 / 00:25:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 explainHereIn:aClass short:shortText
@@ -2193,10 +2194,10 @@
     |visitor|
 
     "/ hack, allowing to deal with both types of AST (sigh)
-    (tree isKindOf:RBProgramNode) ifTrue:[
-        visitor := RBPluggableProgramNodeVisitor new.
+    (tree isKindOf:(Smalltalk at:#RBProgramNode)) ifTrue:[
+        visitor := (Smalltalk at:#RBPluggableProgramNodeVisitor) new.
         visitor 
-            actionForNodeClass:RBAssignmentNode 
+            actionForNodeClass:(Smalltalk at:#RBAssignmentNode)
             put:[:node |
                 |leftSide|
 
@@ -2222,7 +2223,9 @@
                 true "/ yes - visit subnodes
             ].        
         visitor visit:tree.
-    ].    
+    ].
+
+    "Modified (format): / 05-05-2016 / 00:19:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 addTypesOfInstvar:instVarName inClass:aClass fromExistingInstancesTo:setOfTypes
--- a/InstrumentingCompiler.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/InstrumentingCompiler.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1,3 +1,14 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libcomp' }"
 
 "{ NameSpace: Smalltalk }"
@@ -109,6 +120,20 @@
 
 !InstrumentingCompiler class methodsFor:'documentation'!
 
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
 documentation
 "
     an experiment - recompile classes using this compiler adds instrumentation code.
--- a/Make.proto	Fri Sep 23 07:06:30 2016 +0200
+++ b/Make.proto	Sat Sep 24 06:43:04 2016 +0200
@@ -34,7 +34,7 @@
 # add the path(es) here:,
 # ********** OPTIONAL: MODIFY the next lines ***
 # LOCALINCLUDES=-Ifoo -Ibar
-LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/lint -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/parser -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/refactoring -I$(INCLUDE_TOP)/stx/libbasic -I$(INCLUDE_TOP)/stx/libbasic3 -I$(INCLUDE_TOP)/stx/libtool2
+LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/libbasic
 
 
 # if you need any additional defines for embedded C code,
@@ -85,13 +85,20 @@
 		sed -e "s/\"\$$SVN\-Revision:\".*\"\$$\"/\"\$$SVN-Revision:\"\'$$rev2\'\"\$$\"/g" $< > .stx_libcomp.svn.st; \
 	fi
 	$(MAKE) CC="$(CLASSLIB_CC)" OPT="$(OPT)" SEPINITCODE="$(SEPINITCODE)" STC="$(STC)" STFILE=.stx_libcomp.svn $(C_RULE);
-	sed -i -e "s/\".stx_libcomp.svn.st\");/\"\stx_libcomp.st\");/g" .stx_libcomp.svn.c
+	sed -i -e "s/\".stx_libcomp.svn.st\");/\"stx_libcomp.st\");/g" .stx_libcomp.svn.c
 	$(MAKE) .stx_libcomp.svn.$(O)
 	@mv .stx_libcomp.svn.$(O) stx_libcomp.$(O)
 endif
 
 
 
+# Enforce recompilation of package definition class if Mercurial working
+# copy state changes. Together with --guessVersion it ensures that package
+# definition class always contains correct binary revision string.
+ifneq (**NOHG**, $(shell hg root 2> /dev/null || echo -n '**NOHG**'))
+stx_libcomp.$(O): $(shell hg root)/.hg/dirstate
+endif
+
 
 
 
--- a/ObjectFileLoader.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/ObjectFileLoader.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
 	      All Rights Reserved
@@ -188,6 +186,7 @@
 #  endif
 # endif /* BORLANDC */
 
+# include <psapi.h>
 
 # ifdef __DEF_Array
 #  define Array __DEF_Array
@@ -1236,13 +1235,13 @@
 
     handle := self handleForDynamicObject:filename.
     handle notNil ifTrue:[
-	"already loaded"
-	^ handle.
+        "already loaded"
+        ^ handle.
     ].
 
     handle := self loadDynamicObject:filename.
     handle isNil ifTrue:[
-	^ nil
+        ^ nil
     ].
 
     didInit := false.
@@ -1252,23 +1251,23 @@
      are to be resolved. If that's the case, load all libraries ..."
 
     ParserFlags searchedLibraries notEmptyOrNil ifTrue:[
-	(self hasUndefinedSymbolsIn:handle) ifTrue:[
-	    self initializeLoader.
-
-	    ParserFlags searchedLibraries do:[:libName |
-		(self hasUndefinedSymbolsIn:handle) ifTrue:[
-		    Logger info:'   ... trying  %1 to resolve undefined symbols ...' with:libName.
-		    dummyHandle := Array new:4.
-		    dummyHandle := self primLoadDynamicObject:libName into:dummyHandle.
+        (self hasUndefinedSymbolsIn:handle) ifTrue:[
+            self initializeLoader.
+
+            ParserFlags searchedLibraries do:[:libName |
+                (self hasUndefinedSymbolsIn:handle) ifTrue:[
+                    Logger info:'   ... trying  %1 to resolve undefined symbols ...' with:libName.
+                    dummyHandle := Array new:4.
+                    dummyHandle := self primLoadDynamicObject:libName into:dummyHandle.
 "/                    dummyHandle isNil ifTrue:[
 "/                        Transcript showCR:'   ... load of library ' , libName , ' failed.'.
 "/                    ]
-		]
-	    ].
-	    (self hasUndefinedSymbolsIn:handle) isNil ifTrue:[
-		Logger info:'still undefined symbols in %1.' with:pathName.
-	    ].
-	]
+                ]
+            ].
+            (self hasUndefinedSymbolsIn:handle) isNil ifTrue:[
+                Logger info:'still undefined symbols in %1.' with:pathName.
+            ].
+        ]
     ].
 
     "
@@ -1283,209 +1282,212 @@
      This is used in ST packaged classLib object files"
 
     (initFunctionName startsWith:'lib') ifTrue:[
-	definitionClassName := initFunctionName copyFrom:4.
-	definitionClass := Smalltalk classNamed:definitionClassName.
+        definitionClassName := initFunctionName copyFrom:4.
+        definitionClass := Smalltalk classNamed:definitionClassName.
     ].
     (definitionClass isNil or:[definitionClass isLoaded not]) ifTrue:[
-	"the project definition class has not been loaded yet.
-	 initialize and load it"
-
-	initDefinitionAddr := self findInitDefinitionFunction:initFunctionName in:handle.
-	initDefinitionAddr isNil ifTrue:[
-	    ('WARNING: no init definitions for: ' , pathName) errorPrintCR.
-	] ifFalse:[
-	    Verbose ifTrue:[
-		('calling initDefinition at:' , (initDefinitionAddr printStringRadix:16)) errorPrintCR.
-	    ].
-	    info := self
-			performModuleInitAt:initDefinitionAddr
-			invokeInitializeMethods:false
-			for:definitionClassName
-			identifyAs:handle.
-	    status := info at:1.
-	    status == #ok ifTrue:[
-		"/ now, we have only loaded and installed the projectDefinition class.
-		"/ (but no containing classes or extensions, yet).
-		"/ let the projectDefinition load any prereqs
-	       definitionClassName notNil ifTrue:[
-		    definitionClass := Smalltalk classNamed:definitionClassName.
-		    definitionClass notNil ifTrue:[
+        "the project definition class has not been loaded yet.
+         initialize and load it"
+
+        initDefinitionAddr := self findInitDefinitionFunction:initFunctionName in:handle.
+        initDefinitionAddr isNil ifTrue:[
+            ('WARNING: no init definitions for: ' , pathName) errorPrintCR.
+        ] ifFalse:[
+            Verbose ifTrue:[
+                ('calling initDefinition at:' , (initDefinitionAddr printStringRadix:16)) errorPrintCR.
+            ].
+            info := self
+                        performModuleInitAt:initDefinitionAddr
+                        invokeInitializeMethods:false
+                        for:definitionClassName
+                        identifyAs:handle.
+            status := info at:1.
+            status == #ok ifTrue:[
+                "/ now, we have only loaded and installed the projectDefinition class.
+                "/ (but no containing classes or extensions, yet).
+                "/ let the projectDefinition load any prereqs
+               definitionClassName notNil ifTrue:[
+                    definitionClass := Smalltalk classNamed:definitionClassName.
+                    definitionClass notNil ifTrue:[
 "/                        "if projectDefinition denies loading, unload"
 "/                            self unloadDynamicObject:handle.
 
-			definitionClass
-			    checkForLoad;                           "/ raise exception if not supported on platform / not licensed
-			    initialize;
-			    preLoadAction;
-			    loadMandatoryPreRequisitesAsAutoloaded:false.
-		    ].
-		].
-	    ]
-	].
+                        definitionClass
+                            checkForLoad;                           "/ raise exception if not supported on platform / not licensed
+                            initialize;
+                            preLoadAction;
+                            loadMandatoryPreRequisitesAsAutoloaded:false.
+                    ].
+                ].
+            ]
+        ].
     ].
     "look for explicit init (xxx_Init) function
      This is used in ST object files"
 
     initAddr := self findInitFunction:initFunctionName in:handle.
     initAddr notNil ifTrue:[
-	Verbose ifTrue:[
-	    ('calling init at:' , (initAddr printStringRadix:16)) errorPrintCR.
-	].
-	info := self
-		    performModuleInitAt:initAddr
-		    invokeInitializeMethods:invokeInitializeMethods
-		    for:nil
-		    identifyAs:handle.
-	status := info at:1.
-	status == #ok ifTrue:[
-	    didInit := true.
-	    definitionClassName notNil ifTrue:[
-		definitionClass := Smalltalk classNamed:definitionClassName.
-	    ]
-	]
+        Verbose ifTrue:[
+            ('calling init at:' , (initAddr printStringRadix:16)) errorPrintCR.
+        ].
+        info := self
+                    performModuleInitAt:initAddr
+                    invokeInitializeMethods:invokeInitializeMethods
+                    for:nil
+                    identifyAs:handle.
+        status := info at:1.
+        status == #ok ifTrue:[
+            didInit := true.
+            definitionClassName notNil ifTrue:[
+                definitionClass := Smalltalk classNamed:definitionClassName.
+            ]
+        ]
     ] ifFalse:[
-	"look for explicit C-init (xxx__Init) function
-	 This is used in C object files"
-
-	initAddr := self findFunction:initFunctionName suffix:'__Init' in:handle.
-	initAddr notNil ifTrue:[
-	    isCModule := true.
-
-	    OSSignalInterrupt handle:[:ex |
-		Logger error:'hard error in initFunction of class-module: %1' with:pathName.
-		status := #initFailed.
-	    ] do:[
-		cRetVal := self
-		    saveCallInitFunctionAt:initAddr
-		    in:pathNameOrFilename
-		    specialInit:false
-		    forceOld:true
-		    interruptable:false
-		    argument:0
-		    identifyAs:handle
-		    returnsObject:false.
-		(cRetVal < 0) ifTrue:[
-		    Verbose ifTrue:[
-			'init function return failure ... unload' errorPrintCR.
-		    ].
-		    status := #initFailed.
-		] ifFalse:[
-		    didInit := true.
-		]
-	    ]
-	] ifFalse:[
-	    status := #noInitFunction.
-
-	    "look for any init-function(s); call them all"
-	    Verbose ifTrue:[
-		'no good init functions found; looking for candidates ...' errorPrintCR.
-	    ].
-	    initNames := self namesMatching:'*_Init' segment:'[tT?]' in:pathName.
-	    initNames notNil ifTrue:[
-		initNames do:[:aName |
-		    initAddr := self getFunction:aName from:handle.
-		    initAddr isNil ifTrue:[
-			(aName startsWith:'_') ifTrue:[
-			    initAddr := self getFunction:(aName copyFrom:2) from:handle.
-			].
-		    ].
-		    initAddr isNil ifTrue:[
-			Transcript showCR:('no symbol: ',aName,' in ', pathName).
-		    ] ifFalse:[
-			Verbose ifTrue:[
-			    ('calling init at:' , (initAddr printStringRadix:16)) errorPrintCR
-			].
-			self
-			    performModuleInitAt:initAddr
-			    invokeInitializeMethods:invokeInitializeMethods
-			    for:nil
-			    identifyAs:handle.
-			didInit := true.
-		    ]
-		].
-	    ].
-	]
+        "look for explicit C-init (xxx__Init) function
+         This is used in C object files"
+
+        initAddr := self findFunction:initFunctionName suffix:'__Init' in:handle.
+        initAddr notNil ifTrue:[
+            isCModule := true.
+
+            OSSignalInterrupt handle:[:ex |
+                Logger error:'hard error in initFunction of class-module: %1' with:pathName.
+                status := #initFailed.
+            ] do:[
+                cRetVal := self
+                    saveCallInitFunctionAt:initAddr
+                    in:pathNameOrFilename
+                    specialInit:false
+                    forceOld:true
+                    interruptable:false
+                    argument:0
+                    identifyAs:handle
+                    returnsObject:false.
+                (cRetVal < 0) ifTrue:[
+                    Verbose ifTrue:[
+                        'init function return failure ... unload' errorPrintCR.
+                    ].
+                    status := #initFailed.
+                ] ifFalse:[
+                    didInit := true.
+                ]
+            ]
+        ] ifFalse:[
+            status := #noInitFunction.
+
+            "look for any init-function(s); call them all"
+            Verbose ifTrue:[
+                'no good init functions found; looking for candidates ...' errorPrintCR.
+            ].
+            initNames := self namesMatching:'*_Init' segment:'[tT?]' in:pathName.
+            initNames notNil ifTrue:[
+                initNames do:[:aName |
+                    initAddr := self getFunction:aName from:handle.
+                    initAddr isNil ifTrue:[
+                        (aName startsWith:'_') ifTrue:[
+                            initAddr := self getFunction:(aName copyFrom:2) from:handle.
+                        ].
+                    ].
+                    initAddr isNil ifTrue:[
+                        Transcript showCR:('no symbol: ',aName,' in ', pathName).
+                    ] ifFalse:[
+                        Verbose ifTrue:[
+                            ('calling init at:' , (initAddr printStringRadix:16)) errorPrintCR
+                        ].
+                        self
+                            performModuleInitAt:initAddr
+                            invokeInitializeMethods:invokeInitializeMethods
+                            for:nil
+                            identifyAs:handle.
+                        didInit := true.
+                    ]
+                ].
+            ].
+        ]
     ].
 
     (invokeInitializeMethods and:[didInit not]) ifTrue:[
-	status == #noInitFunction ifTrue:[
-	    msg := 'no classLib init function found; assume load ok'
-	] ifFalse:[
-	    (status ~~ #registrationFailed
-		and:[status ~~ #initFailed
-		and:[status ~~ #missingClass
-		and:[status ~~ #versionMismatch]]])
-	    ifTrue:[
-		self listUndefinedSymbolsIn:handle.
-	    ].
-
-	    Verbose ifTrue:[
-		'unloading, since init failed ...' errorPrintCR.
-	    ].
-
-	    "/ give caller a chance to prevent unloading (to register later, when a prerequisite class comes)
-	    status == #missingClass ifTrue:[
-		doNotUnload := (SuperClassMissingErrorNotification query ? false).
-	    ] ifFalse:[
-		status == #registrationFailed ifTrue:[
-		    doNotUnload := (RegistrationFailedErrorNotification query ? false).
-		] ifFalse:[
-		    doNotUnload := false.
-		].
-	    ].
-	    doNotUnload ifFalse:[
-		self unloadDynamicObject:handle.
-		Verbose ifTrue:[
-		    'unloaded.' errorPrintCR.
-		].
-		handle := nil.
-	    ].
-
-	    status == #initFailed ifTrue:[
-		msg := 'module not loaded (init function signaled failure).'
-	    ] ifFalse:[
-		status == #missingClass ifTrue:[
-		    msg := 'module not loaded (superclass missing: ' , (info at:2) , ').'
-		] ifFalse:[
-		    status == #registrationFailed ifTrue:[
-			msg :=  'module registration failed (incompatible object or missing superclass)'
-		    ] ifFalse:[
-			status == #versionMismatch ifTrue:[
-			    msg :=  'module registration failed (class version mismatch ' , (info at:2) printString , ')'
-			] ifFalse:[
-			    (self namesMatching:'*__sepInitCode__*' segment:'[tT?]' in:pathName) notNil ifTrue:[
-				msg := 'module not loaded (unknown error reason).'
-			    ] ifFalse:[
-				msg := 'module not loaded (no _Init entry in object file ?).'
-			    ]
-			]
-		    ].
-		].
-	    ].
-	].
-	Logger info:'%1: %2' with:pathNameOrFilename asFilename baseName with:msg.
+        status == #noInitFunction ifTrue:[
+            msg := 'no classLib init function found; assume load ok'
+        ] ifFalse:[
+            (status ~~ #registrationFailed
+                and:[status ~~ #initFailed
+                and:[status ~~ #missingClass
+                and:[status ~~ #versionMismatch]]])
+            ifTrue:[
+                self listUndefinedSymbolsIn:handle.
+            ].
+
+            Verbose ifTrue:[
+                'unloading, since init failed ...' errorPrintCR.
+            ].
+
+            "/ give caller a chance to prevent unloading (to register later, when a prerequisite class comes)
+            status == #missingClass ifTrue:[
+                doNotUnload := (SuperClassMissingErrorNotification query ? false).
+            ] ifFalse:[
+                status == #registrationFailed ifTrue:[
+                    doNotUnload := (RegistrationFailedErrorNotification query ? false).
+                ] ifFalse:[
+                    doNotUnload := false.
+                ].
+            ].
+            doNotUnload ifFalse:[
+                self unloadDynamicObject:handle.
+                Verbose ifTrue:[
+                    'unloaded.' errorPrintCR.
+                ].
+                handle := nil.
+            ].
+
+            status == #initFailed ifTrue:[
+                msg := 'module not loaded (init function signaled failure).'
+            ] ifFalse:[
+                status == #missingClass ifTrue:[
+                    msg := 'module not loaded (superclass missing: ' , (info at:2) , ').'
+                ] ifFalse:[
+                    status == #registrationFailed ifTrue:[
+                        msg :=  'module registration failed (incompatible object or missing superclass)'
+                    ] ifFalse:[
+                        status == #versionMismatch ifTrue:[
+                            msg :=  'module registration failed (class version mismatch ' , (info at:2) printString , ')'
+                        ] ifFalse:[
+                            (self namesMatching:'*__sepInitCode__*' segment:'[tT?]' in:pathName) notNil ifTrue:[
+                                msg := 'module not loaded (unknown error reason).'
+                            ] ifFalse:[
+                                msg := 'module not loaded (no _Init entry in object file ?).'
+                            ]
+                        ]
+                    ].
+                ].
+            ].
+        ].
+        Logger info:'%1: %2' with:pathNameOrFilename asFilename baseName with:msg.
     ].
 
     isCModule ifFalse:[
-	Smalltalk flushCachedClasses.
-	Class flushSubclassInfo.
-
-	(definitionClass notNil and:[definitionClass isLoaded]) ifTrue:[
-	    definitionClass
-		checkForLoad;                           "/ raise exception if not supported on platform / not licensed
-		loadAllClassesAsAutoloaded:true;
-		loadPreRequisitesAsAutoloaded:true;     "/ load non-mandatory prerequisites
-		projectIsLoaded:true.                   "/ this performs the postLoadAction, too.
-	].
-	Smalltalk isInitialized ifTrue:[
-	    "really don't know, if and what has changed ...
-	     ... but assume, that new classes have been installed."
-	    Smalltalk changed:#postLoad.
-	].
+        Smalltalk flushCachedClasses.
+        Class flushSubclassInfo.
+
+        (definitionClass notNil and:[definitionClass isLoaded]) ifTrue:[
+            definitionClass checkForLoad.               "/ raise exception if not supported on platform / not licensed
+            Smalltalk changed: #aboutToLoadPackage with: definitionClass.
+            definitionClass
+                loadAllClassesAsAutoloaded:true;
+                loadPreRequisitesAsAutoloaded:true;     "/ load non-mandatory prerequisites
+                projectIsLoaded:true.                   "/ this performs the postLoadAction, too.
+            Smalltalk changed: #packageLoaded with: definitionClass.
+        ].
+        Smalltalk isInitialized ifTrue:[
+            "really don't know, if and what has changed ...
+             ... but assume, that new classes have been installed."
+            Smalltalk changed:#postLoad.
+        ].
     ].
     ^ handle
 
     "Modified: / 15-11-2010 / 13:19:26 / cg"
+    "Modified: / 20-09-2016 / 00:02:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 unloadAllObsoleteObjectFiles
@@ -1808,7 +1810,42 @@
 	if (__isStringLike(aString)) {
 	    if (@global(Verbose) == true)
 		console_printf("get sym <%s> handle = %"_lx_"\n", __stringVal(aString), (INT)handle);
-	    entry = GetProcAddress(handle, (char *) __stringVal(aString));
+            /*
+             * Unlike POSIX.1-2001 dlopen(), Windows has no such handle that
+             * would, when passed to GetProcAddress(), search current loaded image
+             * (i.e., all loaded .dlls and .exes). To allow this, when #primLoadObjectFile
+             * is asked to return a such a handle, it returns a fake handle with value 0. 
+             *
+             * In this case we have to loop over all loaded modules (HINSTANCEs) and 
+             * try to GetProcAddress() from each of them. If we find only one, then return
+             * it. 
+             *
+             * What a hack!
+             */
+            if (handle == 0) {
+            	HMODULE modules[256];
+            	DWORD   modules_needed;
+		if (EnumProcessModules(GetCurrentProcess(), modules, sizeof(modules), &modules_needed)) {
+		    int i;
+		    entry = NULL;
+		    for (i = 0; i < modules_needed / sizeof(HMODULE); i++) {
+			FARPROC entry_found = GetProcAddress(modules[i], (char *) __stringVal(aString));
+			if (entry_found != NULL) {
+			    if (entry == NULL) {
+			        entry = entry_found;
+			    } else {
+				if (@global(Verbose) == true) {
+				    console_printf("Multiple symbols found for %s: %"_lx_" and %"_lx_"\n", __stringVal(aString), entry, entry_found);
+				}
+				entry = NULL;
+				break;
+			    }
+			}
+		    }
+		}
+            } else {
+	        entry = GetProcAddress(handle, (char *) __stringVal(aString));
+	    }
 	    if (entry != NULL) {
 		addr = (void *)entry;
 		if (@global(Verbose) == true) {
@@ -2386,7 +2423,7 @@
 			oldMethods keysAndValuesDo:[:selector :oldMethod|
 			    oldMethod
 				code:nil;
-				mclass:self.
+				mclass:newClass.
 			    oldMethod byteCode isNil ifTrue:[
 				"a compiled method, load the new code (addresses may have been changed)"
 				newMthd := newMethodDict at:selector ifAbsent:nil.
@@ -2899,20 +2936,25 @@
      it is your responsibility to fetch any init-functions and
      call them as appropriate.
      This function is not supported on all architectures.
+
+     The `pathNameOrFilename may be nil, then resulting
+     handle is for the main program itself.
     "
 
     |fn handle buffer pathName tempFile encodedPathName|
 
-    fn := pathNameOrFilename asFilename.
-    fn exists ifTrue:[
-        pathName := fn pathName.
-        self copyLibrariesWhenLoading ifTrue:[
-            fn copyTo:(tempFile := ParserFlags stcModulePath asFilename construct:fn baseName).
-            pathName := tempFile pathName.
+    pathNameOrFilename notNil ifTrue:[
+        fn := pathNameOrFilename asFilename.
+        fn exists ifTrue:[
+            pathName := fn pathName.
+            self copyLibrariesWhenLoading ifTrue:[
+                fn copyTo:(tempFile := ParserFlags stcModulePath asFilename construct:fn baseName).
+                pathName := tempFile pathName.
+            ].
+        ] ifFalse:[
+            "/ something like "kernel32.dll"; must be along the PATH setting
+            pathName := pathNameOrFilename asString.
         ].
-    ] ifFalse:[
-        "/ something like "kernel32.dll"; must be along the PATH setting
-        pathName := pathNameOrFilename asString.
     ].
 
     Verbose ifTrue:[
@@ -2924,7 +2966,7 @@
     handle := self handleForDynamicObject:encodedPathName.
     handle notNil ifTrue:[
         Verbose ifTrue:[
-            ('... ' , pathName , ' already loaded.') errorPrintCR.
+            ('... ' , pathName asString , ' already loaded.') errorPrintCR.
         ].
         ^ handle
     ].
@@ -2964,12 +3006,7 @@
                 ].
             ].
         ].
-        ('ObjectFileLoader [warning]: failed to load: ' , pathName) infoPrintCR.
-
-        "sr - no do not print to the Transcript!!    
-         it will corrupt the output of
-         expecco.exe --version"
-"/        Transcript showCR:('ObjectFileLoader [warning]: failed to load: ' , pathName).
+        Logger warning: 'failed to load ''%1''' with: pathName.
         ^ nil
     ].
 
@@ -3012,6 +3049,7 @@
     "
 
     "Modified: / 06-12-2011 / 15:42:16 / cg"
+    "Modified: / 06-09-2016 / 17:24:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 loadModulesFromListOfUndefined:list
@@ -3055,13 +3093,18 @@
 !
 
 primLoadDynamicObject:pathName into:anInfoBuffer
-    "load an object-file (map into my address space).
+    "Load an object-file (map into my address space).
      Return an OS-handle (whatever that is) - where some space
      (a 3-element array) has to be passed in for this.
      The first two entries are used in a machine dependent way,
      and callers may not depend on what is found there
      (instead, only pass around handles transparently).
-     This function is not supported on all architectures."
+     This function is not supported on all architectures.
+
+     `pathName` is a path to the object file. If nil, 
+     a special handle capable to resolve symbols in
+     'currenty loaded image' ir returned. 
+    "
 
 %{  /* CALLSUNLIMITEDSTACK(noWIN32) */
 
@@ -3145,6 +3188,20 @@
 # endif
 	RETURN ( anInfoBuffer );
     }
+    /*
+     * Unlike POSIX.1-2001 dlopen(), Windows has no such handle that
+     * would, when passed to GetProcAddress(), search current loaded image
+     * (i.e., all loaded .dlls and .exes). This has to be done by enumerating
+     * all loaded modules (HMODULE) and searching there. 
+     *
+     * Hence here we return a special 0 handle. This 0-handle is detected in
+     * #getSymbol:function:from: and handled there.
+     */
+    if (pathName == nil) {
+	__ArrayInstPtr(anInfoBuffer)->a_element[0] = __MKSMALLINT( 0 );
+	__ArrayInstPtr(anInfoBuffer)->a_element[1] = __MKSMALLINT( 0 );
+	RETURN ( anInfoBuffer );
+    }
     RETURN ( nil );
   }
 #endif
@@ -3285,7 +3342,7 @@
 	if (! handle) {
 	    errMsg = (char *) dlerror();
 	    if (@global(ErrorPrinting) == true) {
-		console_fprintf(stderr, "ObjectFileLoader [warning]: dlopen %s error:\n", __stringVal(pathName));
+                console_fprintf(stderr, "ObjectFileLoader [warning]: dlopen %s error:\n", pathName == nil ? "(nil)" : __stringVal(pathName));
 		console_fprintf(stderr, "    <%s>\n", errMsg);
 	    }
 	    @global(LastError) = @symbol(linkError);
@@ -3294,7 +3351,7 @@
 	}
 
 	if (@global(Verbose) == true) {
-	    console_fprintf(stderr, "ObjectFileLoader [info]: open %s handle = %"_lx_"\n", __stringVal(pathName), (INT)handle);
+            console_fprintf(stderr, "ObjectFileLoader [info]: open %s handle = %"_lx_"\n",  pathName == nil ? "(nil)" : __stringVal(pathName), (INT)handle);
 	}
 
 #if __POINTER_SIZE__ == 8
@@ -3435,6 +3492,8 @@
 %}.
     LastError := #notImplemented.
     ^ nil
+
+    "Modified: / 24-01-2016 / 22:06:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 primUnloadDynamicObject:aHandle
@@ -3777,6 +3836,9 @@
 				binaryClassLibraryFilename := packageDirOrNil / 'objbc' / shLibName.
 				binaryClassLibraryFilename exists ifFalse:[
 				    binaryClassLibraryFilename := packageDirOrNil / 'objvc' / shLibName.
+                                    binaryClassLibraryFilename exists ifFalse:[
+                                        binaryClassLibraryFilename := packageDirOrNil / 'objmingw' / shLibName.
+                                    ]
 				]
 			    ] ifFalse:[
 				binaryClassLibraryFilename := packageDirOrNil / 'objmingw' / shLibName.
@@ -3804,6 +3866,13 @@
 	].
     ].
     ^ binaryClassLibraryFilename
+
+    "
+    ObjectFileLoader binaryClassFilenameForPackage:'stx:goodies/libcairo' inDirectory: (Smalltalk getPackageDirectoryForPackage: 'stx:goodies/libcairo')
+
+    "
+
+    "Modified: / 19-02-2016 / 15:24:25 / jv"
 !
 
 canLoadObjectFiles
@@ -3829,10 +3898,16 @@
     |pathName|
 
     LoadedObjects isNil ifTrue:[
-	^ nil.
+        ^ nil.
     ].
-    pathName := pathNameOrFilename asFilename pathName.
+    pathNameOrFilename notNil ifTrue:[ 
+        pathName := pathNameOrFilename asFilename pathName.
+    ] ifFalse:[ 
+        pathName := nil.
+    ].
     ^ LoadedObjects at:pathName ifAbsent:nil.
+
+    "Modified: / 24-01-2016 / 21:59:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 handleFromID:id
@@ -4594,6 +4669,11 @@
 
 version_CVS
     ^ '$Header$'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
 
--- a/ParseNode.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/ParseNode.st	Sat Sep 24 06:43:04 2016 +0200
@@ -240,6 +240,14 @@
 
 codeOn:aStream inBlock:codeBlock for:aCompiler
     ^ self subclassResponsibility
+!
+
+codeSourcePosition:nr on:codeStream for:aCompiler
+    "generate source position information"
+
+    aCompiler codeSourcePosition:nr on:codeStream
+
+    "Created: / 31-05-2015 / 03:45:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !ParseNode methodsFor:'code generation helpers'!
--- a/ParseNodeValidator.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/ParseNodeValidator.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1,5 +1,7 @@
 "{ Package: 'stx:libcomp' }"
 
+"{ NameSpace: Smalltalk }"
+
 ParseNodeVisitor subclass:#ParseNodeValidator
 	instanceVariableNames:'stack source'
 	classVariableNames:''
@@ -172,3 +174,4 @@
 version_CVS
     ^ '$Header: /cvs/stx/stx/libcomp/ParseNodeValidator.st,v 1.8 2011-08-25 13:38:46 vrany Exp $'
 ! !
+
--- a/ParseNodeVisitor.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/ParseNodeVisitor.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1,3 +1,14 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libcomp' }"
 
 "{ NameSpace: Smalltalk }"
@@ -11,6 +22,20 @@
 
 !ParseNodeVisitor class methodsFor:'documentation'!
 
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
 documentation
 "
     a whitebox expandable abstract parsenode visitor.
--- a/Parser.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/Parser.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1411,7 +1411,9 @@
         ].
     ].
     nV notNil ifTrue:[
-        blocks := blocks select:[:aBlock | aBlock numVars == nV ].
+        blocks := blocks select:[:aBlock | 
+            (aBlock numVarsIncludingInlined: (m notNil and:[m hasCode and:[m bytecodes isNil]])) == nV 
+        ].
         blocks size == 1 ifTrue:[
             ^ blocks at:1
         ].
@@ -1436,43 +1438,9 @@
     ].
     ^ innerBlock.
 
-    "Created: 11.1.1997 / 23:29:13 / cg"
-    "Modified: 14.2.1997 / 16:51:25 / cg"
-!
-
-checkMethod:aString in:aClass ignoreErrors:ignoreErrors ignoreWarnings:ignoreWarnings
-    "parse a method in a given class.
-     Return a parser (if ok), nil (empty) or #Error (syntax).
-     The parser can be queried for selector, receiver, args, locals,
-     used selectors, modified instvars, referenced classvars etc.
-     The noErrors and noWarnings arguments specify if error and warning
-     messages should be sent to the Transcript or suppressed."
-
-    |parser tree|
-
-    aString isNil ifTrue:[^ nil].
-    parser := self for:(ReadStream on:aString) in:aClass.
-    parser ignoreErrors:ignoreErrors.
-    parser ignoreWarnings:ignoreWarnings.
-    tree := parser parseMethod.
-    "/ (parser errorFlag or:[tree == #Error]) ifTrue:[^ nil].
-
-    RBReadBeforeWrittenTester searchForReadBeforeWrittenIn:tree
-
-    "
-     self
-        checkMethod:'foo
-                        |local1 local2 local3|
-
-                        local1 := local2.
-                        ^ local3
-                    '
-        in:UndefinedObject
-        ignoreErrors:true
-        ignoreWarnings:true
-    "
-
-    "Modified: / 30.10.1997 / 16:38:31 / cg"
+    "Created: / 11-01-1997 / 23:29:13 / cg"
+    "Modified: / 14-02-1997 / 16:51:25 / cg"
+    "Modified (format): / 23-12-2015 / 17:33:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 parseExpression:aString
@@ -10360,6 +10328,14 @@
     ^ annotations collect:[:each | Array with:each key with:each arguments ].
 !
 
+argumentCount
+    "return the number of methodargs (valid after parsing spec)"
+
+    ^ methodArgs size
+
+    "Created: / 09-06-2015 / 21:53:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 classToLookForClassVars
     "helper - return the class to look for classVars.
      If there is a context in which we evaluate, the
@@ -11641,6 +11617,15 @@
     source := aCompiler currentSource.
     badName := source copyFrom:pos1 to:pos2.
 
+    (Smalltalk at:#RenameTemporaryRefactoring) isNil ifTrue:[
+        [
+            Smalltalk loadPackage: #'stx:goodies/refactoryBrowser/refactoring'
+        ] on: PackageLoadError do:[:err |  
+            Dialog warn:'Sorry - no refactoring support available'.
+            ^ self
+        ]
+    ].
+
     node := DoWhatIMeanSupport
                 findNodeForInterval:(pos1 to:pos2)
                 in:source.
@@ -11666,7 +11651,7 @@
         ^ nil
     ].
 
-    refactoring := RenameTemporaryRefactoring
+    refactoring := (Smalltalk at:#RenameTemporaryRefactoring)
                         renameTemporaryFrom:node sourceInterval
                         to:newName
                         in:nil
@@ -11679,6 +11664,8 @@
     refactoring checkPreconditions.
     refactoring transform.
     ^ refactoring newSource
+
+    "Modified: / 05-05-2016 / 00:23:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !Parser::CorrectByMakingValidHexConstant class methodsFor:'queries'!
@@ -12228,7 +12215,7 @@
             (masterParser ? self) ignorableParseError:'possibly unknown type: ', type allBold.
         ] ifFalse:[
             cls autoload.
-            (cls isSubclassOf:ExternalBytes) ifFalse:[
+            ((cls isSubclassOf:ExternalBytes) or:[(cls isSubclassOf:ExternalAddress)]) ifFalse:[
                 (masterParser ? self) ignorableParseError:'possibly wrong type: ', type allBold.
             ].
             type := cls name.
@@ -12238,6 +12225,7 @@
     ^ type
 
     "Modified: / 07-06-2007 / 13:14:59 / cg"
+    "Modified: / 06-07-2015 / 23:14:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 parseVWTypeOrExternalFunctionDeclarationFrom:aStream definitionType:definitionType knownDefinitions:dictionaryOfTypesOrNil lineNr:lineNr for:aParserOrNil
@@ -12506,6 +12494,11 @@
     ^ '$Header$'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$ Id $'
 ! !
--- a/ParserFlags.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/ParserFlags.st	Sat Sep 24 06:43:04 2016 +0200
@@ -127,12 +127,12 @@
     The class side provides correspondingly-named variables, which hold the default values.
 
     howTo_fileInVSE:
-        ParserFlags allowSTVExtensions:true.
-        ParserFlags allowSTVPrimitives:true.
-        ParserFlags allowSTXEOLComments:false.
+	ParserFlags allowSTVExtensions:true.
+	ParserFlags allowSTVPrimitives:true.
+	ParserFlags allowSTXEOLComments:false.
 
     for stx debugging:
-        STCKeepCIntermediate := true
+	STCKeepCIntermediate := true
 
 "
 ! !
@@ -1519,7 +1519,7 @@
 !ParserFlags class methodsFor:'class initialization'!
 
 initialize
-    |executablePath|
+    | executablePath topDirectory stcExe |
 
     Warnings := true.
     WarnUndeclared := true.
@@ -1610,30 +1610,98 @@
     DefineForMINGW := '__MINGW__'.
     DefineForMINGW32 := '__MINGW32__'.
     DefineForMINGW64 := '__MINGW64__'.
-    DefineForCLANG := '__CLANG__'.
+    DefineForCLANG := '__clang__'.
+
+    stcExe := OperatingSystem isMSWINDOWSlike ifTrue:['stc.exe'] ifFalse:['stc'].
 
     (executablePath := OperatingSystem pathOfSTXExecutable) notNil ifTrue:[
-	executablePath := executablePath asFilename directory.
-	(((executablePath / 'include') exists and:[(executablePath / 'stc') exists])
-	  or:[
-	    executablePath := executablePath directory.
-	    ((executablePath / 'include') exists and:[(executablePath / 'stc') exists])
-	      or:[
-		executablePath := executablePath directory.
-		((executablePath / 'include') exists and:[(executablePath / 'stc') exists])
-	      ]
-	   ]
-	) ifTrue:[
-	    self initializeSTCFlagsForTopDirectory: executablePath.
-	]
+        topDirectory := executablePath asFilename directory.
+        (((topDirectory / 'include') exists and:[(topDirectory / 'stc') exists or:[(topDirectory / 'bin' / stcExe) exists]])
+          or:[
+            topDirectory := topDirectory directory.
+            ((topDirectory / 'include') exists and:[(topDirectory / 'stc') exists or:[(topDirectory / 'bin' / stcExe) exists]])
+              or:[
+                topDirectory := topDirectory directory.
+                ((topDirectory / 'include') exists and:[(topDirectory / 'stc') exists or:[(topDirectory / 'bin' / stcExe) exists]])
+              ]
+           ]
+        ) ifTrue:[
+            self initializeSTCFlagsForTopDirectory: topDirectory.
+        ]
     ].
 
+
+    self useGnuC ifTrue:[ 
+        self initializeSTCFlagsForGCC.
+    ].
+    self useMingw32 ifTrue:[ 
+        self initializeSTCFlagsForMINGW32.
+    ].
+    self useMingw64 ifTrue:[ 
+        self initializeSTCFlagsForMINGW64.
+    ].
+    
+
+
+
     "
      ParserFlags initialize
     "
 
     "Modified: / 09-08-2006 / 18:47:18 / fm"
     "Modified: / 31-01-2012 / 12:06:32 / cg"
+    "Modified: / 06-01-2016 / 22:25:30 / jv"
+!
+
+initializeSTCFlagsForGCC
+    self ccPath: 'gcc'.
+    self linkCommand: 'gcc'.
+    ExternalAddress pointerSize == 4 ifTrue:[
+        self linkArgs: '-m32'.
+        self linkSharedArgs: '-shared -m32'
+    ] ifFalse:[ 
+        self linkArgs: '-m64'.
+        self linkSharedArgs: '-shared -m64'
+    ].
+
+    "Created: / 09-12-2015 / 22:10:52 / jv"
+    "Modified: / 03-02-2016 / 23:48:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+initializeSTCFlagsForMINGW32
+    | mingwDirs mingwDir |
+
+    mingwDirs := Array with: (OperatingSystem getEnvironment: 'MINGW_DIR')
+                       with: 'C:\MSYS64\MINGW32' 
+                       with: 'C:\MINGW'.        
+    mingwDir := mingwDirs detect:[:e | e notNil and:[e asFilename isDirectory ] ] ifNone:[ ^ self ].
+    mingwDir := mingwDir asFilename.
+
+    self ccPath: (mingwDir / 'bin' / 'gcc') pathName.
+    self linkCommand: (mingwDir / 'bin' / 'gcc') pathName.
+    self linkArgs: ''.
+    self linkSharedArgs: '-shared'
+
+    "Created: / 09-12-2015 / 22:00:19 / jv"
+    "Modified: / 17-06-2016 / 16:39:41 / jv"
+!
+
+initializeSTCFlagsForMINGW64
+    | mingwDirs mingwDir |
+
+    mingwDirs := Array with: (OperatingSystem getEnvironment: 'MINGW_DIR')  
+                       with: 'C:\MSYS64\MINGW64'
+                       with: 'C:\MINGW64'.        
+    mingwDir := mingwDirs detect:[:e | e notNil and:[e asFilename isDirectory ] ] ifNone:[ ^ self ].
+    mingwDir := mingwDir asFilename.
+
+    self ccPath: (mingwDir / 'bin' / 'gcc') pathName.
+    self linkCommand: (mingwDir / 'bin' / 'gcc') pathName.
+    self linkArgs: ''.
+    self linkSharedArgs: '-shared'
+
+    "Created: / 09-12-2015 / 22:07:25 / jv"
+    "Modified: / 17-06-2016 / 16:39:36 / jv"
 !
 
 initializeSTCFlagsForTopDirectory:topDirArg
@@ -1641,9 +1709,7 @@
      notice: for now, can only initialize for borland+windows or linux;
      visualC setup still fails."
 
-    |topDir topDirName vcTop sdkTop bccTop mingwTop
-     borlandDir useBorlandC useVisualC useMingw32 useMingw64
-     programFiles archArg picArg|
+    |topDir topDirName stcExe stcPath |
 
     topDir := topDirArg.
     OperatingSystem isMSWINDOWSlike ifTrue:[
@@ -1661,193 +1727,36 @@
         STCModulePath := Filename tempDirectory constructString:'modules'.
     ].
 
-    (topDir construct:'stc') exists ifFalse:[
-        ('ParserFlags [warning]: stc not found in "',topDirName,'"') infoPrintCR.
-        'ParserFlags [warning]: stc-compiling (primitive code) will not work in the browser' infoPrintCR.
-        STCCompilation := #never.
-    ].
-
-    OperatingSystem isMSWINDOWSlike ifTrue:[
-        useBorlandC := useVisualC := useMingw32 := useMingw64 := false.
-        programFiles := OperatingSystem getEnvironment:'ProgramFiles'.
-        programFiles isEmptyOrNil ifTrue:[ programFiles := 'C:\Program Files' ].
-
-        STCCompilationIncludes := '-I',topDirName,'\include -I',topDirName,'\libopengl'.
-
-        ExternalAddress pointerSize == 4 ifFalse:[
-            bccTop := nil
-        ] ifTrue:[
-            (bccTop := BCCTop) isNil ifTrue:[
-                borlandDir := OperatingSystem getEnvironment:'BCCDIR'.
-                borlandDir isEmptyOrNil ifTrue:[ borlandDir := 'C:\Borland\bcc55' ].
-                bccTop := {
-                            (borlandDir) .
-                            (programFiles , '\Borland\bcc55') .
-                            (programFiles , '\bcc55') .
-                          } detect:[:path | path asFilename exists and:[(path asFilename construct:'include') exists]]
-                             ifNone:nil.
-            ].
-        ].
-
-        STCCompilationDefines := '-DWIN32'.
-
-        (bccTop notNil and:[bccTop asFilename exists]) ifTrue:[
-            STCCompilationIncludes := STCCompilationIncludes,' -I',bccTop,'\Include'.
-            LibDirectory := topDirName,'\lib\bc'.
-            LinkArgs := '-L',topDirName,'\lib\bc'.
-            LinkArgs := LinkArgs,' -L',bccTop,'\Lib -r -c -ap -Tpd -Gi -w-dup'.
-            CCPath := 'bcc32'.
-            MakeCommand := 'bmake'.
-            LinkCommand := 'ilink32'.
-            CCCompilationOptions := '-w-'.
-            useBorlandC := true.
+    stcExe := OperatingSystem isMSWINDOWSlike ifTrue:['stc.exe'] ifFalse:['stc'].
+
+    (stcPath := topDir / 'stc' / stcExe) exists ifTrue:[
+        "/ build-tree environment
+        STCPath := stcPath pathName.        
+    ] ifFalse:[
+        (stcPath := topDir / 'bin' / stcExe) exists ifTrue:[
+            "/ Packaged environment
+            STCPath := stcPath pathName.        
         ] ifFalse:[
-            ExternalAddress pointerSize == 4 ifFalse:[
-                vcTop := nil.
-            ] ifTrue:[
-                (vcTop := VCTop) isNil ifTrue:[
-                    vcTop := {
-                                (programFiles,'\Microsoft Visual Studio 13.0\VC') .
-                                (programFiles,'\Microsoft Visual Studio 12.0\VC') .
-                                (programFiles,'\Microsoft Visual Studio 11.0\VC') .
-                                (programFiles,'\Microsoft Visual Studio 10.0\VC') .
-                                (programFiles,'\Microsoft Visual Studio 9.0\VC' ) .
-                             } detect:[:path | path asFilename exists and:[(path asFilename construct:'bin/cl.exe') exists]]
-                               ifNone:nil.
-                ].
-            ].
-            (vcTop notNil and:[vcTop asFilename exists]) ifTrue:[
-                useVisualC := true.
-                STCCompilationIncludes := STCCompilationIncludes,' -I',vcTop,'include'.
-
-                (sdkTop := SDKTop) isNil ifTrue:[
-                    sdkTop := {
-                                (programFiles,'\Microsoft SDKs\Windows\v9.0A') .
-                                (programFiles,'\Microsoft SDKs\Windows\v8.0A') .
-                                (programFiles,'\Microsoft SDKs\Windows\v8.0A') .
-                                (programFiles,'\Microsoft SDKs\Windows\v7.0A') .
-                                (programFiles,'\Microsoft SDKs\Windows\v6.0A') .
-                             }  detect:[:path | path asFilename exists and:[(path asFilename construct:'include') exists]] ifNone:nil.
-                ].
-                (sdkTop notNil and:[sdkTop asFilename exists]) ifTrue:[
-                    STCCompilationIncludes := STCCompilationIncludes,' -I',sdkTop,'\include'.
-                ].
-                LibDirectory := topDirName,'\lib\vc'.
-                LinkArgs := '-L',topDirName,'\lib\vc'.
-                LinkArgs := LinkArgs,' -r -c -ap -Tpd -Gi -w-dup'.
-                CCPath := vcTop,'\bin\cl.exe'.
-                LinkCommand := 'ilink32'.
-                MakeCommand := 'vcmake'.
-                CCCompilationOptions := '/nologo /ZI  /w /GF /EHsc /FR.\objvc\'.
-            ] ifFalse:[
-                "/ add definitions for lcc, mingc etc.
-                "/ STCCompilationIncludes := STCCompilationIncludes,' -IC:\xxxxx\Include'.
-                ExternalAddress pointerSize == 4 ifTrue:[
-                    (mingwTop := MingwTop) isNil ifTrue:[
-                        mingwTop := {
-                                    (programFiles,'\mingw') .
-                                    (programFiles,'\mingw') .
-                                    ('c:\mingw32') .
-                                    ('c:\mingw') .
-                                 } detect:[:path | path asFilename exists and:[(path asFilename construct:'bin/gcc.exe') exists]]
-                                   ifNone:nil.
-                    ].
-                    (mingwTop notNil and:[mingwTop asFilename exists]) ifTrue:[
-                        useMingw32 := true.
-                        STCCompilationDefines := STCCompilationDefines,' -D__MINGW32__'.
-                        CCCompilationOptions := '-w32'.
-                    ].
-                ] ifFalse:[
-                    (mingwTop := MingwTop) isNil ifTrue:[
-                        mingwTop := {
-                                    (programFiles,'\mingw64') .
-                                    (programFiles,'\mingw') .
-                                    ('c:\mingw64') .
-                                    ('c:\mingw') .
-                                 } detect:[:path | path asFilename exists and:[(path asFilename construct:'bin/gcc.exe') exists]]
-                                   ifNone:nil.
-                    ].
-                    (mingwTop notNil and:[mingwTop asFilename exists]) ifTrue:[
-                        STCCompilationDefines := STCCompilationDefines,' -D__MINGW64__'.
-                        "/ CCCompilationOptions := '-w64'.
-                    ].
-                ].
-                (mingwTop notNil and:[mingwTop asFilename exists]) ifTrue:[
-                    STCCompilationDefines := STCCompilationDefines,' -D__MINGW__'.
-                    CCPath := mingwTop,'\bin\gcc.exe'.
-                    LinkCommand := 'gcc'.
-                    MakeCommand := 'mingwmake'.
-                    LibDirectory := topDirName,'\lib\mingw'.
-                    LinkArgs := '-L',topDirName,'\lib\mingw'.
-                    "/ LinkArgs := LinkArgs,' -r -c -ap -Tpd -Gi -w-dup'.
-                ].
-            ].
-        ].
-        STCCompilationOptions := '+optinline +inlineNew'.
-        (topDirName,'\stc\stc.exe') asFilename exists ifTrue:[
-            STCPath := (topDirName,'\stc\stc.exe').
-        ] ifFalse:[
-            STCPath := 'stc.exe'.
-        ].
-        LibPath := ''.
-        SearchedLibraries := #('import32.lib').
-        "/ SearchedLibraries := #('import32.lib' 'glu32.lib' 'opengl32.lib').
-    ] ifFalse:[
-        STCCompilationIncludes := '-I',topDirName,'/include'.
-        STCCompilationDefines := ''.
-        STCCompilationOptions := '+optinline +inlineNew'.
-        STCPath := topDirName,'/stc/stc'.
-
-        archArg := picArg := ''.
-        (ExternalAddress pointerSize == 4) ifTrue:[
-            archArg := ' -m32'
-        ] ifFalse:[
-            archArg := ' -m64'.            "gcc -m64 needs -fPIC to make a shared library"
-            picArg := ' -fPIC'.
-        ].
-        CCCompilationOptions := OperatingSystem getCPUDefine,
-                                ' -D', self usedCompilerDefine,
-                                ' ', OperatingSystem getOSDefine,
-                                ' ', '-O', archArg, picArg.
-        ParserFlags useClang ifTrue:[
-            CCPath := 'clang'
-        ] ifFalse:[
-            ParserFlags useGnuC ifTrue:[
-                CCPath := 'gcc'
-            ] ifFalse:[
-                CCPath := 'cc'
-            ].
-        ].
-        LinkArgs := archArg.
-        LinkCommand := CCPath.
-        LinkSharedArgs := '-shared'.
-
-        OperatingSystem isOSXlike ifTrue:[
-            LinkSharedArgs := '-shared -mmacosx-version-min=10.3 -arch x86_64 librun.so'.
-            CCCompilationOptions := CCCompilationOptions ,' -mmacosx-version-min=10.3' 
-        ].    
-        LibPath := ''.
-        SearchedLibraries := #().
-        MakeCommand := 'make'.
+            Logger warning: 'stc not found in "%1"' with: topDirName.
+            Logger warning: 'stc-compiling (primitive code) will not work in the browser'. 
+            STCCompilation := #never.
+        ]
     ].
 
-    Smalltalk infoPrinting ifTrue:[
-        'ParserFlags [info]:' infoPrintCR.
-        '  STC Setup:' infoPrintCR.
-        ('    STCCompilationDefines: ',STCCompilationDefines asString) infoPrintCR.
-        ('    CCPath: ',CCPath asString) infoPrintCR.
-        ('    CCCompilationOptions: ',CCCompilationOptions asString) infoPrintCR.
-        ('    LinkCommand: ',LinkCommand asString) infoPrintCR.
-        ('    MakeCommand: ',MakeCommand asString) infoPrintCR.
-        ('    LinkArgs: ',LinkArgs asString) infoPrintCR.
-    ].
-
+
+    STCCompilationOptions := '+optinline +inlineNew'.
+    LibPath := ''.
+    SearchedLibraries := #().
+    MakeCommand := 'make'
+    .
     "
      ParserFlags initializeSTCFlagsForTopDirectory:'../..'
     "
 
     "Modified: / 09-08-2006 / 18:47:18 / fm"
     "Created: / 06-08-2011 / 19:47:47 / cg"
+    "Modified: / 09-12-2015 / 17:03:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 06-01-2016 / 22:45:09 / jv"
 ! !
 
 !ParserFlags methodsFor:'accessing'!
@@ -2802,6 +2711,11 @@
 
 version_CVS
     ^ '$Header$'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
 
--- a/PluggableParseNodeVisitor.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/PluggableParseNodeVisitor.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1,3 +1,14 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libcomp' }"
 
 "{ NameSpace: Smalltalk }"
@@ -11,6 +22,20 @@
 
 !PluggableParseNodeVisitor class methodsFor:'documentation'!
 
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
 documentation
 "
     a pluggable node visitor.
--- a/STCCompilerInterface.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/STCCompilerInterface.st	Sat Sep 24 06:43:04 2016 +0200
@@ -20,7 +20,8 @@
 	instanceVariableNames:'originator parserFlags initName theNonMetaclassToCompileFor
 		classToCompileFor stFileName cFileName oFileName stcFlags cFlags
 		stcPath ccPath requestor methodCategory executionStatus package'
-	classVariableNames:'SequenceNumber Verbose KeepIntermediateFiles'
+	classVariableNames:'SequenceNumber Verbose KeepIntermediateFiles
+		BuiltinCIncludeDirectories'
 	poolDictionaries:''
 	category:'System-Compiler'
 !
@@ -50,6 +51,56 @@
 
 !STCCompilerInterface class methodsFor:'accessing'!
 
+builtinCFlags
+    "Return C compiler flags that are always passed to the C compiler
+     when a (ST)C file is compiled."
+
+    ^ OperatingSystem getCPUDefine , ' ', OperatingSystem getOSDefine
+
+    "Created: / 04-12-2015 / 16:41:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+builtinCIncludeDirectories
+    "Return C compiler include directories that are always passed to the C compiler
+     when a (ST)C file is compiled."
+
+    BuiltinCIncludeDirectories isNil ifTrue:[ 
+        | executablePath |
+        (executablePath := OperatingSystem pathOfSTXExecutable) notNil ifTrue:[
+            executablePath := executablePath asFilename directory.
+            ((executablePath / 'include' / 'stc.h') exists
+              or:[((executablePath := executablePath directory) / 'include' / 'stc.h') exists
+              or:[((executablePath := executablePath directory) / 'include' / 'stc.h') exists]])
+                ifTrue:[
+                    BuiltinCIncludeDirectories := '-I' , (executablePath / 'include') pathName.
+                    ^ BuiltinCIncludeDirectories
+                ]
+        ].
+        ^ ''
+    ].
+    ^ BuiltinCIncludeDirectories
+
+    "
+    STCCompilerInterface builtinCIncludeDirectories
+    "
+
+    "Created: / 09-12-2015 / 16:54:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+builtinCIncludeDirectories: aString
+    "Set C compiler include directories that are always passed to the C compiler
+     when a (ST)C file is compiled. 
+     This is an entry for init scripts for custom Smalltalk/X distributions which use
+     different directory layout than just a plain St/X worktree (such as Smalltalk/X jv-branch).
+
+     Note, that this is a string, so it must include '-I'
+     "
+
+     BuiltinCIncludeDirectories := aString
+
+    "Created: / 09-12-2015 / 16:59:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 stcPathOf:command 
     "return the path to an stc command, or nil if not found."
 
@@ -105,6 +156,13 @@
     "if on, trace command execution on the Transcript"
 
     Verbose := aBoolean
+
+    "
+    STCCompilerInterface verbose: true.
+    STCCompilerInterface verbose: false.
+    "
+
+    "Modified (comment): / 04-12-2015 / 16:44:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !STCCompilerInterface class methodsFor:'class initialization'!
@@ -535,6 +593,21 @@
     env at:'LANG' put:'C'.
     env at:'LC_MESSAGES' put:'C'.
 
+    "/ When compiling using MINGW32/64, the bin directory
+    "/ must be in path since compiler uses some .dlls found there
+    "/ (an otherwise, they won't be found)
+    (ParserFlags useMingw32 or:[ ParserFlags useMingw64 ]) ifTrue:[
+        "/ JV @ 2016-01-04: I dunno why, but adding new, fixed path to env variable passed
+        "/ to executeCommand:...environment:... below does not work.
+        "/ Modifying this very process own environment works, though,
+        | path |
+
+        path := OperatingSystem getEnvironment: 'PATH'.
+        (path includesSubstring: ccPath) ifFalse:[
+            OperatingSystem setEnvironment: 'PATH' to: path  , ';', ccPath asFilename directory pathName
+        ].
+    ].
+
     ok := OperatingSystem 
                 executeCommand:command 
                 inputFrom:nil
@@ -569,6 +642,7 @@
     ^ ok
 
     "Created: / 07-11-2006 / 12:14:51 / cg"
+    "Modified: / 04-01-2016 / 21:12:56 / jv"
 !
 
 compileToS
@@ -873,7 +947,7 @@
 !
 
 setupCompilationCommandArguments
-    |stFn mapFileName libFileName def libDir incDir incDirArg defs incl opts|
+    |stFn libDir incDir incDirArg defs incl opts|
 
     parserFlags isNil ifTrue:[ parserFlags := ParserFlags new].
 
@@ -883,8 +957,6 @@
 "/    ParserFlags useBorlandC ifTrue:[
 "/        cFileName := (stFn withSuffix:'sc') name. 
 "/    ].
-    mapFileName := (stFn withSuffix:'map') name. 
-    libFileName := (stFn withSuffix:'lib') name. 
     oFileName asFilename delete.
     cFileName asFilename delete.
 
@@ -893,17 +965,14 @@
     initName notEmptyOrNil ifTrue:[
         stcFlags := stcFlags,' -N' , initName .
     ].
-    cFlags := OperatingSystem getOSDefine.
-    cFlags isNil ifTrue:[
-        cFlags := ''
-    ].
-    (def := OperatingSystem getCPUDefine) notEmptyOrNil ifTrue:[
-        cFlags := cFlags , ' ' , def
-    ].
+    cFlags := self class builtinCFlags.
 
     (defs := parserFlags stcCompilationDefines) notEmptyOrNil ifTrue:[
         cFlags := cFlags , ' ' , defs
     ].
+    stcFlags := stcFlags , ' ', self class builtinCIncludeDirectories.
+    cFlags := cFlags , ' ', self class builtinCIncludeDirectories.
+
     (incl := parserFlags stcCompilationIncludes) notEmptyOrNil ifTrue:[
         stcFlags := incl , ' ' , stcFlags.
         cFlags := cFlags , ' ' , incl.
@@ -932,6 +1001,7 @@
 
     "Created: / 07-11-2006 / 12:24:47 / cg"
     "Modified: / 07-11-2006 / 13:58:54 / cg"
+    "Modified: / 09-12-2015 / 17:00:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !STCCompilerInterface class methodsFor:'documentation'!
@@ -942,6 +1012,11 @@
 
 version_CVS
     ^ '$Header$'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
 
--- a/SelectorNode.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/SelectorNode.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1,5 +1,18 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libcomp' }"
 
+"{ NameSpace: Smalltalk }"
+
 ParseNode subclass:#SelectorNode
 	instanceVariableNames:'value'
 	classVariableNames:''
@@ -9,6 +22,20 @@
 
 !SelectorNode class methodsFor:'documentation'!
 
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
 documentation
 "
     A (helper) node that represents a selector (or its part).
--- a/Switch.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/Switch.st	Sat Sep 24 06:43:04 2016 +0200
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libcomp' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#Switch
 	instanceVariableNames:'expressions values default'
 	classVariableNames:''
--- a/SyntaxHighlighter.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/SyntaxHighlighter.st	Sat Sep 24 06:43:04 2016 +0200
@@ -66,6 +66,12 @@
     ^ #method
 
     "Created: / 27-07-2012 / 22:01:42 / cg"
+!
+
+codeAspectStatements
+    ^ #statements
+
+    "Created: / 22-02-2016 / 20:57:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !SyntaxHighlighter class methodsFor:'highlighting'!
@@ -713,5 +719,10 @@
 
 version_CVS
     ^ '$Header$'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
--- a/UndefinedSuperclassError.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/UndefinedSuperclassError.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1,5 +1,18 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libcomp' }"
 
+"{ NameSpace: Smalltalk }"
+
 ParseError subclass:#UndefinedSuperclassError
 	instanceVariableNames:''
 	classVariableNames:''
@@ -7,6 +20,21 @@
 	category:'System-Compiler'
 !
 
+!UndefinedSuperclassError class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
 
 !UndefinedSuperclassError class methodsFor:'documentation'!
 
--- a/UndefinedVariableError.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/UndefinedVariableError.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1,5 +1,18 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libcomp' }"
 
+"{ NameSpace: Smalltalk }"
+
 ParseError subclass:#UndefinedVariableError
 	instanceVariableNames:''
 	classVariableNames:''
@@ -7,6 +20,21 @@
 	category:'System-Compiler'
 !
 
+!UndefinedVariableError class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
 
 !UndefinedVariableError class methodsFor:'documentation'!
 
--- a/UndefinedVariableNotification.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/UndefinedVariableNotification.st	Sat Sep 24 06:43:04 2016 +0200
@@ -1,5 +1,18 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libcomp' }"
 
+"{ NameSpace: Smalltalk }"
+
 Notification subclass:#UndefinedVariableNotification
 	instanceVariableNames:'parser'
 	classVariableNames:''
@@ -7,6 +20,21 @@
 	category:'System-Compiler'
 !
 
+!UndefinedVariableNotification class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
 
 !UndefinedVariableNotification methodsFor:'accessing'!
 
--- a/bc.mak	Fri Sep 23 07:06:30 2016 +0200
+++ b/bc.mak	Sat Sep 24 06:43:04 2016 +0200
@@ -1,142 +1,151 @@
-# $Header$
-#
-# DO NOT EDIT
-# automagically generated from the projectDefinition: stx_libcomp.
-#
-# Warning: once you modify this file, do not rerun
-# stmkmp or projectDefinition-build again - otherwise, your changes are lost.
-#
-# Notice, that the name bc.mak is historical (from times, when only borland c was supported).
-# This file contains make rules for the win32 platform using either borland-bcc or visual-c.
-# It shares common definitions with the unix-make in Make.spec.
-# The bc.mak supports the following targets:
-#    bmake         - compile all st-files to a classLib (dll)
-#    bmake clean   - clean all temp files
-#    bmake clobber - clean all
-#
-# Historic Note:
-#  this used to contain only rules to make with borland
-#    (called via bmake, by "make.exe -f bc.mak")
-#  this has changed; it is now also possible to build using microsoft visual c
-#    (called via vcmake, by "make.exe -f bc.mak -DUSEVC")
-#
-TOP=..
-INCLUDE_TOP=$(TOP)\..
-
-
-# see stdHeader_bc for LIBCOMP_BASE
-LIB_BASE=$(LIBCOMP_BASE)
-
-
-!INCLUDE $(TOP)\rules\stdHeader_bc
-
-!INCLUDE Make.spec
-
-LIBNAME=libstx_libcomp
-MODULE_PATH=libcomp
-RESFILES=stx_libcompWINrc.$(RES)
-
-
-
-LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\lint -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\parser -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\refactoring -I$(INCLUDE_TOP)\stx\libbasic -I$(INCLUDE_TOP)\stx\libbasic3 -I$(INCLUDE_TOP)\stx\libtool2
-LOCALDEFINES=
-
-STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES) $(COMMONSYMBOLS) -varPrefix=$(LIBNAME)
-LOCALLIBS=
-
-OBJS= $(COMMON_OBJS) $(WIN32_OBJS)
-
-ALL::  classLibRule
-
-classLibRule: $(OUTDIR) $(OUTDIR)$(LIBNAME).dll
-
-!INCLUDE $(TOP)\rules\stdRules_bc
-
-# build all mandatory prerequisite packages (containing superclasses) for this package
-prereq:
-	pushd ..\libbasic & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
-
-
-
-
-
-
-
-test: $(TOP)\goodies\builder\reports\NUL
-	pushd $(TOP)\goodies\builder\reports & $(MAKE_BAT)
-	$(TOP)\goodies\builder\reports\report-runner.bat -D . -r Builder::TestReport -p $(PACKAGE)
-        
-clean::
-	-del *.$(CSUFFIX)
-
-
-# BEGINMAKEDEPEND --- do not remove this line; make depend needs it
-$(OUTDIR)Breakpoint.$(O) Breakpoint.$(C) Breakpoint.$(H): Breakpoint.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)BreakpointDescription.$(O) BreakpointDescription.$(C) BreakpointDescription.$(H): BreakpointDescription.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)BreakpointQuery.$(O) BreakpointQuery.$(C) BreakpointQuery.$(H): BreakpointQuery.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(STCHDR)
-$(OUTDIR)CompilationErrorHandler.$(O) CompilationErrorHandler.$(C) CompilationErrorHandler.$(H): CompilationErrorHandler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)CompilationErrorHandlerQuery.$(O) CompilationErrorHandlerQuery.$(C) CompilationErrorHandlerQuery.$(H): CompilationErrorHandlerQuery.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(STCHDR)
-$(OUTDIR)DoNotShowCompilerWarningAgainActionQuery.$(O) DoNotShowCompilerWarningAgainActionQuery.$(C) DoNotShowCompilerWarningAgainActionQuery.$(H): DoNotShowCompilerWarningAgainActionQuery.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(STCHDR)
-$(OUTDIR)DoNotShowCompilerWarningAgainForThisMethodActionQuery.$(O) DoNotShowCompilerWarningAgainForThisMethodActionQuery.$(C) DoNotShowCompilerWarningAgainForThisMethodActionQuery.$(H): DoNotShowCompilerWarningAgainForThisMethodActionQuery.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(STCHDR)
-$(OUTDIR)DoNotShowCompilerWarningAgainForThisReceiverSelectorActionQuery.$(O) DoNotShowCompilerWarningAgainForThisReceiverSelectorActionQuery.$(C) DoNotShowCompilerWarningAgainForThisReceiverSelectorActionQuery.$(H): DoNotShowCompilerWarningAgainForThisReceiverSelectorActionQuery.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(STCHDR)
-$(OUTDIR)InstrumentationContext.$(O) InstrumentationContext.$(C) InstrumentationContext.$(H): InstrumentationContext.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)InstrumentationInfo.$(O) InstrumentationInfo.$(C) InstrumentationInfo.$(H): InstrumentationInfo.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)InstrumentedMethod.$(O) InstrumentedMethod.$(C) InstrumentedMethod.$(H): InstrumentedMethod.st $(INCLUDE_TOP)\stx\libbasic\CompiledCode.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutableFunction.$(H) $(INCLUDE_TOP)\stx\libbasic\Method.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)LazyMethod.$(O) LazyMethod.$(C) LazyMethod.$(H): LazyMethod.st $(INCLUDE_TOP)\stx\libbasic\CompiledCode.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutableFunction.$(H) $(INCLUDE_TOP)\stx\libbasic\Method.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ObjectFileHandle.$(O) ObjectFileHandle.$(C) ObjectFileHandle.$(H): ObjectFileHandle.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ObjectFileLoader.$(O) ObjectFileLoader.$(C) ObjectFileLoader.$(H): ObjectFileLoader.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ParseError.$(O) ParseError.$(C) ParseError.$(H): ParseError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)ParseNode.$(O) ParseNode.$(C) ParseNode.$(H): ParseNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ParseNodeVisitor.$(O) ParseNodeVisitor.$(C) ParseNodeVisitor.$(H): ParseNodeVisitor.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ParseWarning.$(O) ParseWarning.$(C) ParseWarning.$(H): ParseWarning.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ParserFlags.$(O) ParserFlags.$(C) ParserFlags.$(H): ParserFlags.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ProgramNodeBuilder.$(O) ProgramNodeBuilder.$(C) ProgramNodeBuilder.$(H): ProgramNodeBuilder.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ProgramNodeEnumerator.$(O) ProgramNodeEnumerator.$(C) ProgramNodeEnumerator.$(H): ProgramNodeEnumerator.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)STCCompilerInterface.$(O) STCCompilerInterface.$(C) STCCompilerInterface.$(H): STCCompilerInterface.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)Scanner.$(O) Scanner.$(C) Scanner.$(H): Scanner.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)SourceFileLoader.$(O) SourceFileLoader.$(C) SourceFileLoader.$(H): SourceFileLoader.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)Structure.$(O) Structure.$(C) Structure.$(H): Structure.st $(INCLUDE_TOP)\stx\libbasic\Behavior.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)UndefinedVariable.$(O) UndefinedVariable.$(C) UndefinedVariable.$(H): UndefinedVariable.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)UndefinedVariableNotification.$(O) UndefinedVariableNotification.$(C) UndefinedVariableNotification.$(H): UndefinedVariableNotification.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)Variable.$(O) Variable.$(C) Variable.$(H): Variable.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)stx_libcomp.$(O) stx_libcomp.$(C) stx_libcomp.$(H): stx_libcomp.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(STCHDR)
-$(OUTDIR)AssignmentNode.$(O) AssignmentNode.$(C) AssignmentNode.$(H): AssignmentNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
-$(OUTDIR)BlockNode.$(O) BlockNode.$(C) BlockNode.$(H): BlockNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
-$(OUTDIR)BreakpointNode.$(O) BreakpointNode.$(C) BreakpointNode.$(H): BreakpointNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
-$(OUTDIR)CompilationError.$(O) CompilationError.$(C) CompilationError.$(H): CompilationError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseError.$(H) $(STCHDR)
-$(OUTDIR)EvalScriptingErrorHandler.$(O) EvalScriptingErrorHandler.$(C) EvalScriptingErrorHandler.$(H): EvalScriptingErrorHandler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\CompilationErrorHandler.$(H) $(STCHDR)
-$(OUTDIR)MessageNode.$(O) MessageNode.$(C) MessageNode.$(H): MessageNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
-$(OUTDIR)MethodNode.$(O) MethodNode.$(C) MethodNode.$(H): MethodNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
-$(OUTDIR)ParseErrorNode.$(O) ParseErrorNode.$(C) ParseErrorNode.$(H): ParseErrorNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
-$(OUTDIR)Parser.$(O) Parser.$(C) Parser.$(H): Parser.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
-$(OUTDIR)PluggableParseNodeVisitor.$(O) PluggableParseNodeVisitor.$(C) PluggableParseNodeVisitor.$(H): PluggableParseNodeVisitor.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNodeVisitor.$(H) $(STCHDR)
-$(OUTDIR)PrimaryNode.$(O) PrimaryNode.$(C) PrimaryNode.$(H): PrimaryNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
-$(OUTDIR)ProgramNode.$(O) ProgramNode.$(C) ProgramNode.$(H): ProgramNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
-$(OUTDIR)SelectorNode.$(O) SelectorNode.$(C) SelectorNode.$(H): SelectorNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
-$(OUTDIR)StatementNode.$(O) StatementNode.$(C) StatementNode.$(H): StatementNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
-$(OUTDIR)TextCollectingCompilationErrorHandler.$(O) TextCollectingCompilationErrorHandler.$(C) TextCollectingCompilationErrorHandler.$(H): TextCollectingCompilationErrorHandler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\CompilationErrorHandler.$(H) $(STCHDR)
-$(OUTDIR)UndefinedSuperclassError.$(O) UndefinedSuperclassError.$(C) UndefinedSuperclassError.$(H): UndefinedSuperclassError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseError.$(H) $(STCHDR)
-$(OUTDIR)UndefinedVariableError.$(O) UndefinedVariableError.$(C) UndefinedVariableError.$(H): UndefinedVariableError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseError.$(H) $(STCHDR)
-$(OUTDIR)WarningCompilationErrorHandler.$(O) WarningCompilationErrorHandler.$(C) WarningCompilationErrorHandler.$(H): WarningCompilationErrorHandler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\CompilationErrorHandler.$(H) $(STCHDR)
-$(OUTDIR)AbstractSyntaxHighlighter.$(O) AbstractSyntaxHighlighter.$(C) AbstractSyntaxHighlighter.$(H): AbstractSyntaxHighlighter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
-$(OUTDIR)BinaryNode.$(O) BinaryNode.$(C) BinaryNode.$(H): BinaryNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\MessageNode.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
-$(OUTDIR)BreakpointAnalyzer.$(O) BreakpointAnalyzer.$(C) BreakpointAnalyzer.$(H): BreakpointAnalyzer.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
-$(OUTDIR)ByteCodeCompiler.$(O) ByteCodeCompiler.$(C) ByteCodeCompiler.$(H): ByteCodeCompiler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
-$(OUTDIR)CascadeNode.$(O) CascadeNode.$(C) CascadeNode.$(H): CascadeNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\MessageNode.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
-$(OUTDIR)ConstantNode.$(O) ConstantNode.$(C) ConstantNode.$(H): ConstantNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\PrimaryNode.$(H) $(STCHDR)
-$(OUTDIR)Explainer.$(O) Explainer.$(C) Explainer.$(H): Explainer.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
-$(OUTDIR)PrimitiveNode.$(O) PrimitiveNode.$(C) PrimitiveNode.$(H): PrimitiveNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\StatementNode.$(H) $(STCHDR)
-$(OUTDIR)ReturnNode.$(O) ReturnNode.$(C) ReturnNode.$(H): ReturnNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\StatementNode.$(H) $(STCHDR)
-$(OUTDIR)SelfNode.$(O) SelfNode.$(C) SelfNode.$(H): SelfNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\PrimaryNode.$(H) $(STCHDR)
-$(OUTDIR)UnaryNode.$(O) UnaryNode.$(C) UnaryNode.$(H): UnaryNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\MessageNode.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
-$(OUTDIR)VariableNode.$(O) VariableNode.$(C) VariableNode.$(H): VariableNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\PrimaryNode.$(H) $(STCHDR)
-$(OUTDIR)ByteCodeCompilerWithBreakpointSupport.$(O) ByteCodeCompilerWithBreakpointSupport.$(C) ByteCodeCompilerWithBreakpointSupport.$(H): ByteCodeCompilerWithBreakpointSupport.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ByteCodeCompiler.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
-$(OUTDIR)CodeCoverageHighlighter.$(O) CodeCoverageHighlighter.$(C) CodeCoverageHighlighter.$(H): CodeCoverageHighlighter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\AbstractSyntaxHighlighter.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
-$(OUTDIR)Decompiler.$(O) Decompiler.$(C) Decompiler.$(H): Decompiler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ByteCodeCompiler.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
-$(OUTDIR)ECompletionConstantNode.$(O) ECompletionConstantNode.$(C) ECompletionConstantNode.$(H): ECompletionConstantNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ConstantNode.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\PrimaryNode.$(H) $(STCHDR)
-$(OUTDIR)InstrumentingCompiler.$(O) InstrumentingCompiler.$(C) InstrumentingCompiler.$(H): InstrumentingCompiler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ByteCodeCompiler.$(H) $(INCLUDE_TOP)\stx\libcomp\InstrumentationInfo.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
-$(OUTDIR)SuperNode.$(O) SuperNode.$(C) SuperNode.$(H): SuperNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\PrimaryNode.$(H) $(INCLUDE_TOP)\stx\libcomp\SelfNode.$(H) $(STCHDR)
-$(OUTDIR)SyntaxHighlighter.$(O) SyntaxHighlighter.$(C) SyntaxHighlighter.$(H): SyntaxHighlighter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\AbstractSyntaxHighlighter.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
-$(OUTDIR)extensions.$(O): extensions.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-
-# ENDMAKEDEPEND --- do not remove this line
+# $Header$
+#
+# DO NOT EDIT
+# automagically generated from the projectDefinition: stx_libcomp.
+#
+# Warning: once you modify this file, do not rerun
+# stmkmp or projectDefinition-build again - otherwise, your changes are lost.
+#
+# Notice, that the name bc.mak is historical (from times, when only borland c was supported).
+# This file contains make rules for the win32 platform using either borland-bcc or visual-c.
+# It shares common definitions with the unix-make in Make.spec.
+# The bc.mak supports the following targets:
+#    bmake         - compile all st-files to a classLib (dll)
+#    bmake clean   - clean all temp files
+#    bmake clobber - clean all
+#
+# Historic Note:
+#  this used to contain only rules to make with borland
+#    (called via bmake, by "make.exe -f bc.mak")
+#  this has changed; it is now also possible to build using microsoft visual c
+#    (called via vcmake, by "make.exe -f bc.mak -DUSEVC")
+#
+TOP=..
+INCLUDE_TOP=$(TOP)\..
+
+
+# see stdHeader_bc for LIBCOMP_BASE
+LIB_BASE=$(LIBCOMP_BASE)
+
+
+!INCLUDE $(TOP)\rules\stdHeader_bc
+
+!INCLUDE Make.spec
+
+LIBNAME=libstx_libcomp
+MODULE_PATH=libcomp
+RESFILES=stx_libcompWINrc.$(RES)
+
+
+
+LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\libbasic
+LOCALDEFINES=
+
+STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES) $(COMMONSYMBOLS) -varPrefix=$(LIBNAME)
+LOCALLIBS=-lPsapi
+
+OBJS= $(COMMON_OBJS) $(WIN32_OBJS)
+
+ALL::  classLibRule
+
+classLibRule: $(OUTDIR) $(OUTDIR)$(LIBNAME).dll
+
+!INCLUDE $(TOP)\rules\stdRules_bc
+
+# build all mandatory prerequisite packages (containing superclasses) for this package
+prereq:
+	pushd ..\libbasic & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
+
+
+
+
+
+
+
+test: $(TOP)\goodies\builder\reports\NUL
+	pushd $(TOP)\goodies\builder\reports & $(MAKE_BAT)
+	$(TOP)\goodies\builder\reports\report-runner.bat -D . -r Builder::TestReport -p $(PACKAGE)
+        
+clean::
+	del *.$(CSUFFIX)
+
+
+# BEGINMAKEDEPEND --- do not remove this line; make depend needs it
+$(OUTDIR)Breakpoint.$(O) Breakpoint.$(C) Breakpoint.$(H): Breakpoint.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)BreakpointDescription.$(O) BreakpointDescription.$(C) BreakpointDescription.$(H): BreakpointDescription.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)BreakpointQuery.$(O) BreakpointQuery.$(C) BreakpointQuery.$(H): BreakpointQuery.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(STCHDR)
+$(OUTDIR)CompilationErrorHandler.$(O) CompilationErrorHandler.$(C) CompilationErrorHandler.$(H): CompilationErrorHandler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)CompilationErrorHandlerQuery.$(O) CompilationErrorHandlerQuery.$(C) CompilationErrorHandlerQuery.$(H): CompilationErrorHandlerQuery.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(STCHDR)
+$(OUTDIR)DoNotShowCompilerWarningAgainActionQuery.$(O) DoNotShowCompilerWarningAgainActionQuery.$(C) DoNotShowCompilerWarningAgainActionQuery.$(H): DoNotShowCompilerWarningAgainActionQuery.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(STCHDR)
+$(OUTDIR)DoNotShowCompilerWarningAgainForThisMethodActionQuery.$(O) DoNotShowCompilerWarningAgainForThisMethodActionQuery.$(C) DoNotShowCompilerWarningAgainForThisMethodActionQuery.$(H): DoNotShowCompilerWarningAgainForThisMethodActionQuery.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(STCHDR)
+$(OUTDIR)DoNotShowCompilerWarningAgainForThisReceiverSelectorActionQuery.$(O) DoNotShowCompilerWarningAgainForThisReceiverSelectorActionQuery.$(C) DoNotShowCompilerWarningAgainForThisReceiverSelectorActionQuery.$(H): DoNotShowCompilerWarningAgainForThisReceiverSelectorActionQuery.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(STCHDR)
+$(OUTDIR)InstrumentationContext.$(O) InstrumentationContext.$(C) InstrumentationContext.$(H): InstrumentationContext.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)InstrumentationInfo.$(O) InstrumentationInfo.$(C) InstrumentationInfo.$(H): InstrumentationInfo.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)InstrumentedMethod.$(O) InstrumentedMethod.$(C) InstrumentedMethod.$(H): InstrumentedMethod.st $(INCLUDE_TOP)\stx\libbasic\CompiledCode.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutableFunction.$(H) $(INCLUDE_TOP)\stx\libbasic\Method.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)LazyMethod.$(O) LazyMethod.$(C) LazyMethod.$(H): LazyMethod.st $(INCLUDE_TOP)\stx\libbasic\CompiledCode.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutableFunction.$(H) $(INCLUDE_TOP)\stx\libbasic\Method.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ObjectFileHandle.$(O) ObjectFileHandle.$(C) ObjectFileHandle.$(H): ObjectFileHandle.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ObjectFileLoader.$(O) ObjectFileLoader.$(C) ObjectFileLoader.$(H): ObjectFileLoader.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ParseError.$(O) ParseError.$(C) ParseError.$(H): ParseError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)ParseNode.$(O) ParseNode.$(C) ParseNode.$(H): ParseNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ParseNodeVisitor.$(O) ParseNodeVisitor.$(C) ParseNodeVisitor.$(H): ParseNodeVisitor.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ParseWarning.$(O) ParseWarning.$(C) ParseWarning.$(H): ParseWarning.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ParserFlags.$(O) ParserFlags.$(C) ParserFlags.$(H): ParserFlags.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ProgramNodeBuilder.$(O) ProgramNodeBuilder.$(C) ProgramNodeBuilder.$(H): ProgramNodeBuilder.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)ProgramNodeEnumerator.$(O) ProgramNodeEnumerator.$(C) ProgramNodeEnumerator.$(H): ProgramNodeEnumerator.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)STCCompilerInterface.$(O) STCCompilerInterface.$(C) STCCompilerInterface.$(H): STCCompilerInterface.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)Scanner.$(O) Scanner.$(C) Scanner.$(H): Scanner.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)SourceFileLoader.$(O) SourceFileLoader.$(C) SourceFileLoader.$(H): SourceFileLoader.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)Structure.$(O) Structure.$(C) Structure.$(H): Structure.st $(INCLUDE_TOP)\stx\libbasic\Behavior.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)UndefinedVariable.$(O) UndefinedVariable.$(C) UndefinedVariable.$(H): UndefinedVariable.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)UndefinedVariableNotification.$(O) UndefinedVariableNotification.$(C) UndefinedVariableNotification.$(H): UndefinedVariableNotification.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)Variable.$(O) Variable.$(C) Variable.$(H): Variable.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)stx_libcomp.$(O) stx_libcomp.$(C) stx_libcomp.$(H): stx_libcomp.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(STCHDR)
+$(OUTDIR)AssignmentNode.$(O) AssignmentNode.$(C) AssignmentNode.$(H): AssignmentNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
+$(OUTDIR)BlockNode.$(O) BlockNode.$(C) BlockNode.$(H): BlockNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
+$(OUTDIR)BreakpointNode.$(O) BreakpointNode.$(C) BreakpointNode.$(H): BreakpointNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
+$(OUTDIR)CompilationError.$(O) CompilationError.$(C) CompilationError.$(H): CompilationError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseError.$(H) $(STCHDR)
+$(OUTDIR)EvalScriptingErrorHandler.$(O) EvalScriptingErrorHandler.$(C) EvalScriptingErrorHandler.$(H): EvalScriptingErrorHandler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\CompilationErrorHandler.$(H) $(STCHDR)
+$(OUTDIR)MessageNode.$(O) MessageNode.$(C) MessageNode.$(H): MessageNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
+$(OUTDIR)MethodNode.$(O) MethodNode.$(C) MethodNode.$(H): MethodNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
+$(OUTDIR)ParseErrorNode.$(O) ParseErrorNode.$(C) ParseErrorNode.$(H): ParseErrorNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
+$(OUTDIR)Parser.$(O) Parser.$(C) Parser.$(H): Parser.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
+$(OUTDIR)PluggableParseNodeVisitor.$(O) PluggableParseNodeVisitor.$(C) PluggableParseNodeVisitor.$(H): PluggableParseNodeVisitor.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNodeVisitor.$(H) $(STCHDR)
+$(OUTDIR)PrimaryNode.$(O) PrimaryNode.$(C) PrimaryNode.$(H): PrimaryNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
+$(OUTDIR)ProgramNode.$(O) ProgramNode.$(C) ProgramNode.$(H): ProgramNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
+$(OUTDIR)SelectorNode.$(O) SelectorNode.$(C) SelectorNode.$(H): SelectorNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
+$(OUTDIR)StatementNode.$(O) StatementNode.$(C) StatementNode.$(H): StatementNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
+$(OUTDIR)TextCollectingCompilationErrorHandler.$(O) TextCollectingCompilationErrorHandler.$(C) TextCollectingCompilationErrorHandler.$(H): TextCollectingCompilationErrorHandler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\CompilationErrorHandler.$(H) $(STCHDR)
+$(OUTDIR)UndefinedSuperclassError.$(O) UndefinedSuperclassError.$(C) UndefinedSuperclassError.$(H): UndefinedSuperclassError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseError.$(H) $(STCHDR)
+$(OUTDIR)UndefinedVariableError.$(O) UndefinedVariableError.$(C) UndefinedVariableError.$(H): UndefinedVariableError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseError.$(H) $(STCHDR)
+$(OUTDIR)WarningCompilationErrorHandler.$(O) WarningCompilationErrorHandler.$(C) WarningCompilationErrorHandler.$(H): WarningCompilationErrorHandler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\CompilationErrorHandler.$(H) $(STCHDR)
+$(OUTDIR)AbstractSyntaxHighlighter.$(O) AbstractSyntaxHighlighter.$(C) AbstractSyntaxHighlighter.$(H): AbstractSyntaxHighlighter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
+$(OUTDIR)BinaryNode.$(O) BinaryNode.$(C) BinaryNode.$(H): BinaryNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\MessageNode.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
+$(OUTDIR)BreakpointAnalyzer.$(O) BreakpointAnalyzer.$(C) BreakpointAnalyzer.$(H): BreakpointAnalyzer.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
+$(OUTDIR)ByteCodeCompiler.$(O) ByteCodeCompiler.$(C) ByteCodeCompiler.$(H): ByteCodeCompiler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
+$(OUTDIR)CascadeNode.$(O) CascadeNode.$(C) CascadeNode.$(H): CascadeNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\MessageNode.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
+$(OUTDIR)ConstantNode.$(O) ConstantNode.$(C) ConstantNode.$(H): ConstantNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\PrimaryNode.$(H) $(STCHDR)
+$(OUTDIR)Explainer.$(O) Explainer.$(C) Explainer.$(H): Explainer.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
+$(OUTDIR)PrimitiveNode.$(O) PrimitiveNode.$(C) PrimitiveNode.$(H): PrimitiveNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\StatementNode.$(H) $(STCHDR)
+$(OUTDIR)ReturnNode.$(O) ReturnNode.$(C) ReturnNode.$(H): ReturnNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\StatementNode.$(H) $(STCHDR)
+$(OUTDIR)SelfNode.$(O) SelfNode.$(C) SelfNode.$(H): SelfNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\PrimaryNode.$(H) $(STCHDR)
+$(OUTDIR)UnaryNode.$(O) UnaryNode.$(C) UnaryNode.$(H): UnaryNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\MessageNode.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(STCHDR)
+$(OUTDIR)VariableNode.$(O) VariableNode.$(C) VariableNode.$(H): VariableNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\PrimaryNode.$(H) $(STCHDR)
+$(OUTDIR)ByteCodeCompilerWithBreakpointSupport.$(O) ByteCodeCompilerWithBreakpointSupport.$(C) ByteCodeCompilerWithBreakpointSupport.$(H): ByteCodeCompilerWithBreakpointSupport.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ByteCodeCompiler.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
+$(OUTDIR)CodeCoverageHighlighter.$(O) CodeCoverageHighlighter.$(C) CodeCoverageHighlighter.$(H): CodeCoverageHighlighter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\AbstractSyntaxHighlighter.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
+$(OUTDIR)Decompiler.$(O) Decompiler.$(C) Decompiler.$(H): Decompiler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ByteCodeCompiler.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
+$(OUTDIR)ECompletionConstantNode.$(O) ECompletionConstantNode.$(C) ECompletionConstantNode.$(H): ECompletionConstantNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ConstantNode.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\PrimaryNode.$(H) $(STCHDR)
+$(OUTDIR)InstrumentingCompiler.$(O) InstrumentingCompiler.$(C) InstrumentingCompiler.$(H): InstrumentingCompiler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ByteCodeCompiler.$(H) $(INCLUDE_TOP)\stx\libcomp\InstrumentationInfo.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
+$(OUTDIR)SuperNode.$(O) SuperNode.$(C) SuperNode.$(H): SuperNode.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\ParseNode.$(H) $(INCLUDE_TOP)\stx\libcomp\PrimaryNode.$(H) $(INCLUDE_TOP)\stx\libcomp\SelfNode.$(H) $(STCHDR)
+$(OUTDIR)SyntaxHighlighter.$(O) SyntaxHighlighter.$(C) SyntaxHighlighter.$(H): SyntaxHighlighter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\AbstractSyntaxHighlighter.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(STCHDR)
+$(OUTDIR)extensions.$(O): extensions.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+
+# ENDMAKEDEPEND --- do not remove this line
+
+# **Must be at end**
+
+# Enforce recompilation of package definition class if Mercurial working
+# copy state changes. Together with --guessVersion it ensures that package
+# definition class always contains correct binary revision string.
+!IFDEF HGROOT
+$(OUTDIR)stx_libcomp.$(O): $(HGROOT)\.hg\dirstate
+!ENDIF
--- a/bmake.bat	Fri Sep 23 07:06:30 2016 +0200
+++ b/bmake.bat	Sat Sep 24 06:43:04 2016 +0200
@@ -4,9 +4,13 @@
 @REM do not edit - automatically generated from ProjectDefinition
 @REM -------
 @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  %DEFINES% %*
 
 
+@IF "%1" EQU "test" exit /b 0
 
 
--- a/extensions.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/extensions.st	Sat Sep 24 06:43:04 2016 +0200
@@ -24,6 +24,7 @@
 
 !stx_libcomp class methodsFor:'documentation'!
 
-extensionsVersion_CVS
-    ^ '$Header: /cvs/stx/stx/libcomp/extensions.st,v 1.5 2013-04-16 07:21:33 vrany Exp $'
+extensionsVersion_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
--- a/mingwmake.bat	Fri Sep 23 07:06:30 2016 +0200
+++ b/mingwmake.bat	Sat Sep 24 06:43:04 2016 +0200
@@ -4,12 +4,11 @@
 @REM do not edit - automatically generated from ProjectDefinition
 @REM -------
 @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%"
 
 @pushd ..\rules
 @call find_mingw.bat
 @popd
 make.exe -N -f bc.mak %DEFINES% %USEMINGW_ARG% %*
-
-
-
-
--- a/stx_libcomp.st	Fri Sep 23 07:06:30 2016 +0200
+++ b/stx_libcomp.st	Sat Sep 24 06:43:04 2016 +0200
@@ -85,7 +85,7 @@
      by searching along the inheritance chain of all of my classes."
 
     ^ #(
-        #'stx:libbasic'    "Autoload - superclass of ParseNodeValidator"
+        #'stx:libbasic'    "CompiledCode - superclass of InstrumentedMethod"
     )
 !
 
@@ -100,8 +100,6 @@
      by searching all classes (and their packages) which are referenced by my classes."
 
     ^ #(
-        #'stx:libbasic3'    "AbstractSourceCodeManager - referenced by Explainer class>>methodSpecialInfoFor:"
-        #'stx:libtool2'    "MethodFinderWindow - referenced by Explainer class>>actionToOpenMethodFinderFor:"
     )
 !
 
@@ -351,6 +349,10 @@
     ^ '$Header$'
 !
 
+version_HG
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$ Id $'
 ! !
--- a/vcmake.bat	Fri Sep 23 07:06:30 2016 +0200
+++ b/vcmake.bat	Sat Sep 24 06:43:04 2016 +0200
@@ -10,9 +10,14 @@
     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% %*
 
 
+@IF "%1" EQU "test" exit /b 0