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

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Tue Feb 17 22:42:22 UTC 2009


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

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

Name: Sake-Bob-kph.10
Author: kph
Time: 17 February 2009, 10:42:20 pm
UUID: b7a5fc69-68b1-4dba-9c32-98e612a04fdb
Ancestors: Sake-Bob-kph.9

approaching readiness

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

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

Item was added:
+ ----- Method: BobBuildImage>>theScript (in category 'as yet unclassified') -----
+ theScript
+ 
+ 	self 
+ 			scriptTranscriptLogToFile;
+ 			"scriptAddLPF;"
+ 			scriptAddInfoScript;
+ 			"scriptOpenInWorkspace: self configScriptFile fileName;"
+ 			scriptTranscriptLogToFileStop;
+ 			scriptSaveImage.
+ 			
+ !

Item was added:
+ ----- Method: BobBuild>>OSProcess (in category 'as yet unclassified') -----
+ OSProcess
+ 	
+ 	^ Smalltalk at: #OSProcess ifAbsent: [ ^ self error: 'OSProcess no installed' ].
+ 	
+ 	!

Item was added:
+ ----- Method: BobBuildImage>>scriptTranscriptLogToFile (in category 'as yet unclassified') -----
+ scriptTranscriptLogToFile
+ 
+ 	self nextScriptPut:  'HTTPSocket httpFileIn: ''installer.pbwiki.com/f/TranscriptToFile.cs'''.
+ 	.
+ !

Item was added:
+ ----- Method: BobBuildImage>>workingDir (in category 'as yet unclassified') -----
+ workingDir
+ 
+ 	^ self startImage parent!

Item was added:
+ ----- Method: BobBuildImage>>scriptOpenTranscript (in category 'as yet unclassified') -----
+ scriptOpenTranscript
+ 
+ 	self nextScriptPut: 'Transcript open'.
+ !

Item was added:
+ ----- Method: BobBuild>>timeStart (in category 'as yet unclassified') -----
+ timeStart
+ 	
+ 	info timeStart ifNil: [ info timeStart: DateAndTime now ].
+ 	
+ 	^ info timeStart
+ 	!

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

Item was added:
+ ----- Method: BobBuildImage>>linkRelease (in category 'as yet unclassified') -----
+ linkRelease
+ 
+ 	self info release ifTrue: [ 
+ 
+ 		self OSProcess waitForCommand: 'ln -s ', self publishDir, ' release'
+ 	]!

Item was added:
+ ----- Method: BobBuild class>>label (in category 'as yet unclassified') -----
+ label
+ 		
+ 	^ self name readStream upToAll: 'BobBuild'; upToEnd!

Item was changed:
  ----- Method: BobBuild>>outputDir (in category 'as yet unclassified') -----
  outputDir
  
+ 	^ info outputTo ifNil: [self class configOutputDir ]!
- 	^ info outputTo ifNil: [  ]!

Item was added:
+ ----- 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 added:
+ ----- Method: BobConfig class>>configMe (in category 'as yet unclassified') -----
+ configMe
+ 	
+ 	"my host name - my identity"
+ 	
+ 	^ NetNameResolver localHostName!

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

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

Item was added:
+ ----- Method: BobBuild>>isBuildNeeded (in category 'as yet unclassified') -----
+ isBuildNeeded
+ 
+ 	| latest |
+ 
+ 	"if the output directory doesnt exist then we dont build"
+ 	self outputDir asDirectory exists ifFalse: [ ^ false ].
+ 	
+ 	"if we have the dont flag - dont build anything"	
+ 	info when = #dont ifTrue: [ ^ false ].
+ 
+ 	"if an explicit build time has been set and not yet reached"	
+ 	((info when isKindOf: DateAndTime) and: [ info when > info timeStart ]) 
+ 		ifTrue: [ ^ false ].
+ 
+ 	latest := self readInfoFileLatest ifNil: [ self class infoNull ].
+ 
+ 	"we have a new build id, so we build"
+ 	latest build ~= info build ifTrue: [ ^ true ].
+ 	
+ 	(info when isKindOf: Duration) ifTrue: [
+ 		latest timeStart + info when > TimeStamp now ifTrue: [ ^ true ].
+ 	].
+ 
+ 	^ false
+ 
+ 	
+ !

