[Pkg] Installer: Installer-Launcher-mtf.6.mcz

squeaksource-noreply at iam.unibe.ch squeaksource-noreply at iam.unibe.ch
Thu Jul 3 22:16:28 UTC 2008


A new version of Installer-Launcher was added to project Installer:
http://www.squeaksource.com/Installer/Installer-Launcher-mtf.6.mcz

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

Name: Installer-Launcher-mtf.6
Author: mtf
Time: 3 July 2008, 3:16:35 pm
UUID: f0456504-f4fe-4cb7-95ae-400952bf771f
Ancestors: Installer-Launcher-kph.4

reformatted the code to have a consistent style

=============== Diff against Installer-Launcher-kph.4 ===============

Item was changed:
  ----- Method: Launcher>>actionSelector: (in category 'as yet unclassified') -----
  actionSelector: aSelector
  
+ 	actionSelector := aSelector!
-  actionSelector := aSelector!

Item was changed:
  ----- Method: Launcher>>reportFor:with: (in category 'reporting') -----
  reportFor: target with: params
   
+ 	| reports dest scriptIO quit |
+ 	reports := params at: 'REPORT' ifAbsent: [ ^ self error: 'no report requested' ].
+ 	reports := reports findTokens: ' '.
+ 	dest := params at: 'TO' ifAbsent: nil.
+ 	scriptIO := Script new writeTo: (params at: 'TO' ifAbsent: nil) in: (params at: 'DIR' ifAbsent: '').
-  | reports dest scriptIO quit |
-  
-  reports := params at: 'REPORT' ifAbsent: [ ^ self error: 'no report requested' ].
- 
-  reports := reports findTokens: ' '.
- 
-  dest := params at: 'TO' ifAbsent: nil.
- 
-  scriptIO := Script new writeTo: (params at: 'TO' ifAbsent: nil) in: (params at: 'DIR' ifAbsent: '').
- 
-  reports do: [ : reportSelector |
- 	scriptIO := Script new 
- 		writeTo: (dest ifNotNil: [ dest copyReplaceAll:'*' with: reportSelector]) 
- 		in: (params at: 'DIR' ifAbsent: '').
- 
-      scriptIO printWith: [ :out | self report: reportSelector asSymbol for: target on: out ].
-  ].
-  
-  quit := params at: 'QUIT' ifAbsent: [ false ].
-  quit ~= false ifTrue: [ SmalltalkImage current snapshot: false andQuit: true ].
  
+ 	reports do: [ : reportSelector |
+ 		scriptIO := Script new 
+ 			writeTo: (dest ifNotNil: [ dest copyReplaceAll:'*' with: reportSelector]) 
+ 			in: (params at: 'DIR' ifAbsent: '').
+ 		scriptIO printWith: [ :out | self report: reportSelector asSymbol for: target on: out ] ].
+  
+ 	quit := params at: 'QUIT' ifAbsent: [ false ].
+ 	quit ~= false ifTrue: [ SmalltalkImage current snapshot: false andQuit: true ].
+ 	^true!
-  ^true!

Item was changed:
  ----- Method: Script class>>startWith: (in category 'as yet unclassified') -----
  startWith: params
  
+ 	| script |
+ 	script := self new.
+ 	params at: 'TO' ifPresent: [ :v | script writeTo: v in: (params at: 'DIR' ifAbsent: '')].
+ 	params at: 'INIT' ifPresent: [ :v | script evaluate: v ].
+ 	params at: 'INITP' ifPresent: [ :v | script evaluateAndPrint: v ].
+ 	^true!
- | script |
-  
- script := self new.
- 
- params at: 'TO' ifPresent: [ :v | 
- 	 script writeTo: v in: (params at: 'DIR' ifAbsent: '')
- ].
- 
-  
- params at: 'INIT' ifPresent: [ :v | 
- 	 script evaluate: v.
- ].
- 
- params at: 'INITP' ifPresent: [ :v | 
- 	 script evaluateAndPrint: v.
- ].
- 
- ^true!

Item was changed:
  ----- Method: Launcher>>initialize (in category 'as yet unclassified') -----
  initialize
  
+ 	nextParameterIndex := 2!
- nextParameterIndex := 2!

Item was changed:
  ----- Method: Script>>evaluateAndPrint: (in category 'as yet unclassified') -----
  evaluateAndPrint: code
  
+ 	self printWith: [ :output | output nextPutAll: (self evaluate: code) asString; cr ]
- self printWith: [ :output | output nextPutAll: (self evaluate: code) asString; cr ].
  	 !

Item was changed:
  ----- Method: Launcher>>classes (in category 'as yet unclassified') -----
  classes
  
+ 	^ Smalltalk!
- ^ Smalltalk!

