Parser.st
changeset 98 ccc7f9389a8e
parent 97 3b0d380771e9
child 101 845d70bbd94d
equal deleted inserted replaced
97:3b0d380771e9 98:ccc7f9389a8e
    30 			      logged
    30 			      logged
    31 			      warnedUndefVars warnSTXHereExtensionUsed
    31 			      warnedUndefVars warnSTXHereExtensionUsed
    32 			      correctedSource'
    32 			      correctedSource'
    33        classVariableNames:'PrevClass PrevInstVarNames 
    33        classVariableNames:'PrevClass PrevInstVarNames 
    34 			   PrevClassVarNames PrevClassInstVarNames
    34 			   PrevClassVarNames PrevClassInstVarNames
    35 			   LazyCompilation ArraysAreImmutable'
    35 			   LazyCompilation ArraysAreImmutable
       
    36 			   ImplicitSelfSends'
    36        poolDictionaries:''
    37        poolDictionaries:''
    37        category:'System-Compiler'
    38        category:'System-Compiler'
    38 !
    39 !
    39 
    40 
    40 Parser comment:'
    41 Parser comment:'
    41 COPYRIGHT (c) 1989 by Claus Gittinger
    42 COPYRIGHT (c) 1989 by Claus Gittinger
    42 	     All Rights Reserved
    43 	     All Rights Reserved
    43 
    44 
    44 $Header: /cvs/stx/stx/libcomp/Parser.st,v 1.45 1995-07-03 02:38:44 claus Exp $
    45 $Header: /cvs/stx/stx/libcomp/Parser.st,v 1.46 1995-07-23 02:23:59 claus Exp $
    45 '!
    46 '!
    46 
    47 
    47 !Parser class methodsFor:'documentation'!
    48 !Parser class methodsFor:'documentation'!
    48 
    49 
    49 copyright
    50 copyright
    60 "
    61 "
    61 !
    62 !
    62 
    63 
    63 version
    64 version
    64 "
    65 "
    65 $Header: /cvs/stx/stx/libcomp/Parser.st,v 1.45 1995-07-03 02:38:44 claus Exp $
    66 $Header: /cvs/stx/stx/libcomp/Parser.st,v 1.46 1995-07-23 02:23:59 claus Exp $
    66 "
    67 "
    67 !
    68 !
    68 
    69 
    69 documentation
    70 documentation
    70 "
    71 "
   476 ! !
   477 ! !
   477 
   478 
   478 !Parser class methodsFor:'initialization '!
   479 !Parser class methodsFor:'initialization '!
   479 
   480 
   480 initialize
   481 initialize
   481     LazyCompilation := false.   "/ usually set to true in your .rc file
   482     LazyCompilation := false.      "/ usually set to true in your .rc file
   482     ArraysAreImmutable := false "/ usually left true for ST-80 compatibility
   483     ArraysAreImmutable := false.   "/ usually left true for ST-80 compatibility
       
   484     ImplicitSelfSends := false
   483 ! !
   485 ! !
   484 
   486 
   485 !Parser class methodsFor:'instance creation'!
   487 !Parser class methodsFor:'instance creation'!
   486 
   488 
   487 for:aStringOrStream in:aClass
   489 for:aStringOrStream in:aClass
   852     "
   854     "
   853      can be added to your private.rc file:
   855      can be added to your private.rc file:
   854 
   856 
   855      Compiler arraysAreImmutable:true     
   857      Compiler arraysAreImmutable:true     
   856      Compiler arraysAreImmutable:false      
   858      Compiler arraysAreImmutable:false      
       
   859     "
       
   860 !
       
   861 
       
   862 implicitSelfSends
       
   863     "return true if undefined variables with
       
   864      lowercase first character are to be turned
       
   865      into implicit self sends"
       
   866 
       
   867     ^ ImplicitSelfSends
       
   868 !
       
   869 
       
   870 implicitSelfSends:aBoolean
       
   871     "turn on/off implicit self sends"
       
   872 
       
   873     ImplicitSelfSends := aBoolean
       
   874 
       
   875     "
       
   876      Compiler implicitSelfSends:true
       
   877      Compiler implicitSelfSends:false 
   857     "
   878     "
   858 ! !
   879 ! !
   859 
   880 
   860 !Parser methodsFor:'ST-80 compatibility'!
   881 !Parser methodsFor:'ST-80 compatibility'!
   861 
   882 
  2225     ].
  2246     ].
  2226 
  2247 
  2227     classToCompileFor notNil ifTrue:[
  2248     classToCompileFor notNil ifTrue:[
  2228 	"is it an instance-variable ?"
  2249 	"is it an instance-variable ?"
  2229 
  2250 
  2230 	instIndex := (self instVarNames) indexOf:varName startingAt:1.
  2251 	instIndex := (self instVarNames) lastIndexOf:varName.
  2231 	instIndex ~~ 0 ifTrue:[
  2252 	instIndex ~~ 0 ifTrue:[
  2232 	    parseForCode ifFalse:[self rememberInstVarUsed:varName].
  2253 	    parseForCode ifFalse:[self rememberInstVarUsed:varName].
  2233 	    ^ VariableNode type:#InstanceVariable 
  2254 	    ^ VariableNode type:#InstanceVariable 
  2234 			   name:varName
  2255 			   name:varName
  2235 			  index:instIndex
  2256 			  index:instIndex
  2236 		      selfValue:selfValue
  2257 		      selfValue:selfValue
  2237 	].
  2258 	].
  2238 
  2259 
  2239 	"is it a class-instance-variable ?"
  2260 	"is it a class-instance-variable ?"
  2240 
  2261 
  2241 	instIndex := (self classInstVarNames) indexOf:varName startingAt:1.
  2262 	instIndex := (self classInstVarNames) lastIndexOf:varName.
  2242 	instIndex ~~ 0 ifTrue:[
  2263 	instIndex ~~ 0 ifTrue:[
  2243 	    aClass := self inWhichClassIsClassInstVar:varName.
  2264 	    aClass := self inWhichClassIsClassInstVar:varName.
  2244 	    aClass notNil ifTrue:[
  2265 	    aClass notNil ifTrue:[
  2245 		parseForCode ifFalse:[self rememberClassVarUsed:varName].
  2266 		parseForCode ifFalse:[self rememberClassVarUsed:varName].
  2246 		^ VariableNode type:#ClassInstanceVariable
  2267 		^ VariableNode type:#ClassInstanceVariable
  2250 	    ]
  2271 	    ]
  2251 	].
  2272 	].
  2252 
  2273 
  2253 	"is it a class-variable ?"
  2274 	"is it a class-variable ?"
  2254 
  2275 
  2255 	instIndex := (self classVarNames) indexOf:varName startingAt:1.
  2276 	instIndex := (self classVarNames) lastIndexOf:varName.
  2256 	instIndex ~~ 0 ifTrue:[
  2277 	instIndex ~~ 0 ifTrue:[
  2257 	    aClass := self inWhichClassIsClassVar:varName.
  2278 	    aClass := self inWhichClassIsClassVar:varName.
  2258 	    aClass notNil ifTrue:[
  2279 	    aClass notNil ifTrue:[
  2259 		parseForCode ifFalse:[self rememberClassVarUsed:varName].
  2280 		parseForCode ifFalse:[self rememberClassVarUsed:varName].
  2260 		^ VariableNode type:#ClassVariable 
  2281 		^ VariableNode type:#ClassVariable class:aClass name:varName
  2261 			       name:(aClass name , ':' , varName) asSymbol
       
  2262 	    ]
  2282 	    ]
  2263 	]
  2283 	]
  2264     ].
  2284     ].
  2265 
  2285 
  2266     "is it a global-variable ?"
  2286     "is it a global-variable ?"
  2281 
  2301 
  2282     v := self variableOrError.
  2302     v := self variableOrError.
  2283     (v == #Error) ifFalse:[^ v].
  2303     (v == #Error) ifFalse:[^ v].
  2284     v := self correctVariable.
  2304     v := self correctVariable.
  2285     (v == #Error) ifFalse:[^ v].
  2305     (v == #Error) ifFalse:[^ v].
  2286     parseForCode ifFalse:[self rememberGlobalUsed:tokenName].
  2306     parseForCode ifFalse:[
       
  2307 	self rememberGlobalUsed:tokenName
       
  2308     ] ifTrue:[
       
  2309 	tokenName first isLowercase ifTrue:[
       
  2310 	    ImplicitSelfSends ifTrue:[
       
  2311 		selfNode isNil ifTrue:[
       
  2312 		    selfNode := SelfNode value:selfValue
       
  2313 		].
       
  2314 		^ UnaryNode receiver:selfNode selector:('implicit_' , tokenName) asSymbol.
       
  2315 	    ]
       
  2316 	]
       
  2317     ].
  2287     ^ VariableNode type:#GlobalVariable name:tokenName asSymbol
  2318     ^ VariableNode type:#GlobalVariable name:tokenName asSymbol
  2288 !
  2319 !
  2289 
  2320 
  2290 inWhichClassIsClassVar:aString
  2321 inWhichClassIsClassVar:aString
  2291     "search class-chain for the classvariable named aString
  2322     "search class-chain for the classvariable named aString
  2320     [aClass notNil] whileTrue:[
  2351     [aClass notNil] whileTrue:[
  2321 	(aClass class instVarNames includes:aString) ifTrue:[ ^ aClass].
  2352 	(aClass class instVarNames includes:aString) ifTrue:[ ^ aClass].
  2322 	aClass := aClass superclass
  2353 	aClass := aClass superclass
  2323     ].
  2354     ].
  2324     ^ nil
  2355     ^ nil
       
  2356 !
       
  2357 
       
  2358 blockExpression
       
  2359     "parse a blockExpression; return a node-tree, nil or #Error.
       
  2360      Not used by ST/X's parser, but added for ST-80 compatibility."
       
  2361 
       
  2362     tokenType ~~ $[ ifTrue:[
       
  2363 	self syntaxError:'[ expected'.
       
  2364 	^ #Error.
       
  2365     ].
       
  2366     ^ self block
  2325 !
  2367 !
  2326 
  2368 
  2327 block
  2369 block
  2328     "parse a block; return a node-tree, nil or #Error"
  2370     "parse a block; return a node-tree, nil or #Error"
  2329 
  2371 
  2827 "
  2869 "
  2828 	newName := suggestedNames at:1.
  2870 	newName := suggestedNames at:1.
  2829 	(self confirm:('confirm correction to: ' , newName)) ifFalse:[^ #Error]
  2871 	(self confirm:('confirm correction to: ' , newName)) ifFalse:[^ #Error]
  2830 "
  2872 "
  2831     ] ifFalse:[
  2873     ] ifFalse:[
  2832 	self notify:'no good correction found'.
  2874 	self information:'no good correction found'.
  2833 	^ #Error
  2875 	^ #Error
  2834     ].
  2876     ].
  2835 
  2877 
  2836     "
  2878     "
  2837      tell requestor (i.e. CodeView) about the change
  2879      tell requestor (i.e. CodeView) about the change
  2921     suggestedNames := self findBestSelectorsFor:aSelectorString.
  2963     suggestedNames := self findBestSelectorsFor:aSelectorString.
  2922     suggestedNames notNil ifTrue:[
  2964     suggestedNames notNil ifTrue:[
  2923 	newSelector := self askForCorrection:'correct selector to: ' fromList:suggestedNames.
  2965 	newSelector := self askForCorrection:'correct selector to: ' fromList:suggestedNames.
  2924 	newSelector isNil ifTrue:[^ aSelectorString].
  2966 	newSelector isNil ifTrue:[^ aSelectorString].
  2925     ] ifFalse:[
  2967     ] ifFalse:[
  2926 	self notify:'no good correction found'.
  2968 	self information:'no good correction found'.
  2927 	^ aSelectorString
  2969 	^ aSelectorString
  2928     ].
  2970     ].
  2929 
  2971 
  2930     "
  2972     "
  2931      tell requestor (i.e. CodeView) about the change
  2973      tell requestor (i.e. CodeView) about the change