The Trunk: Tools-topa.555.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Tools-topa.555.mcz

commits-2
Tobias Pape uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-topa.555.mcz

==================== Summary ====================

Name: Tools-topa.555
Author: topa
Time: 18 March 2015, 10:33:54.342 am
UUID: 1abeab8b-ed1d-4a14-aaee-8f0c6e25a28d
Ancestors: Tools-topa.554

Move methods from Kernel to Tools/Morphic for basic Models (1/3)

Load this first

=============== Diff against Tools-topa.554 ===============

Item was added:
+ ----- Method: Model>>arrowKey:from: (in category '*Tools-keyboard') -----
+ arrowKey: aChar from: view
+ "backstop; all the PluggableList* classes actually handle arrow keys, and the models handle other keys."
+ ^false!

Item was added:
+ ----- Method: Model>>perform:orSendTo: (in category '*Tools-menus') -----
+ perform: selector orSendTo: otherTarget
+ "Selector was just chosen from a menu by a user.  If can respond, then perform it on myself.  If not, send it to otherTarget, presumably the editPane from which the menu was invoked."
+
+ "default is that the editor does all"
+ ^ otherTarget perform: selector.!

Item was added:
+ ----- Method: Model>>selectedClass (in category '*Tools') -----
+ selectedClass
+ "All owners of TextViews are asked this during a doIt"
+ ^ nil!

Item was added:
+ ----- Method: Model>>trash (in category '*Tools-menus') -----
+ trash
+ "What should be displayed if a trash pane is restored to initial state"
+
+ ^ ''!

Item was added:
+ ----- Method: Model>>trash: (in category '*Tools-menus') -----
+ trash: ignored
+ "Whatever the user submits to the trash, it need not be saved."
+
+ ^ true!

Item was changed:
+ ----- Method: SelectorBrowser>>buildClassListWith: (in category 'toolbuilder') -----
- ----- Method: SelectorBrowser>>buildClassListWith: (in category 'as yet unclassified') -----
  buildClassListWith: builder
  | listSpec |
  listSpec := builder pluggableListSpec new.
  listSpec
  model: self;
  list: #classList;
  getIndex: #classListIndex;
  setIndex: #classListIndex:;
  keyPress: #arrowKey:from:.
  ^listSpec
  !

Item was changed:
+ ----- Method: SelectorBrowser>>buildEditViewWith: (in category 'toolbuilder') -----
- ----- Method: SelectorBrowser>>buildEditViewWith: (in category 'as yet unclassified') -----
  buildEditViewWith: builder
  | textSpec |
  textSpec := builder pluggableInputFieldSpec new.
  textSpec
  model: self;
  getText: #contents;
  setText: #contents:notifying:;
  selection: #contentsSelection;
  menu: #codePaneMenu:shifted:.
  ^textSpec!

Item was changed:
+ ----- Method: SelectorBrowser>>buildExamplePaneWith: (in category 'toolbuilder') -----
- ----- Method: SelectorBrowser>>buildExamplePaneWith: (in category 'as yet unclassified') -----
  buildExamplePaneWith: builder
  | textSpec |
  textSpec := builder pluggableTextSpec new.
  textSpec
  model: self;
  getText: #byExample;
  setText: #byExample:;
  selection: #contentsSelection;
  menu: #codePaneMenu:shifted:.
  ^textSpec!

Item was changed:
+ ----- Method: SelectorBrowser>>buildMessageListWith: (in category 'toolbuilder') -----
- ----- Method: SelectorBrowser>>buildMessageListWith: (in category 'as yet unclassified') -----
  buildMessageListWith: builder
  | listSpec |
  listSpec := builder pluggableListSpec new.
  listSpec
  model: self;
  list: #messageList;
  getIndex: #messageListIndex;
  setIndex: #messageListIndex:;
  menu: #selectorMenu:;
  keyPress: #messageListKey:from:.
  ^listSpec
  !

