The Trunk: Monticello-ul.665.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Monticello-ul.665.mcz

commits-2
Levente Uzonyi uploaded a new version of Monticello to project The Trunk:
http://source.squeak.org/trunk/Monticello-ul.665.mcz

==================== Summary ====================

Name: Monticello-ul.665
Author: ul
Time: 13 March 2017, 2:39:27.024854 pm
UUID: 9b53d6f8-c972-467b-a940-367554d4f223
Ancestors: Monticello-jr.664

- SortedCollection Whack-a-mole
- other minor tweaks

=============== Diff against Monticello-jr.664 ===============

Item was changed:
  ----- Method: MCClassDefinition>>addVariables:ofType: (in category 'initializing') -----
  addVariables: aCollection ofType: aClass
+
+ aCollection do: [ :variable |
+ variables add: (aClass name: variable asString ) ]!
- variables addAll: (aCollection collect: [:var | aClass name: var asString]).!

Item was changed:
  ----- Method: MCClassDefinition>>initializeWithName:superclassName:category:instVarNames:classVarNames:poolDictionaryNames:classInstVarNames:type:comment:commentStamp: (in category 'initializing') -----
  initializeWithName: nameString
  superclassName: superclassString
  category: categoryString
  instVarNames: ivarArray
  classVarNames: cvarArray
  poolDictionaryNames: poolArray
  classInstVarNames: civarArray
  type: typeSymbol
  comment: commentString
  commentStamp: stampStringOrNil
  name := nameString asSymbol.
  superclassName := superclassString ifNil: ['nil'] ifNotNil: [superclassString asSymbol].
  category := categoryString.
  name = #CompiledMethod ifTrue: [type := #compiledMethod] ifFalse: [type := typeSymbol].
  comment := commentString withSqueakLineEndings.
  commentStamp := stampStringOrNil ifNil: [self defaultCommentStamp].
  variables := OrderedCollection  new.
  self addVariables: ivarArray ofType: MCInstanceVariableDefinition.
+ self addVariables: cvarArray sorted ofType: MCClassVariableDefinition.
+ self addVariables: poolArray sorted ofType: MCPoolImportDefinition.
- self addVariables: cvarArray asSortedCollection ofType: MCClassVariableDefinition.
- self addVariables: poolArray asSortedCollection ofType: MCPoolImportDefinition.
  self addVariables: civarArray ofType: MCClassInstanceVariableDefinition.!

Item was changed:
  ----- Method: MCClassDefinition>>initializeWithName:superclassName:traitComposition:classTraitComposition:category:instVarNames:classVarNames:poolDictionaryNames:classInstVarNames:type:comment:commentStamp: (in category 'initializing') -----
  initializeWithName: nameString
  superclassName: superclassString
  traitComposition: traitCompositionString
  classTraitComposition: classTraitCompositionString
  category: categoryString
  instVarNames: ivarArray
  classVarNames: cvarArray
  poolDictionaryNames: poolArray
  classInstVarNames: civarArray
  type: typeSymbol
  comment: commentString
  commentStamp: stampStringOrNil
  name := nameString asSymbol.
  superclassName := superclassString ifNil: ['nil'] ifNotNil: [superclassString asSymbol].
  traitComposition := traitCompositionString.
  classTraitComposition := classTraitCompositionString.
  category := categoryString.
  name = #CompiledMethod ifTrue: [type := #compiledMethod] ifFalse: [type := typeSymbol].
  comment := commentString withSqueakLineEndings.
  commentStamp := stampStringOrNil ifNil: [self defaultCommentStamp].
  variables := OrderedCollection  new.
  self addVariables: ivarArray ofType: MCInstanceVariableDefinition.
+ self addVariables: cvarArray sorted ofType: MCClassVariableDefinition.
+ self addVariables: poolArray sorted ofType: MCPoolImportDefinition.
- self addVariables: cvarArray asSortedCollection ofType: MCClassVariableDefinition.
- self addVariables: poolArray asSortedCollection ofType: MCPoolImportDefinition.
  self addVariables: civarArray ofType: MCClassInstanceVariableDefinition.!

Item was changed:
  ----- Method: MCClassDefinition>>sortedVariables (in category 'accessing') -----
  sortedVariables
  "sort variables for comparison purposes"
 
