Tools__ChangeList.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sun, 29 Jan 2012 15:33:37 +0000
branchjv
changeset 12125 0c49a3b13e43
parent 12123 4bde08cebd48
child 12128 a7ff7d66ee85
permissions -rw-r--r--
Merged with /trunk

"
 COPYRIGHT (c) 2010 by Jan Vrany, SWING Research Group. CTU in Prague
              All Rights Reserved

Permission is hereby granted, free of charge, to any person
obtaining a copy of this software and associated documentation
files (the 'Software'), to deal in the Software without
restriction, including without limitation the rights to use,
copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the
Software is furnished to do so, subject to the following
conditions:

The above copyright notice and this permission notice shall be
included in all copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
OTHER DEALINGS IN THE SOFTWARE.
"
"{ Package: 'stx:libtool' }"

"{ NameSpace: Tools }"

BrowserListWithFilter subclass:#ChangeList
	instanceVariableNames:'listHolder showRemovedHolder showSameHolder allowRemoveHolder
		allowAcceptHolder'
	classVariableNames:'LastSelectionConditionString'
	poolDictionaries:''
	category:'Interface-Browsers-ChangeSet'
!

HierarchicalItem subclass:#ListEntry
	instanceVariableNames:'change application x'
	classVariableNames:''
	poolDictionaries:''
	privateIn:ChangeList
!

!ChangeList class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2010 by Jan Vrany, SWING Research Group. CTU in Prague
              All Rights Reserved

Permission is hereby granted, free of charge, to any person
obtaining a copy of this software and associated documentation
files (the 'Software'), to deal in the Software without
restriction, including without limitation the rights to use,
copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the
Software is furnished to do so, subject to the following
conditions:

The above copyright notice and this permission notice shall be
included in all copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
OTHER DEALINGS IN THE SOFTWARE.
"
! !

!ChangeList class methodsFor:'image specs'!

iconEqual
    ^ ToolbarIconLibrary iconEqual12x12

    "Modified: / 31-08-2011 / 10:52:34 / cg"
!

iconEqualGrayed
    ^ ToolbarIconLibrary iconEqualGray12x12

    "Modified: / 31-08-2011 / 10:54:00 / cg"
!

iconMinus
    ^ ToolbarIconLibrary iconMinus12x12

    "Modified: / 31-08-2011 / 10:51:26 / cg"
!

iconMinusGrayed
    ^ ToolbarIconLibrary iconMinusGray12x12

    "Modified: / 31-08-2011 / 10:54:40 / cg"
!

iconPlus
    ^ ToolbarIconLibrary iconPlus12x12

    "Modified: / 31-08-2011 / 10:51:39 / cg"
!

iconPlusGrayed
    ^ ToolbarIconLibrary iconPlusGray12x12

    "Modified: / 31-08-2011 / 10:54:46 / cg"
! !

!ChangeList class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the UIPainter may not be able to read the specification."

    "
     UIPainter new openOnClass:Tools::ChangeList andSelector:#windowSpec
     Tools::ChangeList new openInterface:#windowSpec
     Tools::ChangeList open
    "

    <resource: #canvas>

    ^ 
     #(FullSpec
        name: windowSpec
        window: 
       (WindowSpec
          label: 'Change List'
          name: 'Change List'
          min: (Point 10 10)
          bounds: (Rectangle 0 0 300 300)
        )
        component: 
       (SpecCollection
          collection: (
           (SelectionInListModelViewSpec
              name: 'List'
              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
              model: selectionHolder
              menu: menuHolderWithShowFilter
              hasHorizontalScrollBar: true
              hasVerticalScrollBar: true
              listModel: listHolder
              multipleSelectOk: true
              useIndex: false
              highlightMode: line
              doubleClickSelector: selectionDoubleclicked
              postBuildCallback: postBuildListView:
            )
           (InputFieldSpec
              name: 'Filter'
              layout: (LayoutFrame 0 0 0 0 0 1 26 0)
              initiallyInvisible: true
              model: filterPatternHolder
              immediateAccept: true
              acceptOnLeave: false
              acceptOnReturn: false
              acceptOnTab: false
              acceptOnPointerLeave: false
              emptyFieldReplacementText: 'Search Filter...'
              usePreferredHeight: true
              useDynamicPreferredHeight: true
              postBuildCallback: postBuildFilterView:
            )
           )
         
        )
      )

    "Modified: / 29-11-2011 / 15:52:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ChangeList class methodsFor:'menu specs'!