Item was changed:
  ----- Method: Script>>printWith: (in category 'as yet unclassified') -----
  printWith: aBlock
  
+ 	fileout ifNil: [ ^aBlock value: stdout ].
+ 	FileStream detectFile: [ dir forceNewFileNamed: fileout ] do: aBlock !
- fileout ifNil: [ ^aBlock value: stdout ].
- 
- FileStream detectFile: [ dir forceNewFileNamed: fileout ] do: aBlock !

Item was changed:
  ----- Method: Script>>stderr (in category 'as yet unclassified') -----
  stderr
  
+ 	^stderr!
- ^stderr!

Item was changed:
  ----- Method: Launcher class>>launchWith: (in category 'as yet unclassified') -----
  launchWith: params
  
+ 	params at: 'H' ifPresent: [:v | params at: 'HELP' put: v ].
+ 	params at: 'S' ifPresent: [ :v | params at: 'SCRIPTS' put: v ].
+ 	params at: 'HELP' ifPresent: [ :v | Script new writeHelp ].
+ 	params at: 'SCRIPTS' ifPresent: [:v |
+ 		CodeLoader new loadSourceFiles: (Array with: (v findTokens: ' '))].
+ 	^true!
- params at: 'H' ifPresent: [:v | params at: 'HELP' put: v ].
- 
- params at: 'S' ifPresent: [ :v |
- 	params at: 'SCRIPTS' put: v
- ].
- 
- params at: 'HELP' ifPresent: [ :v | 
- 	 Script new writeHelp.
- ].
- 
- params at: 'SCRIPTS' ifPresent: [:v | 
- 	 CodeLoader new loadSourceFiles: (Array with: (v findTokens: ' ')).
- ].
- 
- ^true!

Item was changed:
  ----- Method: Launcher>>launch: (in category 'as yet unclassified') -----
  launch: aClass
  
+ 	^ (aClass respondsTo: actionSelector) 
+ 		ifTrue: [ aClass perform: actionSelector with: self ]
+ 		ifFalse: [ false ]!
-  ^ (aClass respondsTo: actionSelector) 
- 	ifTrue: [ aClass perform: actionSelector with: self ]
- 	ifFalse: [ false ]!

Item was changed:
  ----- Method: Launcher>>report:for:on: (in category 'reporting') -----
  report: reportSelector for: item on: stream
- 	
- 	(item respondsTo: reportSelector) ifFalse: [ ^ stream nextPutAll: 'REPORT UNAVAILABLE'; cr ].
- 	
- 	(reportSelector last = $:) ifTrue: [ ^item perform: reportSelector with: stream ].
- 	
- 	(item perform: reportSelector) ifNotNilDo: [ :result | 
- 		^result isString ifTrue: [ stream nextPutAll: result ] 
- 		 			   ifFalse: [ result do: [ :each | stream nextPutAll: each asString; cr ] ].
- 	].
  
+ 	(item respondsTo: reportSelector) ifFalse: [ ^ stream nextPutAll: 'REPORT UNAVAILABLE'; cr ].
+ 	(reportSelector last = $:) ifTrue: [ ^item perform: reportSelector with: stream ].
+ 	(item perform: reportSelector) ifNotNilDo: [ :result | 
+ 		^result isString
+ 			ifTrue: [ stream nextPutAll: result ] 
+ 			ifFalse: [ result do: [ :each | stream nextPutAll: each asString; cr ] ] ]!
-  !

Item was changed:
  ----- Method: Launcher class>>startUp: (in category 'as yet unclassified') -----
  startUp: resuming
- 
  "we are sent this when starting as an image startup item before autostart"
  
  	^ self newStartWith: SmalltalkImage current !

Item was changed:
  ----- Method: Script>>initialize (in category 'as yet unclassified') -----
  initialize
  
+ 	stdout := (MultiByteFileStream new) 
+ 		wantsLineEndConversion: #crlf; 
+ 		open: '/dev/stdout' forWrite: true.
+ 		
+ 	stderr :=  (MultiByteFileStream new) 
+ 		wantsLineEndConversion: #crlf; 
+ 		open: '/dev/stderr' forWrite: true. 
+ 	 
+ 	stdin  := AsyncFile new open: '/dev/stdin' forWrite: false.!
- stdout := (MultiByteFileStream new) 
- 			wantsLineEndConversion: #crlf; 
- 			open: '/dev/stdout' forWrite: true.
- 			 
- 			
- stderr :=  (MultiByteFileStream new) 
- 			wantsLineEndConversion: #crlf; 
- 			open: '/dev/stderr' forWrite: true. 
- 			 
- stdin  := AsyncFile new open: '/dev/stdin' forWrite: false.!

Item was changed:
  ----- Method: Launcher class>>startWith: (in category 'as yet unclassified') -----
  startWith: params
  
