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

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Thu Feb 26 14:08:59 UTC 2009


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

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

Name: Sake-Bob-kph.13
Author: kph
Time: 26 February 2009, 2:08:55 pm
UUID: 011a2f2e-040f-11de-a647-000a95edb42a
Ancestors: Sake-Bob-kph.12

We are getting there -  Bob is working

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

Item was added:
+ ----- 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 added:
+ ----- Method: BobBuildImage class>>taskBuild (in category 'as yet unclassified') -----
+ taskBuild
+ 
+ 	^ self taskBuild: (self lastSelectorPrefixed: #build)!

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

Item was added:
+ ----- Method: BobBuildParallelReleases>>linksDir (in category 'as yet unclassified') -----
+ linksDir
+ 
+ 	^ self outputDir / self moniker!

Item was added:
+ ----- Method: BobBuild>>resolveFile:ifNone: (in category 'zip file') -----
+ resolveFile: fileMatch ifNone: errorBlock	
+ 	"
+ 	(self new resolveFile: 'ftp://ftp.squeak.org/3.10/Squeak3.10.2-*-basic.zip') 
+ 	"
+ 
+ 	^  fileMatch asFile resolveMatchOne 
+ 		ifNil: [ errorBlock value: 'not found: ', fileMatch ]!

Item was added:
+ ----- Method: BobBuildImage class>>configBgColor2 (in category 'as yet unclassified') -----
+ configBgColor2
+ 
+ 	^ Color r: 0.97 g: 0.98 b: 1.0!

Item was changed:
  ----- 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'
- 	self info release = true ifTrue: [ 
- 
- 		self exec:  'cd ', self outputDir ,'; rm release; ln -s ', self publishDir parent, ' release'
  	]!

Item was added:
+ ----- Method: BobBuild>>uploadDirLock (in category 'as yet unclassified') -----
+ uploadDirLock
+ 	
+ 	^ self publishDir parent + '.uploading'!

Item was added:
+ ----- 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: , 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: BobBuild>>outputDir (in category 'as yet unclassified') -----
  outputDir
  
  	^ info outputTo ifNil: [self class configOutputDir ]!

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

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"
- 	"the mac vm doesnt like to be opened viia a symbolic link"
  	
+ 	^ '/bob/vm/Squeak\ 3.8.20beta1U.app/Contents/MacOS/Squeak\ VM\ Opt'
- 	^ '/Squeak/vm/Squeak\ 3.8.20beta1U.app/Contents/MacOS/Squeak\ VM\ Opt'
  !

Item was added:
+ ----- Method: BobBuild class>>selectorsPrefixed: (in category 'as yet unclassified') -----
+ selectorsPrefixed: prefix
+ 
+ 	^  (self selectors select: [ :ea | ea beginsWith: prefix ]) asSortedCollection.
+ 	
+ !

Item was added:
+ ----- Method: BobBuild class>>lastSelectorPrefixed: (in category 'as yet unclassified') -----
+ lastSelectorPrefixed: prefix
+ 
+ 	^ (self selectorsPrefixed: prefix) lastOrNil
+ !

Item was added:
+ ----- Method: BobBuild>>infoFileReadLatest (in category 'as yet unclassified') -----
+ infoFileReadLatest
+ 	"obtain the most recent info file"
+ 	
+ 	^ Compiler evaluate: ((self latestDir fileMatching: '*.info') ifNil: [ ^ self class infoNull ]) contents!

Item was changed:
  ----- Method: BobBuildImage>>package (in category 'as yet unclassified') -----
  package	
  	
  	self exec: 'cd ', self publishDir parent, '; zip -R ', self packageFile, ' "', self stampedName ,'/*" -x "__*" ".DS*"'.
  !

Item was added:
+ ----- 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.
+ 
+ !

Item was added:
+ ----- 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 second.				 		 .
+ 					isNeeded first ].
+ 		
+ 		task action: [ 
+ 			task stepAction.
+ 			task expandZipFileTo: (task newWorkingDir). 
+ 
+ 			task startImage: (task workingDir all fileMatching: '*.image').
+ 	
+ 			task theScript scriptFileWrite.
+ 			 			
+ 			task launchVm: self configVm image: task startImage with: task scriptFile.
+ 			
+ 			task isSuccessfulBuild ifTrue: [ 
+ 				task info timeComplete: DateAndTime now. 
+ 				task info timeDuration: ((task info timeComplete - task info timeStart) roundTo: 1 second).
+ 			
+ 				task publish.
+ 				task package.
+ 				task tidy.
+ 				task publishLinks.
+ 			
+ 				task uploadImmediate.
+ 			]
+ 		]
+ 	]
+ 
+ !

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

