extensions.st
changeset 10051 5b7e30460ea4
parent 9691 312706640f5c
child 10120 92d12afdcffa
equal deleted inserted replaced
10050:dad59ec79a80 10051:5b7e30460ea4
     1 "{ Package: 'stx:libtool' }"!
     1 "{ Package: 'stx:libtool' }"!
       
     2 
       
     3 !AbstractSyntaxHighlighter class methodsFor:'api highlighting'!
       
     4 
       
     5 formatExpression:aString in:aClass elementsInto: elements
       
     6 
       
     7     ^self formatExpression:aString in:aClass
       
     8 
       
     9     "Created: / 25-07-2010 / 08:57:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    10 ! !
       
    11 
       
    12 !AbstractSyntaxHighlighter class methodsFor:'api highlighting'!
       
    13 
       
    14 formatMethod:aString in:aClass using:preferencesOrNil elementsInto: elements
       
    15 
       
    16     ^self formatMethod:aString in:aClass using:preferencesOrNil
       
    17 
       
    18     "Created: / 25-07-2010 / 08:58:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    19 ! !
       
    20 
       
    21 !AddClassChange methodsFor:'testing'!
       
    22 
       
    23 isClassDefinitionChange
       
    24 
       
    25     ^true
       
    26 
       
    27     "Created: / 29-10-2010 / 13:35:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    28 ! !
       
    29 
       
    30 !AddMethodChange methodsFor:'testing'!
       
    31 
       
    32 isMethodCodeChange
       
    33 
       
    34     ^true
       
    35 ! !
       
    36 
       
    37 !AddMethodChange methodsFor:'accessing'!
       
    38 
       
    39 source
       
    40     ^ source
       
    41 ! !
       
    42 
       
    43 !AddMethodChange methodsFor:'initialization & release'!
       
    44 
       
    45 source: aString 
       
    46 
       
    47     source := aString.
       
    48 ! !
       
    49 
       
    50 !Breakpoint methodsFor:'accessing'!
       
    51 
       
    52 icon
       
    53 
       
    54     state == #enabled ifTrue:[^ToolbarIconLibrary brkp_obj].
       
    55     state == #disabled ifTrue:[^ToolbarIconLibrary brkpd_obj].
       
    56 
       
    57     ^nil
       
    58 
       
    59     "Created: / 28-06-2011 / 08:29:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    60 ! !
     2 
    61 
     3 !ByteArray methodsFor:'inspecting'!
    62 !ByteArray methodsFor:'inspecting'!
     4 
    63 
     5 inspectorExtraAttributes
    64 inspectorExtraAttributes
     6     "extra (pseudo instvar) entries to be shown in an inspector."
    65     "extra (pseudo instvar) entries to be shown in an inspector."
    27 
    86 
    28     "Created: / 18-09-2006 / 21:29:59 / cg"
    87     "Created: / 18-09-2006 / 21:29:59 / cg"
    29     "Modified: / 06-10-2006 / 13:57:20 / cg"
    88     "Modified: / 06-10-2006 / 13:57:20 / cg"
    30 ! !
    89 ! !
    31 
    90 
       
    91 !Change methodsFor:'private'!
       
    92 
       
    93 flattenOnto: aCollection 
       
    94 	aCollection add: self
       
    95 ! !
       
    96 
       
    97 !Change methodsFor:'private'!
       
    98 
       
    99 flattenedChanges
       
   100 	| changes |
       
   101 	changes := OrderedCollection new.
       
   102 	self flattenOnto: changes.
       
   103 	^changes
       
   104 ! !
       
   105 
       
   106 !Change methodsFor:'accessing'!
       
   107 
       
   108 removed
       
   109 
       
   110     ^(self objectAttributeAt: #removed) ? false
       
   111 
       
   112     "Created: / 24-10-2009 / 21:10:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   113 ! !
       
   114 
       
   115 !Change methodsFor:'accessing'!
       
   116 
       
   117 removed: aBoolean
       
   118 
       
   119     ^self objectAttributeAt: #removed put: aBoolean
       
   120 
       
   121     "Created: / 24-10-2009 / 21:11:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   122 ! !
       
   123 
       
   124 !ChangeSet methodsFor:'utilities'!
       
   125 
       
   126 condenseChangesForRemoved
       
   127     "remove all changes which has been removed (marked for removal
       
   128      by aChange removed: true)"
       
   129 
       
   130     |changesToRemove|
       
   131 
       
   132     changesToRemove := self select:[:aChange | 
       
   133         aChange isCompositeChange ifTrue:
       
   134             [aChange condenseChangesForRemoved].        
       
   135         aChange removed
       
   136     ].
       
   137 
       
   138     self condenseChanges:changesToRemove
       
   139 
       
   140     "Created: / 05-11-2001 / 14:21:17 / cg"
       
   141     "Modified: / 12-10-2006 / 16:51:27 / cg"
       
   142 ! !
       
   143 
       
   144 !ChangeSet methodsFor:'private'!
       
   145 
       
   146 flattenOnto: aCollection 
       
   147 
       
   148     self do:[:change|change flattenOnto: aCollection]
       
   149 ! !
       
   150 
       
   151 !ChangeSet methodsFor:'private'!
       
   152 
       
   153 flattenedChanges
       
   154 	| changes |
       
   155 	changes := OrderedCollection new.
       
   156 	self flattenOnto: changes.
       
   157 	^changes
       
   158 ! !
       
   159 
       
   160 !ChangeSet methodsFor:'debugging support'!
       
   161 
       
   162 inspector2TabBrowser
       
   163 
       
   164     ^self newInspector2Tab
       
   165         label: 'Changes';    
       
   166         priority: 75;
       
   167         application: (Tools::ChangeSetBrowser on: self)
       
   168 ! !
       
   169 
    32 !Character methodsFor:'inspecting'!
   170 !Character methodsFor:'inspecting'!
    33 
   171 
    34 inspectorExtraAttributes
   172 inspectorExtraAttributes
    35     "extra (pseudo instvar) entries to be shown in an inspector."
   173     "extra (pseudo instvar) entries to be shown in an inspector."
    36 
   174 
    47     "
   185     "
    48 
   186 
    49     "Created: / 22-10-2006 / 03:52:20 / cg"
   187     "Created: / 22-10-2006 / 03:52:20 / cg"
    50 ! !
   188 ! !
    51 
   189 
       
   190 !CharacterArray methodsFor:'debugging support'!
       
   191 
       
   192 inspector2TabText
       
   193 
       
   194     ^self newInspector2Tab
       
   195         label: 'String';
       
   196         priority: 75;
       
   197         view: ((ScrollableView for:TextView) contents: self; yourself)
       
   198 
       
   199     "Created: / 17-02-2008 / 10:10:50 / janfrog"
       
   200 ! !
       
   201 
    52 !CharacterArray methodsFor:'inspecting'!
   202 !CharacterArray methodsFor:'inspecting'!
    53 
   203 
    54 inspectorExtraAttributes
   204 inspectorExtraAttributes
    55     "extra (pseudo instvar) entries to be shown in an inspector."
   205     "extra (pseudo instvar) entries to be shown in an inspector."
    56 
   206 
    66 	d add:'-html' -> [ HTMLUtilities escapeCharacterEntities:self ].
   216 	d add:'-html' -> [ HTMLUtilities escapeCharacterEntities:self ].
    67     ].
   217     ].
    68     ^ d
   218     ^ d
    69 
   219 
    70     "
   220     "
    71      'aouäöü' inspect
   221      'aou' inspect
    72     "
   222     "
    73 
   223 
    74     "Created: / 22-10-2006 / 03:52:20 / cg"
   224     "Created: / 22-10-2006 / 03:52:20 / cg"
       
   225 ! !
       
   226 
       
   227 !ClassDescription methodsFor:'misc'!
       
   228 
       
   229 iconInBrowserForVariableNamed: varName
       
   230     "variables for which an entry is found in the xml-spec (if any) are marked
       
   231      with an <xml>-icon. For now, this is expecco-specific, but should be somehow
       
   232      lifted to the base system"
       
   233 
       
   234     (Expecco::ExpeccoXMLDecoder notNil and:
       
   235         [self canUnderstand: #xmlSpecFor:]) ifTrue:
       
   236             [
       
   237             (Expecco::ExpeccoXMLDecoder xmlSpecForObject:self basicNew)
       
   238                 collect:[:spec|spec getter = varName ifTrue:
       
   239                     [^SystemBrowser instVarOverlayXmlSpec]].
       
   240             ].
       
   241 
       
   242 
       
   243 
       
   244 
       
   245     ^nil
       
   246 
       
   247     "Created: / 12-04-2011 / 16:04:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   248     "Modified (comment): / 03-07-2011 / 15:46:07 / cg"
    75 ! !
   249 ! !
    76 
   250 
    77 !Collection methodsFor:'inspecting'!
   251 !Collection methodsFor:'inspecting'!
    78 
   252 
    79 inspectorExtraAttributes
   253 inspectorExtraAttributes
   115 	yourself
   289 	yourself
   116 
   290 
   117     "
   291     "
   118      Color red inspect
   292      Color red inspect
   119     "
   293     "
       
   294 ! !
       
   295 
       
   296 !CompositeChange methodsFor:'utilities'!
       
   297 
       
   298 condenseChangesForRemoved
       
   299 
       
   300     self changes condenseChangesForRemoved
       
   301 ! !
       
   302 
       
   303 !CompositeChange methodsFor:'private'!
       
   304 
       
   305 flattenOnto: aCollection
       
   306 
       
   307     changes do:[:change|change flattenOnto: aCollection]
       
   308 ! !
       
   309 
       
   310 !CompositeChange methodsFor:'accessing'!
       
   311 
       
   312 removed
       
   313 
       
   314     ^changes allSatisfy: [:e|e removed]
       
   315 ! !
       
   316 
       
   317 !CompositeChange methodsFor:'accessing'!
       
   318 
       
   319 removed: aBoolean
       
   320 
       
   321     changes do:[:e|e removed: aBoolean]
       
   322 ! !
       
   323 
       
   324 !CompositeRefactoryChange methodsFor:'utilities'!
       
   325 
       
   326 condenseChangesForRemoved
       
   327 
       
   328     changes := 
       
   329         changes reject:
       
   330             [:chg|
       
   331             chg isCompositeChange ifTrue:[chg condenseChangesForRemoved].
       
   332             chg removed]
       
   333 ! !
       
   334 
       
   335 !CompositeRefactoryChange methodsFor:'user interface'!
       
   336 
       
   337 inspect
       
   338 
       
   339     ^super inspect
       
   340 
       
   341     "
       
   342         CompositeRefactoryChangeInspector openOn: self
       
   343     "
       
   344 ! !
       
   345 
       
   346 !CompositeRefactoryChange methodsFor:'testing'!
       
   347 
       
   348 isComplexRefactoryChange
       
   349 
       
   350     ^changes size > 1
       
   351 
       
   352     "Created: / 26-11-2008 / 11:56:18 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
   353 ! !
       
   354 
       
   355 !CompositeRefactoryChange methodsFor:'testing'!
       
   356 
       
   357 isCompositeChange
       
   358 
       
   359     ^true
       
   360 
       
   361     "Created: / 26-11-2008 / 11:34:56 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
   362 ! !
       
   363 
       
   364 !CompositeRefactoryChange methodsFor:'testing'!
       
   365 
       
   366 isCompositeRefactoryChange
       
   367 
       
   368     ^true
       
   369 
       
   370     "Created: / 26-11-2008 / 11:34:56 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
   371 ! !
       
   372 
       
   373 !CompositeRefactoryChange methodsFor:'accessing'!
       
   374 
       
   375 removed
       
   376 
       
   377     ^changes allSatisfy: [:e|e removed]
       
   378 ! !
       
   379 
       
   380 !CompositeRefactoryChange methodsFor:'accessing'!
       
   381 
       
   382 removed: aBoolean
       
   383 
       
   384     changes do:[:e|e removed: aBoolean]
   120 ! !
   385 ! !
   121 
   386 
   122 !Date methodsFor:'inspecting'!
   387 !Date methodsFor:'inspecting'!
   123 
   388 
   124 inspectorExtraAttributes
   389 inspectorExtraAttributes
   147      (instead of the default Inspector)."
   412      (instead of the default Inspector)."
   148 
   413 
   149     ^ DictionaryInspectorView
   414     ^ DictionaryInspectorView
   150 ! !
   415 ! !
   151 
   416 
       
   417 !DoWhatIMeanSupport class methodsFor:'code completion-helpers'!
       
   418 
       
   419 askUserForCompletion:what for:codeView at:position from:allTheBest 
       
   420     |list choice lastChoice|
       
   421 
       
   422     allTheBest isEmpty ifTrue:[
       
   423         ^ nil
       
   424     ].
       
   425     allTheBest size == 1 ifTrue:[
       
   426         ^ allTheBest first
       
   427     ].
       
   428     list := allTheBest.
       
   429     LastChoices notNil ifTrue:[
       
   430         lastChoice := LastChoices at:what ifAbsent:nil.
       
   431         lastChoice notNil ifTrue:[
       
   432             list := 
       
   433                     { lastChoice.
       
   434                     nil } , (list copyWithout:lastChoice).
       
   435         ].
       
   436     ].
       
   437     choice := Tools::CodeCompletionMenu 
       
   438                 openFor:codeView
       
   439                 at:position
       
   440                 with:allTheBest.
       
   441     LastChoices isNil ifTrue:[
       
   442         LastChoices := Dictionary new.
       
   443     ].
       
   444     LastChoices at:what put:choice.
       
   445     ^ choice
       
   446 
       
   447     "Created: / 16-02-2010 / 10:09:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   448 ! !
       
   449 
       
   450 !DoWhatIMeanSupport class methodsFor:'code completion-helpers'!
       
   451 
       
   452 codeCompletionForLiteralSymbol:node inClass:classOrNil codeView:codeView
       
   453     |sym possibleCompletions best start stop oldLen newLen oldVar|
       
   454 
       
   455     sym := node value.
       
   456     possibleCompletions := OrderedCollection new.
       
   457 
       
   458     Symbol allInstancesDo:[:existingSym |
       
   459         (existingSym startsWith:sym) ifTrue:[
       
   460             (existingSym = sym) ifFalse:[
       
   461                 possibleCompletions add:existingSym
       
   462             ].
       
   463         ].
       
   464     ].
       
   465     possibleCompletions sort.
       
   466 
       
   467     best := possibleCompletions longestCommonPrefix.
       
   468     (best = sym or:[(possibleCompletions includes:best) not]) ifTrue:[
       
   469         best := self askUserForCompletion:'symbol literal' for:codeView at: node start from:possibleCompletions.
       
   470         best isNil ifTrue:[^ self].
       
   471     ].
       
   472 
       
   473 "/ self showInfo:best.
       
   474 
       
   475     start := node start.
       
   476     stop := node stop.
       
   477     (codeView characterAtCharacterPosition:start) == $# ifTrue:[
       
   478         start := start + 1.
       
   479     ].
       
   480     (codeView characterAtCharacterPosition:start) == $' ifTrue:[
       
   481         start := start + 1.
       
   482         stop := stop - 1.
       
   483     ].
       
   484 
       
   485     oldVar := (codeView textFromCharacterPosition:start to:stop) asString string withoutSeparators.
       
   486 
       
   487     codeView
       
   488         undoableDo:[ codeView replaceFromCharacterPosition:start to:stop with:best ]
       
   489         info:'Completion'.
       
   490 
       
   491     (best startsWith:oldVar) ifTrue:[
       
   492         oldLen := stop - start + 1.
       
   493         newLen := best size.
       
   494         codeView selectFromCharacterPosition:start+oldLen to:start+newLen-1.
       
   495         codeView dontReplaceSelectionOnInput
       
   496     ].
       
   497 
       
   498     "Modified: / 16-02-2010 / 10:15:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   499     "Modified (format): / 03-07-2011 / 15:58:45 / cg"
       
   500 ! !
       
   501 
       
   502 !DoWhatIMeanSupport class methodsFor:'code completion-helpers'!
       
   503 
       
   504 codeCompletionForMessage:node inClass:cls codeView:codeView
       
   505     |selector srchClass implClass 
       
   506      bestSelectors selector2 bestSelectors2 allBest best info numArgs
       
   507      newParts nSelParts oldLen newLen selectorParts 
       
   508      findBest parentNode selectorInBest selector2InBest2
       
   509      parser selectorsSentInCode split|
       
   510 
       
   511     parser := Parser parseMethod:codeView contents string in:cls ignoreErrors:true ignoreWarnings:true.
       
   512     selectorsSentInCode := parser messagesSent.
       
   513 
       
   514     findBest := [:node :selector |
       
   515         |srchClass bestSelectors bestPrefixes|
       
   516 
       
   517         srchClass := self lookupClassForMessage:node inClass:cls.
       
   518 
       
   519         srchClass notNil ifTrue:[
       
   520             bestSelectors := Parser findBest:30 selectorsFor:selector in:srchClass forCompletion:true.
       
   521         ] ifFalse:[
       
   522             codeView topView withCursor:(Cursor questionMark) do:[
       
   523                 bestSelectors := Parser findBest:30 selectorsFor:selector in:nil forCompletion:true.
       
   524             ].
       
   525         ].
       
   526 
       
   527         (bestSelectors includes:selector) ifTrue:[
       
   528             bestSelectors := bestSelectors select:[:sel | sel size > selector size].
       
   529         ].
       
   530         bestSelectors
       
   531     ].
       
   532 
       
   533     selector := node selector.
       
   534     bestSelectors := findBest value:node value:selector.
       
   535 
       
   536     parentNode := node parent.
       
   537 
       
   538     "/ if its a unary message AND the parent is a keyword node, look for parent completion too.
       
   539     (node selector isUnarySelector 
       
   540     and:[ parentNode notNil 
       
   541     and:[ parentNode isMessage 
       
   542     and:[ (selector2 := parentNode selector) isKeywordSelector ]]]) ifTrue:[
       
   543         "/ srchClass2 := self lookupClassForMessage:parentNode inClass:cls.
       
   544         selector2 := selector2,selector.
       
   545         bestSelectors2 := findBest value:parentNode value:selector2.
       
   546     ].
       
   547 
       
   548     bestSelectors2 isEmptyOrNil ifTrue:[
       
   549         allBest := bestSelectors.
       
   550     ] ifFalse:[
       
   551         bestSelectors isEmptyOrNil ifTrue:[
       
   552             allBest := bestSelectors2
       
   553         ] ifFalse:[
       
   554             selectorInBest := (bestSelectors contains:[:sel | sel asLowercase startsWith:selector asLowercase]).
       
   555             selector2InBest2 := (bestSelectors2 contains:[:sel | sel asLowercase startsWith:selector2 asLowercase]).
       
   556 
       
   557             (selectorInBest not and:[ selector2InBest2 ]) ifTrue:[
       
   558                 "/ selector2 is more likely
       
   559                 allBest := bestSelectors2
       
   560             ] ifFalse:[
       
   561                 (selectorInBest and:[ selector2InBest2 not ]) ifTrue:[
       
   562                     "/ selector more likely
       
   563                     allBest := bestSelectors
       
   564                 ] ifFalse:[
       
   565                     "/ assume same likelyness
       
   566 
       
   567                     allBest := bestSelectors isEmpty 
       
   568                                 ifTrue:[ bestSelectors2 ]
       
   569                                 ifFalse:[ bestSelectors , #(nil) , bestSelectors2 ].
       
   570                 ]
       
   571             ].
       
   572         ].
       
   573     ].
       
   574 
       
   575     allBest isEmptyOrNil ifTrue:[ ^ self ].
       
   576 
       
   577     split := [:list :splitHow |
       
   578         |part1 part2 all|
       
   579 
       
   580         part1 := list select:splitHow.
       
   581         part2 := list reject:splitHow.
       
   582         part1 isEmpty ifTrue:[
       
   583             all := part2.
       
   584         ] ifFalse:[
       
   585             part2 isEmpty ifTrue:[
       
   586                 all := part1.
       
   587             ] ifFalse:[
       
   588                 all := part1 , part2.
       
   589             ]
       
   590         ].
       
   591         all
       
   592     ].
       
   593 
       
   594     "/ the ones already sent in the code are moved to the top of the list.
       
   595     allBest := split value:allBest value:[:sel | selectorsSentInCode includes:sel].
       
   596 
       
   597     "/ the ones which are a prefix are moved towards the top of the list
       
   598     allBest := split value:allBest value:[:sel | sel notNil and:[sel startsWith:selector]].
       
   599 
       
   600     best := allBest first.
       
   601     allBest size > 1 ifTrue:[
       
   602         "allBest size < 20 ifTrue:[
       
   603             |idx|
       
   604 
       
   605             idx := (PopUpMenu labels:allBest) startUp.
       
   606             idx == 0 ifTrue:[ ^ self].
       
   607             best := allBest at:idx.
       
   608         ] ifFalse:[
       
   609             best := Dialog request:'Matching selectors:' initialAnswer:best list:allBest.
       
   610 
       
   611         ]."
       
   612         best := self askUserForCompletion:'selector' for:codeView at: node selectorParts first start from:allBest.
       
   613         best isEmptyOrNil ifTrue:[^ self].
       
   614         best = '-' ifTrue:[^ self].
       
   615     ].
       
   616 
       
   617 false ifTrue:[
       
   618     srchClass notNil ifTrue:[
       
   619         implClass := srchClass whichClassIncludesSelector:best.
       
   620     ] ifFalse:[
       
   621         implClass := Smalltalk allClasses select:[:cls | (cls includesSelector:best) or:[cls class includesSelector:best]].
       
   622         implClass size == 1 ifTrue:[
       
   623             implClass := implClass first.
       
   624         ] ifFalse:[
       
   625             implClass := nil
       
   626         ]
       
   627     ].
       
   628 
       
   629     info := best storeString.
       
   630     implClass notNil ifTrue:[
       
   631         info := implClass name , ' >> ' , info.
       
   632     ].
       
   633     self information:info.
       
   634 ].
       
   635 
       
   636     best ~= selector ifTrue:[
       
   637         numArgs := best numArgs.
       
   638         (bestSelectors2 notEmptyOrNil and:[bestSelectors2 includes:best]) ifTrue:[
       
   639             selectorParts := parentNode selectorParts , node selectorParts.
       
   640         ] ifFalse:[
       
   641             selectorParts := node selectorParts.
       
   642         ].
       
   643         nSelParts := selectorParts size.
       
   644 
       
   645         newParts := best asCollectionOfSubstringsSeparatedBy:$:.
       
   646         newParts := newParts select:[:part | part size > 0].
       
   647 
       
   648         codeView
       
   649             undoableDo:[
       
   650                 |newCursorPosition stop|
       
   651 
       
   652                 numArgs > nSelParts ifTrue:[
       
   653                     stop := selectorParts last stop.
       
   654 
       
   655                     "/ append the rest ...
       
   656                     numArgs downTo:nSelParts+1 do:[:idx |
       
   657                         |newPart|
       
   658 
       
   659                         newPart := newParts at:idx.
       
   660                         (best endsWith:$:) ifTrue:[
       
   661                             newPart := newPart , ':'
       
   662                         ].
       
   663 
       
   664                         (codeView characterAtCharacterPosition:stop) == $: ifFalse:[
       
   665                             newPart := ':' , newPart.
       
   666                         ].
       
   667                         newPart := (codeView characterAtCharacterPosition:stop) asString , newPart.
       
   668 
       
   669                         codeView replaceFromCharacterPosition:stop to:stop with:newPart.
       
   670                         newCursorPosition isNil ifTrue:[
       
   671                             newCursorPosition := stop + newPart size.
       
   672                         ]
       
   673                     ]
       
   674                 ].
       
   675 
       
   676                 (nSelParts min:newParts size) downTo:1 do:[:idx |
       
   677                     |newPart oldPartialToken start stop|
       
   678 
       
   679                     newPart := newParts at:idx.
       
   680                     oldPartialToken := selectorParts at:idx.
       
   681                     start := oldPartialToken start.
       
   682                     stop := oldPartialToken stop.
       
   683 
       
   684                     (best endsWith:$:) ifTrue:[
       
   685                         (codeView characterAtCharacterPosition:stop+1) == $: ifFalse:[
       
   686                             newPart := newPart , ':'
       
   687                         ]
       
   688                     ] ifFalse:[
       
   689                         (codeView characterAtCharacterPosition:stop) == $: ifTrue:[
       
   690                             newPart := newPart , ':'
       
   691                         ] ifFalse:[
       
   692                             (codeView characterAtCharacterPosition:stop+1) isSeparator ifFalse:[
       
   693                                 newPart := newPart , ' '
       
   694                             ]
       
   695                         ]
       
   696 "/                            codeView replaceFromCharacterPosition:start to:stop with:(newPart , ':').
       
   697 "/                        ] ifFalse:[
       
   698 "/                            codeView replaceFromCharacterPosition:start to:stop with:newPart.
       
   699                     ].
       
   700 
       
   701                     codeView replaceFromCharacterPosition:start to:stop with:newPart.
       
   702 
       
   703                     oldLen := stop - start + 1.
       
   704                     newLen := newPart size.
       
   705 
       
   706 "/                     codeView selectFromCharacterPosition:start+oldLen to:start+newLen-1.
       
   707                     newCursorPosition isNil ifTrue:[
       
   708                         newCursorPosition := stop + (newLen-oldLen).
       
   709                     ].
       
   710                 ].
       
   711                 codeView cursorToCharacterPosition:newCursorPosition.
       
   712                 codeView cursorRight.  "/ avoid going to the next line !!
       
   713                 codeView dontReplaceSelectionOnInput.
       
   714             ]
       
   715         info:'Completion'.
       
   716     ].
       
   717 
       
   718     "Created: / 10-11-2006 / 13:18:27 / cg"
       
   719     "Modified: / 16-02-2010 / 10:33:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   720 ! !
       
   721 
       
   722 !DoWhatIMeanSupport class methodsFor:'code completion-helpers'!
       
   723 
       
   724 codeCompletionForMethod:node inClass:cls codeView:codeView
       
   725     "completion in a methods selector pattern"
       
   726 
       
   727     |crsrPos
       
   728      selectorSoFar matchingSelectors
       
   729      selectors distances best rest 
       
   730      allExistingMethods namesOfArguments 
       
   731      nameBag namesByCount|  
       
   732 
       
   733     crsrPos := codeView characterPositionOfCursor - 1.
       
   734 
       
   735     selectorSoFar := ''.
       
   736     node selectorParts doWithIndex:[:partToken :argNr|
       
   737         |part|
       
   738 
       
   739         part := partToken value.
       
   740         selectorSoFar := selectorSoFar , part.
       
   741 
       
   742         (crsrPos >= partToken start
       
   743         and:[crsrPos <= partToken stop]) ifTrue:[
       
   744             matchingSelectors := Smalltalk allClasses
       
   745                                     inject:(Set new)
       
   746                                     into:[:theSet :eachClass |
       
   747                                         |md|
       
   748 
       
   749                                         cls isMeta ifTrue:[
       
   750                                             md := eachClass theMetaclass methodDictionary
       
   751                                         ] ifFalse:[
       
   752                                             md := eachClass theNonMetaclass methodDictionary
       
   753                                         ].
       
   754                                         theSet addAll:(md keys select:[:sel |sel startsWith:selectorSoFar]).
       
   755                                         theSet.
       
   756                                     ].
       
   757             selectors := matchingSelectors asOrderedCollection.
       
   758             "/ if there is only one, and user has already entered it, he might want to complete the argument-name    
       
   759             (selectors size == 1 
       
   760             and:[selectors first = selectorSoFar]) ifTrue:[
       
   761                 allExistingMethods := (Smalltalk allImplementorsOf:selectorSoFar asSymbol)
       
   762                                             collect:[:cls | cls compiledMethodAt:selectorSoFar asSymbol].
       
   763                 namesOfArguments := allExistingMethods collect:[:eachMethod | eachMethod methodArgNames].
       
   764                 nameBag := Bag new.
       
   765                 namesOfArguments do:[:eachNameVector | nameBag add:(eachNameVector at:argNr)].
       
   766                 namesByCount := nameBag valuesAndCounts sort:[:a :b | a value < b value].   
       
   767                 "/ take the one which occurs most often     
       
   768                 best := self askUserForCompletion:'argument' for:codeView at: node start from:(namesByCount collect:[:a | a key]).
       
   769 
       
   770                 codeView
       
   771                     undoableDo:[
       
   772                         (crsrPos+1) >= codeView contents size ifTrue:[
       
   773                             codeView paste:best.
       
   774                         ] ifFalse:[
       
   775                             codeView insertString:best atCharacterPosition:crsrPos+1.
       
   776                         ]
       
   777                     ]
       
   778                     info:'completion'.
       
   779                 codeView cursorToCharacterPosition:(crsrPos + best size - 1).    
       
   780             ] ifFalse:[
       
   781                 distances := selectors collect:[:each | each spellAgainst:selectorSoFar].
       
   782                 distances sortWith:selectors.
       
   783                 selectors reverse.
       
   784                 best := self askUserForCompletion:'selector' for:codeView at: node start from:selectors.
       
   785                 best isNil ifTrue:[^ self].
       
   786 
       
   787                 rest := best copyFrom:selectorSoFar size.
       
   788 
       
   789                 codeView
       
   790                     undoableDo:[ 
       
   791                         codeView 
       
   792                             replaceFromCharacterPosition:crsrPos 
       
   793                             to:crsrPos 
       
   794                             with:rest 
       
   795                     ]
       
   796                     info:'Completion'.
       
   797                 codeView cursorToCharacterPosition:(crsrPos + rest size - 1).    
       
   798             ].
       
   799             codeView cursorRight. "/ kludge to make it visible   
       
   800         ].
       
   801     ].
       
   802 
       
   803     "Modified: / 04-07-2006 / 18:48:26 / fm"
       
   804     "Created: / 10-11-2006 / 13:46:44 / cg"
       
   805     "Modified: / 16-02-2010 / 10:13:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   806 ! !
       
   807 
       
   808 !DoWhatIMeanSupport class methodsFor:'input completion support'!
       
   809 
       
   810 methodProtocolCompletion:aPartialProtocolName inEnvironment:anEnvironment
       
   811     "given a partial method protocol name, return an array consisting of
       
   812      2 entries: 1st: the best (longest) match 
       
   813                 2nd: collection consisting of matching protocols"
       
   814 
       
   815     |matches best lcName|
       
   816 
       
   817     matches := IdentitySet new.
       
   818 
       
   819     "/ search for exact match
       
   820     anEnvironment allMethodsWithSelectorDo:[:eachMethod :eachSelector |
       
   821         |protocol|
       
   822 
       
   823         protocol := eachMethod category.
       
   824         (protocol notNil and:[protocol startsWith:aPartialProtocolName]) ifTrue:[
       
   825             matches add:protocol
       
   826         ].
       
   827     ].
       
   828     matches isEmpty ifTrue:[
       
   829         "/ search for case-ignoring match
       
   830         lcName := aPartialProtocolName asLowercase.
       
   831         anEnvironment allMethodsWithSelectorDo:[:eachMethod :eachSelector |
       
   832             |protocol|
       
   833 
       
   834             protocol := eachMethod category.
       
   835             (protocol notNil and:[protocol asLowercase startsWith:lcName]) ifTrue:[
       
   836                 matches add:protocol
       
   837             ].
       
   838         ].
       
   839     ].
       
   840 
       
   841     matches isEmpty ifTrue:[
       
   842         ^ Array with:aPartialProtocolName with:(Array with:aPartialProtocolName)
       
   843     ].
       
   844     matches size == 1 ifTrue:[
       
   845         ^ Array with:matches first with:(matches asArray)
       
   846     ].
       
   847     matches := matches asSortedCollection.
       
   848     best := matches longestCommonPrefix.
       
   849     ^ Array with:best with:matches asArray
       
   850 
       
   851     "
       
   852      Smalltalk methodProtocolCompletion:'doc'
       
   853      Smalltalk methodProtocolCompletion:'docu' 
       
   854      Smalltalk methodProtocolCompletion:'documenta' 
       
   855     "
       
   856 
       
   857     "Created: / 10-08-2006 / 13:05:27 / cg"
       
   858     "Modified: / 16-03-2011 / 12:30:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   859 ! !
       
   860 
       
   861 !DoWhatIMeanSupport class methodsFor:'code completion-helpers'!
       
   862 
       
   863 old_askUserForCompletion:what for:codeView from:allTheBest
       
   864     |list resources choice lastChoice|
       
   865 
       
   866     allTheBest isEmpty ifTrue:[ ^ nil ].
       
   867     allTheBest size == 1 ifTrue:[ ^ allTheBest first ].
       
   868 
       
   869     list := allTheBest.
       
   870     LastChoices notNil ifTrue:[
       
   871         lastChoice := LastChoices at:what ifAbsent:nil.
       
   872         lastChoice notNil ifTrue:[
       
   873             list := {lastChoice. nil. } , (list copyWithout:lastChoice).
       
   874         ].
       
   875     ].
       
   876 
       
   877     list size < 30 ifTrue:[
       
   878         |menu idx exitKey|
       
   879 
       
   880         menu := PopUpMenu labels:list.
       
   881         menu hideOnKeyFilter:[:key | |hide|
       
   882                 hide := ( #( CursorDown CursorUp Escape Return ) includes: key) not.
       
   883                 hide ifTrue:[
       
   884                     exitKey := key.
       
   885                 ].
       
   886                 hide].
       
   887 
       
   888         idx := menu startUp.
       
   889         idx == 0 ifTrue:[
       
   890             exitKey notNil ifTrue:[
       
   891                 codeView keyPress:exitKey x:0 y:0.
       
   892             ].
       
   893             ^ nil
       
   894         ].
       
   895         choice := list at:idx.
       
   896     ] ifFalse:[
       
   897         resources := codeView application isNil 
       
   898                         ifTrue:[ codeView resources]
       
   899                         ifFalse:[ codeView application resources ].
       
   900                     
       
   901         choice := Dialog
       
   902            choose:(resources string:'Choose ',what)
       
   903            fromList:list
       
   904            lines:20
       
   905            title:(resources string:'Code completion').
       
   906         choice isNil ifTrue:[^ nil].
       
   907     ].
       
   908 
       
   909     LastChoices isNil ifTrue:[
       
   910         LastChoices := Dictionary new.
       
   911     ].
       
   912     LastChoices at:what put:choice.
       
   913     ^ choice
       
   914 
       
   915     "Created: / 16-02-2010 / 09:38:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   916 ! !
       
   917 
       
   918 !EditTextView methodsFor:'accessing-dimensions'!
       
   919 
       
   920 absoluteXOfPosition:positionInText 
       
   921     |accumulatedX container|
       
   922 
       
   923     accumulatedX := 0.
       
   924     container := self.
       
   925     [ container notNil ] whileTrue:[
       
   926         accumulatedX := accumulatedX + container origin x.
       
   927         container := container isTopView ifFalse:[
       
   928                     container container
       
   929                 ] ifTrue:[ nil ].
       
   930     ].
       
   931     ^ (self xOfPosition:positionInText) + accumulatedX
       
   932 
       
   933     "Created: / 16-02-2010 / 10:05:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   934 ! !
       
   935 
       
   936 !EditTextView methodsFor:'accessing-dimensions'!
       
   937 
       
   938 absoluteYOfCursor
       
   939 
       
   940     | accumulatedY container |
       
   941     accumulatedY := 0.
       
   942     container := self.
       
   943     [ container notNil ] whileTrue:[
       
   944         accumulatedY := accumulatedY + container origin y.
       
   945         container := container isTopView 
       
   946             ifFalse:[container container]
       
   947             ifTrue:[nil].
       
   948     ].
       
   949     ^(self yOfCursor) + accumulatedY
       
   950 
       
   951     "Created: / 27-05-2005 / 07:45:53 / janfrog"
       
   952     "Modified: / 27-05-2005 / 23:03:40 / janfrog"
       
   953 ! !
       
   954 
       
   955 !EditTextView methodsFor:'accessing-dimensions'!
       
   956 
       
   957 xOfPosition: positionInText
       
   958 
       
   959     | line col |
       
   960     line := self lineOfCharacterPosition: positionInText.
       
   961     col  := positionInText - (self characterPositionOfLine:line col:1) + 1.
       
   962     ^
       
   963         (self xOfCol:col inVisibleLine:(self listLineToVisibleLine: line))
       
   964             - viewOrigin x.
       
   965 
       
   966     "Created: / 16-02-2010 / 10:04:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   967 ! !
       
   968 
       
   969 !EditTextView methodsFor:'accessing-dimensions'!
       
   970 
       
   971 yOfCursor
       
   972 
       
   973     ^self yOfVisibleLine:cursorVisibleLine.
       
   974 
       
   975     "Created: / 27-05-2005 / 07:43:41 / janfrog"
       
   976 ! !
       
   977 
       
   978 !EditTextView methodsFor:'accessing-dimensions'!
       
   979 
       
   980 yOfPosition: positionInText
       
   981 
       
   982     | line |
       
   983     line := self lineOfCharacterPosition: positionInText.
       
   984     ^self yOfVisibleLine:(self listLineToVisibleLine: line)
       
   985 
       
   986     "Created: / 16-02-2010 / 10:08:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   987 ! !
       
   988 
   152 !ExecutableFunction methodsFor:'printing & storing'!
   989 !ExecutableFunction methodsFor:'printing & storing'!
   153 
   990 
   154 printStringForBrowserWithSelector:selector
   991 printStringForBrowserWithSelector:selector
   155     "return a printString to represent myself to the user in a browser."
   992     "return a printString to represent myself to the user in a browser."
   156 
   993 
   162 inspectorClass
   999 inspectorClass
   163     "redefined to launch an ImageInspector
  1000     "redefined to launch an ImageInspector
   164      (instead of the default InspectorView)."
  1001      (instead of the default InspectorView)."
   165 
  1002 
   166     ^ ImageInspectorView
  1003     ^ ImageInspectorView
       
  1004 ! !
       
  1005 
       
  1006 !GenericToolbarIconLibrary class methodsFor:'image specs-22x22'!
       
  1007 
       
  1008 bookmarks22x22
       
  1009     "This resource specification was automatically generated
       
  1010      by the ImageEditor of ST/X."
       
  1011 
       
  1012     "Do not manually edit this!! If it is corrupted,
       
  1013      the ImageEditor may not be able to read the specification."
       
  1014 
       
  1015     "
       
  1016      self bookmarks22x22 inspect
       
  1017      ImageEditor openOnClass:self andSelector:#bookmarks22x22
       
  1018      Icon flushCachedIcons
       
  1019     "
       
  1020 
       
  1021     <resource: #image>
       
  1022 
       
  1023     ^Icon
       
  1024         constantNamed:'GenericToolbarIconLibrary class bookmarks22x22'
       
  1025         ifAbsentPut:[(Depth8Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
       
  1026 ????????????????????????????????????????????????????????????????????????LT;??????????????????????????6BAD/??????????????
       
  1027 ?????????16L''"+???????????????????????<7''95Y????????????????????????YI2[_!!C?????????????????????GXZZ&Y\0????????????I$YF
       
  1028 Q$YFQUBX%)VRZ%YAO34=OR????=T#9RT$9FP#(6K"(VB_718]U0%????FC)9"X"G!!HN@_W]4\V=)YT@E????????J&Y;^''Y3\''A-ZFI_UR8A??????????<Q
       
  1029 SF9,Z6]#WU!!SQBW??????????????1YWXU9ZTT5IP2K???????????????<)V5IOR$\>NS (????????????????M$-HP#,3KB\ZE07?????????????GST<
       
  1030 MB4$GATNB0(]?????????????142J18[@O<RC0XCD?????????????<!!H1$G?????1@T@ $H????????????G2@D?????????14L????????????????????
       
  1031 ?????????????????????????????????????????????0@a') ; colorMapFromArray:#[143 162 38 146 165 38 153 167 24 155 168 21 149 168 39 149 169 39 156 169 21 151 170 40 151 171 40 156 171 30 159 173 22 160 174 20 156 174 34 154 175 41 162 176 20 159 176 32 156 176 41 156 177 41 157 177 41 159 178 37 159 178 38 163 179 26 158 179 42 163 180 27 159 180 42 162 180 35 166 181 20 160 181 40 161 181 39 160 181 42 165 181 28 162 181 37 161 181 40 162 181 38 161 181 41 168 181 23 162 182 36 161 182 41 161 182 43 168 183 20 163 183 35 162 183 41 162 183 42 170 184 22 169 185 20 169 185 23 164 185 38 164 185 40 164 185 42 164 185 43 171 186 24 171 187 21 172 187 22 170 187 29 168 187 35 165 187 44 171 188 19 173 190 19 168 189 44 174 190 21 174 190 22 170 192 37 176 192 20 170 192 38 171 193 33 171 193 38 177 193 21 176 194 19 174 194 26 172 193 47 172 193 48 178 195 20 179 195 21 179 197 19 180 197 20 180 197 21 176 197 38 181 199 19 177 199 46 183 201 20 179 200 50 184 202 19 185 202 21 184 203 18 180 201 50 183 204 21 181 203 37 184 204 27 185 205 18 181 204 45 187 205 19 187 205 21 183 206 27 187 208 18 189 208 20 189 210 17 186 208 51 191 210 20 190 211 17 190 211 19 187 209 53 191 213 17 190 211 43 193 213 19 193 214 17 194 216 16 192 215 38 195 216 20 196 217 25 196 218 18 196 217 28 196 219 17 198 220 18 199 221 17 200 222 23 201 222 28 201 224 17 200 225 16 203 223 33 203 225 20 202 226 16 202 223 51 204 224 38 204 224 41 203 227 16 204 226 26 203 226 47 204 229 16 206 227 34 203 227 53 206 230 21 207 228 39 208 228 43 207 231 26 207 228 60 209 229 48 209 229 51 210 229 52 209 232 33 210 232 39 209 231 58 211 233 46 212 234 52 213 233 63 213 234 56 214 235 59 214 237 41 215 235 62 215 235 64 215 238 49 217 238 55 217 240 46 218 239 61 219 242 53 220 242 59 222 245 56 223 245 62 224 248 57 224 248 58 224 248 64 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255]; mask:((Depth1Image new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@C@@@C @@G @@G @@G0@@O0@_??8O??8O??0C?? A?>@@?<@@?<@@?>@A?>@A>>@A8_@A0F@@@@@@@@@') ; yourself); yourself]
       
  1032 
       
  1033     "Modified: / 05-05-2011 / 12:45:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  1034 ! !
       
  1035 
       
  1036 !GenericToolbarIconLibrary class methodsFor:'image specs - org.eclipse.debug.ui - obj16'!
       
  1037 
       
  1038 brkp_obj
       
  1039     "This resource specification was automatically generated
       
  1040      by the ImageEditor of ST/X."
       
  1041 
       
  1042     "Do not manually edit this!! If it is corrupted,
       
  1043      the ImageEditor may not be able to read the specification."
       
  1044 
       
  1045     "
       
  1046      self brkp_obj inspect
       
  1047      ImageEditor openOnClass:self andSelector:#brkp_obj
       
  1048      Icon flushCachedIcons
       
  1049     "
       
  1050 
       
  1051     <resource: #image>
       
  1052 
       
  1053     ^Icon
       
  1054         constantNamed:'GenericToolbarIconLibrary class brkp_obj'
       
  1055         ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8)); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
       
  1056 D1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1L@@ALSD1LSD1LSD1LS@@@@@@@@D1LSD1LSD0@S@@(C@ LJ@ALSD1LSD1L@@@<ABP,I
       
  1057 @P<@D1LSD1LS@@@CBADQDP C@ALSD1LSD1L@@ PMCAHD@ @SD1LSD1LS@@LEC 8NAPL@D1LSD1LS@@@O@PXPA0DO@ALSD1LSD1LS@@(C@ LJ@@@SD1LSD1LS
       
  1058 D0@@@@@@@ALSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LSD1LS@@@@@@@@@@@@@@@@@@@@@@@@
       
  1059 @@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[255 252 255 46 85 127 38 78 114 54 98 139 108 165 203 107 159 195 131 175 205 130 174 204 130 172 200 152 185 208 169 202 225 180 209 229 83 149 190 90 154 194 115 169 204 144 188 216 145 188 215 152 193 219 89 154 192 255 255 255]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@C8@_0A?@G<@_0A?@C8@@@@@@@@@@@@@@b') ; yourself); yourself]
       
  1060 ! !
       
  1061 
       
  1062 !GenericToolbarIconLibrary class methodsFor:'image specs - org.eclipse.debug.ui - obj16'!
       
  1063 
       
  1064 brkpd_obj
       
  1065     "This resource specification was automatically generated
       
  1066      by the ImageEditor of ST/X."
       
  1067 
       
  1068     "Do not manually edit this!! If it is corrupted,
       
  1069      the ImageEditor may not be able to read the specification."
       
  1070 
       
  1071     "
       
  1072      self brkpd_obj inspect
       
  1073      ImageEditor openOnClass:self andSelector:#brkpd_obj
       
  1074      Icon flushCachedIcons
       
  1075     "
       
  1076 
       
  1077     <resource: #image>
       
  1078 
       
  1079     ^Icon
       
  1080         constantNamed:'GenericToolbarIconLibrary class brkpd_obj'
       
  1081         ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8)); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
       
  1082 B0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,K@@@KB0,KB0,K@@,K@@@@@@@@B0,KB0,KB0@@@@LEA0TC@@,KB0,KB0,@@@LH@@@@
       
  1083 B@L@B0,KB0,K@@@I@@@@@@@I@@,KB0,KB0@@@P@@@@@@@P@KB0,KB0,K@@$@@@@@@@$@B0,KB0,KB0@DA @@@@XD@@@KB0,KB0,K@@PJ@P(D@@,@B0,KB0,@
       
  1084 @@@@@@@@@@,K@@,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0,KB0@@@@@@@@@@@@@@@@@@
       
  1085 @@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[227 235 248 79 80 79 255 255 255 201 201 201 182 182 182 135 135 135 122 122 122 105 105 105 103 103 103 98 98 98 85 85 85 255 255 255]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@C8@]0A#@DD@X0A7@C8@@@@@@@@@@@@@@b') ; yourself); yourself]
       
  1086 ! !
       
  1087 
       
  1088 !GenericToolbarIconLibrary class methodsFor:'image specs-16x16'!
       
  1089 
       
  1090 bug16x16Icon
       
  1091     "This resource specification was automatically generated
       
  1092      by the ImageEditor of ST/X."
       
  1093 
       
  1094     "Do not manually edit this!! If it is corrupted,
       
  1095      the ImageEditor may not be able to read the specification."
       
  1096 
       
  1097     "
       
  1098      self bug16x16Icon inspect
       
  1099      ImageEditor openOnClass:self andSelector:#bug16x16Icon
       
  1100      Icon flushCachedIcons
       
  1101     "
       
  1102 
       
  1103     <resource: #image>
       
  1104 
       
  1105     ^Icon
       
  1106         constantNamed:'GenericToolbarIconLibrary class bug16x16Icon'
       
  1107         ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8)); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
       
  1108 ???????????????????????????????????????????????????3R/??????????????????O"_???????????????????7=?#J1???????????=???=IBP$
       
  1109 ?_????????????7=W5=_W5?=O/7???????>L?PLC@0LC?_????????7=/4S[7S 8TY/=?VC?????L#L.>JI3I+A%H#[?????GA3_]U*/M3_;BPRLD_????7=
       
  1110 ?_B@M>DE-04>?U/??????2_=HEXYQ7:R<Q_???????4>G2$%Q9QEL?5_??????????<=?\;M??????????????????=-H????????0@a') ; colorMapFromArray:#[205 205 205 227 35 35 106 106 106 98 98 98 135 135 135 163 34 34 101 5 5 124 124 124 48 2 2 227 11 11 173 173 173 218 54 54 241 241 241 235 19 19 225 225 225 219 18 18 245 58 58 214 214 214 249 46 46 90 90 90 254 61 61 36 36 36 176 176 176 233 233 233 114 114 114 255 78 78 212 33 33 230 57 57 61 61 61 94 94 94 76 76 76 19 19 19 255 57 57 161 161 161 83 83 83 217 217 217 249 249 249 255 65 65 139 2 2 27 27 27 169 169 169 253 53 53 210 28 28 251 251 251 154 154 154 117 117 117 195 1 1 245 245 245 145 145 145 218 5 5 230 230 230 69 2 2 181 181 181 11 11 11 141 141 141 249 61 61 205 21 21 165 165 165 157 157 157 241 28 28 223 223 223 109 109 109 2 2 2 245 45 45 146 0 0 69 69 69 137 137 137 140 40 40 188 1 1 206 24 24 219 33 33 255 76 76 249 49 49 249 56 56 236 236 236 121 121 121 248 53 53 171 1 1 111 40 40 237 41 41 178 21 21 205 16 16 129 129 129 163 1 1 155 18 18 85 4 4 243 68 68 73 73 73 45 45 45 202 51 51 241 40 40 86 86 86 114 1 1 210 4 4 246 41 41 148 148 148 189 189 189 209 209 209 210 17 17 158 28 28 213 5 5 205 1 1 53 53 53 217 9 9 69 40 40 187 10 10 255 74 74 218 28 28 146 11 11 65 65 65 232 37 37 101 101 101 196 26 26 245 53 53 188 26 26 213 10 10 184 184 184 206 5 5 249 65 65 172 21 21 206 34 34 195 195 195 237 32 32 131 12 12 233 29 29 179 36 36 241 37 37 139 13 13 245 49 49 180 1 1 168 37 37 198 198 198 202 202 202 228 21 21 206 10 10 206 29 29 229 30 30 255 80 80 188 20 20 245 37 37 57 57 57 252 50 50 87 42 42 172 10 10 209 13 13 155 4 4 164 11 11 242 44 44 255 70 70 225 25 25 222 14 14 237 24 24 240 49 49 205 13 13 202 44 44 201 0 0 225 17 17 186 42 42 255 72 72 122 1 1 40 40 40 157 10 10 209 8 8 222 8 8 195 41 41 223 21 21 180 11 11 255 68 68 162 28 28 194 11 11 232 25 25 131 1 1 241 32 32 246 246 246 49 49 49 224 44 44 208 2 2 227 227 227 239 239 239 239 46 46 162 20 20 245 33 33 219 219 219 238 29 29 237 37 37 171 29 29 36 46 46 250 68 68 147 16 16 182 26 26 187 187 187 24 1 1 185 32 32 229 24 24 232 33 33 150 150 150 122 12 12 229 17 17 204 27 27 242 52 52 213 2 2 200 15 15 191 191 191 217 43 43 217 12 12 115 10 10 140 16 16 200 28 28 202 6 6 215 13 13 182 41 41 57 46 46 40 46 46 233 40 40 252 70 70 173 40 40 226 28 28 46 54 54 202 22 22 203 18 18 245 72 72 191 17 17 200 37 37 10 0 0 50 52 52 252 74 74 252 72 72 247 38 38 160 40 40 231 14 14 252 68 68 200 10 10 15 15 15 211 47 47 254 254 254 253 76 76 23 23 23 237 69 69 7 7 7 144 7 7 196 8 7 32 32 32 59 59 59 90 93 93 67 67 67 70 28 28 50 56 56 232 15 16 208 4 4 237 35 35 220 12 11 232 20 20 223 62 62 0 0 0 255 255 255 255 255 255]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@L@@0@C8AO C?0O<C?>G?0??#?>C?0_?@O@@L@b') ; yourself); yourself]
       
  1111 ! !
       
  1112 
       
  1113 !GenericToolbarIconLibrary class methodsFor:'image specs-24x24'!
       
  1114 
       
  1115 bug24x24Icon
       
  1116     "This resource specification was automatically generated
       
  1117      by the ImageEditor of ST/X."
       
  1118 
       
  1119     "Do not manually edit this!! If it is corrupted,
       
  1120      the ImageEditor may not be able to read the specification."
       
  1121 
       
  1122     "
       
  1123      self bug24x24Icon inspect
       
  1124      ImageEditor openOnClass:self andSelector:#bug24x24Icon
       
  1125      Icon flushCachedIcons
       
  1126     "
       
  1127 
       
  1128     <resource: #image>
       
  1129 
       
  1130     ^Icon
       
  1131         constantNamed:'GenericToolbarIconLibrary class bug24x24Icon'
       
  1132         ifAbsentPut:[(Depth8Image new) width: 24; height: 24; photometric:(#palette); bitsPerSample:(#(8)); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
       
  1133 ??????????????????????????????????????????????????>6???????????????????????1???????=????????????????????????<4+????=????
       
  1134 ????????????????????O"_???> ??????????????????????????7.?3;.?????????????????????????_4$?#K=,_????????????????7???=/?RP$
       
  1135 IBP$?_?????=????????MX3=???=L#H2L#H2?_7?XQW.???????????=?_7=W5=_W5=_W?7=O/7?????????????#O4''@0LC@0LC@?7=????????????????
       
  1136 ?_6 PTEAPTEAPSW=?????????????_7=/4R[6=48NC!!"TY-M?_7=XO???????3H0L29%>JK/\2Z",FUDH#YJ????????????L9-$3N>%%ZW/YL!!D????????
       
  1137 ????GA1W77W7V*<7M3\R>0%DAH0\D_???????_7=?_@M C_W8PTP-05MO/7=V???????B!!X4MX>WRW7WFPVZ"?//?1XV??????????<XI?7]HEXYFT]Y_)K=
       
  1138 <Q_???????????4XO!!?DJRU*Q9P%QSL5?U<-?????????3T5???=F$  EB@?L37?G3;=????????????????O_7D3,7=??????????????????????????<(
       
  1139 [RO?????????????????????????????????????????????') ; colorMapFromArray:#[205 205 205 227 35 35 106 106 106 98 98 98 135 135 135 163 34 34 101 5 5 124 124 124 48 2 2 227 11 11 173 173 173 218 54 54 241 241 241 235 19 19 225 225 225 219 18 18 245 58 58 214 214 214 249 46 46 90 90 90 254 61 61 36 36 36 176 176 176 233 233 233 114 114 114 255 78 78 212 33 33 230 57 57 61 61 61 94 94 94 76 76 76 19 19 19 255 57 57 161 161 161 83 83 83 217 217 217 249 249 249 255 65 65 139 2 2 27 27 27 169 169 169 253 53 53 210 28 28 251 251 251 154 154 154 117 117 117 195 1 1 245 245 245 145 145 145 218 5 5 230 230 230 69 2 2 181 181 181 11 11 11 141 141 141 249 61 61 205 21 21 165 165 165 157 157 157 241 28 28 223 223 223 109 109 109 2 2 2 245 45 45 146 0 0 69 69 69 137 137 137 140 40 40 188 1 1 206 24 24 219 33 33 255 76 76 249 49 49 249 56 56 236 236 236 121 121 121 248 53 53 171 1 1 111 40 40 237 41 41 178 21 21 205 16 16 129 129 129 163 1 1 155 18 18 85 4 4 243 68 68 73 73 73 45 45 45 202 51 51 241 40 40 86 86 86 114 1 1 210 4 4 246 41 41 148 148 148 189 189 189 209 209 209 210 17 17 158 28 28 213 5 5 205 1 1 53 53 53 217 9 9 69 40 40 187 10 10 255 74 74 218 28 28 146 11 11 65 65 65 232 37 37 101 101 101 196 26 26 245 53 53 188 26 26 213 10 10 184 184 184 206 5 5 249 65 65 172 21 21 206 34 34 195 195 195 237 32 32 131 12 12 233 29 29 179 36 36 241 37 37 139 13 13 245 49 49 180 1 1 168 37 37 198 198 198 202 202 202 228 21 21 206 10 10 206 29 29 229 30 30 255 80 80 188 20 20 245 37 37 57 57 57 252 50 50 87 42 42 172 10 10 209 13 13 155 4 4 164 11 11 242 44 44 255 70 70 225 25 25 222 14 14 237 24 24 240 49 49 205 13 13 202 44 44 201 0 0 225 17 17 186 42 42 255 72 72 122 1 1 40 40 40 157 10 10 209 8 8 222 8 8 195 41 41 223 21 21 180 11 11 255 68 68 162 28 28 194 11 11 232 25 25 131 1 1 241 32 32 246 246 246 49 49 49 224 44 44 208 2 2 227 227 227 239 239 239 239 46 46 162 20 20 245 33 33 219 219 219 238 29 29 237 37 37 171 29 29 36 46 46 250 68 68 147 16 16 182 26 26 187 187 187 24 1 1 185 32 32 229 24 24 232 33 33 150 150 150 122 12 12 229 17 17 204 27 27 242 52 52 213 2 2 200 15 15 191 191 191 217 43 43 217 12 12 115 10 10 140 16 16 200 28 28 202 6 6 215 13 13 182 41 41 57 46 46 40 46 46 233 40 40 252 70 70 173 40 40 226 28 28 46 54 54 202 22 22 203 18 18 245 72 72 191 17 17 200 37 37 10 0 0 50 52 52 252 74 74 252 72 72 247 38 38 160 40 40 231 14 14 252 68 68 200 10 10 15 15 15 211 47 47 254 254 254 253 76 76 23 23 23 237 69 69 7 7 7 144 7 7 196 8 7 32 32 32 59 59 59 90 93 93 67 67 67 70 28 28 50 56 56 232 15 16 208 4 4 237 35 35 220 12 11 232 20 20 223 62 62 0 0 0 255 255 255 255 255 255]; mask:((ImageMask new) width: 24; height: 24; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@H@@HH@@FH@@FH@@CX@@G<@BO<HGO>8A??0@??@@??@G??<C??8@??@G??<G??<G??XA??0C??8CO>8@G8@@A0@@@@@') ; yourself); yourself]
       
  1140 ! !
       
  1141 
       
  1142 !GenericToolbarIconLibrary class methodsFor:'image specs-32x32'!
       
  1143 
       
  1144 bug32x32Icon
       
  1145     <resource: #image>
       
  1146     "This resource specification was automatically generated
       
  1147      by the ImageEditor of ST/X."
       
  1148     "Do not manually edit this!! If it is corrupted,
       
  1149      the ImageEditor may not be able to read the specification."
       
  1150     "
       
  1151      self bug3232Icon inspect
       
  1152      ImageEditor openOnClass:self andSelector:#bug3232Icon
       
  1153      Icon flushCachedIcons"
       
  1154     
       
  1155     ^ Icon constantNamed:'GenericToolbarIconLibrary class bug3232Icon'
       
  1156         ifAbsentPut:[
       
  1157             (Depth8Image new)
       
  1158                 width:32;
       
  1159                 height:32;
       
  1160                 photometric:(#palette);
       
  1161                 bitsPerSample:(#( 8 ));
       
  1162                 samplesPerPixel:((1));
       
  1163                 bits:(ByteArray 
       
  1164                             fromPackedString:'
       
  1165 ??????????????????????????????????????????????????????????????????>6@/?????????????????????????????1H_????????4-????????
       
  1166 ???????????????????????=?_??????O!!???????????????????????????????3W3R/?????=I????????????????????????????????38''?????:C?
       
  1167 ??????????????????????????????????7.??<>;/???????????????????????????????????_7=?_7=????????????????????????????????[?7=
       
  1168 IO;>L/7=,_?????????????????????=?????6?=?RP$IBP$IO7=???????=????????????MX3=?????_42L#H2L#H2L/7=??=!!E^8Q????????????O.9K
       
  1169 ?_7=@G%9^W%9^W%9JO7=O%K=O/???????????????_7=?_5_W5=_W5=_W5=_?_7=O/7??????????????????83=I0LC@0LC@0LC@0O=?SK?????????????
       
  1170 ?????????_6 PTEAPTEAPTEAPSW=M_??????????????JC(SI?7= S#WP49(ZF"NS$N$]UO=?QU/@6G???????<-?_7=?[=D&5G[7S 8NC!!"65F[S_7=?_4U
       
  1171 XO??????????L#C4L29%,O"";7M3I*K8,FUD?RH6R/????????????????<3&6Q''3N>%%YV%;6]$2DS=????????????????????(@#8(92*/KN3,4=T0YZ#
       
  1172 K/40?????????????0P\GE]X77W7*%*/M3\7M1K9>0%D?PRLGB\Q????????<_7=?S;=<@5> C_W8^DEDC>7CT7=O/7=<U/?????????B!!X4?3VO%59I_]\Y
       
  1173 FPVZSH/;;8O?E!!Y9????????????????I<SAD#^BFX&IFVMI86H3H/??????????????????FB4''?]5^HEXY"Q%GVR%>$/4^<Q_???????????????4X?S8_
       
  1174 1DX)IV)GQ9P%D$T3MS;=W27?????????????MST!!???=1A)HHBTTHC?FL37??1<>?_?????????????????????=A''KUO9M.]0# ?????1_?????????????
       
  1175 ??????????<=?\SN3,7=H???????????????????????????????????JFY-H???????????????????????????????????????????????????????????
       
  1176 ?????????????????????????????????????????????0@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
       
  1177 @@@@@@@@@@@@');
       
  1178                 colorMapFromArray:#[ 205 205 205 227 35 35 106 106 106 98 98 98 135 135 135 163 34 34 101 5 5 124 124 124 48 2 2 227 11 11 173 173 173 218 54 54 241 241 241 235 19 19 225 225 225 219 18 18 245 58 58 214 214 214 249 46 46 90 90 90 254 61 61 36 36 36 176 176 176 233 233 233 114 114 114 255 78 78 212 33 33 230 57 57 61 61 61 94 94 94 76 76 76 19 19 19 255 57 57 161 161 161 83 83 83 217 217 217 249 249 249 255 65 65 139 2 2 27 27 27 169 169 169 253 53 53 210 28 28 251 251 251 154 154 154 117 117 117 195 1 1 245 245 245 145 145 145 218 5 5 230 230 230 69 2 2 181 181 181 11 11 11 141 141 141 249 61 61 205 21 21 165 165 165 157 157 157 241 28 28 223 223 223 109 109 109 2 2 2 245 45 45 146 0 0 69 69 69 137 137 137 140 40 40 188 1 1 206 24 24 219 33 33 255 76 76 249 49 49 249 56 56 236 236 236 121 121 121 248 53 53 171 1 1 111 40 40 237 41 41 178 21 21 205 16 16 129 129 129 163 1 1 155 18 18 85 4 4 243 68 68 73 73 73 45 45 45 202 51 51 241 40 40 86 86 86 114 1 1 210 4 4 246 41 41 148 148 148 189 189 189 209 209 209 210 17 17 158 28 28 213 5 5 205 1 1 53 53 53 217 9 9 69 40 40 187 10 10 255 74 74 218 28 28 146 11 11 65 65 65 232 37 37 101 101 101 196 26 26 245 53 53 188 26 26 213 10 10 184 184 184 206 5 5 249 65 65 172 21 21 206 34 34 195 195 195 237 32 32 131 12 12 233 29 29 179 36 36 241 37 37 139 13 13 245 49 49 180 1 1 168 37 37 198 198 198 202 202 202 228 21 21 206 10 10 206 29 29 229 30 30 255 80 80 188 20 20 245 37 37 57 57 57 252 50 50 87 42 42 172 10 10 209 13 13 155 4 4 164 11 11 242 44 44 255 70 70 225 25 25 222 14 14 237 24 24 240 49 49 205 13 13 202 44 44 201 0 0 225 17 17 186 42 42 255 72 72 122 1 1 40 40 40 157 10 10 209 8 8 222 8 8 195 41 41 223 21 21 180 11 11 255 68 68 162 28 28 194 11 11 232 25 25 131 1 1 241 32 32 246 246 246 49 49 49 224 44 44 208 2 2 227 227 227 239 239 239 239 46 46 162 20 20 245 33 33 219 219 219 238 29 29 237 37 37 171 29 29 36 46 46 250 68 68 147 16 16 182 26 26 187 187 187 24 1 1 185 32 32 229 24 24 232 33 33 150 150 150 122 12 12 229 17 17 204 27 27 242 52 52 213 2 2 200 15 15 191 191 191 217 43 43 217 12 12 115 10 10 140 16 16 200 28 28 202 6 6 215 13 13 182 41 41 57 46 46 40 46 46 233 40 40 252 70 70 173 40 40 226 28 28 46 54 54 202 22 22 203 18 18 245 72 72 191 17 17 200 37 37 10 0 0 50 52 52 252 74 74 252 72 72 247 38 38 160 40 40 231 14 14 252 68 68 200 10 10 15 15 15 211 47 47 254 254 254 253 76 76 23 23 23 237 69 69 7 7 7 144 7 7 196 8 7 32 32 32 59 59 59 90 93 93 67 67 67 70 28 28 50 56 56 232 15 16 208 4 4 237 35 35 220 12 11 232 20 20 223 62 62 0 0 0 255 255 255 255 255 255 ];
       
  1179                 mask:((ImageMask new)
       
  1180                             width:32;
       
  1181                             height:32;
       
  1182                             photometric:(#blackIs0);
       
  1183                             bitsPerSample:(#[ 1 ]);
       
  1184                             samplesPerPixel:((1));
       
  1185                             bits:(ByteArray 
       
  1186                                         fromPackedString:'
       
  1187 @@@@@@@@L@@@LC@@@A 0@@@\L@@@CB@@@@Y @@@G8@@@G? @AC?8H@8??O@G??? @???0@C??0@@??<@G???>A???? G??? @O??@@G??8@_???8G???>@;?
       
  1188 ?7@@??<@@???0@_??>@GO?3 @A?8P@@O<@@@@<@@@@@@@@@@@@@b');
       
  1189                             yourself);
       
  1190                 yourself
       
  1191         ]
       
  1192 ! !
       
  1193 
       
  1194 !GenericToolbarIconLibrary class methodsFor:'image specs-16x16'!
       
  1195 
       
  1196 lint16x16Icon
       
  1197     "This resource specification was automatically generated
       
  1198      by the ImageEditor of ST/X."
       
  1199 
       
  1200     "Do not manually edit this!! If it is corrupted,
       
  1201      the ImageEditor may not be able to read the specification."
       
  1202 
       
  1203     "
       
  1204      self lint16x16Icon inspect
       
  1205      ImageEditor openOnClass:self andSelector:#lint16x16Icon
       
  1206      Icon flushCachedIcons
       
  1207     "
       
  1208 
       
  1209     <resource: #image>
       
  1210 
       
  1211     ^Icon
       
  1212         constantNamed:'GenericToolbarIconLibrary class lint16x16Icon'
       
  1213         ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(8)); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
       
  1214 ??????????????????????????????????????????????????<4[_??????????????????A4W??????????????????2<A()BG??????????<A??<A1_;>
       
  1215 @XS??????????3<)-;^76.Z5A0O???????<P@W!!8>-3J<0+??????0\JI1,;7^?57-[;''T????<JS0P"PN3'':-V>8L??????V5@''G57.1,!!#X-''R_O???1(R
       
  1216 @RMW:Y*KY6+7*RW??????3P*ZU[;.:#!!/:7???????<A@6AV2?S:9+>5??????????< BC &?????;?Z??????????<XU_?????X<P@a') ; colorMapFromArray:#[0 1 0 0 2 0 1 4 0 3 6 2 30 1 0 6 9 5 34 2 2 10 12 8 43 4 2 13 15 12 15 17 13 77 0 0 16 18 15 35 14 12 17 19 16 67 6 1 19 20 18 75 7 10 21 23 20 86 9 4 25 27 24 111 4 7 103 7 10 96 10 12 32 29 28 29 30 28 31 33 30 153 2 0 33 35 33 35 36 34 110 16 16 173 0 1 36 38 35 41 37 36 165 4 0 155 7 7 128 15 14 39 41 39 157 12 16 51 42 42 207 0 4 43 45 42 58 41 39 141 19 15 199 4 0 210 3 0 221 1 4 48 49 47 231 0 12 211 7 8 172 19 10 172 19 18 52 54 51 53 55 53 234 5 23 59 54 53 176 24 21 56 57 55 57 59 56 204 19 22 195 22 24 103 47 48 227 16 9 60 61 59 198 25 19 216 20 21 61 63 60 119 48 45 228 20 20 63 65 62 211 30 27 68 69 67 69 71 68 212 32 34 242 25 29 72 74 71 74 76 74 191 45 50 245 31 38 76 78 75 77 79 76 79 80 78 138 66 66 248 36 40 240 41 43 83 85 82 216 50 52 241 43 50 195 58 61 86 88 85 244 46 46 87 89 86 89 91 88 214 58 58 193 65 67 92 93 91 248 51 49 109 90 87 185 68 87 194 67 80 87 95 125 250 54 57 173 74 96 202 67 84 159 78 103 253 56 52 188 72 90 87 99 135 129 89 121 99 101 98 73 104 148 255 59 60 159 83 106 175 81 94 94 102 132 187 78 98 215 71 85 255 61 67 169 84 104 251 66 66 104 106 103 90 106 147 151 92 119 200 81 93 107 108 106 140 99 131 162 94 119 255 72 76 144 100 128 96 112 153 228 80 83 159 97 120 111 113 110 191 90 111 206 87 104 113 115 112 87 118 163 115 117 114 83 122 166 179 100 117 118 120 117 199 99 101 231 91 88 138 113 147 120 122 119 196 101 119 123 125 122 115 123 167 213 100 113 119 123 162 180 109 128 127 129 126 208 108 109 115 131 173 185 115 140 158 122 154 173 119 144 131 133 130 130 130 163 178 122 124 181 119 147 106 139 178 136 138 135 120 139 175 126 138 175 204 121 132 132 139 172 113 146 186 136 143 176 144 146 143 121 149 184 153 142 173 135 150 181 148 150 147 125 153 188 130 153 182 179 140 167 150 152 149 205 136 148 181 145 146 136 159 189 155 157 154 140 163 193 159 161 158 161 163 160 143 166 196 162 164 161 148 167 192 164 166 163 165 165 187 197 159 173 167 169 166 152 171 196 191 163 180 157 172 191 169 171 168 216 159 166 171 173 170 208 163 179 187 169 190 217 162 175 174 176 173 159 178 203 186 173 174 207 167 175 163 178 198 213 166 176 179 181 178 198 176 192 169 185 204 183 185 182 216 175 184 209 177 189 212 180 192 204 183 198 208 183 193 188 190 187 180 192 206 194 196 193 215 191 201 187 199 213 204 198 197 211 196 210 199 201 198 190 202 216 191 203 217 201 202 212 202 204 201 208 203 201 219 201 210 205 207 203 217 203 217 206 208 205 213 207 206 223 205 214 203 211 220 211 213 210 211 212 222 214 216 213 221 215 227 217 219 216 219 221 218 228 218 224 217 222 225 221 223 220 231 221 227 216 225 233 220 226 228 224 226 223 221 229 238 231 233 230 228 234 236 233 235 232 235 238 234 249 251 248 255 255 255]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@L@@0@C8AO0C?0O>C?>O?0??#?>C?0O?@OC@LLb') ; yourself); yourself]
       
  1217 ! !
       
  1218 
       
  1219 !GenericToolbarIconLibrary class methodsFor:'image specs-24x24'!
       
  1220 
       
  1221 lint24x24Icon
       
  1222     "This resource specification was automatically generated
       
  1223      by the ImageEditor of ST/X."
       
  1224 
       
  1225     "Do not manually edit this!! If it is corrupted,
       
  1226      the ImageEditor may not be able to read the specification."
       
  1227 
       
  1228     "
       
  1229      self lint24x24Icon inspect
       
  1230      ImageEditor openOnClass:self andSelector:#lint24x24Icon
       
  1231      Icon flushCachedIcons
       
  1232     "
       
  1233 
       
  1234     <resource: #image>
       
  1235 
       
  1236     ^Icon
       
  1237         constantNamed:'GenericToolbarIconLibrary class lint24x24Icon'
       
  1238         ifAbsentPut:[(Depth8Image new) width: 24; height: 24; photometric:(#palette); bitsPerSample:(#(8)); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
       
  1239 ??????????????????????????????????????????????????????????????????????????=_W?????< @???????????????????????MF7???<4????
       
  1240 ????????????????????A4W???<L?????????????????????????2AG?4HY????????????????????????K0E[()@J!!????????????????0G?????@\W>
       
  1241 ?/;0@XS???<Z????????JUEK??</0?3<?O3<F G??0)H??????????<GO2$A-;^7-=+,9+T]A0MU????????????D@DG^G!!<>-262/O1B/??????????????
       
  1242 @PDPR4/I):+J+8+Q,_??????????A0(]I1,,N=7J;?W27-ZO>94NS???????B$=QABH(PN2#9>+%5[:@8L>D????????????A!!<-S_BU6=/W3)Y:.]??????
       
  1243 ????V5AEI1<>W^:$1,"2X6I(6]IP_O??????F!!HN@RL0U>&6&(-1Y6)(=:$RI_??????N%%\@1UDXKO;(HM6^7M,<G!!Y#O??????????MB(2ZUZX>;.&*NG:
       
  1244 /:6D??????????<)@PLSXEY?2?S<>.Y-/;V-?????????1$A??<GRU)/]8JMT"_?/;>5#O??????????????H@ +NBXQ??????>:/=*L??????????????<9
       
  1245 FEU_????????6OF5????????????????????????????-]K?') ; colorMapFromArray:#[0 1 0 0 2 0 1 4 0 3 6 2 30 1 0 6 9 5 34 2 2 10 12 8 43 4 2 13 15 12 15 17 13 77 0 0 16 18 15 35 14 12 17 19 16 67 6 1 19 20 18 75 7 10 21 23 20 86 9 4 25 27 24 111 4 7 103 7 10 96 10 12 32 29 28 29 30 28 31 33 30 153 2 0 33 35 33 35 36 34 110 16 16 173 0 1 36 38 35 41 37 36 165 4 0 155 7 7 128 15 14 39 41 39 157 12 16 51 42 42 207 0 4 43 45 42 58 41 39 141 19 15 199 4 0 210 3 0 221 1 4 48 49 47 231 0 12 211 7 8 172 19 10 172 19 18 52 54 51 53 55 53 234 5 23 59 54 53 176 24 21 56 57 55 57 59 56 204 19 22 195 22 24 103 47 48 227 16 9 60 61 59 198 25 19 216 20 21 61 63 60 119 48 45 228 20 20 63 65 62 211 30 27 68 69 67 69 71 68 212 32 34 242 25 29 72 74 71 74 76 74 191 45 50 245 31 38 76 78 75 77 79 76 79 80 78 138 66 66 248 36 40 240 41 43 83 85 82 216 50 52 241 43 50 195 58 61 86 88 85 244 46 46 87 89 86 89 91 88 214 58 58 193 65 67 92 93 91 248 51 49 109 90 87 185 68 87 194 67 80 87 95 125 250 54 57 173 74 96 202 67 84 159 78 103 253 56 52 188 72 90 87 99 135 129 89 121 99 101 98 73 104 148 255 59 60 159 83 106 175 81 94 94 102 132 187 78 98 215 71 85 255 61 67 169 84 104 251 66 66 104 106 103 90 106 147 151 92 119 200 81 93 107 108 106 140 99 131 162 94 119 255 72 76 144 100 128 96 112 153 228 80 83 159 97 120 111 113 110 191 90 111 206 87 104 113 115 112 87 118 163 115 117 114 83 122 166 179 100 117 118 120 117 199 99 101 231 91 88 138 113 147 120 122 119 196 101 119 123 125 122 115 123 167 213 100 113 119 123 162 180 109 128 127 129 126 208 108 109 115 131 173 185 115 140 158 122 154 173 119 144 131 133 130 130 130 163 178 122 124 181 119 147 106 139 178 136 138 135 120 139 175 126 138 175 204 121 132 132 139 172 113 146 186 136 143 176 144 146 143 121 149 184 153 142 173 135 150 181 148 150 147 125 153 188 130 153 182 179 140 167 150 152 149 205 136 148 181 145 146 136 159 189 155 157 154 140 163 193 159 161 158 161 163 160 143 166 196 162 164 161 148 167 192 164 166 163 165 165 187 197 159 173 167 169 166 152 171 196 191 163 180 157 172 191 169 171 168 216 159 166 171 173 170 208 163 179 187 169 190 217 162 175 174 176 173 159 178 203 186 173 174 207 167 175 163 178 198 213 166 176 179 181 178 198 176 192 169 185 204 183 185 182 216 175 184 209 177 189 212 180 192 204 183 198 208 183 193 188 190 187 180 192 206 194 196 193 215 191 201 187 199 213 204 198 197 211 196 210 199 201 198 190 202 216 191 203 217 201 202 212 202 204 201 208 203 201 219 201 210 205 207 203 217 203 217 206 208 205 213 207 206 223 205 214 203 211 220 211 213 210 211 212 222 214 216 213 221 215 227 217 219 216 219 221 218 228 218 224 217 222 225 221 223 220 231 221 227 216 225 233 220 226 228 224 226 223 221 229 238 231 233 230 228 234 236 233 235 232 235 238 234 249 251 248 255 255 255]; mask:((ImageMask new) width: 24; height: 24; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@LL@@FH@@FH@@CX@@G<@BG>HGO>XA??8@?? @?? G??<G??8@??0G??<G??<G??<@??8A??8CO><@G8O@A8G@@@F') ; yourself); yourself]
       
  1246 ! !
       
  1247 
       
  1248 !GenericToolbarIconLibrary class methodsFor:'image specs-32x32'!
       
  1249 
       
  1250 lint32x32Icon
       
  1251     "This resource specification was automatically generated
       
  1252      by the ImageEditor of ST/X."
       
  1253 
       
  1254     "Do not manually edit this!! If it is corrupted,
       
  1255      the ImageEditor may not be able to read the specification."
       
  1256 
       
  1257     "
       
  1258      self lint32x32Icon inspect
       
  1259      ImageEditor openOnClass:self andSelector:#lint32x32Icon
       
  1260      Icon flushCachedIcons
       
  1261     "
       
  1262 
       
  1263     <resource: #image>
       
  1264 
       
  1265     ^Icon
       
  1266         constantNamed:'GenericToolbarIconLibrary class lint32x32Icon'
       
  1267         ifAbsentPut:[(Depth8Image new) width: 32; height: 32; photometric:(#palette); bitsPerSample:(#(8)); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
       
  1268 ????????????????????????????????????????????????????????????????????!!O????????????????????????????=_JU???????2@4@???????
       
  1269 ??????????????????????<AT_??????@Q*??????????????????????????????4H4[_????<4O????????????????????????????????0]E?????01K
       
  1270 ?????????????????????????????????2AG??=BFX_?????????????????????????????????QQ$A@PDR?????????????????????????????????2<A
       
  1271 V96"$@(C!!?????????????????????<A??????<R@\W>?/;><CPA!!O????<Z????????????JUEK????K0GC?O3<?O3<>A(A????B$"G????????????@SQG
       
  1272 V0(ARNO#8>O#8>O_+PD9NS(%@P_?????????????A0\?JPFW-;^7-;_Z;OG&-Q5EA0MU????????????????QQ@AA718^G2?>-26+,+3<W0J????????????
       
  1273 ????????@PDPR4-K2_^''*,+M+8+Q>+G??????????????4IHUV4)B19COVG:(\K9=.7"/XGY;E=HQZ''???????=\A0(]P"\[KC,;7\*+;?W2:-;V#8#;''P8%
       
  1274 S?????????<JS5D)ABH(LTC,(<_'':.W[5[:@^^CO!!@G???????????????<FG241S_BU4M/[5=ON%'')2.]???????????????????0P_K"9^=IOA5MOL1JU&
       
  1275 \FR47?????????????=[TDT:I1<>M%7.)KCF2KJTX6I(Z=''RTD-<????????EA(RC DAH3AJU>&6&9*K\WQ''Z&!!.=:$RMBW?????????N%%\C LUQD9 ,?.Y
       
  1276 (HM6!!''-3[LC0^E%_#O??????????????!!@=AS&UX9N.Y''G:Q!!W6,?]"L?????????????????4,4J#INZUZX9/.;)):(8_+0/:6D??????????????<)GPDC
       
  1277 D4Y U''>N2?S<?_+&[\N?-Z6I????????????FPD)??<GE$%Z[7U7 (6_T"_??;>?-Z6L????????????Q?????<AE31TXFAZRRPM?????;2<.J6R????????
       
  1278 ??????????< BB,3NBXQM????????;*</=*L????????????????????NRDXUU???????????;#X<[W??????????????????????????????????????;WR
       
  1279 ?????????????????????????????????????????????0@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
       
  1280 @@@@@@@@@@@@') ; colorMapFromArray:#[0 1 0 0 2 0 1 4 0 3 6 2 30 1 0 6 9 5 34 2 2 10 12 8 43 4 2 13 15 12 15 17 13 77 0 0 16 18 15 35 14 12 17 19 16 67 6 1 19 20 18 75 7 10 21 23 20 86 9 4 25 27 24 111 4 7 103 7 10 96 10 12 32 29 28 29 30 28 31 33 30 153 2 0 33 35 33 35 36 34 110 16 16 173 0 1 36 38 35 41 37 36 165 4 0 155 7 7 128 15 14 39 41 39 157 12 16 51 42 42 207 0 4 43 45 42 58 41 39 141 19 15 199 4 0 210 3 0 221 1 4 48 49 47 231 0 12 211 7 8 172 19 10 172 19 18 52 54 51 53 55 53 234 5 23 59 54 53 176 24 21 56 57 55 57 59 56 204 19 22 195 22 24 103 47 48 227 16 9 60 61 59 198 25 19 216 20 21 61 63 60 119 48 45 228 20 20 63 65 62 211 30 27 68 69 67 69 71 68 212 32 34 242 25 29 72 74 71 74 76 74 191 45 50 245 31 38 76 78 75 77 79 76 79 80 78 138 66 66 248 36 40 240 41 43 83 85 82 216 50 52 241 43 50 195 58 61 86 88 85 244 46 46 87 89 86 89 91 88 214 58 58 193 65 67 92 93 91 248 51 49 109 90 87 185 68 87 194 67 80 87 95 125 250 54 57 173 74 96 202 67 84 159 78 103 253 56 52 188 72 90 87 99 135 129 89 121 99 101 98 73 104 148 255 59 60 159 83 106 175 81 94 94 102 132 187 78 98 215 71 85 255 61 67 169 84 104 251 66 66 104 106 103 90 106 147 151 92 119 200 81 93 107 108 106 140 99 131 162 94 119 255 72 76 144 100 128 96 112 153 228 80 83 159 97 120 111 113 110 191 90 111 206 87 104 113 115 112 87 118 163 115 117 114 83 122 166 179 100 117 118 120 117 199 99 101 231 91 88 138 113 147 120 122 119 196 101 119 123 125 122 115 123 167 213 100 113 119 123 162 180 109 128 127 129 126 208 108 109 115 131 173 185 115 140 158 122 154 173 119 144 131 133 130 130 130 163 178 122 124 181 119 147 106 139 178 136 138 135 120 139 175 126 138 175 204 121 132 132 139 172 113 146 186 136 143 176 144 146 143 121 149 184 153 142 173 135 150 181 148 150 147 125 153 188 130 153 182 179 140 167 150 152 149 205 136 148 181 145 146 136 159 189 155 157 154 140 163 193 159 161 158 161 163 160 143 166 196 162 164 161 148 167 192 164 166 163 165 165 187 197 159 173 167 169 166 152 171 196 191 163 180 157 172 191 169 171 168 216 159 166 171 173 170 208 163 179 187 169 190 217 162 175 174 176 173 159 178 203 186 173 174 207 167 175 163 178 198 213 166 176 179 181 178 198 176 192 169 185 204 183 185 182 216 175 184 209 177 189 212 180 192 204 183 198 208 183 193 188 190 187 180 192 206 194 196 193 215 191 201 187 199 213 204 198 197 211 196 210 199 201 198 190 202 216 191 203 217 201 202 212 202 204 201 208 203 201 219 201 210 205 207 203 217 203 217 206 208 205 213 207 206 223 205 214 203 211 220 211 213 210 211 212 222 214 216 213 221 215 227 217 219 216 219 221 218 228 218 224 217 222 225 221 223 220 231 221 227 216 225 233 220 226 228 224 226 223 221 229 238 231 233 230 228 234 236 233 235 232 235 238 234 249 251 248 255 255 255]; mask:((ImageMask new) width: 32; height: 32; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
       
  1281 @@@@@@@@D@@@NC @@A 8@@@\L@@@CC@@@@Y0@@@G8@@@C? @AA?<H@8??G@G???0@???8@G??8@@??>@C???>A???? O???0@O??0@C??<@O???8G???>@??
       
  1282 ?? @???@@_??8@O???@GO?38@!!?8_@@O<C8@@>@^@@@@C@@@@@@b') ; yourself); yourself]
   167 ! !
  1283 ! !
   168 
  1284 
   169 !Image methodsFor:'inspecting'!
  1285 !Image methodsFor:'inspecting'!
   170 
  1286 
   171 inspectorClass
  1287 inspectorClass
   198 
  1314 
   199     "Created: / 18-09-2006 / 21:22:46 / cg"
  1315     "Created: / 18-09-2006 / 21:22:46 / cg"
   200     "Modified: / 06-10-2006 / 13:57:28 / cg"
  1316     "Modified: / 06-10-2006 / 13:57:28 / cg"
   201 ! !
  1317 ! !
   202 
  1318 
       
  1319 !MenuView methodsFor:'accessing-behavior'!
       
  1320 
       
  1321 shortKeys
       
  1322     ^ shortKeys
       
  1323 
       
  1324     "Created: / 18-10-2008 / 19:16:59 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
  1325 ! !
       
  1326 
   203 !Method methodsFor:'inspecting'!
  1327 !Method methodsFor:'inspecting'!
   204 
  1328 
   205 inspectorExtraAttributes
  1329 inspectorExtraAttributes
   206     "extra (pseudo instvar) entries to be shown in an inspector."
  1330     "extra (pseudo instvar) entries to be shown in an inspector."
   207 
  1331 
   223 
  1347 
   224 printStringForBrowserWithSelector:selector inClass:aClass
  1348 printStringForBrowserWithSelector:selector inClass:aClass
   225     "return a printString to represent myself to the user in a browser.
  1349     "return a printString to represent myself to the user in a browser.
   226      Defined here to allow for browsers to deal with nonStandard pseudoMethods"
  1350      Defined here to allow for browsers to deal with nonStandard pseudoMethods"
   227 
  1351 
   228     |s privInfo moreInfo p info n cls currentChangeSet isInChangeSet mthdPackage
  1352     |s privInfo moreInfo p info n cls ns currentChangeSet isInChangeSet mthdPackage
   229      userPreferences shownSelector suppressPackage timeRounded|
  1353      userPreferences shownSelector suppressPackage timeRounded|
   230 
  1354 
   231     moreInfo := ''.
  1355     moreInfo := ''.
   232     privInfo := ''.
  1356     privInfo := ''.
   233     userPreferences := UserPreferences current.
  1357     userPreferences := UserPreferences current.
       
  1358 
       
  1359     ns := self nameSpace.
       
  1360     (ns notNil and:[ns isNameSpace]) ifTrue:[
       
  1361         moreInfo := moreInfo , 
       
  1362             ((' < %1 >' bindWith: ns name) asText emphasisAllAdd:
       
  1363                 userPreferences emphasisForNamespacedCode)
       
  1364 
       
  1365     ].
   234 
  1366 
   235     self isWrapped ifTrue:[
  1367     self isWrapped ifTrue:[
   236         (MessageTracer isCounting:self) ifTrue:[
  1368         (MessageTracer isCounting:self) ifTrue:[
   237             (MessageTracer isCountingMemoryUsage:self) ifTrue:[
  1369             (MessageTracer isCountingMemoryUsage:self) ifTrue:[
   238                 moreInfo := moreInfo , (' (mem usage avg: %1 bytes)' bindWith:(MessageTracer memoryUsageOfMethod:self) printString allBold).
  1370                 moreInfo := moreInfo , (' (mem usage avg: %1 bytes)' bindWith:(MessageTracer memoryUsageOfMethod:self) printString allBold).
   332     ^ s
  1464     ^ s
   333 
  1465 
   334     "Modified: / 23-01-1998 / 13:15:15 / stefan"
  1466     "Modified: / 23-01-1998 / 13:15:15 / stefan"
   335     "Created: / 05-02-2000 / 22:55:56 / cg"
  1467     "Created: / 05-02-2000 / 22:55:56 / cg"
   336     "Modified: / 05-03-2007 / 16:18:53 / cg"
  1468     "Modified: / 05-03-2007 / 16:18:53 / cg"
       
  1469     "Modified: / 20-07-2010 / 15:39:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   337 ! !
  1470 ! !
   338 
  1471 
   339 !Method methodsFor:'printing & storing'!
  1472 !Method methodsFor:'printing & storing'!
   340 
  1473 
   341 selectorPrintStringInBrowserFor:selector
  1474 selectorPrintStringInBrowserFor:selector
   348     |nsPart selPart idx ns|
  1481     |nsPart selPart idx ns|
   349 
  1482 
   350     selector isNameSpaceSelector ifFalse:[^ selector].
  1483     selector isNameSpaceSelector ifFalse:[^ selector].
   351 
  1484 
   352     idx := selector indexOf:$: startingAt:3.
  1485     idx := selector indexOf:$: startingAt:3.
       
  1486     "
   353     nsPart := selector copyFrom:2 to:idx-1.
  1487     nsPart := selector copyFrom:2 to:idx-1.
   354     ns := Smalltalk at:nsPart asSymbol.
  1488     ns := Smalltalk at:nsPart asSymbol.
       
  1489     "
   355     selPart := selector copyFrom:idx+2.
  1490     selPart := selector copyFrom:idx+2.
   356     ^ selPart , ' {',nsPart,'}'.
  1491     ^ selPart ", ' {',nsPart,'}'."
       
  1492 
       
  1493     "Modified: / 20-07-2010 / 10:33:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   357 ! !
  1494 ! !
   358 
  1495 
   359 !MethodDictionary methodsFor:'inspecting'!
  1496 !MethodDictionary methodsFor:'inspecting'!
   360 
  1497 
   361 inspectorClass
  1498 inspectorClass
   376      (instead of the default Inspector)."
  1513      (instead of the default Inspector)."
   377 
  1514 
   378     ^ DictionaryInspectorView
  1515     ^ DictionaryInspectorView
   379 
  1516 
   380 
  1517 
       
  1518 ! !
       
  1519 
       
  1520 !Object methodsFor:'converting'!
       
  1521 
       
  1522 asTestCase
       
  1523 
       
  1524     ^self
       
  1525 
       
  1526     "Created: / 04-03-2011 / 08:19:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  1527 ! !
       
  1528 
       
  1529 !Object methodsFor:'debugging'!
       
  1530 
       
  1531 inspect
       
  1532     "{ Pragma: +optSpace }"
       
  1533 
       
  1534     "launch an inspector on the receiver.
       
  1535      this method (or better: inspectorClass) can be redefined in subclasses
       
  1536      to start special inspectors."
       
  1537 
       
  1538     |cls|
       
  1539 
       
  1540     cls := (Smalltalk classNamed: #'Tools::Inspector2') 
       
  1541                 ifNil:[self inspectorClass].
       
  1542 
       
  1543     cls isNil ifTrue:[
       
  1544         ^ self basicInspect
       
  1545     ].
       
  1546     cls openOn:self
       
  1547 
       
  1548     "
       
  1549      Object new inspect
       
  1550      (1 @ 2) inspect
       
  1551      Smalltalk inspect
       
  1552      #(1 2 3) asOrderedCollection inspect
       
  1553      (Color red) inspect
       
  1554      (Image fromFile:'bitmaps/garfield.gif') inspect
       
  1555     "
       
  1556 ! !
       
  1557 
       
  1558 !Object methodsFor:'debugging'!
       
  1559 
       
  1560 inspector2TabCommon
       
  1561 
       
  1562     ^(Tools::Inspector2Tab new
       
  1563             priority: 50;
       
  1564             label:'Object';
       
  1565             view: ((self inspectorClass new inspect:self)
       
  1566                         yourself))
       
  1567 
       
  1568     "Created: / 24-05-2011 / 14:56:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   381 ! !
  1569 ! !
   382 
  1570 
   383 !Object methodsFor:'debugging'!
  1571 !Object methodsFor:'debugging'!
   384 
  1572 
   385 inspectorExtraAttributes
  1573 inspectorExtraAttributes
   399     "Created: / 16-08-2005 / 20:43:33 / janfrog"
  1587     "Created: / 16-08-2005 / 20:43:33 / janfrog"
   400     "Modified: / 02-09-2005 / 19:00:01 / janfrog"
  1588     "Modified: / 02-09-2005 / 19:00:01 / janfrog"
   401     "Modified: / 04-10-2006 / 14:33:34 / cg"
  1589     "Modified: / 04-10-2006 / 14:33:34 / cg"
   402 ! !
  1590 ! !
   403 
  1591 
       
  1592 !Object methodsFor:'testing'!
       
  1593 
       
  1594 isTestCaseLike
       
  1595 
       
  1596     ^false
       
  1597 
       
  1598     "Created: / 28-02-2011 / 21:30:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  1599 ! !
       
  1600 
       
  1601 !Object methodsFor:'debugging'!
       
  1602 
       
  1603 newInspector2Tab
       
  1604 
       
  1605     "Use Smalltalk>>at: to trick the dependency detector"
       
  1606 
       
  1607     ^(Smalltalk at: #'Tools::Inspector2Tab') 
       
  1608         ifNil:[self error:'Inspector2 not available!! Something is rotten...']
       
  1609         ifNotNil:[(Smalltalk at: #'Tools::Inspector2Tab') new]
       
  1610 ! !
       
  1611 
   404 !OrderedCollection methodsFor:'inspecting'!
  1612 !OrderedCollection methodsFor:'inspecting'!
   405 
  1613 
   406 inspectorClass
  1614 inspectorClass
   407     "redefined to launch an OrderedCollectionInspector
  1615     "redefined to launch an OrderedCollectionInspector
   408      (instead of the default InspectorView)."
  1616      (instead of the default InspectorView)."
   414      (OrderedCollection withAll:#(3 2 1)) removeFirst; yourself; inspect
  1622      (OrderedCollection withAll:#(3 2 1)) removeFirst; yourself; inspect
   415      #(0 8 15 3 99 2) asSortedCollection inspect
  1623      #(0 8 15 3 99 2) asSortedCollection inspect
   416     "
  1624     "
   417 ! !
  1625 ! !
   418 
  1626 
   419 !RunArray methodsFor:'inspecting'!
  1627 !PopUpMenu methodsFor:'converting'!
       
  1628 
       
  1629 asMenu
       
  1630 
       
  1631     | menu  |
       
  1632     menu := Menu new receiver: menuView receiver.
       
  1633     1 to: self numberOfItems do:
       
  1634         [:i| | menuItem |
       
  1635         menuItem := MenuItem new
       
  1636                         label: (self labels at: i);
       
  1637                         value: (menuView selectors at: i);
       
  1638                         enabled: (menuView isEnabled: i);
       
  1639                         shortcutKey: (menuView shortKeys at: i);
       
  1640                         yourself.
       
  1641 
       
  1642         (self subMenuAt: i) ifNotNil:
       
  1643             [menuItem submenu: (self subMenuAt: i) asMenu].
       
  1644         menu addItem: menuItem.
       
  1645         ].
       
  1646     ^menu.
       
  1647 
       
  1648     "Created: / 18-10-2008 / 19:01:32 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
  1649 ! !
       
  1650 
       
  1651 !ProfileTree methodsFor:'accessing'!
       
  1652 
       
  1653 method
       
  1654 
       
  1655     class ifNil:[^nil].
       
  1656     ^class >> selector
       
  1657 
       
  1658     "Created: / 01-12-2007 / 22:50:16 / janfrog"
       
  1659     "Modified: / 07-11-2008 / 08:40:35 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
  1660 ! !
       
  1661 
       
  1662 !ProfileTree methodsFor:'accessing'!
       
  1663 
       
  1664 package
       
  1665 
       
  1666     self method ifNil:[^nil].
       
  1667     ^self method package
       
  1668 
       
  1669     "Created: / 01-12-2007 / 22:50:28 / janfrog"
       
  1670     "Modified: / 07-11-2008 / 08:40:35 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
  1671 ! !
       
  1672 
       
  1673 !RBMessageNode methodsFor:'libtool3 support'!
       
  1674 
       
  1675 highlightInCodeView: aCodeView
       
  1676 
       
  1677     ^aCodeView highlightMessageNode: self
       
  1678 
       
  1679     "Created: / 18-02-2008 / 17:51:11 / janfrog"
       
  1680 ! !
       
  1681 
       
  1682 !RBMessageNode methodsFor:'libtool3 support'!
       
  1683 
       
  1684 leftClickMenuInCodeView: aCodeView 
       
  1685     ^ aCodeView leftClickMenuForMessageNode: self.
       
  1686 
       
  1687     "Created: / 18-02-2008 / 19:04:45 / janfrog"
       
  1688 ! !
       
  1689 
       
  1690 !RBMessageNode methodsFor:'libtool3 support'!
       
  1691 
       
  1692 middleClickMenuInCodeView: aCodeView 
       
  1693     ^ aCodeView middleClickMenuForMessageNode: self.
       
  1694 
       
  1695     "Created: / 18-02-2008 / 19:04:58 / janfrog"
       
  1696 ! !
       
  1697 
       
  1698 !RBMessageNode methodsFor:'libtool3 support'!
       
  1699 
       
  1700 rightClickMenuInCodeView: aCodeView 
       
  1701     ^ aCodeView rightClickMenuForMessageNode: self.
       
  1702 
       
  1703     "Created: / 18-02-2008 / 19:05:18 / janfrog"
       
  1704 ! !
       
  1705 
       
  1706 !RBProgramNode methodsFor:'stx:libtool support'!
       
  1707 
       
  1708 highlightInCodeView: aCodeView
       
  1709 
       
  1710     aCodeView highlightClear
       
  1711 
       
  1712     "Created: / 18-02-2008 / 17:48:12 / janfrog"
       
  1713 ! !
       
  1714 
       
  1715 !RBProgramNode methodsFor:'stx:libtool support'!
       
  1716 
       
  1717 leftClickMenuInCodeView: aCodeView 
       
  1718     ^ nil
       
  1719 
       
  1720     "Created: / 18-02-2008 / 17:49:43 / janfrog"
       
  1721 ! !
       
  1722 
       
  1723 !RBProgramNode methodsFor:'stx:libtool support'!
       
  1724 
       
  1725 middleClickMenuInCodeView: aCodeView 
       
  1726     ^ nil
       
  1727 
       
  1728     "Created: / 18-02-2008 / 17:49:57 / janfrog"
       
  1729 ! !
       
  1730 
       
  1731 !RBProgramNode methodsFor:'stx:libtool support'!
       
  1732 
       
  1733 rightClickMenuInCodeView: aCodeView 
       
  1734     ^ nil
       
  1735 
       
  1736     "Created: / 18-02-2008 / 17:50:10 / janfrog"
       
  1737 ! !
       
  1738 
       
  1739 !RBVariableNode methodsFor:'libtool3 support'!
       
  1740 
       
  1741 highlightInCodeView: aCodeView
       
  1742 
       
  1743     ^aCodeView highlightVariableNode: self
       
  1744 
       
  1745     "Created: / 18-02-2008 / 17:51:44 / janfrog"
       
  1746 ! !
       
  1747 
       
  1748 !RBVariableNode methodsFor:'libtool3 support'!
       
  1749 
       
  1750 leftClickMenuInCodeView: aCodeView 
       
  1751     ^ aCodeView leftClickMenuForVariableNode: self.
       
  1752 
       
  1753     "Created: / 01-09-2009 / 08:41:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  1754 ! !
       
  1755 
       
  1756 !RBVariableNode methodsFor:'libtool3 support'!
       
  1757 
       
  1758 rightClickMenuInCodeView: aCodeView 
       
  1759     ^ aCodeView rightClickMenuForVariableNode: self.
       
  1760 
       
  1761     "Created: / 18-02-2008 / 21:05:04 / janfrog"
       
  1762 ! !
       
  1763 
       
  1764 !RefactoryChange methodsFor:'performing-changes'!
       
  1765 
       
  1766 apply
       
  1767 
       
  1768     "Added for compatibility with stx's Change classes"
       
  1769 
       
  1770     ^RefactoryChangeManager performChange: self
       
  1771 
       
  1772     "Created: / 26-11-2008 / 11:26:54 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
  1773 ! !
       
  1774 
       
  1775 !RefactoryChange methodsFor:'accessing'!
       
  1776 
       
  1777 changeLanguage
       
  1778 
       
  1779     ^SmalltalkLanguage instance
       
  1780 
       
  1781     "Created: / 02-02-2010 / 10:54:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  1782 ! !
       
  1783 
       
  1784 !RefactoryChange methodsFor:'accessing'!
       
  1785 
       
  1786 delta
       
  1787 
       
  1788     "Returns a delta to current state as symbol:
       
  1789         #+ .....the subject is to be added to the image (new)
       
  1790         #- .....the subject is to be removed from the image (old)
       
  1791         #= .....the image is up to date
       
  1792         #~ .....change version and image version differ
       
  1793         #? .....delta is unknown or N/A for this kind of change
       
  1794     "
       
  1795 
       
  1796     ^#? "We don't know how to compute delta for generic change"
       
  1797 ! !
       
  1798 
       
  1799 !RefactoryChange methodsFor:'user interface'!
       
  1800 
       
  1801 inspect
       
  1802 
       
  1803     ^super inspect
       
  1804 
       
  1805    "
       
  1806         ^((CompositeRefactoryChange new)
       
  1807                 changes: (Array with: self);
       
  1808                 yourself) inspect
       
  1809 
       
  1810    "
       
  1811 ! !
       
  1812 
       
  1813 !RefactoryChange methodsFor:'user interface'!
       
  1814 
       
  1815 inspector2TabBrowser
       
  1816 
       
  1817     ^self newInspector2Tab
       
  1818         label: 'Changes';    
       
  1819         priority: 75;
       
  1820         application: (Tools::ChangeSetBrowser on: (ChangeSet with:self))
       
  1821 ! !
       
  1822 
       
  1823 !RefactoryChange methodsFor:'testing'!
       
  1824 
       
  1825 isClassChange
       
  1826 
       
  1827     ^false
       
  1828 ! !
       
  1829 
       
  1830 !RefactoryChange methodsFor:'testing'!
       
  1831 
       
  1832 isClassDefinitionChange
       
  1833 
       
  1834     ^false
       
  1835 
       
  1836     "Created: / 29-10-2010 / 13:34:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  1837 ! !
       
  1838 
       
  1839 !RefactoryChange methodsFor:'testing'!
       
  1840 
       
  1841 isComplexRefactoryChange
       
  1842     ^ false
       
  1843 
       
  1844     "Created: / 26-11-2008 / 11:56:03 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
  1845 ! !
       
  1846 
       
  1847 !RefactoryChange methodsFor:'testing'!
       
  1848 
       
  1849 isCompositeChange
       
  1850     ^ false
       
  1851 
       
  1852     "Created: / 26-11-2008 / 11:34:43 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
  1853 ! !
       
  1854 
       
  1855 !RefactoryChange methodsFor:'testing'!
       
  1856 
       
  1857 isCompositeRefactoryChange
       
  1858     ^ false
       
  1859 
       
  1860     "Created: / 26-11-2008 / 11:34:43 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
  1861 ! !
       
  1862 
       
  1863 !RefactoryChange methodsFor:'testing'!
       
  1864 
       
  1865 isMethodCodeChange
       
  1866 
       
  1867     ^false
       
  1868 ! !
       
  1869 
       
  1870 !RefactoryChange methodsFor:'accessing'!
       
  1871 
       
  1872 removed
       
  1873 
       
  1874     ^(self objectAttributeAt: #removed) ? false
       
  1875 
       
  1876     "Created: / 24-10-2009 / 21:10:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  1877 ! !
       
  1878 
       
  1879 !RefactoryChange methodsFor:'accessing'!
       
  1880 
       
  1881 removed: aBoolean
       
  1882 
       
  1883     ^self objectAttributeAt: #removed put: aBoolean
       
  1884 
       
  1885     "Created: / 24-10-2009 / 21:11:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  1886 ! !
       
  1887 
       
  1888 !RefactoryChange methodsFor:'accessing'!
       
  1889 
       
  1890 source
       
  1891 
       
  1892     
       
  1893     ^self printString
       
  1894 ! !
       
  1895 
       
  1896 !RunArray methodsFor:'user interface'!
   420 
  1897 
   421 inspectorClass
  1898 inspectorClass
   422     "Re-reimplemented so that we don't get an ordered collection inspector
  1899     "Re-reimplemented so that we don't get an ordered collection inspector
   423      which would get very confused when confronted with a runArray."
  1900      which would get very confused when confronted with a runArray."
   424 
  1901 
   425     ^ InspectorView
  1902     ^ InspectorView
   426 
  1903 
   427     "Modified: / 30.10.1997 / 14:28:20 / cg"
  1904     "Modified: / 30.10.1997 / 14:28:20 / cg"
   428 ! !
  1905 ! !
   429 
  1906 
       
  1907 !SelectionInListModelView methodsFor:'accessing'!
       
  1908 
       
  1909 textStartLeft
       
  1910     ^ textStartLeft
       
  1911 ! !
       
  1912 
       
  1913 !SelectionInListModelView methodsFor:'accessing'!
       
  1914 
       
  1915 textStartLeft:something
       
  1916     textStartLeft := something.
       
  1917 ! !
       
  1918 
   430 !Set methodsFor:'inspecting'!
  1919 !Set methodsFor:'inspecting'!
   431 
  1920 
   432 inspectorClass
  1921 inspectorClass
   433     "redefined to use SetInspector
  1922     "redefined to use SetInspector
   434      (instead of the default Inspector)."
  1923      (instead of the default Inspector)."
   435 
  1924 
   436     ^ SetInspectorView
  1925     ^ SetInspectorView
   437 ! !
  1926 ! !
   438 
  1927 
   439 !SharedPool class methodsFor:'inspecting'!
  1928 !SimpleView methodsFor:'queries'!
       
  1929 
       
  1930 isCodeView2
       
  1931 
       
  1932     ^ false
       
  1933 
       
  1934     "Created: / 20-07-2010 / 15:42:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  1935 ! !
       
  1936 
       
  1937 !Smalltalk class methodsFor:'inspecting'!
   440 
  1938 
   441 inspectorClass
  1939 inspectorClass
   442     "{ Pragma: +optSpace }"
  1940     "{ Pragma: +optSpace }"
   443 
  1941 
   444     "redefined to launch a DictionaryInspector (instead of the default Inspector)."
  1942     "redefined to launch a DictionaryInspector (instead of the default Inspector)."
   445 
  1943 
   446     ^ DictionaryInspectorView
  1944     ^ DictionaryInspectorView
   447 ! !
  1945 ! !
   448 
  1946 
   449 !Smalltalk class methodsFor:'inspecting'!
  1947 !StringCollection methodsFor:'debugging support'!
   450 
  1948 
   451 inspectorClass
  1949 inspector2TabText
   452     "{ Pragma: +optSpace }"
  1950 
   453 
  1951     ^self newInspector2Tab
   454     "redefined to launch a DictionaryInspector (instead of the default Inspector)."
  1952         label: 'String';
   455 
  1953         priority: 25;
   456     ^ DictionaryInspectorView
  1954         view: ((ScrollableView for:TextView) contents: self asString; yourself)
       
  1955 
       
  1956     "Created: / 17-02-2008 / 10:13:07 / janfrog"
       
  1957 ! !
       
  1958 
       
  1959 !Symbol methodsFor:'accessing'!
       
  1960 
       
  1961 formattedCode
       
  1962 
       
  1963     "Used by CodeGenerator"
       
  1964 
       
  1965     ^self
       
  1966 
       
  1967     "Created: / 07-07-2009 / 20:03:21 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
  1968 ! !
       
  1969 
       
  1970 !Text methodsFor:'debugging support'!
       
  1971 
       
  1972 inspector2TabText
       
  1973 
       
  1974     ^self newInspector2Tab
       
  1975         label: 'Text';
       
  1976         priority: 75;
       
  1977         view: ((ScrollableView for:TextView) contents: self; yourself)
       
  1978 
       
  1979     "Created: / 17-02-2008 / 09:03:36 / janfrog"
       
  1980     "Modified: / 17-02-2008 / 10:28:33 / janfrog"
   457 ! !
  1981 ! !
   458 
  1982 
   459 !Text methodsFor:'inspecting'!
  1983 !Text methodsFor:'inspecting'!
   460 
  1984 
   461 inspectorExtraAttributes
  1985 inspectorExtraAttributes
   493     "
  2017     "
   494 
  2018 
   495     "Created: / 20-01-2011 / 12:19:05 / cg"
  2019     "Created: / 20-01-2011 / 12:19:05 / cg"
   496 ! !
  2020 ! !
   497 
  2021 
       
  2022 !UserPreferences methodsFor:'accessing-prefs-browser'!
       
  2023 
       
  2024 alwaysOpenNewTabWhenCtrlClick
       
  2025 
       
  2026     "
       
  2027         UserPreferences current alwaysOpenNewTabWhenCtrlClick 
       
  2028     "
       
  2029 
       
  2030 
       
  2031     ^ self at:#alwaysOpenNewTabWhenCtrlClick ifAbsent:false.
       
  2032 
       
  2033     "Created: / 19-10-2008 / 08:00:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
  2034     "Modified: / 14-02-2010 / 19:37:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  2035 ! !
       
  2036 
       
  2037 !UserPreferences methodsFor:'accessing-prefs-browser'!
       
  2038 
       
  2039 alwaysOpenNewTabWhenCtrlClick: aBoolean
       
  2040 
       
  2041     self at:#alwaysOpenNewTabWhenCtrlClick put: aBoolean
       
  2042 
       
  2043     "Created: / 19-10-2008 / 08:01:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
  2044 ! !
       
  2045 
       
  2046 !UserPreferences methodsFor:'accessing-prefs-browser'!
       
  2047 
       
  2048 showBookmarkBar
       
  2049     "experimental."
       
  2050 
       
  2051     ^ self at:#showBookmarkBar ifAbsent: true.
       
  2052 
       
  2053     "
       
  2054      UserPreferences current showBookmarkBar
       
  2055      UserPreferences current showBookmarkBar:true
       
  2056      UserPreferences current showBookmarkBar:false
       
  2057     "
       
  2058 
       
  2059     "Created: / 18-05-2011 / 16:48:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  2060     "Modified: / 03-06-2011 / 11:01:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  2061 ! !
       
  2062 
       
  2063 !UserPreferences methodsFor:'accessing-prefs-browser'!
       
  2064 
       
  2065 showBookmarkBar: aBoolean
       
  2066     "experimental."
       
  2067 
       
  2068     ^ self at:#showBookmarkBar put: aBoolean
       
  2069 
       
  2070     "
       
  2071      UserPreferences current showBookmarkBar
       
  2072      UserPreferences current showBookmarkBar:true
       
  2073      UserPreferences current showBookmarkBar:false
       
  2074     "
       
  2075 
       
  2076     "Created: / 18-05-2011 / 17:28:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  2077 ! !
       
  2078 
       
  2079 !UserPreferences methodsFor:'accessing-prefs-browser'!
       
  2080 
       
  2081 showEmbeddedTestRunnerInBrowser
       
  2082     "experimental."
       
  2083 
       
  2084     ^ self at:#showEmbeddedTestRunnerInBrowser ifAbsent:false
       
  2085 
       
  2086     "
       
  2087      UserPreferences current showEmbeddedTestRunnerInBrowser
       
  2088      UserPreferences current showEmbeddedTestRunnerInBrowser:true
       
  2089      UserPreferences current showEmbeddedTestRunnerInBrowser:false
       
  2090     "
       
  2091 
       
  2092     "Created: / 11-03-2010 / 10:11:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  2093 ! !
       
  2094 
       
  2095 !UserPreferences methodsFor:'accessing-prefs-browser'!
       
  2096 
       
  2097 showEmbeddedTestRunnerInBrowser:aBoolean
       
  2098     "experimental."
       
  2099 
       
  2100     ^ self at:#showEmbeddedTestRunnerInBrowser put:aBoolean
       
  2101 
       
  2102     "
       
  2103      UserPreferences current showEmbeddedTestRunnerInBrowser:true
       
  2104      UserPreferences current showEmbeddedTestRunnerInBrowser:false
       
  2105     "
       
  2106 
       
  2107     "Created: / 11-03-2010 / 10:11:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  2108 ! !
       
  2109 
       
  2110 !UserPreferences methodsFor:'accessing-prefs-browser'!
       
  2111 
       
  2112 showMethodTemplate
       
  2113     "experimental."
       
  2114 
       
  2115     ^ self at:#showMethodTemplate ifAbsent:true
       
  2116 
       
  2117     "
       
  2118      UserPreferences current showMethodTemplate
       
  2119      UserPreferences current showMethodTemplate:true
       
  2120      UserPreferences current showMethodTemplate:false
       
  2121     "
       
  2122 
       
  2123     "Created: / 12-02-2010 / 12:06:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  2124 ! !
       
  2125 
       
  2126 !UserPreferences methodsFor:'accessing-prefs-browser'!
       
  2127 
       
  2128 showMethodTemplate:aBoolean
       
  2129     "experimental."
       
  2130 
       
  2131     ^ self at:#showMethodTemplate put:aBoolean
       
  2132 
       
  2133     "
       
  2134      UserPreferences current showMethodTemplate:true
       
  2135      UserPreferences current showMethodTemplate:false
       
  2136     "
       
  2137 
       
  2138     "Created: / 12-02-2010 / 12:05:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  2139 ! !
       
  2140 
       
  2141 !UserPreferences methodsFor:'accessing-prefs-browser'!
       
  2142 
       
  2143 useCodeView2InTools
       
  2144     ^self at:#useCodeView2InTools ifAbsent:false
       
  2145 
       
  2146     "
       
  2147      UserPreferences current useCodeView2InTools 
       
  2148      UserPreferences current useCodeView2InTools:true 
       
  2149      UserPreferences current useCodeView2InTools:false"
       
  2150 
       
  2151     "Created: / 12-02-2010 / 12:13:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  2152     "Modified: / 15-02-2010 / 09:26:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  2153 ! !
       
  2154 
       
  2155 !UserPreferences methodsFor:'accessing-prefs-browser'!
       
  2156 
       
  2157 useCodeView2InTools:aBoolean 
       
  2158     ^self at:#useCodeView2InTools put:aBoolean
       
  2159 
       
  2160     "
       
  2161      UserPreferences current useCodeView2InBrowser:true
       
  2162      UserPreferences current useCodeView2InBrowser:false"
       
  2163     "Created: / 12-02-2010 / 12:14:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  2164 ! !
       
  2165 
       
  2166 !UserPreferences methodsFor:'accessing-prefs-browser'!
       
  2167 
       
  2168 webBrowserLikeLayout
       
  2169     "experimental."
       
  2170 
       
  2171     ^ self at:#webBrowserLikeLayout ifAbsent: false
       
  2172 
       
  2173     "
       
  2174      UserPreferences current webBrowserLikeLayout
       
  2175      UserPreferences current webBrowserLikeLayout:true
       
  2176      UserPreferences current webBrowserLikeLayout:false
       
  2177     "
       
  2178 
       
  2179     "Created: / 07-06-2011 / 14:33:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  2180 ! !
       
  2181 
       
  2182 !UserPreferences methodsFor:'accessing-prefs-browser'!
       
  2183 
       
  2184 webBrowserLikeLayout: aBoolean
       
  2185     "experimental."
       
  2186 
       
  2187     ^ self at:#webBrowserLikeLayout put: aBoolean
       
  2188 
       
  2189     "
       
  2190      UserPreferences current webBrowserLikeLayout
       
  2191      UserPreferences current webBrowserLikeLayout:true
       
  2192      UserPreferences current webBrowserLikeLayout:false
       
  2193     "
       
  2194 
       
  2195     "Created: / 07-06-2011 / 14:31:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
  2196 ! !
       
  2197 
   498 !stx_libtool class methodsFor:'documentation'!
  2198 !stx_libtool class methodsFor:'documentation'!
   499 
  2199 
   500 extensionsVersion_CVS
  2200 extensionsVersion_CVS
   501     ^ '$Header: /cvs/stx/stx/libtool/extensions.st,v 1.30 2011-01-20 11:24:55 cg Exp $'
  2201     ^ '$Header: /cvs/stx/stx/libtool/extensions.st,v 1.31 2011-07-03 14:27:26 cg Exp $'
   502 ! !
  2202 ! !