[squeak-dev] The Trunk: MorphicExtras-tpr.219.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Dec 28 20:40:02 UTC 2017


tim Rowledge uploaded a new version of MorphicExtras to project The Trunk:
http://source.squeak.org/trunk/MorphicExtras-tpr.219.mcz

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

Name: MorphicExtras-tpr.219
Author: tpr
Time: 28 December 2017, 12:39:47.049664 pm
UUID: ca33da45-a124-4124-9add-82d1c22e1a07
Ancestors: MorphicExtras-nice.218

Connect assorted sound/event/PS saving operations to the new file dialogs

=============== Diff against MorphicExtras-nice.218 ===============

Item was changed:
  ----- Method: BookMorph>>printPSToFile (in category 'menus') -----
  printPSToFile
  	"Ask the user for a filename and print this morph as postscript."
  
  	| fileName rotateFlag |
+ 	fileName := 'MyBook' translated asFileName.
+ 	fileName := UIManager default saveFilenameRequest: 'Filename to save BookMorph' translated 
- 	fileName := ('MyBook') translated asFileName.
- 	fileName := UIManager default request: 'File name? (".ps" will be added to end)' translated 
  			initialAnswer: fileName.
  	fileName isEmpty ifTrue: [^ Beeper beep].
  	(fileName endsWith: '.ps') ifFalse: [fileName := fileName,'.ps'].
  
  	rotateFlag := (UIManager default chooseFrom: {
  		'portrait (tall)' translated.
  		'landscape (wide)' translated
  	} title: 'Choose orientation...' translated) = 2.
  
+ 	FileStream newFileNamed: fileName do: [:file|
+ 		file nextPutAll: (DSCPostscriptCanvas morphAsPostscript: self rotated: rotateFlag)]
- 	(FileStream newFileNamed: fileName asFileName)
- 		nextPutAll: (DSCPostscriptCanvas morphAsPostscript: self rotated: rotateFlag); close.
  
  !

Item was changed:
  ----- Method: DSCPostscriptCanvasToDisk class>>morphAsPostscript:rotated:offsetBy:specs: (in category 'as yet unclassified') -----
  morphAsPostscript: aMorph rotated: rotateFlag offsetBy: offset specs: specsOrNil
  
  
  	^[
  		(self new morphAsPostscript: aMorph rotated: rotateFlag offsetBy: offset) close
  	]
  		on: PickAFileToWriteNotification
  		do: [ :ex |
  			| newFileName stream |
  			newFileName := UIManager default
+ 				saveFilenameRequest: 'Name of file to write:' translated
- 				request: 'Name of file to write:' translated
  				initialAnswer: 'xxx',Time millisecondClockValue printString, self defaultExtension. 
  			newFileName isEmptyOrNil ifFalse: [
  				stream := FileStream fileNamed: newFileName.
  				stream ifNotNil: [ex resume: stream].
  			].
  		].
  
  !

Item was changed:
  ----- Method: EnvelopeEditorMorph>>saveLibToDisk: (in category 'menu') -----
+ saveLibToDisk: evt 
- saveLibToDisk: evt
  	"Save the library to disk"
+ 	| newName |
+ 	newName := UIManager default saveFilenameRequest: 'Please confirm name for library...' initialAnswer: 'MySounds.fml'.
+ 	newName ifNil: [^ self].
  
+ 	FileStream newFileNamed: newName
+ 		do: [:f | AbstractSound soundNames
+ 				do: [:name | | snd |
+ 					snd := AbstractSound soundNamed: name.
+ 					f nextChunkPut: 'AbstractSound soundNamed: ' , name , ' put: ' , snd storeString;
+ 						cr;
+ 						cr]]!
- 	| newName f |
- 	newName := UIManager default request: 'Please confirm name for library...'
- 						initialAnswer: 'MySounds'.
- 	newName isEmpty ifTrue: [^ self].
- 	f := FileStream newFileNamed: newName , '.fml'.
- 	AbstractSound soundNames do:
- 		[:name | | snd |
- 		snd := AbstractSound soundNamed: name.
- 		"snd isStorable" true ifTrue: [f nextChunkPut: 'AbstractSound soundNamed: ' , name , ' put: ' , snd storeString; cr; cr]
- 			ifFalse: [self inform: name , ' is not currently storable']].
- 	f close!

