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

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Sat Feb 21 03:07:44 UTC 2009


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

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

Name: Sake-Bob-kph.12
Author: kph
Time: 21 February 2009, 3:07:41 am
UUID: 8907d942-e0f3-41ce-bc28-bb457e2257fb
Ancestors: Sake-Bob-kph.11

. first working release

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

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

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

Item was added:
+ ----- 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 changed:
  ----- Method: BobBuildImage>>linkRelease (in category 'as yet unclassified') -----
  linkRelease
  
+ 	self info release = true ifTrue: [ 
- 	self info release ifTrue: [ 
  
+ 		self exec:  'cd ', self outputDir ,'; rm release; ln -s ', self publishDir parent, ' release'
- 		self OSProcess waitForCommand: 'ln -s ', self publishDir, ' release'
  	]!

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

Item was changed:
  ----- Method: BobBuild>>isBuildNeeded (in category 'as yet unclassified') -----
  isBuildNeeded
  
+ 	self subclassResponsibility!
- 	| 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:
  ----- Method: BobBuildImage>>package (in category 'as yet unclassified') -----
  package	
  	
+ 	self exec: 'cd ', self publishDir parent, '; zip -R ', self packageFile, ' "', self stampedName ,'/*" -x "__*" ".DS*"'.
+ !
- 	self OSProcess waitForCommand: 'zip ', (self outputDir / self stampedName, '.zip'), ' ',
- 		self publishDir,  '/*'.
- 	!

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

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

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

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

Item was added:
+ ----- 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 added:
+ ----- Method: BobBuild>>exec: (in category 'as yet unclassified') -----
+ exec: aCmdString
+ 
+ 	self log bob exec: aCmdString.
+ 	
+ 	^ self OSProcess waitForCommand: aCmdString!

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

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

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

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

Item was changed:
  ----- Method: BobBuildImage>>publish (in category 'as yet unclassified') -----
  publish	
  	
+ 	self info overwrite = true ifTrue: [ self outputDir all delete ].
- 	self info overwrite ifTrue: [ self outputDir all delete ].
  		
  	self publishDir mkpath.
  	
+ 	self publishManifest.
- 	self publishDir addAll: (self workingDir filesMatching: (self stampedName, '.*')).
- 
- 	"one info file for inside the archive"
- 	self infoFile copyTo: (self publishDir / self stampedName, '.info').
  	
+ 	self linkLatest.  
- 	"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>>scriptCommentedHalt (in category 'as yet unclassified') -----
+ scriptCommentedHalt
+ 
+ 	^ '"self halt."' !

Item was added:
+ ----- 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 added:
+ ----- 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!
- 	self OSProcess waitForCommand: vm, ' ' , imageFile, ' ', scriptFile!

Item was added:
+ ----- 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 added:
+ ----- Method: BobConfig class>>configUploader (in category 'as yet unclassified') -----
+ configUploader
+ 
+ 	^ 'mercy.flat'!

Item was added:
+ ----- Method: BobConfig class>>configPackageCacheDir (in category 'as yet unclassified') -----
+ configPackageCacheDir
+ 
+ 	^ self configBaseDir / 'shared-package-cache'!

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

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

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

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

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

Item was added:
+ ----- Method: SshUrl class>>absoluteFromText: (in category 'as yet unclassified') -----
+ absoluteFromText: aString
+ 	"Method that can be called explicitly to create a FileUrl."
+ 
+ 	^self new privateInitializeFromText: aString!

Item was added:
+ ----- Method: BobBuildImage>>isBuildNeeded (in category 'as yet unclassified') -----
+ isBuildNeeded
+ 
+ 	| 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') ].
+  
+ 	"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 readInfoFileLatest.
+ 
+ 	"has our starting image changed? if so"
+ 	(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 changed:
  ----- Method: BobBuild>>timeStart (in category 'as yet unclassified') -----
  timeStart
  	
+ 	
  	info timeStart ifNil: [ info timeStart: DateAndTime now ].
  	
  	^ info timeStart
  	!

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

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

Item was changed:
  BobConfig subclass: #BobBuildImage
+ 	instanceVariableNames: 'startImage'
- 	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 changed:
  ----- 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: BobBuild class>>info (in category 'as yet unclassified') -----
+ info
+ 
+ 	^ BobBuild310Build new infoForLast: #build
+ 
+ !

Item was added:
+ ----- 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 changed:
  ----- Method: BobBuild>>infoFor: (in category 'as yet unclassified') -----
  infoFor: selector
  	 
+ 	self info name: self class label.
  	self info build: selector.
  	self info label: self class label.
  	self info when: #dont.
  	
  	self perform: selector.
  	
+ 	self info when: self preprocessWhen.
  	
  	
  	!

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

Item was added:
+ ----- Method: SshUrl>>pathString (in category 'as yet unclassified') -----
+ pathString
+ 	self path isEmpty ifTrue: [ ^'/' copy ].
+ 
+ 	^String streamContents: [ :s |
+ 		self path do: [ :p |
+ 		 	s nextPut: $/.
+ 			s nextPutAll: p ] ]!

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

Item was added:
+ ----- 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 changed:
  ----- 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!
- 	^ Compiler evaluate: (self latestDir fileMatching: '*.info') contents!

Item was added:
+ ----- 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 bob found: found.
+ 					localZipFile := found
+ 				].
+ 			].
+ 		
+ 			localZipFile exists ifFalse: [ 
+ 				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 changed:
  ----- 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 infoForLatest: #build) ifNil: [ ^ self noop ].
  	
+ 		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 if: [ 	task timeStart. 
- 					task isBuildNeeded					].
  		
  		task action: [ 
  		
+ 			task expandZipFileTo: (task newWipDir). 
+ 
+ 			task startImage: (task wipDir all fileMatching: '*.image').
- 			task expandZipFileMatching: task info image to: (task wipDir all delete). 
- 			task startImage: (task wipDir fileMatching: '*.image').
  	
  			task theScript scriptFileWrite.
+ 			 
+ 			task step.
+ 			
+ 			task launchVm: self configVm image: task startImage with: task scriptFile.
+ 			
- 			
- 			task launchImage: task startImage full with: self scriptFile full.
- 				
  			task info timeComplete: DateAndTime now. 
+ 			task info timeDuration: ((task info timeComplete - task info timeStart) roundTo: 1 second).
- 			task info timeDuration: (task info timeComplete - task info timeStart).
  
  			task infoFileWrite.
  			
+ 			task step.
+ 			
  			task publish.
  			task package.
+ 			task tidy.
+ 			
+ 			self configUploadImmediately ifTrue: [ [task tidy; upload; uploadLinks] fork ].
  		]
  	]
  
  !

