The Trunk: Monticello-tfel.608.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-tfel.608.mcz

commits-2
Nicolas Cellier uploaded a new version of Monticello to project The Trunk:
http://source.squeak.org/trunk/Monticello-tfel.608.mcz

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

Name: Monticello-tfel.608
Author: tfel
Time: 31 March 2015, 6:19:34.129 pm
UUID: 62e1b3e7-bfeb-ca4d-97e6-118c603be2d8
Ancestors: Monticello-bf.607

add a menu item to browse patch against another version in the repository

=============== Diff against Monticello-bf.607 ===============

Item was changed:
  ----- Method: ChangeList>>changeTo: (in category '*monticello') -----
  changeTo: changeSubset
  | newList newChangeList |
 
  newChangeList := OrderedCollection new.
  newList := OrderedCollection new.
 
  1 to: changeList size do:
  [:i | (changeSubset includes: (changeList at: i)) ifTrue:
  [newChangeList add: (changeList at: i).
  newList add: (list at: i)]].
  newChangeList size < changeList size
  ifTrue:
  [changeList := newChangeList.
  list := newList.
  listIndex := 0.
  listSelections := Array new: list size withAll: false].
  self changed: #list
 
  !

Item was changed:
  ----- Method: CrLfFileStream>>lineEndingConvention: (in category '*monticello') -----
  lineEndingConvention: aSymbol
  lineEndConvention := aSymbol!

Item was changed:
  ----- Method: MCAddition>>intializeWithDefinition: (in category 'initializing') -----
  intializeWithDefinition: aDefinition
  definition := aDefinition!

Item was changed:
  ----- Method: MCAncestry>>commonAncestorWith: (in category 'ancestry') -----
  commonAncestorWith: aNode
  | commonAncestors |
  commonAncestors := self commonAncestorsWith: aNode.
  ^ commonAncestors at: 1 ifAbsent: [nil]!

Item was changed:
  ----- Method: MCAncestry>>commonAncestorsWith: (in category 'ancestry') -----
  commonAncestorsWith: aVersionInfo
 
  | sharedAncestors mergedOrder sorter |
  sorter := MCVersionSorter new
  addVersionInfo: self;
  addVersionInfo: aVersionInfo.
  mergedOrder := sorter sortedVersionInfos.
  sharedAncestors := (sorter allAncestorsOf: self) intersection: (sorter allAncestorsOf: aVersionInfo).
  ^ mergedOrder select: [:ea | sharedAncestors includes: ea]!

Item was changed:
  ----- Method: MCAncestry>>initialize (in category 'initialize-release') -----
  initialize
  ancestors := #().
  stepChildren := #()!

Item was changed:
  ----- Method: MCCacheRepository>>cacheForPackage: (in category 'as yet unclassified') -----
  cacheForPackage: aPackage
  packageCaches ifNil: [packageCaches := Dictionary new].
  ^ packageCaches at: aPackage ifAbsentPut: [MCPackageCache new]!

Item was changed:
  ----- Method: MCCacheRepository>>seenFileNames (in category 'as yet unclassified') -----
  seenFileNames
  ^ seenFiles ifNil: [seenFiles := OrderedCollection new]!

Item was changed:
  ----- Method: MCChangeSelectionRequest>>label: (in category 'accessing') -----
  label: aString
  label := aString!

Item was changed:
  ----- Method: MCChangeSelectionRequest>>patch: (in category 'accessing') -----
  patch: aPatch
  patch := aPatch!

Item was changed:
  ----- Method: MCChangeSelector>>kept (in category 'as yet unclassified') -----
  kept
  ^ kept ifNil: [kept := Set new]!

Item was changed:
  ----- Method: MCChangeSelector>>listSelectionAt:put: (in category 'as yet unclassified') -----
  listSelectionAt: aNumber put: aBoolean
  | item |
  item := self items at: aNumber.
  aBoolean
  ifTrue: [self kept add: item ]
  ifFalse: [self kept remove: item ifAbsent: []]!

Item was changed:
  ----- Method: MCChangeSelector>>selectNone (in category 'as yet unclassified') -----
  selectNone
  kept := Set new.
  self changed: #list!

Item was changed:
  ----- Method: MCCodeTool>>browseVersions (in category 'menus') -----
  browseVersions
  "Create and schedule a message set browser on all versions of the
  currently selected message selector."
 
  | class selector compiledMethod |
  class := self selectedClassOrMetaClass.
  selector := self selectedMessageName.
  compiledMethod := class compiledMethodAt: selector ifAbsent: [ ^self ].
  VersionsBrowser
  browseVersionsOf: compiledMethod
  class: class theNonMetaClass
  meta: class isMeta
  category: self selectedMessageCategoryName
  selector: selector!

Item was changed:
  ----- Method: MCCodeTool>>copySelector (in category 'menus') -----
  copySelector
  "Copy the selected selector to the clipboard"
 
  | selector |
  (selector := self selectedMessageName) ifNotNil:
  [Clipboard clipboardText: selector asString]!

Item was changed:
  ----- Method: MCCodeTool>>findMethodInChangeSets (in category 'menus') -----
  findMethodInChangeSets
  "Find and open a changeSet containing the current method."
 
  | aName |
  (aName := self selectedMessageName) ifNotNil: [
  ChangeSorter browseChangeSetsWithClass: self selectedClassOrMetaClass
  selector: aName]!

Item was changed:
  ----- Method: MCConflict>>chooseLocal (in category 'as yet unclassified') -----
  chooseLocal
  chooseRemote := false!

Item was changed:
  ----- Method: MCConflict>>chooseRemote (in category 'as yet unclassified') -----
  chooseRemote
  chooseRemote := true!

Item was changed:
  ----- Method: MCConflict>>clearChoice (in category 'as yet unclassified') -----
  clearChoice
  chooseRemote := nil!

Item was changed:
  ----- Method: MCConflict>>operation: (in category 'as yet unclassified') -----
  operation: anOperation
  operation := anOperation!

