[etoys-dev] Etoys Inbox: ScratchSoundEditor-kfr.5.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Apr 29 05:35:01 EDT 2014


A new version of ScratchSoundEditor was added to project Etoys Inbox:
http://source.squeak.org/etoysinbox/ScratchSoundEditor-kfr.5.mcz

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

Name: ScratchSoundEditor-kfr.5
Author: kfr
Time: 29 April 2014, 11:34:51 am
UUID: e11ccc4a-a059-c242-b6b5-f5d4ddb0fbee
Ancestors: ScratchSoundEditor-kfr.4

Work in progress on ScratchSoundEditor to enable basic sound editing in Etoys

==================== Snapshot ====================

SystemOrganization addCategory: #ScratchSoundEditor!

AlignmentMorph subclass: #ScratchSoundEditor
	instanceVariableNames: 'client soundName graph viewer selection startSelection playCursor cursor origSamplingRate samplingRate rateSlider slider volume snd completeSnd soundMorphSound copy time scrollDelta deltaVal fwdButton backButton undoSound undoSel undoCursor undoScale endPlaying'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ScratchSoundEditor'!

!ScratchSoundEditor commentStamp: 'tpr 12/6/2013 18:23' prior: 0!
A SCratchSoundEditor is an apparently unused class.

A sound editor, based on the wave editor.  It can be brought up by the SoundMorph.  When the soundEditor is brought up, it is created with a copy of the sound in the sound morph. It contains the sound of the soundmorph and is capable of editing that sound.  That sound is set in the method "sound:"

"viewing"
graph 					GraphMorph			
viewer					GraphMorph
selection 				    Array				an array of 2 #s that are the start and end of the selection.  This and the next 2 												variables are in terms of indices of the graph data
startSelection 			   Number				a number indicating the constant pt in a selection (mouse down loc)
cursor					   Number				a number indicating the location of the cursor

"Scrolling in view"
scrollDelta			        Number				a number telling us how much to scroll by, used in stepping to allow scrolling by 												buttons
slider					   slider morph			a slider for the graph
time					   a number			where we are in the graph in terms os msecs
deltaVal 					number				how much the cursor scrolls by, scrolldelta is set to +- this value
fwdButton 					button				scolling
backButton     				button				scrolling

"Playing variables" 
origSamplingRate 		  big number			indicates the sampling rate of the song @ loading
												so u can reset to that sampling rate.