Item was changed:
+ BobConfig subclass: #BobBuildImage
- BobBuild subclass: #BobBuildImage
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Sake-Bob'!
+ 
+ !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>>scriptAddInfoScript (in category 'as yet unclassified') -----
+ scriptAddInfoScript
+ 
+ 	| rs |
+ 	rs := (self class docAt: self info build) readStream.
+ 	
+ 	[ rs atEnd ] whileFalse: [  
+ 		self nextScriptPut: (rs upToAll: '""""""') asString
+ 	].!

Item was added:
+ ----- Method: BobConfig class>>configOutputDir (in category 'as yet unclassified') -----
+ configOutputDir
+ 
+ 	^  self configBaseDir / 'output' / self label!

Item was added:
+ ----- Method: BobBuild>>expandZipFileMatching:to: (in category 'as yet unclassified') -----
+ expandZipFileMatching: zipFileMatch to: destDir
+ 		
+ 	"
+ 	(self obtainImage: 'ftp://ftp.squeak.org/3.10/Squeak3.10.2-*-basic.zip') run  
+ 	"
+ 	| localZipFile zipFile |
+ 
+ 	zipFile := zipFileMatch asFile resolveMatchOne 
+ 		ifNil: [ self error: 'unique zip file matching ', zipFileMatch, ' not found' ].
+ 	
+ 	zipFile executive isRemote 
+ 		ifTrue: [ 
+ 			localZipFile := self class configImagesDir  / zipFile fileName.
+ 			localZipFile exists ifFalse: [ 
+ 				self log: 'downloading: ', zipFile.
+ 				localZipFile parent mkpath add: zipFile ].	
+ 		]
+ 		ifFalse: [ localZipFile := zipFile zip ].
+ 		
+ 	self log: 'expanding: ', localZipFile.
+ 	self log: 'to: ', destDir.		
+ 	localZipFile zip readArchive extractAllTo: destDir mkpath asFileDirectory.
+ 	
+ 	!

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

Item was added:
+ ----- Method: BobBuildImage>>package (in category 'as yet unclassified') -----
+ package	
+ 	
+ 	self OSProcess waitForCommand: 'zip ', (self outputDir / self stampedName, '.zip'), ' ',
+ 		self publishDir,  '/*'.
+ 	!

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

Item was added:
+ ----- Method: BobBuild>>nextScriptPut: (in category 'as yet unclassified') -----
+ nextScriptPut: aScript
+ 
+ 	script 	nextChunkPut: aScript, String cr;
+ 			nextChunkPut: ' ';
+ 			cr.
+ !

Item was added:
+ ----- Method: BobBuildImage>>linkLatest (in category 'as yet unclassified') -----
+ linkLatest
+ 
+ 	self OSProcess waitForCommand: 'ln -s ', self publishDir, ' latest'!

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

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

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

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

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

Item was added:
+ ----- Method: BobBuild>>theScript (in category 'as yet unclassified') -----
+ theScript
+ 	"obtain the image build script from the metadata record"
+ 	
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: BobConfig class>>configImagesDir (in category 'as yet unclassified') -----
+ configImagesDir
+ 
+ 	^ self configBaseDir / 'images' !

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

Item was added:
+ BobBuild subclass: #BobConfig
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Sake-Bob'!
+ 
+ !BobConfig commentStamp: 'kph 2/17/2009 01:37' prior: 0!
+ BobConfig is a class which only contains configuration data. This allows a configuration for a deployment environment to be saved/loaded as a class fileOut.
+ 
+ Each group of building tasks (e.g. BobBuildImage), may define a configuration via its superclass (i.e BobConfig) There may be more than one configuration class (e.g. BobConfigWeb), as appropriate for each group of building tasks (e.g. BobBuildWebsites).!

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

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."
  	
+ 	^ (self allSubclasses collect: [ :c | c build ]) asTask defined
+ 
- 	^ (self allSubclasses collect: [ self build ]) asTask; defined
  !

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

Item was added:
+ ----- Method: BobBuild>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	
+ 	script := String new writeStream!

Item was added:
+ ----- Method: BobBuildImage>>scriptOpenInWorkspace: (in category 'as yet unclassified') -----
+ scriptOpenInWorkspace: afilename
+ 
+ 	self nextScriptPut: 'Workspace openFile: ', afilename printString, '.'.
+ !

