[squeak-dev] The Trunk: Monticello-bf.540.mcz

Nicolas Cellier nicolas.cellier.aka.nice at gmail.com
Wed Nov 4 16:13:19 UTC 2020


Remember this mail from February 2019?

Still cleaning the inbox...
I see this:







*Name: Monticello-bf.540Author: bfTime: 3 May 2013, 12:06:01.01 pmUUID:
759525eb-5ca8-4ab2-9e4a-bddc7d0680dcAncestors: Monticello-bf.532,
Monticello-fbs.539This is my allow-partial-commits mod, improved to always
diff to the target repository, and merged with the latest fbs.359 trunk
version.*

It is not signalled as false ancestor, so it means that this ancestor is in
history, or another package in history has same UUID (unlikely!).

But in trunk there is a different package:







*Name: Monticello-bf.540Author: bfTime: 4 May 2013, 8:13:11.165 pmUUID:
b8904753-a5e5-4061-a912-49480229e91aAncestors: Monticello-fbs.539Add
MCReorganizationPreloader which can resolve moves between arbitrary
packages.*

Do we really have two different Monticello-bf.540 in ancestors or what?
Is there a morphic tool to visualize the ancestry graph?

I do not remember the conclusion, but can we browse/download/access the two
ancestors?

Le mer. 4 nov. 2020 à 15:57, <commits at source.squeak.org> a écrit :