Item was changed:
  ----- Method: BobBuild>>nextScriptPut: (in category 'as yet unclassified') -----
  nextScriptPut: aScript
  
  	| bScript |
  
+ 	bScript := (self class configStepScript = true) ifFalse: [ aScript ] 
- 	bScript := (self info stepping = true) ifFalse: [ aScript ] 
  		ifTrue: [
  			aScript asString copyReplaceAll: self scriptCommentedHalt with: 'self halt.'
  	].
  		
  
  	script 	nextChunkPut: bScript, String cr.
  !

Item was added:
+ ----- Method: BobBuildImage>>scriptCleanUp (in category 'as yet unclassified') -----
+ scriptCleanUp
+ 
+ 	self nextScriptPut: 'SmalltalkImage current cleanUpAllExcept: #(ChangeSet).'!

Item was changed:
  ----- Method: BobBuild>>exec: (in category 'as yet unclassified') -----
  exec: aCmdString
  
+ 	self log info exec: aCmdString.
- 	self log bob exec: aCmdString.
  	
  	^ self OSProcess waitForCommand: aCmdString!

Item was changed:
  ----- Method: BobBuild>>releaseDir (in category 'as yet unclassified') -----
  releaseDir
  
+ 	^ self linksDir / 'release'!
- 	^ self outputDir / 'release'!

Item was added:
+ ----- Method: BobBuildImage>>isUploadedFileAvailableForDownload (in category 'as yet unclassified') -----
+ isUploadedFileAvailableForDownload
+ 	
+ 
+ 	^ ([ (info download asDirectory / self stamp / self stampedName + '.zip') fileSize ]
+ 		on: TelnetProtocolError do: [ ^ false ]) = self uploadFiles first fileSize !

Item was added:
+ ----- Method: BobBuildParallelReleases>>moniker (in category 'as yet unclassified') -----
+ moniker
+ 
+ 	^ info name!

Item was added:
+ ----- Method: BobBuildImage>>scriptGoAtomic (in category 'as yet unclassified') -----
+ scriptGoAtomic
+ 
+ 	self nextScriptPut: 'Preferences setPreference; #useMonticelloAtomicLoader toValue: true.'!

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

Item was changed:
  ----- Method: BobBuild class>>infoNull (in category 'as yet unclassified') -----
  infoNull
  
  	"When No Previous Build"
  
  	^ SakeMeta new 
  		timeStart: DateAndTime epoch;
  		build: #none;
  		yourself
  	
  !

Item was changed:
  ----- Method: BobBuildImage>>publish (in category 'as yet unclassified') -----
  publish	
+ 
+ 	"we publish to a temp directory and publish as an atomic operation
+ 	 otherwise the uploader might start uploading before it is ready"	
- 	
- 	self info overwrite = true ifTrue: [ self outputDir all delete ].
  		
+ 	self info overwrite = true ifTrue: [ self outputDir all delete ].
+ 			
- 	self publishDir mkpath.
- 	
  	self publishManifest.
  	
+ 	self infoFilePublishAlongside: self publishDir.
+ 	
- 	self linkLatest.  
- 	self linkRelease.
  !

Item was changed:
  ----- Method: BobConfig class>>configWipDir (in category 'as yet unclassified') -----
  configWipDir
  
+ 	^ self configBaseDir / 'wip' !
- 	^ self configBaseDir / 'wip' / self label!

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

Item was added:
+ ----- Method: BobConfig class>>configUploadList (in category 'as yet unclassified') -----
+ configUploadList
+ 
+ 	^ ''!

Item was added:
+ ----- Method: BobBuild>>info (in category 'as yet unclassified') -----
+ info
+ 
+ 	^ info ifNil: [ info := SakeMeta new ]!

Item was added:
+ ----- Method: BobBuild class>>isUploader (in category 'as yet unclassified') -----
+ isUploader
+ 
+ 	^ self configUploader = self me!

Item was added:
+ ----- Method: BobPeriodicBuilds>>taskBuildAll (in category 'as yet unclassified') -----
+ taskBuildAll
+ 
+ 	^ BobBuild taskBuildAll!

Item was changed:
  ----- Method: BobBuild>>latestDir (in category 'as yet unclassified') -----
  latestDir
  