listMenu
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the MenuEditor may not be able to read the specification."


    "
     MenuEditor new openOnClass:Tools::ChangeList andSelector:#listMenu
     (Menu new fromLiteralArrayEncoding:(Tools::ChangeList listMenu)) startUp
    "

    <resource: #menu>

    ^ 
     #(Menu
        (
         (MenuItem
            enabled: hasChangeSelectedAndNotRemoved
            label: 'Apply'
            itemValue: listMenuApply
            translateLabel: true
            isVisible: allowAcceptHolder
            shortcutKey: Accept
          )
         (MenuItem
            label: 'Apply all'
            itemValue: listMenuApplyAll
            translateLabel: true
            isVisible: allowAcceptHolder
          )
         (MenuItem
            enabled: hasSingleChangeSelectedAndCanBrowse
            label: 'Browse'
            itemValue: listMenuBrowse
            translateLabel: true
          )
         (MenuItem
            label: '-'
          )
         (MenuItem
            label: 'Delete'
            itemValue: listMenuDeleteSelection
            nameKey: Delete
            translateLabel: true
            isVisible: allowRemoveHolder
            shortcutKey: Delete
          )
         (MenuItem
            label: '-'
            isVisible: allowRemoveHolder
          )
         (MenuItem
            label: 'Select...'
            translateLabel: true
            submenu: 
           (Menu
              (
               (MenuItem
                  label: 'Select same'
                  itemValue: listMenuSelectSame
                  translateLabel: true
                )
               (MenuItem
                  label: 'Select additions (new classes/methods)'
                  itemValue: listMenuSelectAdditions
                  translateLabel: true
                )
               (MenuItem
                  label: 'Select removals'
                  itemValue: listMenuSelectRemovals
                  translateLabel: true
                )
               (MenuItem
                  label: '-'
                )
               (MenuItem
                  label: 'Select all'
                  itemValue: listMenuSelectAll
                  translateLabel: true
                )
               (MenuItem
                  label: 'Select none'
                  itemValue: listMenuSelectNone
                  translateLabel: true
                )
               (MenuItem
                  label: '-'
                )
               (MenuItem
                  label: 'Select using block'
                  itemValue: listMenuSelectUsingBlock
                  translateLabel: true
                )
               )
              nil
              nil
            )
          )
         (MenuItem
            label: '-'
          )
         (MenuItem
            label: 'Show Deleted'
            translateLabel: true
            isVisible: allowRemoveHolder
            indication: showRemovedHolder
          )
         (MenuItem
            label: 'Inspect change'
            itemValue: listMenuInspect
            translateLabel: true
          )
         )
        nil
        nil
      )
! !

!ChangeList class methodsFor:'plugIn spec'!

aspectSelectors
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this. If it is corrupted,
     the UIPainter may not be able to read the specification."

    "Return a description of exported aspects;
     these can be connected to aspects of an embedding application
     (if this app is embedded in a subCanvas)."

    ^ #(
        #allowAcceptHolder
        #allowRemoveHolder

        #inGeneratorHolder
        #menuHolder
        #outGeneratorHolder
        #selectionHolder
        #showRemovedHolder
        #showSameHolder
      ).

    "Modified: / 24-01-2012 / 19:54:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ChangeList methodsFor:'accessing'!

allowAccept
    ^ self allowAcceptHolder value

    "Created: / 24-01-2012 / 19:52:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

allowAccept: aBoolean
    ^ self allowAcceptHolder value: aBoolean

    "Created: / 24-01-2012 / 19:52:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

allowRemoved
    ^ self allowRemoveHolder value ? true

    "Created: / 05-12-2009 / 14:28:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

list
    ^ listHolder value

    "Created: / 05-12-2009 / 14:48:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 27-12-2011 / 14:18:25 / cg"
!

selection

    ^self selectionHolder value

    "Created: / 05-12-2009 / 14:48:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

