[Pkg] Monticello Public: Monticello.impl-kph.642.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Sun Mar 22 21:24:03 UTC 2009


A new version of Monticello.impl was added to project Monticello Public:
http://www.squeaksource.com/mc/Monticello.impl-kph.642.mcz

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

Name: Monticello.impl-kph.642
Author: kph
Time: 22 March 2009, 9:23:46 pm
UUID: 98cc7a71-ca89-4f02-82ef-1812b691aeb2
Ancestors: Monticello.impl-kph.639

System-PasswordManager is now a separate package

=============== Diff against Monticello.impl-kph.639 ===============

Item was changed:
+ ----- Method: MCRepository>>heldVersionInfosClearCache (in category 'versions') -----
- ----- Method: MCRepository>>heldVersionInfosClearCache (in category '') -----
  heldVersionInfosClearCache!

Item was changed:
  ----- Method: MCSMReleaseRepository>>password (in category 'as yet unclassified') -----
  password
+ 	^(self systemPasswordManager queryPasswordAt: self squeakMapUrl user: user) ifNil:[^''].!
- 	^(MCPasswordManager default queryPasswordAt: self squeakMapUrl user: user) ifNil:[^''].!

Item was changed:
  ----- Method: MCFtpRepository>>flushPasswords (in category 'required') -----
  flushPasswords
+ 	self systemPasswordManager passwordAt: 'ftp://',host user: user put: nil.!
- 	MCPasswordManager default passwordAt: 'ftp://',host user: user put: nil.!

Item was changed:
+ ----- Method: MCMergeResolutionRequest>>defaultAction (in category 'as yet unclassified ') -----
- ----- Method: MCMergeResolutionRequest>>defaultAction (in category 'as yet unclassified') -----
  defaultAction
  	^ (MCMergeBrowser new
  		merger: merger;
  		label: messageText) showModally!

Item was changed:
  ----- Method: MCFtpRepository>>password: (in category 'as yet unclassified') -----
  password: passwordString
  	| pwd |
  	passwordString isEmpty ifTrue:[pwd := nil] ifFalse:[pwd := passwordString].
+ 	self systemPasswordManager passwordAt: 'ftp://',host user: user put: pwd.
- 	MCPasswordManager default passwordAt: 'ftp://',host user: user put: pwd.
  !

Item was changed:
  ----- Method: MCFtpRepository>>password (in category 'as yet unclassified') -----
  password
+ 	^(self systemPasswordManager queryPasswordAt: 'ftp://',host user: user) ifNil:[^''].!
- 	^(MCPasswordManager default queryPasswordAt: 'ftp://',host user: user) ifNil:[^''].!

Item was changed:
+ ----- Method: MCRepository>>allVersionNames (in category 'versions') -----
- ----- Method: MCRepository>>allVersionNames (in category '') -----
  allVersionNames 
  	"method for comapibility with MCConfigurations"
  	^ self heldVersionNames!

Item was added:
+ ----- Method: MCRepository>>systemPasswordManager (in category 'interface') -----
+ systemPasswordManager
+ 	
+ 	^ PasswordManager default!

Item was changed:
  ----- Method: MCHttpRepository>>password: (in category 'as yet unclassified') -----
  password: passwordString
  	| pwd |
  	passwordString isEmpty ifTrue:[pwd := nil] ifFalse:[pwd := passwordString].
+ 	self systemPasswordManager passwordAt: self locationHost user: self user put: pwd.!
- 	MCPasswordManager default passwordAt: self locationHost user: self user put: pwd.!

Item was changed:
+ ----- Method: MCVersionInspector>>changes (in category 'as yet unclassified ') -----
- ----- Method: MCVersionInspector>>changes (in category 'as yet unclassified') -----
  changes
   
  	(MCPatchBrowser forPatch: self version changes)
  		showLabelled: 'Changes from ', self version info name!

Item was changed:
+ ----- Method: MCRepository>>heldVersionNames (in category 'versions') -----
- ----- Method: MCRepository>>heldVersionNames (in category '') -----
  heldVersionNames
  	^ self heldVersionInfos collect: [:v |  v versionName ]!