+ 	^ self linksDir / 'latest'!
- 	^ self outputDir / 'latest'!

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

Item was added:
+ ----- Method: BobBuild>>uploadFiles (in category 'as yet unclassified') -----
+ uploadFiles
+ 
+ 	^ #()
+ 	!

Item was changed:
  ----- Method: BobBuild>>tidy (in category 'as yet unclassified') -----
  tidy
  
  	self info tidy = false ifTrue: [ ^ self ].
  	
  	self publishDir all delete!

Item was changed:
  ----- Method: BobBuild>>launchVm:image:with: (in category 'as yet unclassified') -----
  launchVm: vm image: imageFile with: scriptFile
  
+ 	self exec: vm, ' ' , imageFile full, ' ', scriptFile full.
+ 	
+ 	^ DateAndTime now!
- 	self exec: vm, ' ' , imageFile full, ' ', scriptFile full!

Item was added:
+ ----- Method: BobBuildImage>>scriptCleanUpChangeSet (in category 'as yet unclassified') -----
+ scriptCleanUpChangeSet
+ 
+ 	self nextScriptPut: 'ChangeSet cleanUp.'!

Item was changed:
  ----- Method: BobBuildImage>>scriptSaveImageAndQuit: (in category 'as yet unclassified') -----
  scriptSaveImageAndQuit: requestQuit
  
  	| s |
  	s := String new writeStream.
  	
  	s << ' | image resuming |'  ; cr.
  	s << '"self halt."' ; cr.
- 	s << 'SystemVersion newVersion: ' << self name printString << '.' ; cr.
- 	s << 'SystemVersion current date: ''' << self timeStart printString << ''' asDateAndTime.'; cr.
  	s << 'image := SmalltalkImage current.'; cr.
- 	s << 'image cleanUpAllExcept: #(ChangeSet).'; cr.
  	s << 'resuming := image saveAs: '''<< self stampedName << '.image''.'; cr.
  	
  	requestQuit ifTrue: [
  	
  		s <<	'resuming ifFalse: [ image snapshot: false andQuit: true ].' ; cr
  	
  	].
  
  	self nextScriptPut: s contents!

Item was changed:
  ----- Method: BobConfig class>>configUploader (in category 'as yet unclassified') -----
  configUploader
  
+ 	^  'server.flat'!
- 	^ 'mercy.flat'!

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

Item was added:
+ ----- 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 exec: 'ssh -ax -l ', ssh username , ' ' , ssh authority, ' "', cmd,'"'.
+ 	self exec: 'scp -Bpq ', files,' ',dest			
+ !

Item was changed:
  SakeTask subclass: #BobBuild
+ 	instanceVariableNames: 'script zipFile latest'
- 	instanceVariableNames: 'script zipFile'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Sake-Bob'!
  
  !BobBuild commentStamp: 'kph 2/18/2009 05:49' prior: 0!
  [ self taskBuildAll run ] fork.!

Item was added:
+ ----- Method: BobBuild>>linksDir (in category 'as yet unclassified') -----
+ linksDir
+ 
+ 	^ self outputDir!

Item was changed:
  ----- Method: BobBuildImage>>packageFile (in category 'as yet unclassified') -----
  packageFile
  	
+ 	^ self publishDir + '.zip'!
- 	^ self publishDir parent / self stampedName + '.zip'!

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

Item was added:
+ ----- Method: BobBuild>>name: (in category 'as yet unclassified') -----
+ name: aName
+ 
+ 	self info name: aName!

Item was added:
+ ----- Method: BobBuildImage>>scriptSetBackground (in category 'as yet unclassified') -----
+ scriptSetBackground
+ 
+ 	self nextScriptPut: 'World fillStyle: ((GradientFillStyle ramp: {0.0 -> ', self class configBgColor1 printString ,'. 1.0 -> ', self class configBgColor2 printString ,'}) origin: 0 at 0 ; direction: 0 at 400; normal: 640 at 0; radial: false).'
+ !

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

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

Item was added:
+ ----- Method: BobBuild>>uploadDirLockDuring: (in category 'as yet unclassified') -----
+ uploadDirLockDuring: aBlock
+ 	
+ 	[ self uploadDirLock touch.
+ 	  aBlock value 				] ensure: [ self uploadDirLock delete ]
+ 	!

Item was changed:
  ----- Method: BobBuild>>publishDir (in category 'as yet unclassified') -----
  publishDir
  	
