better undef-variable message;
authorClaus Gittinger <cg@exept.de>
Thu, 21 Oct 1999 00:46:26 +0200
changeset 989 6e535d9d87d8
parent 988 5b38d970fb1a
child 990 cd1aa00086fd
better undef-variable message; more suggestions for correct
Parser.st
--- a/Parser.st	Mon Oct 18 15:35:59 1999 +0200
+++ b/Parser.st	Thu Oct 21 00:46:26 1999 +0200
@@ -2096,7 +2096,9 @@
             how := how , #( WorkspaceVariable ).
         ].
         l size > 0 ifTrue:[
-            l := (Array with:('Declare ' , varName asText allBold , ' as:') with:'=') , l.
+            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:[
@@ -2266,7 +2268,7 @@
      return the 10 best suggestions"
 
     |names dists searchBlock args vars globalVarName "aClass className baseClass" 
-     n instVarNames|
+     n instVarNames classVarNames|
 
     names := OrderedCollection new.
     dists := OrderedCollection new.
@@ -2274,54 +2276,54 @@
     "block arguments"
     searchBlock := currentBlock.
     [searchBlock notNil] whileTrue:[
-	args := searchBlock arguments.
-	args notNil ifTrue:[
-	    args do:[:aBlockArg |
-		names add:(aBlockArg name).
-		dists add:(aString spellAgainst: "levenshteinTo:"(aBlockArg name))
-	    ]
-	].
-
-	vars := searchBlock variables.
-	vars notNil ifTrue:[
-	    vars do:[:aBlockVar |
-		names add:(aBlockVar name).
-		dists add:(aString spellAgainst: "levenshteinTo:"(aBlockVar name))
-	    ]
-	].
-	searchBlock := searchBlock home
+        args := searchBlock arguments.
+        args notNil ifTrue:[
+            args do:[:aBlockArg |
+                names add:(aBlockArg name).
+                dists add:(aString spellAgainst: "levenshteinTo:"(aBlockArg name))
+            ]
+        ].
+
+        vars := searchBlock variables.
+        vars notNil ifTrue:[
+            vars do:[:aBlockVar |
+                names add:(aBlockVar name).
+                dists add:(aString spellAgainst: "levenshteinTo:"(aBlockVar name))
+            ]
+        ].
+        searchBlock := searchBlock home
     ].
 
     "method-variables"
     methodVars notNil ifTrue:[
-	methodVarNames do:[:methodVarName |
-	    names add:methodVarName.
-	    dists add:(aString spellAgainst: "levenshteinTo:"methodVarName)
-	]
+        methodVarNames do:[:methodVarName |
+            names add:methodVarName.
+            dists add:(aString spellAgainst: "levenshteinTo:"methodVarName)
+        ]
     ].
 
     "method-arguments"
     methodArgs notNil ifTrue:[
-	methodArgNames do:[:methodArgName |
-	    names add:methodArgName.
-	    dists add:(aString spellAgainst: "levenshteinTo:"methodArgName)
-	]
+        methodArgNames do:[:methodArgName |
+            names add:methodArgName.
+            dists add:(aString spellAgainst: "levenshteinTo:"methodArgName)
+        ]
     ].
 
     "instance-variables"
     classToCompileFor notNil ifTrue:[
-	self classesInstVarNames do:[:instVarName |
-	    names add:instVarName.
-	    dists add:(aString spellAgainst: "levenshteinTo:"instVarName)
-	]
+        self classesInstVarNames do:[:instVarName |
+            names add:instVarName.
+            dists add:(aString spellAgainst: "levenshteinTo:"instVarName)
+        ]
     ].
 
     "class-variables"
     classToCompileFor notNil ifTrue:[
-	self classesClassVarNames do:[:classVarName |
-	    names add:classVarName.
-	    dists add:(aString spellAgainst: "levenshteinTo:"classVarName)
-	].
+        self classesClassVarNames do:[:classVarName |
+            names add:classVarName.
+            dists add:(aString spellAgainst: "levenshteinTo:"classVarName)
+        ].
 
 "/        aClass := classToCompileFor.
 "/        aClass isMeta ifTrue:[
@@ -2344,62 +2346,82 @@
 
     "globals"
     Smalltalk keysDo:[:aKey |
-	globalVarName := aKey asString.
-	"only compare strings where length is about right"
-	((globalVarName size - aString size) abs < 3) ifTrue:[
-	    names add:globalVarName.
-	    dists add:(aString spellAgainst: "levenshteinTo:"globalVarName)
-	]
+        globalVarName := aKey asString.
+        "only compare strings where length is about right"
+        ((globalVarName size - aString size) abs < 3) ifTrue:[
+            names add:globalVarName.
+            dists add:(aString spellAgainst: "levenshteinTo:"globalVarName)
+        ]
     ].
 
     "misc"
     #('self' 'super' 'nil' 'thisContext') do:[:name |
-	names add:name.
-	dists add:(aString spellAgainst: "levenshteinTo:"name)
+        names add:name.
+        dists add:(aString spellAgainst: "levenshteinTo:"name)
     ].
 
     (dists size ~~ 0) ifTrue:[
-	dists sortWith:names.
-	dists := dists reverse.             
-	names := names reverse.
-	n := names size min:10.
-	names := names copyTo:n.
-
-	"if it starts with a lower case character, add all local & instvar names"
-	(aString at:1) isLowercase ifTrue:[
-	    methodVarNames size > 0 ifTrue:[
-		names add:'---- method locals ----'.
-		methodVarNames asSortedCollection do:[:methodVarName |
-		    names add:methodVarName.
-		].
-	    ].
-
-
-	    methodArgs size > 0 ifTrue:[
-		names add:'---- method arguments ----'.
-		methodArgNames asSortedCollection do:[:methodArgName |
-		    names add:methodArgName.
-		]
-	    ].
-
-	    instVarNames := OrderedCollection new.
-	    self classesInstVarNames asSortedCollection do:[:instVarName |
-		(instVarNames includes:instVarName) ifFalse:[
-		    instVarNames add:instVarName.
-		]
-	    ].
-
-	    instVarNames size > 0 ifTrue:[
-		names add:'---- instance variables ----'.
-		instVarNames do:[:instVarName |
-		    (names includes:instVarName) ifFalse:[
-			names add:instVarName.
-		    ]
-		]
-	    ]
-	].
-
-	^ names
+        dists sortWith:names.
+        dists := dists reverse.             
+        names := names reverse.
+        n := names size min:10.
+        names := names copyTo:n.
+
+        "if it starts with a lower case character, add all local & instvar names"
+        (aString at:1) isLowercase ifTrue:[
+            methodVarNames size > 0 ifTrue:[
+                names add:'---- method locals ----'.
+                methodVarNames asSortedCollection do:[:methodVarName |
+                    names add:methodVarName.
+                ].
+            ].
+
+
+            methodArgs size > 0 ifTrue:[
+                names add:'---- method arguments ----'.
+                methodArgNames asSortedCollection do:[:methodArgName |
+                    names add:methodArgName.
+                ]
+            ].
+
+            instVarNames := OrderedCollection new.
+            self classesInstVarNames asSortedCollection do:[:instVarName |
+                (instVarNames includes:instVarName) ifFalse:[
+                    instVarNames add:instVarName.
+                ]
+            ].
+
+            instVarNames size > 0 ifTrue:[
+                (classToCompileFor notNil and:[classToCompileFor isMeta]) ifTrue:[
+                    names add:'---- class instance variables ----'.
+                ] ifFalse:[
+                    names add:'---- instance variables ----'.
+                ].
+                instVarNames do:[:instVarName |
+                    (names includes:instVarName) ifFalse:[
+                        names add:instVarName.
+                    ]
+                ]
+            ].
+
+            classVarNames := OrderedCollection new.
+            self classesClassVarNames asSortedCollection do:[:classVarName |
+                (classVarNames includes:classVarName) ifFalse:[
+                    classVarNames add:classVarName.
+                ]
+            ].
+
+            classVarNames size > 0 ifTrue:[
+                names add:'---- class variables ----'.
+                classVarNames do:[:classVarName |
+                    (names includes:classVarName) ifFalse:[
+                        names add:classVarName.
+                    ]
+                ]
+            ].
+        ].
+
+        ^ names
     ].
     ^ nil
 
@@ -2690,11 +2712,18 @@
         "
         msg := 'Warning: ''' , aName , ''' is undefined'.
         classToCompileFor notNil ifTrue:[
-            "is it an instance-variable marked inaccessable ?"
+            "/ 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)'.
+            ].
+
+            "/ is it an instance variable, while evaluateing for the class ?
+            classToCompileFor isMeta ifTrue:[
+                (classToCompileFor soleInstance allInstVarNames includes:aName) ifTrue:[
+                    msg := 'Warning: ' , aName , ' is an instvar\(hint: you are evaluating/compiling in the classes context)' withCRs.
+                ]
             ]
         ].
 
@@ -5264,6 +5293,6 @@
 !Parser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.229 1999-10-18 13:35:59 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.230 1999-10-20 22:46:26 cg Exp $'
 ! !
 Parser initialize!