+ | orderDependents toSort |
+ orderDependents := OrderedCollection new: variables size.
+ toSort := OrderedCollection new.
+ variables do: [ :variable |
+ variable isOrderDependend
+ ifTrue: [ orderDependents addLast: variable ]
+ ifFalse: [ toSort addLast: variable ] ].
+ toSort sort: [ :a :b | a name <= b name ].
+ ^orderDependents
+ addAllLast: toSort;
+ yourself!
- | sorted |
- sorted := variables select: [:var | var isOrderDependend].
- sorted addAll: ((variables reject: [:var | var isOrderDependend])
- asSortedCollection: [:a :b | a name <= b name]).
- ^sorted!

Item was changed:
  ----- Method: MCMergeBrowser>>merger: (in category 'as yet unclassified') -----
  merger: aMerger
  merger := aMerger.
+ items := aMerger operations sorted.
- items := aMerger operations asSortedCollection.
  conflicts := aMerger conflicts sort: [:a :b | a operation <= b operation].!

Item was changed:
  ----- Method: MCOperationsBrowser>>invert (in category 'selecting') -----
  invert
+ items replace: [:ea | ea inverse].
- items := items collect: [:ea | ea inverse].
  self changed: #list; changed: #text; changed: #selection!

Item was changed:
  ----- Method: MCPackageLoader>>analyze (in category 'private') -----
  analyze
  | sorter |
  sorter := self sorterForItems: additions.
  additions := sorter orderedItems.
  requirements := sorter externalRequirements.
+ unloadableDefinitions := sorter itemsWithMissingRequirements sorted.
- unloadableDefinitions := sorter itemsWithMissingRequirements asSortedCollection.
 
  sorter := self sorterForItems: removals.
  removals := sorter orderedItems reversed.!

Item was changed:
  ----- Method: MCPatchBrowser>>patch: (in category 'initialize-release') -----
  patch: aPatch
+ items := aPatch operations sorted!
- items := aPatch operations asSortedCollection!

Item was changed:
  ----- Method: MCPatchMessage>>patch: (in category 'accessing') -----
  patch: aPatch
  stream ifNil: [stream := WriteStream on: (String new: 100)].
+ aPatch operations sorted
- aPatch operations asSortedCollection
  do: [:op | op applyTo: self]!

Item was changed:
  ----- Method: MCSnapshotBrowser>>extensionClassNames (in category 'accessing') -----
  extensionClassNames
+ ^ (self allClassNames difference: self packageClassNames) sorted!
- ^ (self allClassNames difference: self packageClassNames) asSortedCollection!

Item was changed:
  ----- Method: MCSnapshotBrowser>>snapshot: (in category 'accessing') -----
  snapshot: aSnapshot
+ items := aSnapshot definitions sorted.
- items := aSnapshot definitions asSortedCollection.
  self categorySelection: 0.!

Item was changed:
  ----- Method: MCSnapshotBrowser>>visibleCategories (in category 'listing') -----
  visibleCategories
+
+ | visibleCategories |
+ visibleCategories := Set new.
+ self packageOrganizations do: [ :each | visibleCategories addAll: each categories ].
+ self packageClasses do: [ :each | visibleCategories add: each category ].
+ self hasExtensions ifTrue: [ visibleCategories add: self extensionsCategory ].
+ ^visibleCategories sorted: [:each | each ifNil: ['~(put nils to the end)']] ascending!
- ^ ((self packageOrganizations gather: [:ea | ea categories])
- , (self packageClasses collect: [:ea | ea category])
- , (self hasExtensions
- ifTrue: [{self extensionsCategory}]
- ifFalse: [Array empty])) asSet asSortedCollection: [:each | each ifNil: ['~(put nils to the end)']] ascending!

Item was changed:
  ----- Method: MCSnapshotBrowser>>visibleProtocols (in category 'listing') -----
  visibleProtocols
  | methods protocols |
  self switchIsComment ifTrue: [^ Array new].
  methods := self methodsForSelectedClassAndMetaSelection.
+ protocols := methods collect: [:ea | ea category] as: Set.
- protocols := (methods collect: [:ea | ea category]) asSet asSortedCollection.
  (protocols size > 1) ifTrue: [protocols add: '-- all --'].
+ ^ protocols sorted!
- ^ protocols !

Item was changed:
  ----- Method: MCSubDirectoryRepository>>allFileNames (in category 'enumeration') -----
  allFileNames
  "sorting {entry. dirName. name}"
 
