The Trunk: ToolBuilder-Morphic-ar.49.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-ar.49.mcz

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

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

Name: ToolBuilder-Morphic-ar.49
Author: ar
Time: 23 January 2010, 2:43:44.034 pm
UUID: 411cb04c-628b-6644-99c5-95f902ffeac1
Ancestors: ToolBuilder-Morphic-Igor.Stasenko.48, ToolBuilder-Morphic-mtf.46

Merging ToolBuilder-Morphic-mtf.46:

Merged in the Cobalt version of ToolBuilder. Just makes use of the new properties and the fact that any widget can now have help texs

=============== Diff against ToolBuilder-Morphic-Igor.Stasenko.48 ===============

Item was added:
+ ----- Method: MorphicToolBuilder>>buildHelpFor:spec: (in category 'pluggable widgets') -----
+ buildHelpFor: widget spec: aSpec
+ aSpec help
+ ifNotNil: [widget setBalloonText: aSpec help]!

Item was added:
+ ----- Method: PluggableTreeMorph>>acceptDroppingMorph:event: (in category 'morphic') -----
+ acceptDroppingMorph: aMorph event: evt
+ | item dropTarget |
+ dropItemSelector ifNil:[^self].
+ item := aMorph passenger.
+ dropTarget := (self itemFromPoint: evt position) withoutListWrapper.
+ model perform: dropItemSelector with: item with: dropTarget.
+ evt hand releaseMouseFocus: self.
+ Cursor normal show.
+ !

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

Item was added:
+ ----- Method: PluggableTreeMorph>>wantsDroppedMorph:event: (in category 'morphic') -----
+ wantsDroppedMorph: aMorph event: anEvent
+ aMorph dragTransferType == #dragTransferPlus ifFalse:[^false].
+ dropItemSelector ifNil:[^false].
+ wantsDropSelector ifNil:[^true].
+ ^ (model perform: wantsDropSelector with: aMorph passenger) == true.!

Item was added:
+ PluggableSystemWindow subclass: #PluggableDialogWindow
+ instanceVariableNames: 'statusValue'
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'ToolBuilder-Morphic'!

Item was changed:
  ----- Method: MorphicToolBuilder>>buildPluggableList: (in category 'pluggable widgets') -----
  buildPluggableList: aSpec
  | widget listClass getIndex setIndex |
  aSpec getSelected ifNil:[
  listClass := self listClass.
  getIndex := aSpec getIndex.
  setIndex := aSpec setIndex.
  ] ifNotNil:[
  listClass := self listByItemClass.
  getIndex := aSpec getSelected.
  setIndex := aSpec setSelected.
  ].
  widget := listClass on: aSpec model
  list: aSpec list
  selected: getIndex
  changeSelected: setIndex
  menu: aSpec menu
  keystroke: aSpec keyPress.
  self register: widget id: aSpec name.
+ widget getListElementSelector: aSpec listItem.
+ widget getListSizeSelector: aSpec listSize.
  widget doubleClickSelector: aSpec doubleClick.
  widget dragItemSelector: aSpec dragItem.
  widget dropItemSelector: aSpec dropItem.
  widget wantsDropSelector: aSpec dropAccept.
  widget autoDeselect: aSpec autoDeselect.
+ self buildHelpFor: widget spec: aSpec.
  self setFrame: aSpec frame in: widget.
  parent ifNotNil:[self add: widget to: parent].
  panes ifNotNil:[
  aSpec list ifNotNil:[panes add: aSpec list].
  ].
  ^widget!

Item was changed:
  ----- Method: MorphicToolBuilder>>buildPluggableText: (in category 'pluggable widgets') -----
  buildPluggableText: aSpec
  | widget |
  widget := self textPaneClass on: aSpec model
  text: aSpec getText
  accept: aSpec setText
  readSelection: aSpec selection
  menu: aSpec menu.
  widget askBeforeDiscardingEdits: aSpec askBeforeDiscardingEdits.
  widget font: Preferences standardCodeFont.
  self register: widget id: aSpec name.
  widget getColorSelector: aSpec color.
+ self buildHelpFor: widget spec: aSpec.
  self setFrame: aSpec frame in: widget.
  parent ifNotNil:[self add: widget to: parent].
  widget borderColor: Color lightGray.
  widget color: Color white.
  ^widget!

