The Inbox: Tools-fbs.301.mcz

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

The Inbox: Tools-fbs.301.mcz

commits-2
A new version of Tools was added to project The Inbox:
http://source.squeak.org/inbox/Tools-fbs.301.mcz

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

Name: Tools-fbs.301
Author: fbs
Time: 3 March 2011, 11:20:00.889 pm
UUID: 9f787d80-6eb1-0741-a5ac-57d3a80a3c7a
Ancestors: Tools-fbs.300

* Complete removal of systemCategoryListIndex, replaced by selectedSystemCategory.
* selectedSystemCategoryListIndex/selectedSystemCategoryListIndex: remain, used by Morphic, and defer to selectedSystemCategory/selectedSystemCategory:.
* selectedSystemCategoryName defers to selectedSystemCategory, and all its callers now call selectedSystemCategory.
* PackagePaneBrowser>>hasSystemCategorySelected pulled up to Browser.

=============== Diff against Tools-fbs.300 ===============

Item was changed:
  CodeHolder subclass: #Browser
+ instanceVariableNames: 'systemOrganizer classOrganizer metaClassOrganizer classListIndex messageCategoryListIndex messageListIndex editSelection metaClassIndicated selectedSystemCategory'
- instanceVariableNames: 'systemOrganizer classOrganizer metaClassOrganizer systemCategoryListIndex classListIndex messageCategoryListIndex messageListIndex editSelection metaClassIndicated'
  classVariableNames: 'ListClassesHierarchically RecentClasses'
  poolDictionaries: ''
  category: 'Tools-Browser'!
 
  !Browser commentStamp: '<historical>' prior: 0!
  I represent a query path into the class descriptions, the software of the system.!

Item was changed:
  ----- Method: Browser class>>newOnCategory: (in category 'instance creation') -----
  newOnCategory: aCategory
  "Browse the system category of the given name.  7/13/96 sw"
 
  "Browser newOnCategory: 'Interface-Browser'"
 
+ | newBrowser newCat |
+ newBrowser := self new..
+ newCat := aCategory asSymbol.
+ (newBrowser systemCategoryList includes: newCat)
+ ifTrue: [ newBrowser selectedSystemCategory: newCat ]
+ ifFalse: [ ^ self inform: 'No such category' ].
+
- | newBrowser catList |
- newBrowser := self new.
- catList := newBrowser systemCategoryList.
- newBrowser systemCategoryListIndex:
- (catList indexOf: aCategory asSymbol ifAbsent: [^ self inform: 'No such category']).
  ^ self
  openBrowserView: (newBrowser openSystemCatEditString: nil)
  label: 'Classes in category ', aCategory
  !

Item was changed:
  ----- Method: Browser>>addSystemCategory (in category 'system category functions') -----
  addSystemCategory
  "Prompt for a new category name and add it before the
  current selection, or at the end if no current selection"
+ | oldSelection newName |
- | oldIndex newName |
  self okToChange ifFalse: [^ self].
+ oldSelection := self selectedSystemCategory.
- oldIndex := systemCategoryListIndex.
  newName := self
  request: 'Please type new category name'
  initialAnswer: 'Category-Name'.
  newName isEmpty
  ifTrue: [^ self]
  ifFalse: [newName := newName asSymbol].
  systemOrganizer
  addCategory: newName
+ before: self selectedSystemCategory.
+ self selectedSystemCategory:
+ (oldSelection isNil
+ ifTrue: [ self systemCategoryList last ]
+ ifFalse: [ oldSelection ]).
- before: self selectedSystemCategoryName.
- self systemCategoryListIndex:
- (oldIndex = 0
- ifTrue: [self systemCategoryList size]
- ifFalse: [oldIndex]).
  self changed: #systemCategoryList.!

Item was changed:
  ----- Method: Browser>>alphabetizeSystemCategories (in category 'system category functions') -----
  alphabetizeSystemCategories
 
  self okToChange ifFalse: [^ false].
  systemOrganizer sortCategories.
+ self selectedSystemCategory: nil.
- self systemCategoryListIndex: 0.
  self changed: #systemCategoryList.
  !

Item was changed:
  ----- Method: Browser>>buildMessageCategoryBrowserEditString: (in category 'message category functions') -----
  buildMessageCategoryBrowserEditString: aString
  "Create and schedule a message category browser for the currently
  selected message category. The initial text view contains the characters
  in aString."
  "wod 6/24/1998: set newBrowser classListIndex so that it works whether the
  receiver is a standard or a Hierarchy Browser."
 
  | newBrowser |
  messageCategoryListIndex ~= 0
  ifTrue:
  [newBrowser := Browser new.
+ newBrowser selectedSystemCategory: self selectedSystemCategory.
- newBrowser systemCategoryListIndex: systemCategoryListIndex.
  newBrowser classListIndex: (newBrowser classList indexOf: self selectedClassName).
  newBrowser metaClassIndicated: metaClassIndicated.
  newBrowser messageCategoryListIndex: messageCategoryListIndex.
  newBrowser messageListIndex: messageListIndex.
  self class openBrowserView: (newBrowser openMessageCatEditString: aString)
  label: 'Message Category Browser (' ,
  newBrowser selectedClassOrMetaClassName , ')']!

Item was changed:
  ----- Method: Browser>>buildSystemCategoryBrowserEditString: (in category 'system category functions') -----
  buildSystemCategoryBrowserEditString: aString
  "Create and schedule a new system category browser with initial textual
  contents set to aString."
 
  | newBrowser |
+ self hasSystemCategorySelected
- systemCategoryListIndex > 0
  ifTrue:
  [newBrowser := self class new.
+ newBrowser selectedSystemCategory: self selectedSystemCategory.
- newBrowser systemCategoryListIndex: systemCategoryListIndex.
  newBrowser setClass: self selectedClassOrMetaClass selector: self selectedMessageName.
  self class openBrowserView: (newBrowser openSystemCatEditString: aString)
+ label: 'Classes in category ', newBrowser selectedSystemCategory]!
- label: 'Classes in category ', newBrowser selectedSystemCategoryName]!