samplingRate 	         another big number		indicates current sampling rate.	
(2 above aren't currently used)

volume					   slider morph			indicates volume, (0 to 1.0)		
preview						boolean 			whether we're in play all mode or play 	from 												cursor mode, where the cursor moves along with 												the music
"Sound manipulation"
snd 						SampledSound		Current sound used for playing from cursor + selection
completeSnd 				SampledSound		The entire song after editing (doesn't change with playing)
soundMorphSound   			SampledSound		a ref to the sound of the SoundMorph that created this, 
												so that u can change the sound within that sound editor

"Editing tools"
copy						SoundBuffer		the portion of the graph data that has been copied
undoSound 					SampledSound		the sound before any cuts/pastes crops
undoSel 					Array				a copy of the selection bf any cut/paste/crop


rateSlider 					currently not implemented
keyboard!

----- Method: ScratchSoundEditor class>>descriptionForPartsBin (in category 'icons') -----
descriptionForPartsBin
	^ self partName:	'SoundEditor' translatedNoop
		categories:		{'Multimedia' translatedNoop}
		documentation:	'A workbench for seing and editing wave forms' translatedNoop!

----- Method: ScratchSoundEditor class>>downArrow (in category 'icons') -----
downArrow

	^ Form
		extent: 10 at 12
		depth: 4
		fromArray: #(3722304989 3707764736 3722304989 3707764736 3704479196 3170893824 3692739489 3170893824 3550548241 1023410176 3720417563 3707764736 3711570339 3707764736 3722121645 3707764736 3722252605 3707764736 3722296285 3707764736 3722261469 3707764736 3722304989 3707764736)
		offset: 0 at 0
!

----- Method: ScratchSoundEditor class>>openOn: (in category 'instance creation') -----
openOn: dataCollection
	"Open a new WaveEditor on the given sequencable collection of data."

	^ (self new data: dataCollection) openInWorld
!

----- Method: ScratchSoundEditor class>>upArrow (in category 'icons') -----
upArrow
	"Uparrow form used in slider." 

	^ Form
		extent: 6 at 3
		fromArray: #(2r11e28 2r1111e27 2r111111e26)
		offset: 0 at 0
!

----- Method: ScratchSoundEditor>>addControls (in category 'initialization') -----
addControls

	| b r spacer |
	b := SimpleButtonMorph new target: self; borderColor: Color black; useSquareCorners.
	b borderColor: #raised; borderWidth: 3.
	r := AlignmentMorph newRow.
	r color: Color transparent; borderWidth: 0; layoutInset: 0.
	r hResizing: #spaceFill; vResizing: #shrinkWrap; extent: 5 at 5.
	r wrapCentering: #center.

	spacer := Morph new color: r color; extent: 40 at 5.  "spacer"
	r addMorphBack: (spacer fullCopy width: 5).
	r addMorphBack: self dismissButton.
	r addMorphBack: (spacer fullCopy width: 5).
	r addMorphBack: (b fullCopy label: 'undo';		actionSelector: #undo).
	r addMorphBack: (spacer fullCopy width: 5).
	r addMorphBack: (b fullCopy label: 'copy';		actionSelector: #copy).
	r addMorphBack: (spacer fullCopy width: 5).
	r addMorphBack: (b fullCopy label: 'paste';		actionSelector: #paste).
	r addMorphBack: (spacer fullCopy width: 5).
	r addMorphBack: (b fullCopy label: 'cut';		actionSelector: #cut).
	r addMorphBack: (spacer fullCopy width: 5).
	r addMorphBack: (b fullCopy label: 'crop';		actionSelector: #crop).	
	r addMorphBack: (spacer fullCopy width: 25).
	
	r addMorphBack: (b fullCopy label: 'save';			actionSelector: #saveToSoundLibrary).
	r addMorphBack: (spacer fullCopy width: 5).
	

	self addMorphBack: r.

!

----- Method: ScratchSoundEditor>>addGraph (in category 'initialization') -----
addGraph

	| r |
	r := AlignmentMorph newRow.
	r color: Color transparent; borderWidth: 0; layoutInset: 0.
	r hResizing: #shrinkWrap; vResizing: #shrinkWrap; extent: 5 at 5.
	r wrapCentering: #center.

	r addMorphBack: (AlignmentMorph newSpacer: r color).
	r addMorphBack: graph.
	r addMorphBack: (AlignmentMorph newSpacer: r color).
	self addMorphBack: r.
!

----- Method: ScratchSoundEditor>>addPlayButtons (in category 'initialization') -----
addPlayButtons

	| b r m space n scaleSelector |
	b := SimpleButtonMorph new target: self; borderColor: Color black; useSquareCorners.
	b borderColor: #raised; borderWidth: 3.
	r := AlignmentMorph newColumn.
	r color: Color transparent; borderWidth: 0; layoutInset: 0.
	r hResizing: #spaceFill; vResizing: #shrinkWrap; extent: 5 at 5.
	r wrapCentering: #center.

	m := AlignmentMorph newRow.
	m color: Color transparent; borderWidth: 0; layoutInset: 0.
	m hResizing: #shrinkWrap; vResizing: #shrinkWrap; extent: 5 at 5.
	m wrapCentering: #center.

	space := Morph new color: r color; extent: 3 at 5.

	n := StringMorph new contents: 'Zoom to: '.
	m addMorphBack: n.

	scaleSelector :=  (IconicButton new
		labelGraphic: self class downArrow;
		extent: 15 at 15;
		color: Color transparent;
		borderWidth: 0;
		target: graph;
		actWhen: #buttonDown;
		actionSelector: #setScale).
	m addMorphBack: scaleSelector.
	m addMorphBack: (Morph new color: r color; extent: 5 at 5).
	m addMorphBack: (b copy target: graph; label: '+';			actionSelector: #zoomIn).
	
	m addMorphBack: (b copy target: graph; label: '-';			actionSelector: #zoomOut).
	m addMorphBack: (b copy target: graph;
							label: 'zoom selection';	actionSelector: #viewSelection).

	m addMorphBack: (Morph new color: r color; extent: 5 at 5).
	"n := UpdatingStringMorph new
	target: graph;
	getSelector: #scale; 
	growable: false; width: 25; step.
	m addMorphBack: n."


	m addMorphBack: (Morph new color: r color; extent: 50 at 5).
	
	
	m addMorphBack: (b fullCopy label: 'Play All';			actionSelector: #playAll).
	m addMorphBack: space copy.
	m addMorphBack: (b fullCopy label: 'Play';				actionSelector: #playAfterCursor).
	m addMorphBack: space copy.
	m addMorphBack: (b fullCopy label: 'Stop';				actionSelector: #stopProcess).

	m addMorphBack: (Morph new color: r color; extent: 50 at 5).
	m addMorphBack: (StringMorph new contents: 'Volume').
	m addMorphBack: space copy.
	
	volume := SimpleSliderMorph new
	color: Color veryVeryLightGray;
	extent: 60 at 20;
	target: self;
	actionSelector: #setVolume:.

	m addMorphBack: volume.

	m addMorphBack: (Morph new color: r color; extent: 50 at 5).

	r addMorphBack: (Morph new color: r color; extent: 5 at 5).
	r addMorphBack: m.
	

	self addMorphBack: r.

!

----- Method: ScratchSoundEditor>>addRuler (in category 'initialization') -----
addRuler

	| ruler r |


	r := AlignmentMorph newRow.
	r color: Color transparent; borderWidth: 0; layoutInset: 0.
	r hResizing: #shrinkWrap; vResizing: #shrinkWrap; extent: 5 at 5.
	r wrapCentering: #center.

	r addMorphBack: (AlignmentMorph newSpacer: r color).
	ruler := ScratchRulerMorph graphMorph: self.
	self addMorphBack: ruler.
	"r addMorphBack: (AlignmentMorph newSpacer: r color).
	self addMorphBack: r."
	graph ruler: ruler

	
	!

----- Method: ScratchSoundEditor>>addSlider (in category 'initialization') -----
addSlider

	| r spacer m |
	r := AlignmentMorph newRow.
	r color: Color transparent; borderWidth: 0; layoutInset: 0.
	r hResizing: #spaceFill; vResizing: #shrinkWrap; extent: 5 at 5.
	r wrapCentering: #center.	
	
	spacer := Morph new color: r color; extent: (50)@5.
	backButton := self makeSliderButton: 10 at 13.
	backButton addMorphCentered: (ImageMorph new image: (self class upArrow rotateBy: #left centerAt: 0 at 0)).

	fwdButton := self makeSliderButton: 10 at 13.
	fwdButton addMorphCentered: (ImageMorph new image: (self class upArrow rotateBy: #right centerAt: 0 at 0)).
	
	slider := SimpleSliderMorph new
		color: Color veryVeryLightGray;
		extent: (graph width)@5;
		target: self;
		setMaxVal: (graph bounds width/(graph scale*graph data size));
		actionSelector: #scrollTime:.
	
	r addVariableTransparentSpacer.
	r addMorphBack:backButton.
	r addMorphBack: slider.
	r addMorphBack: fwdButton.
	r addVariableTransparentSpacer.
	m := Morph new color: r color; extent: 15 at 5.  "spacer"
	"r addMorphBack: m."
	time := UpdatingStringMorph new
		target: self;
		getSelector: #startTime; 
		width: 40; step.
	time useStringFormat.
	"r addMorphBack: time."

	self addMorphBack: r.
!

----- Method: ScratchSoundEditor>>addValueSelectors (in category 'initialization') -----
addValueSelectors

	| r m b |
	b := SimpleButtonMorph new target: self; borderColor: Color black; useSquareCorners.
	b borderColor: #raised; borderWidth: 3.
	r := AlignmentMorph newRow.
	r color: Color transparent; borderWidth: 0; layoutInset: 0.
	r hResizing: #spaceFill; vResizing: #shrinkWrap; extent: 5 at 5.
	r wrapCentering: #center.

	r addMorphBack: (Morph new color: r color; extent: 5 at 5).

	r addMorphBack: (b fullCopy label: '<slower';					actionSelector: #slower).
	r addMorphBack: (b fullCopy label: 'reset play rate';	actionSelector: #resetSamplingRate).
	r addMorphBack: (b fullCopy label: 'faster>';					actionSelector: #faster).

	r addMorphBack: (Morph new color: r color; extent: 25 at 5).
	m := StringMorph new contents: 'sampling rate'.
	r addMorphBack: m.
	m :=  Morph new color: r color; extent: 5 at 5. "spacer"
	r addMorphBack: m.

	rateSlider := SimpleSliderMorph new
	color: Color veryVeryLightGray;
	extent: 60 at 20;
	target: self;
	minVal: 0.2;
	maxVal: 2.5;
	actionSelector: #samplingRate:.
	r addMorphBack: rateSlider.
	r addMorphBack: (Morph new color: r color; extent: 30 at 5).

	m := StringMorph new contents: 'index: '.
	r addMorphBack: m.
	m := UpdatingStringMorph new
		target: graph; getSelector: #cursor; putSelector: #cursor:;
		growable:false; minimumWidth: 60; step.
	r addMorphBack: m.
	m fitContents.

	m :=  Morph new color: r color; extent: 20 at 5. "spacer"
	r addMorphBack: m.

	m := StringMorph new contents: 'sample value: '.
	r addMorphBack: m.
	m := UpdatingStringMorph new
		target: graph; getSelector: #valueAtCursor; putSelector: #valueAtCursor:;
		growable: false; minimumWidth: 60; step.
	r addMorphBack: m.
	m fitContents.

	m :=  Morph new color: r color; extent: 20 at 5. "spacer"
	r addMorphBack: m.

	

	self addMorphBack: r.

!

----- Method: ScratchSoundEditor>>addViewer (in category 'initialization') -----
addViewer

	| r |

	r := AlignmentMorph newRow.
	r color: Color transparent; borderWidth: 0; layoutInset: 0.
	r hResizing: #shrinkWrap; vResizing: #shrinkWrap; extent: 5 at 5.
	r wrapCentering: #center.

	r addMorphBack: (AlignmentMorph newSpacer: r color).
	r addMorphBack: viewer.
	r addMorphBack: (AlignmentMorph newSpacer: r color).

	self addMorphBack: r.
	
!

----- Method: ScratchSoundEditor>>back (in category 'graph ops') -----
back
	"Moves the cursor back in the music score."

	scrollDelta := -5.  
	self cursor: cursor + scrollDelta.!

----- Method: ScratchSoundEditor>>cancel (in category 'graph ops') -----
cancel

	self delete.
!

----- Method: ScratchSoundEditor>>client: (in category 'accessing') -----
client: anObject

	client := anObject.
!

----- Method: ScratchSoundEditor>>copy (in category 'graph ops') -----
copy

	"copies the current selection if there is one."
	(selection at: 1) ifNotNil:
		[copy := graph data copyFrom: (graph selection at: 1) to: (graph selection at: 2).]!

----- Method: ScratchSoundEditor>>crop (in category 'graph ops') -----
crop
	
	| sel |

	"Crops the sound in the sound editor to be only the selected region"

	sel := ((selection at: 1) notNil and: [(selection at: 2) - (selection at: 1) > 3]).
	sel ifFalse: [^self].

	undoSel := graph selection copy.
	undoSound := SampledSound samples: graph data samplingRate: samplingRate.
	undoCursor := cursor.
	undoScale := graph scale/ScratchGraphMorph MinScale.

	sel := graph data copyFrom: (selection at: 1) to: (selection at: 2).
	graph data: sel.
	viewer data: graph data.
	cursor := ((cursor - (selection at: 1)) truncated max: 1) min: graph data size truncated.

	"scales the botton viewer so that the data fits on the entire screen." 
	(selection second - selection first)/graph data size >= 0.05
		ifTrue: [ScratchGraphMorph MinScale: (viewer extent x/ graph data size min: 1). "the mult factor in all scales, the minimum scale allowed...to get this just do self scale: 1, since this multiplied by input"
				viewer scale: 1.
				graph scale: 1.
				viewer startIndex: 1.
				graph computeSlider.
				self fixSliderRange.].

	graph calculateDataArray.
	viewer calculateDataArray.

	snd setSamples: sel samplingRate: samplingRate.
	completeSnd setSamples: sel samplingRate: samplingRate.

	selection at: 1 put: 1.
	selection at: 2 put: graph data size.
!

----- Method: ScratchSoundEditor>>cursor (in category 'accessing') -----
cursor

	^cursor.!

----- Method: ScratchSoundEditor>>cursor: (in category 'accessing') -----
cursor: aNumber

	graph data ifNil: [^self].

	cursor ~= aNumber ifTrue:  [
	cursor := ((aNumber truncated max: 1) min: graph data size) truncated.
	"graph keepIndexInView: cursor."
	].!

----- Method: ScratchSoundEditor>>cut (in category 'graph ops') -----
cut 

	| data1 data2 |
	(selection at: 1) ifNil: [^ self.].

	undoSound := SampledSound samples: graph data samplingRate: samplingRate.
	undoSel := graph selection copy.
	undoCursor := cursor.
	undoScale := graph scale/ScratchGraphMorph MinScale.

	self copy.
	data1 := graph data copyFrom: 1 to: (selection at: 1).
	data2 := graph data copyFrom: (selection at: 2) to: graph data size.
	
	graph data: (data1, data2).
	viewer data: graph data.
		
	"scales the botton viewer so that the data fits on the entire screen." 
	((selection second - selection first)/graph data size asFloat) >= 0.05
		ifTrue: [ScratchGraphMorph MinScale: (viewer extent x/ graph data size min: 1).
				viewer scale: 1.
				graph scale: undoScale.
				viewer startIndex: 1.
				graph computeSlider.
				self fixSliderRange.].

	graph calculateDataArray.
	viewer calculateDataArray.

	snd setSamples: graph data samplingRate: samplingRate.
	completeSnd setSamples: graph data samplingRate: samplingRate.
	cursor := (selection at: 1).
	
	selection at: 1 put: nil. 
	selection at: 2 put: nil.!

----- Method: ScratchSoundEditor>>data: (in category 'accessing') -----
data: newData

	graph data: newData.
!

----- Method: ScratchSoundEditor>>endPlaying (in category 'accessing') -----
endPlaying

	^endPlaying.!

----- Method: ScratchSoundEditor>>faster (in category 'menu') -----
faster

	| rate |
	rate := rateSlider getScaledValue*1.1.
	rateSlider setScaledValue: rate.
	self samplingRate: rate.

	!

----- Method: ScratchSoundEditor>>fixSliderRange (in category 'graph ops') -----
fixSliderRange

	slider maxVal: (1 -(slider sliderThickness/slider extent x)).
	^slider!

----- Method: ScratchSoundEditor>>fwd (in category 'graph ops') -----
fwd
	
	"moves the cursor forward in the music."
	scrollDelta := 5.
	self cursor: cursor + 5.!

----- Method: ScratchSoundEditor>>graph (in category 'accessing') -----
graph

	^ graph
!

----- Method: ScratchSoundEditor>>handlesMouseDown: (in category 'event handling') -----
handlesMouseDown: evt

	| p |
	p := evt cursorPoint.
	^ (Rectangle origin: backButton topLeft corner: fwdButton bottomRight) containsPoint: p.!

----- Method: ScratchSoundEditor>>handlesMouseOver: (in category 'event handling') -----
handlesMouseOver: evt

	^true.!

----- Method: ScratchSoundEditor>>initialize (in category 'initialization') -----
initialize

	super initialize.
	copy := nil.
	selection := {nil. nil}.
	scrollDelta := 0.
	deltaVal := 10.
	cursor := 200.
	playCursor := nil.
	samplingRate := SoundPlayer samplingRate.
	soundName := 'sound'.
	self extent: 5 at 5;
		listDirection: #topToBottom;
		wrapCentering: #centered;
		hResizing: #shrinkWrap;
		vResizing: #shrinkWrap;
		layoutInset: 3;
		color: Color lightGray;
		borderWidth: 2.
	graph := ScratchGraphMorph new extent: 380 at 150.
	graph editor: self.
	graph selection: selection.
	graph viewer: false.

	viewer := ScratchGraphMorph new extent: 380 at 30.
	viewer editor: self.
	viewer cursorColorAtZeroCrossings: Color red.
	viewer viewer: true.
	viewer selection: selection.

	self addControls.
	self addPlayButtons.
	self addValueSelectors.
	self addMorphBack: (Morph new color: self color; extent: 10 at 5).

	self addGraph.
	self addMorphBack: (Morph newBounds: (0 at 0 extent: 0 at 3) color: Color transparent).
	self addSlider.

	self addViewer.
	viewer left: backButton right.
!

----- Method: ScratchSoundEditor>>invokeMenu (in category 'menu') -----
invokeMenu
	"Invoke a menu of additonal functions."

	| aMenu |
	aMenu := CustomMenu new.
	aMenu addList:	#(
		('save to file'		saveToFile)
		('read from file'	readFromFile)).
	aMenu invokeOn: self defaultSelection: nil.

!

----- Method: ScratchSoundEditor>>keyStroke: (in category 'event handling') -----
keyStroke: evt

	| keyVal |
	keyVal := evt keyCharacter asciiValue.

	keyVal = 28 ifTrue: [ cursor := cursor + (( -10) / graph scale)].
	keyVal = 29 ifTrue: [ cursor := cursor + (10/graph scale)].!

----- Method: ScratchSoundEditor>>makeSliderButton: (in category 'initialization') -----
makeSliderButton: buttonExtent

	| button |
	button := BorderedMorph
		newBounds: (self innerBounds bottomRight - buttonExtent extent: buttonExtent)
		color: Color lightGray.

	button setBorderWidth: 1 borderColor: #raised.
	^ button
!

----- Method: ScratchSoundEditor>>mouseDown: (in category 'event handling') -----
mouseDown: evt

	| p |
	"do stuff"
	p := evt cursorPoint.
	

	(slider containsPoint: p) ifTrue: [ 
		slider descending ifTrue: [scrollDelta := deltaVal negated.]
						  ifFalse: [scrollDelta := deltaVal.].].
	(backButton containsPoint: p) ifTrue: [ backButton borderInset. scrollDelta := deltaVal negated ].
	(fwdButton containsPoint: p) ifTrue: [ fwdButton borderInset. scrollDelta := deltaVal].!

----- Method: ScratchSoundEditor>>mouseEnter: (in category 'event handling') -----
mouseEnter: evt

	evt hand newKeyboardFocus: self.!

----- Method: ScratchSoundEditor>>mouseUp: (in category 'event handling') -----
mouseUp: evt

	"do stuff"
	scrollDelta := 0.
	fwdButton borderRaised.
	backButton borderRaised.
!

----- Method: ScratchSoundEditor>>normalize: (in category 'other') -----
normalize: sampleArray
	"Return a copy of the given sample array scaled to use the maximum 16-bit sample range. Remove any D.C. offset."

	| max abs scale out |
	max := 0.
	sampleArray do: [:s |
		s > 0 ifTrue: [abs := s] ifFalse: [abs := 0 - s].
		abs > max ifTrue: [max := abs]].
	scale := ((1 << 15) - 1) asFloat / max.

	out := sampleArray species new: sampleArray size.
	1 to: sampleArray size do: [:i |
		out at: i put: (scale * (sampleArray at: i)) truncated].
	^ out
!

----- Method: ScratchSoundEditor>>origSamplingRate (in category 'menu') -----
origSamplingRate

	^origSamplingRate.
!

----- Method: ScratchSoundEditor>>paste (in category 'graph ops') -----
paste
	| data1 data2 |
	"inserts the copied data into the dataset where the cursor is."
	
	copy ifNil: [^self ].
	
	"self selectionNil ifTrue: [undoSel := nil.] ifFalse: [undoSel := selection copy.]."
	undoSel := selection copy.
	undoSound := SampledSound samples: graph data samplingRate: samplingRate.
	undoCursor := cursor.
	undoScale := graph scale/ScratchGraphMorph MinScale.


	((self selectionNil not) and: [(selection at: 2) - (selection at: 1) > 3])
		ifTrue: [data1 := graph data copyFrom: 1 to: (graph selection at: 1).
			     data2 := graph data copyFrom: (graph selection at: 2) to: graph data size.]
		ifFalse: [data1 := graph data copyFrom: 1 to: graph cursor truncated.
				 data2 := graph data copyFrom: graph cursor truncated + 1 to: graph data size.].
	
	graph data: (data1, copy, data2).
	viewer data: graph data.

	"scales the botton viewer so that the data fits on the entire screen." 
	(copy size)/graph data size >= 0.05
		ifTrue: [ScratchGraphMorph MinScale: (viewer extent x/ graph data size min: 1).
				viewer scale: 1.
				graph scale: undoScale.
				self fixSliderRange.
				viewer startIndex: 1.
				graph computeSlider.].

	

	graph calculateDataArray.
	viewer calculateDataArray.

	snd setSamples: graph data samplingRate: samplingRate.
	completeSnd setSamples: graph data samplingRate: samplingRate.

	self selection: {data1 size. (data1 size) + (copy size).}.
	cursor := selection at: 2.
	graph startIndex: (slider getScaledValue)*(graph data size).

	viewer flushCachedForm.
		!

----- Method: ScratchSoundEditor>>pause (in category 'menu') -----
pause

	(snd notNil and: [snd isPlaying])
		ifTrue: [snd pause.].
!

----- Method: ScratchSoundEditor>>playAfterCursor (in category 'initialization') -----
playAfterCursor

	| sel currSel |
	graph data size < 2 ifTrue: [^ self].
	

	sel := ((selection at: 1) notNil and: [(selection at: 2) - (selection at: 1) > 3]).
	sel ifTrue: [currSel := graph data copyFrom: (selection at: 1) asInteger to: (selection at: 2) asInteger. playCursor := selection at: 1.
			    endPlaying := selection at: 2.]
	    ifFalse: [currSel := graph data copyFrom: (cursor max: 1) asInteger to: graph data size.
				playCursor := cursor.
				endPlaying := graph data size].
	
		self changed.


	snd isNil
		ifTrue: [
				 snd := (SampledSound samples: currSel samplingRate: samplingRate).
				 snd play.]
		ifFalse: [
			currSel = snd samples
				ifTrue: [snd samplesRemaining = 0 ifTrue: [snd reset].
						 snd resumePlaying.]
				ifFalse: [ snd setSamples: currSel samplingRate: samplingRate.
						 snd play]].

!

----- Method: ScratchSoundEditor>>playAll (in category 'menu') -----
playAll

	"Resumes playing the selection if there is one, otherwise resumes playing the entire soundtrack."

	graph data size < 2 ifTrue: [^ self].
	playCursor := 1.
	endPlaying := graph data size.

	snd isNil
		ifTrue: [
				 snd := (SampledSound samples: graph data samplingRate: samplingRate).
				 snd play.]
		ifFalse: [
			snd reset.
			(graph data = snd samples)
				ifTrue: [snd samplesRemaining = 0 ifTrue: [snd reset].
						 snd resumePlaying.]
				ifFalse: [snd setSamples: graph data samplingRate: origSamplingRate.
						 snd play]]
!

----- Method: ScratchSoundEditor>>playCursor (in category 'accessing') -----
playCursor
	
	^playCursor.!

----- Method: ScratchSoundEditor>>playCursor: (in category 'accessing') -----
playCursor: aNumber

	graph data ifNil: [^self].

	"allows the graph to set where the playing cursor is"

	cursor ~= aNumber ifTrue:  [
	cursor := ((aNumber truncated max: 1) min: graph data size) truncated.
	].!

----- Method: ScratchSoundEditor>>playFrom:to: (in category 'menu') -----
playFrom: start to: end

	| sz i1 i2 snd2 |
	sz := graph data size.
	i1 := ((start + 1) min: sz) max: 1.
	i2 := ((end + 1) min: sz) max: i1.
	(i1 + 2) >= i2 ifTrue: [^ self].
	snd2 := SampledSound
		samples: (graph data copyFrom: i1 to: i2)
		samplingRate: samplingRate.
	snd2 play.
!

----- Method: ScratchSoundEditor>>readFromFile (in category 'menu') -----
readFromFile
	"Read my samples from a file selected by the user."

	| result |
	result := StandardFileMenu oldFileExtensions: #(aif aiff au wav).
	result ifNil: [^ self].
	self readFromFile: result directory pathName, FileDirectory slash, result name.
!

----- Method: ScratchSoundEditor>>readFromFile: (in category 'menu') -----
readFromFile: fName
	"Read my samples from the file with the given name."

	(FileDirectory default fileExists: fName)
		ifFalse: [^ self inform: 'File not found' withDetails: fName].
	snd := SampledSound fromFileNamed: fName.

	completeSnd := snd copy.
	graph cursor: 200.
	samplingRate := snd originalSamplingRate.
	origSamplingRate := snd originalSamplingRate.
	graph data: snd samples.
	graph scale: 2.0.

	self setVolume: 0.5.
	volume setScaledValue: 0.5.
	
	graph data size > 5000
		ifTrue: [deltaVal := 50]
		ifFalse: [deltaVal := graph data size // 10].

!

----- Method: ScratchSoundEditor>>resetSamplingRate (in category 'menu') -----
resetSamplingRate

	snd ifNil: [^self].

	snd setSamples: snd samples samplingRate: origSamplingRate.
	rateSlider setScaledValue: 1.0.!

----- Method: ScratchSoundEditor>>samplingRate (in category 'accessing') -----
samplingRate

	^ samplingRate

!

----- Method: ScratchSoundEditor>>samplingRate: (in category 'menu') -----
samplingRate: sampleRate

"Sets the samplingRate to somewhere btw 0.1 and 2.5 the original samplingRate, given a number btw 0.2 and 2.5 (sampleRate)"

	snd ifNil: [^self.].

	origSamplingRate = 0 
		ifFalse: [snd setSamples: snd samples samplingRate: (sampleRate*origSamplingRate)]
		ifTrue: [ snd setSamples: snd samples samplingRate: (sampleRate*10000)].

	
!

----- Method: ScratchSoundEditor>>save (in category 'graph ops') -----
save

	snd := SampledSound samples: completeSnd samples samplingRate: samplingRate.
	client ifNotNil: [client saveSound: snd name: soundName].
	self delete.
!

----- Method: ScratchSoundEditor>>saveToFile (in category 'menu') -----
saveToFile
	"Export my samples to a WAV file."

	| fileName samples f |
	fileName := StringDialog ask: 'File name?'.
	fileName size = 0 ifTrue: [^ self].
	(fileName asLowercase endsWith: '.wav') ifFalse: [fileName := fileName, '.wav'].
	(graph data isKindOf: SoundBuffer)
		ifTrue: [samples := graph data]
		ifFalse: [samples := SoundBuffer fromArray: graph data].
	f := (FileStream newFileNamed: fileName) binary.
	(SampledSound samples: samples samplingRate: samplingRate) storeWAVSamplesOn: f.
	f close.
!

----- Method: ScratchSoundEditor>>saveToSoundLibrary (in category 'menu') -----
saveToSoundLibrary
	"The user hit the 'save' button."

	| sndName |
	
	self pause.

	sndName _ FillInTheBlank
				request: 'Sound name?' translated
				initialAnswer: 'unnamed' translated .
			sndName isEmpty ifTrue: [^ self].
			
	sndName := SampledSound unusedSoundNameLike: sndName.
	SampledSound
			addLibrarySoundNamed: sndName
			samples:  snd samples
			samplingRate:  samplingRate.
	

	!

----- Method: ScratchSoundEditor>>scrollTime: (in category 'accessing') -----
scrollTime: relativeValue

	graph startIndex: relativeValue*(graph data size).

	viewer flushCachedForm; changed.




!

----- Method: ScratchSoundEditor>>selection (in category 'accessing') -----
selection

	^selection.!

----- Method: ScratchSoundEditor>>selection: (in category 'accessing') -----
selection: anArrayorNil

	anArrayorNil ifNil: [selection := {nil. nil}.]
			 ifNotNil: [selection := anArrayorNil.].
	graph selection: selection.
	viewer selection: selection!

----- Method: ScratchSoundEditor>>selection:scd: (in category 'accessing') -----
selection: aNumber scd: anotherNumber

	selection := { aNumber min: anotherNumber. aNumber max: anotherNumber}.
	graph selection: selection.
	viewer selection: selection.
	graph flushCachedForm; changed.
	viewer flushCachedForm; changed.!

----- Method: ScratchSoundEditor>>selectionNil (in category 'accessing') -----
selectionNil
	
	(selection at: 1) ifNil: [^ true].
	
	^false.!

----- Method: ScratchSoundEditor>>setVolume: (in category 'menu') -----
setVolume: aFloat

	"aFloat is a value btw 0 and 1.0"
	
	snd ifNil: [^self].
	snd adjustVolumeTo: aFloat overMSecs: 50.!

----- Method: ScratchSoundEditor>>slider (in category 'accessing') -----
slider 
	^slider.!

----- Method: ScratchSoundEditor>>slower (in category 'menu') -----
slower

	| rate |
	rate := rateSlider getScaledValue/1.1.
	rateSlider setScaledValue: rate.
	self samplingRate: rate.

	!

----- Method: ScratchSoundEditor>>sound (in category 'accessing') -----
sound

	^snd.!

----- Method: ScratchSoundEditor>>sound: (in category 'graph ops') -----
sound: aSampledSound

	"completeSnd is a version of the sound that is unaffected by the play mechanism.  This method is called when a SoundMorph brings up a SoundEditor. soundMorphSound is a copy of the initial sampledSound, used for saving and cancelling edits purposes.  It serves as a reference to the original sound so that we can actually change the sound in the soundMorph"

	soundMorphSound := aSampledSound.
	snd := aSampledSound copy.
	completeSnd := snd copy.
	graph cursor: 200.
	samplingRate := snd originalSamplingRate.
	origSamplingRate := snd originalSamplingRate.

	ScratchGraphMorph MinScale: (graph extent x/completeSnd samples size).

	graph data: completeSnd samples.  "SHOULD IT BE COPY?/"
	graph scale: 2.
	graph calculateDataArray.
	"self fixSliderRange.
	graph computeSlider."
	
	viewer data: completeSnd samples.
	viewer scale: 1.
	viewer calculateDataArray.
	self setVolume: snd loudness.
	volume setScaledValue: snd loudness.
	
	(graph data size > 5000)
		ifTrue: [deltaVal := 200]
		ifFalse: [deltaVal := (graph data size) // 10].

	self updateSlider!

----- Method: ScratchSoundEditor>>soundName: (in category 'accessing') -----
soundName: aString
	"Note the sound name to use when saving."

	soundName := aString.
!

----- Method: ScratchSoundEditor>>startSelection (in category 'accessing') -----
startSelection
		
	^ startSelection.!

----- Method: ScratchSoundEditor>>startSelection: (in category 'accessing') -----
startSelection: aNumber


	startSelection := aNumber.!

----- Method: ScratchSoundEditor>>startTime (in category 'graph ops') -----
startTime
	
	| ss |
	"secs := cursor / samplingRate.
	hrs := secs // 3600.
	mins := (secs \\ 3600) // 60.
	secs := secs \\ 60 asFloat.
	ms := ((secs \\ 1) * 100) asFloat truncated.
	secs := secs // 1."

	" hrs asString,':',mins asString, ':', secs asString, '.', ms asString."
	
	origSamplingRate isNil
		ifTrue: [ss := 20000]
		ifFalse: [ss := origSamplingRate].
	^ ((cursor asFloat/ss) roundTo: 0.01) asString.!

----- Method: ScratchSoundEditor>>startTime: (in category 'graph ops') -----
startTime: hrMinSecs
	
	| secs hrs mins hms |
	hms := hrMinSecs findTokens: ' :.'.
	hrs := hms at: 1.
	mins := hms at: 2.
	secs := hms at: 3.
	self startIndex: ((hrs asNumber * 3600) + (mins asNumber * 60) + secs asNumber) * samplingRate.
!

----- Method: ScratchSoundEditor>>step (in category 'stepping') -----
step

	| played prev |
	(SoundPlayer isPlaying: snd) ifTrue: [
		played := ((snd millisecondsSinceStart) * snd samples size) / (1000.0 * snd duration).
		prev := (completeSnd samples size - snd samples size).
		playCursor := (played + prev truncated min: graph data size).
		self changed].

	time contents: self startTime.

	scrollDelta = 0 ifFalse: [
		graph startIndex: graph startIndex + (scrollDelta/graph scale).
		self updateSliderValue.].

	graph computeSlider.
	self fixSliderRange.
!

----- Method: ScratchSoundEditor>>stepTime (in category 'stepping') -----
stepTime


	^ 150
!

----- Method: ScratchSoundEditor>>stopProcess (in category 'menu') -----
stopProcess
"replaces #stop since that is now commonly used in Morph and confuses Scratch."
	snd pause.
	playCursor := nil.
	!

----- Method: ScratchSoundEditor>>stretch:by: (in category 'other') -----
stretch: sampleArray by: stretchFactor
	"Return an array consisting of the given samples \stretched in time by the given factor."

	| out end incr i frac index |
	out := OrderedCollection new: (stretchFactor * sampleArray size) asInteger + 1.
	end := (sampleArray size - 1) asFloat.
	incr := 1.0 / stretchFactor.
	i := 1.0.
	[i < end] whileTrue: [
		frac := i fractionPart.
		index := i truncated.
		i := i + incr.
		out addLast:
			(((1.0 - frac) * (sampleArray at: index)) + (frac * (sampleArray at: index + 1))) rounded].
	^ out asArray
!

----- Method: ScratchSoundEditor>>undo (in category 'graph ops') -----
undo


	| tmpSound tmpSel tmpCursor tmpScale |

	undoSound ifNil: [^self].

	tmpSound := SampledSound samples: graph data samplingRate: samplingRate.
	tmpSel := graph selection copy.
	tmpCursor := cursor.
	tmpScale := graph scale/ScratchGraphMorph MinScale.

	graph data: undoSound samples copy.
	viewer data: graph data.
	
	"scales the botton viewer so that the data fits on the entire screen." 
	(tmpSound samples size - graph data size) abs > 3
		ifTrue: [ScratchGraphMorph MinScale: ((viewer extent x/ graph data size) min: 1).
				viewer scale: 1.
				graph scale: undoScale.
				viewer startIndex: 1.
				graph computeSlider.
				self fixSliderRange.].

	graph calculateDataArray.
	viewer calculateDataArray.

	snd setSamples: graph data samplingRate: samplingRate.
	completeSnd setSamples: graph data samplingRate: samplingRate.
	self selection: undoSel copy.
	cursor := undoCursor.

	undoSound := tmpSound.
	undoSel := tmpSel.
	undoCursor := tmpCursor.
	undoScale := tmpScale.
!

----- Method: ScratchSoundEditor>>updateSlider (in category 'other') -----
updateSlider

	"this is the order that these methods have to be called in order to update slider!!!!!!"
	graph computeSlider.  
	self fixSliderRange.
	self updateSliderValue.!

----- Method: ScratchSoundEditor>>updateSliderValue (in category 'accessing') -----
updateSliderValue

	slider setScaledValue: ((graph startIndex/graph data size min: slider maxVal) max: 0).




!

----- Method: ScratchSoundEditor>>viewer (in category 'accessing') -----
viewer

	^viewer.!

----- Method: SoundLibraryTool>>edit (in category '*ScratchSoundEditor') -----
edit
	"Open a WaveEditor on my samples."
soundIndex > 0
		ifTrue: [(ScratchSoundEditor new sound: currentSound) openInWorld"samples."]
!

----- Method: SoundLibraryTool>>openRecorder (in category '*ScratchSoundEditor') -----
openRecorder
	RecordingControls new openInWorld!

RectangleMorph subclass: #ScratchGraphMorph
	instanceVariableNames: 'data dataColor playCursorColor playing cursorColor cursorColorAtZeroCrossings startIndex minVal maxVal selection scale cachedForm hasChanged ruler viewer trueCalls falseCalls negVals posVals editor minScale'
	classVariableNames: 'MinScale'
	poolDictionaries: ''
	category: 'ScratchSoundEditor'!

!ScratchGraphMorph commentStamp: 'tpr 12/6/2013 18:23' prior: 0!
A SCratchGraphMorph is an apparently unused class.

I display a graph of numbers, normalized so the full range of values just fits my height. I support a movable cursor that can be dragged with the mouse.

Implementation notes: Some operations on me may be done at sound sampling rates (e.g. 11-44 thousand times/second). To allow such high bandwidth application, certain operations that change my appearance do not immediately report a damage rectangle. Instead, a flag is set indicating that my display needs to refreshed and a step method reports the damage rectangle if that flag is set. Also, I cache a bitmap of my graph to allow the cursor to be moved without redrawing the graph.

All indices, like startIndex, cursor, etc are in terms of the graph data.

IMPORTANT!!  The current implementation cannot stand alone, it needs to be a submorph of SoundEditor.
!

----- Method: ScratchGraphMorph class>>MinScale (in category 'instance creation') -----
MinScale

	^MinScale!

----- Method: ScratchGraphMorph class>>MinScale: (in category 'instance creation') -----
MinScale: aNumber

	"aNumber should be equal to: viewer extent x/ graph data size"
	MinScale := aNumber asFloat.
!

----- Method: ScratchGraphMorph class>>openOn: (in category 'instance creation') -----
openOn: dataCollection
	"Open a new GraphMorph on the given sequencable collection of data."

	^ (self new data: dataCollection) openInWorld
!

----- Method: ScratchGraphMorph>>addCustomMenuItems:hand: (in category 'menu') -----
addCustomMenuItems: aCustomMenu hand: aHandMorph

	super addCustomMenuItems: aCustomMenu hand: aHandMorph.
	aCustomMenu add: 'open wave editor' action: #openWaveEditor.
	aCustomMenu add: 'read file' action: #readDataFromFile.
!

----- Method: ScratchGraphMorph>>adjustSelection (in category 'menu') -----
adjustSelection
	"Adjust the selection, if any, to the current cursor position. Do nothing if there is no selection."

	editor selectionNil ifTrue: [^ self].
	editor selection: editor cursor scd: editor startSelection.

!

----- Method: ScratchGraphMorph>>appendValue: (in category 'commands') -----
appendValue: aPointOrNumber

	| newVal |
	(data isKindOf: OrderedCollection) ifFalse: [data := data asOrderedCollection].
	newVal := self asNumber: aPointOrNumber.
	data addLast: newVal.
	newVal < minVal ifTrue: [minVal := newVal].
	newVal > maxVal ifTrue: [maxVal := newVal].
	self cursor: data size.
	self flushCachedForm.
!

----- Method: ScratchGraphMorph>>calculateDataArray (in category 'private') -----
calculateDataArray

	| currIndex neg pos |

	negVals := OrderedCollection new.
	posVals := OrderedCollection new.

	data isEmpty ifTrue: [^ self].
	currIndex :=  neg := pos := 0.

	(1 to: data size) do: [ :i |
		((i * scale) truncated > currIndex)
			ifTrue: [
			
					currIndex := (i*scale) truncated.		
					neg := neg min: (data at: i).
					pos := pos max: (data at: i).
			
					posVals add: pos.
					negVals	add: neg.
		
					pos := neg := 0.]
			ifFalse: [
						neg := neg min: (data at: i).
						pos := pos max: (data at: i).].].!

----- Method: ScratchGraphMorph>>centerCursor (in category 'commands') -----
centerCursor
	"Scroll so that the cursor is as close as possible to the center of my window."

	| w |

	w := self width - (2 * borderWidth).
	self startIndex: ((editor cursor - (w // (scale*2))) max: 1).
!

----- Method: ScratchGraphMorph>>clear (in category 'commands') -----
clear

	self startIndex: 1.
	self cursor: 1.
	self data: OrderedCollection new.
!

----- Method: ScratchGraphMorph>>color: (in category 'accessing') -----
color: aColor

	super color: aColor.
	self flushCachedForm.
!

----- Method: ScratchGraphMorph>>computeSlider (in category 'viewing') -----
computeSlider
	
	editor slider sliderThickness: 10" ((bounds width//scale)/data size)*(editor slider extent x)".
	editor slider changed.!

----- Method: ScratchGraphMorph>>cursor (in category 'accessing') -----
cursor

	^ editor cursor
!

----- Method: ScratchGraphMorph>>cursor: (in category 'accessing') -----
cursor: aNumber


	editor cursor: aNumber.
!

----- Method: ScratchGraphMorph>>cursorAtEnd (in category 'accessing') -----
cursorAtEnd

	^editor cursor truncated >= data size
!

----- Method: ScratchGraphMorph>>cursorColor (in category 'accessing') -----
cursorColor

	^ cursorColor
!

----- Method: ScratchGraphMorph>>cursorColor: (in category 'accessing') -----
cursorColor: aColor

	cursorColor := aColor.
	self flushCachedForm.
!

----- Method: ScratchGraphMorph>>cursorColorAtZeroCrossing (in category 'accessing') -----
cursorColorAtZeroCrossing

	^ cursorColorAtZeroCrossings
!

----- Method: ScratchGraphMorph>>cursorColorAtZeroCrossings: (in category 'accessing') -----
cursorColorAtZeroCrossings: aColor

	cursorColorAtZeroCrossings := aColor.
	self flushCachedForm.
!

----- Method: ScratchGraphMorph>>cursorWrapped: (in category 'accessing') -----
cursorWrapped: aNumber

	| sz |
	editor cursor ~= aNumber ifTrue: [
		editor cursor: aNumber.
		sz := data size.
		sz = 0
			ifTrue: [editor cursor: 1]
			ifFalse: [
				((editor cursor >= (sz + 1)) or: [editor cursor < 0]) ifTrue: [
					 editor cursor: editor cursor - ((editor cursor // sz) * sz)].
				editor cursor < 1 ifTrue: [editor cursor: sz + editor cursor]].
		"assert: 1 <= cursor < data size + 1"
		hasChanged := true].
!

----- Method: ScratchGraphMorph>>customScale (in category 'accessing') -----
customScale
	"Called when the user wants to input a scale value."

	| answer |
	answer := FillInTheBlank request: 'Please type desired scale:' initialAnswer: '2x'.
	answer size = 0 ifTrue: [^ self].
	answer := answer copyWithout: $x.
	self zoom: answer asNumber.
!

----- Method: ScratchGraphMorph>>data (in category 'accessing') -----
data

	^ data
!

----- Method: ScratchGraphMorph>>data: (in category 'accessing') -----
data: aCollection

	data := aCollection.
	maxVal := minVal := 0.
	data do: [:x |
		x < minVal ifTrue: [minVal := x].
		x > maxVal ifTrue: [maxVal := x]].

	self flushCachedForm.
!

----- Method: ScratchGraphMorph>>dataColor (in category 'accessing') -----
dataColor

	^ dataColor
!

----- Method: ScratchGraphMorph>>dataColor: (in category 'accessing') -----
dataColor: aColor

	dataColor := aColor.
	self flushCachedForm.
!

----- Method: ScratchGraphMorph>>drawCursorOn: (in category 'private') -----
drawCursorOn: aCanvas

	| ptr x r c |
	ptr := (editor cursor asInteger max: 1) min: data size.
	c := cursorColor.
	((ptr > 1) and: [ptr < data size]) ifTrue: [
		(data at: ptr) sign ~= (data at: ptr + 1) sign
			ifTrue: [c := cursorColorAtZeroCrossings]].
	r := self innerBounds.
	x := r left + ((ptr - startIndex)*scale).
	((x >= r left) and: [x <= r right]) ifTrue: [
		aCanvas fillRectangle: (x at r top corner: x + 1 at r bottom) color: c].
!

----- Method: ScratchGraphMorph>>drawDataOn: (in category 'private') -----
drawDataOn: aCanvas

	| x start end left right yScale baseLine top bottom |
	super drawOn: aCanvas.

	viewer ifTrue: [self drawViewOn: aCanvas.].
	self drawSelectionOn: aCanvas.

	(posVals isNil) ifTrue: [^ self].

	maxVal = minVal ifTrue: [yScale := 1.] 
					ifFalse: [yScale := (bounds height - (2 * borderWidth)) asFloat / (maxVal - minVal)].
	baseLine := bounds bottom - borderWidth + (minVal * yScale) truncated.

	left := 0. right := 10.
	x := bounds left + borderWidth.

	start := (startIndex*scale) truncated min: data size max: 1.
	end := start + bounds width min: data size.

	start to: end do: [:i |
		i > posVals size ifTrue: [^self].
					
		left := x truncated. right := x + 1.
		right > (bounds right - borderWidth) ifTrue: [^ self].

		top := baseLine min: (baseLine - (yScale*(posVals at: i))) truncated.
		bottom := (baseLine max: baseLine - (yScale*(negVals at: i))) truncated.
											
		aCanvas fillRectangle: (left at top corner: right at bottom) color: dataColor.
		x := x + 1].!

----- Method: ScratchGraphMorph>>drawOn: (in category 'drawing') -----
drawOn: aCanvas

	| c |

	cachedForm = nil ifTrue:  [
		c := FormCanvas extent: bounds extent.
		c translateBy: bounds origin negated
			during:[:tempCanvas| self drawDataOn: tempCanvas].
		cachedForm := c form].
	aCanvas paintImage: cachedForm at: bounds origin.
	self drawCursorOn: aCanvas.
	self drawPlayCursorOn: aCanvas.
	!

----- Method: ScratchGraphMorph>>drawPlayCursorOn: (in category 'private') -----
drawPlayCursorOn: aCanvas

	| ptr x r c |

	editor playCursor ifNil: [^self].
	(editor endPlaying ~= data size) & (editor playCursor >= (editor endPlaying)) ifTrue: [^self].

	ptr := (editor playCursor asInteger max: 1) min: data size.
	c := cursorColor.
	r := self innerBounds.
	x := r left + ((ptr - startIndex)*scale).
	((x >= r left) and: [x <= r right]) ifTrue: [
		aCanvas fillRectangle: (x at r top corner: x + 1 at r bottom) color: c].
!

----- Method: ScratchGraphMorph>>drawSelectionOn: (in category 'private') -----
drawSelectionOn: aCanvas

	| x y lightColor darkColor v1 v2 offsetX s1 s2 bottom |
editor ifNil: [^ self].
	editor selectionNil ifTrue: [^ self].

	lightColor := Color lightBlue. "(Color r: 0.2 g: 1.0 b: 0.907)."
	darkColor := lightColor darker darker darker.

	v1 := (editor graph startIndex asInteger max: 1) min: data size.
	v2 := v1 + (bounds width/(editor graph scale)) min: data size.
	

	offsetX := bounds left + borderWidth.
	x := (offsetX + ((selection first - startIndex)*scale)).
	y := bounds top + borderWidth.

	viewer 
		ifFalse: [
			selection first > v2 ifTrue: [^ self].  "selection is not visible"
			selection last < v1 ifTrue: [^ self].  "selection is not visible"

			aCanvas
				fillRectangle: (x at y extent: ((selection last - selection first)*scale)@(self height - (2 * borderWidth)))
				color: lightColor. "lightYellow"]
		ifTrue: [
			s1 := selection first.
			s2 := selection second.

			bottom := self height - (2 * borderWidth).


			((s1 max: s2) <= v1) | ((s1 min: s2) >= v2)
				ifTrue: [^aCanvas 				
							fillRectangle: ((offsetX + (s1*scale))@y extent: ((s2-s1)*scale)@bottom)
							color: darkColor.].
			
			(s1 <= v1) & (s2 >= v2)
				ifTrue: [^aCanvas fillRectangle: ((offsetX + (s1*scale))@y extent: ((v1-s1)*scale)@bottom)
								color: darkColor;
								fillRectangle: ((offsetX + (v1*scale))@y extent: ((v2-v1)*scale)@bottom)
								color: lightColor;
								fillRectangle: (( offsetX + (v2*scale))@y extent: ((s2-v2)*scale)@bottom)
								color: darkColor.].
			
			(s1 >= v1) & (s2 <= v2)
				ifTrue: [^aCanvas
							fillRectangle: ((offsetX + (s1*scale))@y extent: ((s2-s1)*scale)@bottom)
							color: lightColor.].
	
			(s1 < v1) & (s2 > v1) & (s2 < v2)
				ifTrue: [^aCanvas
							fillRectangle: ((offsetX + (s1*scale))@y extent: ((v1-s1)*scale)@bottom)
							color: darkColor;
							fillRectangle: ((offsetX + (v1*scale))@y extent: ((s2- v1)*scale)@bottom)
							color: lightColor.].
		
			(s1 >= v1) & (s2 >= v2) 
				ifTrue: [^aCanvas
							fillRectangle: ((offsetX + (s1*scale))@y extent: ((v2-s1)*scale)@bottom)
							color: lightColor;
							fillRectangle: ((offsetX + (v2*scale))@y extent: ((s2 - v2)*scale)@bottom)
							color: darkColor.].

			"Transcript show: 'no category :(';cr."

			].



!

----- Method: ScratchGraphMorph>>drawViewOn: (in category 'private') -----
drawViewOn: aCanvas

	"highlights the part of the graph morph we're viewing."
	| y ex start x |

	viewer ifFalse: [^self].
	
	
	start := ((editor graph startIndex*bounds width)/data size) truncated min: data size.
	ex :=  ((editor slider sliderThickness/editor slider extent x)*(bounds width)) min: data size.

	x := (bounds left + borderWidth + start).
	y := bounds top + borderWidth.

	aCanvas
		fillRectangle: (x at y extent: ex@(self height - (2 * borderWidth)))
		color: Color white. "lightYellow".
!

----- Method: ScratchGraphMorph>>editor (in category 'accessing') -----
editor

	^editor!

----- Method: ScratchGraphMorph>>editor: (in category 'accessing') -----
editor: aSoundEditor

	editor := aSoundEditor.!

----- Method: ScratchGraphMorph>>flushCachedForm (in category 'private') -----
flushCachedForm

	cachedForm := nil.
	hasChanged := true.
 !

----- Method: ScratchGraphMorph>>handlesMouseDown: (in category 'events') -----
handlesMouseDown: evt

	^ true
!

----- Method: ScratchGraphMorph>>hasChanged: (in category 'drawing') -----
hasChanged: aBoolean
	
	hasChanged := aBoolean.!

----- Method: ScratchGraphMorph>>initialize (in category 'initialization') -----
initialize

	super initialize.
	self color: (Color r: 0.8 g: 0.8 b: 0.6).
	self extent: 365 at 80.
	self borderWidth: 2.
	dataColor := Color darkGray.
	cursorColor := Color red.
	playCursorColor := Color blue.
	cursorColorAtZeroCrossings := Color red.
	startIndex := 1.
	viewer := false.
	selection := {nil. nil}.
	scale := 1.0.
	hasChanged := false.
	posVals := negVals := nil.

	self data:
		((0 to: 360 - 1) collect:
			[:x | (100.0 * (x degreesToRadians sin)) asInteger]).

	
	
!

----- Method: ScratchGraphMorph>>interpolatedValueAtCursor (in category 'accessing') -----
interpolatedValueAtCursor

	| sz prev frac next |
	data isEmpty ifTrue: [^ 0].
	sz := data size.
	owner cursor < 0 ifTrue: [^ data at: 1].  "just to be safe, though cursor shouldn't be negative"
	prev := owner cursor truncated.
	frac := owner cursor - prev.
	prev < 1 ifTrue: [prev := sz].
	prev > sz ifTrue: [prev := 1].
	"assert: 1 <= prev <= sz"
	frac = 0 ifTrue: [^ data at: prev].  "no interpolation needed"

	"interpolate"
	next := prev = sz ifTrue: [1] ifFalse: [prev + 1].
	^ ((1.0 - frac) * (data at: prev)) + (frac * (data at: next))
!

----- Method: ScratchGraphMorph>>keepIndexInView: (in category 'private') -----
keepIndexInView: index

	| w newStart |

	w := bounds width - (2 * borderWidth).
	index < startIndex ifTrue: [
		newStart := index - w//scale + 1.
		^ self startIndex: (newStart max: 1)].
	index > (startIndex + w//scale) ifTrue: [
		^ self startIndex: (index min: data size)].
!

----- Method: ScratchGraphMorph>>lastValue (in category 'accessing') -----
lastValue

	data size = 0 ifTrue: [^ 0].
	^ data last
!

----- Method: ScratchGraphMorph>>lastValue: (in category 'accessing') -----
lastValue: aNumber

	self appendValue: aNumber.
!

----- Method: ScratchGraphMorph>>layoutChanged (in category 'change reporting') -----
layoutChanged

	super layoutChanged.
	cachedForm := nil.
!

----- Method: ScratchGraphMorph>>loadSineWave (in category 'commands') -----
loadSineWave

	self loadSoundData: FMSound sineTable.
!

----- Method: ScratchGraphMorph>>loadSound: (in category 'commands') -----
loadSound: aSound

	self loadSoundData: aSound samples.
!

----- Method: ScratchGraphMorph>>loadSoundData: (in category 'commands') -----
loadSoundData: aCollection

	| factor absV newData |
	factor := 0.
	aCollection do: [:v | (absV := v abs) > factor ifTrue: [scale := absV]].
	scale := 100.0 / factor.
	newData := OrderedCollection new: aCollection size.
	1 to: aCollection size do: [:i | newData addLast: (factor * (aCollection at: i))].

	self data: newData.
	self startIndex: 1.
	self cursor: 1.
!

----- Method: ScratchGraphMorph>>minScale (in category 'accessing') -----
minScale
	
		
	"aNumber should be equal to: viewer extent x/ graph data size"
	minScale ifNil:[minScale := (self extent x / data size) asFloat].

	^minScale!

----- Method: ScratchGraphMorph>>minScale: (in category 'accessing') -----
minScale: aNumber

	"aNumber should be equal to: viewer extent x/ graph data size"
	minScale := aNumber asFloat.
!

----- Method: ScratchGraphMorph>>mouseDown: (in category 'events') -----
mouseDown: evt

	"Handles mouse down and drag events.  Updates the cursor's position and sets the selection to an array containing two copies of the current cursor value."
	| x s |

	 x := evt cursorPoint x - (bounds left + borderWidth).

	s := editor startSelection.
	editor startSelection: editor cursor.  
	editor cursor: startIndex + (x/scale).
		
	evt shiftPressed
		ifTrue: [  editor selectionNil 
					ifFalse: [
						editor startSelection: s.
				  		self adjustSelection.].]
		ifFalse: [
				 ((editor selectionNil not) and: [(selection at: 2) - (selection at: 1) > 3])
						ifTrue: [ editor selection: nil.
			  				      self flushCachedForm.
				 				 self changed.].
			  	 editor startSelection: editor cursor.
				 editor selection: {editor cursor. editor cursor}.].


	 
	
	!

----- Method: ScratchGraphMorph>>mouseMove: (in category 'events') -----
mouseMove: evt

	"Updates the cursor position as the mouse moves.  Adjusts the selection only if the mouse is currently being pressed"
	| x w |

	x := evt cursorPoint x - (bounds left + borderWidth).
	w := self width - (2 * borderWidth).

	(viewer not and: [x < 0]) ifTrue: [
		editor cursor: startIndex + (x /scale).
		self adjustSelection.
		editor slider setValue: (startIndex/data size).
		^ self startIndex: self editor cursor].
	(viewer not and: [x > w]) ifTrue: [
		editor cursor: startIndex + (x /scale).
		self adjustSelection.
		editor slider setValue: (startIndex/data size).
		^ self startIndex: editor cursor - (w/scale) truncated.
		"^ editor cursor = data size
			ifTrue: [ self startIndex: editor cursor - (w/(scale*2)) truncated.]
			ifFalse: [ self startIndex: editor cursor - (w/scale) truncated.]."].


	evt anyButtonPressed 
		ifTrue: [editor cursor: (startIndex + (x/scale) truncated).
				self adjustSelection.]
!

----- Method: ScratchGraphMorph>>mouseUp: (in category 'events') -----
mouseUp: evt

	((editor selectionNil not) and: [(selection at: 2) - (selection at: 1) <=3])
		ifTrue: [editor selection: nil.
				editor startSelection: nil.].
!

----- Method: ScratchGraphMorph>>openWaveEditor (in category 'menu') -----
openWaveEditor

	| factor scaledData |
	self data: data.  "make sure maxVal and minVal are current"
	factor := 32767 // ((minVal abs max: maxVal abs) max: 1).
	scaledData := SoundBuffer newMonoSampleCount: data size.
	1 to: data size do: [:i | scaledData at: i put: (factor * (data at: i)) truncated].
	(SimpleWaveEditor new
		data: scaledData;
		samplingRate: 11025) openInWorld.
!

----- Method: ScratchGraphMorph>>playOnce (in category 'commands') -----
playOnce

	| factor absV scaledData |
	data isEmpty ifTrue: [^ self].  "nothing to play"
	factor := 1.
	data do: [:v | (absV := v abs) > factor ifTrue: [factor := absV]].
	factor := 32767.0 / factor.
	scaledData := SoundBuffer newMonoSampleCount: data size.
	1 to: data size do: [:i |
		scaledData at: i put: (factor * (data at: i)) truncated].
	(SampledSound samples: scaledData samplingRate: 11025) play.
!

----- Method: ScratchGraphMorph>>readDataFromFile (in category 'menu') -----
readDataFromFile

	| result fName |
	result := StandardFileMenu oldFile. "Extensions: #(aif aiff au wav)."
	result ifNil: [^ self].
	fName :=  result directory pathName, FileDirectory slash, result name.
	self data: (SampledSound fromFileNamed: fName) samples.

!

----- Method: ScratchGraphMorph>>reverse (in category 'commands') -----
reverse

	data := data reversed.
	self flushCachedForm.
!

----- Method: ScratchGraphMorph>>ruler (in category 'accessing') -----
ruler

	^ruler.!

----- Method: ScratchGraphMorph>>ruler: (in category 'accessing') -----
ruler: aRuler

	ruler:=aRuler!

----- Method: ScratchGraphMorph>>scale (in category 'accessing') -----
scale
	
	^scale.!

----- Method: ScratchGraphMorph>>scale: (in category 'accessing') -----
scale: aNumber

	"setting the absolute scale of how the graph is display.  It is relative to MinScale, the minimum scale possible, which is the scale value of the viewer."

	aNumber < 1 ifTrue: [^self].
	scale := (aNumber* self minScale) asFloat min: 1.
	
	self calculateDataArray.
	self flushCachedForm; changed.
	editor viewer flushCachedForm; changed.

	editor updateSlider.
!

----- Method: ScratchGraphMorph>>selection (in category 'accessing') -----
selection

	^ selection
!

----- Method: ScratchGraphMorph>>selection: (in category 'accessing') -----
selection: anArrayOrNil
	"Set the selection to the given (startIndex, stopIndex) pair to to nil."

	anArrayOrNil
		ifNil: [	selection at: 1 put: nil. selection at: 2 put: nil]
		ifNotNil: [ selection := anArrayOrNil.].

!

----- Method: ScratchGraphMorph>>setScale (in category 'viewing') -----
setScale

	| menu choice |

	menu := CustomMenu new.
	menu add: '1x' action: '1';
		   add: '2x' action: '2';
		   add: '3x' action: '3';
		   add: '4x' action: '4';
		   add: '5x' action: '5';
		   add: 'other' action: #customScale.
	choice := menu startUp.
	choice ifNil: [^self].

	choice = #customScale 
		ifFalse: [self scale: choice asNumber.]	
		ifTrue: [ self customScale].!

----- Method: ScratchGraphMorph>>startIndex (in category 'accessing') -----
startIndex

	^ startIndex
!

----- Method: ScratchGraphMorph>>startIndex: (in category 'accessing') -----
startIndex: aNumber

	startIndex ~= aNumber ifTrue:  [
		startIndex := aNumber asInteger.
		self flushCachedForm].
!

----- Method: ScratchGraphMorph>>step (in category 'stepping') -----
step
	"Make a deferred damage rectangle if I've changed. This allows applications to call methods that invalidate my display at high-bandwidth without paying the cost of doing the damage reporting on ever call; they can merely set hasChanged to true."

	super step.
	
	hasChanged == nil ifTrue: [hasChanged := false].
	hasChanged ifTrue: [
		self changed.
		hasChanged := false].
!

----- Method: ScratchGraphMorph>>stepTime (in category 'stepping') -----
stepTime

	^150!

----- Method: ScratchGraphMorph>>valueAtCursor (in category 'accessing') -----
valueAtCursor

	data isEmpty ifTrue: [^ 0].
	^ data at: ((editor cursor truncated max: 1) min: data size).
!

----- Method: ScratchGraphMorph>>valueAtCursor: (in category 'accessing') -----
valueAtCursor: aPointOrNumber

	data isEmpty ifTrue: [^ 0].
	data
		at: ((editor cursor truncated max: 1) min: data size)
		put: (self asNumber: aPointOrNumber).
	self flushCachedForm.
!

----- Method: ScratchGraphMorph>>viewSelection (in category 'viewing') -----
viewSelection

	| diff |
	selection ifNil: [^self].
	scale := (self minScale*(data size/(selection second - selection first)) asFloat min: 1).
	self calculateDataArray.

	diff := (selection second - selection first) - bounds width.
	diff < 0
		ifTrue: [ self startIndex: selection first asInteger + (diff//2)]
		ifFalse: [self startIndex: selection first asInteger.].
	
	
	editor updateSlider.


	!

----- Method: ScratchGraphMorph>>viewer: (in category 'accessing') -----
viewer: aBoolean

	viewer := aBoolean. "whether or not this graphMorph is the viewer graph Morph"
	
	viewer ifFalse: [self color: Color white.].!

----- Method: ScratchGraphMorph>>zoom: (in category 'viewing') -----
zoom: aNumber

	scale := ((scale*aNumber asFloat) max: self minScale asFloat) min: 1.
	
	self calculateDataArray.
	self flushCachedForm; changed.
	editor viewer flushCachedForm; changed.

	editor updateSlider.!

----- Method: ScratchGraphMorph>>zoomIn (in category 'viewing') -----
zoomIn

	self zoom: 2.!

----- Method: ScratchGraphMorph>>zoomOut (in category 'viewing') -----
zoomOut

	self zoom: 0.5.!

RectangleMorph subclass: #ScratchRulerMorph
	instanceVariableNames: 'max min marks graph sigDigs'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ScratchSoundEditor'!

!ScratchRulerMorph commentStamp: 'tpr 12/6/2013 18:23' prior: 0!
A ScratchRulerMorph is an apparently unused class!

----- Method: ScratchRulerMorph class>>graphMorph: (in category 'instance creation') -----
graphMorph: aScratchGraphMorph

	^ self new graph: aScratchGraphMorph; extent: (aScratchGraphMorph extent x)@20.

	!

----- Method: ScratchRulerMorph>>drawOn: (in category 'drawing') -----
drawOn: aCanvas

	| space bigSpace currVal s ss |
	
	"the amt of space btw each bar.  big Space = the amt of space btw each big bar"
	space := (self extent x/marks) truncated max: 1.
	bigSpace := 5* space asFloat.

	graph ifNotNil: [ss := graph editor origSamplingRate ]
		   ifNil: [ss := 1].

ss ifNil:[ss:=1].
	currVal := (min/ss) asFloat roundTo: 0.01.  "the value of where we are in teh rule"

	aCanvas fillRectangle: (Rectangle origin: (self left)@(self top) corner: (self right)@(self bottom)) color: Color lightGray.
	self removeAllMorphs.

	(self left) to: (self right) by: space do: 
		[:pos |
			(pos - (self left)) \\ bigSpace = 0
				ifTrue: [aCanvas line: (pos truncated)@((self top) truncated) to: (pos truncated)@((self top + 5) truncated) color: Color black.
				s := StringMorph contents: (currVal asString).
				s center: (pos truncated)@(self top + 12).
				self addMorph: s.]
				ifFalse: [aCanvas line: (pos truncated)@(self top truncated) to: (pos truncated)@((self top + 1) truncated) color: Color black.]. 
			currVal := currVal + ((max-min)/(marks*ss)) roundTo: 0.01. ].




!

----- Method: ScratchRulerMorph>>graph: (in category 'accessing') -----
graph: aScratchGraphMorph

	graph := aScratchGraphMorph.!

----- Method: ScratchRulerMorph>>initialize (in category 'initialize') -----
initialize
	
	super initialize.
	min := 0.0.
	max := 100.
	marks := 20.0.
	sigDigs := 1. 
	graph := nil. "used specifically to coord with ScratchGraphMorph"

	self borderWidth: 1.
	self extent: 200 at 20.
	self color: Color white.!

----- Method: ScratchRulerMorph>>marks: (in category 'accessing') -----
marks: aNumber
	marks := aNumber.
	self changed.!

----- Method: ScratchRulerMorph>>min:max: (in category 'accessing') -----
min: aMin max: aMax

	min := aMin.
	max := aMax.
	self changed.!

----- Method: ScratchRulerMorph>>sigDigs: (in category 'accessing') -----
sigDigs: aNumber

	sigDigs := aNumber truncated.
	self changed.!

----- Method: ScratchRulerMorph>>step (in category 'stepping') -----
step
	
	| graphStart graphEnd |
	graph ifNil: [^self].

	self extent x = graph extent x
		ifFalse: [self extent: (graph extent x)@(self extent y).].


	graphStart := graph startIndex min: graph data size.
	graphEnd := graphStart + (graph bounds width/graph scale) min: graph data size.
	
	(min = graphStart and:[ max = graphEnd])
		ifFalse: [ min := graphStart.
				  max := graphEnd truncated.
				  self changed.].!



More information about the etoys-dev mailing list