+ | result |
+ result := OrderedCollection new.
- | sorted |
- sorted := SortedCollection sortBlock: [:a :b |
- a first modificationTime >= b first modificationTime ].
  self allDirectories
  do: [:dir | dir entries
  do: [:ent | ent isDirectory
+ ifFalse: [result addLast: {ent. dir fullName. ent name}]]].
+ ^result
+ sort: [:a :b | a first modificationTime >= b first modificationTime ];
+ replace: [:ea | ea third asMCVersionName]!
- ifFalse: [sorted add: {ent. dir fullName. ent name}]]].
- ^ sorted
- collect: [:ea | ea third asMCVersionName]!

Item was changed:
  ----- Method: MCSubDirectoryRepository>>findFullNameForReading: (in category 'as yet unclassified') -----
  findFullNameForReading: aBaseName
  "Answer the latest version of aBaseName"
  | possible |
+ possible := OrderedCollection new.
- possible := SortedCollection sortBlock: [ :a :b | b first modificationTime < a first modificationTime ].
  self allDirectories
  do: [:dir | dir entries
  do: [:ent | ent isDirectory
  ifFalse: [
+ (ent name = aBaseName) ifTrue: [ possible addLast: {ent. dir fullNameFor: ent name}]]]].
+ possible isEmpty ifTrue: [ ^nil ].
+ ^(possible detectMin: [ :each | each first modificationTime ]) second!
- (ent name = aBaseName) ifTrue: [ possible add: {ent. dir fullNameFor: ent name}]]]].
- ^(possible at: 1 ifAbsent: [ ^nil ]) second
- !

Item was changed:
  ----- Method: MCSubDirectoryRepository>>findFullNameForWriting: (in category 'as yet unclassified') -----
  findFullNameForWriting: aBaseName
+
  | possible split prefix fpattern now |
  split := directory splitNameVersionExtensionFor: aBaseName.
  fpattern := split first, '*'.
+ possible := OrderedCollection new.
- possible := SortedCollection sortBlock: [ :a :b |
- a first = b first
- ifTrue: [ a second = b second
- ifFalse: [ a second < b second ]
- ifTrue: [ a third fullName size < b third fullName size ]]
- ifFalse: [ a first > b first ] ].
  now := Time totalSeconds.
  prefix := directory pathParts size.
  self allDirectories do: [:dir | | parts dirScore fileScore |
  parts := dir pathParts allButFirst: prefix.
  dirScore := (parts select: [ :part | fpattern match: part ]) size.
  fileScore := (dir entries collect: [ :ent |
  (ent isDirectory not and: [ fpattern match: ent name ])
  ifFalse: [ SmallInteger maxVal ]
  ifTrue: [ now - ent modificationTime ]]). "minimum age"
  fileScore := fileScore isEmpty ifTrue: [ SmallInteger maxVal  ]
  ifFalse: [ fileScore min ].
  possible add: { dirScore. fileScore. dir } ].
+ possible
+ sort: [ :a :b |
+ a first = b first
+ ifTrue: [ a second = b second
+ ifFalse: [ a second < b second ]
+ ifTrue: [ a third fullName size < b third fullName size ]]
+ ifFalse: [ a first > b first ] ].
+ ^(possible first third) fullNameFor: aBaseName!
- ^ (possible first third) fullNameFor: aBaseName!

Item was changed:
  ----- Method: MCVersionNotification>>initializeWithVersion:repository: (in category 'as yet unclassified') -----
  initializeWithVersion: aVersion repository: aRepository
  version := aVersion.
  repository := aRepository.
  ancestor := repository closestAncestorVersionFor: version info ifNone: [].
  changes := ancestor
  ifNil: [#()]
+ ifNotNil: [(version snapshot patchRelativeToBase: ancestor snapshot) operations sorted]!
- ifNotNil: [(version snapshot patchRelativeToBase: ancestor snapshot) operations asSortedCollection]!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>workingCopies (in category 'morphic ui') -----
  workingCopies
+ ^ MCWorkingCopy allManagers sort:
- ^ MCWorkingCopy allManagers asSortedCollection:
  [ :a :b | a package name <= b package name ]!

Item was changed:
  ----- Method: PseudoClass>>asClassDefinition (in category '*monticello') -----
  asClassDefinition
  ^ MCClassDefinition
  name: self name
  superclassName: self superclass name
  category: self category
  instVarNames: self instVarNames
+ classVarNames: self classVarNames
- classVarNames: self classVarNames asSortedCollection
  poolDictionaryNames: self poolDictionaryNames
+ classInstVarNames: self classInstVarNames
- classInstVarNames: self class instVarNames
  type: self typeOfClass
+ comment: self organization classComment asString
- comment: self organization classComment asString
  commentStamp: self organization commentStamp !