selectionIndices
    |sel|

    (sel := self selectionHolder value) isEmptyOrNil ifTrue:[^ #()].
    ^ sel collect:[:each | self list identityIndexOf:each].

    "Created: / 05-12-2009 / 14:48:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 27-12-2011 / 10:56:20 / cg"
!

showRemoved

    ^self showRemovedHolder value ? true

    "Created: / 05-12-2009 / 14:28:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ChangeList methodsFor:'actions'!

selectionDoubleclicked

    self listMenuBrowse
"/    | app |
"/
"/    self selection do:
"/        [:e|e removed: e removed not].
"/    ((app := self masterApplication) respondsTo: #redrawChangeListViews)
"/        ifTrue:[app redrawChangeListViews].

    "Modified: / 24-01-2012 / 22:01:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ChangeList methodsFor:'aspects'!

allowAcceptHolder
    "return/create the valueHolder 'acceptEnabledHolder'"

    allowAcceptHolder isNil ifTrue:[
        allowAcceptHolder := ValueHolder with:nil "defaultValue here".
    ].
    ^ allowAcceptHolder

    "Created: / 24-01-2012 / 19:53:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

allowAcceptHolder:something
    "set the 'allowAcceptHolder' value holder (automatically generated)"

    allowAcceptHolder := something.
!

allowRemoveHolder
    "return/create the 'allowRemoveHolder' value holder (automatically generated)"
    
    allowRemoveHolder isNil ifTrue:[
        allowRemoveHolder := ValueHolder with:true.
        allowRemoveHolder addDependent:self.
    ].
    ^ allowRemoveHolder

    "Modified (comment): / 24-01-2012 / 19:44:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

allowRemoveHolder:something 
    "set the 'showRemovedHolder' value holder (automatically generated)"
    
    |oldValue newValue|

    allowRemoveHolder notNil ifTrue:[
        oldValue := allowRemoveHolder value.
        allowRemoveHolder removeDependent:self.
    ].
    allowRemoveHolder := something.
    allowRemoveHolder notNil ifTrue:[
        allowRemoveHolder addDependent:self.
    ].
    newValue := allowRemoveHolder value.
    oldValue ~~ newValue ifTrue:[
        self 
            update:#value
            with:newValue
            from:allowRemoveHolder.
    ].
!

listHolder
    listHolder isNil ifTrue:[
        listHolder := ValueHolder new.
    ].
    ^ listHolder
!

showRemovedHolder
    "return/create the 'showRemovedHolder' value holder (automatically generated)"

    showRemovedHolder isNil ifTrue:[
        showRemovedHolder := ValueHolder with: true.
        showRemovedHolder addDependent: self.
    ].
    ^ showRemovedHolder
!

showRemovedHolder:something
    "set the 'showRemovedHolder' value holder (automatically generated)"

    |oldValue newValue|

    showRemovedHolder notNil ifTrue:[
        oldValue := showRemovedHolder value.
        showRemovedHolder removeDependent:self.
    ].
    showRemovedHolder := something.
    showRemovedHolder notNil ifTrue:[
        showRemovedHolder addDependent:self.
    ].
    newValue := showRemovedHolder value.
    oldValue ~~ newValue ifTrue:[
        self update:#value with:newValue from:showRemovedHolder.
    ].
!

showSameHolder
    "return/create the 'showSameHolder' value holder (automatically generated)"

    showSameHolder isNil ifTrue:[
        showSameHolder := ValueHolder with: true.
        showSameHolder addDependent:self.
    ].
    ^ showSameHolder

    "Modified: / 04-08-2011 / 18:39:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

showSameHolder:something
    "set the 'showSameHolder' value holder (automatically generated)"

    |oldValue newValue|

    showSameHolder notNil ifTrue:[
        oldValue := showSameHolder value.
        showSameHolder removeDependent:self.
    ].
    showSameHolder := something.
    showSameHolder notNil ifTrue:[
        showSameHolder addDependent:self.
    ].
    newValue := showSameHolder value.
    oldValue ~~ newValue ifTrue:[
        self update:#value with:newValue from:showSameHolder.
    ].
! !

!ChangeList methodsFor:'change & update'!

update: aspect with: param from: sender

    sender == selectionHolder ifTrue:[
        self selectionChanged.
        ^self
    ].
    sender == showSameHolder ifTrue:[
        self updateList
    ].
    sender == showRemovedHolder ifTrue:[
        self updateList
    ].

    ^super update: aspect with: param from: sender

    "Created: / 24-10-2009 / 19:47:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 27-12-2011 / 14:20:30 / cg"
! !

!ChangeList methodsFor:'event processing'!

buttonPress:button x:x y:y view:aView

    | itemIndex item |

    button ~= 1 ifTrue:[^aView buttonPress:button x:x y:y].

    itemIndex := aView yVisibleToLineNr:y.
    itemIndex isNil ifTrue:[^self].
    itemIndex == 0 ifTrue:[^self].
    itemIndex > aView list size ifTrue:[^self].
    item := aView list at: itemIndex.

    ((aView left + x) between: (item x) and: (item x + 16))
        ifFalse:[^aView buttonPress:button x:x y:y].

    item removed: item removed not.
    aView invalidate

    "Created: / 08-12-2009 / 14:12:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-11-2011 / 14:55:41 / cg"
!

handlesButtonPress:button inView:aView

    ^listView scrolledView == aView

    "Created: / 08-12-2009 / 14:08:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ChangeList methodsFor:'generators'!

makeGenerator
    "Superclass Tools::BrowserList says that I am responsible to implement this method"

    ^Iterator on:
        [:whatToDo|
        selectionHolder value do:
            [:changeListItem| | change |
            change := changeListItem change.
            change isCompositeChange ifTrue:
                [change changes do: whatToDo]]].

    "Modified: / 24-07-2009 / 23:00:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 24-10-2009 / 20:00:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ChangeList methodsFor:'hooks'!

postBuildListView: aView

    super postBuildListView: aView.
    listView scrolledView delegate: self.

    "Created: / 29-11-2011 / 14:56:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ChangeList methodsFor:'initialization'!

initialize

    super initialize.
    menuHolder := [self menuFor: #listMenu].

    "Created: / 29-10-2010 / 12:50:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ChangeList methodsFor:'menu actions'!

listMenuApply

    self acceptEnabled ifFalse:[^self].

    self selectionHolder value do:[:e|e change apply].

    "Modified: / 24-10-2009 / 22:02:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

listMenuApplyAll

    self acceptEnabled ifFalse:[^self].

    self selection value do:
        [:e|e removed ifFalse:[e change apply]].

    "Created: / 05-12-2009 / 14:53:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

listMenuBrowse

    self listMenuBrowseChanges:
        ((self selectionHolder value ? #()) collect:[:e|e change])

    "Modified: / 24-01-2012 / 22:00:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

listMenuBrowseChanges: changes

    | classes methods methodsOnly |
    classes := Set new.
    methods := Set new.
    methodsOnly := true.
    changes do:
        [:each|
        each  isClassChange ifTrue:
            [each  changeClass ifNotNil:
                [classes add: each  changeClass.
                each isMethodCodeChange 
                    ifTrue:
                        [each changeMethod ifNotNil:
                            [methods add:each changeMethod]]
                    ifFalse:
                        [methodsOnly := false]]]].
    methodsOnly 
        ifTrue:
            [methods size = 1 
                ifTrue:[Smalltalk browserClass openInMethod: methods anyOne]
                ifFalse:[Smalltalk browserClass browseMethods: methods asArray title: 'Selected methods from changeset' sort: true]]
        ifFalse:
            [classes size = 1
                ifTrue:[Smalltalk browserClass browseClass: classes anyOne]
                ifFalse:[Smalltalk browserClass browseClasses: classes]]

    "Modified: / 24-10-2009 / 22:02:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 24-01-2012 / 22:00:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

listMenuDeleteSelection

    self selectionHolder value do:
        [:each|each removed: true].
    self updateList
!

listMenuInspect

    | selection |

    selection := self selectionHolder value collect:[:e|e change].
    selection size = 1
        ifTrue:[selection anyOne inspect]
        ifFalse:[selection inspect].

    "Modified: / 24-10-2009 / 22:02:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

listMenuSelectAdditions

    self listMenuSelectAllSuchThat:[:change|change delta = #+]
!

listMenuSelectAll

    self listMenuSelectAllSuchThat:[:change|true]
!

listMenuSelectAllSuchThat:conditionBlock 
    |newSelection|

    newSelection := self listHolder value 
                select:[:entry | conditionBlock value:entry change ].
    self selectionHolder value:newSelection
!

listMenuSelectNone

    self listMenuSelectAllSuchThat:[:change|false]
!

listMenuSelectRemovals

    self listMenuSelectAllSuchThat:[:change|change delta = #-]
!

listMenuSelectSame

    self listMenuSelectAllSuchThat:[:change|change delta = #=]
!

listMenuSelectUsingBlock

    |conditionBlockString conditionBlock dialog textHolder template|

    template :=
'[:change|
     "/ Define condition for selection below:
     "/ change is an instance of Change
     "/ change will be selected if and only if block returns true

    
     true"/always select the change
]
'.

    LastSelectionConditionString isNil ifTrue:[
        LastSelectionConditionString := template.
    ].


    textHolder := ValueHolder new.
    dialog := Dialog
                 forRequestText:(resources string:'Enter condition for selection')
                 lines:20
                 columns:70
                 initialAnswer:LastSelectionConditionString
                 model:textHolder.
    dialog addButton:(Button label:'Template' action:[textHolder value:template. textHolder changed:#value.]).
    dialog open.
    dialog accepted ifFalse:[^ self].

    conditionBlockString := textHolder value.
    LastSelectionConditionString := conditionBlockString.

    conditionBlock := Parser evaluate:conditionBlockString.
    conditionBlock isBlock ifFalse:[
        self error:'Bad selection block (syntax error?)'.
        ^ self
    ].

    self listMenuSelectAllSuchThat: conditionBlock
!

listMenuUndeleteSelection

    self selectionHolder value do:
        [:each|each removed: false].
    self updateList
! !

!ChangeList methodsFor:'private'!

application

    ^self

    "Created: / 05-12-2009 / 14:10:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

browserNameList

    ^'Change list'

    "Modified: / 24-07-2009 / 22:06:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

listEntryFor:chg 
    ^ListEntry change:chg application: self

    "Modified: / 05-12-2009 / 14:39:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

makeDependent

    "Modified: / 24-07-2009 / 22:06:32 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

makeIndependent

    "Modified: / 24-07-2009 / 22:06:37 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

parentOrModel

    ^self

    "Created: / 05-12-2009 / 14:14:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

updateList
    |inGenerator changeset newList |

    inGenerator := self inGeneratorHolder value.
    changeset := inGenerator ifNil:[ #() ] ifNotNil:[ inGenerator ].
    newList := changeset 
                select:
                    [:chg | 
                    (self showRemovedHolder value or:[ chg removed not ])
                        and:[self showSameHolder value or:[chg delta ~~ #=]]
                    ].
    newList := self filterList: newList.
    newList := newList collect:[:chg | self listEntryFor:chg ].
    self listHolder value ~= newList ifTrue:[
        self listHolder value: newList.
    ]

    "Modified: / 29-11-2011 / 15:38:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-12-2011 / 15:46:15 / cg"
! !

!ChangeList methodsFor:'queries'!

hasChangeSelected

    ^self selectionHolder value size > 0
!

hasChangeSelectedAndNotRemoved

    | selection |
    selection := self selectionHolder value ? #().
    ^selection size > 0 and:
        [selection allSatisfy:[:e|e removed not]].
!

hasSingleChangeSelected

    ^self selectionHolder value size = 1
!

hasSingleChangeSelectedAndCanBrowse


    self selectionHolder value ? #() do:
        [:each|
        (each change isClassChange and:
            [each change isMethodChange not
                or:[each change isMethodCodeChange]]) ifFalse:[^false]].
    ^true
! !

!ChangeList::ListEntry class methodsFor:'instance creation'!

change: aChange

    ^self new change: aChange

    "Created: / 24-07-2009 / 22:43:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

change: aChange application: anApplicationModel

    ^self new change: aChange; application: anApplicationModel

    "Created: / 05-12-2009 / 14:16:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

change: aChange parent: aChangeList

    ^self new change: aChange; parent: aChangeList

    "Created: / 25-07-2009 / 23:33:00 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ChangeList::ListEntry methodsFor:'accessing'!

application
    ^ application ifNil:[super application]

    "Modified: / 05-12-2009 / 14:16:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

application:anApplicationModel
    application := anApplicationModel.

    "Modified: / 05-12-2009 / 14:15:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

change
    ^ change
!

change:aChange
    self assert: ((aChange isKindOf: Change) or:[aChange isKindOf: RefactoryChange]).
    change := aChange.

    "Modified: / 25-07-2009 / 23:40:38 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified (format): / 04-12-2011 / 14:58:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

changeClass

    ^change changeClass
!

changeSource

    ^change changeSource

    "Created: / 19-07-2011 / 12:03:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

children

    children isNil ifTrue:[
        change isCompositeChange ifTrue:[
            children := OrderedCollection new: change changes size.
            change changes do:[:chg|
                ((self application showRemovedHolder value or:[ chg removed not ])
                    and:[self application showSameHolder value or:[chg delta ~~ #=]]) 
                        ifTrue:[
                            children add: ((self application listEntryFor: chg) parent: self)
                        ]
            ].
        ] ifFalse:[
            children :=  #()
        ]
    ].
    ^children

    "Created: / 25-07-2009 / 23:32:39 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified (format): / 18-11-2011 / 14:56:25 / cg"
    "Modified: / 04-12-2011 / 15:08:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

delta
    "/ obsolete: please use deltaDetail

    ^change delta

    "Created: / 29-10-2010 / 14:32:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 31-08-2011 / 10:30:02 / cg"
!

deltaDetail

    ^change deltaDetail

    "Created: / 29-10-2010 / 14:32:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 31-08-2011 / 10:29:21 / cg"
!

iconDelta

    | iconSelector |
    iconSelector := self iconSelector.
    iconSelector isNil ifTrue:[^nil].
    self removed ifTrue:[iconSelector := iconSelector , #Grayed].
    ^self application class perform: iconSelector asSymbol.

    "Created: / 05-12-2009 / 14:11:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-11-2011 / 14:56:33 / cg"
!

iconRemoved

    ^self removed 
        ifTrue: [self application class uncheckedIcon ]
        ifFalse:[self application class checkedIcon ]

    "Created: / 05-12-2009 / 14:11:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

imageSource

    ^change imageSource

    "Created: / 19-07-2011 / 12:03:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

label

    | label |
    label := change displayString.
    self removed ifTrue:[label := label asText colorizeAllWith: Color gray].
    ^label

    "Created: / 05-11-2008 / 08:20:02 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 25-07-2009 / 23:43:23 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 05-12-2009 / 14:46:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

removed
    ^ change removed
!

removed:aBoolean
    change removed: aBoolean.
!

source

    ^change source
!

x
    ^ x
! !

!ChangeList::ListEntry methodsFor:'displaying'!

displayLabel:aLabel h:lH on:aGC x:newX y:y h:h 

    | cx icon |
    cx := x := newX.
    self application allowRemoveHolder value ifTrue:
        [(icon := self iconRemoved) ifNotNil:
            [icon displayOn: aGC x: cx y: y + (h / 2) - (icon height / 2) ].
        cx := cx + 22."experimental value - this looks good"].
    (icon := self iconDelta) ifNotNil:
        [icon displayOn: aGC x: cx y: y + (h / 2) - (icon height / 2) ].
    cx := cx + 16."12 + 2px gap"                


    super displayLabel:aLabel h:lH on:aGC x:cx y:y h:h

    "Modified: / 24-01-2012 / 21:44:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ChangeList::ListEntry methodsFor:'private'!

iconSelector
    | delta |

    delta := change deltaDetail.
    delta shortDeltaSymbol = #+ ifTrue:[^#iconPlus].
    delta shortDeltaSymbol = #- ifTrue:[^#iconMinus].
    delta shortDeltaSymbol = #= ifTrue:[^#iconEqual].

    ^ nil.

    "Modified: / 31-08-2011 / 10:39:32 / cg"
! !

!ChangeList::ListEntry methodsFor:'protocol-queries'!

hasChildren

    ^ change isCompositeChange and:[change changes notEmptyOrNil ].

    "Created: / 04-12-2011 / 14:45:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!ChangeList class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/Tools__ChangeList.st,v 1.13 2012/01/24 22:18:39 vrany Exp $'
!

version_CVS
    ^ '§Header: /cvs/stx/stx/libtool/Tools__ChangeList.st,v 1.13 2012/01/24 22:18:39 vrany Exp §'
!

version_SVN
    ^ '$Id: Tools__ChangeList.st 7486 2009-10-26 22:06:24Z vranyj1 $'
! !