Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Mon, 28 Nov 2016 17:14:44 +0000
branchjv
changeset 4061 ebdd14acce2d
parent 4056 d75b18246677 (current diff)
parent 4054 93b38c1d51ef (diff)
child 4062 df81ee6748b7
Merge
Explainer.st
Parser.st
ParserFlags.st
stx_libcomp.st
--- a/BreakpointNode.st	Fri Nov 18 21:21:39 2016 +0000
+++ b/BreakpointNode.st	Mon Nov 28 17:14:44 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2006 by eXept Software AG
 	      All Rights Reserved
@@ -161,6 +159,12 @@
     ^ expression numArgs
 !
 
+plausibilityCheckIn:aParser
+    ^ expression plausibilityCheckIn:aParser
+
+    "Created: / 20-11-2016 / 19:17:54 / cg"
+!
+
 receiver
     "must forward - otherwise cascades won't work"
 
@@ -195,11 +199,11 @@
 !BreakpointNode class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/BreakpointNode.st,v 1.15 2015-06-05 16:08:26 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libcomp/BreakpointNode.st,v 1.15 2015-06-05 16:08:26 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
--- a/Explainer.st	Fri Nov 18 21:21:39 2016 +0000
+++ b/Explainer.st	Mon Nov 28 17:14:44 2016 +0000
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
               All Rights Reserved
@@ -271,7 +273,7 @@
         implMethod := implClass compiledMethodAt:selector.
         clsName := implClass name.
         clsName := self asLink:clsName to:(self actionToBrowseClass:implClass selector:selector).
-        info := '%1  %2' bindWith:clsName "allBold" with:selectorString.
+        info := '%1 » %2' bindWith:clsName "allBold" with:selectorString.
         info := self asLink:info to:(action1 := self actionToBrowseClass:implClass selector:selector info:nil).
         
         redefiningClasses size > 0 ifTrue:[
@@ -1020,7 +1022,7 @@
         "/ a class
         val name = sym ifFalse:[
             "/ an alias (such as OperatingSystem, Screen etc.)
-            template := template,'. Refers to %{realName}'.
+            template := template,'. Refers to %(realName)'.
             bindings at:'realName' put:val name.
         ].
 
@@ -1036,7 +1038,7 @@
             template := template , (val isSharedPool ifTrue:[' pool'] ifFalse:[' class']).
             template := template , ' in %(package) {%(category)}.'.
             bindings at:'package' put:val package.
-            bindings at:'varName' put:(self asClassLink:val name).
+            bindings at:'varName' put:(self asClassLink:varName "val name").
             ^ template bindWithArguments:bindings
         ].
 
@@ -1085,8 +1087,7 @@
     ^ explanation.
 
     "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: / 16-11-2016 / 13:08:07 / cg"
     "Modified: / 05-05-2016 / 00:25:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
@@ -2646,7 +2647,7 @@
                         to:(self actionToOpenMethodFinderFor:sel)) 
             with:(self 
                     asLink:inheritedClass name "allBold" 
-                    info:('Browse %1  %2' bindWith:inheritedClass name with:sel)
+                    info:('Browse %1 » %2' bindWith:inheritedClass name with:sel)
                     to:(self actionToBrowseClass:inheritedClass selector:sel)).
     ].
 
--- a/Parser.st	Fri Nov 18 21:21:39 2016 +0000
+++ b/Parser.st	Mon Nov 28 17:14:44 2016 +0000
@@ -37,7 +37,7 @@
 		interactiveMode variableCorrectActionForAll annotations
 		variableTypeOfLastCorrectAction usedPoolVars readPoolVars
 		modifiedPoolVars warnings didWarnAboutSTXExtensions
-		annotationStartPosition annotationEndPosition'
+		annotationStartPosition annotationEndPosition autoDefineVariables'
 	classVariableNames:'PrevClass PrevInstVarNames PrevClassVarNames
 		PrevClassInstVarNames LazyCompilation FoldConstants
 		LineNumberInfo SuppressDoItCompilation ParseErrorSignal
@@ -5080,7 +5080,7 @@
     ].
 
     self source:s.
-    selector := #doIt.  "/ so isDoit returns the correct answer!!
+    selector := self doItSelector.  "/ so isDoit returns the correct answer!!
 
     self parseForCode.
     self foldConstants:nil.
@@ -5215,7 +5215,7 @@
                 "/ actually, its a block, to allow
                 "/ easy return ...
 
-                sReal := 'doIt ^[ ' , s , '\] value' withCRs.
+                sReal := (self doItSelector),' ^[ ' , s , '\] value' withCRs.
 
                 compiler := ByteCodeCompiler new.
                 compiler initializeFlagsFrom:self.
@@ -5243,8 +5243,8 @@
 
                         value := method
                                     valueWithReceiver:anObject
