Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Tue, 10 May 2016 07:39:05 +0200
branchjv
changeset 3874 4f9db2d4c2b7
parent 3873 707275c1f86d (diff)
parent 3864 eaf361535167 (current diff)
child 3875 45c02b9a43a0
Merge
Explainer.st
InstrumentingCompiler.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/.hgignore	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/AbstractSyntaxHighlighter.st	Tue May 10 07:39:05 2016 +0200
@@ -255,6 +255,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'!
@@ -680,6 +714,11 @@
     ^ '$Header$'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$ Id $'
 ! !
--- a/BlockNode.st	Mon May 09 10:07:49 2016 +0200
+++ b/BlockNode.st	Tue May 10 07:39:05 2016 +0200
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -289,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'!
@@ -410,7 +412,7 @@
                     numArgs:(blockArgs size)
                     numVars:0
                     numStack:stackSize
-                    sourcePosition:nil 
+                    sourcePosition:startPosition
                     initialPC:nil 
                     literals:nil.
         ^ ConstantNode type:#Block value:cheapy.
@@ -562,10 +564,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"
@@ -596,7 +605,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'!
@@ -660,6 +670,7 @@
     "Modified: / 22-10-2006 / 12:03:27 / cg"
 ! !
 
+
 !BlockNode methodsFor:'evaluation'!
 
 evaluateIn:anEnvironment
@@ -1037,6 +1048,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].
@@ -1090,8 +1112,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:
@@ -1099,22 +1122,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
@@ -1148,6 +1170,11 @@
     ^ '$Header: /cvs/stx/stx/libcomp/BlockNode.st,v 1.95 2015-02-27 20:22:49 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$ Id $'
 ! !
--- a/BreakpointAnalyzer.st	Mon May 09 10:07:49 2016 +0200
+++ b/BreakpointAnalyzer.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/BreakpointDescription.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/BreakpointQuery.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/ByteCodeCompiler.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/CompilationErrorHandlerQuery.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/Decompiler.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/Explainer.st	Tue May 10 07:39:05 2016 +0200
@@ -884,7 +884,7 @@
                 "/ TODO: generate a short documentation string (comment plus interface)
                 "/ and return { #html->htmlText . #text->regularText}
                 "/ so caller can extrat what he wants to see...
-                ^ (HTMLDocGenerator htmlDocOf:val).
+                ^ ((Smalltalk at:#HTMLDocGenerator) htmlDocOf:val).
             ].
             explanation := explanation , '\' withCRs , string , ' is '.
             explanation := explanation , (val isLoaded ifTrue:['a'] ifFalse:['an autoloaded']).
@@ -923,6 +923,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
@@ -1966,10 +1967,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|
 
@@ -1995,7 +1996,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	Mon May 09 10:07:49 2016 +0200
+++ b/InstrumentingCompiler.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/Make.proto	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/ObjectFileLoader.st	Tue May 10 07:39:05 2016 +0200
@@ -2386,7 +2386,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,38 +2899,43 @@
      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.
-	].
-    ] ifFalse:[
-	"/ something like "kernel32.dll"; must be along the PATH setting
-	pathName := pathNameOrFilename asString.
+    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.
+        ].
     ].
 
     Verbose ifTrue:[
-	('loadDynamic: ',pathNameOrFilename asString,' (',pathName asString,')...') errorPrintCR
+        ('loadDynamic: ',pathNameOrFilename asString,' (',pathName asString,')...') errorPrintCR
     ].
     encodedPathName := OperatingSystem encodePath:pathName.
 
     "/ already loaded ?
     handle := self handleForDynamicObject:encodedPathName.
     handle notNil ifTrue:[
-	Verbose ifTrue:[
-	    ('... ' , pathName , ' already loaded.') errorPrintCR.
-	].
-	^ handle
+        Verbose ifTrue:[
+            ('... ' , pathName asString , ' already loaded.') errorPrintCR.
+        ].
+        ^ handle
     ].
 
     Verbose ifTrue:[
-	('initializeLoader...') errorPrintCR
+        ('initializeLoader...') errorPrintCR
     ].
     self initializeLoader.
 