Item was changed:
  ----- Method: MCConflict>>summary (in category 'as yet unclassified') -----
  summary
  | attribute |
  attribute :=
  self isResolved
  ifTrue: [self remoteChosen ifTrue: [#underlined] ifFalse: [#struckOut]]
  ifFalse: [#bold].
  ^ Text string: operation summary attribute: (TextEmphasis perform: attribute)!

Item was changed:
  ----- Method: MCDefinitionIndex>>definitionLike:ifPresent:ifAbsent: (in category 'as yet unclassified') -----
  definitionLike: aDefinition ifPresent: foundBlock ifAbsent: errorBlock
  | definition |
  definition := definitions at: aDefinition description ifAbsent: [].
  ^ definition
  ifNil: errorBlock
  ifNotNil: [foundBlock value: definition]!

Item was changed:
  ----- Method: MCDefinitionIndex>>initialize (in category 'as yet unclassified') -----
  initialize
  definitions := Dictionary new!

Item was changed:
  ----- Method: MCDependencySorter class>>sortItems: (in category 'as yet unclassified') -----
  sortItems: aCollection
  | sorter |
  sorter := self items: aCollection.
  sorter externalRequirements do: [:req  | sorter addProvision: req].
  ^ sorter orderedItems.!

Item was changed:
  ----- Method: MCDependencySorter>>addProvision: (in category 'private') -----
  addProvision: anObject
  | newlySatisfied |
  provided add: anObject.
  newlySatisfied := required removeKey: anObject ifAbsent: [#()].
  self addAll: newlySatisfied.!

Item was changed:
  ----- Method: MCDependencySorter>>initialize (in category 'initialize-release') -----
  initialize
  provided := Set new.
  required := Dictionary new.
  orderedItems := OrderedCollection new.!

Item was changed:
  ----- Method: MCDependencySorter>>itemsWithMissingRequirements (in category 'accessing') -----
  itemsWithMissingRequirements
  | items |
  items := Set new.
  required do: [:ea | items addAll: ea].
  ^ items
  !

Item was changed:
  ----- Method: MCDictionaryRepository>>description: (in category 'as yet unclassified') -----
  description: aString
 
  description := aString !

Item was changed:
  ----- Method: MCDictionaryRepository>>dictionary: (in category 'as yet unclassified') -----
  dictionary: aDictionary
 
  dict := aDictionary!

Item was changed:
  ----- Method: MCDictionaryRepository>>initialize (in category 'as yet unclassified') -----
  initialize
 
  dict := Dictionary new.
  !

Item was changed:
  ----- Method: MCDictionaryRepository>>sortedVersionInfos (in category 'as yet unclassified') -----
  sortedVersionInfos
  | sorter |
  sorter := MCVersionSorter new.
  self allVersionInfos do: [:ea | sorter addVersionInfo: ea].
  ^ sorter sortedVersionInfos
  !

Item was changed:
  ----- Method: MCDiffyVersion>>initializeWithPackage:info:dependencies:baseInfo:patch: (in category 'as yet unclassified') -----
  initializeWithPackage: aPackage info: aVersionInfo dependencies: aCollection baseInfo: baseVersionInfo patch: aPatch
  patch := aPatch.
  base := baseVersionInfo.
  super initializeWithPackage: aPackage info: aVersionInfo snapshot: nil dependencies: aCollection.
  !

Item was changed:
  ----- Method: MCDiffyVersion>>snapshot (in category 'as yet unclassified') -----
  snapshot
  ^ snapshot ifNil: [snapshot := MCPatcher apply: patch to: self baseSnapshot]!

Item was changed:
  ----- Method: MCDirectoryRepository>>directory: (in category 'accessing') -----
  directory: aDirectory
  directory := aDirectory!

Item was changed:
  ----- Method: MCDirectoryRepository>>initialize (in category 'accessing') -----
  initialize
  directory := FileDirectory default!

Item was changed:
  ----- Method: MCDirectoryRepository>>readStreamForFileNamed:do: (in category 'accessing') -----
  readStreamForFileNamed: aString do: aBlock
  | file val |
  file := FileStream readOnlyFileNamed: (directory fullNameFor: aString).
  val := aBlock value: file.
  file close.
  ^ val!

Item was changed:
  ----- Method: MCDirectoryRepository>>writeStreamForFileNamed:replace:do: (in category 'accessing') -----
  writeStreamForFileNamed: aString replace: aBoolean do: aBlock
  | file sel |
  sel := aBoolean ifTrue: [#forceNewFileNamed:] ifFalse: [#newFileNamed:].
  file := FileStream perform: sel with: (directory fullNameFor: aString).
  aBlock value: file.
  file close.!

Item was changed:
  ----- Method: MCDoItParser>>source: (in category 'as yet unclassified') -----
  source: aString
  source := aString!

Item was changed:
  ----- Method: MCFileBasedRepository>>canReadFileNamed: (in category 'private-files') -----
  canReadFileNamed: aString
  | reader |
  reader := MCVersionReader readerClassForFileNamed: aString.
  ^ reader notNil!

Item was changed:
  ----- Method: MCFilteredVersionSorter>>target: (in category 'as yet unclassified') -----
  target: aVersionInfo
  target := aVersionInfo!

Item was changed:
  ----- Method: MCFtpRepository>>clientDo: (in category 'as yet unclassified') -----
  clientDo: aBlock
  | client |
  client := FTPClient openOnHostNamed: host.
  client loginUser: user password: password.
  directory isEmpty ifFalse: [client changeDirectoryTo: directory].
  ^ [aBlock value: client] ensure: [client close]!

Item was changed:
  ----- Method: MCFtpRepository>>directory: (in category 'as yet unclassified') -----
  directory: dirPath
  directory := dirPath!

Item was changed:
  ----- Method: MCFtpRepository>>host: (in category 'as yet unclassified') -----
  host: hostname
  host := hostname!

Item was changed:
  ----- Method: MCFtpRepository>>password: (in category 'as yet unclassified') -----
  password: passwordString
  password := passwordString!

Item was changed:
  ----- Method: MCFtpRepository>>user: (in category 'as yet unclassified') -----
  user: userString
  user := userString!

Item was changed:
  ----- Method: MCFtpRepository>>writeStreamForFileNamed:replace:do: (in category 'required') -----
  writeStreamForFileNamed: aString replace: ignoreBoolean do: aBlock
  | stream |
  stream := RWBinaryOrTextStream on: String new.
  aBlock value: stream.
  self clientDo:
  [:client |
  client binary.
  client putFileStreamContents: stream reset as: aString]!

Item was changed:
  ----- Method: MCGOODSRepository>>host: (in category 'as yet unclassified') -----
  host: aString
  hostname := aString!

Item was changed:
  ----- Method: MCGOODSRepository>>port: (in category 'as yet unclassified') -----
  port: aNumber
  port := aNumber!

Item was changed:
  ----- Method: MCHttpRepository>>location: (in category 'accessing') -----
  location: aUrlString
  location := aUrlString!

Item was changed:
  ----- Method: MCHttpRepository>>password: (in category 'accessing') -----
  password: passwordString
  password := passwordString!

Item was changed:
  ----- Method: MCHttpRepository>>user: (in category 'accessing') -----
  user: userString
  user := userString!

Item was changed:
  ----- Method: MCMcdReader>>loadBaseInfo (in category 'as yet unclassified') -----
  loadBaseInfo
  ^ baseInfo := self extractInfoFrom: (self parseMember: 'base')!

Item was changed:
  ----- Method: MCMczReader>>infoCache (in category 'as yet unclassified') -----
  infoCache
  ^ infoCache ifNil: [infoCache := Dictionary new]!

Item was changed:
  ----- Method: MCMczReader>>loadDependencies (in category 'loading') -----
  loadDependencies
  dependencies := (self zip membersMatching: 'dependencies/*') collect: [:m | self extractDependencyFrom: m].
  dependencies := dependencies asArray.
  !

Item was changed:
  ----- Method: MCMczReader>>loadPackage (in category 'loading') -----
  loadPackage
  | dict |
  dict := self parseMember: 'package'.
  package := MCPackage named: (dict at: #name)!

Item was changed:
  ----- Method: MCMczReader>>loadVersionInfo (in category 'loading') -----
  loadVersionInfo
  info := self extractInfoFrom: (self parseMember: 'version')!

Item was changed:
  ----- Method: MCMczReader>>zip (in category 'as yet unclassified') -----
  zip
  zip ifNil:
  [zip := ZipArchive new.
  zip readFrom: stream].
  ^ zip!

Item was changed:
  ----- Method: MCMczWriter class>>fileOut:on: (in category 'as yet unclassified') -----
  fileOut: aVersion on: aStream
  | inst |
  inst := self on: aStream.
  inst writeVersion: aVersion.
  inst flush.
 
  !

Item was changed:
  ----- Method: MCMczWriter>>addString:at: (in category 'writing') -----
  addString: string at: path
  | member |
  member := zip addString: string as: path.
  member desiredCompressionMethod: ZipArchive compressionDeflated
  !

Item was changed:
  ----- Method: MCMczWriter>>initialize (in category 'initializing') -----
  initialize
  zip := ZipArchive new.
  !

Item was changed:
  ----- Method: MCMczWriter>>serializeInBinary: (in category 'serializing') -----
  serializeInBinary: aSnapshot
  | writer s |
  s := RWBinaryOrTextStream on: String new.
  writer := DataStream on: s.
  writer nextPut: aSnapshot.
  ^ s contents!

Item was changed:
  ----- Method: MCMczWriter>>serializeVersionInfo: (in category 'serializing') -----
  serializeVersionInfo: aVersionInfo
  infoWriter ifNil: [infoWriter := MCVersionInfoWriter new].
  ^ String streamContents:
  [:s |
  infoWriter stream: s.
  infoWriter writeVersionInfo: aVersionInfo]!

Item was changed:
  ----- Method: MCMergeBrowser class>>resolveConflictsInMerger: (in category 'as yet unclassified') -----
  resolveConflictsInMerger: aMerger
  | inst |
  inst := self new merger: aMerger.
  ^ inst showModally ifNil: [false]!

Item was changed:
  ----- Method: MCMergeRecord>>ancestorInfo (in category 'as yet unclassified') -----
  ancestorInfo
  ^ ancestorInfo ifNil: [ancestorInfo := version info commonAncestorWith: version workingCopy ancestry]!

Item was changed:
  ----- Method: MCMergeRecord>>ancestorSnapshot (in category 'as yet unclassified') -----
  ancestorSnapshot
  ^ ancestorSnapshot ifNil: [ancestorSnapshot := version workingCopy findSnapshotWithVersionInfo: self ancestorInfo]!

Item was changed:
  ----- Method: MCMergeRecord>>imagePatch (in category 'as yet unclassified') -----
  imagePatch
  ^ imagePatch ifNil: [imagePatch := self packageSnapshot patchRelativeToBase: self ancestorSnapshot]!

Item was changed:
  ----- Method: MCMergeRecord>>initializeWithVersion: (in category 'as yet unclassified') -----
  initializeWithVersion: aVersion
  version := aVersion!

Item was changed:
  ----- Method: MCMergeRecord>>mergePatch (in category 'as yet unclassified') -----
  mergePatch
  ^ mergePatch ifNil: [mergePatch := version snapshot patchRelativeToBase: self ancestorSnapshot]!

Item was changed:
  ----- Method: MCMergeRecord>>packageSnapshot (in category 'as yet unclassified') -----
  packageSnapshot
  ^ packageSnapshot ifNil: [packageSnapshot := version package snapshot]!

Item was changed:
  ----- Method: MCMergeResolutionRequest>>merger: (in category 'accessing') -----
  merger: aMerger
  merger := aMerger!

Item was changed:
  ----- Method: MCMerger>>conflicts (in category 'as yet unclassified') -----
  conflicts
  ^ conflicts ifNil: [conflicts := OrderedCollection new]!

Item was changed:
  ----- Method: MCMerger>>load (in category 'as yet unclassified') -----
  load
  | loader |
  loader := MCPackageLoader new.
  loader provisions addAll: self provisions.
  self applyTo: loader.
  loader load!

Item was changed:
  ----- Method: MCModification>>initializeWithBase:target: (in category 'initializing') -----
  initializeWithBase: base target: target
  obsoletion := base.
  modification := target.!

Item was changed:
  ----- Method: MCOrganizationDefinition>>categories: (in category 'accessing') -----
  categories: anArray
  categories := anArray!

Item was changed:
  ----- Method: MCOrganizationDefinition>>commonPrefix (in category 'accessing') -----
  commonPrefix
  | stream |
  categories isEmpty ifTrue: [^ ''].
 
  stream := String new writeStream.
  categories first withIndexDo:
  [:c :i|
  categories do:
  [:ea |
  (ea at: i ifAbsent: []) = c ifFalse: [^ stream contents]].
  stream nextPut: c].
  ^ stream contents!

Item was changed:
  ----- Method: MCPackage>>name: (in category 'accessing') -----
  name: aString
  name := aString!

Item was changed:
  ----- Method: MCPackageCache>>initialize (in category 'as yet unclassified') -----
  initialize
  sorter := MCVersionSorter new.
  fileNames := Dictionary new.!

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

Item was changed:
  ----- Method: MCPackageLoader>>installSnapshot: (in category 'public') -----
  installSnapshot: aSnapshot
  | patch |
  patch := aSnapshot patchRelativeToBase: MCSnapshot empty.
  patch applyTo: self.
  !

Item was changed:
  ----- Method: MCPackageLoader>>sorterForItems: (in category 'private') -----
  sorterForItems: aCollection
  | sorter |
  sorter := MCDependencySorter items: aCollection.
  sorter addExternalProvisions: self provisions.
  ^ sorter!

Item was changed:
  ----- Method: MCPackageLoader>>updatePackage:withSnapshot: (in category 'public') -----
  updatePackage: aPackage withSnapshot: aSnapshot
  |  patch packageSnap |
  packageSnap := aPackage snapshot.
  patch := aSnapshot patchRelativeToBase: packageSnap.
  patch applyTo: self.
  packageSnap definitions do: [:ea | self provisions addAll: ea provisions]
  !

Item was changed:
  ----- Method: MCPackageManager class>>forPackage: (in category 'as yet unclassified') -----
  forPackage: aPackage
  ^ self registry at: aPackage ifAbsent:
  [|mgr|
  mgr := self new initializeWithPackage: aPackage.
  self registry at: aPackage put: mgr.
  self changed: #allManagers.
  mgr]!

Item was changed:
  ----- Method: MCPackageManager class>>registry (in category 'as yet unclassified') -----
  registry
  ^ registry ifNil: [registry := Dictionary new]!

Item was changed:
  ----- Method: MCPackageManager>>initialize (in category 'initialize-release') -----
  initialize
  modified := false.
  self registerForNotifications.!

Item was changed:
  ----- Method: MCPackageManager>>initializeWithPackage: (in category 'initialize-release') -----
  initializeWithPackage: aPackage
  package := aPackage.
  self initialize.!

Item was changed:
  ----- Method: MCPatch>>initializeWithBase:target: (in category 'initialize-release') -----
  initializeWithBase: baseSnapshot target: targetSnapshot
  | base target |
  operations := OrderedCollection new.
  base := MCDefinitionIndex definitions: baseSnapshot definitions.
  target := MCDefinitionIndex definitions: targetSnapshot definitions.
 
  target definitions do:
  [:t |
  base
  definitionLike: t
  ifPresent: [:b | (b isSameRevisionAs: t) ifFalse: [operations add: (MCModification of: b to: t)]]
  ifAbsent: [operations add: (MCAddition of: t)]]
  displayingProgress: 'Diffing...'.
 
  base definitions do:
  [:b |
  target
  definitionLike: b
  ifPresent: [:t]
  ifAbsent: [operations add: (MCRemoval of: b)]] !

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

Item was changed:
  ----- Method: MCPatcher class>>apply:to: (in category 'as yet unclassified') -----
  apply: aPatch to: aSnapshot
  | loader |
  loader := self snapshot: aSnapshot.
  aPatch applyTo: loader.
  ^ loader patchedSnapshot!

Item was changed:
  ----- Method: MCPatcher>>initializeWithSnapshot: (in category 'as yet unclassified') -----
  initializeWithSnapshot: aSnapshot
  definitions := MCDefinitionIndex definitions: aSnapshot definitions!

Item was changed:
  ----- Method: MCReader class>>on:name: (in category 'instance creation') -----
  on: aStream name: aFileName
  | class |
  class := self readerClassForFileNamed: aFileName.
  ^ class
  ifNil: [self error: 'Unsupported format: ', aFileName]
  ifNotNil: [class on: aStream]!

Item was changed:
  ----- Method: MCReader>>stream: (in category 'accessing') -----
  stream: aStream
  stream := aStream!

Item was changed:
  ----- Method: MCRemoval>>intializeWithDefinition: (in category 'initializing') -----
  intializeWithDefinition: aDefinition
  definition := aDefinition!

Item was changed:
  ----- Method: MCRepository>>doAlwaysStoreDiffs (in category 'accessing') -----
  doAlwaysStoreDiffs
  storeDiffs := true!

Item was changed:
  ----- Method: MCRepository>>doNotAlwaysStoreDiffs (in category 'accessing') -----
  doNotAlwaysStoreDiffs
  storeDiffs := false!

Item was changed:
  ----- Method: MCRepository>>sendNotificationsForVersion: (in category 'accessing') -----
  sendNotificationsForVersion: aVersion
  | notification notifyList |
  notifyList := self notifyList.
  notifyList isEmpty ifFalse:
  [notification := self notificationForVersion: aVersion.
  notifyList do: [:ea | notification notify: ea]]!

Item was changed:
  ----- Method: MCRepositoryGroup class>>default (in category 'accessing') -----
  default
  ^ default ifNil: [default := self new]!

Item was changed:
  ----- Method: MCRepositoryInspector class>>repository:workingCopy: (in category 'instance creation') -----
  repository: aFileBasedRepository workingCopy: aWorkingCopy
  ^self new
  setRepository: aFileBasedRepository workingCopy: aWorkingCopy;
  yourself!

Item was changed:
  ----- Method: MCRepositoryInspector>>defaultExtent (in category 'morphic ui') -----
  defaultExtent
  ^450@300!

Item was changed:
  ----- Method: MCRepositoryInspector>>defaultLabel (in category 'morphic ui') -----
  defaultLabel
  ^'Repository: ' , repository description!

Item was changed:
  ----- Method: MCRepositoryInspector>>hasVersion (in category 'morphic ui') -----
  hasVersion
  ^ selectedVersion notNil!

Item was changed:
  ----- Method: MCRepositoryInspector>>packageListMenu: (in category 'morphic ui') -----
  packageListMenu: aMenu
  ^aMenu!

Item was changed:
  ----- Method: MCRepositoryInspector>>versionListMenu: (in category 'morphic ui') -----
  versionListMenu: aMenu
  1 to: self orderSpecs size do: [ :index |
  aMenu addUpdating: #orderString: target: self selector: #order: argumentList: { index } ].
+ aMenu addLine.
+ aMenu add: 'Changes against ...' action: [| ri |
+ ri := aMenu defaultTarget.
+ (UIManager default
+ chooseFrom: ri allVersionNames
+ values: ri allVersionNames
+ title: 'Select version to show patch against ...') ifNotNilDo: [:name |
+ | versionName target base |
+ versionName := MCVersionName on: name.
+ target := ri repository versionNamed: ri versionInfo name.
+ base := aMenu defaultTarget repository versionNamed: versionName.
+ (MCPatchBrowser
+ forPatch: (target snapshot patchRelativeToBase: base snapshot))
+ showLabelled: 'Changes from ', versionName, ' to ', ri versionInfo name]].
  ^aMenu!

Item was changed:
  ----- Method: MCRepositoryInspector>>widgetSpecs (in category 'morphic ui') -----
  widgetSpecs
  ^#( ((buttonRow) (0 0 1 0) (0 0 0 30))
  ((listMorph: package) (0 0 0.5 0.6) (0 30 0 0))
  ((listMorph: version) (0.5 0 1 0.6) (0 30 0 0))
  ((textMorph: summary) (0 0.6 1 1) (0 0 0 0)) )!

Item was changed:
  ----- Method: MCSMCacheRepository>>allFullFileNames (in category 'accessing') -----
  allFullFileNames
  | cachedPackages |
  cachedPackages := smCache map installedPackages select: [ :ea | ea isCached ].
  ^Array streamContents: [ :s |
  cachedPackages do: [ :ea | | d |
  d := ea cacheDirectory.
  (d fileNamesMatching: '*.mcz') do: [ :fn | s nextPut: (d fullNameFor: fn) ]]]!

Item was changed:
  ----- Method: MCSMCacheRepository>>readStreamForFileNamed:do: (in category 'file streaming') -----
  readStreamForFileNamed: aString do: aBlock
  | file fileName |
  fileName := self fullNameFor: aString.
  fileName ifNil: [
  "assume that this will come from the cache."
  ^MCCacheRepository default readStreamForFileNamed: aString do: aBlock ].
  file := FileStream readOnlyFileNamed: fileName.
  ^[ aBlock value: file ] ensure: [ file close ].
  !

Item was changed:
  ----- Method: MCSMReleaseRepository>>basicStoreVersion: (in category 'as yet unclassified') -----
  basicStoreVersion: aVersion
  | url |
  url := self uploadVersion: aVersion.
  self releaseVersion: aVersion url: url!

Item was changed:
  ----- Method: MCSMReleaseRepository>>initializeWithPackage:user:password: (in category 'as yet unclassified') -----
  initializeWithPackage: packageString user: userString password: passString
  packageName := packageString.
  user := userString.
  password := passString.
  !

Item was changed:
  ----- Method: MCSMReleaseRepository>>stringForVersion: (in category 'as yet unclassified') -----
  stringForVersion: aVersion
  | stream |
  stream := RWBinaryOrTextStream on: String new.
  aVersion fileOutOn: stream.
  ^ stream contents!

Item was changed:
  ----- Method: MCSMReleaseRepository>>uploadVersion: (in category 'as yet unclassified') -----
  uploadVersion: aVersion
  | result stream |
  result := HTTPSocket
  httpPut: (self stringForVersion: aVersion)
  to: self squeakMapUrl, '/upload/', aVersion fileName
  user: user
  passwd: password.
  self checkResult: result.
  stream := result readStream.
  stream upToAll: 'http://'.
  ^ 'http://', stream upToEnd!

Item was changed:
  ----- Method: MCSaveVersionDialog>>logMessage: (in category 'accessing') -----
  logMessage: aString
  message := aString.
  self changed: #logMessage!

Item was changed:
  ----- Method: MCSaveVersionDialog>>versionName: (in category 'accessing') -----
  versionName: aString
  name := aString.
  self changed: #versionName!

Item was changed:
  ----- Method: MCScanner>>next (in category 'as yet unclassified') -----
  next
  | c |
  stream skipSeparators.
  c := stream peek.
  c = $# ifTrue: [c := stream next; peek].
  c = $' ifTrue: [^ self nextString].
  c = $( ifTrue: [^ self nextArray].
  c isAlphaNumeric ifTrue: [^ self nextSymbol].
  self error: 'Unknown token type'. !

Item was changed:
  ----- Method: MCScanner>>stream: (in category 'as yet unclassified') -----
  stream: aStream
  stream := aStream!

Item was changed:
  ----- Method: MCSmtpRepository>>emailAddress: (in category 'as yet unclassified') -----
  emailAddress: aString
  email := aString !

Item was changed:
  ----- Method: MCSnapshot>>initializeWithDefinitions: (in category 'initializing') -----
  initializeWithDefinitions: aCollection
  definitions := aCollection.!

Item was changed:
  ----- Method: MCSnapshotBrowser>>categorySelection: (in category 'selecting') -----
  categorySelection: aNumber
  categorySelection := aNumber = 0 ifFalse: [self visibleCategories at: aNumber].
  self classSelection: 0.
  self changed: #categorySelection;
  changed: #annotations;
  changed: #classList.
  !

Item was changed:
  ----- Method: MCSnapshotBrowser>>classDefinitionString (in category 'text') -----
  classDefinitionString
  | defs |
  defs := items select: [:ea | (ea isClassDefinition or: [ea isClassDefinitionExtension])
  and: [ea className = classSelection]].
 
  defs isEmpty ifTrue: [^ 'This class is defined elsewhere.'].
 
  ^ String streamContents: [:stream |
  defs asArray sort
  do: [:ea | ea printDefinitionOn: stream]
  separatedBy: [stream nextPut: $.; cr]
  ].!

Item was changed:
  ----- Method: MCSnapshotBrowser>>methodSelection: (in category 'selecting') -----
  methodSelection: aNumber
  methodSelection := aNumber = 0 ifFalse: [self visibleMethods at: aNumber].
  self changed: #methodSelection; changed: #text; changed: #annotations!

Item was changed:
  ----- Method: MCSnapshotBrowser>>methodsForSelectedProtocol (in category 'accessing') -----
  methodsForSelectedProtocol
  | methods |
  protocolSelection ifNil: [^ Array new].
  methods := self methodsForSelectedClass asOrderedCollection.
  (protocolSelection = '-- all --')
  ifFalse: [methods removeAllSuchThat: [:ea | ea category ~= protocolSelection]].
  ^ methods
 
  !

Item was changed:
  ----- Method: MCSnapshotBrowser>>protocolSelection: (in category 'selecting') -----
  protocolSelection: anInteger
  protocolSelection := (anInteger = 0 ifFalse: [self visibleProtocols at: anInteger]).
  self methodSelection: 0.
  self changed: #protocolSelection;
  changed: #methodList;
  changed: #annotations!

Item was changed:
  ----- Method: MCSnapshotBrowser>>selectedClassOrMetaClass (in category 'accessing') -----
  selectedClassOrMetaClass
  | class |
  classSelection ifNil: [ ^nil ].
  class := Smalltalk at: classSelection ifAbsent: [ ^nil ].
  ^self switchIsClass ifTrue: [ class class ]
  ifFalse: [ class ].!

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

Item was changed:
  ----- Method: MCSnapshotBrowser>>switchBeClass (in category 'switch') -----
  switchBeClass
  switch := #class.
  self signalSwitchChanged.!

Item was changed:
  ----- Method: MCSnapshotBrowser>>switchBeComment (in category 'switch') -----
  switchBeComment
  switch := #comment.
  self signalSwitchChanged.!

Item was changed:
  ----- Method: MCSnapshotBrowser>>switchBeInstance (in category 'switch') -----
  switchBeInstance
  switch := #instance.
  self signalSwitchChanged.!

Item was changed:
  ----- Method: MCSnapshotBrowser>>switchIsInstance (in category 'switch') -----
  switchIsInstance
  switch ifNil: [switch := #instance].
  ^ switch = #instance.!

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

Item was changed:
  ----- Method: MCStReader>>categoryFromDoIt: (in category 'as yet unclassified') -----
  categoryFromDoIt: aString
  | tokens  |
  tokens := Scanner new scanTokens: aString.
  tokens size = 3 ifFalse: [self error: 'Unrecognized category definition'].
  ^ tokens at: 3!

Item was changed:
  ----- Method: MCStReader>>commentFor: (in category 'as yet unclassified') -----
  commentFor: aPseudoClass
  | comment |
  comment := aPseudoClass organization classComment.
  ^ comment asString = ''
  ifTrue: [comment]
  ifFalse: [comment string]!

Item was changed:
  ----- Method: MCStReader>>commentStampFor: (in category 'as yet unclassified') -----
  commentStampFor: aPseudoClass
  | comment |
  comment := aPseudoClass organization classComment.
  ^  [comment stamp] on: MessageNotUnderstood do: [nil]!

Item was changed:
  ----- Method: MCStReader>>loadDefinitions (in category 'evaluating') -----
  loadDefinitions
  | filePackage |
  filePackage :=
  FilePackage new
  fullName: 'ReadStream';
  fileInFrom: self readStream.
  definitions := OrderedCollection new.
  filePackage classes do:
  [:pseudoClass |
  pseudoClass hasDefinition
  ifTrue: [definitions add:
  (self classDefinitionFrom: pseudoClass)].
  definitions addAll: (self methodDefinitionsFor: pseudoClass).
  definitions addAll: (self methodDefinitionsFor: pseudoClass metaClass)].
  filePackage doIts do:
  [:ea |
  self addDefinitionsFromDoit: ea string].
  !

Item was changed:
  ----- Method: MCStReader>>systemOrganizationFromRecords: (in category 'as yet unclassified') -----
  systemOrganizationFromRecords: changeRecords
  | categories |
  categories := changeRecords
  select: [:ea | 'SystemOrganization*' match: ea string]
  thenCollect: [:ea | (self categoryFromDoIt: ea string)].
  ^ categories isEmpty ifFalse: [MCOrganizationDefinition categories: categories asArray]!

Item was changed:
  ----- Method: MCSubDirectoryRepository>>findFullNameForReading: (in category 'as yet unclassified') -----
  findFullNameForReading: aBaseName
  "Answer the latest version of aBaseName"
  | possible |
  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 add: {ent. dir fullNameFor: ent name}]]]].
  ^(possible at: 1 ifAbsent: [ ^nil ]) second
  !

Item was changed:
  ----- Method: MCSubDirectoryRepository>>readStreamForFileNamed:do: (in category 'as yet unclassified') -----
  readStreamForFileNamed: aString do: aBlock
  | file val |
  file := FileStream readOnlyFileNamed: (self findFullNameForReading: aString).
  val := aBlock value: file.
  file close.
  ^ val!

Item was changed:
  ----- Method: MCSystemCategoryParser>>addDefinitionsTo: (in category 'as yet unclassified') -----
  addDefinitionsTo: aCollection
  | definition |
  definition := aCollection detect: [:ea | ea isOrganizationDefinition ] ifNone: [aCollection add: (MCOrganizationDefinition categories: #())].
  definition categories: (definition categories copyWith: self category).!

Item was changed:
  ----- Method: MCSystemCategoryParser>>category (in category 'as yet unclassified') -----
  category
  | tokens  |
  tokens := Scanner new scanTokens: source.
  tokens size = 3 ifFalse: [self error: 'Unrecognized category definition'].
  ^ tokens at: 3!

Item was changed:
  ----- Method: MCThreeWayMerger>>initialize (in category 'as yet unclassified') -----
  initialize
  index := MCDefinitionIndex new.
  provisions := Set new!

Item was changed:
  ----- Method: MCThreeWayMerger>>operations (in category 'as yet unclassified') -----
  operations
  ^ operations ifNil: [operations := OrderedCollection new]!

Item was changed:
  ----- Method: MCTool>>label: (in category 'morphic ui') -----
  label: aString
  label := aString!

Item was changed:
  ----- Method: MCTool>>window (in category 'morphic ui') -----
  window
  ^ morph ifNil: [morph := self buildWindow]!

Item was changed:
  ----- Method: MCVariableDefinition>>name: (in category 'accessing') -----
  name: aString
  name := aString!

Item was changed:
  ----- Method: MCVersion>>allDependenciesDo:ifUnresolved: (in category 'enumerating') -----
  allDependenciesDo: aBlock ifUnresolved: failBlock
  | dict |
  dict := Dictionary new.
  self allDependenciesNotIn: dict do: aBlock ifUnresolved: failBlock!

Item was changed:
  ----- Method: MCVersion>>setPackage:info:snapshot:dependencies: (in category 'initialize-release') -----
  setPackage: aPackage info: aVersionInfo snapshot: aSnapshot dependencies: aCollection
  package := aPackage.
  info := aVersionInfo.
  snapshot := aSnapshot.
  dependencies := aCollection!

Item was changed:
  ----- Method: MCVersion>>withAllDependenciesDo:ifUnresolved: (in category 'enumerating') -----
  withAllDependenciesDo: aBlock ifUnresolved: failBlock
  | dict |
  dict := Dictionary new.
  self allDependenciesNotIn: dict do: aBlock ifUnresolved: failBlock.
  aBlock value: self!

Item was changed:
  ----- Method: MCVersionDependency>>initializeWithPackage:info: (in category 'initialize-release') -----
  initializeWithPackage: aPackage info: aVersionInfo
  package := aPackage.
  versionInfo := aVersionInfo!

Item was changed:
  ----- Method: MCVersionHistoryBrowser>>ancestry: (in category 'accessing') -----
  ancestry: anAncestry
  ancestry := anAncestry!

Item was changed:
  ----- Method: MCVersionHistoryBrowser>>index: (in category 'accessing') -----
  index: anObject
  "Set the value of index"
 
  index := anObject!

Item was changed:
  ----- Method: MCVersionHistoryBrowser>>package: (in category 'accessing') -----
  package: aMCPackage
  package := aMCPackage!

Item was changed:
  ----- Method: MCVersionHistoryBrowser>>selection: (in category 'accessing') -----
  selection: aNumber
  index := aNumber.
  self changed: #selection; changed: #summary!

Item was changed:
  ----- Method: MCVersionHistoryBrowser>>summary (in category 'accessing') -----
  summary
  | selInfo |
  selInfo := self selectedInfo.
  ^ selInfo
  ifNil: ['']
  ifNotNil: [selInfo summary]!

Item was changed:
  ----- Method: MCVersionInfoWriter>>written (in category 'as yet unclassified') -----
  written
  ^ written ifNil: [written := Set new]!

Item was changed:
  ----- Method: MCVersionInspector>>version: (in category 'accessing') -----
  version: aVersion
  version := aVersion!

Item was changed:
  ----- Method: MCVersionLoader>>checkForModifications (in category 'checking') -----
  checkForModifications
  | modifications |
  modifications := versions select: [:ea | ea package workingCopy modified].
  modifications isEmpty ifFalse: [self warnAboutLosingChangesTo: modifications].!

Item was changed:
  ----- Method: MCVersionLoader>>initialize (in category 'initialize-release') -----
  initialize
  versions := OrderedCollection new!

Item was changed:
  ----- Method: MCVersionMerger>>initialize (in category 'as yet unclassified') -----
  initialize
  records := OrderedCollection new.
  merger := MCThreeWayMerger new.!

Item was changed:
  ----- Method: MCVersionNameAndMessageRequest>>suggestedName: (in category 'accessing') -----
  suggestedName: aString
  suggestion := aString!

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 asSortedCollection]!

Item was changed:
  ----- Method: MCVersionNotification>>messageTo: (in category 'as yet unclassified') -----
  messageTo: aString
  | message |
  message := MailMessage empty.
  message setField: 'from' toString: self fromAddress.
  message setField: 'to' toString: aString.
  message setField: 'subject' toString: '[MC] ', version info name.
  message body: (MIMEDocument contentType: 'text/plain' content: self messageText).
  ^ message!

Item was changed:
  ----- Method: MCVersionNotification>>notify: (in category 'as yet unclassified') -----
  notify: aString
  | message |
  message := self messageTo: aString.
  SMTPClient
  deliverMailFrom: message from
  to: (Array with: message to)
  text: message text
  usingServer: MailSender smtpServer!

Item was changed:
  ----- Method: MCVersionSorter>>addToCurrentLayer: (in category 'as yet unclassified') -----
  addToCurrentLayer: aVersionInfo
  | layer |
  layer := layers at: depthIndex.
  (layer includes: aVersionInfo) ifFalse:
  [depths at: aVersionInfo ifPresent:
  [:i |
  i < depthIndex
  ifTrue: [(layers at: i) remove: aVersionInfo]
  ifFalse: [^ false]].
  layer add: aVersionInfo.
  depths at: aVersionInfo put: depthIndex.
  ^ true].
  ^ false !

Item was changed:
  ----- Method: MCVersionSorter>>allAncestorsOf: (in category 'as yet unclassified') -----
  allAncestorsOf: aVersionInfo
  | all |
  all := Set new.
  self addAllAncestorsOf: aVersionInfo to: all.
  ^ all!

Item was changed:
  ----- Method: MCVersionSorter>>initialize (in category 'as yet unclassified') -----
  initialize
  stepparents := Dictionary new.
  roots := OrderedCollection new.!

Item was changed:
  ----- Method: MCVersionSorter>>popLayer (in category 'as yet unclassified') -----
  popLayer
  depthIndex := depthIndex - 1!

Item was changed:
  ----- Method: MCVersionSorter>>pushLayer (in category 'as yet unclassified') -----
  pushLayer
  depthIndex := depthIndex + 1.
  depthIndex > layers size ifTrue: [layers add: OrderedCollection new].
  !

Item was changed:
  ----- Method: MCVersionSorter>>sortedVersionInfos (in category 'as yet unclassified') -----
  sortedVersionInfos
  layers := OrderedCollection with: OrderedCollection new.
  depthIndex := 1.
  depths := Dictionary new.
  roots do: [:ea | self processVersionInfo: ea].
  ^ layers gather: [:ea | ea]!

Item was changed:
  ----- Method: MCWorkingAncestry>>addStepChild: (in category 'as yet unclassified') -----
  addStepChild: aVersionInfo
  stepChildren := stepChildren copyWith: aVersionInfo!

Item was changed:
  ----- Method: MCWorkingCopy>>changesRelativeToRepository: (in category 'operations') -----
  changesRelativeToRepository: aRepository
  | ancestorVersion ancestorSnapshot |
  ancestorVersion := aRepository closestAncestorVersionFor: ancestry ifNone: [].
  ancestorSnapshot := ancestorVersion ifNil: [MCSnapshot empty] ifNotNil: [ancestorVersion snapshot].
  ^ package snapshot patchRelativeToBase: ancestorSnapshot!

Item was changed:
  ----- Method: MCWorkingCopy>>clearRequiredPackages (in category 'accessing') -----
  clearRequiredPackages
  requiredPackages := nil!

Item was changed:
  ----- Method: MCWorkingCopy>>initialize (in category 'private') -----
  initialize
  super initialize.
  ancestry := MCWorkingAncestry new!

Item was changed:
  ----- Method: MCWorkingCopy>>loaded: (in category 'operations') -----
  loaded: aVersion
  ancestry := MCWorkingAncestry new addAncestor: aVersion info.
  requiredPackages := OrderedCollection withAll: (aVersion dependencies collect: [:ea | ea package]).
  self modified: false.
  self changed!

Item was changed:
  ----- Method: MCWorkingCopy>>repositoryGroup (in category 'repositories') -----
  repositoryGroup
  ^ repositoryGroup ifNil: [repositoryGroup := MCRepositoryGroup new]!

Item was changed:
  ----- Method: MCWorkingCopy>>repositoryGroup: (in category 'repositories') -----
  repositoryGroup: aRepositoryGroup
  repositoryGroup := aRepositoryGroup!

Item was changed:
  ----- Method: MCWorkingCopy>>requiredPackages (in category 'accessing') -----
  requiredPackages
  ^ requiredPackages ifNil: [requiredPackages := OrderedCollection new]!

Item was changed:
  ----- Method: MCWorkingCopy>>uniqueVersionName (in category 'private') -----
  uniqueVersionName
  |versionName|
  counter := nil.
  [versionName := self nextVersionName.
  self repositoryGroup includesVersionNamed: versionName] whileTrue.
  ^ versionName!

Item was changed:
  ----- Method: MCWorkingCopy>>updateInstVars (in category 'migration') -----
  updateInstVars
  ancestry ifNil:
  [ancestry := MCWorkingAncestry new.
  versionInfo ifNotNil:
  [versionInfo ancestors do: [:ea | ancestry addAncestor: ea].
  versionInfo := nil]]!

Item was changed:
  ----- Method: MCWorkingCopy>>versionInfo: (in category 'accessing') -----
  versionInfo: aVersionInfo
  ancestry := MCWorkingAncestry new addAncestor: aVersionInfo!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>defaults (in category 'morphic ui') -----
  defaults
  ^ defaults ifNil: [defaults := Dictionary new]!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>repository (in category 'actions') -----
  repository
  workingCopy ifNotNil: [repository := self defaults at: workingCopy ifAbsent: []].
  ^ repository!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>repository: (in category 'actions') -----
  repository: aRepository
  repository := aRepository.
  workingCopy ifNotNil: [self defaults at: workingCopy put: aRepository]!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>viewChanges (in category 'actions') -----
  viewChanges
  | patch |
  self canSave ifTrue:
  [patch := workingCopy changesRelativeToRepository: self repository.
  patch isNil ifTrue: [^ self].
  patch isEmpty
  ifTrue: [ workingCopy modified: false.
  self inform: 'No changes' ]
  ifFalse:
  [ workingCopy modified: true.
  (MCPatchBrowser forPatch: patch)
  label: 'Patch Browser: ', workingCopy description;
  show]]!

Item was changed:
  ----- Method: MCWriter>>stream: (in category 'accessing') -----
  stream: aStream
  stream := aStream!

Item was changed:
  ----- Method: TimeStamp class>>fromMethodTimeStamp: (in category '*monticello-instance creation') -----
  fromMethodTimeStamp: aString
  | stream |
  stream := ReadStream on: aString.
  stream skipSeparators.
  stream skipTo: Character space.
  ^self readFrom: stream.!

Item was changed:
  ----- Method: TimeStamp class>>fromString: (in category '*monticello-instance creation') -----
  fromString: aString
  "Answer a new instance for the value given by aString.
 
  TimeStamp fromString: '1-10-2000 11:55:00 am'.
  "
 
  ^self readFrom: (ReadStream on: aString).!

Item was changed:
  ----- Method: TimeStamp class>>readFrom: (in category '*monticello-instance creation') -----
  readFrom: stream
  | date time |
  stream skipSeparators.
  date := Date readFrom: stream.
  stream skipSeparators.
  time := Time readFrom: stream.
  ^self
  date: date
  time: time!