The Trunk: ToolBuilder-Morphic-mt.95.mcz

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

The Trunk: ToolBuilder-Morphic-mt.95.mcz

commits-2
Marcel Taeumel uploaded a new version of ToolBuilder-Morphic to project The Trunk:
http://source.squeak.org/trunk/ToolBuilder-Morphic-mt.95.mcz

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

Name: ToolBuilder-Morphic-mt.95
Author: mt
Time: 7 March 2015, 12:12:08.671 pm
UUID: f31dcf42-ecf7-8f41-9627-091e9f980483
Ancestors: ToolBuilder-Morphic-mt.94

Pluggable tree morph bug-fixed and extended to understand simple selections and custom node classes. Its companion -- PluggableTreeItemNode -- now speaks #parent and has a stub for #refresh.

Preparation for refactored object explorer.

=============== Diff against ToolBuilder-Morphic-mt.94 ===============

Item was changed:
  ----- Method: MorphicToolBuilder>>buildPluggableTree: (in category 'pluggable widgets') -----
  buildPluggableTree: aSpec
  | widget |
  widget := self treeClass new.
  self register: widget id: aSpec name.
  widget model: aSpec model.
  widget getSelectedPathSelector: aSpec getSelectedPath.
  widget setSelectedSelector: aSpec setSelected.
+ widget getSelectedSelector: aSpec getSelected.
+ widget setSelectedParentSelector: aSpec setSelectedParent.
  widget getChildrenSelector: aSpec getChildren.
  widget hasChildrenSelector: aSpec hasChildren.
  widget getLabelSelector: aSpec label.
  widget getIconSelector: aSpec icon.
  widget getHelpSelector: aSpec help.
  widget getMenuSelector: aSpec menu.
  widget keystrokeActionSelector: aSpec keyPress.
+ widget nodeClass: aSpec nodeClass.
  widget getRootsSelector: aSpec roots.
  widget autoDeselect: aSpec autoDeselect.
  widget dropItemSelector: aSpec dropItem.
  widget wantsDropSelector: aSpec dropAccept.
  widget dragItemSelector: aSpec dragItem.
+ widget columns: aSpec columns.
  self setFrame: aSpec frame in: widget.
  parent ifNotNil:[self add: widget to: parent].
  " panes ifNotNil:[
  aSpec roots ifNotNil:[panes add: aSpec roots].
  ]. "
  ^widget!

Item was changed:
  ListItemWrapper subclass: #PluggableTreeItemNode
+ instanceVariableNames: 'parent'
- instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
  category: 'ToolBuilder-Morphic'!
 
+ !PluggableTreeItemNode commentStamp: 'mt 3/7/2015 09:15' prior: 0!
+ Tree item for PluggableTreeMorph. My model is the tree morph.!
- !PluggableTreeItemNode commentStamp: 'ar 2/12/2005 04:37' prior: 0!
- Tree item for PluggableTreeMorph.!

Item was added:
+ ----- Method: PluggableTreeItemNode>>parent (in category 'accessing') -----
+ parent
+ ^ parent!

Item was added:
+ ----- Method: PluggableTreeItemNode>>parent: (in category 'accessing') -----
+ parent: aNode
+ parent := aNode.!

Item was added:
+ ----- Method: PluggableTreeItemNode>>refresh (in category 'as yet unclassified') -----
+ refresh
+ "Todo. See ObjectExplorerWrapper >> #refresh."!

Item was changed:
  SimpleHierarchicalListMorph subclass: #PluggableTreeMorph
+ instanceVariableNames: 'rootWrappers selectedWrapper getRootsSelector getChildrenSelector hasChildrenSelector getLabelSelector getIconSelector getSelectedPathSelector setSelectedParentSelector getHelpSelector dropItemSelector wantsDropSelector dragItemSelector nodeClass'
- instanceVariableNames: 'roots selectedWrapper getRootsSelector getChildrenSelector hasChildrenSelector getLabelSelector getIconSelector getSelectedPathSelector setSelectedSelector getHelpSelector dropItemSelector wantsDropSelector dragItemSelector'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'ToolBuilder-Morphic'!
 
  !PluggableTreeMorph commentStamp: 'ar 2/12/2005 04:38' prior: 0!
  A pluggable tree morph.!

Item was changed:
  ----- Method: PluggableTreeMorph>>contentsOfNode: (in category 'node access') -----
  contentsOfNode: node