@@ -2944,29 +2949,29 @@
     buffer at:4 put:NextHandleID. NextHandleID := NextHandleID + 1.
 
     Verbose ifTrue:[
-	('primLoadDynamicObject...') errorPrintCR
+        ('primLoadDynamicObject...') errorPrintCR
     ].
 
     buffer := self primLoadDynamicObject:encodedPathName into:buffer.
     Verbose ifTrue:[
-	('done') errorPrintCR
+        ('done') errorPrintCR
     ].
 
     buffer isNil ifTrue:[
-	LastError == #notImplemented ifTrue:[
-	    'ObjectFileLoader [warning]: no dynamic load facility present.' infoPrintCR.
-	] ifFalse:[
-	    LastError == #linkError ifTrue:[
-		LinkErrorMessage notNil ifTrue:[
-		    ('ObjectFileLoader [warning]: load error:' , LinkErrorMessage) infoPrintCR.
-		] ifFalse:[
-		    ('ObjectFileLoader [warning]: load error') infoPrintCR.
-		].
-	    ].
-	].
-	('ObjectFileLoader [warning]: failed to load: ' , pathName) infoPrintCR.
-	Transcript showCR:('ObjectFileLoader [warning]: failed to load: ' , pathName).
-	^ nil
+        LastError == #notImplemented ifTrue:[
+            'ObjectFileLoader [warning]: no dynamic load facility present.' infoPrintCR.
+        ] ifFalse:[
+            LastError == #linkError ifTrue:[
+                LinkErrorMessage notNil ifTrue:[
+                    ('ObjectFileLoader [warning]: load error:' , LinkErrorMessage) infoPrintCR.
+                ] ifFalse:[
+                    ('ObjectFileLoader [warning]: load error') infoPrintCR.
+                ].
+            ].
+        ].
+        ('ObjectFileLoader [warning]: failed to load: ' , pathName asString ) infoPrintCR.
+        Transcript showCR:('ObjectFileLoader [warning]: failed to load: ' , pathName asString).
+        ^ nil
     ].
 
     "
@@ -2979,13 +2984,13 @@
     handle moduleID:(buffer at:4).
 
     LoadedObjects isNil ifTrue:[
-	LoadedObjects := Dictionary new.
+        LoadedObjects := Dictionary new.
     ].
     LoadedObjects at:pathName put:handle.
     "/ Smalltalk flushCachedClasses.
 
     Verbose ifTrue:[
-	('loadDynamic ok; handle is: ' , handle printString) errorPrintCR.
+        ('loadDynamic ok; handle is: ' , handle printString) errorPrintCR.
     ].
     "/ ObjectMemory garbageCollect.
 
@@ -3008,6 +3013,7 @@
     "
 
     "Modified: / 06-12-2011 / 15:42:16 / cg"
+    "Modified: / 24-01-2016 / 21:57:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 loadModulesFromListOfUndefined:list
@@ -3281,7 +3287,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);
@@ -3290,7 +3296,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
@@ -3431,6 +3437,8 @@
 %}.
     LastError := #notImplemented.
     ^ nil
+
+    "Modified: / 24-01-2016 / 22:06:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 primUnloadDynamicObject:aHandle
@@ -3774,6 +3782,9 @@
 				binaryClassLibraryFilename := packageDirOrNil / 'objbc' / shLibName.
 				binaryClassLibraryFilename exists ifFalse:[
 				    binaryClassLibraryFilename := packageDirOrNil / 'objvc' / shLibName.
+                                    binaryClassLibraryFilename exists ifFalse:[
+                                        binaryClassLibraryFilename := packageDirOrNil / 'objmingw' / shLibName.
+                                    ]
 				]
 			    ] ifFalse:[
 				binaryClassLibraryFilename := packageDirOrNil / 'objmingw' / shLibName.
@@ -3801,6 +3812,13 @@
 	].
     ].
     ^ binaryClassLibraryFilename