Item was added:
+ ----- Method: BobConfig class>>configRssUrl (in category 'as yet unclassified') -----
+ configRssUrl
+ 
+ 	^ 'http://www.squeaksource.com/Bob/feed.rss'!

Item was added:
+ ----- Method: BobBuildImage>>publish (in category 'as yet unclassified') -----
+ publish	
+ 	
+ 	self info overwrite ifTrue: [ self outputDir all delete ].
+ 		
+ 	self publishDir mkpath.
+ 	
+ 	self publishDir addAll: (self workingDir filesMatching: (self stampedName, '.*')).
+ 
+ 	"one info file for inside the archive"
+ 	self infoFile copyTo: (self publishDir / self stampedName, '.info').
+ 	
+ 	"one info file for outside the archive"
+ 	self infoFile copyTo: (self publishDir parent / self stampedName, '.info').
+ 	
+ 	self linkLatest.
+ 	self linkRelease.
+ !

Item was added:
+ ----- Method: BobBuild>>stampedName (in category 'as yet unclassified') -----
+ stampedName
+ 
+ 	^self stamp , '_' , self name !

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

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

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

Item was added:
+ ----- Method: BobBuildImage>>launchImage (in category 'as yet unclassified') -----
+ launchImage
+ 
+ 	self launchVm: self class configVm image: self startImage full with: self scriptFile full!

Item was changed:
  ----- Method: BobBuildImage class>>build (in category 'as yet unclassified') -----
  build
  