+ 	^ self outputDir / self moniker / self stamp / self stampedName!
- 	^ self outputDir / info build / self stamp / self stampedName
- 	!

Item was added:
+ ----- Method: BobBuild class>>taskBuild (in category 'as yet unclassified') -----
+ taskBuild
+ 
+ 	"self subclassResponsibility"
+ 	^ self noop!

Item was added:
+ ----- Method: BobBuild>>when: (in category 'as yet unclassified') -----
+ when: w
+ 
+ 
+ 	(w isKindOf: ByteString) ifFalse:[ ^ info when: w ].
+ 	
+ 	FileExecutive allSubclassesDo: [ :ea | (ea canInstanciateFrom: w) > 0  ifTrue: [ ^ info when: w asFile ] ].
+ 	
+ 	^ info when:  ([[[ w asDateAndTime ] ifError: [ w asTimeStamp ]] ifError: [ w asDuration ]] ifError: [ w asTime ])
+ 
+ 	
+ 	!

Item was changed:
  ----- Method: BobBuildImage>>isBuildNeeded (in category 'as yet unclassified') -----
  isBuildNeeded
  
+ 	| wait dependentFile |
- 	| latest wait |
  	
  	"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 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. ('time is not yet ', info when asString). } ].
  	
+ 	"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. ('time is not yet ', info when asString). } ].
- 	[	
- 	self info dependentCreationTime: (self creationTimeOfZipFile: self info image asFile).
- 	] ifError: [ ^ { false. self info image, ' file not found'.} ].
  
+ 	latest := self infoFileReadLatest.
+ 	
+ 	"if 'when' is set to a file obtain creation time, if not use info image"
+ 	(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. msg.} ]. 
+ 		self info dependentCreationTime: zipFile creationTime.
+ 	]. 	
- 	latest := self readInfoFileLatest.
  
  	"has our starting image changed? if so"
+ 	(latest dependentCreationTime notNil and: [ latest dependentCreationTime ~= self info dependentCreationTime ]) 		ifTrue: [ ^ { true. (dependentFile asString , ' has changed').}  ].
- 	(latest dependentCreationTime notNil and: [ latest dependentCreationTime ~= self info dependentCreationTime ]) 		ifTrue: [ ^ { true. (zipFile asString , ' has changed').}  ].
  	
  	"we have a new build id, so we 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. (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. ((latest package ifNil: [ latest name ]) ,  ' already built'). } ].
  
  	^ { true. ('building ', self info name). }
  
  	
  !

Item was added:
+ ----- Method: BobBuildImage>>scriptSetVersion (in category 'as yet unclassified') -----
+ 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.
+ 
+ 	self nextScriptPut: s contents!

Item was changed:
  ----- Method: BobBuild>>workingDir (in category 'as yet unclassified') -----
  workingDir
  
+ 	^ self class configWipDir / self class label / self moniker!
- 	^ self subclassResponsibility!

Item was added:
+ ----- Method: BobBuildImage>>newWorkingDir (in category 'as yet unclassified') -----
+ newWorkingDir
+ 	
+ 	self workingDir mkpath.
+ 
+ 	self exec: 'cd ', self workingDir,'; rm -rf *; ln -s ', self class configPackageCacheDir mkpath, ' package-cache'.
+ 	
+ 	^ self workingDir. !

Item was added:
+ ----- Method: BobPeriodicWatchRepositories>>taskWatchPackages (in category 'as yet unclassified') -----
+ taskWatchPackages
+ 
+ 	^ SakeTask 
+ 		checkUrl: 'http://www.squeaksource.com/Packages/feed.rss' 
+ 		onChanged: [
+ 			
+ 			self log info: 'Packages Library Updated'.
+ 
+ 			Installer squeaksource project: 'Packages';
+ 				install: 'Packages-Library'. ].
+ 			
+ 		!

Item was added:
+ ----- 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 info upload: newInfo upload.
+ 		task info download: newInfo download.
+ 		task info linkRelease: newInfo linkRelease.
+ 		task info comment: newInfo comment.
+ 	
+ 		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.
+  
+ 			task infoFilePublishAlongside: task publishDir.
+ 			task linkRelease.
+ 			
+ 			task perform: ('uploadUsing', (task info upload upTo: $:) capitalized) asSymbol. 
+ 		
+ 			task isUploadedFileAvailableForDownload ifTrue: [ task uploadDirLock delete ].
+ 		]
+ 	] 
+ 
+ !

