Skip to content

Commit

Permalink
Merge branch 'dev' of origin into 114-no-changes-info
Browse files Browse the repository at this point in the history
  • Loading branch information
Tobias Straeubig committed Jul 16, 2021
2 parents 567798f + 14f4b40 commit f00cdd7
Show file tree
Hide file tree
Showing 82 changed files with 362 additions and 104 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -8,4 +8,4 @@ getChangeListItemsMissingInImageFrom: anOrderedCollectionOfChangeRecords

changeListItems removeAllSuchThat: [:each | each category = #nonPersistentDoIt].

^ changeListItems
^changeListItems
Original file line number Diff line number Diff line change
@@ -1,6 +1,4 @@
updating
codeOfSelectedChange

^ self hasSelectedMethodChangeListItem
ifTrue: [self diffFromPriorSourceFor: self selectedChangeListItem string]
ifFalse: [self selectedChangeListItem string]
^ self diffFromPriorSourceFor: self selectedChangeListItem string

This file was deleted.

Original file line number Diff line number Diff line change
Expand Up @@ -7,5 +7,5 @@ fileInPickedChanges
during: [:bar | self pickedChangeListItems reverse
doWithIndex: [:each :index |
bar value: index.
bar value: 'loading ', index printString , '/' , self numberOfPickedChangeListItems printString , ': ' , each description printString.
bar value: 'loading ', index printString , '/' , self numberOfPickedChangeListItems printString , ': ' , each description.
each fileIn]]

This file was deleted.

This file was deleted.

Original file line number Diff line number Diff line change
Expand Up @@ -4,5 +4,4 @@ initializeWith: aMultiByteFileStream
super initialize.
self
initializeChangeListItemsWith: aMultiByteFileStream;
groupChangeListItems;
updateAfterChangeListChange.
groupChangeListItems.

This file was deleted.

Original file line number Diff line number Diff line change
@@ -1,9 +1,4 @@
misc
priorSourceOrNil
| aClass aSelector changeRecords |
(aClass := self selectedClass) ifNil: [^ nil].
(aSelector := self selectedMessageName) ifNil: [^ nil].
changeRecords := aClass changeRecordsAt: aSelector.
changeRecords ifNil: [^ nil].
changeRecords ifEmpty: [^ nil].
^ changeRecords first string

^ self selectedChangeListItem priorSourceOrNil

This file was deleted.

This file was deleted.

Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,6 @@ updateAfterChangeListChange

self
updateLoadButton;
updateCodePane;
changed: #changeGroupDescriptions;
changed: #versionDescriptions;
clipVersionIndex;
Expand Down
Original file line number Diff line number Diff line change
@@ -1,10 +1,8 @@
updating
updateCodePane

self contents: (self hasChanges
ifTrue: [self hasSelectedChangeListItem
ifTrue: [self codeOfSelectedChange asText]
ifFalse: ['']]
ifFalse: [self noChangesInfoString]).
self contents: (self hasSelectedChangeListItem
ifTrue: [self codeOfSelectedChange asText]
ifFalse: ['']).

self contentsChanged.
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@
"defaultBrowserHeight" : "SV 8/7/2020 12:58",
"defaultBrowserWidth" : "SV 8/7/2020 12:58",
"extent" : "SV 8/7/2020 15:37",
"getChangeListItemsMissingInImageFrom:" : "abd 6/27/2021 20:03",
"getChangeListItemsMissingInImageFrom:" : "abd 7/5/2021 23:41",
"getChangeRecordsFromLastCrashFrom:" : "abd 6/20/2021 19:06",
"newWith:" : "uh 6/21/2020 21:32",
"numberOfBytesToLoadChangesFrom" : "gf 5/20/2020 10:43",
Expand Down Expand Up @@ -33,49 +33,43 @@
"changeListItems:" : "gf 7/15/2020 10:40",
"clipGroupIndex" : "JA 7/1/2021 11:12",
"clipVersionIndex" : "JA 7/1/2021 11:14",
"codeOfSelectedChange" : "abd 7/3/2021 00:03",
"codeOfSelectedChange" : "JA 7/3/2021 18:40",
"codePaneFraction" : "SV 6/21/2020 12:23",
"codePaneFrame" : "mg 8/7/2020 22:25",
"createNewGroupFor:" : "abd 6/20/2021 14:15",
"diffFromPriorSourceFor:" : "abd 7/3/2021 00:06",
"fileInPickedChanges" : "7/2/2021 20:05:34",
"fileInPickedChanges" : "abd 7/3/2021 11:16",
"getCorrespondingGroupOf:in:" : "JA 6/30/2021 22:34",
"groupChangeListItems" : "abd 7/2/2021 18:53",
"groupIndex" : "TS 6/30/2021 21:53",
"groupIndex:" : "FK 6/16/2021 14:09",
"groupListFrame" : "abd 6/16/2021 10:25",
"hasChanges" : "TS 7/10/2021 14:10",
"hasSelectedChangeListItem" : "TS 6/18/2021 18:43",
"hasSelectedMethodChangeListItem" : "TS 6/18/2021 18:44",
"hasValidGroupIndex" : "TS 6/18/2021 18:47",
"hasValidVersionIndex" : "TS 6/18/2021 18:47",
"initializeChangeListItemsWith:" : "abd 7/2/2021 19:44",
"initializeWith:" : "TS 7/10/2021 14:23",
"initializeWith:" : "TS 6/18/2021 15:09",
"isLoadButtonEnabled" : "mg 8/6/2020 11:27",
"isPickButtonEnabled" : "gf 7/25/2020 20:09",
"loadButtonLabel" : "mg 8/6/2020 11:29",
"loadPickedChanges" : "anonym-HPI 5/17/2021 17:21",
"noChangesInfoString" : "TS 7/10/2021 14:02",
"numberOfPickedChangeListItems" : "mg 8/6/2020 11:16",
"openHelpPopUp" : "anonym-HPI 5/28/2021 20:43",
"pickAllChangeListItems" : "gf 7/15/2020 10:48",
"pickButtonFrame" : "mg 8/6/2020 12:29",
"pickButtonLabel" : "abd 6/16/2021 11:38",
"pickedChangeListItems" : "mg 8/6/2020 11:17",
"priorSourceOrNil" : "abd 7/3/2021 00:17",
"priorSourceOrNil" : "JA 7/3/2021 18:41",
"removeAllChangeListItemsExcept:" : "SV 8/5/2020 22:13",
"selectedChangeListItem" : "TS 6/18/2021 18:05",
"selectedClass" : "JA 5/20/2021 22:50",
"selectedGroup" : "TS 6/18/2021 18:02",
"selectedMessageName" : "JA 5/20/2021 22:50",
"switchToDetailedView" : "mg 8/6/2020 11:24",
"togglePickStatusOfSelectedChangeListItem" : "abd 6/17/2021 13:03",
"updateAfterChangeListChange" : "TS 7/13/2021 16:52",
"updateAfterChangeListChange" : "TS 6/18/2021 18:32",
"updateAfterChangeSelection" : "FK 6/16/2021 13:45",
"updateAfterLoadingChanges" : "TS 6/19/2021 12:06",
"updateAfterPick" : "FK 6/16/2021 15:09",
"updateButtons" : "abd 6/16/2021 11:44",
"updateCodePane" : "TS 7/10/2021 14:14",
"updateCodePane" : "abd 7/2/2021 19:39",
"updateGroupSelection" : "abd 6/20/2021 14:39",
"updateLoadButton" : "gf 7/25/2020 19:42",
"updatePickButton" : "gf 7/25/2020 20:18",
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ categoryRegexAttributesList

{#methodRecategorized. '^([^ ]+) (class )?organization classify\: #(.+) under\: #(.+)$'. [:m | {#method -> (m subexpression: 4). #category -> (m subexpression: 5) } as: Dictionary]}.
{#methodRemoved. '^([^ ]+) (class )?removeSelector\: #([^ ]+)$'. [:m | {#method -> (m subexpression: 4). #class -> (m subexpression: 2) } as: Dictionary]}.
{#methodRenamed. '^\(RBRenameMethodRefactoring renameMethod\: #([^ ]+) in\: ([^ ]+) to\: #([^ ]+) permutation\: #\(([^\)]*)\)\) execute$'. [:m | {#class -> (m subexpression: 3). #oldMethod -> (m subexpression: 2). #newMethod -> (m subexpression: 4). #permutation -> (self stringToIntArray: (m subexpression: 5))} as: Dictionary]}.

{#packageCreated. '^SystemOrganization addCategory\: #(.+)$'. [:m | {#package -> (m subexpression: 2)} as: Dictionary]}.
{#packageRemoved. '^SystemOrganization removeSystemCategory\: #(.+)$'. [:m | {#package -> (m subexpression: 2)} as: Dictionary]}.
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
categories & attributes
stringToIntArray: aString

^ ((aString findBetweenSubStrs: ' ') collect: [:each | each asInteger]) asArray
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
misc
classCommentPriorSource

| aClass |
(aClass := Smalltalk classNamed: (self attributes at: #class))
ifNil: [^''].
^ aClass comment asString
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,9 @@ description

[#methodRecategorized] -> ['#', (self attributes at: #method), ' to #', (self attributes at: #category)].
[#methodRemoved] -> [(self attributes at: #method), ' from ', (self attributes at: #class)].
[#methodRenamed] -> [(self attributes at: #oldMethod), ' -> ', (self attributes at: #newMethod), ' in #', (self attributes at: #class)].

[#packageCreated] -> ['#', (self attributes at: #package)].
[#packageRemoved] -> ['#', (self attributes at: #package)].
[#packageRenamed] -> ['#', (self attributes at: #oldPackage), ' -> #', (self attributes at: #newPackage)]
})
})
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
misc
methodPriorSource

| aSelector aClass changeRecords |

aSelector := (self attributes at: #method).
(aClass := Smalltalk classNamed: (self attributes at: #class))
ifNil: [^ ''].
(changeRecords := aClass changeRecordsAt: aSelector)
ifNil: [^ ''];
ifEmpty: [^ ''].
^ changeRecords first string
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
misc
priorSourceOrNil

^ self category caseOf: {
[#method] -> [self methodPriorSource].
[#classComment] -> [self classCommentPriorSource]
}
otherwise: [nil]
Original file line number Diff line number Diff line change
@@ -1,13 +1,14 @@
{
"class" : {
"categoryAndAttributesFor:" : "abd 6/27/2021 20:01",
"categoryRegexAttributesList" : "abd 7/2/2021 23:44",
"categoryRegexAttributesList" : "abd 7/14/2021 11:43",
"classCommentCategoryAndAttributesFor:" : "abd 7/2/2021 23:45",
"doItCategoryAndAttributesFor:" : "abd 6/27/2021 20:01",
"doItCategoryAndAttributesFor:" : "abd 7/3/2021 21:40",
"if:matches:do:" : "abd 6/27/2021 20:01",
"methodCategoryAndAttributesFor:" : "abd 7/2/2021 23:45",
"newWith:" : "abd 6/27/2021 20:00",
"setCategoryAndAttributesOf:" : "abd 6/27/2021 20:00" },
"setCategoryAndAttributesOf:" : "abd 6/27/2021 20:00",
"stringToIntArray:" : "abd 7/14/2021 11:47" },
"instance" : {
"=" : "abd 7/2/2021 19:32",
"attributes" : "abd 6/20/2021 12:57",
Expand All @@ -16,7 +17,8 @@
"category:" : "abd 6/17/2021 12:57",
"changeRecord" : "SV 5/29/2020 22:13",
"changeRecord:" : "abd 6/17/2021 11:57",
"description" : "abd 6/20/2021 13:46",
"classCommentPriorSource" : "JA 7/3/2021 19:24",
"description" : "abd 7/3/2021 21:44",
"doesNotUnderstand:" : "gf 6/15/2020 23:22",
"formatted:" : "TS 6/30/2021 21:20",
"groupDescription" : "abd 6/20/2021 13:53",
Expand All @@ -25,7 +27,9 @@
"isMethod" : "abd 7/2/2021 19:02",
"isPicked" : "SV 7/13/2020 16:05",
"isPicked:" : "abd 6/20/2021 12:56",
"methodPriorSource" : "JA 7/3/2021 19:30",
"pick" : "gf 7/15/2020 10:45",
"priorSourceOrNil" : "JA 7/3/2021 19:30",
"separatesGroup:" : "abd 7/2/2021 19:08",
"shouldBeGrouped" : "abd 7/2/2021 19:10",
"toggleIsPicked" : "abd 6/17/2021 13:03",
Expand Down
Empty file.
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
instance creation
class: aClass oldName: anOldName newName: aNewName permutation: aPermutation

^ (self class: aClass)
oldName: anOldName;
newName: aNewName;
permutation: aPermutation
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
triggering
logString

^ '(RBRenameMethodRefactoring renameMethod: #{1} in: {2} to: #{3} permutation: #({4})) execute'
format: {self oldName. self item. self newName. self permutation joinSeparatedBy: ' '}
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
accessing
permutation: t1
permutation := t1
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
accessing
permutation
^ permutation
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
triggering
trigger: anEventManager

SystemChangeNotifier uniqueInstance evaluated: self logString
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
{
"class" : {
"class:oldName:newName:permutation:" : "abd 7/6/2021 00:34" },
"instance" : {
"logString" : "abd 7/14/2021 11:23",
"permutation" : "",
"permutation:" : "",
"trigger:" : "abd 7/6/2021 00:38" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
{
"category" : "ChangesReloaded-Core",
"classinstvars" : [
],
"classvars" : [
],
"commentStamp" : "",
"instvars" : [
"permutation" ],
"name" : "CRMethodRenamedEvent",
"pools" : [
],
"super" : "RenamedEvent",
"type" : "normal" }
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
*ChangesReloaded-Core
executeSilently

| undo |
undo := self asUndoOperation.
undo name: self name.
self primitiveExecute.
^ undo
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
{
"class" : {
},
"instance" : {
"executeSilently" : "abd 7/10/2021 12:03" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
{
"name" : "RBAddMethodChange" }
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
*ChangesReloaded-Core
executeSilently
| undos undo |
undos := changes collect: [ :each | each class = RBAddMethodChange
ifTrue: [each executeSilently]
ifFalse: [each execute]].
undo := self copy.
undo changes: undos reversed.
^ undo
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
{
"class" : {
},
"instance" : {
"executeSilently" : "abd 7/10/2021 12:09" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
{
"name" : "RBCompositeRefactoryChange" }
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
*ChangesReloaded-Core
addRefactoringSilently: aRefactoring
RBRefactoryChangeManager instance performChangeSilently: aRefactoring changes.
refactorings add: aRefactoring class name
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
{
"class" : {
},
"instance" : {
"addRefactoringSilently:" : "abd 7/10/2021 11:54" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
{
"name" : "RBRefactoringManager" }
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
*ChangesReloaded-Core
performChangeSilently: aRefactoringChange
self ignoreChangesWhile: [ self addUndo: aRefactoringChange executeSilently ]
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
{
"class" : {
},
"instance" : {
"performChangeSilently:" : "abd 7/10/2021 11:55" } }
Loading

0 comments on commit f00cdd7

Please sign in to comment.