+
+    "
+    ObjectFileLoader binaryClassFilenameForPackage:'stx:goodies/libcairo' inDirectory: (Smalltalk getPackageDirectoryForPackage: 'stx:goodies/libcairo')
+
+    "
+
+    "Modified: / 19-02-2016 / 15:24:25 / jv"
 !
 
 canLoadObjectFiles
@@ -3826,10 +3844,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
@@ -4586,6 +4610,11 @@
 
 version_CVS
     ^ '$Header$'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
 
--- a/ParseNode.st	Mon May 09 10:07:49 2016 +0200
+++ b/ParseNode.st	Tue May 10 07:39:05 2016 +0200
@@ -241,6 +241,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'!
@@ -702,6 +710,14 @@
     ^ false
 !
 
+isSelector
+    "return true, if this is a node for an selctors"
+
+    ^ false
+
+    "Created: / 22-02-2011 / 21:44:45 / Jakub <zelenja7@fel.cvut.cz>"
+!
+
 isSelf
     "return true, if this is a self-node"
 
--- a/ParseNodeValidator.st	Mon May 09 10:07:49 2016 +0200
+++ b/ParseNodeValidator.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/ParseNodeVisitor.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/Parser.st	Tue May 10 07:39:05 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
@@ -10258,6 +10226,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
@@ -11539,6 +11515,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.
@@ -11564,7 +11549,7 @@
         ^ nil
     ].
 
-    refactoring := RenameTemporaryRefactoring
+    refactoring := (Smalltalk at:#RenameTemporaryRefactoring)
                         renameTemporaryFrom:node sourceInterval
                         to:newName
                         in:nil
@@ -11577,6 +11562,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'!
@@ -12126,7 +12113,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.
@@ -12136,6 +12123,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
@@ -12404,6 +12392,11 @@
     ^ '$Header$'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$ Id $'
 ! !
--- a/ParserFlags.st	Mon May 09 10:07:49 2016 +0200
+++ b/ParserFlags.st	Tue May 10 07:39:05 2016 +0200
@@ -1496,7 +1496,7 @@
 !ParserFlags class methodsFor:'class initialization'!
 
 initialize
-    |executablePath|
+    | executablePath topDirectory stcExe |
 
     Warnings := true.
     WarnUndeclared := true.
@@ -1589,28 +1589,92 @@
     DefineForMINGW64 := '__MINGW64__'.
     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])
