Tools__ChangeList.st
branchjv
changeset 12680 4e2f5b0d4cb2
parent 12650 e0f607754b9a
parent 12666 c90e266fc135
child 13530 2269bce1636d
equal deleted inserted replaced
12679:7dffb3cbf7c4 12680:4e2f5b0d4cb2
    27 
    27 
    28 "{ NameSpace: Tools }"
    28 "{ NameSpace: Tools }"
    29 
    29 
    30 Tools::BrowserListWithFilter subclass:#ChangeList
    30 Tools::BrowserListWithFilter subclass:#ChangeList
    31 	instanceVariableNames:'listHolder showRemovedHolder showSameHolder showTimestampHolder
    31 	instanceVariableNames:'listHolder showRemovedHolder showSameHolder showTimestampHolder
    32 		allowRemoveHolder allowAcceptHolder scrollToBottom applyAction'
    32                 allowRemoveHolder allowAcceptHolder scrollToBottom applyAction showConflictsOnlyHolder'
    33 	classVariableNames:'LastSelectionConditionString'
    33 	classVariableNames:'LastSelectionConditionString'
    34 	poolDictionaries:''
    34 	poolDictionaries:''
    35 	category:'Interface-Browsers-ChangeSet'
    35 	category:'Interface-Browsers-ChangeSet'
    36 !
    36 !
    37 
    37 
    83 
    83 
    84 iconEqualGrayed
    84 iconEqualGrayed
    85     ^ ToolbarIconLibrary iconEqualGray12x12
    85     ^ ToolbarIconLibrary iconEqualGray12x12
    86 
    86 
    87     "Modified: / 31-08-2011 / 10:54:00 / cg"
    87     "Modified: / 31-08-2011 / 10:54:00 / cg"
       
    88 !
       
    89 
       
    90 iconExcla
       
    91     ^ ToolbarIconLibrary iconExclaRed12x12
    88 !
    92 !
    89 
    93 
    90 iconMinus
    94 iconMinus
    91     ^ ToolbarIconLibrary iconMinusRed12x12
    95     ^ ToolbarIconLibrary iconMinusRed12x12
    92 
    96 
   438     "Return a description of exported aspects;
   442     "Return a description of exported aspects;
   439      these can be connected to aspects of an embedding application
   443      these can be connected to aspects of an embedding application
   440      (if this app is embedded in a subCanvas)."
   444      (if this app is embedded in a subCanvas)."
   441 
   445 
   442     ^ #(
   446     ^ #(
   443 	#allowAcceptHolder
   447         #allowAcceptHolder
   444 	#allowRemoveHolder
   448         #allowRemoveHolder
   445 	#inGeneratorHolder
   449         #inGeneratorHolder
   446 	#menuHolder
   450         #menuHolder
   447 	#outGeneratorHolder
   451         #outGeneratorHolder
   448 	#selectionHolder
   452         #selectionHolder
   449 	#showFilterHolder
   453         #showFilterHolder
   450 	#showRemovedHolder
   454         #showRemovedHolder
   451 	#showSameHolder
   455         #showSameHolder
   452 	#showTimestampHolder
   456         #showTimestampHolder
       
   457         #showConflictsOnlyHolder
   453       ).
   458       ).
   454 
   459 
   455 ! !
   460 ! !
   456 
   461 
   457 
   462 
   624 	listHolder := ValueHolder new.
   629 	listHolder := ValueHolder new.
   625     ].
   630     ].
   626     ^ listHolder
   631     ^ listHolder
   627 !
   632 !
   628 
   633 
       
   634 showConflictsOnlyHolder
       
   635     "return/create the 'showConflictsOnlyHolder' value holder (automatically generated)"
       
   636 
       
   637     showConflictsOnlyHolder isNil ifTrue:[
       
   638         showConflictsOnlyHolder := ValueHolder with: true.
       
   639         showConflictsOnlyHolder addDependent: self.
       
   640     ].
       
   641     ^ showConflictsOnlyHolder
       
   642 !
       
   643 
       
   644 showConflictsOnlyHolder:something
       
   645     "set the 'showConflictsOnlyHolder' value holder (automatically generated)"
       
   646 
       
   647     |oldValue newValue|
       
   648 
       
   649     showConflictsOnlyHolder notNil ifTrue:[
       
   650         oldValue := showConflictsOnlyHolder value.
       
   651         showConflictsOnlyHolder removeDependent:self.
       
   652     ].
       
   653     showConflictsOnlyHolder := something.
       
   654     showConflictsOnlyHolder notNil ifTrue:[
       
   655         showConflictsOnlyHolder addDependent:self.
       
   656     ].
       
   657     newValue := showConflictsOnlyHolder value.
       
   658     oldValue ~~ newValue ifTrue:[
       
   659         self update:#value with:newValue from:showConflictsOnlyHolder.
       
   660     ].
       
   661 !
       
   662 
   629 showRemovedHolder
   663 showRemovedHolder
   630     "return/create the 'showRemovedHolder' value holder (automatically generated)"
   664     "return/create the 'showRemovedHolder' value holder (automatically generated)"
   631 
   665 
   632     showRemovedHolder isNil ifTrue:[
   666     showRemovedHolder isNil ifTrue:[
   633 	showRemovedHolder := ValueHolder with: true.
   667 	showRemovedHolder := ValueHolder with: true.
   716 ! !
   750 ! !
   717 
   751 
   718 
   752 
   719 !ChangeList methodsFor:'change & update'!
   753 !ChangeList methodsFor:'change & update'!
   720 
   754 
       
   755 selectionChanged
       
   756    super selectionChanged
       
   757 !
       
   758 
   721 update: aspect with: param from: sender
   759 update: aspect with: param from: sender
   722 
   760 
   723     sender == allowRemoveHolder ifTrue:[
   761     sender == allowRemoveHolder ifTrue:[
   724 	self listColumn: #removed visible: allowRemoveHolder value.
   762         self listColumn: #removed visible: allowRemoveHolder value.
   725 	^self.
   763         ^self.
   726     ].
   764     ].
   727 
   765 
   728     sender == showTimestampHolder ifTrue:[
   766     sender == showTimestampHolder ifTrue:[
   729 	self listColumn: #timeStamp visible: showTimestampHolder value.
   767         self listColumn: #timeStamp visible: showTimestampHolder value.
   730 	^self.
   768         ^self.
   731     ].
   769     ].
   732 
   770 
   733 
   771 
   734     sender == selectionHolder ifTrue:[
   772     sender == selectionHolder ifTrue:[
   735 	self selectionChanged.
   773         self selectionChanged.
   736 	^self
   774         ^ self
   737     ].
   775     ].
   738     sender == showSameHolder ifTrue:[
   776     sender == showSameHolder ifTrue:[
   739 	self updateList.
   777         self updateList.
   740 	^self.
   778         ^self.
   741     ].
   779     ].
   742     sender == showRemovedHolder ifTrue:[
   780     sender == showRemovedHolder ifTrue:[
   743 	self updateList.
   781         self updateList
   744 	^self.
   782     ].
       
   783     sender == showConflictsOnlyHolder ifTrue:[
       
   784         self updateList
   745     ].
   785     ].
   746 
   786 
   747     ^super update: aspect with: param from: sender
   787     ^super update: aspect with: param from: sender
   748 
   788 
   749     "Created: / 24-10-2009 / 19:47:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   789     "Created: / 24-10-2009 / 19:47:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   813 
   853 
   814 makeGenerator
   854 makeGenerator
   815     "Superclass Tools::BrowserList says that I am responsible to implement this method"
   855     "Superclass Tools::BrowserList says that I am responsible to implement this method"
   816 
   856 
   817     ^Iterator on:
   857     ^Iterator on:
   818 	[:whatToDo|
   858         [:whatToDo|
   819 	selectionHolder value do:
   859 
   820 	    [:changeListItem| | change |
   860         selectionHolder value do:
   821 	    changeListItem notNil ifTrue:[
   861             [:changeListItem| | change |
   822 		change := changeListItem change.
   862             change := changeListItem change.
   823 		change isCompositeChange ifTrue:
   863             change isCompositeChange ifTrue:
   824 		    [change changes do: whatToDo]]]]
   864                 [change changes do: whatToDo]]].
   825 
   865 
   826     "Modified: / 24-07-2009 / 23:00:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
   866     "Modified: / 24-07-2009 / 23:00:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
   827     "Modified: / 25-07-2012 / 15:39:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   867     "Modified: / 24-10-2009 / 20:00:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   828 ! !
   868 ! !
   829 
   869 
   830 
   870 
   831 !ChangeList methodsFor:'hooks'!
   871 !ChangeList methodsFor:'hooks'!
   832 
   872 
   855 
   895 
   856 
   896 
   857 !ChangeList methodsFor:'menu actions'!
   897 !ChangeList methodsFor:'menu actions'!
   858 
   898 
   859 listMenuApply
   899 listMenuApply
   860     |sel list idx|
   900     |sel list idx selectionHolder|
   861 
   901 
   862     self acceptEnabled ifFalse:[^self].
   902     self acceptEnabled ifFalse:[^self].
   863 
   903     selectionHolder := self selectionHolder.
   864     (sel := self selectionHolder value) do:[:e| applyAction value:e change].
   904 
       
   905     (sel := selectionHolder value) do:[:e| applyAction value:e change].
   865     sel size == 1 ifTrue:[
   906     sel size == 1 ifTrue:[
   866 	list := self listHolder value.
   907         list := self listHolder value. 
   867 	idx := list indexOf:(sel first).
   908         idx := list indexOf:(sel first). 
   868 	idx < list size ifTrue:[
   909         idx < list size ifTrue:[
   869 	    self selectionHolder value:(Array with:(list at:idx+1))
   910             selectionHolder value:(Array with:(list at:idx+1))
   870 	] ifFalse:[
   911         ] ifFalse:[
   871 	    self selectionHolder value:#()
   912             selectionHolder value:#()
   872 	].
   913         ].
   873     ].
   914     ].
   874 
   915 
   875     "Modified: / 24-10-2009 / 22:02:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   916     "Modified: / 24-10-2009 / 22:02:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   876     "Modified: / 10-09-2012 / 13:57:46 / cg"
   917     "Modified: / 10-09-2012 / 13:57:46 / cg"
   877 !
   918 !
   894 
   935 
   895     "Modified: / 24-01-2012 / 22:00:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   936     "Modified: / 24-01-2012 / 22:00:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   896 !
   937 !
   897 
   938 
   898 listMenuBrowseChanges: changes
   939 listMenuBrowseChanges: changes
   899 
   940     | classes methods methodsOnly browserClass|
   900     | classes methods methodsOnly |
   941 
   901     classes := Set new.
   942     classes := Set new.
   902     methods := Set new.
   943     methods := Set new.
   903     methodsOnly := true.
   944     methodsOnly := true.
   904     changes do:
   945     changes do: [:each |
   905 	[:each|
   946         each isClassChange ifTrue:[
   906 	each  isClassChange ifTrue:
   947             each changeClass ifNotNil:[
   907 	    [each  changeClass ifNotNil:
   948                 classes add: each  changeClass.
   908 		[classes add: each  changeClass.
   949                 each isMethodCodeChange 
   909 		each isMethodCodeChange
   950                     ifTrue:
   910 		    ifTrue:
   951                         [each changeMethod ifNotNil:
   911 			[each changeMethod ifNotNil:
   952                             [methods add:each changeMethod]]
   912 			    [methods add:each changeMethod]]
   953                     ifFalse:
   913 		    ifFalse:
   954                         [methodsOnly := false]
   914 			[methodsOnly := false]]]].
   955             ]
   915     methodsOnly
   956         ]
   916 	ifTrue:
   957     ].
   917 	    [methods size = 1
   958 
   918 		ifTrue:[Smalltalk browserClass openInMethod: methods anyOne]
   959     browserClass := Smalltalk browserClass.
   919 		ifFalse:[Smalltalk browserClass browseMethods: methods asArray title: 'Selected methods from changeset' sort: true]]
   960     methodsOnly 
   920 	ifFalse:
   961         ifTrue:
   921 	    [classes size = 1
   962             [methods size = 1 
   922 		ifTrue:[Smalltalk browserClass browseClass: classes anyOne]
   963                 ifTrue:[ browserClass openInMethod: methods anyOne]
   923 		ifFalse:[Smalltalk browserClass browseClasses: classes]]
   964                 ifFalse:[ browserClass browseMethods: methods asArray title: 'Selected methods from changeset' sort: true]]
       
   965         ifFalse:
       
   966             [classes size = 1
       
   967                 ifTrue:[ browserClass browseClass: classes anyOne]
       
   968                 ifFalse:[ browserClass browseClasses: classes]]
   924 
   969 
   925     "Modified: / 24-10-2009 / 22:02:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   970     "Modified: / 24-10-2009 / 22:02:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   926     "Created: / 24-01-2012 / 22:00:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   971     "Created: / 24-01-2012 / 22:00:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   927 !
   972 !
   928 
   973 
  1041 browserNameList
  1086 browserNameList
  1042 
  1087 
  1043     ^'Change list'
  1088     ^'Change list'
  1044 
  1089 
  1045     "Modified: / 24-07-2009 / 22:06:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
  1090     "Modified: / 24-07-2009 / 22:06:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
  1091 !
       
  1092 
       
  1093 iconSelectorForChange:change
       
  1094     | delta sym selectorOrNil |
       
  1095 
       
  1096     masterApplication notNil ifTrue:[
       
  1097         selectorOrNil := masterApplication iconSelectorForChange:change.
       
  1098         selectorOrNil notNil ifTrue:[ ^ selectorOrNil ].
       
  1099     ].
       
  1100     delta := change deltaDetail.
       
  1101     sym := delta shortDeltaSymbol.
       
  1102     sym = #+ ifTrue:[^#iconPlus].
       
  1103     sym = #- ifTrue:[^#iconMinus].
       
  1104     sym = #= ifTrue:[^#iconEqual].
       
  1105     "/ different.
       
  1106     ^ nil.
  1046 !
  1107 !
  1047 
  1108 
  1048 listColumn: columnId visible: visible
  1109 listColumn: columnId visible: visible
  1049     visible ifTrue:[
  1110     visible ifTrue:[
  1050         self listColumnShow: columnId
  1111         self listColumnShow: columnId
  1124     "Created: / 05-12-2009 / 14:14:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
  1185     "Created: / 05-12-2009 / 14:14:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
  1125 !
  1186 !
  1126 
  1187 
  1127 updateList
  1188 updateList
  1128     |inGenerator changeset firstLineShown oldSel newList newSel |
  1189     |inGenerator changeset firstLineShown oldSel newList newSel |
  1129 
  1190     self withWaitCursorDo:[
  1130     inGenerator := self inGeneratorHolder value.
  1191         inGenerator := self inGeneratorHolder value.
  1131     listView notNil ifTrue:[
  1192         listView notNil ifTrue:[
  1132 	((listView isKindOf: ScrollableView) not or:[listView scrolledView notNil]) ifTrue:[
  1193             ((listView isKindOf: ScrollableView) not or:[listView scrolledView notNil]) ifTrue:[
  1133 	    firstLineShown := listView firstLineShown
  1194                 firstLineShown := listView firstLineShown
  1134 	].
  1195             ].
  1135     ].
  1196         ].
  1136     oldSel := self selection.
  1197         oldSel := self selection.
  1137 
  1198 
  1138     changeset := inGenerator isNil ifTrue:[ #() ] ifFalse:[ inGenerator ].
  1199         changeset := inGenerator isNil ifTrue:[ #() ] ifFalse:[ inGenerator ].
  1139     newList := changeset
  1200         newList := changeset
  1140 		select:
  1201                     select:
  1141 		    [:chg |
  1202                         [:chg |
  1142 		    (self showRemovedHolder value or:[ chg removed not ])
  1203                         (self showRemovedHolder value or:[ chg removed not ])
  1143 			and:[self showSameHolder value or:[chg delta ~~ #=]]
  1204                             and:[self showSameHolder value or:[chg delta ~~ #=]]
  1144 		    ].
  1205                         ].
  1145     newList := self filterList: newList.
  1206         newList := self filterList: newList.
  1146     newList := newList collect:[:chg | self listEntryFor:chg ].
  1207         newList := newList collect:[:chg | self listEntryFor:chg ].
  1147     self listHolder value ~= newList ifTrue:[
  1208         self listHolder value ~= newList ifTrue:[
  1148 	self listHolder value: newList.
  1209             self listHolder value: newList.
  1149 	((newList size ~~ 0) and:[scrollToBottom]) ifTrue:[
  1210             ((newList size ~~ 0) and:[scrollToBottom]) ifTrue:[
  1150 	    self selection: { newList last }
  1211                 self selection: { newList last }
  1151 	] ifFalse:[
  1212             ] ifFalse:[
  1152 	    oldSel notEmptyOrNil ifTrue:[
  1213                 oldSel notEmptyOrNil ifTrue:[
  1153 		newSel := OrderedCollection new: oldSel size.
  1214                     newSel := OrderedCollection new: oldSel size.
  1154 		oldSel := oldSel reject:[:e|e isNil].
  1215                     oldSel := oldSel reject:[:e|e isNil].
  1155 		oldSel := oldSel collect:[:e|e change].
  1216                     oldSel := oldSel collect:[:e|e change].
  1156 		newList do:[:e|(oldSel includes:e change) ifTrue:[newSel add:e]].
  1217                     newList do:[:e|(oldSel includes:e change) ifTrue:[newSel add:e]].
  1157 		self selection: newSel.
  1218                     self selection: newSel.
  1158 	    ].
  1219                 ].
  1159 	    (listView notNil and:[firstLineShown notNil]) ifTrue:[
  1220                 (listView notNil and:[firstLineShown notNil]) ifTrue:[
  1160 		listView scrollToLine: (newList size min: firstLineShown).
  1221                     listView scrollToLine: (newList size min: firstLineShown).
  1161 	    ].
  1222                 ].
  1162 	].
  1223             ].
  1163 	scrollToBottom := false.
  1224             scrollToBottom := false.
  1164 
  1225 
       
  1226         ]
  1165     ]
  1227     ]
  1166 
       
  1167     "Modified: / 28-12-2011 / 15:46:15 / cg"
  1228     "Modified: / 28-12-2011 / 15:46:15 / cg"
  1168     "Modified: / 01-08-2012 / 18:10:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
  1229     "Modified: / 01-08-2012 / 18:10:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
  1169 ! !
  1230 ! !
  1170 
  1231 
  1171 
  1232 
  1188 
  1249 
  1189     ^self selectionHolder value size = 1
  1250     ^self selectionHolder value size = 1
  1190 !
  1251 !
  1191 
  1252 
  1192 hasSingleChangeSelectedAndCanBrowse
  1253 hasSingleChangeSelectedAndCanBrowse
  1193 
  1254     self selectionHolder value ? #() do: [:each |
  1194 
  1255         |chg|
  1195     self selectionHolder value ? #() do:
  1256 
  1196 	[:each|
  1257         chg := each change.
  1197 	(each change isClassChange and:
  1258         chg isClassChange ifTrue:[
  1198 	    [each change isMethodChange not
  1259             (chg isMethodChange not or:[chg isMethodCodeChange]) ifFalse:[^ false]
  1199 		or:[each change isMethodCodeChange]]) ifFalse:[^false]].
  1260         ].
  1200     ^true
  1261     ].
       
  1262     ^ true
  1201 !
  1263 !
  1202 
  1264 
  1203 showColumn: columnSymbol
  1265 showColumn: columnSymbol
  1204 
  1266 
  1205     ^self showColumnSpecHolder value includes: columnSymbol.
  1267     ^self showColumnSpecHolder value includes: columnSymbol.
  1273 !
  1335 !
  1274 
  1336 
  1275 children
  1337 children
  1276 
  1338 
  1277     children isNil ifTrue:[
  1339     children isNil ifTrue:[
  1278 	change isCompositeChange ifTrue:[
  1340         change isCompositeChange ifTrue:[
  1279 	    children := OrderedCollection new: change changes size.
  1341             children := OrderedCollection new: change changes size.
  1280 	    change changes do:[:chg|
  1342             self application showConflictsOnlyHolder value ifTrue:[
  1281 		((self application showRemovedHolder value or:[ chg removed not ])
  1343                 change changes do:[:chg|
  1282 		    and:[self application showSameHolder value or:[chg delta ~~ #=]])
  1344                     (chg isConflict) ifTrue:[
  1283 			ifTrue:[
  1345                         children add: ((self application listEntryFor: chg) parent: self)
  1284 			    children add: ((self application listEntryFor: chg) parent: self)
  1346                     ]
  1285 			]
  1347                 ].
  1286 	    ].
  1348             ] ifFalse:[
  1287 	] ifFalse:[
  1349                 |showRemoved showSame|
  1288 	    children :=  #()
  1350 
  1289 	]
  1351                 showRemoved := self application showRemovedHolder value.
       
  1352                 showSame := self application showSameHolder value.
       
  1353 
       
  1354                 change changes do:[:chg|
       
  1355                     ((showRemoved or:[ chg removed not ])
       
  1356                         and:[showSame or:[chg delta ~~ #=]]) 
       
  1357                             ifTrue:[
       
  1358                                 children add: ((self application listEntryFor: chg) parent: self)
       
  1359                             ]
       
  1360                 ].
       
  1361             ]
       
  1362         ] ifFalse:[
       
  1363             children :=  #()
       
  1364         ]
  1290     ].
  1365     ].
  1291     ^children
  1366     ^children
  1292 
  1367 
  1293     "Created: / 25-07-2009 / 23:32:39 / Jan Vrany <vranyj1@fel.cvut.cz>"
  1368     "Created: / 25-07-2009 / 23:32:39 / Jan Vrany <vranyj1@fel.cvut.cz>"
  1294     "Modified (format): / 18-11-2011 / 14:56:25 / cg"
  1369     "Modified (format): / 18-11-2011 / 14:56:25 / cg"
  1311     "Created: / 29-10-2010 / 14:32:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
  1386     "Created: / 29-10-2010 / 14:32:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
  1312     "Created: / 31-08-2011 / 10:29:21 / cg"
  1387     "Created: / 31-08-2011 / 10:29:21 / cg"
  1313 !
  1388 !
  1314 
  1389 
  1315 iconDelta
  1390 iconDelta
  1316 
       
  1317     | iconSelector |
  1391     | iconSelector |
       
  1392 
  1318     iconSelector := self iconSelector.
  1393     iconSelector := self iconSelector.
  1319     iconSelector isNil ifTrue:[^nil].
  1394     iconSelector isNil ifTrue:[^nil].
  1320     self removed ifTrue:[iconSelector := iconSelector , #Grayed].
  1395     self removed ifTrue:[iconSelector := iconSelector , #Grayed].
  1321     ^self application class perform: iconSelector asSymbol.
  1396     ^self application class perform: iconSelector asSymbol.
  1322 
  1397 
  1323     "Created: / 05-12-2009 / 14:11:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
  1398     "Created: / 05-12-2009 / 14:11:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
  1324     "Modified: / 18-11-2011 / 14:56:33 / cg"
  1399     "Modified: / 18-11-2011 / 14:56:33 / cg"
  1325 !
  1400 !
  1326 
  1401 
  1327 iconRemoved
  1402 iconRemoved
  1328 
  1403     |appClass|
  1329     ^self removed
  1404 
  1330 	ifTrue: [self application class uncheckedIcon ]
  1405     appClass := self application class.
  1331 	ifFalse:[self application class checkedIcon ]
  1406     ^self removed 
       
  1407         ifTrue: [appClass uncheckedIcon ]
       
  1408         ifFalse:[appClass checkedIcon ]
  1332 
  1409 
  1333     "Created: / 05-12-2009 / 14:11:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
  1410     "Created: / 05-12-2009 / 14:11:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
  1334 !
  1411 !
  1335 
  1412 
  1336 imageSource
  1413 imageSource
  1454 
  1531 
  1455 
  1532 
  1456 !ChangeList::ListEntry methodsFor:'private'!
  1533 !ChangeList::ListEntry methodsFor:'private'!
  1457 
  1534 
  1458 iconSelector
  1535 iconSelector
  1459     | delta |
  1536     ^ application iconSelectorForChange:change
  1460 
       
  1461     delta := change deltaDetail.
       
  1462     delta shortDeltaSymbol = #+ ifTrue:[^#iconPlus].
       
  1463     delta shortDeltaSymbol = #- ifTrue:[^#iconMinus].
       
  1464     delta shortDeltaSymbol = #= ifTrue:[^#iconEqual].
       
  1465 
       
  1466     ^ nil.
       
  1467 
       
  1468     "Modified: / 31-08-2011 / 10:39:32 / cg"
       
  1469 ! !
  1537 ! !
  1470 
  1538 
  1471 
  1539 
  1472 !ChangeList::ListEntry methodsFor:'protocol-queries'!
  1540 !ChangeList::ListEntry methodsFor:'protocol-queries'!
  1473 
  1541 
  1480 
  1548 
  1481 
  1549 
  1482 !ChangeList class methodsFor:'documentation'!
  1550 !ChangeList class methodsFor:'documentation'!
  1483 
  1551 
  1484 version
  1552 version
  1485     ^ '$Header: /cvs/stx/stx/libtool/Tools__ChangeList.st,v 1.21 2013-03-30 01:59:17 cg Exp $'
  1553     ^ '$Header: /cvs/stx/stx/libtool/Tools__ChangeList.st,v 1.24 2013-04-14 19:55:58 cg Exp $'
  1486 !
  1554 !
  1487 
  1555 
  1488 version_CVS
  1556 version_CVS
  1489     ^ '$Header: /cvs/stx/stx/libtool/Tools__ChangeList.st,v 1.21 2013-03-30 01:59:17 cg Exp $'
  1557     ^ '$Header: /cvs/stx/stx/libtool/Tools__ChangeList.st,v 1.24 2013-04-14 19:55:58 cg Exp $'
  1490 !
  1558 !
  1491 
  1559 
  1492 version_HG
  1560 version_HG
  1493 
  1561 
  1494     ^ '$Changeset: <not expanded> $'
  1562     ^ '$Changeset: <not expanded> $'