> Marcel Taeumel uploaded a new version of Monticello to project The Trunk:
> http://source.squeak.org/trunk/Monticello-bf.540.mcz
>
> ==================== Summary ====================
>
> Name: Monticello-bf.540
> Author: bf
> Time: 3 May 2013, 12:06:01.01 pm
> UUID: 759525eb-5ca8-4ab2-9e4a-bddc7d0680dc
> Ancestors: Monticello-bf.532, Monticello-fbs.539
>
> This is my allow-partial-commits mod, improved to always diff to the
> target repository, and merged with the latest fbs.359 trunk version.
>
> =============== Diff against Monticello-fbs.539 ===============
>
> Item was added:
> + ----- Method: MCPatch>>ignoring: (in category 'accessing') -----
> + ignoring: ignoredOperations
> +       ^ MCPatch operations: (operations difference: ignoredOperations)!
>
> Item was added:
> + Notification subclass: #MCRepositoryRequest
> +       instanceVariableNames: ''
> +       classVariableNames: ''
> +       poolDictionaries: ''
> +       category: 'Monticello-UI'!
>
> Item was changed:
> + MCPatchBrowser subclass: #MCSaveVersionDialog
> +       instanceVariableNames: 'name message ignore'
> - MCTool subclass: #MCSaveVersionDialog
> -       instanceVariableNames: 'name message'
>         classVariableNames: ''
>         poolDictionaries: ''
>         category: 'Monticello-UI'!
>
> Item was changed:
>   ----- Method: MCSaveVersionDialog>>accept (in category 'as yet
> unclassified') -----
>   accept
>         self answer:
>                 (Array
>                         with: (self findTextMorph: #versionName) text
> asString
> +                       with: (self findTextMorph: #logMessage) text
> asString
> +                       with: ignore)
> + !
> -                       with: (self findTextMorph: #logMessage) text
> asString)
> -       !
>
> Item was changed:
>   ----- Method: MCSaveVersionDialog>>defaultExtent (in category 'as yet
> unclassified') -----
>   defaultExtent
> +       ^ 600 at 600!
> -       ^ 400 at 300!
>
> Item was added:
> + ----- Method: MCSaveVersionDialog>>ignore (in category 'as yet
> unclassified') -----
> + ignore
> +       ^ ignore ifNil: [ignore := Set new]!
>
> Item was added:
> + ----- Method: MCSaveVersionDialog>>ignoreSelection (in category 'as yet
> unclassified') -----
> + ignoreSelection
> +       selection
> +               ifNil: [ignore size = items size
> +                       ifFalse: [ignore addAll: items]
> +                       ifTrue: [ignore removeAll]]
> +               ifNotNil: [
> +                       ignore remove: selection ifAbsent: [
> +                               ignore add: selection].
> +                       self selection < items size
> +                               ifTrue: [self selection: self selection +
> 1]].
> +       self changed: #list
> + !
>
> Item was added:
> + ----- Method: MCSaveVersionDialog>>installSelection (in category 'as yet
> unclassified') -----
> + installSelection
> +       super installSelection.
> +       selection ifNotNil: [
> +               ignore remove: selection ifAbsent: [].
> +               self changed: #list].
> +
> + !
>
> Item was added:
> + ----- Method: MCSaveVersionDialog>>list (in category 'as yet
> unclassified') -----
> + list
> +       ^ self items collect: [:ea |
> +               (self ignore includes: ea)
> +                       ifFalse: [ea summary]
> +                       ifTrue: [Text string: '( ', ea summary, ' )'
> attribute: TextEmphasis struckOut ]]!
>
> Item was added:
> + ----- Method: MCSaveVersionDialog>>methodListKey:from: (in category 'as
> yet unclassified') -----
> + methodListKey: aKeystroke from: aListMorph
> +       aKeystroke caseOf: {
> +               [$I] -> [self ignoreSelection].
> +       } otherwise: [super methodListKey: aKeystroke from: aListMorph ]!
>
> Item was added:
> + ----- Method: MCSaveVersionDialog>>methodListMenu: (in category 'as yet
> unclassified') -----
> + methodListMenu: aMenu
> +       aMenu addList:#(
> +               ('ignore (I)'   ignoreSelection 'Do not include this
> change when saving')
> +               -).
> +       super methodListMenu: aMenu.
> +       ^aMenu!
>
> Item was added:
> + ----- Method: MCSaveVersionDialog>>revertSelection (in category 'as yet
> unclassified') -----
> + revertSelection
> +       super revertSelection.
> +       selection ifNotNil: [
> +               ignore add: selection.
> +               self changed: #list].
> + !
>
> Item was changed:
>   ----- Method: MCSaveVersionDialog>>widgetSpecs (in category 'as yet
> unclassified') -----
>   widgetSpecs
>         ^ #(
>                 ((textMorph: versionName) (0 0 1 0) (0 0 0 30))
> +               ((textMorph: logMessage) (0 0 1 0.3) (0 30 0 -30))
> +               ((buttonRow) (0 0.3 1 0.3) (0 -40 0 0))
> +               ((listMorph:selection:menu:keystroke: list selection
> methodListMenu: methodListKey:from:) (0 0.3 1 0.6) (0 0 0 0))
> +               ((textMorph: text) (0 0.6 1 1) (0 0 0 0))
> -               ((textMorph: logMessage) (0 0 1 1) (0 30 0 -30))
> -               ((buttonRow) (0 1 1 1) (0 -40 0 0))
>                 )!
>
> Item was changed:
>   ----- Method: MCTool>>showModally (in category 'morphic ui') -----
>   showModally
>         modalProcess := Processor activeProcess.
> +       self window openInWorldExtent: self defaultExtent.
> -       self window openInWorldExtent: (400 at 400).
>         [self window world notNil] whileTrue: [
>                 self window outermostWorldMorph doOneCycle.
>         ].
>         morph := nil.
>         ^ modalValue!
>
> Item was changed:
>   Notification subclass: #MCVersionNameAndMessageRequest
> +       instanceVariableNames: 'suggestion initialMessage patch'
> -       instanceVariableNames: 'suggestion initialMessage'
>         classVariableNames: ''
>         poolDictionaries: ''
>         category: 'Monticello-Versioning'!
>
> Item was changed:
>   ----- Method: MCVersionNameAndMessageRequest>>defaultAction (in category
> 'as yet unclassified') -----
>   defaultAction
>         ^ MCSaveVersionDialog new
>                 versionName: suggestion;
>                 logMessage: initialMessage;
> +               patch: patch;
>                 showModally!
>
> Item was added:
> + ----- Method: MCVersionNameAndMessageRequest>>patch (in category 'as yet
> unclassified') -----
> + patch
> +       ^ patch!
>
> Item was added:
> + ----- Method: MCVersionNameAndMessageRequest>>patch: (in category 'as
> yet unclassified') -----
> + patch: aPatch
> +       patch := aPatch
> + !
>
> Item was changed:
>   ----- Method: MCWorkingCopy>>newVersion (in category 'operations') -----
>   newVersion
> +       | packageSnapshot parentSnapshot patch |
> +       parentSnapshot := self parentSnapshot.
> +       packageSnapshot := package snapshot.
> +       patch := packageSnapshot patchRelativeToBase: parentSnapshot.
>         ^ (self requestVersionNameAndMessageWithSuggestion: self
> uniqueVersionName
> +               initialMessage: self patchMessageDefault
> +               patch: patch) ifNotNil:
> +                       [:tuple |
> +                       self newVersionWithName: tuple first
> withBlanksTrimmed
> +                               message: (self patchMessageStripped: tuple
> second)
> +                               snapshot: (tuple third
> +                                       ifEmpty: [packageSnapshot]
> +                                       ifNotEmpty: [
> +                                               MCPatcher apply: (patch
> ignoring: tuple third)
> +                                                       to:
> parentSnapshot])]
> -               initialMessage: self patchMessageSuggestion) ifNotNil:
> -                       [:pair |
> -                       self newVersionWithName: pair first
> withBlanksTrimmed
> -                               message: (self patchMessageStripped: pair
> last)].
>   !
>
> Item was changed:
>   ----- Method: MCWorkingCopy>>newVersionWithName:message: (in category
> 'operations') -----
>   newVersionWithName: nameString message: messageString
> +       ^self newVersionWithName: nameString message: messageString
> snapshot: package snapshot!
> -       | info deps |
> -       info := ancestry infoWithName: nameString message: messageString.
> -       ancestry := MCWorkingAncestry new addAncestor: info.
> -       self modified: true; modified: false.
> -
> -       deps := self requiredPackages collect:
> -               [:ea |
> -               MCVersionDependency
> -                       package: ea
> -                       info: ea workingCopy currentVersionInfo].
> -
> -       ^ MCVersion
> -               package: package
> -               info: info
> -               snapshot: package snapshot
> -               dependencies: deps!
>
> Item was added:
> + ----- Method: MCWorkingCopy>>newVersionWithName:message:snapshot: (in
> category 'operations') -----
> + newVersionWithName: nameString message: messageString snapshot: aSnapshot
> +       | info deps clean |
> +       info := ancestry infoWithName: nameString message: messageString.
> +       ancestry := MCWorkingAncestry new addAncestor: info.
> +       clean := (package snapshot patchRelativeToBase: aSnapshot) isEmpty.
> +       self modified: clean; modified: clean not. "hack to ensure label
> is updated"
> +
> +       deps := self requiredPackages collect:
> +               [:ea |
> +               MCVersionDependency
> +                       package: ea
> +                       info: ea workingCopy currentVersionInfo].
> +
> +       ^ MCVersion
> +               package: package
> +               info: info
> +               snapshot: aSnapshot
> +               dependencies: deps!
>
> Item was added:
> + ----- Method: MCWorkingCopy>>parentSnapshot (in category 'private') -----
> + parentSnapshot
> +       "prefer parent in selected repository"
> +       MCRepositoryRequest signal ifNotNil: [:repo |
> +               self ancestors do: [:ancestor |
> +                       (repo versionWithInfo: ancestor)
> +                               ifNotNil: [:ver | ^ver snapshot]]].
> +       "otherwise, look in all repositories"
> +       self ancestors do: [:ancestor |
> +               (self repositoryGroup versionWithInfo: ancestor)
> +                       ifNotNil: [:ver | ^ver snapshot]].
> +       "otherwise"
> +       ^MCSnapshot empty!
>
> Item was changed:
>   ----- Method: MCWorkingCopy>>patchMessageChanges (in category
> 'operations') -----
>   patchMessageChanges
> +       | changes |
> +       changes := package snapshot patchRelativeToBase: self
> parentSnapshot.
> -       | changes parentInfo parentSnapshot |
> -       parentInfo := self ancestors
> -               ifEmpty: [nil]
> -               ifNotEmpty: [self ancestors first].
> -       parentSnapshot :=       self findSnapshotWithVersionInfo:
> parentInfo.
> -       changes := package snapshot patchRelativeToBase: parentSnapshot.
>         ^ (MCPatchMessage new patch: changes) message!
>
> Item was removed:
> - ----- Method:
> MCWorkingCopy>>requestVersionNameAndMessageWithSuggestion:initialMessage:
> (in category 'private') -----
> - requestVersionNameAndMessageWithSuggestion: nameString initialMessage:
> msgString
> -       ^ (MCVersionNameAndMessageRequest new
> -               suggestedName: nameString;
> -               initialMessage: msgString
> -               ) signal!
>
> Item was added:
> + ----- Method:
> MCWorkingCopy>>requestVersionNameAndMessageWithSuggestion:initialMessage:patch:
> (in category 'private') -----
> + requestVersionNameAndMessageWithSuggestion: nameString initialMessage:
> msgString patch: aPatch
> +       ^ (MCVersionNameAndMessageRequest new
> +               suggestedName: nameString;
> +               initialMessage: msgString;
> +               patch: aPatch
> +               ) signal!
>
> Item was changed:
>   ----- Method: MCWorkingCopyBrowser>>saveVersion (in category 'actions')
> -----
>   saveVersion
>         | repo |
>         self canSave ifFalse: [^self].
>         self checkForNewerVersions ifFalse: [^self].
>         repo := self repository.
> +       (self withRepository: repo do: [workingCopy newVersion]) ifNotNil:
> -       workingCopy newVersion ifNotNil:
>                 [:v |
>                 (MCVersionInspector new version: v) show.
>                 Cursor wait showWhile: [repo storeVersion: v].
>                 MCCacheRepository default cacheAllFileNamesDuring:
>                         [repo cacheAllFileNamesDuring:
>                                 [v allAvailableDependenciesDo:
>                                         [:dep |
>                                         (repo includesVersionNamed: dep
> info name)
>                                                 ifFalse: [repo
> storeVersion: dep]]]]]!
>
> Item was added:
> + ----- Method: MCWorkingCopyBrowser>>withRepository:do: (in category
> 'actions') -----
> + withRepository: aRepository do: aBlock
> +       ^aBlock
> +               on: MCRepositoryRequest
> +               do: [:req | req resume: aRepository]!
>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20201104/64a5197e/attachment-0001.html>


More information about the Squeak-dev mailing list