[Pkg] Sake : Sake-Bob-kph.18.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Sun Mar 8 22:53:22 UTC 2009


A new version of Sake-Bob was added to project Sake :
http://www.squeaksource.com/Sake/Sake-Bob-kph.18.mcz

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

Name: Sake-Bob-kph.18
Author: kph
Time: 8 March 2009, 10:53:13 pm
UUID: e8e79476-0c33-11de-987b-000a95edb42a
Ancestors: Sake-Bob-kph.17

+ added accessors for metadata that the framework knows about - helps for documentation
+ vm is now mac21beta1U


=============== Diff against Sake-Bob-kph.17 ===============

Item was added:
+ ----- Method: BobBuild>>makeLocal: (in category 'zip file') -----
+ makeLocal: aZipFile
+ 
+ 	"if the zip file is remote, check it wasnt one we generated in our output tree"
+ 
+ 	| localZipFile |
+ 	
+ 	localZipFile := nil.
+ 	
+ 	aZipFile executive isRemote ifTrue: [
+ 		 
+ 		(self outputDir parent all filesMatching: aZipFile fileName) firstOrNil
+ 				 ifNotNilDo: [ :found |
+ 					self log info found: found.
+ 					 ^ localZipFile
+ 				]
+ 	] 
+ 	ifFalse: [ aZipFile exists ifTrue: [ ^ aZipFile ]].
+ 
+ 	(localZipFile := self class configImagesDir / aZipFile fileName) exists ifTrue: [ ^ localZipFile ].
+ 
+ 	"default is not to overwrite if the file exists"
+ 	localZipFile := (self class configImagesDir add: (localZipFile ifNil: [ aZipFile ])).
+ 		
+ 	^ localZipFile
+ 
+ 	!

Item was changed:
  ----- Method: BobPeriodicWatchSqueakMap class>>initialize (in category 'as yet unclassified') -----
  initialize
  	super initialize.