Item was added:
+ ----- Method: PluggableDialogWindow>>statusValue (in category 'as yet unclassified') -----
+ statusValue
+ ^statusValue!

Item was added:
+ ----- Method: MorphicUIManager>>confirm:trueChoice:falseChoice: (in category 'ui requests') -----
+ confirm: queryString trueChoice: trueChoice falseChoice: falseChoice
+ "Put up a yes/no menu with caption queryString. The actual wording for the two choices will be as provided in the trueChoice and falseChoice parameters. Answer true if the response is the true-choice, false if it's the false-choice.
+ This is a modal question -- the user must respond one way or the other."
+ ^ UserDialogBoxMorph confirm: queryString trueChoice: trueChoice falseChoice: falseChoice !

Item was changed:
  ----- Method: PluggableButtonMorphPlus>>enabled (in category 'accessing') -----
  enabled
+ ^ enabled ifNil: [enabled := true]!
- ^enabled!

Item was changed:
  ----- Method: PluggableListMorphByItemPlus>>getCurrentSelectionIndex (in category 'model access') -----
  getCurrentSelectionIndex
  "Answer the index of the current selection."
  | item |
  getIndexSelector == nil ifTrue: [^ 0].
  item := model perform: getIndexSelector.
+ ^ itemList findFirst: [ :x | x = item]
- ^ list findFirst: [ :x | x = item]
  !

Item was added:
+ ----- Method: PluggableDialogWindow>>statusValue: (in category 'as yet unclassified') -----
+ statusValue: val
+ statusValue := val!

Item was added:
+ ----- Method: PluggableTreeMorph>>dragItemSelector: (in category 'accessing') -----
+ dragItemSelector: aSymbol
+ dragItemSelector := aSymbol.
+ aSymbol ifNotNil:[self dragEnabled: true].!

Item was changed:
  ----- Method: MorphicToolBuilder>>buildPluggableButton: (in category 'pluggable widgets') -----
  buildPluggableButton: aSpec
  | widget label state action enabled |
  label := aSpec label.
  state := aSpec state.
  action := aSpec action.
  widget := self buttonClass on: aSpec model
  getState: (state isSymbol ifTrue:[state])
  action: nil
  label: (label isSymbol ifTrue:[label]).
  self register: widget id: aSpec name.
  enabled := aSpec enabled.
  enabled isSymbol
  ifTrue:[widget getEnabledSelector: enabled]
  ifFalse:[widget enabled:enabled].
  widget action: action.
  widget getColorSelector: aSpec color.
  widget offColor: Color white..
+ self buildHelpFor: widget spec: aSpec.
- aSpec help ifNotNil:[widget setBalloonText: aSpec help].
  (label isSymbol or:[label == nil]) ifFalse:[widget label: label].
  self setFrame: aSpec frame in: widget.
  parent ifNotNil:[self add: widget to: parent].
  ^widget!

Item was changed:
  ----- Method: MorphicToolBuilder>>buildPluggableWindow: (in category 'pluggable widgets') -----
  buildPluggableWindow: aSpec
  | widget children label |
  aSpec layout == #proportional ifFalse:[
  "This needs to be implemented - probably by adding a single pane and then the rest"
  ^self error: 'Not implemented'.
  ].
  widget := self windowClass new.
  self register: widget id: aSpec name.
  widget model: aSpec model.
  (label := aSpec label) ifNotNil:[
  label isSymbol
  ifTrue:[widget getLabelSelector: label]
  ifFalse:[widget setLabel: label]].
  children := aSpec children.
  children isSymbol ifTrue:[
  widget getChildrenSelector: children.
  widget update: children.
  children := #().
  ].
  widget closeWindowSelector: aSpec closeAction.
  panes := OrderedCollection new.
  self buildAll: children in: widget.
+ self buildHelpFor: widget spec: aSpec.
  widget bounds: (RealEstateAgent
  initialFrameFor: widget
  initialExtent: (aSpec extent ifNil:[widget initialExtent])
  world: self currentWorld).
  widget setUpdatablePanesFrom: panes.
  ^widget!

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 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 getRootsSelector: aSpec roots.
  widget autoDeselect: aSpec autoDeselect.
  widget dropItemSelector: aSpec dropItem.
  widget wantsDropSelector: aSpec dropAccept.
+ widget dragItemSelector: aSpec dragItem.
  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:
  ----- Method: MorphicToolBuilder>>setFrame:in: (in category 'private') -----
  setFrame: aRectangle in: widget
  | frame |
  aRectangle ifNil:[^nil].