+
  | children |
  getChildrenSelector ifNil:[^#()].
  children := model perform: getChildrenSelector with: node item.
+ ^children collect: [:item|
+ (self nodeClass with: item model: self) parent: node]!
- ^children collect:[:item| PluggableTreeItemNode with: item model: self]!

Item was added:
+ ----- Method: PluggableTreeMorph>>getCurrentSelectionItem (in category 'selection') -----
+ getCurrentSelectionItem
+ "Our models are supposed to return real objects, not wrappers. See PluggableTreeItemNode."
+
+ | selectedObject |
+ selectedObject := self getSelectedSelector
+ ifNil: [^ nil]
+ ifNotNil: [:symbol | model perform: symbol].
+ ^ scroller submorphs
+ detect: [:each | each complexContents item = selectedObject]
+ ifFound: [:each | each complexContents]
+ ifNone: [nil]!

Item was added:
+ ----- Method: PluggableTreeMorph>>getSelectedSelector (in category 'accessing') -----
+ getSelectedSelector
+ ^getSelectionSelector!

Item was added:
+ ----- Method: PluggableTreeMorph>>getSelectedSelector: (in category 'accessing') -----
+ getSelectedSelector: aSymbol
+ getSelectionSelector := aSymbol.!

Item was added:
+ ----- Method: PluggableTreeMorph>>nodeClass (in category 'accessing') -----
+ nodeClass
+ ^ nodeClass ifNil: [PluggableTreeItemNode]!

Item was added:
+ ----- Method: PluggableTreeMorph>>nodeClass: (in category 'accessing') -----
+ nodeClass: aListWrapperClass
+ nodeClass := aListWrapperClass.!

Item was removed:
- ----- Method: PluggableTreeMorph>>roots (in category 'accessing') -----
- roots
- ^roots!

Item was removed:
- ----- Method: PluggableTreeMorph>>roots: (in category 'accessing') -----
- roots: anArray
- roots := anArray collect:[:item| PluggableTreeItemNode with: item model: self].
- self list: roots.!

Item was changed:
+ ----- Method: PluggableTreeMorph>>selectPath:in: (in category 'selection') -----
- ----- Method: PluggableTreeMorph>>selectPath:in: (in category 'updating') -----
  selectPath: path in: listItem
  path isEmpty ifTrue: [^self setSelectedMorph: nil].
  listItem withSiblingsDo: [:each |
  (each complexContents item = path first) ifTrue: [
  each isExpanded ifFalse: [
  each toggleExpandedState.
  self adjustSubmorphPositions.
  ].
  each changed.
  path size = 1 ifTrue: [
  ^self setSelectedMorph: each
  ].
  each firstChild ifNil: [^self setSelectedMorph: nil].
  ^self selectPath: path allButFirst in: each firstChild
  ].
  ].
  ^self setSelectedMorph: nil
 
  !

Item was changed:
  ----- Method: PluggableTreeMorph>>setSelectedMorph: (in category 'selection') -----
  setSelectedMorph: aMorph
  selectedWrapper := aMorph complexContents.
+
+ "Let the model now about the selected object, not wrapper."
+ setSelectionSelector ifNotNil: [:symbol |
- self selection: selectedWrapper.
- setSelectedSelector ifNotNil:[
  model
+ perform: symbol
+ with: (selectedWrapper ifNotNil: [:w | w item])].
+
+ "The model may not have access to the parent object in terms of this tree structure."
+ setSelectedParentSelector ifNotNil: [:symbol |
+ model
+ perform: symbol
+ with: (selectedWrapper ifNotNil: [:w | w parent ifNotNil: [:pw | pw item]])].!
- perform: setSelectedSelector
- with: (selectedWrapper ifNotNil:[selectedWrapper item]).
- ].!

Item was added:
+ ----- Method: PluggableTreeMorph>>setSelectedParentSelector (in category 'accessing') -----
+ setSelectedParentSelector
+ ^ setSelectedParentSelector!

Item was added:
+ ----- Method: PluggableTreeMorph>>setSelectedParentSelector: (in category 'accessing') -----
+ setSelectedParentSelector: aSymbol
+ setSelectedParentSelector := aSymbol.!

Item was changed:
  ----- Method: PluggableTreeMorph>>setSelectedSelector (in category 'accessing') -----
  setSelectedSelector
+ ^setSelectionSelector!
- ^setSelectedSelector!

Item was changed:
  ----- Method: PluggableTreeMorph>>setSelectedSelector: (in category 'accessing') -----
  setSelectedSelector: aSymbol
+ setSelectionSelector := aSymbol!
- setSelectedSelector := aSymbol!

Item was changed:
  ----- Method: PluggableTreeMorph>>update: (in category 'updating') -----
  update: what
  what ifNil:[^self].
  what == getRootsSelector ifTrue:[
+ self wrapRoots: (model perform: getRootsSelector).
+ ^ self].
+
- self roots: (model perform: getRootsSelector)
- ].
  what == getSelectedPathSelector ifTrue:[
+ self
+ selectPath: (model perform: getSelectedPathSelector)
+ in: (scroller submorphs at: 1 ifAbsent: [^self]).
+ ^ self].
+
+ what == #expandRootsRequested ifTrue: [
+ self expandRoots.
+ ^ self].
+
+ super update: what.
+ !
- ^self selectPath: (model perform: getSelectedPathSelector)
- in: (scroller submorphs at: 1 ifAbsent: [^self])
- ].
- ^super update: what!

Item was added:
+ ----- Method: PluggableTreeMorph>>update:with: (in category 'updating') -----
+ update: what with: anObject
+
+ super update: what with: anObject.
+
+ what == #objectChanged ifTrue: [
+ self updateFromChangedObject: anObject].!

Item was added:
+ ----- Method: PluggableTreeMorph>>updateFromChangedObject: (in category 'updating') -----
+ updateFromChangedObject: anObject
+
+ scroller submorphs
+ detect: [:morph | morph complexContents item == anObject]
+ ifFound: [:morph | self updateMorph: morph]
+ ifNone: ["Ignore the request. Object may not be visible anyway."].!

Item was added:
+ ----- Method: PluggableTreeMorph>>updateMorph: (in category 'updating') -----
+ updateMorph: morph
+
+ morph complexContents refresh.
+ morph refresh.
+
+ morph isExpanded
+ ifFalse: [self changed]
+ ifTrue: [
+ morph
+ toggleExpandedState;
+ toggleExpandedState.
+ self adjustSubmorphPositions].
+ !

Item was added:
+ ----- Method: PluggableTreeMorph>>updateNode: (in category 'node access') -----
+ updateNode: node
+ !

Item was added:
+ ----- Method: PluggableTreeMorph>>wrapRoots: (in category 'updating') -----
+ wrapRoots: someObjects
+
+ rootWrappers := someObjects collect: [:item|
+ self nodeClass with: item model: self].
+ self list: rootWrappers.!