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

Chris Muller asqueaker at gmail.com
Fri May 3 17:04:09 UTC 2013


Bert, the UI enhancement is great, but, as you can see from my test
commit of Kernel, it has the same problem as before.

What happened here was that, I had 2 changed methods in Kernel.
During review, I discovered an additional change to one more method
needed, so I did that.  Then I saved it -- but the package remained
dirty and it didn't capture any of my changes resulting from the
review!  So the package was saved with incorrect comments and I had to
save again, further bloating out ancestry and our repositories with
ticky-tack one-liner changes.

It's very nice to invoke the save dialog and see the changes on the
save dialog all with one click, but not at the cost of decimating the
review-and-fix process.  We need to diff to the target repository
BEFORE invoking the final save rather than after.

On Fri, May 3, 2013 at 5:06 AM,  <commits at source.squeak.org> wrote:
> Bert Freudenberg uploaded a new version of Monticello to project The Inbox:
> http://source.squeak.org/inbox/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-bf.532 ===============
>
> Item was changed:
>   ----- Method: MCClassDefinition>>createClass (in category 'installing') -----
>   createClass
>         | superClass class composition |
>         superClass := superclassName == #nil ifFalse:
>                                         [Smalltalk at: superclassName].
>         [class := (ClassBuilder new)
>                         name: name
>                         inEnvironment: superClass environment
>                         subclassOf: superClass
>                         type: type
>                         instanceVariableNames: self instanceVariablesString
>                         classVariableNames: self classVariablesString
>                         poolDictionaries: self sharedPoolsString
>                         category: category.
>         ] on: Warning, DuplicateVariableError do:[:ex| ex resume].
>
>         "The following is written to support traits unloading"
> +       composition := self traitComposition ifNil: [Array new] ifNotNil: [:traitComposition | Compiler evaluate: traitComposition].
> -       composition := Compiler evaluate: (self traitComposition ifNil:['{}']).
>         (composition isCollection and:[composition isEmpty and:[class traitComposition isEmpty]]) ifFalse:[
>                 class setTraitComposition: composition asTraitComposition.
>         ].
>
> +       composition := self classTraitComposition ifNil: [Array new] ifNotNil: [:traitComposition | Compiler evaluate: traitComposition].
> -       composition := Compiler evaluate: (self classTraitComposition ifNil:['{}']).
>         (composition isCollection and:[composition isEmpty and:[class class traitComposition isEmpty]]) ifFalse:[
>                 class class setTraitComposition: composition asTraitComposition.
>         ].
>
>         ^class!
>
> Item was changed:
>   ----- Method: MCFileBasedRepository>>versionNamed: (in category 'versions') -----
> + versionNamed: aMCVersionName
> - versionNamed: aMCVersionName
>         "For FileBased repositories, aMCVersionName must have the appropriate extension!!  :-("
> +       | version |
> +       version := self cache
> +               at: aMCVersionName
> +               ifAbsent:
> +                       [ [ self loadVersionFromFileNamed: aMCVersionName ]
> +                               on: FileDoesNotExistException
> +                               do: [ : err | nil ] ].
> -       | v |
> -       v := self cache at: aMCVersionName ifAbsent: [self loadVersionFromFileNamed: aMCVersionName].
>         self resizeCache: cache.
> +       (version notNil and: [ version isCacheable ]) ifTrue:
> +               [ cache
> +                       at: aMCVersionName asMCVersionName
> +                       put: version ].
> +       ^ version!
> -       (v notNil and: [v isCacheable]) ifTrue: [cache at: aMCVersionName asMCVersionName put: v].
> -       ^ v!
>
> Item was changed:
>   ----- Method: MCRepository class>>fillInTheBlankConfigure: (in category 'configuring') -----
>   fillInTheBlankConfigure: aTemplateString
>         | chunk repo |
>
>         aTemplateString ifNil: [ ^ false ].
> +       chunk := UIManager default
> +               multiLineRequest: self fillInTheBlankRequest
> +               centerAt: Sensor cursorPoint
> +               initialAnswer: aTemplateString
> +               answerHeight: 120.
> -       chunk := FillInTheBlankMorph
> -                       request: self fillInTheBlankRequest
> -                       initialAnswer: aTemplateString
> -                       centerAt: Sensor cursorPoint
> -                       inWorld: World
> -                       onCancelReturn: nil
> -                       acceptOnCR: false
> -                       answerExtent: 400 at 120.
>
>         chunk
>                 ifNotNil: [
>                         repo := self readFrom: chunk readStream.
>                         repo creationTemplate: chunk.
>         ].
>
>         ^ repo!
>
> Item was added:
> + ----- Method: MCRepository>>normalized (in category 'accessing') -----
> + normalized
> +       ^ (MCRepositoryGroup default repositories includes: self)
> +               ifTrue: [ self ]
> +               ifFalse: [ self copy ]!
>
> Item was added:
> + ----- Method: MCRepository>>normalizedRepositories (in category 'private') -----
> + normalizedRepositories
> +       ^ Array with: self normalized!
>
> Item was added:
> + ----- Method: MCRepository>>repositories (in category 'accessing') -----
> + repositories
> +       ^ Array with: self!
>
> Item was added:
> + ----- Method: MCRepositoryGroup>>allPackageNames (in category 'repository-api') -----
> + allPackageNames
> +       ^ repositories
> +               inject: Set new
> +               into:
> +                       [ : set : each | set
> +                                addAll: each allPackageNames ;
> +                                yourself ]!
>
> Item was added:
> + ----- Method: MCRepositoryGroup>>basicStoreVersion: (in category 'repository-api') -----
> + basicStoreVersion: aVersion
> +       "RepositoryGroup is used for reading, not writing."
> +       self shouldNotImplement!
>
> Item was added:
> + ----- Method: MCRepositoryGroup>>description (in category 'repository-api') -----
> + description
> +       ^ String streamContents:
> +               [ : stream | stream nextPutAll: '{ '.
> +               repositories
> +                       do: [ : each | stream nextPut: $';  nextPutAll: each description; nextPut: $' ]
> +                       separatedBy: [ stream nextPutAll: '. ' ].
> +               stream nextPutAll: ' }' ]!
>
> Item was changed:
> + ----- Method: MCRepositoryGroup>>includesVersionNamed: (in category 'repository-api') -----
> - ----- Method: MCRepositoryGroup>>includesVersionNamed: (in category 'testing') -----
>   includesVersionNamed: aString
> +       ^ repositories anySatisfy: [ : each | [each includesVersionNamed: aString] on: Error do: [false]]!
> -       | versionName |
> -       versionName := aString asMCVersionName.
> -       self repositoriesDo:
> -               [ : ea | (ea includesVersionNamed: versionName) ifTrue: [ ^ true ] ].
> -       ^ false!
>
> Item was changed:
>   ----- Method: MCRepositoryGroup>>initialize (in category 'initialize-release') -----
>   initialize
> +       super initialize.
>         repositories := OrderedCollection new!
>
> Item was added:
> + ----- Method: MCRepositoryGroup>>morphicOpen: (in category 'ui') -----
> + morphicOpen: aWorkingCopy
> +       ^ self repositories do: [:repo | repo morphicOpen: aWorkingCopy].!
>
> Item was added:
> + ----- Method: MCRepositoryGroup>>normalizedRepositories (in category 'accessing') -----
> + normalizedRepositories
> +       "Find an existing instance of any active repository so that we use whatever name and password the user usually uses. If not found, answer a copy"
> +       ^ repositories collect: [ : each | each normalized ]!
>
> Item was added:
> + ----- Method: MCRepositoryGroup>>versionNamed: (in category 'repository-api') -----
> + versionNamed: aMCVersionName
> +       repositories do:
> +               [ : each | (each versionNamed: aMCVersionName) ifNotNil: [ : ver | ^ ver ] ].
> +       ^ nil!
>
> Item was added:
> + ----- Method: MCRepositoryGroup>>versionNamesForPackageNamed: (in category 'repository-api') -----
> + versionNamesForPackageNamed: aString
> +       ^ repositories
> +               inject: Set new
> +               into:
> +                       [ : set : each | set
> +                                addAll: (each versionNamesForPackageNamed: aString) ;
> +                                yourself ]!
>
> Item was added:
> + ----- Method: MCRepositoryGroup>>versionWithInfo:ifAbsent: (in category 'repository-api') -----
> + versionWithInfo: aVersionInfo ifAbsent: aBlock
> +       repositories do:
> +               [ : each | (each
> +                       versionWithInfo: aVersionInfo
> +                       ifAbsent: [  ]) ifNotNil:
> +                       [ : ver | ^ ver ] ].
> +       ^ aBlock value!
>
> Item was added:
> + Notification subclass: #MCRepositoryRequest
> +       instanceVariableNames: ''
> +       classVariableNames: ''
> +       poolDictionaries: ''
> +       category: 'Monticello-UI'!
>
> Item was changed:
>   ----- Method: MCSaveVersionDialog>>defaultExtent (in category 'as yet unclassified') -----
>   defaultExtent
> +       ^ 600 at 600!
> -       ^ 400 at 300!
>
> Item was changed:
>   ----- 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]].
> -                               ignore add: selection]].
>         self changed: #list
>   !
>
> Item was changed:
>   ----- Method: MCSmtpRepository class>>morphicConfigure (in category 'as yet unclassified') -----
>   morphicConfigure
>         | address |
> +       address := UIManager default request: 'Email address:'.
> -       address := FillInTheBlankMorph request: 'Email address:'.
>         ^ address isEmpty ifFalse: [self new emailAddress: address]!
>
> Item was changed:
>   Model subclass: #MCTool
> +       instanceVariableNames: 'morph label modalProcess modalValue'
> -       instanceVariableNames: 'morph label modal modalValue'
>         classVariableNames: ''
>         poolDictionaries: ''
>         category: 'Monticello-UI'!
>
> Item was changed:
>   ----- Method: MCTool>>answer: (in category 'morphic ui') -----
>   answer: anObject
> +       (modalProcess notNil and: [modalProcess ~~ Processor activeProcess])
> +               ifTrue: [^self inform: 'This modal dialog was interrupted, please close it'].
>         modalValue := anObject.
>         self close.!
>
> Item was changed:
>   ----- Method: MCTool>>show (in category 'morphic ui') -----
>   show
> +       modalProcess := nil.
> -       modal := false.
>         Smalltalk at: #ToolBuilder ifPresent: [:tb | tb open: self. ^ self].
>         ^self window openInWorldExtent: self defaultExtent; yourself!
>
> Item was changed:
>   ----- Method: MCTool>>showLabelled: (in category 'morphic ui') -----
>   showLabelled: labelString
> +       modalProcess := nil.
> -       modal := false.
>         self label: labelString.
>         ^(self window)
>                 openInWorldExtent: self defaultExtent;
>                 yourself!
>
> Item was changed:
>   ----- Method: MCTool>>showModally (in category 'morphic ui') -----
>   showModally
> +       modalProcess := Processor activeProcess.
> +       self window openInWorldExtent: self defaultExtent.
> -       modal := true.
> -       self window openInWorldExtent: (400 at 400).
>         [self window world notNil] whileTrue: [
>                 self window outermostWorldMorph doOneCycle.
>         ].
>         morph := nil.
>         ^ modalValue!
>
> Item was changed:
>   ----- Method: MCVersion>>fileName (in category 'accessing') -----
>   fileName
> +       |rawName cookedName|
> +
> +       rawName := info name.
> +       "care for invalid filename characters"
> +       cookedName := rawName copy
> +                                               replaceAll: $/ with: $_;
> +                                               replaceAll: $: with: $_..
> +       ^ (cookedName, '.', self writerClass extension) asMCVersionName!
> -       ^ (info name, '.', self writerClass extension) asMCVersionName!
>
> Item was changed:
>   ----- 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!
> -       ^ self findSnapshotWithVersionInfo: (self ancestors
> -               ifEmpty: [nil]
> -               ifNotEmpty: [self ancestors first])!
>
> Item was changed:
>   ----- Method: MCWorkingCopyBrowser>>addWorkingCopy (in category 'actions') -----
>   addWorkingCopy
>         |name|
> +       name := UIManager default request: 'Name of package:'.
> -       name := FillInTheBlankMorph request: 'Name of package:'.
>         name isEmptyOrNil ifFalse:
>                 [PackageInfo registerPackageName: name.
>                 workingCopy := MCWorkingCopy forPackage: (MCPackage new name: name).
>                 workingCopyWrapper := nil.
>                 self repositorySelection: 0].
>         self workingCopyListChanged; changed: #workingCopySelection; changed: #repositoryList.
>         self changedButtons.!
>
> Item was changed:
>   ----- Method: MCWorkingCopyBrowser>>editLoadScripts (in category 'morphic ui') -----
>   editLoadScripts
>
> +       | arg |
> -       | menu |
>         self hasWorkingCopy ifFalse: [^self].
> +       arg := UIManager default
> +               chooseFrom: #('edit preamble' 'edit postscript' 'edit preambleOfRemoval' 'edit postscriptOfRemoval')
> +               values: #(#preamble #postscript #preambleOfRemoval #postscriptOfRemoval).
> +
> +       arg ifNotNil: [
> +               self editScript: arg].!
> -       menu := MenuMorph new defaultTarget: self.
> -       menu add: 'edit preamble' selector: #editScript: argument: #preamble.
> -       menu add: 'edit postscript' selector: #editScript: argument: #postscript.
> -       menu add: 'edit preambleOfRemoval' selector: #editScript: argument: #preambleOfRemoval.
> -       menu add: 'edit postscriptOfRemoval' selector: #editScript: argument: #postscriptOfRemoval.
> -       menu popUpInWorld.!
>
> Item was changed:
>   ----- Method: MCWorkingCopyBrowser>>renamePackage (in category 'actions') -----
>   renamePackage
>         | newName |
>         workingCopy ifNil:
>                 [ UIManager inform: 'Please select a package to be renamed.'.
>                 ^ self ].
>         workingCopy modified ifTrue:
>                 [ UIManager inform: 'Only unmodified packages should be renamed.'.
>                 ^ self ].
> +       newName := UIManager default
> -       newName := FillInTheBlankMorph
>                 request: 'New name of package:'
>                 initialAnswer: workingCopy packageName.
>         newName isEmptyOrNil ifFalse:
>                 [ | newWorkingCopy |
>                 newWorkingCopy := workingCopy renameToBe: newName.
>                 workingCopy package snapshot definitions
>                         ifEmpty:
>                                 [ "It worked."
>                                 workingCopy unregister.
>                                 workingCopy := newWorkingCopy.
>                                 self repositorySelection: 0.
>                                 self
>                                          workingCopyListChanged ;
>                                          changed: #workingCopySelection ;
>                                          changed: #repositoryList.
>                                 self changedButtons ]
>                         ifNotEmpty:
>                                 [ "It didn't work, browse the remaining definitions."
>                                 self browseWorkingCopy ] ]!
>
> 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]!
>
>


More information about the Squeak-dev mailing list