+ 	params at: 'START' ifPresent: [:v | CodeLoader new loadSourceFiles: (Array with: (v findTokens: ' '))].
+ 	^true!
- params at: 'START' ifPresent: [:v | 
- 	 CodeLoader new loadSourceFiles: (Array with: (v findTokens: ' ')).
- ].
- 
- ^true!

Item was changed:
  ----- Method: Script class>>launchWith: (in category 'as yet unclassified') -----
  launchWith: params
  
+ 	| script quit |
+ 	params at: 'E' ifPresent: [:v | params at: 'EVAL' put: v ].
+ 	params at: 'P' ifPresent: [:v | params at: 'PRINT' put: v ].
- | script quit |
- 
- params at: 'E' ifPresent: [:v | params at: 'EVAL' put: v ].
- params at: 'P' ifPresent: [:v | params at: 'PRINT' put: v ].
- 
- script := self new.
- 
- params at: 'TO' ifPresent: [ :v | 
- 	 script writeTo: v in: (params at: 'DIR' ifAbsent: '')
- ].
- 
- params at: 'HELP' ifPresent: [ :v | 
- 	 script writeHelp.
- ].
- 
- params at: 'EVAL' ifPresent: [ :v | 
- 	 script evaluate: v.
- ].
- 
- params at: 'PRINT' ifPresent: [ :v | 
- 	 script evaluateAndPrint: v.
- ].
  
+ 	script := self new.
- quit := params at: 'QUIT' ifAbsent: true.
  
+ 	params at: 'TO' ifPresent: [ :v | script writeTo: v in: (params at: 'DIR' ifAbsent: '')].
+ 	params at: 'HELP' ifPresent: [ :v | script writeHelp ].
+ 	params at: 'EVAL' ifPresent: [ :v | script evaluate: v ].
+ 	params at: 'PRINT' ifPresent: [ :v | script evaluateAndPrint: v ].
+ 
+ 	quit := params at: 'QUIT' ifAbsent: true.
+ 	quit ~= false ifTrue: [ SmalltalkImage current snapshot: false andQuit: true ].
+ 	^true!
- quit ~= false ifTrue: [ SmalltalkImage current snapshot: false andQuit: true ].
- 
- ^true!

Item was changed:
  ----- Method: Script>>stdout (in category 'as yet unclassified') -----
  stdout
  
+ 	^stdout!
- ^stdout!

Item was changed:
  ----- Method: Launcher>>getSystemAttribute: (in category 'as yet unclassified') -----
  getSystemAttribute: n
+ "this provides the ability for us to be a mock image with startup parameters in our array."
-  "this provides the ability for us to be a mock image with startup parameters in our array."
  
+ 	^ mock at: n - 1 ifAbsent: nil!
- ^ mock at: n - 1 ifAbsent: nil!

Item was changed:
  ----- Method: Script>>writeTo:in: (in category 'as yet unclassified') -----
  writeTo: fileName in: directory
  
+ 	fileout := fileName.
+ 	dir := FileDirectory on: (FileDirectory default fullNameFor: directory).
+ 	dir assureExistence.!
- fileout := fileName.
- dir := FileDirectory on: (FileDirectory default fullNameFor: directory).
- dir assureExistence.!

Item was changed:
  ----- Method: Launcher>>reportFor: (in category 'reporting') -----
  reportFor: target  
  
+ 	^ self reportFor: target with: self getParameters!
- ^ self reportFor: target with: self getParameters!

Item was changed:
  ----- Method: Launcher>>commandLineClass: (in category 'as yet unclassified') -----
  commandLineClass: aClass
+ 
+ 	commandLineClass := aClass.
-    commandLineClass := aClass.
   			
  			!

Item was changed:
  ----- Method: Launcher>>image: (in category 'as yet unclassified') -----
  image: imageOrMock
  
+ 	image := imageOrMock isCollection  
+ 		ifTrue: [ mock := imageOrMock. self ]
+ 		ifFalse: [ imageOrMock ] .
-   image := imageOrMock isCollection  
- 			ifTrue: [ mock := imageOrMock. self ] ifFalse: [ imageOrMock ] .
  
   !

Item was changed:
  ----- Method: Script>>writeHelp (in category 'as yet unclassified') -----
  writeHelp
  
  	| helps |
- 	
  	helps := SystemNavigation default allImplementorsOf: #launchHelp.
- 
  	self printWith: [ :output |	
  		helps do: [ :mr | 
+ 			output nextPutAll: mr classSymbol; cr; cr.
+ 			output nextPutAll: (mr actualClass soleInstance launchHelp); cr; cr ] ]!
- 			output nextPutAll: mr classSymbol; cr;cr.
- 			output nextPutAll: (mr actualClass soleInstance launchHelp); cr;cr.
- 		].
- 	].!



More information about the Packages mailing list