Parser.st
changeset 877 e75488a39c46
parent 869 c483b1e6a0c3
child 878 f9c8d2544909
--- a/Parser.st	Sat Jun 26 16:31:17 1999 +0200
+++ b/Parser.st	Sat Jun 26 16:31:42 1999 +0200
@@ -1945,14 +1945,17 @@
      return #Error if there was no correction 
      or a ParseNode as returned by variable"
 
-    |correctIt varName suggestedNames newName pos1 pos2 rslt|
+    |correctIt varName suggestedNames newName pos1 pos2 rslt
+     varNameIsLowercase l how choice holder|
 
     pos1 := tokenPosition.
     varName := tokenName.
     pos2 := pos1 + varName size - 1.
 
+    varNameIsLowercase := (varName at:1) isLowercase.
+
 "OLD:
-    (varName at:1) isLowercase ifTrue:[
+    varNameIsLowercase ifTrue:[
         correctIt := self undefError:varName position:pos1 to:pos2.
         correctIt ifFalse:[^ #Error]
     ] ifFalse:[
@@ -1964,32 +1967,89 @@
 "
 
     correctIt := self undefError:varName position:pos1 to:pos2.
-    correctIt ifFalse:[
-        (varName at:1) isLowercase ifTrue:[
+    correctIt == false ifTrue:[
+        "/ no correction wanted.
+
+        "/ lowerCase vars are added to the Undeclared dictionary,
+        "/ allowing easy search for bad-spots later.
+
+        varNameIsLowercase ifTrue:[
             ((Smalltalk includesKey:#Undeclared)
             and:[((Smalltalk at:#Undeclared) includes:varName asSymbol)]) ifFalse:[ 
                 self warning:('adding ''' , varName , ''' as Undeclared.\\Remember to fix that later.') withCRs position:pos1 to:pos2.
             ].
             ^ self defineAsUndeclaredVariable:varName
+        ].
+
+        "/ upperCase vars are declared as global
+        self warning:('adding ''' , varName , ''' as Global.') withCRs position:pos1 to:pos2.
+        ^ VariableNode type:#GlobalVariable name:(varName asSymbol)
+    ].
+
+    correctIt == #declare ifTrue:[
+        "/ declare it
+        l := #().
+        how := #().
+
+        varNameIsLowercase ifTrue:[
+            currentBlock notNil ifTrue:[
+                l := l , #( 'Block local' ).
+                how := how , #( BlockVariable ).
+            ].
+            selector notNil ifTrue:[
+                l := l , #( 'Method local' ).
+                how := how , #( MethodVariable ).
+            ].
+            (classToCompileFor notNil
+            and:[classToCompileFor isMeta not
+            and:[classToCompileFor isBuiltInClass not]]) ifTrue:[
+                l := l , (Array with:( 'Instance variable of ' , classToCompileFor name )).
+                how := how , #( InstanceVariable ).
+            ].
         ] ifFalse:[
-            self warning:('adding ''' , varName , ''' as Global.') withCRs position:pos1 to:pos2.
-            ^ VariableNode type:#GlobalVariable name:(varName asSymbol)
+            l := l , #(
+                   'Global'
+                   'Class Variable'
+                  ).
+            how := how , #( GlobalVariable Classvariable ).
+        ].
+        (requestor notNil and:[requestor isStream not]) ifTrue:[
+            l size > 0 ifTrue:[
+                l := l ,  #( '-' ).
+                how := how , #( nil ).
+            ].
+            l := l , #( 'Workspace variable' ).
+            how := how , #( WorkspaceVariable ).
+        ].
+        l size > 0 ifTrue:[
+            l := (Array with:('Declare ' , varName asText allBold , ' as:') with:'=') , l.
+            how := #(nil nil) , how.
+            choice := (PopUpMenu labels:l) startUp.
+            (choice notNil and:[choice > 0]) ifTrue:[
+                choice := how at:choice.
+
+                choice == #WorkspaceVariable ifTrue:[
+                    holder := Workspace addWorkspaceVariable:varName.
+                    ^ VariableNode type:#WorkspaceVariable holder:holder name:varName
+                ].
+            ].
+self halt.
         ]
     ].
 
     suggestedNames := self findBestVariablesFor:varName.
-    suggestedNames notNil ifTrue:[
-        newName := self askForCorrection:'correct variable to: ' fromList:suggestedNames.
-        newName isNil ifTrue:[^ #Error].
-"
-        newName := suggestedNames at:1.
-        (self confirm:('confirm correction to: ' , newName)) ifFalse:[^ #Error]
-"
-    ] ifFalse:[
+    suggestedNames isNil ifTrue:[
         self information:'no good correction found'.
         ^ #Error
     ].
 
+    newName := self askForCorrection:'correct variable to: ' fromList:suggestedNames.
+    newName isNil ifTrue:[^ #Error].
+"
+        newName := suggestedNames at:1.
+        (self confirm:('confirm correction to: ' , newName)) ifFalse:[^ #Error].
+"
+
     "
      tell requestor (i.e. CodeView) about the change
      this will update what the requestor shows.
@@ -2457,10 +2517,10 @@
      alredy warned about this one ?
     "
     warnedUndefVars notNil ifTrue:[
-	(warnedUndefVars includes:aName) ifTrue:[
-	    "already warned about this one"
-	    ^ false
-	].
+        (warnedUndefVars includes:aName) ifTrue:[
+            "already warned about this one"
+            ^ false
+        ].
     ].
 
 "/    (classToCompileFor notNil 
@@ -2471,34 +2531,34 @@
 "/    ].
 
     (requestor isNil or:[requestor isStream]) ifTrue:[
-	aName first isUppercase ifFalse:[
-	    self showErrorMessage:('Error: ''' , aName , ''' is undefined') position:pos1.
-	].
-	doCorrect := false.
+        aName first isUppercase ifFalse:[
+            self showErrorMessage:('Error: ''' , aName , ''' is undefined') position:pos1.
+        ].
+        doCorrect := false.
     ] ifFalse:[
-	"
-	 ask requestor for correct/continue/abort ...
-	 it is supposed to raise abort or return true/false.
-	 True return means that correction is wanted.
-	"
-	msg := 'Warning: ''' , aName , ''' is undefined'.
-	classToCompileFor notNil ifTrue:[
-	    "is it an instance-variable marked inaccessable ?"
-
-	    idx := (self classesInstVarNames) indexOf:(aName , '*') startingAt:1.
-	    idx ~~ 0 ifTrue:[
-		msg := 'Warning: ' , aName , ' is a hidden instvar (not accessable from ST-code)'.
-	    ]
-	].
-
-	doCorrect := self correctableError:msg position:pos1 to:pos2
+        "
+         ask requestor for correct/continue/abort ...
+         it is supposed to raise abort or return true/false.
+         True return means that correction is wanted.
+        "
+        msg := 'Warning: ''' , aName , ''' is undefined'.
+        classToCompileFor notNil ifTrue:[
+            "is it an instance-variable marked inaccessable ?"
+
+            idx := (self classesInstVarNames) indexOf:(aName , '*') startingAt:1.
+            idx ~~ 0 ifTrue:[
+                msg := 'Warning: ' , aName , ' is a hidden instvar (not accessable from ST-code)'.
+            ]
+        ].
+
+        doCorrect := self correctableError:msg position:pos1 to:pos2
     ].
 
-    doCorrect ifFalse:[
-	warnedUndefVars isNil ifTrue:[
-	    warnedUndefVars := Set new.
-	].
-	warnedUndefVars add:aName.
+    doCorrect == false ifTrue:[
+        warnedUndefVars isNil ifTrue:[
+            warnedUndefVars := Set new.
+        ].
+        warnedUndefVars add:aName.
     ].
 
     ^ doCorrect
@@ -4060,7 +4120,7 @@
     "parse a variable; return a node-tree, nil or #Error"
 
     |var varIndex aClass searchBlock args vars
-     tokenSymbol space classVarIndex|
+     tokenSymbol space classVarIndex holder|
 
     "is it a block-arg or block-var ?"
     searchBlock := currentBlock.
@@ -4259,6 +4319,19 @@
         ]
     ].
 
+    "is it a workspace 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
+        (selector isNil or:[selector == #doIt]) ifTrue:[
+            (holder := Workspace workspaceVariableAt:varName) notNil ifTrue:[
+                ^ VariableNode type:#WorkspaceVariable holder:holder name:varName
+            ]
+        ]
+    ].
+
     ^ #Error
 
     "Modified: / 8.3.1999 / 01:35:56 / cg"
@@ -4761,6 +4834,6 @@
 !Parser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.202 1999-06-25 14:54:45 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.203 1999-06-26 14:31:42 cg Exp $'
 ! !
 Parser initialize!