+ 	| |
- 	^ self define: [ :task |
- 	
- 		"obtain latest meta-data from instance side"	
- 
- 		task latest: #build.
- 		task info timeStart: TimeStamp now.
  	
+ 	^ self define: [ :task |
+ 	
+ 		"obtain latest meta-data from instance side"	
+ 		(task infoForLatest: #build) ifNil: [ ^ self noop ].
+ 	
+ 		task if: [ 	task timeStart. 
+ 					task isBuildNeeded					].
- 		task action: { 
  		
+ 		task action: [ 
+ 		
+ 			task expandZipFileMatching: task info image to: (task wipDir all delete). 
+ 			task startImage: (task wipDir fileMatching: '*.image').
+ 	
+ 			task theScript scriptFileWrite.
- 			self taskObtainImage: task info image asFile. 
- 			
  			
+ 			task launchImage: task startImage full with: self scriptFile full.
+ 				
+ 			task info timeComplete: DateAndTime now. 
+ 			task info timeDuration: (task info timeComplete - task info timeStart).
+ 
+ 			task infoFileWrite.
+ 			
+ 			task publish.
+ 			task package.
+ 		]
+ 	]
+ 
+ !
- 			
- 			}
- 	]!

Item was added:
+ ----- Method: BobBuild>>preprocessWhen (in category 'as yet unclassified') -----
+ preprocessWhen
+ 
+ 	| w |
+ 	
+ 	w := info when.
+ 	
+ 	(w isKindOf: ByteString) ifFalse:[ ^ w ].
+ 	
+ 	^  [[[ w asDateAndTime ] ifError: [ w asTimeStamp ]] ifError: [ w asDuration ]] ifError: [ w asTime ]
+ 
+ 	
+ 	!

Item was added:
+ ----- Method: BobBuildImage>>scriptTranscriptLogToFileStop (in category 'as yet unclassified') -----
+ scriptTranscriptLogToFileStop
+ 
+ 	self nextScriptPut: 'Preferences setPreference: #logTranscriptToFile toValue: false'.
+ !

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

Item was added:
+ ----- Method: Duration>>storeOno: (in category '*sake-bob') -----
+ storeOno: aStream
+ 
+ 	self printOn: aStream.
+ 	aStream nextPutAll: ' asDuration'!

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

Item was added:
+ ----- Method: BobBuildImage>>startImage (in category 'accessing') -----
+ startImage
+ 	"Answer the value of startImage"
+ 
+ 	^ startImage!

Item was added:
+ ----- Method: BobBuildImage>>newImageName (in category 'as yet unclassified') -----
+ newImageName
+ 
+ 	^ (self timeStart printYYMMDDHHSS: '-'), info name, '.image'!

Item was added:
+ ----- Method: BobBuildImage>>scriptSaveImage (in category 'as yet unclassified') -----
+ scriptSaveImage
+ 
+ 	| s |
+ 	s := String new writeStream.
+ 	
+ 	s << 'SystemVersion newVersion: ' << self name printString << '.' ; cr.
+ 	s << 'SystemVersion current date: ''' << self timeStart printString << ''' asDateAndTime.'; cr.
+ 	s << 'SmalltalkImage current cleanUpAllExcept: #(ChangeSet); saveAs: '<< self stampedName << '.'.
+ 	
+ 	self nextScriptPut: s contents!

Item was added:
+ ----- 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 added:
+ ----- Method: BobBuild>>launchVm:image:with: (in category 'as yet unclassified') -----
+ launchVm: vm image: imageFile with: scriptFile
+ 
+ 	self OSProcess waitForCommand: vm, ' ' , imageFile, ' ', scriptFile!

Item was added:
+ ----- Method: BobBuildImage>>scriptAddLPF (in category 'as yet unclassified') -----
+ scriptAddLPF
+ 
+ 	self nextScriptPut: 'HTTPSocket httpFileIn: ''installer.pbwiki.com/f/LPF.st'''.
+ !

Item was added:
+ ----- Method: BobBuild>>scriptFileWrite (in category 'as yet unclassified') -----
+ scriptFileWrite
+ 	
+ 	self scriptFile delete contents: script contents
+ 	
+ 	script reset.
+ 	
+ 	^ self scriptFile!

Item was added:
+ ----- Method: BobBuild>>scriptFile (in category 'as yet unclassified') -----
+ scriptFile
+ 	 
+ 	^ self workingDir / self class configScriptFileName !

Item was changed:
  SakeTask subclass: #BobBuild
+ 	instanceVariableNames: 'script'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Sake-Bob'!

Item was removed:
- ----- Method: BobBuild class>>configRssUrl (in category 'as yet unclassified') -----
- configRssUrl
- 
- 	^ 'http://www.squeaksource.com/Bob/feed.rss'!

Item was removed:
- ----- Method: BobBuild class>>taskObtainImage: (in category 'as yet unclassified') -----
- taskObtainImage: zipFile
- 		
- 	"
- 	(self taskObtainImage: 'ftp://ftp.squeak.org/3.10/Squeak3.10.2-7179-basic.zip' asFile) run  
- 	"
- 	| localZipFile |
- 
- 	localZipFile := (self configImagesDir  / zipFile fileName) zip.
- 
- 	^ self define: [ :task |
- 		task dependsOn: { self taskObtainImageZipFile: zipFile }.
- 		
- 		task action: [
- 			localZipFile readArchive extractAllTo: task wipDir mkpath asFileDirectory.
- 		]
-  	]
- !

Item was removed:
- ----- Method: BobBuild>>latest: (in category 'as yet unclassified') -----
- latest: prefix
- 
- 	"
- 	BobBuildReleaseAfterSqueak310 new latest: #build.
- 	"
- 	
- 	| selector |
- 	selector := (self class selectors select: [ :ea | ea beginsWith: prefix ]) asSortedCollection last.
- 	
- 	self info build: selector asString.
- 	self perform: selector.
- 	
- 	
- 	
- 	!

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

Item was removed:
- ----- Method: BobBuild class>>configMe (in category 'as yet unclassified') -----
- configMe
- 	
- 	"my host name - my identity"
- 	
- 	^ NetNameResolver localHostName!

Item was removed:
- ----- Method: BobBuild class>>taskObtainImageZipFile: (in category 'as yet unclassified') -----
- taskObtainImageZipFile: zipFile
- 
- 	"
- 	(self taskObtainImageZipFile: 'ftp://ftp.squeak.org/3.10/Squeak3.10.2-7179-basic.zip' asFile) run
- 	"
- 
- 	^ self define: [ :task |
- 		
- 		task if: [ (self configImagesDir  / zipFile fileName) exists not ]. 
- 		
- 		task action: [ 
- 			self configImagesDir mkpath add: zipFile.	
- 		]
-  	]
- !

Item was removed:
- ----- Method: BobBuild class>>configImagesDir (in category 'as yet unclassified') -----
- configImagesDir
- 
- 	^ 'images' asDirectory!

Item was removed:
- ----- Method: BobBuild class>>obtainImageFtp: (in category 'as yet unclassified') -----
- obtainImageFtp: aUrl
- 
- 	 !



More information about the Packages mailing list