Skip to content

Commit

Permalink
dc: make replacements compatible with diffing
Browse files Browse the repository at this point in the history
  • Loading branch information
tom95 committed Oct 2, 2023
1 parent 7e8ac23 commit 6ce78c0
Show file tree
Hide file tree
Showing 16 changed files with 272 additions and 61 deletions.
61 changes: 61 additions & 0 deletions packages/DomainCode-Core/Morph.extension.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,61 @@
Extension { #name : #Morph }

{ #category : #'*DomainCode-Core' }
Morph >> allChildrenBreadthFirstDo: aBlock [

| remaining |
remaining := OrderedCollection with: self.
[remaining notEmpty] whileTrue: [ | next |
next := remaining removeFirst.
aBlock value: next.
remaining addAll: next children]
]

{ #category : #'*DomainCode-Core' }
Morph >> allChildrenDo: aBlock [

self children do: [:c | c allChildrenDo: aBlock].
aBlock value: self
]

{ #category : #'*DomainCode-Core' }
Morph >> allChildrenSelect: aBlock [

^ Array streamContents: [:stream | self allChildrenDo: [:b | (aBlock value: b) ifTrue: [stream nextPut: b]]]
]

{ #category : #'*DomainCode-Core' }
Morph >> children [

^ submorphs
]

{ #category : #'*DomainCode-Core' }
Morph >> firstDeepChildNode [

| current |
current := self.
[current children isEmpty] whileFalse: [current := current children first].
^ current
]

{ #category : #'*DomainCode-Core' }
Morph >> hasChildren [

^ self children notEmpty
]

{ #category : #'*DomainCode-Core' }
Morph >> isNode: aNode [

^ self = aNode
]

{ #category : #'*DomainCode-Core' }
Morph >> treeSize [

| i |
i := 0.
self allChildrenDo: [:m | i := i + 1].
^ i
]
18 changes: 9 additions & 9 deletions packages/DomainCode-Diff/DCChawatheScriptGenerator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -8,11 +8,11 @@ Class {
DCChawatheScriptGenerator >> alignChildrenSrc: w dest: x srcInOrder: srcInOrder destInOrder: destInOrder in: aMapping [

| s1 s2 lcs |
w submorphs do: [:c | srcInOrder remove: c ifAbsent: []].
x submorphs do: [:c | destInOrder remove: c ifAbsent: []].
w children do: [:c | srcInOrder remove: c ifAbsent: []].
x children do: [:c | destInOrder remove: c ifAbsent: []].

s1 := w submorphs select: [:c | (aMapping isSrcMapped: c) and: [x submorphs includes: (aMapping destForSrc: c)]].
s2 := x submorphs select: [:c | (aMapping isDestMapped: c) and: [w submorphs includes: (aMapping srcForDest: c)]].
s1 := w children select: [:c | (aMapping isSrcMapped: c) and: [x children includes: (aMapping destForSrc: c)]].
s2 := x children select: [:c | (aMapping isDestMapped: c) and: [w children includes: (aMapping srcForDest: c)]].

lcs := self lcsWith: s1 and: s2 in: aMapping.
lcs do: [:mapping |
Expand All @@ -21,7 +21,7 @@ DCChawatheScriptGenerator >> alignChildrenSrc: w dest: x srcInOrder: srcInOrder

s2 do: [:b |
s1 do: [:a |
((aMapping includes: {a. b}) and: [(lcs includes: {a. b}) not]) ifTrue: [
((aMapping includes: {a. b}) and: [(lcs includes: {a. b}) not]) ifTrue: [
self move: a to: w postDeleteDo: [self findPosition: b dest: destInOrder in: aMapping].
srcInOrder add: a.
destInOrder add: b]]]
Expand All @@ -37,7 +37,7 @@ DCChawatheScriptGenerator >> delete: aMorph [
DCChawatheScriptGenerator >> findPosition: aTree dest: destInOrder in: aMapping [

| siblings v u |
siblings := aTree owner submorphs.
siblings := aTree owner children.
siblings do: [:c | (destInOrder includes: c) ifTrue: [c = aTree ifTrue: [^ 1]]].

v := nil.
Expand All @@ -64,7 +64,7 @@ DCChawatheScriptGenerator >> generateFrom: src to: dest in: aMapping [
destInOrder := Set new.
inserted := Set new.

dest allMorphsBreadthFirstDo: [:x | | y z w |
dest allChildrenBreadthFirstDo: [:x | | y z w |
w := nil.
y := x owner.
z := aMapping srcForDest: y.
Expand All @@ -81,13 +81,13 @@ DCChawatheScriptGenerator >> generateFrom: src to: dest in: aMapping [
v := w owner.
w treeLabel = x treeLabel ifFalse: [self update: w with: x contents].
k := self findPosition: x dest: destInOrder in: aMapping.
z = v ifFalse: [self move: w to: z postDeleteDo: [k]]]].
(z isNode: v) ifFalse: [self move: w to: z postDeleteDo: [k]]]].

srcInOrder add: w.
destInOrder add: x.
self alignChildrenSrc: w dest: x srcInOrder: srcInOrder destInOrder: destInOrder in: aMapping].

(Array streamContents: [:s | src allMorphsDo: [:w | ((aMapping isSrcMapped: w) not and: [(inserted includes: w) not]) ifTrue: [s nextPut: w]]]) do: [:w | self delete: w]
(Array streamContents: [:s | src allChildrenDo: [:w | ((aMapping isSrcMapped: w) not and: [(inserted includes: w) not]) ifTrue: [s nextPut: w]]]) do: [:w | self delete: w]
]

{ #category : #actions }
Expand Down
2 changes: 1 addition & 1 deletion packages/DomainCode-Diff/DCCommandScriptGenerator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ DCCommandScriptGenerator >> move: aMorph to: anOwnerMorph postDeleteDo: aBlock [
self editor do: command.

self maybeAttachFlash: aMorph.
self logChanges ifTrue: [Transcript showln: {#move. anOwnerMorph. aBlock. aMorph}]
self logChanges ifTrue: [Transcript showln: {#move. anOwnerMorph. command index. aMorph}]
]

{ #category : #actions }
Expand Down
6 changes: 3 additions & 3 deletions packages/DomainCode-Diff/DCGreedyBottomUpMatcher.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ DCGreedyBottomUpMatcher >> destCandidatesFor: src in: aMapping [
{ #category : #'as yet unclassified' }
DCGreedyBottomUpMatcher >> lastChanceMatchFrom: src to: dest in: aMapping [

(src recursiveSubmorphCount < self sizeThreshold or: [dest recursiveSubmorphCount < self sizeThreshold]) ifTrue: [ | m zsMappings |
(src treeSize < self sizeThreshold or: [dest treeSize < self sizeThreshold]) ifTrue: [ | m zsMappings |
m := DCZhangShashaMatcher new.
zsMappings := DCMappingStore new.
m matchFrom: src to: dest in: zsMappings.
Expand All @@ -44,13 +44,13 @@ DCGreedyBottomUpMatcher >> lastChanceMatchFrom: src to: dest in: aMapping [
DCGreedyBottomUpMatcher >> matchFrom: src to: dest in: aMapping [

rootDest := dest.
src allMorphsDo: [:t |
src allChildrenDo: [:t |
src = t
ifTrue: [
aMapping addMappingFrom: t to: dest.
self lastChanceMatchFrom: t to: dest in: aMapping]
ifFalse: [
((aMapping isSrcMapped: t) not or: [t hasSubmorphs not]) ifTrue: [
((aMapping isSrcMapped: t) not or: [t hasChildren not]) ifTrue: [
(((self destCandidatesFor: t in: aMapping) select: [:candidate | (DCMappingComparator diceSimilarityFrom: t to: candidate in: aMapping) >= self similarityThreshold]) detectMax: [:candidate | DCMappingComparator diceSimilarityFrom: t to: candidate in: aMapping]) ifNotNil: [:best |
self lastChanceMatchFrom: t to: best in: aMapping.
aMapping addMappingFrom: t to: best]]]]
Expand Down
6 changes: 3 additions & 3 deletions packages/DomainCode-Diff/DCGreedySubtreeMatcher.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -17,9 +17,9 @@ DCGreedySubtreeMatcher >> handleAmbiguousMappings: aCollection for: aMapping [
mappingStore: aMapping.

aCollection sort: [:m1 :m2 | | s1 s2 |
s1 := m1 first detectMax: [:t | t recursiveSubmorphCount].
s2 := m2 first detectMax: [:t | t recursiveSubmorphCount].
s1 recursiveSubmorphCount < s2 recursiveSubmorphCount].
s1 := m1 first detectMax: [:t | t treeSize].
s2 := m2 first detectMax: [:t | t treeSize].
s1 treeSize < s2 treeSize].

aCollection do: [:entry | | candidates |
candidates := Array streamContents: [:s | entry first do: [:src | entry second do: [:dest | s nextPut: {src. dest}]]].
Expand Down
10 changes: 5 additions & 5 deletions packages/DomainCode-Diff/DCLeftOverLeafMatcher.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -17,9 +17,9 @@ DCLeftOverLeafMatcher >> handleAmbiguousMappings: aCollection for: aMapping [
mappingStore: aMapping.

aCollection sort: [:m1 :m2 | | s1 s2 |
s1 := m1 first detectMax: [:t | t recursiveSubmorphCount].
s2 := m2 first detectMax: [:t | t recursiveSubmorphCount].
s1 recursiveSubmorphCount < s2 recursiveSubmorphCount].
s1 := m1 first detectMax: [:t | t treeSize].
s2 := m2 first detectMax: [:t | t treeSize].
s1 treeSize < s2 treeSize].

aCollection do: [:entry | | candidates |
candidates := Array streamContents: [:s | entry first do: [:src | entry second do: [:dest | s nextPut: {src. dest}]]].
Expand All @@ -37,10 +37,10 @@ DCLeftOverLeafMatcher >> matchFrom: src to: dest in: aMapping [
ambiguousMappings := OrderedCollection new.
srcTrees := DCPriorityTreeQueue new
minimumHeight: 0;
addAll: (Array streamContents: [:s | src allMorphsDo: [:k | (aMapping isSrcMapped: k) ifFalse: [s nextPut: k]]]).
addAll: (Array streamContents: [:s | src allChildrenDo: [:k | (aMapping isSrcMapped: k) ifFalse: [s nextPut: k]]]).
destTrees := DCPriorityTreeQueue new
minimumHeight: 0;
addAll: (Array streamContents: [:s | dest allMorphsDo: [:k | (aMapping isDestMapped: k) ifFalse: [s nextPut: k]]]).
addAll: (Array streamContents: [:s | dest allChildrenDo: [:k | (aMapping isDestMapped: k) ifFalse: [s nextPut: k]]]).

[
self synchronizePriority: srcTrees with: destTrees.
Expand Down
4 changes: 2 additions & 2 deletions packages/DomainCode-Diff/DCMappingComparator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -24,8 +24,8 @@ DCMappingComparator class >> diceSimilarityFrom: src to: dest in: aMapping [

^ self
diceCoefficientCommon: (self numberOfMappedDescendantsFrom: src to: dest in: aMapping)
left: src recursiveSubmorphCount - 1
right: dest recursiveSubmorphCount - 1
left: src treeSize - 1
right: dest treeSize - 1
]

{ #category : #'as yet unclassified' }
Expand Down
6 changes: 1 addition & 5 deletions packages/DomainCode-Diff/DCMappingStore.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -11,10 +11,6 @@ Class {
{ #category : #'as yet unclassified' }
DCMappingStore >> addMappingFrom: src to: dest [

SBToggledCode
comment: ''
active: 1
do: {[src type = 'lexical_declaration' ifTrue: [self halt]]}.
srcToDest at: src put: dest.
destToSrc at: dest put: src
]
Expand All @@ -23,7 +19,7 @@ DCMappingStore >> addMappingFrom: src to: dest [
DCMappingStore >> addRecursiveMappingFrom: src to: dest [

self addMappingFrom: src to: dest.
src submorphs with: dest submorphs do: [:a :b | self addRecursiveMappingFrom: a to: b]
src children with: dest children do: [:a :b | self addRecursiveMappingFrom: a to: b]
]

{ #category : #'as yet unclassified' }
Expand Down
6 changes: 2 additions & 4 deletions packages/DomainCode-Diff/DCMatchTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -8,20 +8,18 @@ Class {
DCMatchTest >> testAppendBinary [

| src dest |
Transcript clear.
src := DCBlock parseBlock: 'a' language: SBJavascript.
dest := DCBlock parseBlock: 'a+' language: SBJavascript.
DCMatcher new matchFrom: src to: dest.
DCMatcher new applyEditsIn: dest to: src.
self assert: 'a+' equals: src sourceString
]

{ #category : #'as yet unclassified' }
DCMatchTest >> testSplitBinary [

| src dest |
Transcript clear.
src := DCBlock parseBlock: 'a2' language: SBJavascript.
dest := DCBlock parseBlock: 'a+2' language: SBJavascript.
DCMatcher new matchFrom: src to: dest.
DCMatcher new applyEditsIn: dest to: src.
self assert: 'a+2' equals: src sourceString
]
10 changes: 5 additions & 5 deletions packages/DomainCode-Diff/DCMatcher.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -47,10 +47,10 @@ DCMatcher >> fineGrainedMatch2From: src to: dest in: aMapping [

| topSrc topDest |
topSrc := self
commonAncestorOf: (Array streamContents: [:s | src allMorphsDo: [:k | (aMapping isSrcMapped: k) ifFalse: [s nextPut: k]]])
commonAncestorOf: (Array streamContents: [:s | src allChildrenDo: [:k | (aMapping isSrcMapped: k) ifFalse: [s nextPut: k]]])
root: src.
topDest := self
commonAncestorOf: (Array streamContents: [:s | dest allMorphsDo: [:k | (aMapping isDestMapped: k) ifFalse: [s nextPut: k]]])
commonAncestorOf: (Array streamContents: [:s | dest allChildrenDo: [:k | (aMapping isDestMapped: k) ifFalse: [s nextPut: k]]])
root: dest.
(topSrc notNil and: [topDest notNil]) ifTrue: [
"see if we can answer quickly, otherwise we accept a worse diff result"
Expand All @@ -66,8 +66,8 @@ DCMatcher >> fineGrainedMatch2From: src to: dest in: aMapping [
DCMatcher >> fineGrainedMatchFrom: src to: dest in: aMapping [

| topSrc topDest |
topSrc := (Array streamContents: [:s | src allMorphsDo: [:k | (aMapping isSrcMapped: k) ifFalse: [s nextPut: k]]]) detectMax: #treeHeight.
topDest := (Array streamContents: [:s | dest allMorphsDo: [:k | (aMapping isDestMapped: k) ifFalse: [s nextPut: k]]]) detectMax: #treeHeight.
topSrc := (Array streamContents: [:s | src allChildrenDo: [:k | (aMapping isSrcMapped: k) ifFalse: [s nextPut: k]]]) detectMax: #treeHeight.
topDest := (Array streamContents: [:s | dest allChildrenDo: [:k | (aMapping isDestMapped: k) ifFalse: [s nextPut: k]]]) detectMax: #treeHeight.

self halt.
topSrc ifNotNil: [
Expand All @@ -80,7 +80,7 @@ DCMatcher >> fineGrainedMatchFrom: src to: dest in: aMapping [
{ #category : #'as yet unclassified' }
DCMatcher >> largestUnmappedFor: aTree isSrc: aBoolean in: aMapping [

^ (Array streamContents: [:s | aTree allMorphsDo: [:k | (aBoolean ifTrue: [aMapping isSrcMapped: k] ifFalse: [aMapping isDestMapped: k]) ifFalse: [s nextPut: k]]]) detectMax: #treeHeight
^ (Array streamContents: [:s | aTree allChildrenDo: [:k | (aBoolean ifTrue: [aMapping isSrcMapped: k] ifFalse: [aMapping isDestMapped: k]) ifFalse: [s nextPut: k]]]) detectMax: #treeHeight
]

{ #category : #'as yet unclassified' }
Expand Down
2 changes: 1 addition & 1 deletion packages/DomainCode-Diff/DCPriorityTreeQueue.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ DCPriorityTreeQueue >> addAll: aCollection [
{ #category : #'as yet unclassified' }
DCPriorityTreeQueue >> addTree: tree [

tree submorphs do: [:child | self add: child]
tree children do: [:child | self add: child]
]

{ #category : #'as yet unclassified' }
Expand Down
8 changes: 4 additions & 4 deletions packages/DomainCode-Diff/DCZhangShashaTree.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -15,18 +15,18 @@ Class {
DCZhangShashaTree >> for: aTree [

| index tmpData visited k |
nodeCount := aTree recursiveSubmorphCount.
nodeCount := aTree treeSize.
leafCount := 0.
llds := Array new: nodeCount.
labels := Array new: nodeCount.

index := 1.
tmpData := Dictionary new.
aTree allMorphsDo: [:n |
aTree allChildrenDo: [:n |
tmpData at: n put: index.
labels at: index put: n.
llds at: index put: (tmpData at: n firstDeepSubmorph) - 1.
n hasSubmorphs ifFalse: [leafCount := leafCount + 1].
llds at: index put: (tmpData at: n firstDeepChildNode) - 1.
n hasChildren ifFalse: [leafCount := leafCount + 1].
index := index + 1].

keyRoots := Array new: leafCount + 1.
Expand Down
Loading

0 comments on commit 6ce78c0

Please sign in to comment.