+ frame := aRectangle isRectangle
+ ifTrue: [self asFrame: aRectangle]
+ ifFalse: [aRectangle]. "assume LayoutFrame"
- frame := self asFrame: aRectangle.
  widget layoutFrame: frame.
  widget hResizing: #spaceFill; vResizing: #spaceFill.
  (parent isSystemWindow) ifTrue:[
  widget borderWidth: 2; borderColor: #inset.
  ].!

Item was changed:
  ----- Method: MorphicToolBuilder>>buildPluggablePanel: (in category 'pluggable widgets') -----
  buildPluggablePanel: aSpec
+ | widget children frame |
- | widget children |
  widget := self panelClass new.
  self register: widget id: aSpec name.
  widget model: aSpec model.
  widget color: Color transparent.
  widget clipSubmorphs: true.
  children := aSpec children.
  children isSymbol ifTrue:[
  widget getChildrenSelector: children.
  widget update: children.
  children := #().
  ].
  self buildAll: children in: widget.
+ self buildHelpFor: widget spec: aSpec.
  self setFrame: aSpec frame in: widget.
  parent ifNotNil:[self add: widget to: parent].
  self setLayout: aSpec layout in: widget.
  widget layoutInset: 0.
  widget borderWidth: 0.
+ widget submorphsDo:[:sm|
- widget submorphsDo:[:sm| | frame |
  (frame := sm layoutFrame) ifNotNil:[
  (frame rightFraction = 0 or:[frame rightFraction = 1])
  ifFalse:[frame rightOffset:1].
  (frame bottomFraction = 0 or:[frame bottomFraction = 1])
  ifFalse:[frame bottomOffset: 1]]].
  widget color: Color transparent.
  ^widget!

Item was added:
+ ----- Method: PluggableTreeMorph>>startDrag: (in category 'morphic') -----
+ startDrag: evt
+ | ddm itemMorph passenger |
+ self dragEnabled
+ ifTrue: [itemMorph := scroller submorphs
+ detect: [:any | any highlightedForMouseDown]
+ ifNone: []].
+ (itemMorph isNil
+ or: [evt hand hasSubmorphs])
+ ifTrue: [^ self].
+ itemMorph highlightForMouseDown: false.
+ itemMorph ~= self selectedMorph
+ ifTrue: [self setSelectedMorph: itemMorph].
+ passenger := self model perform: dragItemSelector with: itemMorph withoutListWrapper.
+ passenger
+ ifNotNil: [ddm := TransferMorph withPassenger: passenger from: self.
+ ddm dragTransferType: #dragTransferPlus.
+ Preferences dragNDropWithAnimation
+ ifTrue: [self model dragAnimationFor: itemMorph transferMorph: ddm].
+ evt hand grabMorph: ddm].
+ evt hand releaseMouseFocus: self!

Item was changed:
  ----- Method: MorphicToolBuilder>>buildPluggableMultiSelectionList: (in category 'pluggable widgets') -----
  buildPluggableMultiSelectionList: aSpec
  | widget listClass |
  aSpec getSelected ifNotNil:[^self error:'There is no PluggableListMorphOfManyByItem'].
  listClass := self multiSelectListClass.
  widget := listClass on: aSpec model
  list: aSpec list
  primarySelection: aSpec getIndex
  changePrimarySelection: aSpec setIndex
  listSelection: aSpec getSelectionList
  changeListSelection: aSpec setSelectionList
  menu: aSpec menu.
  self register: widget id: aSpec name.
  widget keystrokeActionSelector: aSpec keyPress.
+ widget getListElementSelector: aSpec listItem.
+ widget getListSizeSelector: aSpec listSize.
+ self buildHelpFor: widget spec: aSpec.
  self setFrame: aSpec frame in: widget.
  parent ifNotNil:[self add: widget to: parent].
  panes ifNotNil:[
  aSpec list ifNotNil:[panes add: aSpec list].
  ].
  ^widget!

Item was changed:
  ----- Method: PluggableTreeMorph>>dropItemSelector: (in category 'accessing') -----
  dropItemSelector: aSymbol
+ dropItemSelector := aSymbol.
+ aSymbol ifNotNil:[self dropEnabled: true].!
- dropItemSelector := aSymbol!

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