Item was changed:
  ----- 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:
+ HierarchicalUrl subclass: #SshUrl
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Sake-Bob'!

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

Item was added:
+ ----- Method: BobBuildImage>>publishManifest (in category 'as yet unclassified') -----
+ publishManifest
+ 	
+ 	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 changed:
  ----- Method: BobBuildImage>>scriptTranscriptLogToFileStop (in category 'as yet unclassified') -----
  scriptTranscriptLogToFileStop
  
+ 	self nextScriptPut: '"self halt." Preferences setPreference: #logTranscriptToFile toValue: false.'.
- 	self nextScriptPut: 'Preferences setPreference: #logTranscriptToFile toValue: false'.
  !

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

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

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

Item was added:
+ ----- Method: BobBuild>>zipFileMatching: (in category 'as yet unclassified') -----
+ zipFileMatching: zipFileMatch
+ 		
+ 	"
+ 	(self obtainImage: 'ftp://ftp.squeak.org/3.10/Squeak3.10.2-*-basic.zip') run  
+ 	"
+ 	| localZipFile zipFile |
+ 
+ 	^ zipFileMatch asFile resolveMatchOne 
+ 		ifNil: [ self error: 'unique zip file matching ', zipFileMatch, ' not found' ].
+ 	!

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

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

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

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: BobBuildImage class>>infoNull (in category 'as yet unclassified') -----
- infoNull
- 
- 	"When No Previous Build"
- 
- 	^ SakeMeta new 
- 		timeStart: DateAndTime epoch;
- 		build: #none;
- 		yourself
- 	
- !

Item was removed:
- ----- 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!



More information about the Packages mailing list