+ 	self scheduler addTask: ((self do: #doAllTasks every: 1 days) 
- 	self scheduler addTask: ((self do: #doAllTasks every: 3 days) 
  									noRunHistory;
  									description: 'watching-squeakmap';
  									yourself)
  
   !

Item was changed:
  ----- Method: BobBuildImage class>>taskBuild: (in category 'as yet unclassified') -----
  taskBuild: metaSelector
  
+ 	| reason |
- 	| isNeeded |
  	^ self define: [ :task |
  	
  		"obtain latest meta-data from instance side"	
  		(task infoFor: metaSelector) ifNil: [ ^ self noop ].
+ 		
+ 		"we set our start time to the time of the build request, the actual action may take a while longer to actually happen, however this helps to give builds instancated together a similar start time"
+ 		
+ 		task info timeInitiated: DateAndTime now.
+ 		
- 	
  		task if: [ 
  					task timeStart. 
+ 					reason := task isBuildNeeded.  "1. continue 2. symbol 3. msg"
+ 					self log info build: task info name isNeeded: reason first because: reason third.				 		 .
+ 					task info reason: reason third.
+ 						
+ 					reason first ].
- 					isNeeded := task isBuildNeeded.
- 					self log info build: task info name isNeeded: isNeeded first because: isNeeded third.				 		 .
- 					task info reason: isNeeded third.
- 					
- 					"if we are building because an upstream image has changed we grab the same build time
- 					this helps us to see which images were built together"
- 					
- 					task info timeStart: task latest timeStart.
- 					
- 					isNeeded first ].
  		
  		task action: [ 
  				task stepAction.
+ 				task actionBuild.
- 				task perform: task info action. 
  			]
  	]
  	
  
  !

Item was added:
+ ----- Method: BobBuildImage>>upload: (in category 'as yet unclassified') -----
+ upload: destDir
+ 
+ 	info upload: destDir!

Item was added:
+ ----- Method: BobBuildImage>>theScriptBasic (in category 'script') -----
+ theScriptBasic
+ 
+ 	script reset.
+ 	
+  	self
+ 		scriptTranscriptLogToFileStart;
+ 		scriptSetVersion;
+ 		scriptAddInfoScript;
+ 		scriptTranscriptLogToFileStop;
+ 		scriptSaveImageAndQuit: true!

Item was added:
+ ----- Method: BobBuildImage>>publishLinkLatest (in category 'as yet unclassified') -----
+ publishLinkLatest
+ 
+ 	self exec: 'cd ', self linksDir ,'; rm latest; ln -s ', self stamp , ' latest'
+ 	!

Item was changed:
  ----- Method: BobBuild>>stamp (in category 'as yet unclassified') -----
  stamp
  
+ 	^ (info timeInitiated ifNil: [ self timeStart ]) printYYMMDDHHSS: '-'!
- 	^ self timeStart printYYMMDDHHSS: '-'!

Item was added:
+ ----- Method: BobPeriodicWatchUniverses class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	super initialize.
+ 	self scheduler addTask: ((self do: #doAllTasks every: 15 minutes) 
+ 									noRunHistory;
+ 									description: 'watching-squeakmap';
+ 									yourself)
+ 
+  !

Item was added:
+ ----- Method: BobBuildImage>>imageCreationTime: (in category 'as yet unclassified') -----
+ imageCreationTime: aTimeStamp
+ 
+ 	info imageCreationTime: aTimeStamp!

Item was added:
+ ----- Method: BobBuild>>scriptSelector: (in category 'as yet unclassified') -----
+ scriptSelector: aSelector
+ 
+ 	info scriptSelector: aSelector!

Item was added:
+ ----- Method: BobBuildImage>>comment: (in category 'as yet unclassified') -----
+ comment: aComment
+ 
+ 	info comment: aComment!

Item was added:
+ ----- Method: BobBuildImage>>download: (in category 'as yet unclassified') -----
+ download: aComment
+ 
+ 	info download: aComment!

Item was added:
+ ----- Method: BobPeriodicWatchSqueakMap>>taskWatchSqueakMap (in category 'as yet unclassified') -----
+ taskWatchSqueakMap
+ 
+ 	| wc changes |
+ 	^ [
+ 
+ 		Packages squeakmap taskGenerateSqueakMapPackageTasks run.
+ 
+ 		wc := ((MCPackage named: 'Packages-SqueakMap') workingCopy).
+ 
+ 		changes := (wc changesRelativeToRepository: wc repository) operations collect: [ :ea | ea summary ].
+ 
+ 		changes notEmpty ifTrue: [ 
+ 			wc saveWithComment: ('auto regenerated:' , String cr, String cr, (changes joinUsing: String cr)).
+ 		]
+ 	]
+  
+  !

Item was changed:
  ----- Method: BobBuildImage>>scriptSetVersion (in category 'as yet unclassified') -----
  scriptSetVersion
  
+ 	self scriptSetVersion: ''
+ !
- 	| s |
- 	s := String new writeStream.
- 	
- 	s << '"self halt."' ; cr.
- 	s << 'SystemVersion newVersion: ' << self name printString << '.' ; cr.
- 	s << 'SystemVersion current date: ''' << self timeStart asTimeStamp printString << ''' asTimeStamp.'; cr.
- 	s << 'Smalltalk at: #Scripter ifPresent: [ :scr | scr transcript windowLabel: ''' <<
- 			self stampedName <<''' ].' ; cr.
- 
- 	self nextScriptPut: s contents!

Item was changed:
  BobConfig subclass: #BobBuildImage
  	instanceVariableNames: 'startImage'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Sake-Bob'!
  
+ !BobBuildImage commentStamp: 'kph 3/8/2009 11:16' prior: 0!
+ BobConfig is a class with only configuration data. This allows a bob installation to be customized to a local environment, and that configuation can be save by a class fileOut.
+ 
+ If you specify #imageCreationTime for an image that you do not expect to change then this saves looking up the host site every time.!
- !BobBuildImage commentStamp: 'kph 2/17/2009 01:24' prior: 0!
- BobConfig is a class with only configuration data. This allows a bob installation to be customized to a local environment, and that configuation can be save by a class fileOut.!

Item was added:
+ ----- Method: BobBuildImage>>linkRelease: (in category 'as yet unclassified') -----
+ linkRelease: aFlag
+ 
+ 	info linkRelease: aFlag
+ !

Item was added:
+ ----- Method: BobBuildImage>>scriptUpgradeMonticello (in category 'as yet unclassified') -----
+ scriptUpgradeMonticello
+ 
+ 	self nextScriptPut: 'Installer upgrade install: ''UpgradeMonticello''.'
+ !

Item was added:
+ ----- Method: BobBuildImage>>linkInProgress (in category 'accessing') -----
+ linkInProgress
+ 
+ 	^ self linksDir / 'BUILD-IN-PROGRESS'  !

Item was changed:
  ----- Method: BobConfig>>defaultUpload (in category 'as yet unclassified') -----
  defaultUpload
  		
  	"	info upload: 'ssh://updates@squeakfoundation.org/var/www/files/3.11/' , info name."
  
+ 		info upload: 'link:///bob/release/' , info name.
- 		info upload: 'link:///bob/3.11/' , info name.
  
  		"http not yet supported"
+ 		info download: 'ftp://squeak@bob.warwick.st/bob/release/' , info name.
- 		info download: 'ftp://squeak@bob.warwick.st/bob/3.11/' , info name.
  !

Item was changed:
  ----- Method: BobBuild class>>configStepAction (in category 'as yet unclassified') -----
  configStepAction
  
  	^ false
  	
  
   !

Item was changed:
  ----- Method: BobBuildImage>>publishManifest (in category 'as yet unclassified') -----
  publishManifest
  	
  	self publishDir mkpath 
  		addAll: (self imageDir filesMatching: (self stampedName, '.*')).
  		
  	self publishDir
+ 		addTree: (self imageDir all filesMatching: #('*.txt' '*.text' '*.pr' '*.pass' '*.fail' '.pdf' '*.js' '*.css' '*.html' ))
- 		addAll: (self imageDir all filesMatching: #('*.txt' '*.text' '*.pr' '*.pass' '*.fail' ))
  	
  	
  !

Item was added:
+ ----- Method: BobBuildImage>>publishLinkRelease (in category 'as yet unclassified') -----
+ publishLinkRelease
+ 	
+ 	self info linkRelease = true ifTrue: [ 
+ 
+ 		self exec:  'cd ', self linksDir ,'; rm release; ln -s ', self stamp , ' release'
+ 	]!

Item was added:
+ ScheduledLoggedTask subclass: #BobPeriodicWatchUniverses
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Sake-Bob'!

Item was added:
+ ----- Method: BobBuildImage>>image: (in category 'as yet unclassified') -----
+ image: anImageFile
+ 
+ 	info image: anImageFile!

Item was added:
+ ----- Method: BobBuildImage>>scriptSetVersion: (in category 'as yet unclassified') -----
+ scriptSetVersion: suffix
+ 
+ 	| s |
+ 	s := String new writeStream.
+ 	
+ 	s << '"self halt."' ; cr.
+ 	s << 'SystemVersion newVersion: ' << self name printString << ',' << suffix printString << '.' ; cr.
+ 	s << 'SystemVersion current date: ''' << self timeStart asTimeStamp printString << ''' asTimeStamp.'; cr.
+ 	s << 'Smalltalk at: #Scripter ifPresent: [ :scr | scr transcript windowLabel: ''' <<
+ 			self stampedName << suffix <<''' ].' ; cr.
+ 
+ 	self nextScriptPut: s contents!

Item was changed:
  ----- Method: BobConfig class>>configVm (in category 'as yet unclassified') -----
  configVm
  
  	"the mac vm doesnt like to be opened via a symbolic link"
  	
+ 	^ '/bob/vm/Squeak\ 3.8.21beta1U.app/Contents/MacOS/Squeak\ VM\ Opt'
- 	^ '/bob/vm/Squeak\ 3.8.20beta1U.app/Contents/MacOS/Squeak\ VM\ Opt'
  !

Item was changed:
  ----- Method: BobBuildImage>>scriptCleanUp (in category 'as yet unclassified') -----
  scriptCleanUp
  
+ 	self nextScriptPut: '"self halt." 
+ 	Smalltalk at: #Scripter ifPresent: [ :s | s nonTranscriptWindows do: #windowForceClose ].
+ 	SmalltalkImage current cleanUpAllExcept: #(ChangeSet).
+ 	'!
- 	self nextScriptPut: '"self halt." SmalltalkImage current cleanUpAllExcept: #(ChangeSet).'!

Item was added:
+ ----- Method: BobBuildImage>>scriptSaveAllPackagesInDir: (in category 'as yet unclassified') -----
+ scriptSaveAllPackagesInDir: dirRepoPath
+ 
+ 	| s |
+ 	s := String new writeStream.
+ 	
+ 	s << '| comment |' ; cr.
+ 
+ 	s << '"self halt."' ; cr.
+  
+ 	s << 'comment := String streamContents: [:s | ' ; cr.
+ 	s << '	Installer mantis fixesApplied asStringOn: s delimiter: String cr ].'; cr.
+ 
+ 	s << 'MCWorkingCopy saveAllAdoptingHistoryIn:'; cr.
+ 	s << '  (MCDirectoryRepository new directory: (FileDirectory on: ' <<
+ 		dirRepoPath asString printString << ')) withComment: comment contents  printString.' ; cr.
+ 
+ 	self nextScriptPut: s contents
+ 	!

Item was changed:
  ----- Method: BobBuildImage>>actionBuild (in category 'as yet unclassified') -----
  actionBuild
  
  	self log notice BUILDING: info name.
  	
+ 	self expand: (self makeLocal: zipFile) to: (self workingDir mkpath clean). 
- 	self stepAction.
- 	self expand: zipFile to: (self workingDir mkpath clean). 
  
  	self startImage: (self workingDir all fileMatching: '*.image').
- 	self linkPackageCache.
- 	
- 	self theScript scriptFileWrite.
- 			 			
- 	self launchVm: self class configVm image: self startImage with: self scriptFile.
- 			
- 	self isSuccessfulBuild ifFalse: [ ^ self ].
- 	 
- 	info timeComplete: DateAndTime now. 
- 	info timeDuration: ((info timeComplete - info timeStart) roundTo: 1 second).
- 			
- 	self publish.
- 	 
- 	self package.
- 		
- 	self tidy.
- 	self publishLinks.
- 			
- 	self log notice BUILDING: info name COMPLETE: true.
- 
- 	(self class taskUpload: info build) run.
  	
+ 	self blockDuring: [
+ 	
+ 		self linkPackageCache.
+ 	
+ 		(self perform: info scriptSelector) scriptFileWrite.
+ 			 			
+ 		self launchVm: self class configVm image: self startImage with: self scriptFile.
+ 			
+ 		self isSuccessfulBuild ifFalse: [ ^ self ].
+ 	 
+ 		info timeComplete: DateAndTime now. 
+ 		info timeDuration: ((info timeComplete - info timeStart) roundTo: 1 second).
+ 			
+ 		self publish.
+ 	 
+ 		self package.
+ 		
+ 		self tidy.
+ 		self publishLinks.
+ 			
+ 		self log notice BUILDING: info name COMPLETE: true.
+ 
+ 	].
+ 		
+ 	(self class taskUpload: info build) run.
+ 	
  !

Item was changed:
  ----- Method: BobBuildImage>>scriptSaveImageAndQuit: (in category 'as yet unclassified') -----
+ scriptSaveImageAndQuit: quit
- scriptSaveImageAndQuit: requestQuit
  
  	| s |
  	s := String new writeStream.
  	
  	s << ' | image resuming |'  ; cr.
  	s << '"self halt."' ; cr.
+ 	quit ifTrue: [ s << 'WorldState addDeferredUIMessage: [ (Delay forSeconds: 1) wait. '; cr ].
- 	s << 'WorldState addDeferredUIMessage: [ (Delay forSeconds: 1) wait. '; cr.
  	s << 'image := SmalltalkImage current.'; cr.
+ 	s << 'resuming := image saveAs: ' << self stamp printString << ', ''_'', SystemVersion current version,''.image''.'; cr.
- 	s << 'resuming := image saveAs: '''<< self stampedName << '.image''.'; cr.
  	
+ 	quit ifTrue: [
- 	requestQuit ifTrue: [
  	
  		s <<	'resuming ifFalse: [ image snapshot: false andQuit: true ].' ; cr
  	
  	].
  
+ 	quit ifTrue: [s << '].' ].
- 	s << '].'.
  
  	self nextScriptPut: s contents!

Item was added:
+ ----- Method: BobBuildImage>>isBuildNeededForBuildNow (in category 'as yet unclassified') -----
+ isBuildNeededForBuildNow
+ 	| |
+ 	
+ 	"if the output directory doesnt exist then - dont build"
+ 	self outputDir asDirectory exists ifFalse: [ 'no - ', self outputDir, ' not found' ].
+ 	
+ 	"if we have the don't flag - dont build"
+ 	info when = #dont ifTrue: [ ^ #(false #dont 'dont flag set') ].
+  	info when = false ifTrue: [ ^ #(false #dont 'dont flag false') ].
+  
+ 	self stepNeeded.
+ 	
+  
+ 	latest := self infoFileReadLatest.
+ 	
+ 	zipFile := self resolveFile: info image asFile ifNone: [:msg |  ^ { false. #notFound. msg.} ]. 
+  	
+ 	^ { true. #itsAnOrder. ('building ', self info name). }
+ 
+ 	
+ !

Item was changed:
  ----- Method: BobBuildImage>>theScript (in category 'as yet unclassified') -----
  theScript
  	
  	script reset.
  	
  	self 
  			scriptTranscriptLogToFileStart;
+ 			scriptSetVersion: '=wip';
+ 			scriptSaveImageAndQuit: false;
- 			scriptSetVersion;
  			scriptAddInfoScript;
  			scriptCleanUp;
+ 			scriptSetVersion;
  			scriptTranscriptLogToFileStop;
  			scriptSaveImageAndQuit: true.!

Item was added:
+ ----- Method: BobPeriodicWatchUniverses>>taskGeneratePackagesFromUniverses (in category 'as yet unclassified') -----
+ taskGeneratePackagesFromUniverses
+ 
+ 	| wc changes |
+ 	^ [
+ 
+ 		Packages taskGenerateAllUniverses run.
+ 
+ 		wc := ((MCPackage named: 'Packages-Library') workingCopy).
+ 
+ 		changes := (wc changesRelativeToRepository: wc repository) operations collect: [ :ea | ea summary ].
+ 
+ 		changes notEmpty ifTrue: [ 
+ 			wc saveWithComment: ('auto regenerated:' , String cr, String cr, (changes joinUsing: String cr)).
+ 		]
+ 	]!

Item was changed:
  ----- Method: BobPeriodicBuilds class>>initialize (in category 'as yet unclassified') -----
  initialize
  	super initialize.
+ 	self scheduler addTask: ((self do: #doAllTasks every: 600 seconds) 
- 	self scheduler addTask: ((self do: #doAllTasks every: 300 seconds) 
  										noRunHistory;
  										description: 'builder';
  										yourself)
  
   !

Item was changed:
  ----- Method: BobBuildImage>>isBuildNeeded (in category 'as yet unclassified') -----
  isBuildNeeded
  
  	| wait dependentFile |
  	
  	"if the output directory doesnt exist then - dont build"
+ 	self outputDir asDirectory exists ifFalse: [ ^ { false. #notWanted. 'Output directory not present: ', self outputDir.}. ].
- 	self outputDir asDirectory exists ifFalse: [ 'no - ', self outputDir, ' not found' ].
  	
  	"if we have the don't flag - dont build"
+ 	#dont = info when  ifTrue: [ ^ #(false #dont 'dont flag set') ].
+  	false = info when ifTrue: [ ^ #(false #dont 'dont flag false') ].
- 	info when = #dont ifTrue: [ ^ #(false #dont 'dont flag set') ].
-  	info when = false ifTrue: [ ^ #(false #dont 'dont flag false') ].
   
  	self stepNeeded.
  	
  	"if an explicit build time has been set and not yet reached - dont build"	
  	((info when isKindOf: DateAndTime) and: [ info when > info timeStart ]) 
  		ifTrue: [ ^ { false. #notYet. ('time is not yet ', info when asString). } ].
  
  	latest := self infoFileReadLatest.
  	
  	"if 'when' is set to a file obtain creation time, if not use info image"
  	info when isFileOrDirectory ifTrue: [
  		dependentFile := self resolveFile: info when ifNone: [:msg |  ^ { false. #notFound. msg.}].
  		self info dependentCreationTime: dependentFile creationTime.
  		zipFile := self resolveFile: info image ifNone: [:msg |  ^ { false. msg.}  ].
  
  	] ifFalse: [  
  		dependentFile := zipFile := self resolveFile: info image asFile ifNone: [:msg |  ^ { false. #notFound. msg.} ]. 
+ 		
+ 		self info dependentCreationTime: (info imageCreationTime ifNil: [ zipFile creationTime ]).
- 		self info dependentCreationTime: zipFile creationTime.
  	].
  
  	"has our starting image changed? if so"
  	 (latest dependentCreationTime notNil and: [ latest dependentCreationTime ~= self info dependentCreationTime ]) 		
+ 			ifTrue: [
+ 				self dependentFileChanged: dependentFile.
+ 				 ^ { true. #dependentChanged. (dependentFile asString , ' has changed').}  
+ 			]
+ 			ifFalse: [ true = info when ifTrue: [ ^ { false. ('waiting for ', dependentFile asString , ' to change').} ]].
- 			ifTrue: [ ^ { true. #dependentChanged. (dependentFile asString , ' has changed').}  ]
- 			ifFalse: [ info when = true ifTrue: [ ^ { false. ('waiting for ', dependentFile asString , ' to change').} ]].
  				
  				
  	"we have a new build id, so we build"
  	latest build ~= info build ifTrue: [ ^ { true. #newBuildNumber. ('new build number ',info build).}  ].
  	
  	(info when isKindOf: Duration) ifTrue: [
  		wait := latest startTime + info when - TimeStamp now
  		wait > 0 ifTrue: [ ^  { false. #waiting. (wait seconds asString, ' seconds to go').}   ].
  	].
  
  	"an explicit build time has been given, and this is present existing latest"
  	((info when isKindOf: DateAndTime) and: [ info when <= latest timeStart ]) 
  		ifTrue: [ ^ { false. #done. ((latest package ifNil: [ latest name ]) ,  ' already built'). } ].
   	
  	^ { true. #itsTime. ('building ', self info name). }
  
  	
  !

Item was added:
+ ----- Method: BobBuildImage>>blockDuring: (in category 'accessing') -----
+ blockDuring: aBlock
+ 
+ 	[ self linkInProgress exists ] whileTrue: [ SakeBlock signalTask: self ].
+ 
+ 	[ self linkInProgress symbolicLinkTo: self imageDir.
+ 	 
+ 	  aBlock value.
+ 	
+ 	] ensure: [ self exec: 'rm ', self linkInProgress ]!

Item was added:
+ ----- Method: BobBuildImage>>description: (in category 'as yet unclassified') -----
+ description: aComment
+ 
+ 	info description: aComment!

Item was changed:
  ----- Method: BobPeriodicWatchRepositories>>taskWatchPackages (in category 'as yet unclassified') -----
  taskWatchPackages
  
+ 	| |
- 	| wc changes |
  	
  	^ SakeTask 
  		checkUrl: 'http://www.squeaksource.com/Packages/feed.rss' 
  		onChanged: [
  			
  			self log info: 'Packages Library Updated'.
  
  			Installer squeaksource project: 'Packages'; install: 'Packages-Library'. 
  			
- 			Packages taskGenerateAllUniverses run.
- 
- 			wc := ((MCPackage named: 'Packages-Library') workingCopy).
- 
- 			changes := (wc changesRelativeToRepository: wc repository) operations collect: [ :ea | ea modification summary ].
- 
- 		 	wc taskSaveWithComment: ('auto regenerated:' , String cr, String cr, (changes joinUsing: String cr)).
- 			
- 			
  		].
  			
   !

Item was changed:
  ----- Method: BobBuild class>>taskUpload: (in category 'as yet unclassified') -----
  taskUpload: metaSelector
  	"the task of uploading is defined as a top level task, because it is more generic than image building, and may be applied to any result."
  	
  	| newInfo lock ul dl yes |
  	^ self define: [ :task |
  	
  		(task infoFor: metaSelector) ifNil: [ ^ self noop ].
  		task dependsOn: #().
  		
  		newInfo := task info.
  		
  		"obtain and use the latest meta-data from the most recent build activity"	
  		task info: task infoFileReadLatest.
  		
  		"some fields in the metadata we prefer new values over the older"
  		
+ 		task upload: newInfo upload.
+ 		task download: newInfo download.
+ 		task linkRelease: newInfo linkRelease.
+ 		task comment: newInfo comment.
+ 		task uploadLatest: newInfo uploadLatest.
- 		task info upload: newInfo upload.
- 		task info download: newInfo download.
- 		task info linkRelease: newInfo linkRelease.
- 		task info comment: newInfo comment.
- 		task info uploadLatest: newInfo uploadLatest.
  	
  		task if: [
  			lock := ul := dl := nil. 
  			yes := task name notNil 
  					and: [ (ul := task isUploadRequested) 
  					and: [  dl := task isUploadedFileAvailableForDownload.
  						    dl ifTrue: [ task uploadDirLock delete ].
  						    dl not and: [ (lock := task uploadDirLock exists) not ] ] ].
  					
  			task name ifNotNil:[
  					self log info name: task name uploadRequested: ul done: dl inProgress: lock.
  			].
  		
  			"if we decide that we shall upload, we lock the upload dir to inform others"
  			yes ifTrue: [ task uploadDirLock touch ].
  			yes.	
  		].
  		
  		task action: [ 
  
  			self log info UPLOADING: task publishDir.
   			self configStepUpload ifTrue: [ self halt ].
  			
  			task infoFilePublishAlongside: task publishDir.
+ 			task publishLinkRelease.
- 			task linkRelease.
  			
  			task info oneClick = true ifTrue: [ BobOneClickPackageGenerator taskMakeOneClickfor: self build: task info build ].
  			
  			task perform: ('uploadUsing', (task info upload upTo: $:) capitalized) asSymbol. 
  		
  			task isUploadedFileAvailableForDownload ifTrue: [ task uploadDirLock delete ].
  		]
  	] 
  
  !

Item was added:
+ Object subclass: #PRDelayedPersistency
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Sake-Bob'!

Item was changed:
  ----- Method: BobBuild>>infoFor: (in category 'as yet unclassified') -----
  infoFor: selector
  	 
  	selector ifNil: [ ^ nil ].
  	
  	self info name: self class label.
  	self info build: selector.
  	self info label: self class label.
  	self when: self class configWhen.
+ 	self linkRelease: self class configLinkRelease.
+ 	self description ifNotEmpty: [ self description: self description ].
+ 	info scriptSelector: #theScript.
- 	self info linkRelease: self class configLinkRelease.
- 	self description ifNotEmpty: [ self info description: self description ].
- 	info action: #actionBuild.
- 
  	self perform: selector.
  	
  ^ info!

Item was added:
+ ----- Method: BobBuild>>overwrite: (in category 'as yet unclassified') -----
+ overwrite: flag
+ 
+ 	info overwrite: flag
+ !

Item was changed:
  ----- Method: BobBuildImage>>publishLinks (in category 'as yet unclassified') -----
  publishLinks
  
+ 	self publishLinkLatest.  
+ 	self publishLinkRelease.
- 	self linkLatest.  
- 	self linkRelease.
  
  !

Item was added:
+ ----- Method: BobBuildImage>>dependentFileChanged: (in category 'as yet unclassified') -----
+ dependentFileChanged: aFile
+ 
+ 	| dependentInfo |
+ 	dependentInfo := (Compiler evaluate: (aFile copy ext: 'info') contents) ifNil: [ ^ self ].
+ 	
+ 	info timeInitiated: dependentInfo timeInitiated.
+ 	
+ 	info description: info comment, String cr,  String cr , 'Description from: ', dependentInfo name, String cr, String cr, dependentInfo description.
+  	info comment: info comment, String cr,  String cr , 'Comment from: ', dependentInfo name, String cr, String cr, dependentInfo comment.!

Item was changed:
  ----- Method: BobBuildImage class>>taskBuildNow: (in category 'as yet unclassified') -----
  taskBuildNow: metaSelector
  
  	| isNeeded |
  	^ self define: [ :task |
  	
  		"obtain latest meta-data from instance side"	
  		(task infoFor: metaSelector) ifNil: [ ^ self noop ].
  	
  		task if: [ 
  					task timeStart. 
  					
+ 					isNeeded := task isBuildNeededForBuildNow.
- 					isNeeded := task isBuildNeededOverridden.
  					
   					self log info build: task info name isNeeded: isNeeded first because: isNeeded third.				 		 .
  					task info reason: isNeeded third.
  
  					isNeeded first.
  				].
  		
  		task action: [ 
  				task stepAction.
+ 				task actionBuild.
- 				task perform: task info action. 
  			]
  	]
  	
  
  !

Item was changed:
  ScheduledLoggedTask subclass: #BobPeriodicBuilds
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Sake-Bob'!
+ 
+ !BobPeriodicBuilds commentStamp: 'kph 3/8/2009 12:46' prior: 0!
+ [  BobBuild taskBuildAll run ] fork!

Item was added:
+ ----- Method: BobBuildImage>>uploadLatest: (in category 'as yet unclassified') -----
+ uploadLatest: aBool
+ 
+ 	info uploadLatest: aBool!

Item was changed:
  ----- Method: BobBuild class>>configStepNeeded (in category 'as yet unclassified') -----
  configStepNeeded
  
  	^ false!

Item was changed:
  ----- Method: BobBuild>>expand:to: (in category 'zip file') -----
+ expand: localZipFile to: destDir
- expand: aZipFile to: destDir
- 	
- 	"if the zip file is remote, check it wasnt one we generated in our output tree"
- 
- 	| localZipFile |
- 	
- 	localZipFile := nil.
- 	
- 	aZipFile executive isRemote ifTrue: [
- 		 
- 		(self outputDir parent all filesMatching: aZipFile fileName) firstOrNil
- 				 ifNotNilDo: [ :found |
- 					self log info found: found.
- 					localZipFile := found.
- 				]
- 	].
- 
- 	"default is not to overwrite if the file exists"
- 	localZipFile := (self class configImagesDir add: (localZipFile ifNil: [ aZipFile ])).
  	
  	self log info bob expanding: localZipFile to: destDir.	
  
+ 	self exec: 'unzip "', localZipFile, '" -d ', destDir full mkpath.
- 	self exec: 'unzip ', localZipFile, ' -d ', destDir full mkpath.
  	
  	^ localZipFile
  
  	!

Item was removed:
- ----- Method: BobBuildImage>>isBuildNeededOverridden (in category 'as yet unclassified') -----
- isBuildNeededOverridden
- 
- 	| |
- 	
- 	"if the output directory doesnt exist then - dont build"
- 	self outputDir asDirectory exists ifFalse: [ 'no - ', self outputDir, ' not found' ].
- 	
- 	"if we have the don't flag - dont build"
- 	info when = #dont ifTrue: [ ^ #(false #dont 'dont flag set') ].
-  	info when = false ifTrue: [ ^ #(false #dont 'dont flag false') ].
-  
- 	self stepNeeded.
- 	
-  
- 	latest := self infoFileReadLatest.
- 	
- 	zipFile := self resolveFile: info image asFile ifNone: [:msg |  ^ { false. #notFound. msg.} ]. 
-  	
- 	^ { true. #itsAnOrder. ('building ', self info name). }
- 
- 	
- !

Item was removed:
- ----- Method: BobBuildImage>>linkLatest (in category 'as yet unclassified') -----
- linkLatest
- 
- 	self exec: 'cd ', self linksDir ,'; rm latest; ln -s ', self stamp , ' latest'
- 	!

Item was removed:
- ----- Method: BobPeriodicWatchSqueakMap>>taskWatchPackages (in category 'as yet unclassified') -----
- taskWatchPackages
- 
- 	| wc changes |
- 	
- 	^ SakeTask 
- 		checkUrl: 'http://www.squeaksource.com/Packages/feed.rss' 
- 		onChanged: [
- 			
- 			self log info: 'Packages-SqueakMapLibrary Updating'.
- 
- 			Installer squeaksource project: 'Packages'; install: 'Packages-SqueakMap'. 
- 			
- 			self squeakmap taskGenerateSqueakMapPackageTasks run.
- 
- 			wc := ((MCPackage named: 'Packages-SqueakMap') workingCopy).
- 
- 			changes := (wc changesRelativeToRepository: wc repository) operations collect: [ :ea | ea modification summary ].
- 
- 		 	wc taskSaveWithComment: ('auto regenerated:' , String cr, String cr, (changes joinUsing: String cr)).
- 			
- 			
- 		].
- 			
-  !

Item was removed:
- ----- Method: BobBuildImage>>linkRelease (in category 'as yet unclassified') -----
- linkRelease
- 	
- 	self info linkRelease = true ifTrue: [ 
- 
- 		self exec:  'cd ', self linksDir ,'; rm release; ln -s ', self stamp , ' release'
- 	]!



More information about the Packages mailing list