The Trunk: Tools-pre.839.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-pre.839.mcz

commits-2
Patrick Rein uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-pre.839.mcz

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

Name: Tools-pre.839
Author: pre
Time: 20 December 2018, 4:11:49.123699 pm
UUID: 0f67ed36-954c-497e-83b4-9d41bd164416
Ancestors: Tools-eem.838

Categorizes uncategorized methods in Tools and moves one method to a Deprecated package

=============== Diff against Tools-eem.838 ===============

Item was changed:
+ ----- Method: BasicInspector>>inspect: (in category 'initialize-release') -----
- ----- Method: BasicInspector>>inspect: (in category 'as yet unclassified') -----
  inspect: anObject
  "Initialize the receiver so that it is inspecting anObject. There is no
  current selection."
 
  self initialize.
  object := anObject.
  selectionIndex := 0.
  contents := ''!

Item was changed:
  ----- Method: Browser>>aboutToStyle: (in category 'code pane') -----
  aboutToStyle: aStyler
  "This is a notification that aStyler is about to re-style its text.
  Set the classOrMetaClass in aStyler, so that identifiers
  will be resolved correctly.
  Answer true to allow styling to proceed, or false to veto the styling"
  | type |
 
  self isModeStyleable ifFalse: [^false].
  type := self editSelection.
  (#(newMessage editMessage editClass newClass) includes: type) ifFalse:[^false].
  aStyler classOrMetaClass: ((type = #editClass or: [type = #newClass]) ifFalse:[self selectedClassOrMetaClass]).
  ^true!

Item was changed:
  ----- Method: Browser>>classListMenu:shifted: (in category 'class functions') -----
  classListMenu: aMenu shifted: shifted
  "Set up the menu to apply to the receiver's class list, honoring the #shifted boolean"
  ^ self menu: aMenu for: #(classListMenu classListMenuShifted:) shifted: shifted.
  !

Item was changed:
  ----- Method: Browser>>fileOutClass (in category 'class functions') -----
  fileOutClass
  "Print a description of the selected class onto a file whose name is the
  category name followed by .st."
 
+ Cursor write showWhile:
- Cursor write showWhile:
  [self hasClassSelected ifTrue: [self selectedClass fileOut]]!

Item was changed:
+ ----- Method: CPUWatcher class>>current (in category 'singleton') -----
- ----- Method: CPUWatcher class>>current (in category 'as yet unclassified') -----
  current
  ^CurrentCPUWatcher
  !

Item was changed:
+ ----- Method: CPUWatcher class>>currentWatcherProcess (in category 'accessing') -----
- ----- Method: CPUWatcher class>>currentWatcherProcess (in category 'as yet unclassified') -----
  currentWatcherProcess
  ^CurrentCPUWatcher ifNotNil: [ CurrentCPUWatcher watcherProcess ]
  !

Item was changed:
+ ----- Method: CPUWatcher class>>dumpTallyOnTranscript (in category 'monitoring') -----
- ----- Method: CPUWatcher class>>dumpTallyOnTranscript (in category 'as yet unclassified') -----
  dumpTallyOnTranscript
  self current ifNotNil: [
  ProcessBrowser dumpTallyOnTranscript: self current tally
  ]!

Item was changed:
+ ----- Method: CPUWatcher class>>initialize (in category 'class initialization') -----
- ----- Method: CPUWatcher class>>initialize (in category 'as yet unclassified') -----
  initialize
  "CPUWatcher initialize"
  Smalltalk addToStartUpList: self.
  Smalltalk addToShutDownList: self.!

Item was changed:
+ ----- Method: CPUWatcher class>>isMonitoring (in category 'monitoring') -----
- ----- Method: CPUWatcher class>>isMonitoring (in category 'as yet unclassified') -----
  isMonitoring
 
  ^CurrentCPUWatcher notNil and: [ CurrentCPUWatcher isMonitoring ]
  !

Item was changed:
+ ----- Method: CPUWatcher class>>monitorPreferenceChanged (in category 'preferences') -----
- ----- Method: CPUWatcher class>>monitorPreferenceChanged (in category 'as yet unclassified') -----
  monitorPreferenceChanged
  self cpuWatcherEnabled
  ifTrue: [ self startMonitoring ]
  ifFalse: [ self stopMonitoring ]!

Item was changed:
+ ----- Method: CPUWatcher class>>shutDown (in category 'system startup') -----
- ----- Method: CPUWatcher class>>shutDown (in category 'as yet unclassified') -----
  shutDown
  self stopMonitoring.!

Item was changed:
+ ----- Method: CPUWatcher class>>startMonitoring (in category 'monitoring') -----
- ----- Method: CPUWatcher class>>startMonitoring (in category 'as yet unclassified') -----
  startMonitoring
  "CPUWatcher startMonitoring"
 
  ^self startMonitoringPeriod: 20 rate: 100 threshold: 0.8!

Item was changed:
+ ----- Method: CPUWatcher class>>startMonitoringPeriod:rate:threshold: (in category 'monitoring') -----
- ----- Method: CPUWatcher class>>startMonitoringPeriod:rate:threshold: (in category 'as yet unclassified') -----
  startMonitoringPeriod: pd rate: rt threshold: th
  "CPUWatcher startMonitoring"
 
  CurrentCPUWatcher ifNotNil: [ ^CurrentCPUWatcher startMonitoring. ].
  CurrentCPUWatcher := (self new)
  monitorProcessPeriod: pd sampleRate: rt;
  threshold: th;
  yourself.
  ^CurrentCPUWatcher
  !

Item was changed:
+ ----- Method: CPUWatcher class>>startUp (in category 'system startup') -----
- ----- Method: CPUWatcher class>>startUp (in category 'as yet unclassified') -----
  startUp
  self monitorPreferenceChanged.!

Item was changed:
+ ----- Method: CPUWatcher class>>stopMonitoring (in category 'monitoring') -----
- ----- Method: CPUWatcher class>>stopMonitoring (in category 'as yet unclassified') -----
  stopMonitoring
  "CPUWatcher stopMonitoring"
 
  CurrentCPUWatcher ifNotNil: [ CurrentCPUWatcher stopMonitoring. ].
  CurrentCPUWatcher := nil.
  !

Item was changed:
+ ----- Method: ChangedMessageSet class>>openFor: (in category 'opening') -----
- ----- Method: ChangedMessageSet class>>openFor: (in category 'as yet unclassified') -----
  openFor: aChangeSet
  "Open up a ChangedMessageSet browser on the given change set; this is a conventional message-list browser whose message-list consists of all the methods in aChangeSet.  After any method submission, the message list is refigured, making it plausibly dynamic"
 
  | messageSet |
 
  messageSet := aChangeSet changedMessageListAugmented select: [ :each | each isValid].
  self
  openMessageList: messageSet
  name: 'Methods in Change Set ', aChangeSet name
  autoSelect: nil
  changeSet: aChangeSet!

Item was changed:
+ ----- Method: ChangedMessageSet class>>openMessageList:name:autoSelect:changeSet: (in category 'opening') -----
- ----- Method: ChangedMessageSet class>>openMessageList:name:autoSelect:changeSet: (in category 'as yet unclassified') -----
  openMessageList: messageList name: labelString autoSelect: autoSelectString changeSet: aChangeSet
  | messageSet |
  messageSet := self messageList: messageList.
  messageSet changeSet: aChangeSet.
  messageSet autoSelectString: autoSelectString.
  ToolBuilder open: messageSet label: labelString.!

Item was changed:
+ ----- Method: FileList2 class>>hideSqueakletDirectoryBlock (in category 'blocks') -----
- ----- Method: FileList2 class>>hideSqueakletDirectoryBlock (in category 'as yet unclassified') -----
  hideSqueakletDirectoryBlock
  ^[:dirName| (dirName sameAs: 'Squeaklets') not]!

Item was changed:
+ ----- Method: FileList2 class>>morphicView (in category 'morphic ui') -----
- ----- Method: FileList2 class>>morphicView (in category 'as yet unclassified') -----
  morphicView
  ^ self morphicViewOnDirectory: FileDirectory default!

Item was changed:
+ ----- Method: FileList2 class>>projectOnlySelectionBlock (in category 'blocks') -----
- ----- Method: FileList2 class>>projectOnlySelectionBlock (in category 'as yet unclassified') -----
  projectOnlySelectionBlock
 
  ^[ :entry :myPattern |
  entry isDirectory ifTrue: [
  false
  ] ifFalse: [
  #('*.pr' '*.pr.gz' '*.project') anySatisfy: [ :each | each match: entry name]
  ]
  ]!

Item was removed:
- ----- Method: FileList2 class>>projectOnlySelectionMethod: (in category 'as yet unclassified') -----
- projectOnlySelectionMethod: incomingEntries
-
- self deprecated: 'use Project class>latestProjectVersionsFromFileEntries: instead'.
-
- ^Project latestProjectVersionsFromFileEntries: incomingEntries!

Item was changed:
+ ----- Method: FileList2 class>>selectionBlockForSuffixes: (in category 'blocks') -----
- ----- Method: FileList2 class>>selectionBlockForSuffixes: (in category 'as yet unclassified') -----
  selectionBlockForSuffixes: anArray
 
  ^[ :entry :myPattern |
  entry isDirectory ifTrue: [
  false
  ] ifFalse: [
  anArray anySatisfy: [ :each | each match: entry name]
  ]
  ]!

Item was changed:
+ ----- Method: FileList2>>specsForImageViewer (in category 'user interface') -----
- ----- Method: FileList2>>specsForImageViewer (in category 'as yet unclassified') -----
  specsForImageViewer
 
  ^{self serviceSortByName. self serviceSortByDate. self serviceSortBySize }!

Item was changed:
  ----- Method: Inspector>>dragFromFieldList: (in category 'drag-drop') -----
  dragFromFieldList: index
  selectionIndex = index ifFalse: [self toggleIndex: index].
  ^self selection!

Item was changed:
+ ----- Method: InspectorBrowser>>fieldList (in category 'accessing') -----
- ----- Method: InspectorBrowser>>fieldList (in category 'as yet unclassified') -----
  fieldList
  fieldList ifNotNil: [^ fieldList].
  ^ (fieldList := super fieldList)!

Item was changed:
+ ----- Method: InspectorBrowser>>msgAccept:from: (in category 'messages') -----
- ----- Method: InspectorBrowser>>msgAccept:from: (in category 'as yet unclassified') -----
  msgAccept: newText from: editor
  | category |
  category := msgListIndex = 0
  ifTrue: [ClassOrganizer default]
  ifFalse: [object class organization categoryOfElement: (msgList at: msgListIndex)].
  ^ (object class compile: newText classified: category notifying: editor) ~~ nil!

Item was changed:
+ ----- Method: InspectorBrowser>>msgListIndex (in category 'messages') -----
- ----- Method: InspectorBrowser>>msgListIndex (in category 'as yet unclassified') -----
  msgListIndex
  ^msgListIndex!

Item was changed:
+ ----- Method: InspectorBrowser>>msgListIndex: (in category 'messages') -----
- ----- Method: InspectorBrowser>>msgListIndex: (in category 'as yet unclassified') -----
  msgListIndex: anInteger
  "A selection has been made in the message pane"
 
  msgListIndex := anInteger.
  self changed: #msgText.!

Item was changed:
+ ----- Method: InspectorBrowser>>msgPaneMenu:shifted: (in category 'messages') -----
- ----- Method: InspectorBrowser>>msgPaneMenu:shifted: (in category 'as yet unclassified') -----
  msgPaneMenu: aMenu shifted: shifted
  ^ aMenu labels:
  'find... (f)
  find again (g)
  find and replace...
  do/replace again (j)
  undo (z)
  redo (Z)
  copy (c)
  cut (x)
  paste (v)
  do it (d)
  print it (p)
  inspect it (i)
  accept (s)
  cancel (l)'
  lines: #(0 4 6 9 12)
  selections: #(find findAgain findReplace again undo redo copySelection cut paste doIt printIt inspectIt accept cancel)!

Item was changed:
+ ----- Method: InspectorBrowser>>msgText (in category 'messages') -----
- ----- Method: InspectorBrowser>>msgText (in category 'as yet unclassified') -----
  msgText
  msgListIndex = 0 ifTrue: [^ nil].
  ^ object class sourceCodeAt: (msgList at: msgListIndex)!

Item was changed:
+ ----- Method: InspectorBrowser>>step (in category 'stepping and presenter') -----
- ----- Method: InspectorBrowser>>step (in category 'as yet unclassified') -----
  step
  | list fieldString msg |
  (list := super fieldList) = fieldList ifFalse:
  [fieldString := selectionIndex > 0 ifTrue: [fieldList at: selectionIndex] ifFalse: [nil].
  fieldList := list.
  selectionIndex := fieldList indexOf: fieldString.
  self changed: #fieldList.
  self changed: #selectionIndex].
  list := msgList.  msgList := nil.  "force recomputation"
  list = self msgList ifFalse:
  [msg := msgListIndex > 0 ifTrue: [list at: msgListIndex] ifFalse: [nil].
  msgListIndex := msgList indexOf: msg.
  self changed: #msgList.
  self changed: #msgListIndex].
  super step!

Item was changed:
+ ----- Method: InspectorBrowser>>wantsSteps (in category 'accessing') -----
- ----- Method: InspectorBrowser>>wantsSteps (in category 'as yet unclassified') -----
  wantsSteps
  ^ true!

Item was changed:
+ ----- Method: MethodFinder class>>methodFor: (in category 'utility') -----
- ----- Method: MethodFinder class>>methodFor: (in category 'as yet unclassified') -----
  methodFor: dataAndAnswers
  "Return a Squeak expression that computes these answers.  (This method is called by the comment in the bottom pane of a MethodFinder.  Do not delete this method.)"
 
  | resultOC resultString |
  resultOC := (self new) load: dataAndAnswers; findMessage.
  resultString := String streamContents: [:strm |
  resultOC do: [:exp | strm nextPut: $(; nextPutAll: exp; nextPut: $); space]].
  ^ resultString!

Item was changed:
+ ----- Method: OrderedCollectionInspector>>fieldList (in category 'accessing') -----
- ----- Method: OrderedCollectionInspector>>fieldList (in category 'as yet unclassified') -----
  fieldList
  object ifNil: [ ^ OrderedCollection new].
  ^ self baseFieldList ,
  (self objectSize <= (self i1 + self i2)
  ifTrue: [(1 to: self objectSize)
  collect: [:i | i printString]]
  ifFalse: [(1 to: self i1) , (self objectSize - (self i2-1) to: self objectSize)
  collect: [:i | i printString]])
  "
  OrderedCollection new inspect
  (OrderedCollection newFrom: #(3 5 7 123)) inspect
  (OrderedCollection newFrom: (1 to: 1000)) inspect
  "!

Item was changed:
+ ----- Method: OrderedCollectionInspector>>objectSize (in category 'private') -----
- ----- Method: OrderedCollectionInspector>>objectSize (in category 'as yet unclassified') -----
  objectSize
  "Single stepping through a debugger might observe the state of an OrderedCollection
  instance after creation by basicNew but before initiialisation.  Thus 'object size'
  throws a DNU error for arithmetic on a nil value that needs to be handled here."
 
  ^ [ object size ] on: Error do: [ 0 ]
  !

Item was changed:
+ ----- Method: OrderedCollectionInspector>>replaceSelectionValue: (in category 'selecting') -----
- ----- Method: OrderedCollectionInspector>>replaceSelectionValue: (in category 'as yet unclassified') -----
  replaceSelectionValue: anObject
  "The receiver has a list of variables of its inspected object. One of these
  is selected. The value of the selected variable is set to the value, anObject."
 
  (selectionIndex - 2) <= object class instSize
  ifTrue: [^ super replaceSelectionValue: anObject].
  object at: self selectedObjectIndex put: anObject!

Item was changed:
+ ----- Method: OrderedCollectionInspector>>selectedObjectIndex (in category 'selecting') -----
- ----- Method: OrderedCollectionInspector>>selectedObjectIndex (in category 'as yet unclassified') -----
  selectedObjectIndex
  "Answer the index of the inspectee's collection that the current selection refers to."
 
  | basicIndex |
  basicIndex := selectionIndex - 2 - object class instSize.
  ^ (object size <= (self i1 + self i2)  or: [basicIndex <= self i1])
  ifTrue: [basicIndex]
  ifFalse: [object size - (self i1 + self i2) + basicIndex]!

Item was changed:
+ ----- Method: OrderedCollectionInspector>>selection (in category 'selecting') -----
- ----- Method: OrderedCollectionInspector>>selection (in category 'as yet unclassified') -----
  selection
  "The receiver has a list of variables of its inspected object.
  One of these is selected. Answer the value of the selected variable."
 
  (selectionIndex - 2) <= object class instSize
  ifTrue: [^ super selection].
  ^ object at: self selectedObjectIndex!

Item was changed:
+ ----- Method: ToolIconHelp class>>abstract (in category 'icons') -----
- ----- Method: ToolIconHelp class>>abstract (in category 'as yet unclassified') -----
  abstract
 
  ^ 'This method is abstract.' !

Item was changed:
+ ----- Method: ToolIconHelp class>>arrowDown (in category 'icons') -----
- ----- Method: ToolIconHelp class>>arrowDown (in category 'as yet unclassified') -----
  arrowDown
 
  ^ 'This method is overriden by another method.'!

Item was changed:
+ ----- Method: ToolIconHelp class>>arrowUp (in category 'icons') -----
- ----- Method: ToolIconHelp class>>arrowUp (in category 'as yet unclassified') -----
  arrowUp
 
  ^ 'This method overrides a super method.'!

Item was changed:
+ ----- Method: ToolIconHelp class>>arrowUpAndDown (in category 'icons') -----
- ----- Method: ToolIconHelp class>>arrowUpAndDown (in category 'as yet unclassified') -----
  arrowUpAndDown
 
  ^ 'This method overrides and is overridden by other methods.'!

Item was changed:
+ ----- Method: ToolIconHelp class>>blank (in category 'icons') -----
- ----- Method: ToolIconHelp class>>blank (in category 'as yet unclassified') -----
  blank
 
  ^ ''!

Item was changed:
+ ----- Method: ToolIconHelp class>>breakpoint (in category 'icons') -----
- ----- Method: ToolIconHelp class>>breakpoint (in category 'as yet unclassified') -----
  breakpoint
 
  ^ 'This method contains a breakpoint.'!

Item was changed:
+ ----- Method: ToolIconHelp class>>flag (in category 'icons') -----
- ----- Method: ToolIconHelp class>>flag (in category 'as yet unclassified') -----
  flag
 
  ^ 'This method needs attention of some kind.' !

Item was changed:
+ ----- Method: ToolIconHelp class>>helpTexts (in category 'accessing') -----
- ----- Method: ToolIconHelp class>>helpTexts (in category 'as yet unclassified') -----
  helpTexts
 
  ^ HelpTexts ifNil: [HelpTexts := IdentityDictionary new]!

Item was changed:
+ ----- Method: ToolIconHelp class>>iconHelpNamed: (in category 'icons help') -----
- ----- Method: ToolIconHelp class>>iconHelpNamed: (in category 'as yet unclassified') -----
  iconHelpNamed: aSymbol
 
  ^ (self respondsTo: aSymbol)
  ifTrue: [self helpTexts at: aSymbol ifAbsentPut: [self perform: aSymbol]]
  ifFalse: [String empty]
  !

Item was changed:
+ ----- Method: ToolIconHelp class>>no (in category 'icons') -----
- ----- Method: ToolIconHelp class>>no (in category 'as yet unclassified') -----
  no
 
  ^  'This method should not be implemented.' !

Item was changed:
+ ----- Method: ToolIconHelp class>>notOverridden (in category 'icons') -----
- ----- Method: ToolIconHelp class>>notOverridden (in category 'as yet unclassified') -----
  notOverridden
 
  ^ 'This method is abstract and has not been overridden.' !

Item was changed:
+ ----- Method: ToolIconHelp class>>primitive (in category 'icons') -----
- ----- Method: ToolIconHelp class>>primitive (in category 'as yet unclassified') -----
  primitive
 
  ^ 'This method implements a primitive.'!