Item was changed:
  ----- Method: EnvelopeEditorMorph>>saveToDisk: (in category 'menu') -----
  saveToDisk: evt
+ 	| newName |
+ 	newName := UIManager default saveFilenameRequest: 'Please confirm name for save...'
+ 						initialAnswer: soundName, '.fmp'.
- 	| newName f |
- 	newName := UIManager default request: 'Please confirm name for save...'
- 						initialAnswer: soundName.
  	newName isEmpty ifTrue: [^ self].
+ 	FileStream newFileNamed: newName
+ 		do:[:f| sound storeOn: f]!
- 	f := FileStream newFileNamed: newName , '.fmp'.
- 	sound storeOn: f.
- 	f close!

Item was changed:
  ----- Method: EventRecorderMorph>>writeTape (in category 'fileIn/Out') -----
  writeTape
+ 	| args b fileName |
+ 	args := (b := self button: 'writeTape') isNil
- 	| args b |
- 	args := (b := self button: 'writeTape') isNil 
  				ifTrue: [#()]
  				ifFalse: [b arguments].
+ 	(args notEmpty
+ 			and: [args first notEmpty])
+ 		ifTrue: [args first.
- 	(args notEmpty and: [args first notEmpty]) 
- 		ifTrue: 
- 			[args first.
  			self writeTape: args first]
+ 		ifFalse: [fileName := UIManager default saveFilenameRequest: 'Tape to write' initialAnswer: 'tapeName.tape'.
+ 			fileName ifNil: [^ self].
+ 			^ self writeTape: fileName]!
- 		ifFalse: 
- 			[^self writeTape: (UIManager default request: 'Tape to write'
- 								initialAnswer: 'tapeName.tape')].!

Item was changed:
  ----- Method: GraphMorph>>readDataFromFile (in category 'sound') -----
  readDataFromFile
+ "This makes very little sense; it appears to be inteded as a general load data method but explicitly handles only AIFF files; very odd"
- 
  	| fileName |
  	fileName := UIManager default
+ 		chooseFileMatchingSuffixes: #('aif')
+ 		label: 'File name?' translated.
- 		request: 'File name?' translated
- 		initialAnswer: ''.
  	fileName isEmpty ifTrue: [^ self].
  	(StandardFileStream isAFileNamed: fileName) ifFalse: [
  		^ self inform: 'Sorry, I cannot find that file' translated].
  	self data: (SampledSound fromAIFFfileNamed: fileName) samples.
  
  !

Item was changed:
  ----- Method: Morph>>printPSToFileNamed: (in category '*MorphicExtras-menus') -----
  printPSToFileNamed: aString 
  	"Ask the user for a filename and print this morph as postscript."
  	| fileName rotateFlag psCanvasType psExtension |
+ 
- 	fileName := aString asFileName.
  	psCanvasType := PostscriptCanvas defaultCanvasType.
  	psExtension := psCanvasType defaultExtension.
+ 	fileName := UIManager default saveFilenameRequest: 'File name? '
+ 			initialAnswer: (aString, psExtension) asFileName.
+ 	fileName ifNil: [^ Beeper beep].
+ 
- 	fileName := UIManager default request: (String streamContents: [ :s |
- 		s nextPutAll: ('File name? ("{1}" will be added to end)' translated format: {psExtension})])
- 			initialAnswer: fileName.
- 	fileName isEmpty
- 		ifTrue: [^ Beeper beep].
- 	(fileName endsWith: psExtension)
- 		ifFalse: [fileName := fileName , psExtension].
  	rotateFlag := (UIManager default chooseFrom: {
  		'portrait (tall)' translated.
  		'landscape (wide)' translated.
  	} title: 'Choose orientation...' translated) = 2.
+ 	((FileStream newFileNamed: fileName) converter: TextConverter defaultSystemConverter)
- 	((FileStream newFileNamed: fileName asFileName) converter: TextConverter defaultSystemConverter)
  		nextPutAll: (psCanvasType morphAsPostscript: self rotated: rotateFlag);
  		 close!



More information about the Squeak-dev mailing list