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

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Thu Mar 5 15:32:20 UTC 2009


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

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

Name: Sake-Bob-kph.16
Author: kph
Time: 5 March 2009, 3:32:13 pm
UUID: cd080087-099a-11de-9863-000a95edb42a
Ancestors: Sake-Bob-kph.15

getting uploads working

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

Item was changed:
  ----- Method: BobBuild>>uploadUsingLink (in category 'as yet unclassified') -----
  uploadUsingLink
  
  	"we link the completed files to a different local directory"
  	
  	| cmd path |
  
  	path := (info upload allButFirst: 7) asDirectory.
  	
  	(path / self stamp) mkpath.
  
  	cmd := 'cd ', path full, '; rm latest; ln -s ', self stamp, ' latest'.
  	
  	self info linkRelease = true ifTrue:[ 
   		cmd := cmd , '; rm release; ln -s ', self stamp, ' release'	
  	].
  
  	self uploadFiles do: [ :outFile | 
  		cmd := cmd , '; ln ', outFile , ' ', self stamp, '/',outFile fileName.
  	].
  
  	self exec: cmd.
  
+ 	self log notice UPLOADING: self publishDir LINKED: true
  !

Item was changed:
  ----- Method: BobBuildImage class>>taskBuild: (in category 'as yet unclassified') -----
  taskBuild: metaSelector
  
  	| isNeeded |
  	^ self define: [ :task |
  	
  		"obtain latest meta-data from instance side"	
  		(task infoFor: metaSelector) ifNil: [ ^ self noop ].
  	
  		task if: [ 
  					task timeStart. 
  					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.
+ 					
- 					self log info build: task info name isNeeded: isNeeded first because: isNeeded second.				 		 .
  					isNeeded first ].
  		
  		task action: [ 
  				task stepAction.
  				task perform: task info action. 
  			]
  	]
  	
  
  !

Item was added:
+ ----- Method: BobBuild class>>configStepUpload (in category 'as yet unclassified') -----
+ configStepUpload
+ 
+ 	^ false!

Item was added:
+ ----- 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/3.11/' , info name.
+ 
+ 		"http not yet supported"
+ 		info download: 'ftp://squeak@bob.warwick.st/bob/3.11/' , info name.
+ !

Item was changed:
  ----- Method: BobBuild>>uploadUsingFile (in category 'as yet unclassified') -----
  uploadUsingFile
  
  	"we copy the completed files to a different local directory"
  	
  	| cmd path |
  
  	path := info upload.
  	
  	(path / self stamp) mkpath.
  
  	cmd := 'cd ', path full, '; rm latest; ln -s ', self stamp, ' latest'.
  	
  	self info linkRelease = true ifTrue:[ 
   		cmd := cmd , '; rm release; ln -s ', self stamp, ' release'	
  	].
  
  	self exec: cmd.
  
  	(path / self stamp) addAll: self uploadFiles.
+ 
+ 	self log notice UPLOADING: self publishDir COPIED: true
  !

