[Pkg] Installer: Installer-Core-nm.350.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Fri Mar 12 15:00:52 UTC 2010


A new version of Installer-Core was added to project Installer:
http://www.squeaksource.com/Installer/Installer-Core-nm.350.mcz

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

Name: Installer-Core-nm.350
Author: nm
Time: 12 March 2010, 12:02:54 pm
UUID: 8dc3f477-c20e-a442-9365-a7a95a603f76
Ancestors: Installer-Core-nm.349

- InstallerMonticello >>mcDetectFileBlock:
   The detection is made with #beginsWith:, but if you have two different    packages which begins with the same string, it would detect a wrong package.
   Reeplaced by #copyUpToLast: $-
- InstallerMonticello >>mcSortFileBlock
   If the file has no number (it could happen, yes, and it happened to me with   a file create by MonticelloConfiguration, which I didn't remember it  existed) the files collection is sorted wrongly, since #asInteger will   answer nil.
   Replaced #asInteger by #asNumber
- Errors were logued only to the Transcript. An instance variable erros was added, and the method #logErr: add to it only the errors. Other methods were changes to support error detection

=============== Diff against Installer-Core-mtf.335 ===============

Item was changed:
  ----- Method: Installer class>>squeakfoundation (in category 'repositories') -----
  squeakfoundation
  
+ 	^ self monticello http: 'http://source.squeakfoundation.org'!
- 	^ self monticello http: 'source.squeakfoundation.org'!

Item was changed:
  ----- Method: InstallerMonticello>>basicInstall (in category 'basic interface') -----
  basicInstall
  	 
+ 	| loader |
+ 	loader:= self mcThing.
+ 	(loader notNil and:[loader versions notEmpty])
+ 		 ifTrue:[	self withAnswersDo: [  loader  load ].
+ 		self logCR: 'loaded']						
+ 
- 	self withAnswersDo: [ self mcThing load ].
- 	self logCR: 'loaded'.
  !

Item was changed:
  ----- Method: InstallerMonticello>>mcDetectFileBlock: (in category 'monticello') -----
  mcDetectFileBlock: pkg
  
+ 	pkg isString ifTrue: [  ^ [ :aFile | (aFile copyUpToLast: $- )= pkg ] ].
- 	pkg isString ifTrue: [  ^ [ :aFile | aFile beginsWith: pkg ] ].
  
  	(pkg isKindOf: Array) 
+ 			ifTrue: [  ^  [ :aFile | (pkg detect: [ :item | (aFile copyUpToLast: $- )= item ] ifNone: [ false ]) ~= false ] ].
- 			ifTrue: [  ^  [ :aFile | (pkg detect: [ :item | aFile beginsWith: item ] ifNone: [ false ]) ~= false ] ].
  
  	pkg isBlock ifTrue: [ ^ pkg ].
+   
+  
    
   !

Item was added:
+ ----- Method: Installer>>errors (in category 'accessing') -----
+ errors
+ 	"Answer the value of errors"
+ 
+ 	^ errors ifNil:[errors:= OrderedCollection new]!

Item was changed:
  ----- Method: InstallerMonticello>>mcThing (in category 'monticello') -----
  mcThing
- 
  	| loader files fileToLoad  version  count |
  
  	loader := self classMCVersionLoader new.
- 	
  	count := 0. files := nil.
  	self logCR: 'reading ', mc description, '...'.
  		"several attempts to read files - repository readableFileNames sometimes fails"
  	[ count := count + 1.
  	 (files = nil) and:[ count < 5 ] ] 
  		whileTrue: [files := mc readableFileNames asSortedCollection: self mcSortFileBlock ].
  	files ifNil: [  Warning signal: 'Repository not readable: ', mc description. ^ nil  ].
  		
  	self packages do: [ :pkg |
- 
  		self log: 'finding ', pkg asString, '...'.
  		
  		fileToLoad := files detect: (self mcDetectFileBlock: pkg) ifNone: [ nil ].
+ 			fileToLoad  isNil
+ 			ifTrue:[self logError: 'File ',pkg,' not found'.  version:=  nil. ]
- 		
- 		version := mc versionFromFileNamed: fileToLoad.
- 		(version isKindOf: MCConfiguration) 
- 			ifTrue: [ ^ version ]
  			ifFalse:[
+ 				version := mc versionFromFileNamed: fileToLoad.			
+ 				(version isKindOf: MCConfiguration) 
+ 					ifTrue: [ ^ version ]
+ 					ifFalse:[MCRepositoryGroup default addRepository: self normalizedRepository.
+ 									version workingCopy repositoryGroup addRepository: self normalizedRepository.
+ 									loader addVersion: version ].
- 				MCRepositoryGroup default addRepository: self normalizedRepository.
- 				version workingCopy repositoryGroup addRepository: self normalizedRepository.
- 				loader addVersion: version ].
  			
+ 				self logCR: ' found ', version fileName, '...'].
- 		self logCR: ' found ', version fileName, '...'.
  	].
  
  	^ loader!