Item was changed:
  ----- Method: MCHttpRepository>>asCreationTemplate (in category 'as yet unclassified') -----
  asCreationTemplate
  	^self class creationTemplateLocation: location user: user password: (
+ 		(self systemPasswordManager passwordAt: location user: user) ifNil:['']
- 		(MCPasswordManager default passwordAt: location user: user) ifNil:['']
  	)!

Item was changed:
  ----- Method: MCHttpRepository>>flushPasswords (in category 'required') -----
  flushPasswords
+ 	self systemPasswordManager 
+ 		passwordAt: self locationHost user: user put: nil.!
- 	MCPasswordManager default passwordAt: self locationHost user: user put: nil.!

Item was changed:
  ----- Method: MCSMReleaseRepository>>flushPasswords (in category 'as yet unclassified') -----
  flushPasswords
+ 	self systemPasswordManager passwordAt: self squeakMapUrl user: user put: nil!
- 	MCPasswordManager default passwordAt: self squeakMapUrl user: user put: nil!

Item was changed:
  ----- Method: MCHttpRepository>>password (in category 'as yet unclassified') -----
  password
  	self user isEmpty ifTrue: [^''].
  	self user = 'squeak' ifTrue: [ ^ 'squeak' ].
  	
+ 	^(self systemPasswordManager queryPasswordAt: self locationHost user: self user) ifNil:[^'']!
- 	^(MCPasswordManager default queryPasswordAt: self locationHost user: self user) ifNil:[^'']!

Item was changed:
  ----- Method: MCSMReleaseRepository>>password: (in category 'as yet unclassified') -----
  password: passwordString
  	| pwd |
  	passwordString isEmpty ifTrue:[pwd := nil] ifFalse:[pwd := passwordString].
+ 	self systemPasswordManager passwordAt: self squeakMapUrl user: user put: pwd.!
- 	MCPasswordManager default passwordAt: self squeakMapUrl user: user put: pwd.!

Item was removed:
- ----- Method: MCPasswordManager>>passwordAt:user:put: (in category 'queries') -----
- passwordAt: location user: user put: password
- 	"Store the password under the given key"
- 	| file tokens pwd in out done sz pwdFile |
- 	user ifNil:[ ^ self ].
- 	(location indexOf: Character space) = 0 
- 		ifFalse:[^self error: 'Key must not contain spaces'].
- 	(user indexOf: Character space) = 0 
- 		ifFalse:[^self error: 'Key must not contain spaces'].
- 	password ifNotNil:[
- 		pwd := (Base64MimeConverter mimeEncode: password readStream) contents.
- 	].
- 	pwdFile := user,'.pwd'.
- 	file := [self directory readOnlyFileNamed: pwdFile] on: Error do:[:ex| ex return: nil].
- 	file ifNotNil:[
- 		[in := file contents readStream] ensure:[file close].
- 	] ifNil:[in := String new readStream].
- 	out := WriteStream on: (String new: 1000).
- 
- 	done := pwd == nil. "if clearing passwords, we're done already"
- 	[in atEnd] whileFalse:[
- 		tokens := in nextLine findTokens: ' '.
- 		tokens size = 2 ifTrue:[
- 			(tokens first match: location) 
- 				ifTrue:[pwd ifNotNil:[out nextPutAll: location; space; nextPutAll: pwd; cr. done := true]]
- 				ifFalse:[out nextPutAll: tokens first; space; nextPutAll: tokens last; cr]]].
- 	done ifFalse:[out nextPutAll: location; space; nextPutAll: pwd; cr].
- 
- 	file := [self directory forceNewFileNamed: pwdFile] on: Error do:[:ex| ex return: nil].
- 	file ifNil:[^nil].
- 	[file nextPutAll: out contents.
- 	sz := file size] ensure:[file close].
- 	sz = 0 ifTrue:[self directory deleteFileNamed: pwdFile ifAbsent:[]].
- !

Item was removed:
- Object subclass: #MCPasswordManager
- 	instanceVariableNames: 'directory'
- 	classVariableNames: 'Default'
- 	poolDictionaries: ''
- 	category: 'Monticello-Base-Repositories'!
- 
- !MCPasswordManager commentStamp: '<historical>' prior: 0!
- Simple password manager to avoid storing passwords in the image.!