Item was changed:
+ ----- Method: SelectorBrowser>>buildWith: (in category 'toolbuilder') -----
- ----- Method: SelectorBrowser>>buildWith: (in category 'as yet unclassified') -----
  buildWith: builder
  "Create a Browser that lets you type part of a selector, shows a list of selectors, shows the classes of the one you chose, and spawns a full browser on it.  Answer the window
  SelectorBrowser new open "
  | windowSpec |
  selectorIndex := classListIndex := 0.
  windowSpec := self buildWindowWith: builder specs: {
  (0@0 corner: 0.5@0.14) -> [self buildEditViewWith: builder].
  (0@0.14 corner: 0.5@0.6) -> [self buildMessageListWith: builder].
  (0.5@0 corner: 1@0.6) -> [self buildClassListWith: builder].
  (0@0.6 corner: 1@1) -> [self buildExamplePaneWith: builder].
  }.
  ^builder build: windowSpec!

Item was changed:
+ ----- Method: SelectorBrowser>>byExample (in category 'example pane') -----
- ----- Method: SelectorBrowser>>byExample (in category 'as yet unclassified') -----
  byExample
  "The comment in the bottom pane"
 
  false ifTrue: [MethodFinder methodFor: #( (4 3) 7  (0 5) 5  (5 5) 10)].
  "to keep the method methodFor: from being removed from the system"
 
  ^ 'Type a fragment of a selector in the top pane.  Accept it.
 
  Or, use an example to find a method in the system.  Type receiver, args, and answer in the top pane with periods between the items.  3. 4. 7
 
  Or, in this pane, use examples to find a method in the system.  Select the line of code and choose "print it".  
 
  MethodFinder methodFor: #( (4 3) 7  (0 5) 5  (5 5) 10).
  This will discover (data1 + data2).
 
  You supply inputs and answers and the system will find the method.  Each inner array is a list of inputs.  It contains the receiver and zero or more arguments.  For Booleans and any computed arguments, use brace notation.
 
  MethodFinder methodFor: { {1. 3}. true.  {20. 10}. false}.
  This will discover the expressions (data1 < data2), (data2 > data1), and many others.
 
  MethodFinder methodFor: { {''29 Apr 1999'' asDate}. ''Thursday''.  
  {''30 Apr 1999'' asDate}. ''Friday'' }.
  This will discover the expression (data1 weekday)
 
  Receiver and arguments do not have to be in the right order.
  See MethodFinder.verify for more examples.'!

Item was changed:
+ ----- Method: SelectorBrowser>>byExample: (in category 'example pane') -----
- ----- Method: SelectorBrowser>>byExample: (in category 'as yet unclassified') -----
  byExample: newText
  "Don't save it"
  ^ true!

Item was changed:
+ ----- Method: SelectorBrowser>>classList (in category 'class list') -----
- ----- Method: SelectorBrowser>>classList (in category 'as yet unclassified') -----
  classList
  ^ classList!

Item was changed:
+ ----- Method: SelectorBrowser>>classListIndex (in category 'class list') -----
- ----- Method: SelectorBrowser>>classListIndex (in category 'as yet unclassified') -----
  classListIndex
  ^ classListIndex!

Item was changed:
+ ----- Method: SelectorBrowser>>classListIndex: (in category 'class list') -----
- ----- Method: SelectorBrowser>>classListIndex: (in category 'as yet unclassified') -----
  classListIndex: anInteger
 
  classListIndex := anInteger.
  classListIndex > 0 ifTrue:
  [self changed: #startNewBrowser. "MVC view will terminate control to prepare for new browser"
  Browser fullOnClass: self selectedClass selector: self selectedMessageName.
  "classListIndex := 0"]
  !

Item was changed:
+ ----- Method: SelectorBrowser>>classListSelectorTitle (in category 'class list') -----
- ----- Method: SelectorBrowser>>classListSelectorTitle (in category 'as yet unclassified') -----
  classListSelectorTitle
  ^ 'Class List Menu'!

Item was changed:
+ ----- Method: SelectorBrowser>>contents:notifying: (in category 'example pane') -----
- ----- Method: SelectorBrowser>>contents:notifying: (in category 'as yet unclassified') -----
  contents: aString notifying: aController
  "Take what the user typed and find all selectors containing it"
 
  | tokens |
  contents := aString.
  classList := #().  classListIndex := 0.
  selectorIndex := 0.
  tokens := contents asString findTokens: ' .'.
  selectorList := Cursor wait showWhile: [
  tokens size = 1
  ifTrue: [(Symbol selectorsContaining: contents asString) asArray
  sort: [:x :y | x asLowercase <= y asLowercase]]
  ifFalse: [self quickList]]. "find selectors from a single example of data"
  self changed: #messageList.
  self changed: #classList.
  ^ true!

Item was changed:
+ ----- Method: SelectorBrowser>>implementors (in category 'selector functions') -----
- ----- Method: SelectorBrowser>>implementors (in category 'as yet unclassified') -----
  implementors
  | aSelector |
  (aSelector := self selectedMessageName) ifNotNil:
  [self systemNavigation browseAllImplementorsOf: aSelector]!

Item was changed:
+ ----- Method: SelectorBrowser>>initialExtent (in category 'message list') -----
- ----- Method: SelectorBrowser>>initialExtent (in category 'as yet unclassified') -----
  initialExtent
 
  ^ 350@250
  !

Item was changed:
+ ----- Method: SelectorBrowser>>listFromResult: (in category 'selector finding') -----
- ----- Method: SelectorBrowser>>listFromResult: (in category 'as yet unclassified') -----
  listFromResult: resultOC
  "ResultOC is of the form #('(data1 op data2)' '(...)'). Answer a sorted array."
 
  (resultOC first beginsWith: 'no single method') ifTrue: [^ #()].
  ^ resultOC sortBy: [:a :b |
  (a copyFrom: 6 to: a size) < (b copyFrom: 6 to: b size)].
 
  !

Item was changed:
+ ----- Method: SelectorBrowser>>markMatchingClasses (in category 'message list') -----
- ----- Method: SelectorBrowser>>markMatchingClasses (in category 'as yet unclassified') -----
  markMatchingClasses
  "If an example is used, mark classes matching the example instance with an asterisk."
 
  | unmarkedClassList firstPartOfSelector receiverString receiver |
 
  self flag: #mref. "allows for old-fashioned style"
 
  "Only 'example' queries can be marked."
  (contents asString includes: $.) ifFalse: [^ self].
 
  unmarkedClassList := classList copy.
 
  "Get the receiver object of the selected statement in the message list."
  firstPartOfSelector := (Scanner new scanTokens: (selectorList at: selectorIndex)) second.
  receiverString := (ReadStream on: (selectorList at: selectorIndex))
  upToAll: firstPartOfSelector.
  receiver := Compiler evaluate: receiverString.
 
  unmarkedClassList do: [ :classAndMethod | | class |
  (classAndMethod isKindOf: MethodReference) ifTrue: [
  (receiver isKindOf: classAndMethod actualClass) ifTrue: [
  classAndMethod stringVersion: '*', classAndMethod stringVersionDefault.
  ]
  ] ifFalse: [
  class := Compiler evaluate:
  ((ReadStream on: classAndMethod) upToAll: firstPartOfSelector).
  (receiver isKindOf: class) ifTrue: [
  classList add: '*', classAndMethod.
  classList remove: classAndMethod
  ]
  ].
  ].
  !

Item was changed:
+ ----- Method: SelectorBrowser>>messageList (in category 'message list') -----
- ----- Method: SelectorBrowser>>messageList (in category 'as yet unclassified') -----
  messageList
  "Find all the selectors containing what the user typed in."
 
  ^ selectorList!

Item was changed:
+ ----- Method: SelectorBrowser>>messageListIndex (in category 'message list') -----
- ----- Method: SelectorBrowser>>messageListIndex (in category 'as yet unclassified') -----
  messageListIndex
  "Answer the index of the selected message selector."
 
  ^ selectorIndex!

Item was changed:
+ ----- Method: SelectorBrowser>>messageListIndex: (in category 'message list') -----
- ----- Method: SelectorBrowser>>messageListIndex: (in category 'as yet unclassified') -----
  messageListIndex: anInteger
  "Set the selected message selector to be the one indexed by anInteger.
  Find all classes it is in."
  selectorIndex := anInteger.
  selectorIndex = 0
  ifTrue: [^ self].
  classList := self systemNavigation allImplementorsOf: self selectedMessageName.
  self markMatchingClasses.
  classListIndex := 0.
  self changed: #messageListIndex.
  "update my selection"
  self changed: #classList!

Item was changed:
+ ----- Method: SelectorBrowser>>messageListKey:from: (in category 'message list') -----
- ----- Method: SelectorBrowser>>messageListKey:from: (in category 'as yet unclassified') -----
  messageListKey: aChar from: view
  "Respond to a command key. Handle (m) and (n) here,
  else defer to the StringHolder behaviour."
 
  aChar == $m ifTrue: [^ self implementors].
  aChar == $n ifTrue: [^ self senders].
  super messageListKey: aChar from: view
  !

Item was changed:
+ ----- Method: SelectorBrowser>>open (in category 'toolbuilder') -----
- ----- Method: SelectorBrowser>>open (in category 'as yet unclassified') -----
  open
  "Create a Browser that lets you type part of a selector, shows a list of selectors,
  shows the classes of the one you chose, and spwns a full browser on it.
  SelectorBrowser new open
  "
  ^ToolBuilder open: self!

Item was changed:
+ ----- Method: SelectorBrowser>>quickList (in category 'selector finding') -----
- ----- Method: SelectorBrowser>>quickList (in category 'as yet unclassified') -----
  quickList
  "Compute the selectors for the single example of receiver and args, in the very top pane"
 
  | data result resultArray dataStrings mf dataObjects aa statements |
  data := contents asString withBlanksTrimmed.
  mf := MethodFinder new.
  data := mf cleanInputs: data. "remove common mistakes"
  dataObjects := Compiler evaluate: '{', data, '}'. "#( data1 data2 result )"
  statements := (Compiler new parse: 'zort ' , data in: Object notifying: nil)
  body statements select: [:each | (each isKindOf: ReturnNode) not].
    dataStrings := statements collect:
  [:node | String streamContents:
  [:strm | (node isMessage) ifTrue: [strm nextPut: $(].
  node shortPrintOn: strm.
  (node isMessage) ifTrue: [strm nextPut: $)].]].
  dataObjects size < 2 ifTrue: [self inform: 'If you are giving an example of receiver, \args, and result, please put periods between the parts.\Otherwise just type one selector fragment' withCRs. ^#()].
    dataObjects := Array with: dataObjects allButLast with: dataObjects last. "#( (data1
    data2) result )"
  result := mf load: dataObjects; findMessage.
  (result first beginsWith: 'no single method') ifFalse: [
  aa := self testObjects: dataObjects strings: dataStrings.
  dataObjects := aa second.  dataStrings := aa third].
  resultArray := self listFromResult: result.
  resultArray isEmpty ifTrue: [self inform: result first].
 
  dataStrings size = (dataObjects first size + 1) ifTrue:
  [resultArray := resultArray collect: [:expression | | newExp |
  newExp := expression.
  dataObjects first withIndexDo: [:lit :i |
  newExp := newExp copyReplaceAll: 'data', i printString
  with: (dataStrings at: i)].
  newExp, ' --> ', dataStrings last]].
 
    ^ resultArray!

Item was changed:
+ ----- Method: SelectorBrowser>>searchResult: (in category 'example pane') -----
- ----- Method: SelectorBrowser>>searchResult: (in category 'as yet unclassified') -----
  searchResult: anExternalSearchResult
 
  self contents: ''.
  classList := #(). classListIndex := 0.
  selectorIndex := 0.
  selectorList := self listFromResult: anExternalSearchResult.
    self changed: #messageList.
  self changed: #classList.
  self changed: #contents
  !

Item was changed:
+ ----- Method: SelectorBrowser>>selectedClass (in category 'class list') -----
- ----- Method: SelectorBrowser>>selectedClass (in category 'as yet unclassified') -----
  selectedClass
  "Answer the currently selected class."
 
  | pairString |
 
  self flag: #mref. "allows for old-fashioned style"
 
  classListIndex = 0 ifTrue: [^nil].
  pairString := classList at: classListIndex.
  (pairString isKindOf: MethodReference) ifTrue: [
  ^pairString actualClass
  ].
  (pairString includes: $*) ifTrue: [pairString := pairString allButFirst].
  MessageSet
  parse: pairString
  toClassAndSelector: [:cls :sel | ^ cls].!

Item was changed:
+ ----- Method: SelectorBrowser>>selectedClassName (in category 'accessing') -----
- ----- Method: SelectorBrowser>>selectedClassName (in category 'as yet unclassified') -----
  selectedClassName
  "Answer the name of the currently selected class."
 
  classListIndex = 0 ifTrue: [^nil].
  ^ self selectedClass name!

Item was changed:
+ ----- Method: SelectorBrowser>>selectedMessageName (in category 'accessing') -----
- ----- Method: SelectorBrowser>>selectedMessageName (in category 'as yet unclassified') -----
  selectedMessageName
  "Answer the name of the currently selected message."
 
  | example tokens |
  selectorIndex = 0 ifTrue: [^nil].
  example := selectorList at: selectorIndex.
  tokens := Scanner new scanTokens: example.
  tokens size = 1 ifTrue: [^ tokens first].
  tokens first == #'^' ifTrue: [^ nil].
  (tokens second includes: $:) ifTrue: [^ example findSelector].
  Symbol hasInterned: tokens second ifTrue: [:aSymbol | ^ aSymbol].
  ^ nil!

Item was changed:
+ ----- Method: SelectorBrowser>>selectorList: (in category 'selector list') -----
- ----- Method: SelectorBrowser>>selectorList: (in category 'as yet unclassified') -----
  selectorList: anExternalList
 
  self contents: ''.
  classList := #(). classListIndex := 0.
  selectorIndex := 0.
  selectorList := anExternalList.
  self changed: #messageList.
  self changed: #classList.
  self changed: #contents
 
  !

Item was changed:
+ ----- Method: SelectorBrowser>>selectorMenu: (in category 'selector list') -----
- ----- Method: SelectorBrowser>>selectorMenu: (in category 'as yet unclassified') -----
  selectorMenu: aMenu
  ^ aMenu labels:
  'senders (n)
  implementors (m)
  copy selector to clipboard'
  lines: #()
  selections: #(senders implementors copyName)!

Item was changed:
+ ----- Method: SelectorBrowser>>selectorMenuTitle (in category 'selector list') -----
- ----- Method: SelectorBrowser>>selectorMenuTitle (in category 'as yet unclassified') -----
  selectorMenuTitle
  ^ self selectedMessageName ifNil: ['<no selection>']!

Item was changed:
+ ----- Method: SelectorBrowser>>senders (in category 'selector functions') -----
- ----- Method: SelectorBrowser>>senders (in category 'as yet unclassified') -----
  senders
  | aSelector |
  (aSelector := self selectedMessageName) ifNotNil:
  [self systemNavigation browseAllCallsOn: aSelector]!

Item was changed:
+ ----- Method: SelectorBrowser>>testObjects:strings: (in category 'selector finding') -----
- ----- Method: SelectorBrowser>>testObjects:strings: (in category 'as yet unclassified') -----
  testObjects: dataObjects strings: dataStrings
  | dataObjs dataStrs selectors classes didUnmodifiedAnswer |
  "Try to make substitutions in the user's inputs and search for the selector again.
  1 no change to answer.
  2 answer Array -> OrderedCollection.
  2 answer Character -> String
  4 answer Symbol or String of len 1 -> Character
  For each of these, try straight, and try converting args:
  Character -> String
  Symbol or String of len 1 -> Character
  Return array with result, dataObjects, dataStrings.  Don't ever do a find on the same set of data twice."
 
  dataObjs := dataObjects.  dataStrs := dataStrings.
  selectors := {#asString. #first. #asOrderedCollection}.
  classes := {Character. String. Array}.
  didUnmodifiedAnswer := false.
  selectors withIndexDo: [:ansSel :ansInd | | ds do result answerMod | "Modify the answer object"
  answerMod := false.
  do := dataObjs copyTwoLevel.  ds := dataStrs copy.
  (dataObjs last isKindOf: (classes at: ansInd)) ifTrue: [
  ((ansSel ~~ #first) or: [dataObjs last size = 1]) ifTrue: [
  do at: do size put: (do last perform: ansSel). "asString"
  ds at: ds size put: ds last, ' ', ansSel.
  result := MethodFinder new load: do; findMessage.
  (result first beginsWith: 'no single method') ifFalse: [
  "found a selector!!"
  ^ Array with: result first with: do with: ds].
  answerMod := true]].
 
  selectors allButLast withIndexDo: [:argSel :argInd | | ddo dds | "Modify an argument object"
  "for args, no reason to do Array -> OrderedCollection.  Identical protocol."
  didUnmodifiedAnswer not | answerMod ifTrue: [
  ddo := do copyTwoLevel.  dds := ds copy.
  dataObjs first withIndexDo: [:arg :ind |
  (arg isKindOf: (classes at: argInd))  ifTrue: [
  ((argSel ~~ #first) or: [arg size = 1]) ifTrue: [
  ddo first at: ind put: ((ddo first at: ind) perform: argSel). "asString"
  dds at: ind put: (dds at: ind), ' ', argSel.
  result := MethodFinder new load: ddo; findMessage.
  (result first beginsWith: 'no single method') ifFalse: [
  "found a selector!!"
  ^ Array with: result first with: ddo with: dds] .
  didUnmodifiedAnswer not & answerMod not ifTrue: [
  didUnmodifiedAnswer := true].
  ]]]]].
  ].
  ^ Array with: 'no single method does that function' with: dataObjs with: dataStrs!

Item was added:
+ ----- Method: StringHolder class>>codePaneMenu:shifted: (in category '*Tools-yellow button menu') -----
+ codePaneMenu: aMenu shifted: shifted
+ "Utility method for the 'standard' codePane menu"
+ aMenu addList: (shifted
+ ifTrue:[self shiftedYellowButtonMenuItems]
+ ifFalse:[self yellowButtonMenuItems]).
+ ^aMenu!

Item was added:
+ ----- Method: StringHolder class>>shiftedYellowButtonMenuItems (in category '*Tools-yellow button menu') -----
+ shiftedYellowButtonMenuItems
+ "Returns the standard yellow button menu items"
+ | entries |
+ entries := OrderedCollection withAll:
+ {
+ {'explain' translated. #explain}.
+ {'pretty print' translated. #prettyPrint}.
+ {'pretty print with color' translated. #prettyPrintWithColor}.
+ {'file it in (G)' translated. #fileItIn}.
+ {'spawn (o)' translated. #spawn}.
+ #-.
+ {'browse it (b)' translated. #browseIt}.
+ {'senders of it (n)' translated. #sendersOfIt}.
+ {'implementors of it (m)' translated. #implementorsOfIt}.
+ {'references to it (N)' translated. #referencesToIt}.
+ #-.
+ {'selectors containing it (W)' translated. #methodNamesContainingIt}.
+ {'method strings with it (E)' translated. #methodStringsContainingit}.
+ {'method source with it' translated. #methodSourceContainingIt}.
+ {'class names containing it' translated. #classNamesContainingIt}.
+ {'class comments with it' translated. #classCommentsContainingIt}.
+ {'change sets with it' translated. #browseChangeSetsWithSelector}.
+ #-.
+ {'save contents to file...' translated. #saveContentsInFile}.
+ {'send contents to printer' translated. #sendContentsToPrinter}.
+ {'printer setup' translated. #printerSetup}.
+ #-.
+ }.
+ Smalltalk isMorphic ifFalse: [ entries add:
+ {'special menu...' translated. #presentSpecialMenu}.].
+ entries add:
+ {'more...' translated. #yellowButtonActivity}.
+ ^ entries!

Item was added:
+ ----- Method: StringHolder class>>yellowButtonMenuItems (in category '*Tools-yellow button menu') -----
+ yellowButtonMenuItems
+ "Returns the standard yellow button menu items"
+ ^{
+ {'set font... (k)' translated. #offerFontMenu}.
+ {'set style... (K)' translated. #changeStyle}.
+ {'set alignment... (u)' translated. #chooseAlignment}.
+ #-.
+ {'make project link (P)' translated. #makeProjectLink}.
+ #-.
+ {'find...(f)' translated. #find}.
+ {'find again (g)' translated. #findAgain}.
+ {'set search string (h)' translated. #setSearchString}.
+ #-.
+ {'do again (j)' translated. #again}.
+ {'undo (z)' translated. #undo}.
+ #-.
+ {'copy (c)' translated. #copySelection}.
+ {'cut (x)' translated. #cut}.
+ {'paste (v)' translated. #paste}.
+ {'paste...' translated. #pasteRecent}.
+ #-.
+ {'do it (d)' translated. #doIt}.    
+ {'print it (p)' translated. #printIt}.    
+ {'inspect it (i)' translated. #inspectIt}.    
+ {'explore it (I)' translated. #exploreIt}.    
+ {'debug it' translated. #debugIt}.    
+ {'button for it' translated. #buttonForIt}.    
+ {'tally it' translated. #tallyIt}.
+ #-.
+ {'accept (s)' translated. #accept}.
+ {'cancel (l)' translated. #cancel}.
+ #-.
+ {'show bytecodes' translated. #showBytecodes}.
+ #-.
+ {'copy html' translated. #copyHtml}.
+ #-.
+ {'more...' translated. #shiftedTextPaneMenuRequest}.
+ }!

Item was added:
+ ----- Method: StringHolder>>codePaneMenu:shifted: (in category '*Tools-code pane menu') -----
+ codePaneMenu: aMenu shifted: shifted
+ "Fill in the given menu with additional items. The menu is prepoulated with the 'standard' text commands that the editor supports. Note that unless we override perform:orSendTo:, the editor will respond to all menu items in a text pane"
+ ^self class codePaneMenu: aMenu shifted: shifted!

Item was added:
+ ----- Method: StringHolder>>contents:notifying: (in category '*Tools-code pane menu') -----
+ contents: aString notifying: aController
+ "Accept text"
+ ^self acceptContents: aString!

Item was added:
+ ----- Method: StringHolder>>menuHook:named:shifted: (in category '*Tools-code pane menu') -----
+ menuHook: aMenu named: aSymbol shifted: aBool
+ "Provide a hook for supplemental menu items.  Answer the appropriately-enhanced menu."
+ ^ aMenu!

Item was added:
+ ----- Method: StringHolder>>perform:orSendTo: (in category '*Tools-code pane menu') -----
+ perform: selector orSendTo: otherTarget
+ "Selector was just chosen from a menu by a user.  If can respond, then
+ perform it on myself. If not, send it to otherTarget, presumably the
+ editPane from which the menu was invoked."
+
+ (self respondsTo: selector)
+ ifTrue: [^ self perform: selector]
+ ifFalse: [^ otherTarget perform: selector]!

Item was added:
+ ----- Method: StringHolder>>showBytecodes (in category '*Tools-code pane menu') -----
+ showBytecodes
+ "We don't know how to do this"
+
+ ^ self changed: #flash!

Item was added:
+ ----- Method: StringHolder>>wantsAnnotationPane (in category '*Tools-optional panes') -----
+ wantsAnnotationPane
+ "Answer whether the receiver, seen in some browser window, would like to have the so-called  annotationpane included.  By default, various browsers defer to the global preference 'optionalButtons' -- but individual subclasses can insist to the contrary."
+
+ ^ Preferences annotationPanes!

Item was added:
+ ----- Method: StringHolder>>wantsOptionalButtons (in category '*Tools-optional panes') -----
+ wantsOptionalButtons
+ "Answer whether the receiver, seen in some browser window, would like to have the so-called optional button pane included.  By default, various browsers defer to the global preference 'optionalButtons' -- but individual subclasses can insist to the contrary."
+
+ ^ Preferences optionalButtons!