The Trunk: Tools-ar.152.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-ar.152.mcz

commits-2
Andreas Raab uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-ar.152.mcz

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

Name: Tools-ar.152
Author: ar
Time: 28 December 2009, 1:44:05 am
UUID: f2ace051-702b-2f45-a492-0c29208020f1
Ancestors: Tools-nice.151

NanoTraits preparations: Remove several unnecessary direct dependencies between tools package and traits package.

=============== Diff against Tools-nice.151 ===============

Item was changed:
  ----- Method: Browser>>defineTrait:notifying: (in category 'traits') -----
  defineTrait: defString notifying: aController  
 
  | defTokens keywdIx envt oldTrait newTraitName trait |
  oldTrait := self selectedClassOrMetaClass.
  defTokens := defString findTokens: Character separators.
  keywdIx := defTokens findFirst: [:x | x = 'category'].
  envt := self selectedEnvironment.
  keywdIx := defTokens findFirst: [:x | x = 'named:'].
  newTraitName := (defTokens at: keywdIx+1) copyWithoutAll: '#()'.
  ((oldTrait isNil or: [oldTrait baseTrait name asString ~= newTraitName])
  and: [envt includesKey: newTraitName asSymbol]) ifTrue:
  ["Attempting to define new class/trait over existing one when
  not looking at the original one in this browser..."
  (self confirm: ((newTraitName , ' is an existing class/trait in this system.
  Redefining it might cause serious problems.
  Is this really what you want to do?') asText makeBoldFrom: 1 to: newTraitName size))
  ifFalse: [^ false]].
 
  trait := Compiler evaluate: defString notifying: aController logged: true.
+ ^(trait isTrait)
- ^(trait isKindOf: TraitBehavior)
  ifTrue: [
  self changed: #classList.
  self classListIndex: (self classListIndexOf: trait baseTrait name).
  self clearUserEditFlag; editClass.
  true]
  ifFalse: [ false ]
  !

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 selectedSystemCategoryName].
- ifTrue: [^Trait newTemplateIn: self selectedSystemCategoryName].
  editSelection == #none ifTrue: [^ ''].
  editSelection == #editSystemCategories
  ifTrue: [^ systemOrganizer printString].
  editSelection == #newClass
  ifTrue: [^ (theClass := self selectedClass)
  ifNil:
  [Class template: self selectedSystemCategoryName]
  ifNotNil:
  [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].
- ifTrue: [
- self selectedClassOrMetaClass isTrait
- ifTrue: [^'']
- ifFalse: [^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>>addTrait (in category 'traits') -----
  addTrait
  | input trait |
  input := UIManager default request: 'add trait'.
  input isEmptyOrNil ifFalse: [
  trait := Smalltalk classNamed: input.
  (trait isNil or: [trait isTrait not]) ifTrue: [
  ^self inform: 'Input invalid. ' , input , ' does not exist or is not a trait'].
+ self selectedClass setTraitComposition: self selectedClass traitComposition asTraitComposition +  trait.
- self selectedClass addToComposition: trait.
  self contentsChanged].
  !

Item was changed:
  ----- Method: Browser>>removeMessage (in category 'message functions') -----
  removeMessage
  "If a message is selected, create a Confirmer so the user can verify that  
  the currently selected message should be removed from the system. If
  so,  
  remove it. If the Preference 'confirmMethodRemoves' is set to false, the
  confirmer is bypassed."
  | messageName confirmation |
  messageListIndex = 0
  ifTrue: [^ self].
  self okToChange
  ifFalse: [^ self].
  messageName := self selectedMessageName.
  confirmation := self systemNavigation   confirmRemovalOf: messageName on: self selectedClassOrMetaClass.
  confirmation == 3
  ifTrue: [^ self].
+ self selectedClassOrMetaClass removeSelector: messageName.
- (self selectedClassOrMetaClass includesLocalSelector: messageName)
- ifTrue: [self selectedClassOrMetaClass removeSelector: messageName]
- ifFalse: [self removeNonLocalSelector: messageName].
  self messageListIndex: 0.
  self changed: #messageList.
  self setClassOrganizer.
  "In case organization not cached"
  confirmation == 2
  ifTrue: [self systemNavigation browseAllCallsOn: messageName]!

Item was removed:
- ----- Method: TraitBehavior>>browse (in category '*tools-browser') -----
- browse
- self systemNavigation browseClass: self!

Item was removed:
- ----- Method: Browser>>removeNonLocalSelector: (in category 'traits') -----
- removeNonLocalSelector: aSymbol
- | traits isAlias |
- traits := self selectedClassOrMetaClass traitsProvidingSelector: aSymbol.
- isAlias := self selectedClassOrMetaClass isLocalAliasSelector: aSymbol.
- isAlias
- ifTrue: [
- self assert: traits size = 1.
- self selectedClassOrMetaClass removeAlias: aSymbol of: traits first]
- ifFalse: [
- traits do: [:each |
- self selectedClassOrMetaClass addExclusionOf: aSymbol to: each ]]
- !