+        topDirectory := executablePath asFilename directory.
+        (((topDirectory / 'include') exists and:[(topDirectory / 'stc') exists or:[(topDirectory / 'bin' / stcExe) exists]])
           or:[
-            executablePath := executablePath directory.
-            ((executablePath / 'include') exists and:[(executablePath / 'stc') exists])
+            topDirectory := topDirectory directory.
+            ((topDirectory / 'include') exists and:[(topDirectory / 'stc') exists or:[(topDirectory / 'bin' / stcExe) exists]])
               or:[
-                executablePath := executablePath directory.
-                ((executablePath / 'include') exists and:[(executablePath / 'stc') exists])
+                topDirectory := topDirectory directory.
+                ((topDirectory / 'include') exists and:[(topDirectory / 'stc') exists or:[(topDirectory / 'bin' / stcExe) exists]])
               ]
            ]
         ) ifTrue:[
-            self initializeSTCFlagsForTopDirectory: executablePath.
+            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:\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"
+!
+
+initializeSTCFlagsForMINGW64
+    | mingwDirs mingwDir |
+
+    mingwDirs := Array with: (OperatingSystem getEnvironment: 'MINGW_DIR')
+                       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"
 !
 
 initializeSTCFlagsForTopDirectory:topDirArg
@@ -1618,9 +1682,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:[
@@ -1638,188 +1700,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.
-        LinkSharedArgs := '-shared'.
-        LinkCommand := CCPath.
-        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'!
@@ -2751,6 +2661,11 @@
 
 version_CVS
     ^ '$Header$'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
 
--- a/PluggableParseNodeVisitor.st	Mon May 09 10:07:49 2016 +0200
+++ b/PluggableParseNodeVisitor.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/STCCompilerInterface.st	Tue May 10 07:39:05 2016 +0200
@@ -18,7 +18,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'
 !
@@ -48,6 +49,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."
 
@@ -103,6 +154,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'!
@@ -532,6 +590,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
@@ -565,6 +638,7 @@
     ^ ok
 
     "Created: / 07-11-2006 / 12:14:51 / cg"
+    "Modified: / 04-01-2016 / 21:12:56 / jv"
 !
 
 compileToS
@@ -869,7 +943,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].
 
@@ -879,8 +953,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.
 
@@ -889,17 +961,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.
@@ -928,6 +997,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'!
@@ -938,6 +1008,11 @@
 
 version_CVS
     ^ '$Header$'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
 
--- a/SelectorNode.st	Mon May 09 10:07:49 2016 +0200
+++ b/SelectorNode.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/Switch.st	Tue May 10 07:39:05 2016 +0200
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libcomp' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#Switch
 	instanceVariableNames:'expressions values default'
 	classVariableNames:''
--- a/SyntaxHighlighter.st	Mon May 09 10:07:49 2016 +0200
+++ b/SyntaxHighlighter.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/UndefinedSuperclassError.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/UndefinedVariableError.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/UndefinedVariableNotification.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/bc.mak	Tue May 10 07:39:05 2016 +0200
@@ -38,7 +38,7 @@
 
 
 
-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
 LOCALDEFINES=
 
 STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES) $(COMMONSYMBOLS) -varPrefix=$(LIBNAME)
@@ -140,3 +140,12 @@
 $(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	Mon May 09 10:07:49 2016 +0200
+++ b/bmake.bat	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/extensions.st	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/mingwmake.bat	Tue May 10 07:39:05 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	Mon May 09 10:07:49 2016 +0200
+++ b/stx_libcomp.st	Tue May 10 07:39:05 2016 +0200
@@ -78,7 +78,7 @@
      by searching along the inheritance chain of all of my classes."
 
     ^ #(
-        #'stx:libbasic'    "Autoload - superclass of ParseNodeValidator"
+        #'stx:libbasic'    "CompiledCode - superclass of InstrumentedMethod"
     )
 !
 
@@ -93,11 +93,6 @@
      by searching all classes (and their packages) which are referenced by my classes."
 
     ^ #(
-        #'stx:goodies/refactoryBrowser/lint'    "RBReadBeforeWrittenTester - referenced by Parser class>>checkMethod:in:ignoreErrors:ignoreWarnings:"
-        #'stx:goodies/refactoryBrowser/parser'    "RBAssignmentNode - referenced by Explainer class>>addTypesAssignedToLocal:inTree:to:"
-        #'stx:goodies/refactoryBrowser/refactoring'    "RenameTemporaryRefactoring - referenced by Parser::CorrectByInteractiveRename>>fixFrom:to:for:"
-        #'stx:libbasic3'    "AbstractSourceCodeManager - referenced by Explainer class>>methodSpecialInfoFor:"
-        #'stx:libtool2'    "MethodFinderWindow - referenced by Explainer class>>actionToOpenMethodFinderFor:"
     )
 !
 
@@ -347,6 +342,10 @@
     ^ '$Header$'
 !
 
+version_HG
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$ Id $'
 ! !
--- a/vcmake.bat	Mon May 09 10:07:49 2016 +0200
+++ b/vcmake.bat	Tue May 10 07:39:05 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