Item was changed:
  ----- Method: Browser>>classListIndex: (in category 'class list') -----
  classListIndex: anInteger
  "Set anInteger to be the index of the current class selection."
 
  | className currentMessageCategoryName currentMessageName |
  currentMessageCategoryName := [self selectedMessageCategoryName]
  on: Error
  do: [:ex| ex return: nil].
  currentMessageName := [self selectedMessageName]
  on: Error
  do: [:ex| ex return: nil].
 
  classListIndex := anInteger.
  self setClassOrganizer.
 
  "Try to reselect the category and/or selector if the new class has them."
  messageCategoryListIndex := self messageCategoryList
  indexOf: currentMessageCategoryName
  ifAbsent: [0].
  messageListIndex := messageCategoryListIndex = 0
  ifTrue: [0]
  ifFalse: [self messageList
  indexOf: currentMessageName
  ifAbsent: [0]].
 
  messageListIndex ~= 0 ifTrue:
  [self editSelection: #editMessage] ifFalse:
  [messageCategoryListIndex ~= 0 ifTrue:
  [self editSelection: #newMessage] ifFalse:
  [self classCommentIndicated
  ifTrue: []
  ifFalse: [self editSelection: (anInteger = 0
+ ifTrue: [(metaClassIndicated or: [ self hasSystemCategorySelected not ])
- ifTrue: [(metaClassIndicated or: [ self selectedSystemCategoryName isNil ])
  ifTrue: [#none]
  ifFalse: [#newClass]]
  ifFalse: [#editClass])]]].
  contents := nil.
  self selectedClass isNil
  ifFalse: [className := self selectedClass name.
  (RecentClasses includes: className)
  ifTrue: [RecentClasses remove: className].
  RecentClasses addFirst: className.
  RecentClasses size > 16
  ifTrue: [RecentClasses removeLast]].
  self changed: #classSelectionChanged.
  self changed: #classCommentText.
  self changed: #classListIndex. "update my selection"
  self changed: #messageCategoryList.
  self changed: #messageList.
  self changed: #relabel.
  self contentsChanged!

Item was changed:
  ----- Method: Browser>>contents (in category 'accessing') -----
  contents
  "Depending on the current selection, different information is retrieved.
  Answer a string description of that information. This information is the
  method of the currently selected class and message."
 
  | comment theClass latestCompiledMethod |
  latestCompiledMethod := currentCompiledMethod.
  currentCompiledMethod := nil.
 
  editSelection == #newTrait
+ ifTrue: [^ClassDescription newTraitTemplateIn: self selectedSystemCategory].
- ifTrue: [^ClassDescription newTraitTemplateIn: self selectedSystemCategoryName].
  editSelection == #none ifTrue: [^ ''].
  editSelection == #editSystemCategories
  ifTrue: [^ systemOrganizer printString].
  editSelection == #newClass
  ifTrue: [^ (theClass := self selectedClass)
  ifNil:
+ [Class template: self selectedSystemCategory]
- [Class template: self selectedSystemCategoryName]
  ifNotNil:
+ [Class templateForSubclassOf: theClass category: self selectedSystemCategory]].
- [Class templateForSubclassOf: theClass category: self selectedSystemCategoryName]].
  editSelection == #editClass
  ifTrue: [^self classDefinitionText].
  editSelection == #editComment
  ifTrue:
  [(theClass := self selectedClass) ifNil: [^ ''].
  comment := theClass comment.
  currentCompiledMethod := theClass organization commentRemoteStr.
  ^ comment size = 0
  ifTrue: ['This class has not yet been commented.']
  ifFalse: [comment]].
  editSelection == #hierarchy
  ifTrue: [^self selectedClassOrMetaClass printHierarchy].
  editSelection == #editMessageCategories
  ifTrue: [^ self classOrMetaClassOrganizer printString].
  editSelection == #newMessage
  ifTrue:
  [^ (theClass := self selectedClassOrMetaClass)
  ifNil: ['']
  ifNotNil: [theClass sourceCodeTemplate]].
  editSelection == #editMessage
  ifTrue:
  [^ self editContentsWithDefault:
  [currentCompiledMethod := latestCompiledMethod.
  self selectedMessage]].
 
  self error: 'Browser internal error: unknown edit selection.'!

Item was changed:
  ----- Method: Browser>>defaultClassList (in category 'class list') -----
  defaultClassList
  "Answer an array of the class names of the selected category. Answer an
  empty array if no selection exists."
+
+ ^ self hasSystemCategorySelected
+ ifTrue: [systemOrganizer listAtCategoryNamed: self selectedSystemCategory]
+ ifFalse: [Array new].!
-
- ^ self selectedSystemCategoryName isNil
- ifTrue: [Array new]
- ifFalse: [systemOrganizer listAtCategoryNumber: systemCategoryListIndex]!

Item was changed:
  ----- Method: Browser>>editSystemCategories (in category 'system category functions') -----
  editSystemCategories
  "Retrieve the description of the class categories of the system organizer."
 
  self okToChange ifFalse: [^ self].
+ self selectedSystemCategory: nil.
- self systemCategoryListIndex: 0.
  self editSelection: #editSystemCategories.
  self changed: #editSystemCategories.
  self contentsChanged!

Item was changed:
  ----- Method: Browser>>fileOutSystemCategory (in category 'system category functions') -----
  fileOutSystemCategory
  "Print a description of each class in the selected category onto a file
  whose name is the category name followed by .st."
 
+ self hasSystemCategorySelected
+ ifTrue: [systemOrganizer fileOutCategory: self selectedSystemCategory]!
- self selectedSystemCategoryName notNil
- ifTrue: [systemOrganizer fileOutCategory: self selectedSystemCategoryName]!

Item was added:
+ ----- Method: Browser>>hasSystemCategorySelected (in category 'system category list') -----
+ hasSystemCategorySelected
+ ^ self selectedSystemCategory notNil.!

Item was changed:
  ----- Method: Browser>>metaClassIndicated: (in category 'metaclass') -----
  metaClassIndicated: trueOrFalse
  "Indicate whether browsing instance or class messages."
 
  metaClassIndicated := trueOrFalse.
  self setClassOrganizer.
+ self hasSystemCategorySelected ifTrue:
- self selectedSystemCategoryName notNil ifTrue:
  [self editSelection: (classListIndex = 0
  ifTrue: [metaClassIndicated
  ifTrue: [#none]
  ifFalse: [#newClass]]
  ifFalse: [#editClass])].
  messageCategoryListIndex := 0.
  messageListIndex := 0.
  contents := nil.
  self changed: #classSelectionChanged.
  self changed: #messageCategoryList.
  self changed: #messageList.
  self changed: #contents.
  self changed: #annotation.
  self decorateButtons
  !

Item was changed:
  ----- Method: Browser>>noteSelectionIndex:for: (in category 'accessing') -----
  noteSelectionIndex: anInteger for: aSymbol
  aSymbol == #systemCategoryList
  ifTrue:
+ [self systemCategoryListIndex: anInteger].
- [systemCategoryListIndex := anInteger].
  aSymbol == #classList
  ifTrue:
  [classListIndex := anInteger].
  aSymbol == #messageCategoryList
  ifTrue:
  [messageCategoryListIndex := anInteger].
  aSymbol == #messageList
  ifTrue:
  [messageListIndex := anInteger].!

Item was changed:
  ----- Method: Browser>>printOutSystemCategory (in category 'system category functions') -----
  printOutSystemCategory
  "Print a description of each class in the selected category as Html."
 
  Cursor write showWhile:
+ [self hasSystemCategorySelected
+ ifTrue: [systemOrganizer fileOutCategory: self selectedSystemCategory
- [systemCategoryListIndex ~= 0
- ifTrue: [systemOrganizer fileOutCategory: self selectedSystemCategoryName
  asHtml: true ]]
  !

Item was changed:
  ----- Method: Browser>>removeSystemCategory (in category 'system category functions') -----
  removeSystemCategory
  "If a class category is selected, create a Confirmer so the user can
  verify that the currently selected class category and all of its classes
    should be removed from the system. If so, remove it."
 
+ self hasSystemCategorySelected ifFalse: [^ self].
- self selectedSystemCategoryName isNil ifTrue: [^ self].
  self okToChange ifFalse: [^ self].
  (self classList size = 0
  or: [self confirm: 'Are you sure you want to
  remove this system category
  and all its classes?'])
  ifTrue:
+ [systemOrganizer removeSystemCategory: self selectedSystemCategory.
+ self selectedSystemCategory: nil.
- [systemOrganizer removeSystemCategory: self selectedSystemCategoryName.
- self systemCategoryListIndex: 0.
  self changed: #systemCategoryList]!

Item was changed:
  ----- Method: Browser>>renameSystemCategory (in category 'system category functions') -----
  renameSystemCategory
  "Prompt for a new category name and add it before the
  current selection, or at the end if no current selection"
+ | oldSelection newName |
+ oldSelection := self selectedSystemCategory.
+ oldSelection isNil
- | oldIndex oldName newName |
- (oldIndex := systemCategoryListIndex) = 0
  ifTrue: [^ self].  "no selection"
  self okToChange ifFalse: [^ self].
+
- oldName := self selectedSystemCategoryName.
  newName := self
  request: 'Please type new category name'
+ initialAnswer: oldSelection.
- initialAnswer: oldName.
  newName isEmpty
  ifTrue: [^ self]
  ifFalse: [newName := newName asSymbol].
+ oldSelection = newName ifTrue: [^ self].
- oldName = newName ifTrue: [^ self].
  systemOrganizer
+ renameCategory: oldSelection
- renameCategory: oldName
  toBe: newName.
+ self selectedSystemCategory: oldSelection.
- self systemCategoryListIndex: oldIndex.
  self changed: #systemCategoryList.!

Item was changed:
  ----- Method: Browser>>restoreToCategory:className:protocol:selector:mode:meta: (in category 'multi-window support') -----
  restoreToCategory: category className: className protocol: protocol selector: selector mode: editMode meta: metaBool
+ self selectedSystemCategory: category.
- self systemCategoryListIndex: (self systemCategoryList indexOf: category).
  self classListIndex: (self classListIndexOf: className).
  self metaClassIndicated: metaBool.
  self messageCategoryListIndex: (self messageCategoryList indexOf: protocol).
  self messageListIndex: (self messageList indexOf: selector).
  editSelection := editMode.
  self
  contentsChanged;
  decorateButtons!

Item was changed:
  ----- Method: Browser>>saveMultiWindowState (in category 'multi-window support') -----
  saveMultiWindowState
  ^Message
  selector: #restoreToCategory:className:protocol:selector:mode:meta:
+ arguments: { self selectedSystemCategory.
- arguments: { self selectedSystemCategoryName.
  self selectedClassName.
  self selectedMessageCategoryName.
  self selectedMessageName.
  self editSelection.
  self metaClassIndicated }!

Item was changed:
  ----- Method: Browser>>selectCategoryForClass: (in category 'system category list') -----
  selectCategoryForClass: theClass
+ self selectedSystemCategory: theClass category.!
-
- self systemCategoryListIndex: (self systemCategoryList indexOf: theClass category)
- !

Item was changed:
  ----- Method: Browser>>selectedEnvironment (in category 'system category list') -----
  selectedEnvironment
  "Answer the name of the selected system category or nil."
 
+ self hasSystemCategorySelected ifFalse: [^nil].
- self selectedSystemCategoryName isNil ifTrue: [^nil].
  ^ Smalltalk!

Item was added:
+ ----- Method: Browser>>selectedSystemCategory (in category 'system category list') -----
+ selectedSystemCategory
+ ^ selectedSystemCategory!

Item was added:
+ ----- Method: Browser>>selectedSystemCategory: (in category 'system category list') -----
+ selectedSystemCategory: aSymbol
+ "Set the selected system category. Update all other selections to be deselected."
+
+ selectedSystemCategory := aSymbol.
+
+ classListIndex := 0.
+ messageCategoryListIndex := 0.
+ messageListIndex := 0.
+ self editSelection: ( aSymbol isNil ifTrue: [#none] ifFalse: [#newClass]).
+ metaClassIndicated := false.
+ self setClassOrganizer.
+ contents := nil.
+ self changed: #systemCategorySelectionChanged.
+ self changed: #systemCategoryListIndex. "update my selection"
+ self changed: #classList.
+ self changed: #messageCategoryList.
+ self changed: #messageList.
+ self changed: #relabel.
+ self contentsChanged!

Item was changed:
  ----- Method: Browser>>selectedSystemCategoryName (in category 'system category list') -----
  selectedSystemCategoryName
  "Answer the name of the selected system category or nil."
 
+ ^ self selectedSystemCategory.!
- systemCategoryListIndex = 0 ifTrue: [^nil].
- ^self systemCategoryList at: systemCategoryListIndex!

Item was changed:
  ----- Method: Browser>>spawn: (in category 'accessing') -----
  spawn: aString
  "Create and schedule a fresh browser and place aString in its code pane.  This method is called when the user issues the #spawn command (cmd-o) in any code pane.  Whatever text was in the original code pane comes in to this method as the aString argument; the changes in the original code pane have already been cancelled by the time this method is called, so aString is the only copy of what the user had in his code pane."
 
  self selectedClassOrMetaClass ifNotNil: [^ super spawn: aString].
 
+ self hasSystemCategorySelected ifTrue:
+ ["This choice is slightly useless but is the historical implementation"
+ ^ self buildSystemCategoryBrowserEditString: aString].
- systemCategoryListIndex ~= 0
- ifTrue:
- ["This choice is slightly useless but is the historical implementation"
- ^ self buildSystemCategoryBrowserEditString: aString].
 
  ^ super spawn: aString  
  "This bail-out at least saves the text being spawned, which would otherwise be lost"!

Item was changed:
  ----- Method: Browser>>systemCategoryListIndex (in category 'system category list') -----
  systemCategoryListIndex
  "Answer the index of the selected class category."
 
+ ^ self systemCategoryList indexOf: self selectedSystemCategory.!
- ^systemCategoryListIndex!

Item was changed:
  ----- Method: Browser>>systemCategoryListIndex: (in category 'system category list') -----
  systemCategoryListIndex: anInteger
  "Set the selected system category index to be anInteger. Update all other
  selections to be deselected."
+
+ self selectedSystemCategory: (self systemCategoryList at: anInteger ifAbsent: [ nil ])!
-
- systemCategoryListIndex := anInteger.
- classListIndex := 0.
- messageCategoryListIndex := 0.
- messageListIndex := 0.
- self editSelection: ( anInteger = 0 ifTrue: [#none] ifFalse: [#newClass]).
- metaClassIndicated := false.
- self setClassOrganizer.
- contents := nil.
- self changed: #systemCategorySelectionChanged.
- self changed: #systemCategoryListIndex. "update my selection"
- self changed: #classList.
- self changed: #messageCategoryList.
- self changed: #messageList.
- self changed: #relabel.
- self contentsChanged!

Item was changed:
  ----- Method: Browser>>systemCategorySingleton (in category 'system category list') -----
  systemCategorySingleton
 
  | cat |
+ cat := self selectedSystemCategory.
- cat := self selectedSystemCategoryName.
  ^ cat ifNil: [Array new]
  ifNotNil: [Array with: cat]!

Item was changed:
  ----- Method: Browser>>systemOrganizer: (in category 'initialize-release') -----
  systemOrganizer: aSystemOrganizer
  "Initialize the receiver as a perspective on the system organizer,
  aSystemOrganizer. Typically there is only one--the system variable
  SystemOrganization."
 
  contents := nil.
  systemOrganizer := aSystemOrganizer.
+ selectedSystemCategory := nil.
- systemCategoryListIndex := 0.
  classListIndex := 0.
  messageCategoryListIndex := 0.
  messageListIndex := 0.
  metaClassIndicated := false.
  self setClassOrganizer.
  self editSelection: #none.!

Item was removed:
- ----- Method: Browser>>toggleSystemCategoryListIndex: (in category 'system category list') -----
- toggleSystemCategoryListIndex: anInteger
- "If anInteger is the current system category index, deselect it. Else make
- it the current system category selection."
-
- self systemCategoryListIndex:
- (systemCategoryListIndex = anInteger
- ifTrue: [0]
- ifFalse: [anInteger])!

Item was changed:
  ----- Method: Browser>>veryDeepInner: (in category 'copying') -----
  veryDeepInner: deepCopier
  "Copy all of my instance variables.  Some need to be not copied at all, but shared.  See DeepCopier class comment."
 
  super veryDeepInner: deepCopier.
  "systemOrganizer := systemOrganizer. clone has the old value. we share it"
  "classOrganizer := classOrganizer clone has the old value. we share it"
  "metaClassOrganizer := metaClassOrganizer clone has the old value. we share it"
+ selectedSystemCategory := selectedSystemCategory veryDeepCopyWith: deepCopier.
- systemCategoryListIndex := systemCategoryListIndex veryDeepCopyWith: deepCopier.
  classListIndex := classListIndex veryDeepCopyWith: deepCopier.
  messageCategoryListIndex := messageCategoryListIndex veryDeepCopyWith: deepCopier.
  messageListIndex := messageListIndex veryDeepCopyWith: deepCopier.
  editSelection := editSelection veryDeepCopyWith: deepCopier.
  metaClassIndicated := metaClassIndicated veryDeepCopyWith: deepCopier.
  !

Item was changed:
  ----- Method: CodeHolder>>spawn: (in category 'commands') -----
  spawn: aString
  "Create and schedule a spawned message category browser for the currently selected message category.  The initial text view contains the characters in aString.  In the spawned browser, preselect the current selector (if any) as the going-in assumption, though upon acceptance this will often change"
 
  | newBrowser aCategory aClass |
  (aClass := self selectedClassOrMetaClass) isNil ifTrue:
  [^ aString isEmptyOrNil ifFalse: [(Workspace new contents: aString) openLabel: 'spawned workspace']].
 
  (aCategory := self categoryOfCurrentMethod)
  ifNil:
  [self buildClassBrowserEditString: aString]
  ifNotNil:
  [newBrowser := Browser new setClass: aClass selector: self selectedMessageName.
  self suggestCategoryToSpawnedBrowser: newBrowser.
+ ^ Browser openBrowserView: (newBrowser openMessageCatEditString: aString)
- Browser openBrowserView: (newBrowser openMessageCatEditString: aString)
  label: 'category "', aCategory, '" in ',
  newBrowser selectedClassOrMetaClassName]!

Item was changed:
  ----- Method: FileContentsBrowser>>classList (in category 'class list') -----
  classList
  "Answer an array of the class names of the selected category. Answer an
  empty array if no selection exists."
 
+ (self hasSystemCategorySelected not or:[self selectedPackage isNil])
- (systemCategoryListIndex = 0 or:[self selectedPackage isNil])
  ifTrue: [^Array new]
  ifFalse: [^self selectedPackage classes keys asArray sort].!

Item was changed:
  ----- Method: FileContentsBrowser>>findClass (in category 'class list') -----
  findClass
  | pattern foundClass classNames index foundPackage |
  self okToChange ifFalse: [^ self classNotFound].
  pattern := (UIManager default request: 'Class Name?') asLowercase.
  pattern isEmpty ifTrue: [^ self].
  classNames := Set new.
  self packages do:[:p| classNames addAll: p classes keys].
  classNames := classNames asArray select:
  [:n | (n asLowercase indexOfSubCollection: pattern startingAt: 1) > 0].
  classNames isEmpty ifTrue: [^ self].
  index := classNames size = 1
  ifTrue: [1]
  ifFalse: [(UIManager default chooseFrom: classNames lines: #())].
  index = 0 ifTrue: [^ self].
  foundPackage := nil.
  foundClass := nil.
  self packages do:[:p|
  (p classes includesKey: (classNames at: index)) ifTrue:[
  foundClass := p classes at: (classNames at: index).
  foundPackage := p]].
  foundClass isNil ifTrue:[^self].
+   self selectedSystemCategory: foundPackage packageName asSymbol.
-   self systemCategoryListIndex: (self systemCategoryList indexOf: foundPackage packageName asSymbol).
  self classListIndex: (self classList indexOf: foundClass name). !

Item was changed:
  ----- Method: FileContentsBrowser>>labelString (in category 'other') -----
  labelString
  "Answer the string for the window title"
 
+ ^ 'File Contents Browser ', (self selectedSystemCategory ifNil: [''])!
- ^ 'File Contents Browser ', (self selectedSystemCategoryName ifNil: [''])!

Item was changed:
  ----- Method: FileContentsBrowser>>removePackage (in category 'removing') -----
  removePackage
+ self hasSystemCategorySelected ifTrue: [^ self].
- systemCategoryListIndex = 0 ifTrue: [^ self].
  self okToChange ifFalse: [^ self].
  (self confirm: 'Are you sure you want to
  remove this package
  and all its classes?') ifFalse:[^self].
+ (systemOrganizer listAtCategoryNamed: self selectedSystemCategory) do:[:el|
- (systemOrganizer listAtCategoryNamed: self selectedSystemCategoryName) do:[:el|
  systemOrganizer removeElement: el].
  self packages removeKey: self selectedPackage packageName.
+ systemOrganizer removeCategory: self selectedSystemCategory.
+ self selectedSystemCategory: nil.
- systemOrganizer removeCategory: self selectedSystemCategoryName.
- self systemCategoryListIndex: 0.
  self changed: #systemCategoryList!

Item was changed:
  ----- Method: FileContentsBrowser>>renameClass (in category 'class list') -----
  renameClass
  | oldName newName |
  classListIndex = 0 ifTrue: [^ self].
  self okToChange ifFalse: [^ self].
  oldName := self selectedClass name.
  newName := (self request: 'Please type new class name'
  initialAnswer: oldName) asSymbol.
  (newName isEmpty or:[newName = oldName]) ifTrue: [^ self].
  (self selectedPackage classes includesKey: newName)
  ifTrue: [^ self error: newName , ' already exists in the package'].
+ systemOrganizer classify: newName under: self selectedSystemCategory.
- systemOrganizer classify: newName under: self selectedSystemCategoryName.
  systemOrganizer removeElement: oldName.
  self selectedPackage renameClass: self selectedClass to: newName.
  self changed: #classList.
+ self classListIndex: ((systemOrganizer listAtCategoryNamed: self selectedSystemCategory) indexOf: newName).
- self classListIndex: ((systemOrganizer listAtCategoryNamed: self selectedSystemCategoryName) indexOf: newName).
  !

Item was changed:
  ----- Method: FileContentsBrowser>>selectedPackage (in category 'accessing') -----
  selectedPackage
  | cat |
+ cat := self selectedSystemCategory.
- cat := self selectedSystemCategoryName.
  cat isNil ifTrue:[^nil].
  ^self packages at: cat asString ifAbsent:[nil]!

Item was changed:
  ----- Method: HierarchyBrowser>>classListIndex: (in category 'initialization') -----
  classListIndex: newIndex
  "Cause system organization to reflect appropriate category"
  | newClassName ind |
  newIndex ~= 0 ifTrue:
  [newClassName := (classList at: newIndex) copyWithout: $ .
+ self selectedSystemCategory: (systemOrganizer categories at:
+ (systemOrganizer numberOfCategoryOfElement: newClassName))].
- systemCategoryListIndex :=
- systemOrganizer numberOfCategoryOfElement: newClassName].
  ind := super classListIndex: newIndex.
  self changed: #systemCategorySingleton.
  ^ ind!

Item was changed:
  ----- Method: PackagePaneBrowser>>classList (in category 'class list') -----
  classList
  "Answer an array of the class names of the selected category. Answer an
  empty array if no selection exists."
 
  ^ self hasSystemCategorySelected
+ ifFalse: [self packageClasses]
+ ifTrue: [systemOrganizer listAtCategoryNamed: self selectedSystemCategory]!
- ifFalse:
- [self packageClasses]
- ifTrue: [systemOrganizer listAtCategoryNumber:
- (systemOrganizer categories indexOf: self selectedSystemCategoryName asSymbol)]!

Item was changed:
  ----- Method: PackagePaneBrowser>>dstCategoryDstListMorph:internal: (in category 'dragNDrop util') -----
  dstCategoryDstListMorph: dstListMorph internal: internal
  | dropItem |
  ^ internal & (dstListMorph getListSelector == #systemCategoryList)
  ifTrue: [(dropItem := dstListMorph potentialDropItem) ifNotNil: [(self package , '-' , dropItem) asSymbol]]
+ ifFalse: [self selectedSystemCategory]!
- ifFalse: [self selectedSystemCategoryName]!

Item was removed:
- ----- Method: PackagePaneBrowser>>hasSystemCategorySelected (in category 'system category list') -----
- hasSystemCategorySelected
- ^ systemCategoryListIndex ~= 0!

Item was changed:
  ----- Method: PackagePaneBrowser>>multiWindowName (in category 'multi-window support') -----
  multiWindowName
  "Answer the string to display for the receiver in a multi-window."
  ^String streamContents:
  [:s| | str |
  self package
  ifNil: [s nextPut: $a; space; nextPutAll: self defaultBrowserTitle]
  ifNotNil:
  [:pkg|
  self selectedClass
+ ifNil: [self selectedSystemCategory
- ifNil: [self selectedSystemCategoryName
  ifNil: [s nextPutAll: pkg]
  ifNotNil: [:cat| s nextPutAll: cat]]
  ifNotNil:
  [:class|
  s nextPutAll: pkg; space; print: class.
  self metaClassIndicated ifTrue:
  [s nextPutAll: ' class']]].
  (str := self selectedMessageName) notNil
  ifTrue: [s nextPutAll: '>>'; nextPutAll: str]
  ifFalse:
  [(str := self selectedMessageCategoryName) notNil
  ifTrue: [s space; nextPut: ${; nextPutAll: str; nextPut: $}]]]!

Item was changed:
  ----- Method: PackagePaneBrowser>>packageListIndex: (in category 'package list') -----
  packageListIndex: anInteger
  "Set anInteger to be the index of the current package selection."
 
  packageListIndex := anInteger.
  anInteger = 0
  ifFalse: [package := self packageList at: packageListIndex].
  messageCategoryListIndex := 0.
+ self selectedSystemCategory: nil.
- systemCategoryListIndex := 0.
  messageListIndex := 0.
  classListIndex := 0.
  self setClassOrganizer.
  self changed: #packageSelectionChanged.
  self changed: #packageListIndex. "update my selection"
  self changed: #systemCategoryList. "update the category list"
+ self selectedSystemCategory: nil. "update category list selection"
- self systemCategoryListIndex: 0. "update category list selection"
  !

Item was changed:
  ----- Method: PackagePaneBrowser>>saveMultiWindowState (in category 'multi-window support') -----
  saveMultiWindowState
  ^Message
  selector: #restoreToPackage:category:className:protocol:selector:mode:meta:
  arguments: { self package.
+ self selectedSystemCategory.
- self systemCategoryList at: systemCategoryListIndex ifAbsent: [].
  self selectedClassName.
  self selectedMessageCategoryName.
  self selectedMessageName.
  self editSelection.
  self metaClassIndicated }!

Item was changed:
  ----- Method: PackagePaneBrowser>>selectCategoryForClass: (in category 'system category list') -----
  selectCategoryForClass: theClass
  "Set the package and category lists to display the given class."
 
+ | cat catName |
- | cat |
  cat := theClass category.
+ self packageListIndex: (self packageList indexOf: (cat copyUpTo: $-)).
+ catName := (cat copyFrom: ((cat indexOf: $- ifAbsent: [0]) + 1) to: cat size).
+ self selectedSystemCategory: catName.!
- self packageListIndex: (self packageList indexOf: (cat copyUpTo: $-)).
- self systemCategoryListIndex: (self systemCategoryList indexOf:
- (cat copyFrom: ((cat indexOf: $- ifAbsent: [0]) + 1) to: cat size)).!

Item was changed:
  ----- Method: PackagePaneBrowser>>selectedSystemCategoryName (in category 'system category list') -----
  selectedSystemCategoryName
  "Answer the name of the selected system category or nil."
 
+ self hasSystemCategorySelected
+ ifFalse: [^nil].
- systemCategoryListIndex = 0
- ifTrue: [^nil].
  packageListIndex = 0
+ ifTrue: [^ self selectedSystemCategory ].
+ ^ self package , '-' , self selectedSystemCategory!
- ifTrue: [^ self systemCategoryList at: systemCategoryListIndex].
- ^ self package , '-' , (self systemCategoryList at: systemCategoryListIndex)!

Item was changed:
  ----- Method: ParagraphEditor>>browseItHere (in category '*Tools') -----
  browseItHere
  "Retarget the receiver's window to look at the selected class, if appropriate.  3/1/96 sw"
  | aSymbol b |
  (((b := model) isKindOf: Browser) and: [b couldBrowseAnyClass])
  ifFalse: [^ view flash].
  model okToChange ifFalse: [^ view flash].
  self selectionInterval isEmpty ifTrue: [self selectWord].
  (aSymbol := self selectedSymbol) ifNil: [^ view flash].
 
  self terminateAndInitializeAround:
  [| foundClass |
  foundClass := (Smalltalk at: aSymbol ifAbsent: [nil]).
  foundClass ifNil: [^ view flash].
  (foundClass isKindOf: Class)
  ifTrue:
+ [model selectedSystemCategory: foundClass category.
- [model systemCategoryListIndex:
- (model systemCategoryList indexOf: foundClass category).
  model classListIndex: (model classList indexOf: foundClass name)]]!


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Tools-fbs.301.mcz

Frank Shearar
On 2011/03/03 23:20, [hidden email] wrote:

> A new version of Tools was added to project The Inbox:
> http://source.squeak.org/inbox/Tools-fbs.301.mcz
>
> ==================== Summary ====================
>
> Name: Tools-fbs.301
> Author: fbs
> Time: 3 March 2011, 11:20:00.889 pm
> UUID: 9f787d80-6eb1-0741-a5ac-57d3a80a3c7a
> Ancestors: Tools-fbs.300
>
> * Complete removal of systemCategoryListIndex, replaced by selectedSystemCategory.
> * selectedSystemCategoryListIndex/selectedSystemCategoryListIndex: remain, used by Morphic, and defer to selectedSystemCategory/selectedSystemCategory:.
> * selectedSystemCategoryName defers to selectedSystemCategory, and all its callers now call selectedSystemCategory.
> * PackagePaneBrowser>>hasSystemCategorySelected pulled up to Browser.
>
> =============== Diff against Tools-fbs.300 ===============

Inbox etiquette question: I'm working on a fairly big chunk of code,
ripping out Browser's indices. I could make 4 or 5 further commits of
about the same complexity as this commit to finish off the change.

I can see a couple of options:
1. Submit big chunks basing off Trunk, letting us lose the indices
piecemeal. Basically, branch-per-feature, and each commit's a completed
subfeature.
2. Submit one megachange, so that Tools-fbs.301 can be deleted.
3. Submit big chunks each based off the previous commit: a single branch
with serial commits.
4. Other situations?

I really don't like option 2: we're talking about rewriting large chunks
of a critical piece of infrastructure.

So what's the preferred way of submitting large features to the Inbox?

frank

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Tools-fbs.301.mcz

Levente Uzonyi-2
On Fri, 4 Mar 2011, Frank Shearar wrote:

> On 2011/03/03 23:20, [hidden email] wrote:
>> A new version of Tools was added to project The Inbox:
>> http://source.squeak.org/inbox/Tools-fbs.301.mcz
>>
>> ==================== Summary ====================
>>
>> Name: Tools-fbs.301
>> Author: fbs
>> Time: 3 March 2011, 11:20:00.889 pm
>> UUID: 9f787d80-6eb1-0741-a5ac-57d3a80a3c7a
>> Ancestors: Tools-fbs.300
>>
>> * Complete removal of systemCategoryListIndex, replaced by
>> selectedSystemCategory.
>> * selectedSystemCategoryListIndex/selectedSystemCategoryListIndex: remain,
>> used by Morphic, and defer to
>> selectedSystemCategory/selectedSystemCategory:.
>> * selectedSystemCategoryName defers to selectedSystemCategory, and all its
>> callers now call selectedSystemCategory.
>> * PackagePaneBrowser>>hasSystemCategorySelected pulled up to Browser.
>>
>> =============== Diff against Tools-fbs.300 ===============
>
> Inbox etiquette question: I'm working on a fairly big chunk of code, ripping
> out Browser's indices. I could make 4 or 5 further commits of about the same
> complexity as this commit to finish off the change.
>
> I can see a couple of options:
> 1. Submit big chunks basing off Trunk, letting us lose the indices piecemeal.
> Basically, branch-per-feature, and each commit's a completed subfeature.
> 2. Submit one megachange, so that Tools-fbs.301 can be deleted.
> 3. Submit big chunks each based off the previous commit: a single branch with
> serial commits.
> 4. Other situations?
>
> I really don't like option 2: we're talking about rewriting large chunks of a
> critical piece of infrastructure.
>
> So what's the preferred way of submitting large features to the Inbox?

It's up to you. For the integrators 1 and 3 are the best. Reviewing small
changes is always easier.


Levente

>
> frank
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Tools-fbs.301.mcz

Frank Shearar
On 2011/03/05 10:47, Levente Uzonyi wrote:

> On Fri, 4 Mar 2011, Frank Shearar wrote:
>
>> On 2011/03/03 23:20, [hidden email] wrote:
>>> A new version of Tools was added to project The Inbox:
>>> http://source.squeak.org/inbox/Tools-fbs.301.mcz
>>>
>>> ==================== Summary ====================
>>>
>>> Name: Tools-fbs.301
>>> Author: fbs
>>> Time: 3 March 2011, 11:20:00.889 pm
>>> UUID: 9f787d80-6eb1-0741-a5ac-57d3a80a3c7a
>>> Ancestors: Tools-fbs.300
>>>
>>> * Complete removal of systemCategoryListIndex, replaced by
>>> selectedSystemCategory.
>>> * selectedSystemCategoryListIndex/selectedSystemCategoryListIndex:
>>> remain, used by Morphic, and defer to
>>> selectedSystemCategory/selectedSystemCategory:.
>>> * selectedSystemCategoryName defers to selectedSystemCategory, and
>>> all its callers now call selectedSystemCategory.
>>> * PackagePaneBrowser>>hasSystemCategorySelected pulled up to Browser.
>>>
>>> =============== Diff against Tools-fbs.300 ===============
>>
>> Inbox etiquette question: I'm working on a fairly big chunk of code,
>> ripping out Browser's indices. I could make 4 or 5 further commits of
>> about the same complexity as this commit to finish off the change.
>>
>> I can see a couple of options:
>> 1. Submit big chunks basing off Trunk, letting us lose the indices
>> piecemeal. Basically, branch-per-feature, and each commit's a
>> completed subfeature.
>> 2. Submit one megachange, so that Tools-fbs.301 can be deleted.
>> 3. Submit big chunks each based off the previous commit: a single
>> branch with serial commits.
>> 4. Other situations?
>>
>> I really don't like option 2: we're talking about rewriting large
>> chunks of a critical piece of infrastructure.
>>
>> So what's the preferred way of submitting large features to the Inbox?
>
> It's up to you. For the integrators 1 and 3 are the best. Reviewing
> small changes is always easier.

3's mildly easier for me. I just wasn't sure about how people would feel
with me dumping a whole string of commits in the Inbox. On one hand it
seems a bit messy because the actual thing I want to go into Trunk will
be the when-I'm-done commit, but on the other hand putting the versions
in the Inbox means that integrators can more easily see what's going on.

frank

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Tools-fbs.301.mcz

Chris Muller-3
Each individually-approvable enhancement in the Inbox should be based
off of some version in the trunk.  Sometimes one "enhancement" might
be big or complex enough to have required a string of
package-versions; but that's ok if they're all part of the same
logical change (e.g., converting away from selected indices to
selected objects).

In that latter situation, when core-devs move things to trunk, please
make sure that _all_ versions are copied into trunk, not just the
final one, so that we have all of the ancestry in the same repository.


On Sat, Mar 5, 2011 at 7:24 AM, Frank Shearar
<[hidden email]> wrote:

> On 2011/03/05 10:47, Levente Uzonyi wrote:
>>
>> On Fri, 4 Mar 2011, Frank Shearar wrote:
>>
>>> On 2011/03/03 23:20, [hidden email] wrote:
>>>>
>>>> A new version of Tools was added to project The Inbox:
>>>> http://source.squeak.org/inbox/Tools-fbs.301.mcz
>>>>
>>>> ==================== Summary ====================
>>>>
>>>> Name: Tools-fbs.301
>>>> Author: fbs
>>>> Time: 3 March 2011, 11:20:00.889 pm
>>>> UUID: 9f787d80-6eb1-0741-a5ac-57d3a80a3c7a
>>>> Ancestors: Tools-fbs.300
>>>>
>>>> * Complete removal of systemCategoryListIndex, replaced by
>>>> selectedSystemCategory.
>>>> * selectedSystemCategoryListIndex/selectedSystemCategoryListIndex:
>>>> remain, used by Morphic, and defer to
>>>> selectedSystemCategory/selectedSystemCategory:.
>>>> * selectedSystemCategoryName defers to selectedSystemCategory, and
>>>> all its callers now call selectedSystemCategory.
>>>> * PackagePaneBrowser>>hasSystemCategorySelected pulled up to Browser.
>>>>
>>>> =============== Diff against Tools-fbs.300 ===============
>>>
>>> Inbox etiquette question: I'm working on a fairly big chunk of code,
>>> ripping out Browser's indices. I could make 4 or 5 further commits of
>>> about the same complexity as this commit to finish off the change.
>>>
>>> I can see a couple of options:
>>> 1. Submit big chunks basing off Trunk, letting us lose the indices
>>> piecemeal. Basically, branch-per-feature, and each commit's a
>>> completed subfeature.
>>> 2. Submit one megachange, so that Tools-fbs.301 can be deleted.
>>> 3. Submit big chunks each based off the previous commit: a single
>>> branch with serial commits.
>>> 4. Other situations?
>>>
>>> I really don't like option 2: we're talking about rewriting large
>>> chunks of a critical piece of infrastructure.
>>>
>>> So what's the preferred way of submitting large features to the Inbox?
>>
>> It's up to you. For the integrators 1 and 3 are the best. Reviewing
>> small changes is always easier.
>
> 3's mildly easier for me. I just wasn't sure about how people would feel
> with me dumping a whole string of commits in the Inbox. On one hand it seems
> a bit messy because the actual thing I want to go into Trunk will be the
> when-I'm-done commit, but on the other hand putting the versions in the
> Inbox means that integrators can more easily see what's going on.
>
> frank
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Tools-fbs.301.mcz

Frank Shearar
On 2011/03/05 19:41, Chris Muller wrote:
> Each individually-approvable enhancement in the Inbox should be based
> off of some version in the trunk.  Sometimes one "enhancement" might
> be big or complex enough to have required a string of
> package-versions; but that's ok if they're all part of the same
> logical change (e.g., converting away from selected indices to
> selected objects).
 >
> In that latter situation, when core-devs move things to trunk, please
> make sure that _all_ versions are copied into trunk, not just the
> final one, so that we have all of the ancestry in the same repository.

In which case at some point before I can say "feature done" I must
submit my versions to the Inbox.

I wanted to check before doing something like dumping seven revisions in
the Inbox (which is my current count). Maybe I should copy the revisions
to Inbox as I go along, so that more experienced eyes can look over my
shoulder?

frank

> On Sat, Mar 5, 2011 at 7:24 AM, Frank Shearar
> <[hidden email]>  wrote:
>> On 2011/03/05 10:47, Levente Uzonyi wrote:
>>>
>>> On Fri, 4 Mar 2011, Frank Shearar wrote:
>>>
>>>> On 2011/03/03 23:20, [hidden email] wrote:
>>>>>
>>>>> A new version of Tools was added to project The Inbox:
>>>>> http://source.squeak.org/inbox/Tools-fbs.301.mcz
>>>>>
>>>>> ==================== Summary ====================
>>>>>
>>>>> Name: Tools-fbs.301
>>>>> Author: fbs
>>>>> Time: 3 March 2011, 11:20:00.889 pm
>>>>> UUID: 9f787d80-6eb1-0741-a5ac-57d3a80a3c7a
>>>>> Ancestors: Tools-fbs.300
>>>>>
>>>>> * Complete removal of systemCategoryListIndex, replaced by
>>>>> selectedSystemCategory.
>>>>> * selectedSystemCategoryListIndex/selectedSystemCategoryListIndex:
>>>>> remain, used by Morphic, and defer to
>>>>> selectedSystemCategory/selectedSystemCategory:.
>>>>> * selectedSystemCategoryName defers to selectedSystemCategory, and
>>>>> all its callers now call selectedSystemCategory.
>>>>> * PackagePaneBrowser>>hasSystemCategorySelected pulled up to Browser.
>>>>>
>>>>> =============== Diff against Tools-fbs.300 ===============
>>>>
>>>> Inbox etiquette question: I'm working on a fairly big chunk of code,
>>>> ripping out Browser's indices. I could make 4 or 5 further commits of
>>>> about the same complexity as this commit to finish off the change.
>>>>
>>>> I can see a couple of options:
>>>> 1. Submit big chunks basing off Trunk, letting us lose the indices
>>>> piecemeal. Basically, branch-per-feature, and each commit's a
>>>> completed subfeature.
>>>> 2. Submit one megachange, so that Tools-fbs.301 can be deleted.
>>>> 3. Submit big chunks each based off the previous commit: a single
>>>> branch with serial commits.
>>>> 4. Other situations?
>>>>
>>>> I really don't like option 2: we're talking about rewriting large
>>>> chunks of a critical piece of infrastructure.
>>>>
>>>> So what's the preferred way of submitting large features to the Inbox?
>>>
>>> It's up to you. For the integrators 1 and 3 are the best. Reviewing
>>> small changes is always easier.
>>
>> 3's mildly easier for me. I just wasn't sure about how people would feel
>> with me dumping a whole string of commits in the Inbox. On one hand it seems
>> a bit messy because the actual thing I want to go into Trunk will be the
>> when-I'm-done commit, but on the other hand putting the versions in the
>> Inbox means that integrators can more easily see what's going on.
>>
>> frank
>>
>>
>
>


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Tools-fbs.301.mcz

Chris Muller-3
> In which case at some point before I can say "feature done" I must submit my
> versions to the Inbox.
>
> I wanted to check before doing something like dumping seven revisions in the
> Inbox (which is my current count).

Yes, that is currently the only good way I can see to do it.  Nor do I
really see any problem with that.

The important thing for me is that we have all of the version ancestry
in the trunk repository.

> Maybe I should copy the revisions to
> Inbox as I go along, so that more experienced eyes can look over my
> shoulder?

I doubt that would happen; I think people are too busy to look over
someone elses shoulder.  I would just wait until you have it done
"done".  Then I think there will be appropriate "motivation" for a
core-dev to look in the Inbox for an "easy" way to improve Squeak.

Thanks,
  Chris

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Tools-fbs.301.mcz

Frank Shearar
On 2011/03/09 21:32, Chris Muller wrote:

>> In which case at some point before I can say "feature done" I must submit my
>> versions to the Inbox.
>>
>> I wanted to check before doing something like dumping seven revisions in the
>> Inbox (which is my current count).
>
> Yes, that is currently the only good way I can see to do it.  Nor do I
> really see any problem with that.
>
> The important thing for me is that we have all of the version ancestry
> in the trunk repository.

In which case you'll see a number of new versions arrive soon. Also,
it's handy to have a backup.

>> Maybe I should copy the revisions to
>> Inbox as I go along, so that more experienced eyes can look over my
>> shoulder?
>
> I doubt that would happen; I think people are too busy to look over
> someone elses shoulder.  I would just wait until you have it done
> "done".  Then I think there will be appropriate "motivation" for a
> core-dev to look in the Inbox for an "easy" way to improve Squeak.

:) I'm hoping Eliot will watch with interest: he gets indices replaced
by symbols, and I hope to get RB :)

frank