Item was added:
+ ----- Method: Installer>>errors: (in category 'accessing') -----
+ errors: anObject
+ 	"Set the value of errors"
+ 
+ 	errors := anObject!

Item was changed:
  ----- Method: InstallerWeb>>basicInstall (in category 'basic interface') -----
  basicInstall
   
   	 self thing size > 0 
  		ifTrue: [ self install: url from: pageDataStream ]
+ 		ifFalse: [ url ifNil: [ ^ self logError: self package, ' not found on webSearchPath' ].
+ 				  self logError: '...',url,' was empty' ].
- 		ifFalse: [ url ifNil: [ ^ self logCR: self package, ' not found on webSearchPath' ].
- 				  self logCR: '...',url,' was empty' ].
  	 !

Item was added:
+ ----- Method: Installer>>logError: (in category 'logging') -----
+ logError: text
+ 	self errors add: text.
+ 	^self logCR: text.
+ 	!

Item was changed:
  ----- Method: InstallerWeb>>thing (in category 'web install') -----
  thing
  
  	self logCR: 'searching for web package ''', self package, ''''.
   	url := self urlToDownload.
+ 	url ifNil: [ self logError: 'page ', self package, ' not found on path' ]
- 	url ifNil: [ self logCR: 'page ', self package, ' not found on path' ]
  		ifNotNil: [ self logCR: 'found ',  url, ' ...'.   ].
  	^ pageDataStream!

Item was changed:
  Object subclass: #Installer
+ 	instanceVariableNames: 'answers packages messagesToSuppress useFileIn noiseLevel errors'
+ 	classVariableNames: 'IsSetToTrapErrors Remembered SkipLoadingTests InstallerBindings ValidationBlock'
- 	instanceVariableNames: 'answers packages messagesToSuppress useFileIn noiseLevel'
- 	classVariableNames: 'InstallerBindings IsSetToTrapErrors Remembered SkipLoadingTests ValidationBlock'
  	poolDictionaries: ''
  	category: 'Installer-Core'!
  
  !Installer commentStamp: 'kph 3/30/2009 01:29' prior: 0!
  Documentation now available at http://installer.pbwiki.com/Installer
   
  useFileIn - flag to load source.st rather than using Monticello!

Item was changed:
  ----- Method: InstallerMonticello>>mcSortFileBlock (in category 'monticello') -----
  mcSortFileBlock
  
  	^ [:a :b | 
+         	[(a findBetweenSubStrs: #($.)) allButLast last asNumber > (b findBetweenSubStrs: #($.)) allButLast last asNumber] 
-         	[(a findBetweenSubStrs: #($.)) allButLast last asInteger > (b findBetweenSubStrs: #($.)) allButLast last asInteger] 
  				on: Error do: [:ex | false]].!

Item was changed:
  ----- Method: InstallerWeb>>basicView (in category 'basic interface') -----
  basicView
   
   	 self thing size > 0 
  		ifTrue: [ self view: url from: pageDataStream ]
+ 		ifFalse: [ self logError: 'NO DATA ',url,' was empty' ].
- 		ifFalse: [ self logCR: 'NO DATA ',url,' was empty' ].
  	 !

Item was removed:
- ----- Method: Installer class>>squeaksource (in category 'repositories') -----
- squeaksource
- 
- 	^ self monticello http: 'http://www.squeaksource.com'!



More information about the Packages mailing list