-                                    arguments:nil  "/ (Array with:m)
-                                    selector:(requestor isNil ifTrue:[#'doItX'] ifFalse:[#'doIt']) "/ #doIt:
+                                    arguments:nil 
+                                    selector:(self doItSelector) "/ #__doIt__
                                     search:nil
                                     sender:nil.
                     ] ifFalse:[
@@ -5261,7 +5261,7 @@
 
     "Created: / 08-02-1997 / 19:34:44 / cg"
     "Modified: / 18-03-1999 / 18:25:40 / stefan"
-    "Modified: / 06-07-2011 / 11:46:24 / cg"
+    "Modified: / 22-11-2016 / 00:08:52 / cg"
 !
 
 evaluate:aStringOrStream logged:logged
@@ -7841,27 +7841,33 @@
      return a node-tree, or raise an Error."
 
     |pos1 pos2 expr varName rawName var globlName nameSpace nameSpaceGlobal
-     t cls lnr node holder autoHow assignmentAllowed|
+     t cls lnr node holder assignmentAllowed|
 
     pos1 := tokenPosition.
     pos2 := tokenPosition + tokenName size - 1.
 
     varName := tokenName.
 
-    (self isDoIt
-    and:[ currentBlock isNil
-    and:[ requestor notNil
-    and:[ (autoHow := requestor perform:#autoDefineVariables ifNotUnderstood:nil) notNil]]]) ifTrue:[
+    autoDefineVariables isNil ifTrue:[
+        autoDefineVariables := false.    
+        requestor notNil ifTrue:[
+            autoDefineVariables := requestor perform:#autoDefineVariables ifNotUnderstood:false.
+        ]
+    ].    
+    (autoDefineVariables ~~ false) ifTrue:[
         var := self variableOrError:varName.
         self nextToken.
+        
         (var == #Error) ifTrue:[
             ((tokenType == $_) or:[tokenType == #':=']) ifTrue:[
-                autoHow == #workspace ifTrue:[
+                autoDefineVariables == #doIt ifTrue:[
+                    "/ as doIt var (only within this expression)   
+                    holder := self addDoItTemporary:varName.
+                    var := VariableNode type:#DoItTemporary holder:holder name:varName.
+                ] ifFalse:[
+                    "/ as workspace var (only within doIts)    
                     holder := Workspace addWorkspaceVariable:varName.
                     var := VariableNode type:#WorkspaceVariable holder:holder name:varName.
-                ] ifFalse:[
-                    holder := self addDoItTemporary:varName.
-                    var := VariableNode type:#DoItTemporary holder:holder name:varName.
                 ].
             ] ifFalse:[
                 var := self correctVariable:varName atPosition:pos1 to:pos2.
@@ -8757,6 +8763,25 @@
         ^ v
     ].
 
+    "/ hack: if we are in a doIt of a debugger's context,
+    "/ AND the variable is an inlined block variable,
+    "/ it will not be found in the context.
+"/    self isDoIt ifTrue:[
+"/        contextToEvaluateIn notNil ifTrue:[
+"/            |mthd source parseTree|
+"/
+"/            "/ we need a parse tree to find the temporary var's slot
+"/            mthd := contextToEvaluateIn method.
+"/            (source := mthd source) notNil ifTrue:[
+"/self halt.
+"/                parseTree := Parser parseMethod:source.
+"/                (parseTree notNil and:[parseTree ~~ #Error]) ifTrue:[
+"/self halt.
+"/                ].
+"/            ].
+"/        ].
+"/    ].
+
     pos1 := tokenPosition.
     pos2 := pos1+tokenName size-1.
     self markUnknownIdentifierFrom:pos1 to:pos2.
@@ -8798,7 +8823,7 @@
         startPosition: pos1 endPosition: (pos1 + tokenName size - 1)
 
     "Modified: / 25-08-2011 / 11:57:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 04-09-2011 / 07:34:57 / cg"
+    "Modified: / 22-11-2016 / 00:23:44 / cg"
 !
 
 variableOrError
@@ -8825,12 +8850,9 @@
         vars notNil ifTrue:[
             varIndex := vars findFirst:[:aBlockVar | aBlockVar name = varName].
             varIndex ~~ 0 ifTrue:[
-                ^ (VariableNode type:#BlockVariable
-                               name:varName
-                              token:(vars at:varIndex)
-                              index:varIndex
-                              block:searchBlock
-                               from:currentBlock)
+                ^ (VariableNode type:#BlockVariable name:varName 
+                        token:(vars at:varIndex) index:varIndex 
+                        block:searchBlock from:currentBlock)
                     startPosition: tokenPosition endPosition: tokenPosition + varName size - 1
             ].
         ].
@@ -8839,12 +8861,9 @@
         args notNil ifTrue:[
             varIndex := args findFirst:[:aBlockArg | aBlockArg name = varName].
             varIndex ~~ 0 ifTrue:[
-                ^ (VariableNode type:#BlockArg
-                               name:varName
-                              token:(args at:varIndex)
-                              index:varIndex
-                              block:searchBlock
-                               from:currentBlock)
+                ^ (VariableNode type:#BlockArg name:varName
+                        token:(args at:varIndex) index:varIndex
+                        block:searchBlock from:currentBlock)
                     startPosition: tokenPosition endPosition: tokenPosition + varName size - 1
             ].
 
@@ -8876,11 +8895,8 @@
             varNames size > 0 ifTrue:[
                 varIndex := varNames lastIndexOf:varName.
                 varIndex ~~ 0 ifTrue:[
-                    ^ (VariableNode
-                            type:#ContextVariable
-                            name:varName
-                            context:con
-                            index:varIndex)
+                    ^ (VariableNode type:#ContextVariable name:varName
+                            context:con index:varIndex)
                         startPosition: tokenPosition endPosition: tokenPosition + varName size - 1
                 ].
             ].
@@ -8928,11 +8944,8 @@
                 ].
             ].
             parseForCode ifFalse:[self rememberInstVarUsed:varName].
-            ^ (VariableNode
-                    type:#InstanceVariable
-                    name:varName
-                    index:varIndex
-                    selfValue:selfValue)
+            ^ (VariableNode type:#InstanceVariable name:varName
+                    index:varIndex selfValue:selfValue)
                     startPosition: tokenPosition endPosition: tokenPosition + varName size - 1
         ].
 
@@ -8957,10 +8970,8 @@
                         contextToEvaluateIn notNil ifTrue:[
                             "/ allow it in a doIt ...
 
-                            ^ (VariableNode type:#ClassInstanceVariable
-                                           name:varName
-                                          index:varIndex
-                                      selfClass:aClass)
+                            ^ (VariableNode type:#ClassInstanceVariable name:varName
+                                    index:varIndex selfClass:aClass)
                                 startPosition: tokenPosition endPosition: tokenPosition + varName size - 1
                         ].
                         self parseError:'access to class-inst-var from inst method is not allowed'.
@@ -9050,29 +9061,23 @@
         ]
     ].
 
-    (self isDoIt) ifTrue:[
-        "is it a workspace variable ?"
+    autoDefineVariables isNil ifTrue:[
+        autoDefineVariables := false.    
         (requestor notNil and:[requestor isStream not]) ifTrue:[
-            "/ when parsing doits, this is done twice;
-            "/ first, for the parse, then as a block-code
-            "/ for the code.
-            "/ We only care for WorkspaceVars in doIts
-            (self isDoIt) ifTrue:[
-                (Workspace notNil
-                and:[(holder := Workspace workspaceVariableHolderAt:varName) notNil])
-                ifTrue:[
-                    ^ (VariableNode type:#WorkspaceVariable holder:holder name:varName)
-                        startPosition: tokenPosition endPosition: tokenPosition + varName size - 1
-                ]
-            ]
-        ].
-        "is it a doIt variable ?"
-
-        "/ (requestor notNil and:[requestor isStream not]) ifTrue:[
-            "/ when parsing doits, this is done twice;
-            "/ first, for the parse, then as a block-code
-            "/ for the code.
-            "/ We only care for WorkspaceVars in doIts
+            autoDefineVariables := requestor perform:#autoDefineVariables ifNotUnderstood:false.
+        ]
+    ].    
+    (autoDefineVariables ~~ false) ifTrue:[
+        "is it a workspace variable ?"
+
+        (Workspace notNil
+        and:[(holder := Workspace workspaceVariableHolderAt:varName) notNil])
+        ifTrue:[
+            ^ (VariableNode type:#WorkspaceVariable holder:holder name:varName)
+                startPosition: tokenPosition endPosition: tokenPosition + varName size - 1
+        ].
+        self isDoIt ifTrue:[
+            "is it a doIt variable ?"
 
             (doItTemporaries notNil
             and:[(holder := doItTemporaries at:varName asSymbol ifAbsent:nil) notNil])
@@ -9080,7 +9085,7 @@
                 ^ (VariableNode type:#DoItTemporary holder:holder name:varName)
                     startPosition: tokenPosition endPosition: tokenPosition + varName size - 1
             ].
-        "/ ].
+        ].
     ].
     
     "/ do not raise parseError here, but instead report it a the old stupid #Error token.
@@ -10497,6 +10502,16 @@
     ^ didWarnAboutSqueakExtensions ? false
 !
 
+doItSelector
+    "the name of the method used for doit's.
+     The method will not be installed, but called directly,
+     so the name is more or less arbitrary."
+
+    ^ #'doIt'
+
+    "Created: / 21-11-2016 / 23:58:43 / cg"
+!
+
 hasNonOptionalPrimitiveCode
     "return true if there was any ST/X style primitive code (valid after parsing)"
 
@@ -10516,7 +10531,9 @@
 !
 
 isDoIt
-    ^ (false "selector isNil" or:[selector == #'doIt' or:[selector == #'doIt:']])
+    ^ selector == self doItSelector
+
+    "Modified: / 22-11-2016 / 00:00:10 / cg"
 !
 
 isEmptyMethod
--- a/ParserFlags.st	Fri Nov 18 21:21:39 2016 +0000
+++ b/ParserFlags.st	Mon Nov 28 17:14:44 2016 +0000
@@ -20,9 +20,9 @@
 		warnUnderscoreInIdentifier warnOldStyleAssignment
 		warnCommonMistakes warnSTXNameSpaceUse
 		warnPossibleIncompatibilities warnDollarInIdentifier
-		warnHiddenVariables warnAboutVariableNameConventions
-		warnAboutWrongVariableNames warnAboutBadComments
-		warnInconsistentReturnValues
+		warnParagraphInIdentifier warnHiddenVariables
+		warnAboutVariableNameConventions warnAboutWrongVariableNames
+		warnAboutBadComments warnInconsistentReturnValues
 		warnAboutNonLowercaseLocalVariableNames
 		warnAboutPossibleSTCCompilationProblems
 		warnAboutReferenceToPrivateClass warnAboutShortLocalVariableNames
@@ -30,9 +30,10 @@
 		warnAboutUnknownCharacterEscapesInJavaScriptStringConstant
 		warnPlausibilityChecks allowLiteralNameSpaceSymbols
 		allowUnderscoreInIdentifier allowDollarInIdentifier
-		allowOldStyleAssignment allowSqueakExtensions
-		allowDolphinExtensions allowExtendedBinarySelectors
-		allowQualifiedNames allowFunctionCallSyntaxForBlockEvaluation
+		allowParagraphInIdentifier allowOldStyleAssignment
+		allowSqueakExtensions allowDolphinExtensions
+		allowExtendedBinarySelectors allowQualifiedNames
+		allowFunctionCallSyntaxForBlockEvaluation
 		allowLocalVariableDeclarationWithInitializerExpression
 		allowDomainVariables allowArrayIndexSyntaxExtension
 		allowReservedWordsAsSelectors allowVariableReferences
@@ -56,48 +57,50 @@
 		lineNumberInfo allowSTXDelimiterComments
 		allowSTXExtendedArrayLiterals warnAssignmentToBlockArgument
 		warnAssignmentToMethodArgument warnAssignmentToPoolVariable'
-	classVariableNames:'WarnST80Directives WarnUnusedVars WarnUndeclared
-		WarnAboutWrongVariableNames WarnAboutBadComments
-		WarnAboutVariableNameConventions WarnSTXSpecials
-		WarnOldStyleAssignment WarnUnderscoreInIdentifier
-		WarnCommonMistakes WarnPossibleIncompatibilities
-		WarnDollarInIdentifier WarnHiddenVariables
-		WarnAboutNonLowercaseLocalVariableNames
-		WarnInconsistentReturnValues Warnings
-		WarnAboutPossibleSTCCompilationProblems
-		WarnAboutReferenceToPrivateClass WarnAboutShortLocalVariableNames
-		WarnAboutPossiblyUnimplementedSelectors WarnAboutPeriodInSymbol
-		WarnAboutUnknownCharacterEscapesInJavaScriptStringConstant
-		WarnPlausibilityChecks AllowUnderscoreInIdentifier
-		AllowFunctionCallSyntaxForBlockEvaluation AllowLazyValueExtension
-		AllowVariableReferences AllowReservedWordsAsSelectors
-		AllowLocalVariableDeclarationWithInitializerExpression
-		AllowArrayIndexSyntaxExtension AllowDomainVariables
-		AllowDollarInIdentifier AllowSqueakExtensions AllowQualifiedNames
-		AllowDolphinExtensions AllowOldStyleAssignment
+	classVariableNames:'AllowArrayIndexSyntaxExtension AllowAssignmentToBlockArgument
+		AllowAssignmentToMethodArgument AllowAssignmentToPoolVariable
+		AllowCaretAsBinop AllowCharacterEscapes AllowDollarInIdentifier
+		AllowDolphinExtensions AllowDomainVariables AllowEmptyStatements
 		AllowExtendedBinarySelectors AllowExtendedSTXSyntax
-		AllowFixedPointLiterals AllowLiteralNameSpaceSymbols
-		AllowVisualAgeESSymbolLiterals AllowExtensionsToPrivateClasses
-		AllowSqueakPrimitives AllowVisualAgePrimitives AllowSTVPrimitives
-		AllowSTVExtensions AllowNationalCharactersInIdentifier
-		AllowHashAsBinarySelector AllowSTXEOLComments
-		AllowPossibleSTCCompilationProblems AllowEmptyStatements
-		AllowVisualWorksMethodAnnotations ArraysAreImmutable
-		AllowPeriodInSymbol StringsAreImmutable ImplicitSelfSends
-		STCModulePath STCKeepCIntermediate STCKeepOIntermediate
-		STCKeepSTIntermediate STCCompilation STCCompilationIncludes
-		STCCompilationDefines STCCompilationOptions STCPath
-		CCCompilationOptions CCPath LinkArgs LinkSharedArgs LinkCommand
-		LibPath SearchedLibraries MakeCommand AllowCaretAsBinop
-		AllowUnicodeStrings AllowUnicodeCharacters AllowCharacterEscapes
-		AllowStringEscapes AllowAssignmentToBlockArgument
-		AllowAssignmentToMethodArgument AllowAssignmentToPoolVariable
-		LineNumberInfo LibDirectory VCTop SDKTop BCCTop MingwTop
-		ForcedCompiler DefineForBorlandC DefineForVisualC DefineForMSC
-		DefineForGNUC PerMethodFlags AllowSTXDelimiterComments
-		AllowSTXExtendedArrayLiterals DefineForMINGW32 DefineForMINGW64
-		DefineForMINGW DefineForCLANG WarnAssignmentToBlockArgument
-		WarnAssignmentToPoolVariable WarnAssignmentToMethodArgument'
+		AllowExtensionsToPrivateClasses AllowFixedPointLiterals
+		AllowFunctionCallSyntaxForBlockEvaluation
+		AllowHashAsBinarySelector AllowLazyValueExtension
+		AllowLiteralNameSpaceSymbols
+		AllowLocalVariableDeclarationWithInitializerExpression
+		AllowNationalCharactersInIdentifier AllowOldStyleAssignment
+		AllowParagraphInIdentifier AllowPeriodInSymbol
+		AllowPossibleSTCCompilationProblems AllowQualifiedNames
+		AllowReservedWordsAsSelectors AllowSTVExtensions
+		AllowSTVPrimitives AllowSTXDelimiterComments AllowSTXEOLComments
+		AllowSTXExtendedArrayLiterals AllowSqueakExtensions
+		AllowSqueakPrimitives AllowStringEscapes
+		AllowUnderscoreInIdentifier AllowUnicodeCharacters
+		AllowUnicodeStrings AllowVariableReferences
+		AllowVisualAgeESSymbolLiterals AllowVisualAgePrimitives
+		AllowVisualWorksMethodAnnotations ArraysAreImmutable BCCTop
+		CCCompilationOptions CCPath DefineForBorlandC DefineForCLANG
+		DefineForGNUC DefineForMINGW DefineForMINGW32 DefineForMINGW64
+		DefineForMSC DefineForVisualC ForcedCompiler ImplicitSelfSends
+		LibDirectory LibPath LineNumberInfo LinkArgs LinkCommand
+		LinkSharedArgs MakeCommand MingwTop PerMethodFlags SDKTop
+		STCCompilation STCCompilationDefines STCCompilationIncludes
+		STCCompilationOptions STCKeepCIntermediate STCKeepOIntermediate
+		STCKeepSTIntermediate STCModulePath STCPath SearchedLibraries
+		StringsAreImmutable VCTop WarnAboutBadComments
+		WarnAboutNonLowercaseLocalVariableNames WarnAboutPeriodInSymbol
+		WarnAboutPossibleSTCCompilationProblems
+		WarnAboutPossiblyUnimplementedSelectors
+		WarnAboutReferenceToPrivateClass WarnAboutShortLocalVariableNames
+		WarnAboutUnknownCharacterEscapesInJavaScriptStringConstant
+		WarnAboutVariableNameConventions WarnAboutWrongVariableNames
+		WarnAssignmentToBlockArgument WarnAssignmentToMethodArgument
+		WarnAssignmentToPoolVariable WarnCommonMistakes
+		WarnDollarInIdentifier WarnHiddenVariables
+		WarnInconsistentReturnValues WarnOldStyleAssignment
+		WarnParagraphInIdentifier WarnPlausibilityChecks
+		WarnPossibleIncompatibilities WarnST80Directives WarnSTXSpecials
+		WarnUndeclared WarnUnderscoreInIdentifier WarnUnusedVars Warnings
+		AutoDefineVariables'
 	poolDictionaries:''
 	category:'System-Compiler'
 !
@@ -714,12 +717,13 @@
 
 allowDollarInIdentifier
     "return true, if $-characters are allowed in identifiers.
-     Notice, that dollars are NEVER allowed as the first character in an identifier."
+     Notice, that dollars are NEVER allowed as the first character in an identifier
+     (because they are interpreted as character-constant then)."
 
     ^ AllowDollarInIdentifier
 
-    "Created: 7.9.1997 / 01:32:18 / cg"
-    "Modified: 7.9.1997 / 01:39:44 / cg"
+    "Created: / 07-09-1997 / 01:32:18 / cg"
+    "Modified (comment): / 16-11-2016 / 22:25:59 / cg"
 !
 
 allowDollarInIdentifier:aBoolean
@@ -727,16 +731,17 @@
      Notice, that dollars are NEVER allowed as the first character in an identifier.
      If turned off (the default), dollars are not allowed in identifiers,
      but instead are scanned as character-constant prefix.
-     If turned on, dollars are in identifiers are allowed, while extra
+     If turned on, dollars in identifiers are allowed, while extra
      dollars are still scanned as constant character prefix.
      If you have to fileIn old VW-Vsn2.x classes, turn this off
      before filing them in; i.e.:
-	Compiler allowDollarInIdentifiers:false"
+        Compiler allowDollarInIdentifiers:false
+    "
 
     AllowDollarInIdentifier := aBoolean.
 
-    "Created: 7.9.1997 / 01:34:49 / cg"
-    "Modified: 7.9.1997 / 01:39:30 / cg"
+    "Created: / 07-09-1997 / 01:34:49 / cg"
+    "Modified (comment): / 16-11-2016 / 22:26:38 / cg"
 !
 
 allowDolphinExtensions
@@ -908,6 +913,22 @@
     AllowOldStyleAssignment := aBoolean
 !
 
+allowParagraphInIdentifier
+    "return true, if -characters are allowed in identifiers (treated as letter)"
+
+    ^ AllowParagraphInIdentifier
+
+    "Created: / 16-11-2016 / 22:24:32 / cg"
+!
+
+allowParagraphInIdentifier:aBoolean
+    "this allows turning on/off -characters in identifiers."
+
+    AllowParagraphInIdentifier := aBoolean.
+
+    "Created: / 16-11-2016 / 22:28:49 / cg"
+!
+
 allowPeriodInSymbol
     "return true, if periods are allowed in a symbol literal #foo.bar.
      Needed to parse some old ST80/Squeak code"
@@ -1372,18 +1393,19 @@
 warnDollarInIdentifier:aBoolean
     "this allows turning on/off warnings about $-characters in identifiers.
      You may find those warnings useful, to make certain that your code
-     is portable to other smalltalk versions, which do not allow this
+     is portable to other Smalltalk versions, which do not allow this
      (i.e. VW releases 2.x and maybe others).
      Notice, that dollars are NEVER allowed as the first character in an identifier.
      If you get bored by those warnings, turn them off by adding
      a line as:
-	ParserFlags warnDollarInIdentifier:false
+        ParserFlags warnDollarInIdentifier:false
      in your 'private.rc' file"
 
     WarnDollarInIdentifier := aBoolean
 
     "Created: / 07-09-1997 / 01:37:42 / cg"
     "Modified: / 05-09-2006 / 11:46:23 / cg"
+    "Modified (comment): / 16-11-2016 / 22:31:06 / cg"
 !
 
 warnHiddenVariables
@@ -1430,6 +1452,24 @@
     "Modified: / 05-09-2006 / 11:46:17 / cg"
 !
 
+warnParagraphInIdentifier
+    "return true, if -characters in identifiers are to be warned about"
+
+    ^ Warnings and:[WarnParagraphInIdentifier]
+
+    "Created: / 16-11-2016 / 22:30:01 / cg"
+!
+
+warnParagraphInIdentifier:aBoolean
+    "this allows turning on/off warnings about -characters in identifiers.
+     You may find those warnings useful, to make certain that your code
+     is portable to other Smalltalk versions, which do not allow this"
+
+    WarnParagraphInIdentifier := aBoolean
+
+    "Created: / 16-11-2016 / 22:30:45 / cg"
+!
+
 warnPlausibilityChecks
     "controls generation of warning messages about plausibility checks (possible precedence, etc.)"
 
@@ -1558,6 +1598,7 @@
     WarnAboutBadComments := true.
     WarnUnderscoreInIdentifier := false.
     WarnDollarInIdentifier := true.
+    WarnParagraphInIdentifier := true.
     WarnOldStyleAssignment := true.
     WarnCommonMistakes := true.
     WarnPossibleIncompatibilities := false.
@@ -1577,6 +1618,7 @@
 
     AllowReservedWordsAsSelectors := false.
     AllowUnderscoreInIdentifier := true.
+    AllowParagraphInIdentifier := false.
     AllowDollarInIdentifier := false.           "/ st80-vms dollars in identifiers
     AllowOldStyleAssignment := true.            "/ st80 underscore as assignment
     AllowDolphinExtensions := false.            "/ dolphin computed literal
@@ -1624,7 +1666,7 @@
     "/ ArraysAreImmutable := true.                 "/ do not care for ST-80 compatibility
     "/ StringsAreImmutable := true.                "/ do not care for ST-80 compatibility
     ImplicitSelfSends := false.
-
+    
     STCKeepCIntermediate := false.
     STCKeepOIntermediate := false.
     STCKeepSTIntermediate := false.
@@ -1676,7 +1718,7 @@
     "
 
     "Modified: / 09-08-2006 / 18:47:18 / fm"
-    "Modified: / 31-01-2012 / 12:06:32 / cg"
+    "Modified: / 16-11-2016 / 22:32:03 / cg"
     "Modified: / 06-01-2016 / 22:25:30 / jv"
 !
 
@@ -1853,6 +1895,12 @@
 
 ccCompilationOptions
     ^ ccCompilationOptions ? ''
+
+    "
+     self ccCompilationOptions
+    "
+
+    "Modified (comment): / 17-11-2016 / 15:40:29 / cg"
 !
 
 ccCompilationOptions:something
@@ -1861,6 +1909,12 @@
 
 ccPath
     ^ ccPath
+
+    "
+     self ccPath
+    "
+
+    "Modified (comment): / 17-11-2016 / 15:40:40 / cg"
 !
 
 ccPath:something
@@ -1877,6 +1931,12 @@
 
 libPath
     ^ libPath
+
+    "
+     self libPath
+    "
+
+    "Modified (comment): / 17-11-2016 / 15:40:52 / cg"
 !
 
 libPath:aString
@@ -1885,6 +1945,12 @@
 
 linkArgs
     ^ linkArgs
+
+    "
+     self linkArgs
+    "
+
+    "Modified (comment): / 17-11-2016 / 15:41:03 / cg"
 !
 
 linkArgs:aString
@@ -1893,6 +1959,12 @@
 
 linkCommand
     ^ linkCommand
+
+    "
+     self linkCommand
+    "
+
+    "Modified (comment): / 17-11-2016 / 15:41:16 / cg"
 !
 
 linkCommand:aString
@@ -1933,6 +2005,12 @@
 
 stcCompilationIncludes
     ^ stcCompilationIncludes
+
+    "
+     self stcCompilationIncludes
+    "
+
+    "Modified (comment): / 17-11-2016 / 15:41:43 / cg"
 !
 
 stcCompilationIncludes:something
@@ -2169,6 +2247,18 @@
     allowOldStyleAssignment := aBoolean
 !
 
+allowParagraphInIdentifier
+    ^ allowParagraphInIdentifier
+
+    "Created: / 16-11-2016 / 22:29:06 / cg"
+!
+
+allowParagraphInIdentifier:aBoolean
+    allowParagraphInIdentifier := aBoolean.
+
+    "Created: / 16-11-2016 / 22:29:14 / cg"
+!
+
 allowPeriodInSymbol
     ^ allowPeriodInSymbol
 !
@@ -2534,6 +2624,18 @@
     warnOldStyleAssignment := aBoolean.
 !
 
+warnParagraphInIdentifier
+    ^ warnParagraphInIdentifier
+
+    "Created: / 16-11-2016 / 22:29:33 / cg"
+!
+
+warnParagraphInIdentifier:aBoolean
+    warnParagraphInIdentifier := aBoolean.
+
+    "Created: / 16-11-2016 / 22:29:45 / cg"
+!
+
 warnPlausibilityChecks
     "controls generation of warning messages about plausibility checks (possible precedence, etc.)"
 
@@ -2649,6 +2751,7 @@
     warnSTXHereExtensionUsed := WarnSTXSpecials.
     warnUnderscoreInIdentifier := WarnUnderscoreInIdentifier.
     warnDollarInIdentifier := WarnDollarInIdentifier.
+    warnParagraphInIdentifier := WarnParagraphInIdentifier.
     warnOldStyleAssignment := WarnOldStyleAssignment.
     warnCommonMistakes := WarnCommonMistakes.
     warnPossibleIncompatibilities := WarnPossibleIncompatibilities.
@@ -2671,6 +2774,7 @@
 
     allowUnderscoreInIdentifier := AllowUnderscoreInIdentifier.
     allowDollarInIdentifier := AllowDollarInIdentifier.
+    allowParagraphInIdentifier := AllowParagraphInIdentifier.
     allowOldStyleAssignment := AllowOldStyleAssignment.
     allowSqueakExtensions := AllowSqueakExtensions.
     allowDolphinExtensions := AllowDolphinExtensions.
@@ -2737,7 +2841,7 @@
      self new inspect.
     "
 
-    "Modified: / 26-09-2012 / 14:22:38 / cg"
+    "Modified: / 16-11-2016 / 22:32:37 / cg"
 ! !
 
 !ParserFlags class methodsFor:'documentation'!
--- a/Scanner.st	Fri Nov 18 21:21:39 2016 +0000
+++ b/Scanner.st	Mon Nov 28 17:14:44 2016 +0000
@@ -143,7 +143,7 @@
 extendedBinarySelectorCharacters
     "return a collection of characters which are optionally allowed in binary selectors"
 
-"/    ^ '±×·÷«»'.
+    "/ ^ '±×·÷«»'.
     ^ String
         with:(Character value:16rB1)  "/ plus-minus
         with:(Character value:16rD7)  "/ times
@@ -151,10 +151,12 @@
         with:(Character value:16rF7)  "/ divide
         with:(Character value:16rAB)  "/ <<
         with:(Character value:16rBB). "/ >>
+
+    "Modified (comment): / 17-11-2016 / 09:22:42 / cg"
 !
 
 setupActions
-    "initialize the scanners actionTables - these are used to dispatch
+    "initialize the scanner's actionTables - these are used to dispatch
      into scanner methods as characters are read.
      Compatibility note: in previous versions, these tables used to be kept
      in classVariables, which made reuse hard as subclasses had no easy way of
@@ -219,7 +221,7 @@
      Scanner withAllSubclassesDo:[:cls | cls setupActions ]
     "
 
-    "Modified: / 25-03-2011 / 13:58:59 / cg"
+    "Modified: / 17-11-2016 / 09:31:38 / cg"
 ! !
 
 !Scanner class methodsFor:'instance creation'!
@@ -1446,7 +1448,11 @@
         errMsg := 'Invalid character: ' , (v radixPrintStringRadix:16) , '.'.
     ].
     v > 16r7F ifTrue:[
-        errMsg := errMsg , '\\Notice:\  Only 7-bit ascii allowed (for compatibility with other Smalltalk dialects).' withCRs.
+        errMsg := errMsg , '
+
+Notice:
+  Only 7-bit ascii allowed (for compatibility with other Smalltalk dialects).
+  You can enable some of the special characters via the compiler-settings dialog.'.
     ].
     self syntaxError:errMsg position:tokenPosition to:tokenPosition.
     source next.
@@ -1454,7 +1460,7 @@
     tokenType := #Error.
     ^ #Error
 
-    "Modified: / 22-08-2006 / 14:26:21 / cg"
+    "Modified: / 17-11-2016 / 09:37:52 / cg"
 !
 
 lastTokenLineNumber
@@ -1751,6 +1757,29 @@
     "Modified: 23.5.1997 / 12:16:48 / cg"
 !
 
+warnParagraphAt:position
+    "warn about §-character in an identifier"
+
+    ignoreWarnings ifFalse:[
+        "/ didWarnAboutParagraphInIdentifier ifFalse:[
+            parserFlags warnParagraphInIdentifier ifTrue:[
+                self 
+                    warning:'§-characters in identifiers/symbols are nonportable' 
+                    doNotShowAgainAction:[ ParserFlags warnParagraphInIdentifier:false ]
+                    position:position to:position.
+                "
+                 only warn once (per method)
+                "
+                parserFlags := parserFlags copy.
+                parserFlags warnParagraphInIdentifier:false.
+                "/ didWarnAboutParagraphInIdentifier := true
+            ]
+        "/ ]
+    ]
+
+    "Created: / 17-11-2016 / 09:16:22 / cg"
+!
+
 warnPeriodAt:position
     "warn about a period in an identifier"
 
@@ -2761,8 +2790,9 @@
     nextChar := source peekOrNil.
 
     (((nextChar == $_) and:[allowUnderscoreInIdentifier]) 
-    or:[(allowDollarInIdentifier and:[nextChar == $$ ])
-    or:[allowNationalCharactersInIdentifier and:[ nextChar notNil and:[nextChar isNationalLetter]]]]) ifTrue:[
+    or:[ (allowDollarInIdentifier and:[nextChar == $$ ])
+    or:[ (nextChar == $§ and:[ parserFlags allowParagraphInIdentifier])
+    or:[ allowNationalCharactersInIdentifier and:[ nextChar notNil and:[nextChar isNationalLetter]]]]]) ifTrue:[
         pos := source position + 1.
         nextChar == $_ ifTrue:[
             self warnUnderscoreAt:pos.
@@ -2770,7 +2800,11 @@
             nextChar == $$ ifTrue:[
                 self warnDollarAt:pos.
             ] ifFalse:[
-                "/ self warnNationalCharacterAt:pos.
+                nextChar == $§ ifTrue:[
+                    self warnParagraphAt:pos.
+                ] ifFalse:[
+                    "/ self warnNationalCharacterAt:pos.
+                ]
             ]
         ].
         ok := true.
@@ -2786,7 +2820,8 @@
                 ].
                 ok := ((nextChar == $_) and:[allowUnderscoreInIdentifier]) 
                       or:[((nextChar == $$ ) and:[allowDollarInIdentifier])
-                      or:[(nextChar notNil and:[nextChar isNationalLetter]) and:[allowNationalCharactersInIdentifier]]].
+                      or:[((nextChar == $§ ) and:[parserFlags allowParagraphInIdentifier])
+                      or:[(nextChar notNil and:[nextChar isNationalLetter]) and:[allowNationalCharactersInIdentifier]]]].
             ]
         ].
     ].
@@ -2849,7 +2884,7 @@
     ^ tokenType
 
     "Created: / 13-09-1995 / 12:56:42 / claus"
-    "Modified: / 24-11-2006 / 10:38:47 / cg"
+    "Modified: / 17-11-2016 / 09:19:46 / cg"
 !
 
 nextMantissa:radix
@@ -3461,15 +3496,24 @@
                 tok notNil ifTrue:[
                     ^ tok
                 ].
+                "/ a nil token means: continue reading
             ] ifFalse:[
-                ^ self invalidCharacter:ch.
-            ]
+                (ch == $§ and:[parserFlags allowParagraphInIdentifier]) ifTrue:[
+                    tok := self nextIdentifier.
+                    tok notNil ifTrue:[
+                        ^ tok
+                    ].
+                    "/ a nil token means: continue reading
+                ] ifFalse:[
+                    ^ self invalidCharacter:ch.
+                ].
+            ].
         ]
     ] loop.
 
     "Modified: / 13-09-1995 / 12:56:14 / claus"
