Skip to content

Commit

Permalink
instead of going by updating submorphs and copying them, only watch i…
Browse files Browse the repository at this point in the history
…nternal values are updated so no flickering and invisible watches possible
  • Loading branch information
JoeAtHPI committed Jan 19, 2024
1 parent 79d0863 commit 509e485
Show file tree
Hide file tree
Showing 11 changed files with 156 additions and 55 deletions.
6 changes: 3 additions & 3 deletions packages/Sandblocks-Babylonian/SBCluster.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -11,9 +11,9 @@ Class {
SBCluster >> compressedMorphsForDisplay: aSBWatchView [

| displayedMorphs |
displayedMorphs := aSBWatchView displayedMorphs collect: [:aMorph |
aMorph watchValue morphResizer: self morphResizer.
aMorph watchValue asValueMorph].
displayedMorphs := aSBWatchView watchValues collect: [:aWatchValue |
aWatchValue morphResizer: self morphResizer.
aWatchValue asValueMorph].
^ (displayedMorphs size = 1)
ifTrue: [displayedMorphs first]
ifFalse: [self newCellMorph
Expand Down
6 changes: 3 additions & 3 deletions packages/Sandblocks-Babylonian/SBExample.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -419,15 +419,15 @@ SBExample >> runSetup [
]

{ #category : #'as yet unclassified' }
SBExample >> runSynchronouslyIgnoreReturn [
SBExample >> runSynchUpdatingOnlyValuesOf: aCollectionOfSBWatches [

| returned |
self sendStartNotification.
aCollectionOfSBWatches do: [:aWatch | aWatch resetOnlyValuesFor: self].
SBExecutionEnvironment value: self.
[returned := self evaluate] on: Error do: [:e | self scheduleLastError: e].
self scheduleLastError: nil.
aCollectionOfSBWatches do: [:aWatch | aWatch exampleFinished: self]

self sendFinishNotification.
]

{ #category : #'as yet unclassified' }
Expand Down
2 changes: 1 addition & 1 deletion packages/Sandblocks-Babylonian/SBExampleCluster.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -72,7 +72,7 @@ SBExampleCluster >> extractedTopHeadingsFrom: aSBMultiverse [
^ (aSBMultiverse universes collect: [:aUniverse |
self newContainerMorph
addAllMorphsBack: {
SBStringMorph new contents: aUniverse activePermutation asString.
TextMorph new contents: aUniverse activePermutation asStylizedText.
SBButton newApplyPermutationFor: aUniverse activePermutation}])
]

Expand Down
68 changes: 65 additions & 3 deletions packages/Sandblocks-Babylonian/SBExampleWatch.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -124,7 +124,21 @@ SBExampleWatch >> applyResizerOnValues [
{ #category : #copying }
SBExampleWatch >> asInactiveCopy [

^ SBInactiveExampleWatch newFromWatch: self
"Ignore the existing morphs in ourselves and recreate the graphics from the data"
| copy |
copy := SBInactiveExampleWatch new
newIdentifier;
expression: (SBTextBubble new contents: self cleanedExpression sourceString);
modifyExpression: self modifyExpression veryDeepCopy;
dimensionOptions: self dimensionOptions veryDeepCopy.

exampleToValues keys do: [:anExample | copy exampleStarting: anExample;
reportValues: (self valuesForExample: anExample) for: anExample;
exampleFinished: anExample ].

^ copy
saveObjectsActivePermutations;
yourself
]

{ #category : #accessing }
Expand Down Expand Up @@ -162,6 +176,19 @@ SBExampleWatch >> deleteCommandFor: aBlock [
^ nil
]

{ #category : #accessing }
SBExampleWatch >> dimensionOptions [

^ dimensionOptions
]

{ #category : #accessing }
SBExampleWatch >> dimensionOptions: aSBComboBox [

"private"
dimensionOptions := aSBComboBox
]

{ #category : #'event handling' }
SBExampleWatch >> doubleClick: anEvent [

Expand Down Expand Up @@ -276,8 +303,8 @@ SBExampleWatch >> initialize [
super initialize.
options := SBMorphResizer standardOptions.

exampleToDisplay := Dictionary new.
exampleToValues := Dictionary new.
exampleToDisplay := IdentityDictionary new.
exampleToValues := IdentityDictionary new.
watchedExpression := SBStMessageSend new.
dimensionOptions := SBComboBox new
prefix: 'Morph Dimensions: ';
Expand Down Expand Up @@ -425,6 +452,33 @@ SBExampleWatch >> reportValue: anObject for: anExample [
ifPresent: [:values | values add: anObject]
]

{ #category : #actions }
SBExampleWatch >> reportValues: aCollectionOfObjects for: anExample [

exampleToValues
at: anExample
ifPresent: [:values | values addAll: aCollectionOfObjects]
]

{ #category : #'event handling' }
SBExampleWatch >> resetOnlyValuesFor: anExample [

"Private"
exampleToValues at: anExample put: OrderedCollection new.
(exampleToDisplay at: anExample) display resetOnlyValues



]

{ #category : #testing }
SBExampleWatch >> resumeGraphicalUpdates [

exampleToDisplay values do: [:anExampleValueDisplay |
anExampleValueDisplay display shouldUpdateDisplay: true]

]

{ #category : #accessing }
SBExampleWatch >> selectedMorphResizer [

Expand All @@ -437,6 +491,14 @@ SBExampleWatch >> setWatchedExpressionUneditable [
watchedExpression selectable: false
]

{ #category : #testing }
SBExampleWatch >> stopGraphicalUpdates [

exampleToDisplay values do: [:anExampleValueDisplay |
anExampleValueDisplay display shouldUpdateDisplay: false]

]

{ #category : #accessing }
SBExampleWatch >> valuesForExample: anExample [

Expand Down
4 changes: 2 additions & 2 deletions packages/Sandblocks-Babylonian/SBExploriants.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -149,7 +149,7 @@ SBExploriants >> tryToUpdateInBackgroundAfterChangeIn: aMethodBlock [
"aMethodBlock compiledMethod getSource asString allRangesOfRegexMatches: '(?<=activeIndex\: )\d*'."
"multiverse variants select: [:aVariant | aVariant containingArtefact = aMethodBlock]""]."

updateProcessRunning ifTrue: [
"updateProcessRunning ifTrue: [
updateProcess ifNotNil: #terminate.
updateProcessRunning := false.].
Expand All @@ -163,7 +163,7 @@ SBExploriants >> tryToUpdateInBackgroundAfterChangeIn: aMethodBlock [
onTimeout: [
newMultiverse cleanUp. updateProcess := nil. updateProcessRunning := false.].
updateProcess := nil. updateProcessRunning := false.
] forkAt: Processor userBackgroundPriority.
] forkAt: Processor userBackgroundPriority."



Expand Down
10 changes: 0 additions & 10 deletions packages/Sandblocks-Babylonian/SBInactiveExampleWatch.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -7,16 +7,6 @@ Class {
#category : #'Sandblocks-Babylonian'
}

{ #category : #'initialize-release' }
SBInactiveExampleWatch class >> newFromWatch: anActiveWatch [

^ (anActiveWatch veryDeepCopy)
primitiveChangeClassTo: self basicNew;
expression: (SBTextBubble new contents: anActiveWatch cleanedExpression sourceString);
saveObjectsActivePermutations;
yourself
]

{ #category : #'event handling' }
SBInactiveExampleWatch class >> registerWatch: aWatch [

Expand Down
46 changes: 20 additions & 26 deletions packages/Sandblocks-Babylonian/SBMultiverse.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -109,17 +109,10 @@ SBMultiverse >> asyncKaboom [
{ #category : #actions }
SBMultiverse >> cleanUp [

self resetWatchesToOriginalPermutationRunning: activeExamples.
watches do: #resumeGraphicalUpdates.
(watches select: [:anOpenWatch | anOpenWatch containingArtefact isNil]) copy do: #delete
]

{ #category : #actions }
SBMultiverse >> cleanUpRemovingCopies: outOfWorldWatches [

self resetWatchesToOriginalPermutationRunning: activeExamples.
outOfWorldWatches copy do: #delete
]

{ #category : #collecting }
SBMultiverse >> findExistingOrConvertToBlocks: aCollectionOfCompiledMethods [

Expand All @@ -140,14 +133,15 @@ SBMultiverse >> gatherElements [

allMethodBlocksContainingWatches := self allCompiledMethodsContainingExampleWatches collect: #asSandblock.

universes := OrderedCollection new.
activeExamples := self allActiveExamples.

variants := (allMethodBlocksContainingVariants collect: #containedVariants) flatten.
variants := variants select: #isActive.

watches := (self allMethodBlocksContainingWatches collect: #containedExampleWatches) flatten.

universes := OrderedCollection new.
activeExamples := self allActiveExamples.

watches do: [:aWatch | activeExamples do: [:anExample | aWatch exampleStarting: anExample].
aWatch hide].

]

Expand All @@ -162,14 +156,22 @@ SBMultiverse >> initialize [
{ #category : #actions }
SBMultiverse >> kaboom [

| outOfWorldWatches |
| outOfWorldWatches permutations |
"Only open watches display values when examples are run. We want to show them too"
(outOfWorldWatches := watches reject: #isInEditor) do: [:aWatch | self sandblockEditor openMorph: aWatch].
permutations := (SBPermutation allPermutationsOf: variants).
watches do: #stopGraphicalUpdates.

(SBPermutation allPermutationsOf: variants) do: [:aPermutation |
"Running the active one last"
(permutations sorted: [:a :b | a activeScore <= b activeScore ] ) do: [:aPermutation |
self runPermutation: aPermutation copyingWatches: watches ].
self resetWatchesToOriginalPermutationRunning: activeExamples.
outOfWorldWatches copy do: #delete.

"but stay consistent of the permutation sequences for alignment in clusters"
"sorting this is cheaper than running a permutation twice just to reset to prior state"
universes := universes sorted: [:a :b |
(permutations indexOf: a activePermutation) <= (permutations indexOf: b activePermutation)].
self cleanUp.

self triggerEvent: #updated.
]

Expand All @@ -187,13 +189,6 @@ SBMultiverse >> reset [
self triggerEvent: #updated.
]

{ #category : #'action-helper' }
SBMultiverse >> resetWatchesToOriginalPermutationRunning: activeExamples [

SBActiveVariantPermutation value: nil.
activeExamples do: #runSynchronouslyIgnoreReturn
]

{ #category : #actions }
SBMultiverse >> resolve [

Expand All @@ -214,10 +209,9 @@ SBMultiverse >> resolve [
{ #category : #actions }
SBMultiverse >> runPermutation: aPermutation copyingWatches: allWatches [


SBActiveVariantPermutation value: aPermutation.
activeExamples do: #runSynchronouslyIgnoreReturn.
universes add: (SBUniverse newActive: aPermutation watches: (watches collect: #asInactiveCopy))
activeExamples do: [:anExample | anExample runSynchUpdatingOnlyValuesOf: allWatches].
universes add: (SBUniverse newActive: aPermutation watches: (allWatches collect: #asInactiveCopy))

]

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ SBPermutationGridsView >> buildPermutationFor: aSBUniverse [
addAllMorphsBack: {
self containerRow listDirection: #topToBottom;
addAllMorphsBack: {
SBOwnTextMorph new contents: aSBUniverse activePermutation asString.
TextMorph new contents: aSBUniverse activePermutation asStylizedText.
SBButton newApplyPermutationFor: aSBUniverse activePermutation.
(SBPermutationCluster
newForSize: morphResizer
Expand Down
26 changes: 26 additions & 0 deletions packages/Sandblocks-Utils/SBPermutation.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,14 @@ SBPermutation class >> newCombinedOf: onePermutation and: anotherPermutation [

]

{ #category : #accessing }
SBPermutation >> activeScore [

^ (self referencedVariants collect: [:aVariant |
aVariant activeIndex = (self at: aVariant id) ifTrue: [1] ifFalse: [0]])
inject: 0 into: [:a :c | a + c]
]

{ #category : #actions }
SBPermutation >> apply [

Expand All @@ -60,6 +68,24 @@ SBPermutation >> asString [

]

{ #category : #converting }
SBPermutation >> asStylizedText [

| text |
text := Text fromString: self asString.
^ self isActive
ifTrue: [text allBold]
ifFalse: [text]


]

{ #category : #accessing }
SBPermutation >> isActive [

^ self activeScore = self referencedVariants size
]

{ #category : #accessing }
SBPermutation >> referencedVariants [

Expand Down
3 changes: 1 addition & 2 deletions packages/Sandblocks-Watch/SBExampleWatchView.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,5 @@ SBExampleWatchView >> reportValues: aCollectionOfObjects sized: aMorphResizer [
SBExampleWatchView >> updateDisplay [

super updateDisplay.

self count: (watchValues size) asString
self count: (watchValues size) asString.
]
Loading

0 comments on commit 509e485

Please sign in to comment.