[etoys-dev] Etoys: Sound-kfr.3.mcz

commits at source.squeak.org commits at source.squeak.org
Mon May 31 17:31:51 EDT 2010


Karl Ramberg uploaded a new version of Sound to project Etoys:
http://source.squeak.org/etoys/Sound-kfr.3.mcz

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

Name: Sound-kfr.3
Author: kfr
Time: 31 May 2010, 11:31:54 pm
UUID: 993ec98f-6ab6-7f4d-81aa-2759ae21de86
Ancestors: Sound-kfr.2

Added possibility to compress sounds in the SoundLibrary. Menu option to show compression format of sounds in  library.

=============== Diff against Sound-kfr.2 ===============

Item was changed:
  ----- Method: SoundLibraryTool>>handMeATile (in category 'menu') -----
  handMeATile 
+ 	| tile |
- 	| tile name |
  	soundIndex = 0 ifTrue:[^nil].
+ 	tile _ SoundTile new literal: self soundName.
- 	name _ (listBox getList at: soundIndex ).
- 	tile _ SoundTile new literal: name.
  		tile bounds: tile fullBounds.
  		tile openInHand!

Item was added:
+ ----- Method: SoundLibraryTool>>soundName (in category 'accessing') -----
+ soundName
+ 	^ (listBox getListRow: soundIndex) first!

Item was changed:
  ----- Method: SoundLibraryTool>>initialize (in category 'initialization') -----
  initialize
  	"initialize the state of the receiver"
  
  	super initialize.
+ 	showCompression _ false.
  	self hResizing: #shrinkWrap;
  		 vResizing: #shrinkWrap.
  	self cellPositioning: #topLeft.
  	self listDirection: #topToBottom.
  	self borderWidth: 2;
  		 borderColor: Color black.
  	self addHeaderRow.
  
  	self addButtonRow.
  	soundIndex := 1.
  	self addSoundList.
  	self soundIndex: 1.
  	self on: #mouseEnter send: #verifyContents to: listBox!

Item was changed:
  ----- Method: SoundLibraryTool>>renameSound (in category 'menu') -----
  renameSound
  	"Rename the selected sound, if appropriate."
  
  	| name newName |
+ 	name := self soundName.
  	soundIndex = 0
  		ifTrue: [^ self inform: 'No sound selected' translated].
- 	name := listBox getList at: soundIndex.
  	(SampledSound universalSoundKeys includes: name)
  		ifTrue: [^ self inform: 'You can not rename this sound' translated].
  
  	newName := FillInTheBlank request: 'New name for ' translated, name initialAnswer: name.
  	(newName isEmptyOrNil or: [newName = name]) ifTrue: [^ self].
  	(SampledSound soundLibrary includesKey: newName) ifTrue:
  		[^ self inform: 'sorry, that name is already used.' translated].
  	ScriptingSystem renameSound: name newName: newName.
  	listBox updateList.
  	self soundIndex: (listBox getList indexOf: newName)!

Item was added:
+ ----- Method: SoundLibraryTool>>toggleShowCompression (in category 'menu') -----
+ toggleShowCompression
+ 	showCompression _ showCompression not.
+ 	self listing.!

Item was added:
+ ----- Method: SoundLibraryTool>>showCompression (in category 'menu') -----
+ showCompression
+ 	^showCompression!

Item was changed:
  ----- Method: SoundLibraryTool>>soundIndex: (in category 'accessing') -----
  soundIndex: aInteger
+  	"Set the soundIndex to the given integer."
-  	"Set the sound index to the given integer."
  
+ 	| |
- 	| name |
  	soundIndex :=  aInteger.
  	soundIndex = 0
  		ifFalse:
+ 			[
+ 			currentSound :=  SampledSound soundNamed: self soundName]
- 			[name := (listBox getList at: soundIndex ).
- 			currentSound :=  SampledSound soundNamed: name]
  		ifTrue:
  			[currentSound := nil].
  	
          self changed: #soundIndex.!

Item was added:
+ ----- Method: SoundLibraryTool>>compressWith: (in category 'menu') -----
+ compressWith: aCodec 
+ 	"Compress the sound."
+ 	| newSound name writer |
+ 	soundIndex = 0
+ 		ifTrue: [^ self inform: 'No sound selected' translated].
+ 	
+ 	(SampledSound universalSoundKeys includes: self soundName)
+ 		ifTrue: [^ self inform: 'You can not compress this sound' translated].
+ 	newSound := currentSound compressWith: aCodec.
+ 	writer := ByteArray new writeStream.
+ 	newSound channels
+ 		do: [:channel | writer nextPutAll: channel].
+ 	name := self soundName.
+ 	SampledSound removeSoundNamed: self soundName.
+ 	SampledSound
+ 		addLibrarySoundNamed: name
+ 		bytes: writer contents
+ 		codecSignature: newSound codecSignature.
+ 	currentSound := SampledSound soundNamed: name!

Item was changed:
  ----- Method: SoundLibraryTool>>deleteSound (in category 'menu') -----
  deleteSound
  	"Delete the selected sound, if appropriate."
  