-    "Modified: / 25-03-2011 / 13:56:28 / cg"
     "Modified: / 27-07-2011 / 15:36:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 17-11-2016 / 09:35:39 / cg"
 !
 
 nextToken:aCharacter
--- a/stx_libcomp.st	Fri Nov 18 21:21:39 2016 +0000
+++ b/stx_libcomp.st	Mon Nov 28 17:14:44 2016 +0000
@@ -1,5 +1,5 @@
 "
- COPYRIGHT (c) 2006 by eXept Software AG
+ COPYRIGHT (c) 1989 by Claus Gittinger / eXept Software AG
               All Rights Reserved
 
  This software is furnished under a license and may be used
@@ -24,7 +24,7 @@
 
 copyright
 "
- COPYRIGHT (c) 2006 by eXept Software AG
+ COPYRIGHT (c) 1989 by Claus Gittinger / eXept Software AG
               All Rights Reserved
 
  This software is furnished under a license and may be used
@@ -44,7 +44,7 @@
     and related support classes (AST representation).
 
     This compiler is used when code is changed within the running IDE or application,
-    and when source code is loaded.
+    and when source code is loaded (fileIn).
     It generates bytecode methods, which are (typically) further translated to machine code by the VM,
     when first executed 
     (although for some architectures, no JITTER is available, and the bytecode will be interpreted, 
@@ -56,6 +56,12 @@
     And only patches or dynamically generated code uses bytecode methods.
     Therefore, the speed of the bytecode interpreter is usually not at all relevant to a deployed app's 
     overall speed (and also not to the ST/X IDE itself, as it also consists of precompiled machine code).
+
+    [author:]
+        cg
+
+    [primary maintainer:]
+        cg
 "
 ! !
 
@@ -304,7 +310,9 @@
 companyName
     "Return a companyname which will appear in <lib>.rc"
 
-    ^ 'eXept Software AG'
+    ^ 'Claus Gittinger / eXept Software AG'
+
+    "Modified: / 18-11-2016 / 11:48:29 / cg"
 !
 
 description
@@ -316,9 +324,9 @@
 legalCopyright
     "Return copyright string which will appear in <lib>.rc"
 
-    ^ 'Copyright Claus Gittinger 1988-2012\nCopyright eXept Software AG 2012'
+    ^ 'Copyright Claus Gittinger 1988\nCopyright eXept Software AG 2012'
 
-    "Modified: / 18-07-2012 / 19:11:33 / cg"
+    "Modified: / 18-11-2016 / 12:17:52 / cg"
 !
 
 productName