NewInspectorList.st
changeset 2621 285fa261cbcb
parent 1213 6cf7a4c2dfce
child 3612 959a338e5888
equal deleted inserted replaced
2620:fccbd77a9409 2621:285fa261cbcb
     1 "
     1 "
     2  COPYRIGHT (c) 1997 by eXept Software AG
     2  COPYRIGHT (c) 1997 by eXept Software AG
     3               All Rights Reserved
     3 	      All Rights Reserved
     4 
     4 
     5  This software is furnished under a license and may be used
     5  This software is furnished under a license and may be used
     6  only in accordance with the terms of that license and with the
     6  only in accordance with the terms of that license and with the
     7  inclusion of the above copyright notice.   This software may not
     7  inclusion of the above copyright notice.   This software may not
     8  be provided or otherwise made available to, or used by, any
     8  be provided or otherwise made available to, or used by, any
     9  other person.  No title to or ownership of the software is
     9  other person.  No title to or ownership of the software is
    10  hereby transferred.
    10  hereby transferred.
    11 "
    11 "
    12 
    12 
    13 
    13 
    14 "{ NameSpace: NewInspector }"
    14 "{ NameSpace: Tools }"
    15 
    15 
    16 Object subclass:#NewInspectorList
    16 Object subclass:#NewInspectorList
    17 	instanceVariableNames:'inspectedObject instanceNames instanceTypes selection'
    17 	instanceVariableNames:'inspectedObject instanceNames instanceTypes selection'
    18 	classVariableNames:''
    18 	classVariableNames:''
    19 	poolDictionaries:''
    19 	poolDictionaries:''
    23 !NewInspectorList class methodsFor:'documentation'!
    23 !NewInspectorList class methodsFor:'documentation'!
    24 
    24 
    25 copyright
    25 copyright
    26 "
    26 "
    27  COPYRIGHT (c) 1997 by eXept Software AG
    27  COPYRIGHT (c) 1997 by eXept Software AG
    28               All Rights Reserved
    28 	      All Rights Reserved
    29 
    29 
    30  This software is furnished under a license and may be used
    30  This software is furnished under a license and may be used
    31  only in accordance with the terms of that license and with the
    31  only in accordance with the terms of that license and with the
    32  inclusion of the above copyright notice.   This software may not
    32  inclusion of the above copyright notice.   This software may not
    33  be provided or otherwise made available to, or used by, any
    33  be provided or otherwise made available to, or used by, any
    62      string.
    62      string.
    63     "
    63     "
    64     |string|
    64     |string|
    65 
    65 
    66     aCollection isCollection ifTrue:[
    66     aCollection isCollection ifTrue:[
    67         aCollection isString ifTrue:[
    67 	aCollection isString ifTrue:[
    68             string := aCollection
    68 	    string := aCollection
    69         ] ifFalse:[
    69 	] ifFalse:[
    70             string := aCollection asStringWith:Character space
    70 	    string := aCollection asStringWith:Character space
    71                                           from:1 to:(aCollection size)
    71 					  from:1 to:(aCollection size)
    72                                   compressTabs:true 
    72 				  compressTabs:true
    73                                          final:nil
    73 					 final:nil
    74         ].
    74 	].
    75         string := string withoutSeparators.
    75 	string := string withoutSeparators.
    76 
    76 
    77         string notEmpty ifTrue:[
    77 	string notEmpty ifTrue:[
    78             ^ string
    78 	    ^ string
    79         ]
    79 	]
    80     ].
    80     ].
    81     ^ nil
    81     ^ nil
    82 
    82 
    83 
    83 
    84 ! !
    84 ! !
    89     "returns true if the instance is a directory
    89     "returns true if the instance is a directory
    90     "
    90     "
    91     |cls|
    91     |cls|
    92 
    92 
    93     anInstance notNil ifTrue:[
    93     anInstance notNil ifTrue:[
    94         cls := anInstance class.
    94 	cls := anInstance class.
    95 
    95 
    96         cls == Character  ifTrue:[ ^ false ].
    96 	cls == Character  ifTrue:[ ^ false ].
    97         cls == Symbol     ifTrue:[ ^ false ].
    97 	cls == Symbol     ifTrue:[ ^ false ].
    98         cls == String     ifTrue:[ ^ false ].
    98 	cls == String     ifTrue:[ ^ false ].
    99         cls == Float      ifTrue:[ ^ false ].
    99 	cls == Float      ifTrue:[ ^ false ].
   100         cls == ShortFloat ifTrue:[ ^ false ].
   100 	cls == ShortFloat ifTrue:[ ^ false ].
   101 
   101 
   102         cls allInstVarNames notEmpty ifTrue:[
   102 	cls allInstVarNames notEmpty ifTrue:[
   103             ^ true
   103 	    ^ true
   104         ].
   104 	].
   105 
   105 
   106         anInstance isVariable ifTrue:[
   106 	anInstance isVariable ifTrue:[
   107             ^ true
   107 	    ^ true
   108         ].
   108 	].
   109     ].
   109     ].
   110     ^ false
   110     ^ false
   111 
   111 
   112     "Modified: / 4.2.1999 / 20:00:11 / cg"
   112     "Modified: / 4.2.1999 / 20:00:11 / cg"
   113 !
   113 !
   116     "returns true if the instance could be traced or traped
   116     "returns true if the instance could be traced or traped
   117     "
   117     "
   118     |cls|
   118     |cls|
   119 
   119 
   120     anInstance notNil ifTrue:[
   120     anInstance notNil ifTrue:[
   121         cls := anInstance class.
   121 	cls := anInstance class.
   122 
   122 
   123       ^ (     cls ~~ True
   123       ^ (     cls ~~ True
   124          and:[cls ~~ False
   124 	 and:[cls ~~ False
   125          and:[cls ~~ SmallInteger]]
   125 	 and:[cls ~~ SmallInteger]]
   126         )
   126 	)
   127     ].
   127     ].
   128     ^ false.
   128     ^ false.
   129 
   129 
   130 ! !
   130 ! !
   131 
   131 
   133 
   133 
   134 includesSelf:aBoolean
   134 includesSelf:aBoolean
   135     "includes 'self' dependant on the boolean
   135     "includes 'self' dependant on the boolean
   136     "
   136     "
   137     (self includesSelf) ~~ aBoolean ifTrue:[
   137     (self includesSelf) ~~ aBoolean ifTrue:[
   138         aBoolean ifTrue:[
   138 	aBoolean ifTrue:[
   139             instanceNames addFirst:'self'.
   139 	    instanceNames addFirst:'self'.
   140             instanceTypes addFirst:#self.
   140 	    instanceTypes addFirst:#self.
   141 
   141 
   142             selection notNil ifTrue:[selection := selection + 1]
   142 	    selection notNil ifTrue:[selection := selection + 1]
   143                             ifFalse:[selection := 1]
   143 			    ifFalse:[selection := 1]
   144 
   144 
   145         ] ifFalse:[
   145 	] ifFalse:[
   146             instanceNames removeFirst.
   146 	    instanceNames removeFirst.
   147             instanceTypes removeFirst.
   147 	    instanceTypes removeFirst.
   148 
   148 
   149             selection isNil ifFalse:[
   149 	    selection isNil ifFalse:[
   150                 (selection := selection - 1) == 0 ifTrue:[
   150 		(selection := selection - 1) == 0 ifTrue:[
   151                     selection := nil
   151 		    selection := nil
   152                 ]
   152 		]
   153             ]
   153 	    ]
   154         ]
   154 	]
   155     ]
   155     ]
   156 
   156 
   157 
   157 
   158 !
   158 !
   159 
   159 
   174     "update list contents
   174     "update list contents
   175     "
   175     "
   176     |start stop size|
   176     |start stop size|
   177 
   177 
   178     inspectedObject isVariable ifTrue:[
   178     inspectedObject isVariable ifTrue:[
   179         start := instanceNames findFirst:[:el|(el at:1) isDigit].
   179 	start := instanceNames findFirst:[:el|(el at:1) isDigit].
   180         stop  := instanceTypes size.
   180 	stop  := instanceTypes size.
   181 
   181 
   182         start == 0 ifTrue:[
   182 	start == 0 ifTrue:[
   183             size := stop + 10.  "must be > 1: force a resize the first time"   
   183 	    size := stop + 10.  "must be > 1: force a resize the first time"
   184         ] ifFalse:[
   184 	] ifFalse:[
   185             instanceTypes last ~~ #grow ifTrue:[size := stop]
   185 	    instanceTypes last ~~ #grow ifTrue:[size := stop]
   186                                        ifFalse:[size := stop-1].
   186 				       ifFalse:[size := stop-1].
   187 
   187 
   188             instanceTypes removeFromIndex:start toIndex:stop.
   188 	    instanceTypes removeFromIndex:start toIndex:stop.
   189             instanceNames removeFromIndex:start toIndex:stop.
   189 	    instanceNames removeFromIndex:start toIndex:stop.
   190         ].
   190 	].
   191         self resizeTo:size.
   191 	self resizeTo:size.
   192     ]
   192     ]
   193 
   193 
   194     "Modified: / 4.2.1999 / 20:00:38 / cg"
   194     "Modified: / 4.2.1999 / 20:00:38 / cg"
   195 ! !
   195 ! !
   196 
   196 
   215 instanceTypeAt:anIndex
   215 instanceTypeAt:anIndex
   216     "returns type assigned to the list entry (#directory #normal #self #grow)
   216     "returns type assigned to the list entry (#directory #normal #self #grow)
   217      In case of an invalid index nil is returned.
   217      In case of an invalid index nil is returned.
   218     "
   218     "
   219     (anIndex isNil or:[anIndex > instanceTypes size]) ifFalse:[^ instanceTypes at:anIndex]
   219     (anIndex isNil or:[anIndex > instanceTypes size]) ifFalse:[^ instanceTypes at:anIndex]
   220                                                        ifTrue:[^ nil].
   220 						       ifTrue:[^ nil].
   221 
   221 
   222 
   222 
   223 !
   223 !
   224 
   224 
   225 instanceTypes
   225 instanceTypes
   229 
   229 
   230 
   230 
   231 !
   231 !
   232 
   232 
   233 instanceVarAt:anIndex
   233 instanceVarAt:anIndex
   234     "returns the instnace variable assigned to the index or 
   234     "returns the instnace variable assigned to the index or
   235      nil in case of an invalid index.
   235      nil in case of an invalid index.
   236     "
   236     "
   237     |nm|
   237     |nm|
   238 
   238 
   239     (anIndex isNil or:[anIndex > instanceTypes size]) ifFalse:[
   239     (anIndex isNil or:[anIndex > instanceTypes size]) ifFalse:[
   240         nm := instanceNames at:anIndex.
   240 	nm := instanceNames at:anIndex.
   241 
   241 
   242         (nm at:1) isDigit ifFalse:[
   242 	(nm at:1) isDigit ifFalse:[
   243             self includesSelf ifFalse:[
   243 	    self includesSelf ifFalse:[
   244                 ^ inspectedObject instVarAt:anIndex
   244 		^ inspectedObject instVarAt:anIndex
   245             ].
   245 	    ].
   246             anIndex == 1 ifFalse:[^ inspectedObject instVarAt:(anIndex-1)]
   246 	    anIndex == 1 ifFalse:[^ inspectedObject instVarAt:(anIndex-1)]
   247                           ifTrue:[^ inspectedObject]
   247 			  ifTrue:[^ inspectedObject]
   248         ].
   248 	].
   249       ^ inspectedObject basicAt:(Number readFrom:nm onError:0)
   249       ^ inspectedObject basicAt:(Number readFrom:nm onError:0)
   250     ].
   250     ].
   251     ^ nil
   251     ^ nil
   252 
   252 
   253 
   253 
   271     "resize list to minimum aNumber
   271     "resize list to minimum aNumber
   272     "
   272     "
   273     |lstVarId basicSize newLastId obj instSize|
   273     |lstVarId basicSize newLastId obj instSize|
   274 
   274 
   275     (inspectedObject isVariable and:[self class isDirectory:inspectedObject]) ifFalse:[
   275     (inspectedObject isVariable and:[self class isDirectory:inspectedObject]) ifFalse:[
   276         ^ self
   276 	^ self
   277     ].
   277     ].
   278 
   278 
   279     instanceTypes size == 0 ifTrue:[
   279     instanceTypes size == 0 ifTrue:[
   280         lstVarId := 0
   280 	lstVarId := 0
   281     ] ifFalse:[
   281     ] ifFalse:[
   282         instSize := inspectedObject class instSize.
   282 	instSize := inspectedObject class instSize.
   283 
   283 
   284         instanceTypes first == #self ifTrue:[
   284 	instanceTypes first == #self ifTrue:[
   285             instSize := instSize + 1
   285 	    instSize := instSize + 1
   286         ].
   286 	].
   287         instanceTypes last == #grow ifTrue:[
   287 	instanceTypes last == #grow ifTrue:[
   288             instanceNames removeLast.       " ..    "
   288 	    instanceNames removeLast.       " ..    "
   289             instanceTypes removeLast.       " #grow "
   289 	    instanceTypes removeLast.       " #grow "
   290         ].
   290 	].
   291         lstVarId := instanceTypes size - instSize.
   291 	lstVarId := instanceTypes size - instSize.
   292     ].
   292     ].
   293 
   293 
   294     (basicSize := inspectedObject basicSize) == lstVarId ifTrue:[
   294     (basicSize := inspectedObject basicSize) == lstVarId ifTrue:[
   295         ^ self
   295 	^ self
   296     ].
   296     ].
   297     newLastId := (1 bitShift:((aNumber-1) highBit)) max:128.
   297     newLastId := (1 bitShift:((aNumber-1) highBit)) max:128.
   298 
   298 
   299     (newLastId + 64) > basicSize ifTrue:[
   299     (newLastId + 64) > basicSize ifTrue:[
   300         newLastId := basicSize
   300 	newLastId := basicSize
   301     ].
   301     ].
   302 
   302 
   303     [lstVarId ~~ newLastId] whileTrue:[
   303     [lstVarId ~~ newLastId] whileTrue:[
   304         lstVarId := lstVarId + 1.
   304 	lstVarId := lstVarId + 1.
   305         obj := inspectedObject basicAt:lstVarId.
   305 	obj := inspectedObject basicAt:lstVarId.
   306 
   306 
   307         (self class isDirectory:obj) ifTrue:[instanceTypes add:#directory]
   307 	(self class isDirectory:obj) ifTrue:[instanceTypes add:#directory]
   308                                     ifFalse:[instanceTypes add:#normal].
   308 				    ifFalse:[instanceTypes add:#normal].
   309 
   309 
   310         instanceNames add:(lstVarId printString, '   ', obj class name printString).
   310 	instanceNames add:(lstVarId printString, '   ', obj class name printString).
   311     ].
   311     ].
   312 
   312 
   313     lstVarId ~~ basicSize ifTrue:[
   313     lstVarId ~~ basicSize ifTrue:[
   314         instanceNames add:'..'.
   314 	instanceNames add:'..'.
   315         instanceTypes add:#grow
   315 	instanceTypes add:#grow
   316     ].
   316     ].
   317 ! !
   317 ! !
   318 
   318 
   319 !NewInspectorList methodsFor:'selections'!
   319 !NewInspectorList methodsFor:'selections'!
   320 
   320 
   347     "change current selection to a number or nil; may resize the lists
   347     "change current selection to a number or nil; may resize the lists
   348     "
   348     "
   349     selection := aNrOrNil.
   349     selection := aNrOrNil.
   350 
   350 
   351     (selection isNil or:[instanceTypes size > selection]) ifFalse:[
   351     (selection isNil or:[instanceTypes size > selection]) ifFalse:[
   352         self resizeTo:selection.
   352 	self resizeTo:selection.
   353 
   353 
   354         selection > instanceTypes size ifTrue:[
   354 	selection > instanceTypes size ifTrue:[
   355             selection := nil
   355 	    selection := nil
   356         ]
   356 	]
   357     ]    
   357     ]
   358 ! !
   358 ! !
   359 
   359 
   360 !NewInspectorList methodsFor:'testing'!
   360 !NewInspectorList methodsFor:'testing'!
   361 
   361 
   362 includesSelf
   362 includesSelf
   389      will be updated.
   389      will be updated.
   390     "
   390     "
   391     |text slNr value|
   391     |text slNr value|
   392 
   392 
   393     selection notNil ifTrue:[
   393     selection notNil ifTrue:[
   394         text := self class asString:aText.
   394 	text := self class asString:aText.
   395 
   395 
   396         text notNil ifTrue:[
   396 	text notNil ifTrue:[
   397             self includesSelf ifFalse:[slNr := selection]
   397 	    self includesSelf ifFalse:[slNr := selection]
   398                                ifTrue:[slNr := selection-1].
   398 			       ifTrue:[slNr := selection-1].
   399 
   399 
   400             value := inspectedObject class evaluatorClass 
   400 	    value := inspectedObject class evaluatorClass
   401                        evaluate:text
   401 		       evaluate:text
   402                        receiver:inspectedObject 
   402 		       receiver:inspectedObject
   403                       notifying:aView.
   403 		      notifying:aView.
   404 
   404 
   405             slNr ~~ 0 ifTrue:[
   405 	    slNr ~~ 0 ifTrue:[
   406                 (inspectedObject class isVariable) ifFalse:[
   406 		(inspectedObject class isVariable) ifFalse:[
   407                     inspectedObject instVarAt:slNr put:value
   407 		    inspectedObject instVarAt:slNr put:value
   408                 ] ifTrue:[
   408 		] ifTrue:[
   409                     slNr <= (inspectedObject class instSize) ifTrue:[
   409 		    slNr <= (inspectedObject class instSize) ifTrue:[
   410                         inspectedObject instVarAt:slNr put:value
   410 			inspectedObject instVarAt:slNr put:value
   411                     ] ifFalse:[
   411 		    ] ifFalse:[
   412                         slNr := slNr - inspectedObject class instSize.
   412 			slNr := slNr - inspectedObject class instSize.
   413                         inspectedObject basicAt:slNr put:value
   413 			inspectedObject basicAt:slNr put:value
   414                     ]
   414 		    ]
   415                 ]
   415 		]
   416             ].
   416 	    ].
   417             inspectedObject changed.
   417 	    inspectedObject changed.
   418             self update.
   418 	    self update.
   419           ^ inspectedObject
   419 	  ^ inspectedObject
   420         ]
   420 	]
   421     ].
   421     ].
   422     ^ #Error
   422     ^ #Error
   423 !
   423 !
   424 
   424 
   425 doIt:aCode notifying:aView
   425 doIt:aCode notifying:aView
   430     |successFg result evaluator selInstVar code|
   430     |successFg result evaluator selInstVar code|
   431 
   431 
   432     selInstVar := self selectedInstanceVar.
   432     selInstVar := self selectedInstanceVar.
   433 
   433 
   434     selInstVar notNil ifTrue:[
   434     selInstVar notNil ifTrue:[
   435         code := self class asString:aCode.
   435 	code := self class asString:aCode.
   436 
   436 
   437         code notNil ifTrue:[
   437 	code notNil ifTrue:[
   438             evaluator := selInstVar class evaluatorClass.
   438 	    evaluator := selInstVar class evaluatorClass.
   439             successFg := true.
   439 	    successFg := true.
   440 
   440 
   441             evaluator notNil ifTrue:[
   441 	    evaluator notNil ifTrue:[
   442                 result := evaluator evaluate:code 
   442 		result := evaluator evaluate:code
   443                                           in:nil 
   443 					  in:nil
   444                                     receiver:selInstVar 
   444 				    receiver:selInstVar
   445                                    notifying:aView 
   445 				   notifying:aView
   446                                       logged:true 
   446 				      logged:true
   447                                       ifFail:[successFg := false].
   447 				      ifFail:[successFg := false].
   448 
   448 
   449                 successFg ifTrue:[
   449 		successFg ifTrue:[
   450                     self update. 
   450 		    self update.
   451                   ^ result 
   451 		  ^ result
   452                 ]
   452 		]
   453             ]
   453 	    ]
   454         ]
   454 	]
   455     ].
   455     ].
   456     ^ #Error.
   456     ^ #Error.
   457 
   457 
   458 
   458 
   459 !
   459 !
   464     |varNamesSize|
   464     |varNamesSize|
   465 
   465 
   466     selection := nil.
   466     selection := nil.
   467 
   467 
   468     anObject == inspectedObject ifFalse:[
   468     anObject == inspectedObject ifFalse:[
   469         inspectedObject := anObject.
   469 	inspectedObject := anObject.
   470 
   470 
   471         (self class isDirectory:inspectedObject) ifFalse:[
   471 	(self class isDirectory:inspectedObject) ifFalse:[
   472             instanceNames := OrderedCollection new.
   472 	    instanceNames := OrderedCollection new.
   473             instanceTypes := OrderedCollection new.
   473 	    instanceTypes := OrderedCollection new.
   474         ] ifTrue:[    
   474 	] ifTrue:[
   475             instanceNames := inspectedObject class allInstVarNames.
   475 	    instanceNames := inspectedObject class allInstVarNames.
   476             varNamesSize  := instanceNames size.
   476 	    varNamesSize  := instanceNames size.
   477             instanceTypes := OrderedCollection new:varNamesSize.
   477 	    instanceTypes := OrderedCollection new:varNamesSize.
   478 
   478 
   479             1 to:varNamesSize do:[:i|
   479 	    1 to:varNamesSize do:[:i|
   480                 (self class isDirectory:(inspectedObject instVarAt:i)) ifTrue:[
   480 		(self class isDirectory:(inspectedObject instVarAt:i)) ifTrue:[
   481                     instanceTypes add:#directory
   481 		    instanceTypes add:#directory
   482                 ] ifFalse:[
   482 		] ifFalse:[
   483                     instanceTypes add:#normal
   483 		    instanceTypes add:#normal
   484                 ]
   484 		]
   485             ].
   485 	    ].
   486         ]
   486 	]
   487     ].
   487     ].
   488     self update
   488     self update
   489 ! !
   489 ! !
   490 
   490 
   491 !NewInspectorList class methodsFor:'documentation'!
   491 !NewInspectorList class methodsFor:'documentation'!