+ 	 
- 	| name |
  	soundIndex = 0
  		ifTrue: [^ self inform: 'No sound selected' translated].
+ 	currentSound pause.
+ 	(SampledSound universalSoundKeys includes: self soundName)
+ 		ifTrue: [^self inform: 'You can not delete this sound' translated]
+ 		ifFalse: [ScriptingSystem removeFromSoundLibrary: self soundName].
- 	name := listBox getList at: soundIndex.
- 	(SampledSound universalSoundKeys includes: name)
- 		ifTrue: [self inform: 'You can not delete this sound' translated]
- 		ifFalse: [ScriptingSystem removeFromSoundLibrary: name].
  	self soundIndex: 0.
  	listBox updateList!

Item was added:
+ ----- Method: SoundLibraryTool>>listing (in category 'initialization') -----
+ listing
+ 	| list newList format soundData selectorList formatList |
+ 	list := SampledSound soundLibrary keys asSortedArray.
+ 	selectorList := OrderedCollection new.
+ 	formatList _ OrderedCollection new.
+ 	list
+ 		do: [:each | 
+ 			soundData := (SampledSound soundLibrary at: each) second.
+ 			soundData isNumber
+ 				ifTrue: [format := 'uncompressed']
+ 				ifFalse: [(soundData includesSubString: 'Vorbis')
+ 						ifTrue: [format := 'Vorbis']
+ 						ifFalse: [(soundData includesSubString: 'Speex')
+ 								ifTrue: [format := 'Speex']
+ 								ifFalse: [(soundData includesSubString: 'GSM')
+ 										ifTrue: [format := 'GSM']]]].
+ 			selectorList add: each.
+ 			formatList add:  format].
+ 	 newList _ OrderedCollection new.
+ 	newList add: selectorList asArray.
+ 	showCompression
+ 		ifTrue:[newList add: formatList asArray]
+ 		ifFalse:[newList add:  (Array new: (formatList size) withAll:' ')].
+ 	^newList!

Item was changed:
  AlignmentMorph subclass: #SoundLibraryTool
+ 	instanceVariableNames: 'listBox button soundIndex currentSound showCompression'
- 	instanceVariableNames: 'listBox button soundIndex currentSound'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Sound-Interface'!
  
  !SoundLibraryTool commentStamp: 'sw 10/20/2007 01:54' prior: 0!
  A tool for browsing and managing the sound library.
  Offers a self-updating, scrolling list of all the sounds in the library.  
  Has a row of buttons to initiate various functions on the selected sound; the buttons are:
  	Play	Play the selected sound
  	Stop		Stop playing selected sound (if it is playing)
  	Tile		Hand the user a tile for the selected sound.
  	Rename	Rename the selected sound.
  	Delete	Delete the selected sound from the ibrary
  	Load	Load a sound into the sound library from a file.
  
  Additionally, a wave-editor can be invoked via an item in the tool's halo menu.
  
  The Sound Library tool can be launched from the Objects catalog, and also from the authoring-tools menu!

Item was changed:
  ----- Method: SoundLibraryTool>>addSoundList (in category 'initialization') -----
  addSoundList
  	"Add the sounds list to the tool."
  	
+ 	listBox _ PluggableMultiColumnListMorph
- 	listBox _ PluggableListMorph
  				on: self
+ 				list: #listing
- 				list: #soundList
  				selected: #soundIndex
  				changeSelected: #soundIndex:.
  	listBox hResizing: #spaceFill.
  	
  	listBox hideMenuButton.
  	listBox height: 240.
  	listBox font: Preferences standardEToysFont.
  	self  addMorphBack: listBox!

Item was changed:
  ----- Method: SoundLibraryTool>>addCustomMenuItems:hand: (in category 'menu') -----
  addCustomMenuItems: aMenu hand: aHand
  	"Add custom menu items to a menu"
  
  	super addCustomMenuItems: aMenu hand: aHand.
+ 	aMenu addUpdating: #showCompressionString target: self action: #toggleShowCompression.
+ 	aMenu add: 'GSM compress sound' translated target: self selector: #compressWith: argument: GSMCodec.
+ 	aMenu add: 'Ogg Vorbis compress sound' translated target: self selector: #compressWith: argument:  OggVorbisCodec.
+ 	aMenu add: 'Ogg Speex compress sound' translated target: self selector: #compressWith: argument:  OggSpeexCodec.
  	aMenu addTranslatedList: #(
+ 		('Wave editor' edit 'open a tool which, operating with the selected sound as a point of departure, will allow you to construct a new "instrument"')
+ 	) translatedNoop
+ !
- 		('wave editor' edit 'open a tool which, operating with the selected sound as a point of departure, will allow you to construct a new "instrument"')
- 	) translatedNoop!

Item was added:
+ ----- Method: SoundLibraryTool>>showCompressionString (in category 'menu') -----
+ showCompressionString
+ 	^ (self showCompression
+ 		ifTrue: ['<yes>']
+ 		ifFalse: ['<no>'])
+ 		, 'show compression' translated!



More information about the etoys-dev mailing list