Parser.st
branchjv
changeset 4061 ebdd14acce2d
parent 4056 d75b18246677
parent 4054 93b38c1d51ef
child 4067 990997b11137
--- 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