Item was added:
+ ----- Method: BobBuildParallelReleases class>>taskUpload (in category 'as yet unclassified') -----
+ taskUpload
+  
+ 	^((self selectorsPrefixed: #build) collect: [ :sel | self taskUpload: sel ]) asTask.
+ 	
+   !

Item was changed:
  ----- Method: BobBuild>>uploadUsingList (in category 'as yet unclassified') -----
  uploadUsingList
  
  	"we append the paths of the result files to the given list file, the list file can be used by some external process"
  
  	self class configUploadListFile asFile append: [ :str | 
  
  		self uploadFiles do: [ :ea | str << (ea relativeTo: self outputDir) asString ; cr  ]	
+ 	].
+ 
+ 	self log notice UPLOADING: self publishDir DELEGATED: true
+ !
- 	]!

Item was changed:
  ----- Method: BobBuild class>>taskUploadAll (in category 'as yet unclassified') -----
  taskUploadAll
  
  "
  self taskUploadAll run 
  "
  	"we need to tell this task to sort its dependencies appropriately before it is run"
+ 	"there is a sorting algorithm in collection:"
- 	"there is a sorting algorithm in collection: , but this might not be exactly what we want."
  	
  	^ (BobBuild allSubclasses select: [ :c | c isUploader ] thenCollect: [ :c | c taskUpload ]) asTask defined
  
  !

Item was changed:
  ----- Method: BobBuildImage>>actionBuild (in category 'as yet unclassified') -----
  actionBuild
  
+ 	self log notice BUILDING: info name.
+ 	
  	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 uploadImmediate.
- 	!

Item was added:
+ ----- Method: BobUtilities>>latest (in category 'as yet unclassified') -----
+ latest
+ 
+ 	^ latest!

Item was changed:
  ----- Method: BobBuildImage>>packageOneClick (in category 'as yet unclassified') -----
  packageOneClick
  	
  	| appZip appDir resources plist bundleName imageName template filename |
  	 
  	info oneClick = true ifFalse: [ ^ self ].
  	
+ 	template := info oneClickTemplate ifNil: [ self class configOneClickTemplate ].
- 	template := info oneClickTemplate ifNil: [ self configOneClickTemplate ].
  		
  	"use the match string given to find the template"	
  	appZip := self resolveFile: template ifNone: [ :msg | self error: msg ].
  	
  	"download to images cache, and decompress to the output area"
  	self expand: appZip to: self workingDirOneClickOut mkpath clean.
  
  	"the result should have a .app dir, find it"
   	appDir := self workingDirOneClickOut directories detect: [ :ea |  ea asString endsWith: '.app' ] ifNone: [ self error: '*.app not found' ].
  
  	"get our plist contribution"
  	plist := self configPlist.
  
  	bundleName := plist at: 'CFBundleName'.
  	imageName := bundleName asLowercase.
  	plist at: 'SqueakImageName' put: (imageName, '.image').
  
  	"rename the .app dir to the desired name"
  	appDir beRenaming fileName: (bundleName , '.app').
  
  	"top level directory"
  	(appDir filesMatching: #('*.exe' '*.ini' '*.sh')) do: [ :ea | ea rename base: bundleName ].
  	(appDir / bundleName + '.ini' ) delete contents: ((self configOneClickIni: imageName) copyReplaceAll: String cr with: String crlf).
  	(appDir / bundleName + '.sh' ) delete contents: (self configOneClickSh: imageName).
  	(appDir / 'COPYRIGHT') delete contents: (info oneClickCopyrightStatement ifNil: [ self configOneClickCopyrightStatement ] ).
  	
  	"Contents Directory"
  	appDir / 'Contents' / 'PkgInfo' contents: ((plist at: 'CFBundlePackageType') , (plist at: 'CFBundleSignature')).
  	self oneClickUpdatePlist: (appDir / 'Contents' / 'Info.plist')  fromDictionary: plist.
  	
  	"Resources Directory"	
  	resources := (appDir / 'Contents' / 'Resources') all delete mkpath.
  
  	resources addTree: self imageDir entries.
  	(resources filesMatching: #('*.image' '*.changes')) do: [ :ea | ea rename base: imageName ].
  	resources add: self configOneClickIcns asFile.
  	resources add: (info oneClickSources ifNil: [ self configOneClickSources ]) asFile.
  	
  	self halt.
  	filename := appDir fileName.
  	self packageDirectory: filename intoZip: (self stamp,'_', filename) from: appDir parent.
  
  	 !

Item was changed:
  ----- Method: BobBuild>>uploadUsingSsh (in category 'as yet unclassified') -----
  uploadUsingSsh
  
  	"we upload the result files to the given ssh url location"
  
  	| ssh cmd dest files |
  	ssh := SshUrl absoluteFromText: self info upload.
  
  	cmd := 'mkdir -p ', ssh pathString, '/', self stamp,  '; cd  ', ssh pathString,'; rm latest; ln -s ', self stamp, ' latest'.
  	dest := ssh username, '@', ssh authority, ':', ssh pathString, '/', self stamp.	
  	files := self uploadFiles joinUsing: ' ', dest , ' '.
  
  	self info linkRelease = true ifTrue:[ 
  		cmd := cmd , '; rm release; ln -s ', self stamp, ' release'
  	].		
  					
+ 	self execForking: 'ssh -ax -l ', ssh username , ' ' , ssh authority, ' "', cmd,'" ; scp -Bpq ', files,' ',dest.		
+ 
+ 	self log notice UPLOADING: self publishDir INPROGRESS: true
- 	self exec: 'ssh -ax -l ', ssh username , ' ' , ssh authority, ' "', cmd,'"'.
- 	self exec: 'scp -Bpq ', files,' ',dest			
  !

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: [ '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') ].
- 	info when = #dont ifTrue: [ ^ #(false 'dont flag set') ].
-  	info when = false ifTrue: [ ^ #(false '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). } ].
- 		ifTrue: [ ^ { false. ('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.}].
- 	(info when isKindOf: FileKernel) ifTrue: [
- 		dependentFile := self resolveFile: info when ifNone: [:msg |  ^ { false. 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.} ]. 
- 		dependentFile := zipFile := self resolveFile: info image asFile ifNone: [:msg |  ^ { false. msg.} ]. 
  		self info dependentCreationTime: zipFile creationTime.
+ 	].
- 	]. 	
  
  	"has our starting image changed? if so"
+ 	 (latest dependentCreationTime notNil and: [ latest dependentCreationTime ~= self info dependentCreationTime ]) 		
+ 			ifTrue: [ ^ { true. #dependentChanged. (dependentFile asString , ' has changed').}  ]
+ 			ifFalse: [ info when = true ifTrue: [ ^ { false. ('waiting for ', dependentFile asString , ' to change').} ]].
+ 				
+ 				
- 	(latest dependentCreationTime notNil and: [ latest dependentCreationTime ~= self info dependentCreationTime ]) 		ifTrue: [ ^ { true. (dependentFile asString , ' has changed').}  ].
- 	
  	"we have a new build id, so we build"
+ 	latest build ~= info build ifTrue: [ ^ { true. #newBuildNumber. ('new build number ',info build).}  ].
- 	latest build ~= info build ifTrue: [ ^ { true. ('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').}   ].
- 		wait > 0 ifTrue: [ ^  { false. (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). }
- 		ifTrue: [ ^ { false. ((latest package ifNil: [ latest name ]) ,  ' already built'). } ].
- 
- 	^ { true. ('building ', self info name). }
  
  	
  !

Item was added:
+ ----- Method: BobBuild>>execForking: (in category 'as yet unclassified') -----
+ execForking: aCmdString
+ 
+ 	self log info fork: aCmdString.
+ 	
+ 	^ self OSProcess command: aCmdString!

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 |
+ 	
- 		metaSelector = #build310 ifTrue: [ self halt ].
  		(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 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 linkRelease.
  			
+ 			task info oneClick = true ifTrue: [ BobOneClickPackageGenerator taskMakeOneClickfor: self build: task info build ].
- 			task info oneClick = true ifTrue: [ task packageOneClick ].
  			
  			task perform: ('uploadUsing', (task info upload upTo: $:) capitalized) asSymbol. 
  		
  			task isUploadedFileAvailableForDownload ifTrue: [ task uploadDirLock delete ].
  		]
  	] 
  
  !

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

Item was added:
+ ----- Method: BobBuild>>doNeededStep: (in category 'as yet unclassified') -----
+ doNeededStep: runPriorTasks
+  
+ 	self step: self context printString, ' is Needed for: ', String cr, String cr, self info printString .
+ 	
+  	^ ifBlock valueWithPossibleArgument: runPriorTasks!

Item was removed:
- ----- Method: BobPeriodicUploads>>taskUploadAll (in category 'as yet unclassified') -----
- taskUploadAll
- 	
- 	^ BobBuild taskUploadAll!

Item was removed:
- ----- Method: BobPeriodicUploads class>>initialize (in category 'as yet unclassified') -----
- initialize
- 	super initialize.
- 	
- 	BobConfig isUploader ifFalse: [ ^ self ].
- 	
- 	self scheduler addTask: ((self do: #doAllTasks every: 300 seconds) 
- 										noRunHistory;
- 										description: 'uploader';
- 										yourself)
- 	!

Item was removed:
- ----- Method: BobConfig class>>configUploadImmediate (in category 'as yet unclassified') -----
- configUploadImmediate
- 	"if the upload: is any of these options then do the upload immediately on completing the build"
- 	^ #( 'list' 'link' 'file')!

Item was removed:
- ----- Method: BobBuild>>uploadImmediate (in category 'as yet unclassified') -----
- uploadImmediate
- 
- 	| type |
- 	
- 	type := self info upload upTo: $:.
- 	
- 	(self class configUploadImmediate includes: type) ifFalse: [ ^ self ].
- 	
- 	(self class taskUpload: info build) run.!

Item was removed:
- ScheduledLoggedTask subclass: #BobPeriodicUploads
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Sake-Bob'!



More information about the Packages mailing list