Item was added:
+ ----- Method: BobBuild>>moniker (in category 'as yet unclassified') -----
+ moniker
+ 
+ 	^ info moniker ifNil: [ info build ]!

Item was added:
+ ----- Method: BobBuild>>infoFilePublishAlongside: (in category 'as yet unclassified') -----
+ infoFilePublishAlongside: aDir
+ 
+ 	"info file for alongside the published archive, (tidy it up first)"
+ 	
+ 	| i |
+ 	(aDir parent / self stampedName + '.info') delete writer: [ :str | 
+ 		
+ 		i := self info copy.
+ 		
+ 		i keys do: [ :k | (k beginsWith: 'step') ifTrue: [ i removeKey: k ] ].
+ 		
+ 		i storeOn: str 
+ 		
+ 		]
+ 	
+ 	!

Item was added:
+ ----- Method: BobBuild class>>taskUpload (in category 'as yet unclassified') -----
+ taskUpload
+ 
+ 	^ self taskUpload: (self lastSelectorPrefixed: #build)!

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 info when: #dont.
  	
+ 	self info name: self class label.
+ 	self info build: selector.
+ 	self info label: self class label.
+ 	self when: self class configWhen.
+ 	self info linkRelease: self class configLinkRelease.
+ 
  	self perform: selector.
  	
  	self info when: self preprocessWhen.
  	
  	
  	!

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

Item was added:
+ ----- Method: BobBuildImage>>isUploadRequested (in category 'as yet unclassified') -----
+ isUploadRequested
+ 	
+ 	^ (info upload isNil or: [ self class configUploadReleaseOnly and: [ self info linkRelease ~= true ]]) not!

Item was added:
+ ----- 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 added:
+ ----- Method: BobBuild>>stepAction (in category 'as yet unclassified') -----
+ stepAction
+ 
+ 	self class configStepAction = true ifTrue: [ self halt ]!

Item was added:
+ ----- Method: BobPeriodicWatchRepositories>>taskWatchBob (in category 'as yet unclassified') -----
+ taskWatchBob
+ 
+ 	^ SakeTask  
+ 		checkUrl: 'http://www.squeaksource.com/Bob/feed.rss' 
+ 		onChanged: [ 
+ 			
+ 			self log info: 'Bob Repository Updated'.
+ 			
+ 			Installer squeaksource project: 'Bob';
+ 				install: 'Tasks-Common';
+ 				install: 'Tasks-Squeak311';
+ 				install: 'Tasks-Squeak310';
+ 				install: 'Bob-Releases'. 
+ 				
+ 			].
+ 	
+ !

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

Item was changed:
  ----- Method: BobBuildImage>>scriptTranscriptLogToFileLoad (in category 'as yet unclassified') -----
  scriptTranscriptLogToFileLoad
  
+ 	self nextScriptPut:  '"self halt." (HTTPSocket httpGet: ''ftp.squeak.org/3.11/bob/TranscriptToFile.cs'') readStream fileIn.'.
- 	self nextScriptPut:  '"self halt." HTTPSocket httpFileIn: ''installer.pbwiki.com/f/TranscriptToFile.cs''.'.
  	
  !

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

Item was changed:
  ----- Method: BobBuild>>expandZipFileTo: (in category 'zip file') -----
  expandZipFileTo: destDir
  		
  	"
  	(self obtainImage: 'ftp://ftp.squeak.org/3.10/Squeak3.10.2-*-basic.zip') run  
  	"
  	| localZipFile |
  	
  	zipFile executive isRemote 
  		ifTrue: [ 
  		
  			localZipFile := self class configImagesDir  / zipFile fileName.
  		
  			"if it is not in the local downloaded images cache, look in our output tree"	
  			localZipFile exists ifFalse: [ 
  				(self outputDir parent all filesMatching: zipFile fileName) firstOrNil
  				 ifNotNilDo: [ :found |
+ 					self log info found: found.
- 					self log info bob found: found.
  					localZipFile := found
  				].
  			].
  		
  			localZipFile exists ifFalse: [ 
+ 				self log info downloading: zipFile.
- 				self log info bob downloading: zipFile.
  				localZipFile parent mkpath add: zipFile ].	
  		]
  		ifFalse: [ localZipFile := zipFile ].
  		
  	self log info bob expanding: localZipFile to: destDir.	
  
  	self exec: 'unzip ', localZipFile, ' -d ', destDir full mkpath.
  	
  	^ localZipFile
  
  	"	
  	localZipFile zip readArchive extractAllTo: destDir mkpath asFileDirectory.
  	"
  	!

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

Item was added:
+ ----- Method: BobBuildImage>>uploadFiles (in category 'as yet unclassified') -----
+ uploadFiles
+ 	"the files to upload, the first is supposed to be the downloadable zip file,
+ 	see downloadAvailableSizeOrNil"
+ 	^ { 
+ 		(self publishDir  + '.zip'). 
+ 		(self publishDir + '.info').
+ 	   }!

Item was changed:
  ----- Method: BobBuild>>preprocessWhen (in category 'as yet unclassified') -----
  preprocessWhen
  
+ 	"if the when field is supplied as a string we do our best to decipher it"
+ 	
  	| w |
  	w := info when.
  	
  	(w isKindOf: ByteString) ifFalse:[ ^ w ].
+ 	
+ 	FileExecutive allSubclassesDo: [ :ea | (ea canInstanciateFrom: w) > 0  ifTrue: [ ^ w asFile ] ].
  	
  	^  [[[ w asDateAndTime ] ifError: [ w asTimeStamp ]] ifError: [ w asDuration ]] ifError: [ w asTime ]
  
  	
  	!

Item was added:
+ ----- Method: BobBuild>>stepNeeded (in category 'as yet unclassified') -----
+ stepNeeded
+ 
+ 	self class configStepNeeded = true ifTrue: [ self halt ]!

Item was changed:
  ----- Method: BobBuildImage>>publishManifest (in category 'as yet unclassified') -----
  publishManifest
  	
+ 	self publishDir mkpath 
+ 		addAll: (self imageDir filesMatching: (self stampedName, '.*')).
+ 		
+ 	self publishDir
+ 		addAll: (self imageDir all filesMatching: #('*.txt' '*.text' '*.pr' '*.pass' '*.fail' ))
- 	self publishDir addAll: (self imageDir filesMatching: (self stampedName, '.*')).
- 	
- 	"a second info file for outside the archive"
- 	self infoFile copyTo: (self publishDir parent / self stampedName, '.info').
- 	
- 	self publishDir addAll: (self imageDir all filesMatching: #('*.txt' '*.text' '*.pr' '*.pass' '*.fail' ))
- 	
  	
+ 	
  !

Item was added:
+ ----- Method: BobBuildImage class>>testBackground (in category 'as yet unclassified') -----
+ testBackground
+ 
+ self new scriptSetBackground script contents readStream fileIn!

Item was added:
+ ----- 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.
+ !

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

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

Item was added:
+ ----- 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  ]	
+ 	]!

Item was changed:
  ----- Method: BobBuildImage>>scriptAddLPF (in category 'as yet unclassified') -----
  scriptAddLPF
  
+ 	self nextScriptPut: '"self halt." (HTTPSocket httpGet: ''ftp.squeak.org/3.11/bob/LPF.st'') readStream fileIn.'.
- 	self nextScriptPut: '"self halt." HTTPSocket httpFileIn: ''installer.pbwiki.com/f/LPF.st''.'.
  !

Item was added:
+ ----- 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 added:
+ ----- Method: BobBuildImage>>isSuccessfulBuild (in category 'as yet unclassified') -----
+ isSuccessfulBuild	
+ 
+ 	^ (self imageDir fileMatching: (self stampedName, '.image')) notNil
+ !

Item was added:
+ ----- Method: BobBuildImage class>>configBgColor1 (in category 'as yet unclassified') -----
+ configBgColor1
+ 
+ 	^ Color r: 0.97 g: 0.98 b: 1.0!

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

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

Item was removed:
- ----- Method: BobBuild>>infoFile (in category 'as yet unclassified') -----
- infoFile
- 	
- 	^ self wipDir / self stampedName + '.info' !

Item was removed:
- ----- Method: BobBuild>>isUploader (in category 'as yet unclassified') -----
- isUploader
- 
- 	^ self class configUploader = self class me!

Item was removed:
- ----- Method: BobPeriodicallyWatchRepositories class>>initialize (in category 'as yet unclassified') -----
- initialize
- 	super initialize.
- 	self scheduler addTask: (self do: #doAllTasks every: 180 seconds) noRunHistory
- 
-  !

Item was removed:
- ----- Method: BobBuildImage class>>upload (in category 'as yet unclassified') -----
- upload
- 
- 	| upload |
- 	^ self define: [ :task |
- 			
- 		(task infoForLast: #build) ifNil: [ ^ self noop ].
- 
- 		upload := task info upload.
- 		
- 		"obtain latest meta-data from instance side"	
- 		task info: task readInfoFileLatest.
- 		
- 		"if the upload location in the info file is different to the current one use the current one"
- 		task info upload = upload ifFalse: [ task info upload: upload ].
- 		
- 		task action: [ 
- 			task info stepping ifTrue:[ self halt].
- 			task upload.
- 			task uploadLinks.
- 		]
- 	]
- 
- !

Item was removed:
- ----- Method: BobBuild>>task: (in category 'as yet unclassified') -----
- task: selector
- 	 
- 	self info build: selector.
- 	self info label: self class label.
- 	self info when: #dont.
- 	
- 	self perform: selector.
- 	
- 	self preprocessWhen
- 	
- 	!

Item was removed:
- ----- Method: BobBuildImage>>uploadLinks (in category 'as yet unclassified') -----
- uploadLinks	
- 
- 	| ssh cmd |
- 	ssh := SshUrl absoluteFromText: self info upload.
- 
- 	cmd := 'cd ', ssh pathString, '; rm latest; ln -s ', self stamp, ' latest'.
- 
- 	self info release = true ifTrue:[ 
- 		cmd := cmd , '; rm release; ln -s ', self timeStamp, ' release'.
- 	].
- 	
- 	self exec: 'ssh -l ', ssh username , ' ' , ssh authority, ' "', cmd,'"'
- 	
- !

Item was removed:
- ----- Method: BobBuildImage class>>dependsOn (in category 'as yet unclassified') -----
- dependsOn
- 
- 	^ #()!

Item was removed:
- ----- Method: BobConfig class>>configUploadImmediately (in category 'as yet unclassified') -----
- configUploadImmediately
- 
- 	^ false!

Item was removed:
- ----- Method: BobBuild>>creationTimeOfZipFile: (in category 'zip file') -----
- creationTimeOfZipFile: zipFileMatch		
- 	"
- 	(self new creationTimeOfZipFile: 'ftp://ftp.squeak.org/3.10/Squeak3.10.2-*-basic.zip') 
- 	"
- 
- 	zipFile := zipFileMatch asFile resolveMatchOne 
- 		ifNil: [ self error: 'unique zip file matching ', zipFileMatch, ' not found' ].
- 	
- 	^ zipFile creationTime
- 	!

Item was removed:
- ----- Method: BobBuild>>wipDir (in category 'as yet unclassified') -----
- wipDir
- 
- 	^ self class configWipDir!

Item was removed:
- ----- Method: BobBuild class>>test (in category 'as yet unclassified') -----
- test
- 
- 	| bd |
- 	bd := self build.
- 	bd info stepping: true.
- 	bd runStepping.!

Item was removed:
- ----- Method: BobPeriodicallyWatchRepositories>>taskWatchTasks (in category 'as yet unclassified') -----
- taskWatchTasks
- 
- 	^ SakeTask  checkUrl: 'http://www.squeaksource.com/Tasks/feed.rss' 
- 				onChanged: [ " Installer sake install: 'Tasks'. 
- 					            BobBuild build run." ].
- 	
- !

Item was removed:
- ScheduledTask subclass: #BobPeriodicallyBuilds
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Sake-Bob'!

Item was removed:
- ----- Method: BobBuild class>>build (in category 'as yet unclassified') -----
- build
- 
- 	"self subclassResponsibility"
- 	^ self noop!

Item was removed:
- ----- Method: BobBuildImage>>newWipDir (in category 'as yet unclassified') -----
- newWipDir
- 	
- 	self wipDir mkpath.
- 
- 	self exec: 'cd ', self wipDir,'; rm -rf *; ln -s ', self class configPackageCacheDir mkpath, ' package-cache'.
- 	
- 	^ self wipDir. !

Item was removed:
- ----- Method: BobBuild>>infoFileWrite (in category 'as yet unclassified') -----
- infoFileWrite
- 	"obtain the image build script from the metadata record"
- 	
- 	self infoFile delete writer: [ :str | self info storeOn: str ]
- 	
- 	!

Item was removed:
- ScheduledTask subclass: #BobPeriodicallyWatchRepositories
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Sake-Bob'!

Item was removed:
- ----- Method: BobBuildImage>>addScript: (in category 'as yet unclassified') -----
- addScript: aScript
- 
- 	| rs |
- 	rs := aScript readStream.
- 	
- 	[ rs atEnd ] whileFalse: [  
- 		self nextScriptPut: (rs upToAll: '""""""')
- 	].!

Item was removed:
- ----- Method: BobBuild class>>info (in category 'as yet unclassified') -----
- info
- 
- 	^ BobBuild310Build new infoForLast: #build
- 
- !

Item was removed:
- ----- Method: BobBuildImage>>upload (in category 'as yet unclassified') -----
- upload	
- 
- 	| ssh |
- 	(self isUploader not or: [ self info upload isNil ]) ifTrue: [ ^ self ].
- 		
- 	(self class configUploadReleaseOnly and: [ self info release ~= true ]) ifTrue: [ ^ self ].
- 	
- 	ssh := SshUrl absoluteFromText: self info upload.
- 		
- 	self exec: 'scp -r ', self publishDir parent, ' ', ssh username, '@', ssh authority, ':', ssh pathString!

Item was removed:
- ----- Method: BobPeriodicallyWatchRepositories>>taskWatchPackages (in category 'as yet unclassified') -----
- taskWatchPackages
- 
- 	^ SakeTask checkUrl: 'http://www.squeaksource.com/Packages/feed.rss' onChanged: [ "Installer install: 'Packages'" ].!

Item was removed:
- ----- Method: BobBuild>>infoForLast: (in category 'as yet unclassified') -----
- infoForLast: prefix
- 
- 	| selectors |
- 
- 	selectors := (self class selectors select: [ :ea | ea beginsWith: prefix ]) asSortedCollection.
- 	
- 	selectors size < 1 ifTrue: [ ^ nil ].
- 	
- 	self infoFor: selectors last.!

Item was removed:
- ----- Method: BobBuild>>readInfoFileLatest (in category 'as yet unclassified') -----
- readInfoFileLatest
- 	"obtain the most recent info file"
- 	
- 	^ Compiler evaluate: ((self latestDir fileMatching: '*.info') ifNil: [ ^ self class infoNull ]) contents!

Item was removed:
- ----- Method: BobBuildImage class>>build (in category 'as yet unclassified') -----
- build
- 
- 	| isNeeded |
- 	^ self define: [ :task |
- 	
- 		"obtain latest meta-data from instance side"	
- 		(task infoForLast: #build) ifNil: [ ^ self noop ].
- 
- 		task dependsOn: self dependsOn.
- 	
- 		task if: [ 	self log bob starting: task info name.
- 					task timeStart. 
- 					isNeeded := task isBuildNeeded.
- 					self log bob build: task info name isNeeded: isNeeded first because: isNeeded second.
- 					isNeeded first ].
- 		
- 		task action: [ 
- 		
- 			task expandZipFileTo: (task newWipDir). 
- 
- 			task startImage: (task wipDir all fileMatching: '*.image').
- 	
- 			task theScript scriptFileWrite.
- 			 
- 			task step.
- 			
- 			task launchVm: self configVm image: task startImage with: task scriptFile.
- 			
- 			task info timeComplete: DateAndTime now. 
- 			task info timeDuration: ((task info timeComplete - task info timeStart) roundTo: 1 second).
- 
- 			task infoFileWrite.
- 			
- 			task step.
- 			
- 			task publish.
- 			task package.
- 			task tidy.
- 			
- 			self configUploadImmediately ifTrue: [ [task tidy; upload; uploadLinks] fork ].
- 		]
- 	]
- 
- !

Item was removed:
- ----- Method: BobBuild>>step (in category 'as yet unclassified') -----
- step
- 
- 	self info stepping = true ifTrue: [ self halt ]!

Item was removed:
- ----- Method: BobPeriodicallyReadMantis class>>initialize (in category 'as yet unclassified') -----
- initialize
- 
- 	"the squeak community only needs to run this process on a single computer whose name is given in configMantisMonitor"
- 	super initialize.
- 
- 	self scheduler addTask: (self do: [ Mantis pullRecent ] every: 15 minutes).
- 	!

Item was removed:
- ScheduledTask subclass: #BobPeriodicallyReadMantis
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Sake-Bob'!

Item was removed:
- ----- Method: BobPeriodicallyReadMantis class>>configMantisMonitor (in category 'as yet unclassified') -----
- configMantisMonitor
- 
- 	"the squeak community only needs to run this process on a single computer whose name is configured here"
- 
- 	^ 'mercy.flat' !



More information about the Packages mailing list