Item was removed:
- ----- Method: MCPasswordManager>>passwordAt:user: (in category 'queries') -----
- passwordAt: location user: user
- 	"Answer the password stored under the given key, or nil if none can be found"
- 	| file stream tokens pwdFile |
- 	(location indexOf: Character space) = 0 
- 		ifFalse:[^self error: 'Location must not contain spaces'].
- 	(user indexOf: Character space) = 0 
- 		ifFalse:[^self error: 'User name must not contain spaces'].
- 	pwdFile := user,'.pwd'.
- 	file := [self directory readOnlyFileNamed: pwdFile] on: Error do:[:ex| ex return: nil].
- 	file ifNil:[^nil].
- 	[stream := file contents readStream] ensure:[file close].
- 	[stream atEnd] whileFalse:[
- 		tokens := stream nextLine findTokens: ' '.
- 		(tokens size = 2 and:[tokens first match: location]) ifTrue:[
- 			^(Base64MimeConverter mimeDecode: tokens last as: String)
- 		].
- 	].
- 	^nil!

Item was removed:
- ----- Method: MCPasswordManager>>queryPasswordAt:user: (in category 'queries') -----
- queryPasswordAt: location user: user
- 	"Answer the password for the given user/location. 
- 	If the password is absent, query the user if interactive."
- 	| pwd |
- 	"search for existing password"
-  
- 	pwd := self passwordAt: location user: user.
- 	pwd ifNotNil:[^pwd].
- 
- 	pwd := FillInTheBlank requestPassword: 'Password for "', user, '" at ', location.
- 	pwd isEmptyOrNil ifTrue:[^nil].
- 	(self confirm: 'Remember password for "', user, '" at ', location,'?') ifTrue:[
- 		self passwordAt: location user: user put: pwd.
- 	].
- 	^pwd
- 	
-  !

Item was removed:
- ----- Method: MCPasswordManager class>>passwordAt:user:put: (in category 'accessing') -----
- passwordAt: location user: user put: password
- 	^self default passwordAt: location user: user put: password!

Item was removed:
- ----- Method: MCPasswordManager>>directory (in category 'accessing') -----
- directory
- 	"Answer the directory in which to find the passwords"
- 	^directory ifNil:[ExternalSettings assuredPreferenceDirectory]!

Item was removed:
- ----- Method: MCPasswordManager>>editPasswords (in category 'editing') -----
- editPasswords
- 	"Edit the passwords"
- 	(self directory fileNamesMatching: '*.pwd') do:[:fName|
- 		self editPasswordsIn: (self directory fullNameFor: fName).
- 	].!

Item was removed:
- ----- Method: MCPasswordManager>>directory: (in category 'accessing') -----
- directory: aDirectory
- 	"Indicate the directory in which to find the passwords"
- 	directory := aDirectory!

Item was removed:
- ----- Method: MCPasswordManager class>>queryPasswordAt:user: (in category 'accessing') -----
- queryPasswordAt: location user: user
- 	^self default queryPasswordAt: location user: user!

Item was removed:
- ----- Method: MCPasswordManager class>>passwordAt:user: (in category 'accessing') -----
- passwordAt: location user: user
- 	^self default passwordAt: location user: user!

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

Item was removed:
- ----- Method: MCPasswordManager class>>editPasswords (in category 'accessing') -----
- editPasswords
- 	^self default editPasswords!

Item was removed:
- ----- Method: MCPasswordManager>>editPasswordsIn: (in category 'editing') -----
- editPasswordsIn: pwdFile
- 	"Edit the passwords"
- 	| file data |
- 	file := FileStream readOnlyFileNamed: pwdFile.
- 	data := file contents.
- 	file close.
- 	UIManager default edit: data label: pwdFile accept:[:text|
- 		file := FileStream forceNewFileNamed: pwdFile.
- 		file nextPutAll: text asString.
- 		file close.
- 	].
- 
- !



More information about the Packages mailing list