[etoys-dev] Etoys Inbox: Etoys-Richo.32.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Aug 14 12:55:40 EDT 2010


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

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

Name: Etoys-Richo.32
Author: Richo
Time: 14 August 2010, 1:54:24 pm
UUID: 201d0471-7b7c-7545-9ae0-9794f9a68204
Ancestors: Etoys-Richo.31

* Added SpeechBubbles and Graphing tools. I cleaned the code as Bert suggested:
- I removed all Player subclasses.
- I removed Vector class and Point>>#to: method.
- I changed the GSoC category for "Tools" (in the case of the Graphing tools) and "Just for Fun" (in the case of the Speech Bubbles). Please feel free to change it as you wish.
The only thing I didn't removed yet is the classes PointMorph, BarMorph and VectorMorph. They're mostly hacks but I don't know how to remove them by preserving its viewer categories.

=============== Diff against Etoys-Richo.31 ===============

Item was added:
+ ----- Method: Player>>setRowLabel: (in category '*Etoys-graphing') -----
+ setRowLabel: aString
+ | selector |
+ selector := #rowLabelAt:put:.
+ (self costumeRespondingTo: selector) ifNotNilDo: [:c | c perform: selector withArguments: {self getRowIndex. aString}]!

Item was added:
+ ----- Method: Player>>getXMax (in category '*Etoys-graphing') -----
+ getXMax
+ ^ self getValueFromCostume: #xMax!

Item was added:
+ ----- Method: VectorMorph>>terminalPointY (in category 'accessing') -----
+ terminalPointY
+ ^terminalPoint y!

Item was added:
+ ----- Method: BarGraphMorph>>minorGrid (in category 'accessing grid') -----
+ minorGrid
+ ^self isVerticalGraph ifTrue: [super minorGrid y] ifFalse: [super minorGrid x]!

Item was added:
+ ----- Method: Player>>getMyPointColor (in category '*Etoys-graphing') -----
+ getMyPointColor
+ ^ self getValueFromCostume: #color!

Item was added:
+ ----- Method: Player>>setTerminalPointY: (in category '*Etoys-graphing') -----
+ setTerminalPointY: aNumber
+ | current |
+ current := self currentVector.
+ current isNil ifTrue: [^self].
+ current terminalPointY: aNumber!

Item was added:
+ ----- Method: Player>>getVectorIndex (in category '*Etoys-graphing') -----
+ getVectorIndex
+ self vectorIndex > self getVectorCount ifTrue: [self vectorIndex: self getVectorCount].
+ ^ self vectorIndex!

Item was added:
+ ----- Method: BarMorph>>barLabel: (in category 'accessing') -----
+ barLabel: aString
+ label := aString.
+ self updateLabel.!

Item was added:
+ ----- Method: CartesianGraphMorph>>initialize (in category 'initialize-release') -----
+ initialize
+ super initialize.
+ self  clipSubmorphs: true; extent: 600 at 600; color: Color white; borderColor: Color gray;
+ 	initializeCartesianBounds;
+ 	initializeLegendSpacing;
+ 	initializeColors;
+ 	initializeAxes;
+ 	initializeGrids;
+ 	initializeLegends!

Item was added:
+ ----- Method: BarGraphMorph>>barAt:ifAbsent: (in category 'accessing bars') -----
+ barAt: index ifAbsent: aBlock
+ | m |
+ m := barMorphs at: index ifAbsent: [nil].
+ ^m isNil ifTrue: [aBlock value] ifFalse: [m]
+ !

Item was added:
+ ----- Method: BarMorph>>initialize (in category 'initialize-release') -----
+ initialize
+ super initialize.
+ self width: 30; color: Color blue muchDarker.
+ labelMorph := StringMorph new.
+ self update!

Item was added:
+ ----- Method: CartesianGraphMorph>>delete (in category 'initialize-release') -----
+ delete
+ self submorphsDo: [:each| each delete].
+ super delete!

Item was added:
+ ----- Method: BarTableMorph>>makeRow: (in category 'building') -----
+ makeRow: anAssoc 
+ 	^ AlignmentMorph newRow color: Color transparent;
+ 		 addMorphBack: (self newTextMorph
+ 			contents: (anAssoc isNil
+ 					ifTrue: ['']
+ 					ifFalse: [anAssoc key asString]);
+ 			 wrapFlag: true);
+ 		 addMorphBack: (self newTextMorph
+ 			contents: (anAssoc isNil
+ 					ifTrue: ['']
+ 					ifFalse: [anAssoc value isInteger ifFalse: [anAssoc value printShowingDecimalPlaces: 2] ifTrue: [anAssoc value asString]]);
+ 			 wrapFlag: true) !

Item was added:
+ ----- Method: CartesianGraphMorph>>translateTurtleTrailsBy: (in category 'moving') -----
+ translateTurtleTrailsBy: aPoint
+ | newForm |
+ turtleTrailsForm ifNil: [^self].
+ 
+ newForm := turtleTrailsForm blankCopyOf: turtleTrailsForm scaledBy: 1.
+ turtleTrailsForm contentsOfArea: (turtleTrailsForm boundingBox translateBy: 
+ (self cartesianPointToRelativePixel: aPoint + cartesianBounds bottomLeft )) into: newForm.
+ turtleTrailsForm := newForm.
+ turtlePen := Pen newOnForm: turtleTrailsForm
+ !

Item was added:
+ ----- Method: Player>>getMyInitialPointY (in category '*Etoys-graphing') -----
+ getMyInitialPointY
+ ^ self getValueFromCostume: #initialPointY!

Item was added:
+ ----- Method: BarTableMorph>>rowValueAt: (in category 'accessing') -----
+ rowValueAt: barIndex
+ | count |
+ count := 0.
+ self list submorphs do: [:each|
+ 	(each isAlignmentMorph and: [ each submorphs first isTextMorph])
+ 	 ifTrue: [
+ 		count := count + 1.
+ 		count = barIndex ifTrue: [
+ 			^[each submorphs second getNumericValue] on: Error do: [0]
+ 			]			
+ 		]
+ 	]!

Item was added:
+ ----- Method: CartesianGraphMorph>>initializeColors (in category 'initialize-release') -----
+ initializeColors
+ backgroundColor := Color white.
+ minorGridColor := Color gray.
+ majorGridColor := Color gray.
+ axisColor := Color black.
+ !

Item was added:
+ ----- Method: SpeechBubbleMorph>>tailHeight (in category 'accessing') -----
+ tailHeight
+ ^self tail height!

Item was added:
+ ----- Method: Morph>>bubble (in category '*Etoys-SpeechBubbles') -----
+ bubble
+ 	^self valueOfProperty: #bubble ifAbsent: [nil].!

Item was added:
+ ----- Method: PointMorph classSide>>additionsToViewerCategories (in category 'viewer categories') -----
+ additionsToViewerCategories
+ ^ #(
+ (#plot (
+ #(command remove '' )
+ #(slot pointX '' Number readWrite Player getMyPointX Player setMyPointX:  )
+ #(slot pointY '' Number readWrite Player getMyPointY Player setMyPointY:  )
+ #(slot pointColor '' Color readWrite Player getMyPointColor Player setMyPointColor:  )
+ ))
+ 
+ )!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>thoughtPrototype (in category 'parts bin') -----
+ thoughtPrototype
+ 	^self string: 'Hello world!!' type: #thought!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>morph:type: (in category 'instance creation') -----
+ morph: aMorph type: aSymbol 
+ ^(self basicNew setMorph: aMorph type: aSymbol) initialize!

Item was added:
+ ----- Method: CartesianGraphMorph>>restoreDefaultColors (in category 'accessing colors') -----
+ restoreDefaultColors
+ self initializeColors; updateBackground!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>thoughtGraphicPrototype (in category 'parts bin') -----
+ thoughtGraphicPrototype
+ 	^self form: (ScriptingSystem formAtKey: 'Painting') type: #thought!

Item was changed:
+ ----- Method: Player>>setBackgroundColor: (in category '*Etoys-graphing') -----
- ----- Method: Player>>setBackgroundColor: (in category 'scripts-standard') -----
  setBackgroundColor: aColor
+ ^ self setCostumeSlot: #backgroundColor: toValue: aColor!
- 	"Set the background color; the costume is presumed to be a text morph."
- 
- 	self costume renderedMorph backgroundColor: aColor!

Item was added:
+ ----- Method: Player>>apply (in category '*Etoys-graphing') -----
+ apply
+ ^ self sendMessageToCostume: #apply!

Item was added:
+ ----- Method: Player>>moveLeft: (in category '*Etoys-graphing') -----
+ moveLeft: aNumber
+ ^ self  sendMessageToCostume: #move: with: aNumber negated @ 0!

Item was added:
+ ----- Method: BarTableMorph classSide>>additionsToViewerCategories (in category 'viewer categories') -----
+ additionsToViewerCategories
+ ^ #(
+ (#plot (
+ #(command apply '' )
+ #(command addRow '' )
+ #(command removeRow '' )
+ #(slot rowCount '' Number readOnly Player getRowCount Player unused )
+ #(slot rowIndex '' Number readWrite Player getRowIndex Player setRowIndex:  )
+ #(slot rowValue '' Number readWrite Player getRowValue Player setRowValue:  )
+ #(slot rowLabel '' String readWrite Player getRowLabel Player setRowLabel:  )
+ #(slot rowsFilled '' Number readOnly Player getRowsFilled Player unused )
+ ))
+ 
+ )!

Item was added:
+ ----- Method: BarGraphMorph>>barColorAt:put: (in category 'accessing bars') -----
+ barColorAt: index put: aColor
+ | current |
+ current := self barAt: index ifAbsent: [^self].
+ current color: aColor!

Item was added:
+ ----- Method: PointTableMorph classSide>>includeInNewMorphMenu (in category 'as yet unclassified') -----
+ includeInNewMorphMenu
+ 	"Return true for all classes that can be instantiated from the menu"
+ 	^ false!

Item was added:
+ ----- Method: BarMorph classSide>>additionsToViewerCategories (in category 'viewer categories') -----
+ additionsToViewerCategories
+ ^ #(
+ (#plot (
+ #(slot barLabel '' String readWrite Player getMyBarLabel Player setMyBarLabel:  )
+ #(slot barValue '' Number readWrite Player getMyBarValue Player setMyBarValue:  )
+ #(slot barColor '' Color readWrite Player getMyBarColor Player setMyBarColor:  )
+ #(command remove '' )
+ ))
+ 
+ )!

Item was added:
+ ----- Method: SpeechBubbleMorph>>setMorph:type: (in category 'private') -----
+ setMorph: aMorph type: aSymbol
+ 	msgMorph := aMorph.
+ 	type := aSymbol!

Item was added:
+ ----- Method: CartesianGraphMorph>>controlCartesianBounds: (in category 'controlling errors') -----
+ controlCartesianBounds: aRectangle
+ 
+ aRectangle right <= aRectangle left ifTrue: [^self error: 'x range error'].
+ aRectangle bottom <= aRectangle top ifTrue: [^self error: 'y range error'].!

Item was added:
+ ----- Method: CartesianGraphMorph>>xMin: (in category 'accessing cartesian bounds') -----
+ xMin: aNumber
+ [self cartesianBounds: ((aNumber @ self cartesianBounds origin y) corner: self cartesianBounds corner)]
+ 	on: Error do: [:err| self inform: err description]..!

Item was added:
+ ----- Method: BarGraphMorph>>initializeToStandAlone (in category 'initialize-release') -----
+ initializeToStandAlone
+ 	"Answer an instance of the receiver suitable for placing in a parts bin for authors"
+ 	
+ 	self initialize.!

Item was added:
+ ----- Method: PointMorph>>fillStyle: (in category 'accessing') -----
+ fillStyle: aFillStyle
+ 	"Set the current fillStyle of the receiver."
+ 	self setProperty: #fillStyle toValue: aFillStyle.
+ 	"Workaround for Morphs not yet converted"
+ 	self color: aFillStyle asColor!

Item was added:
+ ----- Method: CartesianGraphMorph>>majorGridColor (in category 'accessing colors') -----
+ majorGridColor
+ ^majorGridColor!

Item was added:
+ ----- Method: PointTableMorph>>removeRow (in category 'actions') -----
+ removeRow
+ 	| |
+ 	numberOfRows <= 1 ifTrue: [^self].
+ 	numberOfRows := numberOfRows - 1.
+ 	list removeMorph: list submorphs last.
+ 	self updateScrollPane!

Item was added:
+ PasteUpMorph subclass: #CartesianGraphMorph
+ 	instanceVariableNames: 'cartesianBounds minorGrid majorGrid legendSpacing backgroundColor minorGridColor majorGridColor axisColor verticalAxis horizontalAxis legends grids gridForm'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Etoys-Graphing'!
+ 
+ !CartesianGraphMorph commentStamp: 'Richo 5/21/2010 08:59' prior: 0!
+ This class is responsible of drawing a cartesian coordinate system.
+ You can change its grid, x and y range, legend spacing and colors using the following methods:
+ 	#majorGrid:
+ 	#minorGrid:
+ 	#cartesianBounds:
+ 	#legendSpacing:
+ 	#axisColor:
+ 	#backgroundColor:
+ 	#majorGridColor:
+ 	#minorGridColor:!

Item was added:
+ ----- Method: DataGraphMorph>>addVector (in category 'accessing vectors') -----
+ addVector
+ | m |
+ m := VectorMorph graph: self initialPoint: 0 at 0 terminalPoint: 0 at 0.
+ self addMorph: m.
+ vectorMorphs add: m.
+ !

Item was added:
+ ----- Method: SpeechBubbleMorph>>refresh (in category 'refreshing') -----
+ refresh
+ self refreshBalloon; refreshTail; refreshMsgMorph!

Item was added:
+ ----- Method: Player>>currentPoint (in category '*Etoys-graphing') -----
+ currentPoint
+ | selector |
+ selector := #pointAt:ifAbsent:.
+ ^(self costumeRespondingTo: selector) ifNotNilDo: [:c | c perform: selector withArguments: {self getPointIndex. [nil]}]!

Item was added:
+ ----- Method: Player>>getXMin (in category '*Etoys-graphing') -----
+ getXMin
+ ^ self getValueFromCostume: #xMin!

Item was added:
+ ----- Method: Morph>>showGraphic:inBubbleType: (in category '*Etoys-SpeechBubbles') -----
+ showGraphic: aForm inBubbleType: typeSymbol
+ | currentBubble |
+ currentBubble := self bubble.
+ currentBubble notNil ifTrue: [
+ 	(currentBubble form = aForm and: [currentBubble type = typeSymbol and: [currentBubble isInWorld]]) ifTrue: [^self].
+ 	currentBubble delete].
+ self setProperty: #bubble toValue: (SpeechBubbleMorph form: aForm type: typeSymbol for: self).!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>speechPrototype (in category 'parts bin') -----
+ speechPrototype
+ 	^self string: 'Hello world!!' type: #speech!

Item was added:
+ ----- Method: DataGraphMorph classSide>>additionsToViewerCategoryPlotPoints (in category 'viewer categories') -----
+ additionsToViewerCategoryPlotPoints
+ ^#(#'plot - points' (
+ #(slot pointIndex '' Number  readWrite Player getPointIndex Player setPointIndex:  )
+ #(command removePointAt: '' Number )
+ #(command removeAllPoints '')
+ #(command removeCurrentPoint '')
+ #(command addPoint '')
+ #(slot pointX '' Number readWrite Player getPointX Player setPointX:  )
+ #(slot pointY '' Number readWrite Player getPointY Player setPointY:  )
+ #(command openPointTable '')
+ #(slot pointCount '' Number readOnly Player getPointCount Player unused  )
+ #(slot pointColor '' Color readWrite Player getPointColor Player setPointColor:  )
+ #(slot playerAtPointIndex '' Player readWrite Player getPlayerAtPointIndex  unused unused)
+ ))!

Item was added:
+ ----- Method: Player>>getRowLabel (in category '*Etoys-graphing') -----
+ getRowLabel
+ ^self sendMessageToCostume: #rowLabelAt: with: self getRowIndex.
+ !

Item was added:
+ ----- Method: Morph>>sayObject: (in category '*Etoys-SpeechBubbles') -----
+ sayObject: aPlayer
+ self showObject: aPlayer inBubbleType: #speech!

Item was added:
+ ----- Method: PointTableMorph>>rowXAt: (in category 'accessing') -----
+ rowXAt: pointIndex
+ | count |
+ count := 0.
+ self list submorphs do: [:each|
+ 	(each isAlignmentMorph and: [ each submorphs first isTextMorph])
+ 	 ifTrue: [
+ 		count := count + 1.
+ 		count = pointIndex ifTrue: [
+ 			^[each submorphs first getNumericValue] on: Error do: [0].
+ 			]
+ 		]
+ 	]
+ !

Item was added:
+ ----- Method: Player>>setXMinorGrid: (in category '*Etoys-graphing') -----
+ setXMinorGrid: aNumber
+ self setCostumeSlot: #xMinorGrid: toValue: aNumber!

Item was added:
+ ----- Method: BarTableMorph>>makeColumnNames (in category 'building') -----
+ makeColumnNames
+ | columnName |
+ 	columnName := [:contents | self newTextMorph contents: contents; wrapFlag: true; autoFit: true; backgroundColor: Color transparent; borderWidth: 0; centered].
+ 	^ AlignmentMorph newRow color: Color transparent;
+ 		addMorphBack: self makeSpacer;
+ 		addMorphBack: (columnName value: 'Label');
+ 		addMorphBack: self makeSpacer;
+ 		addMorphBack: (columnName value: 'Value');
+ 		addMorphBack: self makeSpacer;
+ 		addMorphBack: (Morph new color: Color transparent; extent:  20 at 1)!

Item was added:
+ AlignmentMorph subclass: #BarTableMorph
+ 	instanceVariableNames: 'numberOfRows graph list scrollPane'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Etoys-Graphing'!

Item was added:
+ ----- Method: Player>>setRowValue: (in category '*Etoys-graphing') -----
+ setRowValue: aNumber
+ | selector |
+ selector := #rowValueAt:put:.
+ (self costumeRespondingTo: selector) ifNotNilDo: [:c | c perform: selector withArguments: {self getRowIndex. aNumber}]!

Item was added:
+ ----- Method: SpeechBubbleMorph>>target (in category 'accessing') -----
+ target
+ 	^target!

Item was added:
+ ----- Method: CartesianGraphMorph>>xMax: (in category 'accessing cartesian bounds') -----
+ xMax: aNumber
+ [self cartesianBounds: (self cartesianBounds origin corner: (aNumber @ self cartesianBounds corner y))]
+ 	on: Error do: [:err| self inform: err description].!

Item was added:
+ ----- Method: BarGraphMorph>>barValueAt:put: (in category 'accessing bars') -----
+ barValueAt: barIndex put: aNumber
+ | current |
+ current := self barAt: barIndex ifAbsent: [^self].
+ current barValue: aNumber!

Item was added:
+ ----- Method: BarGraphMorph classSide>>descriptionForPartsBin (in category 'parts bin') -----
+ descriptionForPartsBin
+ 	^ self
+ 		partName: 'Bar Graph'
+ 		categories: #('Tools' )
+ 		documentation: ''
+ !

Item was added:
+ ----- Method: PointMorph>>point (in category 'accessing') -----
+ point
+ ^point!

Item was added:
+ ----- Method: BarGraphMorph>>extentFor: (in category 'calculations') -----
+ extentFor: aNumber
+ "Returns the correct extent for a bar morph depending on its value"
+ ^self isVerticalGraph
+ 	ifTrue: [30@((self cartesianYToRelativePixel: 0) - (self cartesianYToRelativePixel: aNumber)) abs]
+ 	ifFalse: [((self cartesianXToRelativePixel: 0) - (self cartesianXToRelativePixel: aNumber)) abs @ 30]!

Item was added:
+ ----- Method: Morph>>say: (in category '*Etoys-SpeechBubbles') -----
+ say: aString
+ self showMessage: aString inBubbleType: #speech!

Item was added:
+ ----- Method: Player>>setXMajorGrid: (in category '*Etoys-graphing') -----
+ setXMajorGrid: aNumber
+ self setCostumeSlot: #xMajorGrid: toValue: aNumber!

Item was added:
+ ----- Method: BarTableMorph>>textMorphWidth (in category 'private') -----
+ textMorphWidth
+ 	^ 100!

Item was added:
+ ----- Method: PointTableMorph>>setGraph: (in category 'private') -----
+ setGraph: aDataGraphMorph
+ graph := aDataGraphMorph!

Item was added:
+ ----- Method: BarMorph>>barLabel (in category 'accessing') -----
+ barLabel
+ ^label!

Item was added:
+ ----- Method: DataGraphMorph>>removePointsFrom:to: (in category 'accessing points') -----
+ removePointsFrom: start to: stop
+ | removed |
+ removed := OrderedCollection new.
+ start to: stop do: [:i|
+ 	removed add: (pointMorphs at: i) delete.
+ 	].
+ pointMorphs removeAllFoundIn: removed!

Item was added:
+ ----- Method: CartesianGraphMorph>>placeXLegends (in category 'building') -----
+ placeXLegends
+ | index legendPos legend xLegends |
+ index := 0.
+ xLegends := legends at: #x.
+ cartesianBounds left ceiling to: cartesianBounds right floor do: [:x | 
+ 		| pos |
+ 		pos := self cartesianXToPixel: x.
+ 		(x isDivisibleBy: legendSpacing x) 
+ 			ifTrue: [
+ 			legendPos := (self preferredPositionForXLegend: x asString at: pos).
+ 			legendPos notNil ifTrue: [
+ 				legend := xLegends at: (index := index + 1) ifAbsent: [xLegends add: StringMorph new].
+ 				self addMorph: legend.
+ 				legend contents: x asString; position: legendPos; color: axisColor]]].
+ xLegends isEmpty ifFalse: [
+ xLegends from: index + 1 to: xLegends size do: [:each | each delete].
+ xLegends removeLast: (xLegends size - index)]!

Item was added:
+ ----- Method: DataGraphMorph>>points (in category 'accessing points') -----
+ points
+ ^pointMorphs!

Item was added:
+ ----- Method: Player>>getBarValue (in category '*Etoys-graphing') -----
+ getBarValue
+ ^self sendMessageToCostume: #barValueAt: with: self getBarIndex!

Item was added:
+ ----- Method: BarTableMorph>>makeSpacer (in category 'building') -----
+ makeSpacer
+ 	^ AlignmentMorph newVariableTransparentSpacer!

Item was added:
+ ----- Method: Player>>getMyVectorColor (in category '*Etoys-graphing') -----
+ getMyVectorColor
+ ^ self getValueFromCostume: #color!

Item was added:
+ ----- Method: CartesianGraphMorph>>legendSpacing: (in category 'accessing legends') -----
+ legendSpacing: aPoint
+ self controlLegendSpacing: aPoint.
+ legendSpacing := aPoint.
+ self updateBackground!

Item was added:
+ ----- Method: PointMorph classSide>>graph:point: (in category 'instance creation') -----
+ graph: aDataGraphMorph point: aPoint 
+ ^(self basicNew setGraph: aDataGraphMorph point: aPoint) initialize!

Item was added:
+ ----- Method: CartesianGraphMorph>>preferredPositionForXLegend:at: (in category 'building') -----
+ preferredPositionForXLegend: legendString at: gridPos
+ "The preferred position is below the horizontal axis at the right of the major grid.
+ If nothing can be drawn return nil"
+ | preferredPosition font axis  stringWidth |
+ font := TextStyle defaultFont.
+ stringWidth := (font widthOfString: legendString).
+ axis :=  horizontalAxis center y.
+ preferredPosition := (gridPos @ axis) + ((stringWidth / -2) rounded @ 2).
+ 
+ "If the legend width doesn't fit inside the form"
+ ((gridPos + stringWidth) > self right)
+ 	ifTrue: [^ nil "Draw nothing"].
+ "If the axis is not visible"
+ (axis < self top or: [axis > self bottom])
+ 	ifTrue: [^preferredPosition x @ (self bottom - font height )].
+ "If the axis is close to the bottom so the legend height doesn't fit inside the form"
+ (axis > (self bottom - font height))
+ 	ifTrue: [^preferredPosition x @ (axis - font height)].
+ "If the preferred position is perfect :)"
+ ^preferredPosition !

Item was added:
+ ----- Method: PointMorph>>pointX: (in category 'accessing') -----
+ pointX: aNumber
+ self point: aNumber @ self pointY!

Item was added:
+ ----- Method: PointMorph>>point: (in category 'accessing') -----
+ point: aPoint
+ 	self privateCenter: (graph cartesianPointToPixel: aPoint).
+ 	point := aPoint!

Item was added:
+ ----- Method: Morph>>showMessage:inBubbleType: (in category '*Etoys-SpeechBubbles') -----
+ showMessage: aString inBubbleType: typeSymbol
+ | currentBubble |
+ currentBubble := self bubble.
+ currentBubble notNil ifTrue: [
+ 	(currentBubble string = aString and: [currentBubble type = typeSymbol and: [currentBubble isInWorld]]) ifTrue: [^self].
+ 	currentBubble delete].
+ aString isEmpty ifTrue: [^self removeProperty: #bubble].
+ self setProperty: #bubble toValue: (SpeechBubbleMorph string: aString type: typeSymbol for: self)!

Item was added:
+ ----- Method: BarGraphMorph classSide>>additionsToViewerCategoryPlotRange (in category 'viewer categories') -----
+ additionsToViewerCategoryPlotRange
+ ^#(#'plot - range' (
+ #(command move: '' Number)
+ #(command restoreInitialPosition '')
+ #(slot max '' Number readWrite Player getMax Player setMax:  )
+ #(slot min '' Number readWrite Player getMin Player setMin:  )
+ ))!

Item was added:
+ ----- Method: Player>>getShowCursorPosition (in category '*Etoys-graphing') -----
+ getShowCursorPosition
+ ^ self getValueFromCostume: #showCursorPosition!

Item was added:
+ ----- Method: CartesianGraphMorph classSide>>includeInNewMorphMenu (in category 'new-morph participation') -----
+ includeInNewMorphMenu
+ 	"Return true for all classes that can be instantiated from the menu"
+ 	^ false!

Item was added:
+ ----- Method: Player>>getRowY (in category '*Etoys-graphing') -----
+ getRowY
+ ^self sendMessageToCostume: #rowYAt: with: self getRowIndex!

Item was added:
+ ----- Method: BarGraphMorph>>range (in category 'accessing range') -----
+ range
+ self isVerticalGraph
+ ifTrue: [^cartesianBounds top to: cartesianBounds bottom]
+ ifFalse: [^cartesianBounds left to: cartesianBounds right]
+ !

Item was added:
+ ----- Method: BarGraphMorph>>filterViewerCategoryDictionary: (in category 'initialize-release') -----
+ filterViewerCategoryDictionary: dict
+ 	super filterViewerCategoryDictionary: dict.
+ 	dict removeKey: #'plot - coordinate system' ifAbsent: [].
+ 	dict removeKey: #'plot - grid' ifAbsent: [].
+ 	dict removeKey: #'plot - legends' ifAbsent: [].!

Item was added:
+ ----- Method: Player>>setVectorColor: (in category '*Etoys-graphing') -----
+ setVectorColor: aColor
+ | current |
+ current := self currentVector.
+ current isNil ifTrue: [^self].
+ current color: aColor!

Item was added:
+ ----- Method: Player>>getVectorAngle (in category '*Etoys-graphing') -----
+ getVectorAngle
+ | current |
+ current := self currentVector.
+ ^current isNil ifTrue: [nil] ifFalse: [current angle]!

Item was added:
+ ----- Method: Player>>getMajorGridColor (in category '*Etoys-graphing') -----
+ getMajorGridColor
+ ^ self getValueFromCostume: #majorGridColor!

Item was added:
+ ----- Method: Morph>>thinkGraphic: (in category '*Etoys-SpeechBubbles') -----
+ thinkGraphic: aForm
+ self showGraphic: aForm inBubbleType: #thought!

Item was added:
+ ----- Method: BarGraphMorph>>initialize (in category 'initialize-release') -----
+ initialize
+ 	graphDirection := #horizontal.
+ 	self initializeBars;
+ 		 initializeDistanceBetweenBars.
+ 	super initialize.!

Item was added:
+ ----- Method: CartesianGraphMorph>>relativePixelToCartesianY: (in category 'calculations') -----
+ relativePixelToCartesianY: anInteger
+ ^cartesianBounds top + ((bounds height - anInteger) * cartesianBounds height / bounds height)!

Item was added:
+ ----- Method: CartesianGraphMorph>>update (in category 'updating') -----
+ update
+ self updateAll!

Item was added:
+ ----- Method: Player>>getBarColor (in category '*Etoys-graphing') -----
+ getBarColor
+ ^ self sendMessageToCostume: #barColorAt: with: self getBarIndex!

Item was added:
+ ----- Method: BarGraphMorph>>min: (in category 'accessing range') -----
+ min: aNumber
+ self range: (aNumber to: self range last)!

Item was added:
+ ----- Method: BarGraphMorph>>move: (in category 'moving') -----
+ move: aNumber
+ self range: ((self range first + aNumber) to: (self range last + aNumber)).
+ self update!

Item was added:
+ ----- Method: Player>>pointIndex (in category '*Etoys-graphing') -----
+ pointIndex
+ ^self costume renderedMorph valueOfProperty: #pointIndex ifAbsent: [self getPointCount > 0 ifTrue: [1] ifFalse: [0]].!

Item was added:
+ ----- Method: SpeechBubbleMorph>>drawOn: (in category 'drawing') -----
+ drawOn: aCanvas!

Item was added:
+ ----- Method: Player>>setMyVectorMagnitude: (in category '*Etoys-graphing') -----
+ setMyVectorMagnitude: aNumber
+ self setCostumeSlot: #magnitude: toValue: aNumber
+ !

Item was added:
+ ----- Method: Player>>getRowCount (in category '*Etoys-graphing') -----
+ getRowCount
+ ^self getValueFromCostume: #rowCount!

Item was added:
+ ----- Method: Player>>getGraphDirection (in category '*Etoys-graphing') -----
+ getGraphDirection
+ ^ self sendMessageToCostume: #graphDirection!

Item was added:
+ ----- Method: Player>>remove (in category '*Etoys-graphing') -----
+ remove
+ self sendMessageToCostume: #remove.
+ !

Item was added:
+ ----- Method: DataGraphMorph classSide>>exampleVectors (in category 'examples') -----
+ exampleVectors
+ "To watch the example simply execute (Cmd-d):
+ 
+ self exampleVectors
+ 
+ "
+ | graph | 
+ 
+ "Creating the morph and opening it in the world"
+ graph := DataGraphMorph new.
+ graph openInHand.
+ 
+ "Changing the minor grid"
+ graph minorGrid: 0 at 0.
+ 
+ "Adding a vector"
+ graph addVector: (Vector terminalPoint: 10 at 5).
+ graph vectorColorAt: 1 put: Color red muchDarker.
+ 
+ "Adding another vector"
+ graph addVector: (Vector terminalPoint: 3 at 10).
+ graph vectorColorAt: 2 put: Color red.
+ 
+ "Adding the sum of the vectors above"
+ graph addVector: (Vector terminalPoint: 13 at 15).
+ graph vectorColorAt: 3 put: Color red muchLighter.
+ 
+ "Adding two additional vectors"
+ graph addVector: ((3 at 10) to: (13 at 15)).
+ graph vectorColorAt: 4 put: Color red muchDarker.
+ graph addVector: ((10 at 5) to: (13 at 15)).
+ graph vectorColorAt: 5 put: Color red.!

Item was added:
+ ----- Method: Player>>restoreDefaultColors (in category '*Etoys-graphing') -----
+ restoreDefaultColors
+ ^ self sendMessageToCostume: #restoreDefaultColors.!

Item was added:
+ ----- Method: Player>>removeVectorAt: (in category '*Etoys-graphing') -----
+ removeVectorAt: aNumber
+ (aNumber > self getVectorCount or: [aNumber <= 0])
+ 	ifTrue: [^self].
+ self sendMessageToCostume: #removeVectorAt: with: aNumber.
+ self vectorIndex = aNumber ifTrue: [self setVectorIndex: self vectorIndex - 1]!

Item was added:
+ ----- Method: BarGraphMorph>>axisYPos (in category 'calculations') -----
+ axisYPos
+ "Returns the vertical position of the axis. It makes sure that the legends fit in this space"
+ ^self bottom - TextStyle defaultFont height - 5
+ !

Item was added:
+ ----- Method: CartesianGraphMorph>>xLegendSpacing (in category 'accessing legends') -----
+ xLegendSpacing
+ ^self legendSpacing x!

Item was added:
+ ----- Method: VectorMorph>>terminalPointX (in category 'accessing') -----
+ terminalPointX
+ ^ terminalPoint x!

Item was added:
+ ----- Method: CartesianGraphMorph>>yMinorGrid: (in category 'accessing grid') -----
+ yMinorGrid: aNumber
+ self minorGrid: self minorGrid x @ ((aNumber max: 0) rounded).!

Item was added:
+ ----- Method: Player>>rowIndex (in category '*Etoys-graphing') -----
+ rowIndex
+ | rowCount |
+ ^self costume renderedMorph valueOfProperty: #rowIndex ifAbsent: [((rowCount := self getRowCount) notNil and: [rowCount > 0]) ifTrue: [1] ifFalse: [0]].!

Item was added:
+ ----- Method: CartesianGraphMorph>>drawMinorGridFrom:to:on: (in category 'building') -----
+ drawMinorGridFrom: p1 to: p2 on: aCanvas
+ 
+ 	((gridForm boundingBox containsPoint: p1) and: [gridForm boundingBox containsPoint: p2])
+ 		ifFalse: [^self].
+ 	aCanvas
+ 				line: p1
+ 				to: p2
+ 				width: 1
+ 				color: minorGridColor 
+ 				stepWidth: 1
+ 				secondWidth: 1
+ 				secondColor: backgroundColor
+ 				secondStepWidth: 6!

Item was added:
+ ----- Method: CartesianGraphMorph>>xMax (in category 'accessing cartesian bounds') -----
+ xMax
+ ^self cartesianBounds right!

Item was added:
+ ----- Method: SpeechBubbleMorph>>defaultColor (in category 'accessing') -----
+ defaultColor
+ 	^Color white!

Item was added:
+ ----- Method: SpeechBubbleMorph>>minimumAcceptedHeight (in category 'accessing') -----
+ minimumAcceptedHeight
+ ^100 max: self msgMorph fullBounds height + 20 + self tailHeight!

Item was added:
+ ----- Method: SpeechBubbleMorph>>privatePosition: (in category 'private') -----
+ privatePosition: aPoint
+ "Always changes the position, regardless of the target"
+ super position: aPoint!

Item was added:
+ ----- Method: SpeechBubbleMorph>>minimumStepTime (in category 'stepping') -----
+ minimumStepTime
+ 	^20!

Item was added:
+ ----- Method: Player>>getMyInitialPointX (in category '*Etoys-graphing') -----
+ getMyInitialPointX
+ ^ self getValueFromCostume: #initialPointX!

Item was added:
+ ----- Method: DataGraphMorph>>vectorAt:ifAbsent: (in category 'accessing vectors') -----
+ vectorAt: index ifAbsent: aBlock
+ | m |
+ m := vectorMorphs at: index ifAbsent: [nil].
+ ^m ifNil: [aBlock value]
+ !

Item was added:
+ ----- Method: BarGraphMorph>>placeAxes (in category 'building') -----
+ placeAxes
+ 	| axisPos |
+ 	self isVerticalGraph 
+ 		ifTrue: [axisPos := self axisXPos @ (self cartesianYToPixel: 0).]
+ 		ifFalse: [axisPos := (self cartesianXToPixel: 0) @ self axisYPos.].
+ 
+ 	verticalAxis vertices at: 1 put: axisPos x @ self bottom.
+ 	verticalAxis vertices at: 2 put: axisPos x @ self top.
+ 	verticalAxis borderColor: axisColor.
+ 	verticalAxis computeBounds.
+ 	horizontalAxis vertices at: 1 put: self left @ axisPos y.
+ 	horizontalAxis vertices at: 2 put: self right @ axisPos y.
+ 	horizontalAxis borderColor: axisColor.
+ 	horizontalAxis computeBounds!

Item was added:
+ ----- Method: PointMorph>>pointY (in category 'accessing') -----
+ pointY
+ ^self point y!

Item was added:
+ ----- Method: PointMorph>>color: (in category 'accessing') -----
+ color: aColor
+ 	"Set the receiver's color.  Directly set the color if appropriate, else go by way of fillStyle"
+ 
+ 	(aColor isColor or: [aColor isKindOf: InfiniteForm]) ifFalse:[^ self fillStyle: aColor].
+ 	color = aColor ifFalse:
+ 		[self removeProperty: #fillStyle.
+ 		color _ aColor.
+ 		self changed].
+ 	self initializeForm!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>new (in category 'instance creation') -----
+ new
+ 	^self string: 'Hello world!!'!

Item was added:
+ ----- Method: DataGraphMorph>>vectorColorAt: (in category 'accessing vectors') -----
+ vectorColorAt: index
+ ^(vectorMorphs at: index) color!

Item was added:
+ ----- Method: Player>>setInitialPointX: (in category '*Etoys-graphing') -----
+ setInitialPointX: aNumber
+ | current |
+ current := self currentVector.
+ current isNil ifTrue: [^self].
+ current initialPointX: aNumber!

Item was added:
+ ----- Method: CartesianGraphMorph>>cartesianYToRelativePixel: (in category 'calculations') -----
+ cartesianYToRelativePixel: aNumber
+ 	^ (self height - (aNumber - cartesianBounds top * bounds height / cartesianBounds height)) rounded.
+ !

Item was added:
+ ----- Method: CartesianGraphMorph>>cartesianPointToRelativePixel: (in category 'calculations') -----
+ cartesianPointToRelativePixel: aPoint
+ ^(self cartesianXToRelativePixel: aPoint x) @ (self cartesianYToRelativePixel: aPoint y)!

Item was added:
+ ----- Method: DataGraphMorph>>removeVectorAt: (in category 'accessing vectors') -----
+ removeVectorAt: index
+ 	| m |
+ 	m := vectorMorphs at: index ifAbsent: [^self error: 'Vector not found'].
+ 	m delete.
+ 	vectorMorphs removeAt: index.
+ !

Item was added:
+ ----- Method: Player>>getAxisColor (in category '*Etoys-graphing') -----
+ getAxisColor 
+ ^ self getValueFromCostume: #axisColor!

Item was added:
+ ----- Method: VectorMorph>>initialize (in category 'initialize-release') -----
+ initialize
+ super initialize.
+ self makeOpen.
+ vertices := Array with: 0 at 0 with: 0 at 0.
+ arrows := #forward.
+ self arrowSpec: 4 at 3; color: Color blue.
+ self update!

Item was added:
+ ----- Method: Player>>getMinorGridColor (in category '*Etoys-graphing') -----
+ getMinorGridColor
+ ^ self getValueFromCostume: #minorGridColor!

Item was added:
+ ----- Method: Player>>getMyBarLabel (in category '*Etoys-graphing') -----
+ getMyBarLabel
+ ^self getValueFromCostume: #barLabel!

Item was added:
+ ----- Method: DataGraphMorph>>initializeVectors (in category 'initialize') -----
+ initializeVectors
+ vectorMorphs := OrderedCollection new !

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>bottomRightCornerForm (in category 'forms') -----
+ bottomRightCornerForm
+ ^(self topLeftCornerForm flipBy: #horizontal centerAt: self topLeftCornerForm boundingBox leftCenter) flipBy: #vertical centerAt: self topLeftCornerForm boundingBox topCenter!

Item was added:
+ ----- Method: PointMorph>>pointY: (in category 'accessing') -----
+ pointY: aNumber
+ self point: self pointX @ aNumber!

Item was added:
+ ----- Method: Player>>setMin: (in category '*Etoys-graphing') -----
+ setMin: aNumber
+ self setCostumeSlot: #min: toValue: aNumber!

Item was added:
+ ----- Method: BarGraphMorph>>graphDirection (in category 'accessing') -----
+ graphDirection
+ ^graphDirection!

Item was added:
+ ----- Method: Player>>sayObject: (in category '*Etoys-SpeechBubbles') -----
+ sayObject: aPlayer
+ self costume renderedMorph sayObject: aPlayer!

Item was added:
+ ----- Method: BarMorph>>update: (in category 'initialize-release') -----
+ update: newIndex
+ index := newIndex.
+ self penUpWhile: [self barValue: value].
+ !

Item was added:
+ ----- Method: BarTableMorph>>makeListWithData: (in category 'building') -----
+ makeListWithData: data
+ 	list := AlignmentMorph newColumn color: Color transparent.
+ 	1 to: numberOfRows do: [:i| 
+ 		list addMorphBack: (self makeRow: (data at: i ifAbsent: [nil]))].
+ 	scrollPane := ScrollPane new extent: (self textMorphWidth * 2 ) + 40 at 281; borderWidth: 0.
+ 	scrollPane scroller addMorph: list.
+ 	data isEmpty ifFalse: [scrollPane vSetScrollDelta].
+ 	^scrollPane!

Item was added:
+ CartesianGraphMorph subclass: #DataGraphMorph
+ 	instanceVariableNames: 'vectorMorphs pointMorphs'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Etoys-Graphing'!
+ 
+ !DataGraphMorph commentStamp: 'Richo 5/21/2010 08:57' prior: 0!
+ This class is responsible of drawing points and vectors in a cartesian coordinate system.
+ 
+ To add points use the following protocol:
+ 	#pointAt:
+ 	#pointAt:put:
+ 	#removePointAt:
+ 	#removeAllPoints
+ 	
+ To add vectors use the following protocol:
+ 	#addVector:
+ 	#vectorAt:
+ 	#vectorAt:put:
+ 	#removeVector:
+ 	#removeVectorAt:
+ 	#removeAllVectors
+ 	
+ For more information, see the "examples" category at the class side.
+ 
+ !

Item was added:
+ ----- Method: Player>>setBarIndex: (in category '*Etoys-graphing') -----
+ setBarIndex: aNumber 
+ self getBarCount = 0 ifTrue: [^self].
+ self barIndex: aNumber - 1 \\ self getBarCount + 1!

Item was added:
+ ----- Method: DataGraphMorph>>vectorColorAt:put: (in category 'accessing vectors') -----
+ vectorColorAt: index put: aColor
+ (vectorMorphs at: index) color: aColor!

Item was added:
+ ----- Method: BarGraphMorph>>barLabelAt:put: (in category 'accessing bars') -----
+ barLabelAt: barIndex put: aString
+ | current |
+ current := self barAt: barIndex ifAbsent: [^self].
+ current barLabel: aString!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>topLeftCornerForm (in category 'forms') -----
+ topLeftCornerForm
+ "
+ topLeftCornerForm := nil
+ (SketchMorph withForm: topLeftCornerForm) openInHand
+ "
+ ^topLeftCornerForm ifNil: [topLeftCornerForm := (Form
+ 	extent: 25 at 25
+ 	depth: 16
+ 	fromArray: #( 0 0 0 0 0 0 0 1 65537 65537 65537 65537 65536 0 0 0 0 0 1 65537 65537 65537 65537 65537 65537 65536 0 0 0 0 1 65537 65537 65537 2147450879 2147450879 2147450879 2147450879 2147418112 0 0 0 1 65537 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 0 0 0 65537 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 0 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 0 1 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 1 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 1 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 1 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418112)
+ 	offset: 0 at 0)]!

Item was added:
+ ----- Method: Player>>getBubble (in category '*Etoys-SpeechBubbles') -----
+ getBubble
+ ^[self costume renderedMorph bubble assuredPlayer] on: Error do: [self presenter standardPlayer]!

Item was added:
+ ----- Method: Player>>getRowsFilled (in category '*Etoys-graphing') -----
+ getRowsFilled
+ ^ self getValueFromCostume: #rowsFilled!

Item was added:
+ ----- Method: Player>>removeCurrentBar (in category '*Etoys-graphing') -----
+ removeCurrentBar
+ | barIndex |
+ barIndex := self getBarIndex.
+ barIndex = 0 ifTrue: [^self].
+ self sendMessageToCostume: #removeBarAt: with: barIndex.
+ self setBarIndex: barIndex - 1!

Item was added:
+ ----- Method: VectorMorph classSide>>additionsToViewerCategories (in category 'viewer categories') -----
+ additionsToViewerCategories
+ ^ #(
+ (#plot (
+ #(command remove '' )
+ #(slot initialPointX '' Number readWrite Player getMyInitialPointX Player setMyInitialPointX:  )
+ #(slot initialPointY '' Number readWrite Player getMyInitialPointY Player setMyInitialPointY:  )
+ #(slot terminalPointX '' Number readWrite Player getMyTerminalPointX Player setMyTerminalPointX:  )
+ #(slot terminalPointY '' Number readWrite Player getMyTerminalPointY Player setMyTerminalPointY:  )
+ #(slot vectorAngle '' Number readWrite Player getMyVectorAngle Player setMyVectorAngle:  )
+ #(slot vectorColor '' Color readWrite Player getMyVectorColor Player setMyVectorColor:  )
+ #(slot vectorMagnitude '' Number readWrite Player getMyVectorMagnitude Player setMyVectorMagnitude:  )
+ ))
+ 
+ )!

Item was added:
+ ----- Method: DataGraphMorph>>removeVector: (in category 'accessing vectors') -----
+ removeVector: aVector 
+ 	| v |
+ 	v := vectorMorphs select: [:each| each = aVector].
+ 	v isEmpty ifTrue: [^self error: 'Vector not found'].
+ 	vectorMorphs remove: v anyOne delete.!

Item was added:
+ ----- Method: BarGraphMorph>>distanceBetweenBars (in category 'accessing bars') -----
+ distanceBetweenBars
+ ^distanceBetweenBars!

Item was added:
+ ----- Method: CartesianGraphMorph classSide>>additionsToViewerCategoryPlotLegends (in category 'viewer categories') -----
+ additionsToViewerCategoryPlotLegends
+ ^#(#'plot - legends' (
+ #(slot xSpacing '' Number readWrite Player getXLegendSpacing Player setXLegendSpacing:  )
+ #(slot ySpacing '' Number readWrite Player getYLegendSpacing Player setYLegendSpacing:  )
+ ))!

Item was added:
+ ----- Method: CartesianGraphMorph classSide>>additionsToViewerCategoryPlotGrid (in category 'viewer categories') -----
+ additionsToViewerCategoryPlotGrid
+ ^#(#'plot - grid' (
+ #(slot xMajorGrid '' Number readWrite Player getXMajorGrid Player setXMajorGrid:  )
+ #(slot xMinorGrid '' Number readWrite Player getXMinorGrid Player setXMinorGrid:  )
+ #(slot yMajorGrid '' Number readWrite Player getYMajorGrid Player setYMajorGrid:  )
+ #(slot yMinorGrid '' Number readWrite Player getYMinorGrid Player setYMinorGrid:  )
+ #(command restoreDefaultGrids '' )
+ ))!

Item was added:
+ ----- Method: CartesianGraphMorph>>controlGriddingParameter: (in category 'controlling errors') -----
+ controlGriddingParameter: aPoint
+ | |
+ (aPoint x isInteger and: [aPoint y isInteger]) ifFalse: [^self error: 'Gridding parameters must be natural numbers'].
+ (aPoint x < 0 or: [aPoint y < 0]) ifTrue: [^self error: 'Gridding parameters must be natural numbers'].!

Item was added:
+ ----- Method: BarGraphMorph>>removeBar: (in category 'accessing bars') -----
+ removeBar: aBarMorph
+ 	| m |
+ 	m := barMorphs select: [:each| each = aBarMorph].
+ 	m isEmpty ifTrue: [^self error: 'Bar not found'].
+ 	barMorphs remove: m anyOne delete.
+ 	self updateBars!

Item was added:
+ ----- Method: Player>>getMajorGrid (in category '*Etoys-graphing') -----
+ getMajorGrid
+ ^ self  sendMessageToCostume: #majorGrid!

Item was added:
+ ----- Method: Player>>addPoint (in category '*Etoys-graphing') -----
+ addPoint
+ self sendMessageToCostume: #addPoint.
+ self setPointIndex: (self getPointCount ifNil: [^self])!

Item was added:
+ ----- Method: CartesianGraphMorph>>initializeCartesianBounds (in category 'initialize-release') -----
+ initializeCartesianBounds
+ cartesianBounds := -1 at -1 corner: 19 at 19.!

Item was added:
+ ----- Method: BarTableMorph>>apply (in category 'actions') -----
+ apply
+ | newRows oldBar newBar |
+ newRows := self rows.
+ 1 to: newRows size do: [:i|
+ 	oldBar := graph barAt: i ifAbsent: [nil].
+ 	newBar := newRows at: i.
+ 	oldBar isNil
+ 	ifTrue: [graph addBar: (BarMorph graph: graph label: newBar key value: newBar value index: graph barCount + 1)]
+ 	ifFalse: [oldBar barLabel: newBar key; barValue: newBar value]
+ 	].
+ newRows size < graph barCount
+ 	ifTrue: [graph removeBarsFrom: newRows size + 1 to: graph barCount].!

Item was added:
+ ----- Method: BarGraphMorph>>distanceBetweenBars: (in category 'accessing bars') -----
+ distanceBetweenBars: aNumber
+ distanceBetweenBars := aNumber.
+ self updateBars!

Item was added:
+ ----- Method: VectorMorph>>initialPointX: (in category 'accessing') -----
+ initialPointX: aNumber
+ | angle magnitude |
+ angle := self angle.
+ magnitude := self magnitude.
+ initialPoint := aNumber @ initialPoint y.
+ self angle: angle; magnitude: magnitude!

Item was added:
+ ----- Method: PointMorph>>privateCenter: (in category 'private') -----
+ privateCenter: aPoint
+ self privatePosition: (aPoint - (self extent // 2))!

Item was added:
+ ----- Method: Player>>vectorIndex (in category '*Etoys-graphing') -----
+ vectorIndex
+ ^self costume renderedMorph valueOfProperty: #vectorIndex ifAbsent: [self getVectorCount > 0 ifTrue: [1] ifFalse: [0]].!

Item was added:
+ Morph subclass: #SpeechBubbleMorph
+ 	instanceVariableNames: 'type balloon tail target lastHash stepTime msgMorph'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Etoys-SpeechBubbles'!
+ SpeechBubbleMorph class
+ 	instanceVariableNames: 'speakingForm topLeftCornerForm thinkingForm'!
+ SpeechBubbleMorph class
+ 	instanceVariableNames: 'speakingForm topLeftCornerForm thinkingForm'!

Item was added:
+ ----- Method: BarGraphMorph>>barColorAt: (in category 'accessing bars') -----
+ barColorAt: index
+ | current |
+ current := self barAt: index ifAbsent: [^Color black].
+ ^current color!

Item was added:
+ ----- Method: SpeechBubbleMorph>>position: (in category 'accessing') -----
+ position: aPoint
+ target notNil ifTrue: [^self positionMyselfAccordingToTarget ].
+ super position: aPoint.!

Item was added:
+ ----- Method: SpeechBubbleMorph>>positionBalloon (in category 'initialize-release') -----
+ positionBalloon
+ self balloon position: self position!

Item was added:
+ ----- Method: Player>>getMinorGrid (in category '*Etoys-graphing') -----
+ getMinorGrid
+ ^ self  sendMessageToCostume: #minorGrid!

Item was added:
+ ----- Method: Morph>>think: (in category '*Etoys-SpeechBubbles') -----
+ think: aString
+ self showMessage: aString inBubbleType: #thought!

Item was added:
+ ----- Method: PointTableMorph>>rowCount (in category 'accessing') -----
+ rowCount
+ ^( self list submorphs select: [:each| each isAlignmentMorph and: [each submorphs first isTextMorph]]) size!

Item was added:
+ ----- Method: BarMorph>>privateCenter: (in category 'private') -----
+ privateCenter: aPoint
+ self privatePosition: (aPoint - (self extent // 2))!

Item was added:
+ ----- Method: CartesianGraphMorph>>cartesianXToPixel: (in category 'calculations') -----
+ cartesianXToPixel: aNumber
+ 	^ (bounds left + (aNumber - cartesianBounds left * bounds width / cartesianBounds width)) rounded.
+ !

Item was added:
+ ----- Method: DataGraphMorph>>vectorCount (in category 'accessing vectors') -----
+ vectorCount
+ 	^vectorMorphs size!

Item was added:
+ ----- Method: Player>>setShowCursorPosition: (in category '*Etoys-graphing') -----
+ setShowCursorPosition: aBoolean
+ ^ self setCostumeSlot: #showCursorPosition: toValue: aBoolean!

Item was added:
+ ----- Method: PointTableMorph>>addRow (in category 'actions') -----
+ addRow
+ 	| |
+ 	numberOfRows := numberOfRows + 1.
+ "	self resetData."
+ 	list addMorph: (self makeRow: nil)   asElementNumber: numberOfRows + 1.
+ 	self updateScrollPane.!

Item was added:
+ ----- Method: Player>>setInitialPointY: (in category '*Etoys-graphing') -----
+ setInitialPointY: aNumber
+ | current |
+ current := self currentVector.
+ current isNil ifTrue: [^self].
+ current initialPointY: aNumber!

Item was added:
+ ----- Method: Player>>removeAllBars (in category '*Etoys-graphing') -----
+ removeAllBars
+ self barIndex: 0.
+ ^ self sendMessageToCostume: #removeAllBars!

Item was added:
+ ----- Method: PointTableMorph>>makeListWithData: (in category 'building') -----
+ makeListWithData: data
+ 	list := AlignmentMorph newColumn color: Color transparent.
+ 	1 to: numberOfRows do: [:i| 
+ 		list addMorphBack: (self makeRow: (data at: i ifAbsent: [nil]))].
+ 	scrollPane := ScrollPane new extent:  (self textMorphWidth * 2) + 40 @281; borderWidth: 0.
+ 	scrollPane scroller addMorph: list.
+ 	data isEmpty ifFalse: [scrollPane vSetScrollDelta].
+ 	^scrollPane!

Item was added:
+ ----- Method: BarMorph>>privateExtent: (in category 'private') -----
+ privateExtent: aPoint
+ super extent: aPoint!

Item was added:
+ ----- Method: DataGraphMorph classSide>>defaultNameStemForInstances (in category 'parts bin') -----
+ defaultNameStemForInstances
+ 	^ 'Graph' !

Item was added:
+ ----- Method: SpeechBubbleMorph>>maximumStepTime (in category 'stepping') -----
+ maximumStepTime
+ 	^500!

Item was added:
+ ----- Method: Player>>removeRow (in category '*Etoys-graphing') -----
+ removeRow
+ ^self sendMessageToCostume: #removeRow!

Item was added:
+ RectangleMorph subclass: #BarMorph
+ 	instanceVariableNames: 'graph label value index labelMorph'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Etoys-Graphing'!

Item was added:
+ ----- Method: Player>>thinkGraphic: (in category '*Etoys-SpeechBubbles') -----
+ thinkGraphic: aGraphic
+ self costume renderedMorph thinkGraphic: aGraphic!

Item was added:
+ ----- Method: SpeechBubbleMorph>>form (in category 'accessing') -----
+ form
+ ^(msgMorph isKindOf: SketchMorph) ifTrue: [msgMorph form]!

Item was added:
+ ----- Method: Player>>setAxisColor: (in category '*Etoys-graphing') -----
+ setAxisColor: aColor
+ ^ self setCostumeSlot: #axisColor: toValue: aColor!

Item was added:
+ ----- Method: Player>>setPointIndex: (in category '*Etoys-graphing') -----
+ setPointIndex: aNumber 
+ self getPointCount = 0 ifTrue: [^self].
+ self pointIndex: aNumber - 1 \\ self getPointCount + 1!

Item was added:
+ ----- Method: BarGraphMorph>>removeAllBars (in category 'accessing bars') -----
+ removeAllBars
+ 	barMorphs do: [:each| each delete].
+ 	self initializeBars!

Item was added:
+ ----- Method: Player>>getPointsFilled (in category '*Etoys-graphing') -----
+ getPointsFilled
+ ^ self getValueFromCostume: #pointsFilled!

Item was added:
+ ----- Method: Player>>setYMax: (in category '*Etoys-graphing') -----
+ setYMax: aNumber
+ self setCostumeSlot: #yMax: toValue: aNumber!

Item was added:
+ ----- Method: CartesianGraphMorph>>xLegendSpacing: (in category 'accessing legends') -----
+ xLegendSpacing: aNumber
+ self legendSpacing: ((aNumber max: 0) rounded  @ self legendSpacing y)!

Item was added:
+ ----- Method: Player>>getRowValue (in category '*Etoys-graphing') -----
+ getRowValue
+ ^self sendMessageToCostume: #rowValueAt: with: self getRowIndex!

Item was added:
+ AlignmentMorph subclass: #PointTableMorph
+ 	instanceVariableNames: 'graph list scrollPane numberOfRows'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Etoys-Graphing'!
+ 
+ !PointTableMorph commentStamp: 'Richo 4/17/2010 23:33' prior: 0!
+ This object is a table of points whose purpose is let the user fill the DataGraphMorph with points. !

Item was added:
+ ----- Method: Player>>openPointTable (in category '*Etoys-graphing') -----
+ openPointTable
+ ^ self sendMessageToCostume: #openPointTable!

Item was added:
+ ----- Method: DataGraphMorph classSide>>includeInNewMorphMenu (in category 'new-morph participation') -----
+ includeInNewMorphMenu
+ 	"Return true for all classes that can be instantiated from the menu"
+ 	^ true!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>topRightCornerForm (in category 'forms') -----
+ topRightCornerForm
+ ^self topLeftCornerForm flipBy: #horizontal centerAt:  self topLeftCornerForm boundingBox leftCenter!

Item was added:
+ ----- Method: Player>>getRowX (in category '*Etoys-graphing') -----
+ getRowX
+ ^self sendMessageToCostume: #rowXAt: with: self getRowIndex!

Item was added:
+ ----- Method: CartesianGraphMorph>>cartesianBounds (in category 'accessing cartesian bounds') -----
+ cartesianBounds
+ ^cartesianBounds!

Item was added:
+ ----- Method: PointTableMorph>>rows (in category 'accessing') -----
+ rows
+ "Searches across the submorphs and returns an array of points with the data written by the user"
+ 	| data x y firstSubmorph secondSubmorph |
+ 	data := OrderedCollection new.
+ 	list
+ 		submorphsDo: [:morph | morph isAlignmentMorph
+ 				ifTrue: [
+ 					x := y := nil.
+ 					firstSubmorph := morph submorphs first.
+ 					secondSubmorph := morph submorphs second.
+ 					firstSubmorph isTextMorph
+ 						ifTrue: [firstSubmorph contents asString = ''
+ 								ifFalse: [x := firstSubmorph getNumericValue]].
+ 					secondSubmorph isTextMorph
+ 						ifTrue: [secondSubmorph contents asString = ''
+ 								ifFalse: [y := secondSubmorph getNumericValue]].
+ 					(x isNumber
+ 							and: [y isNumber])
+ 						ifTrue: [data add: x @ y]]].
+ 	^ data!

Item was added:
+ ----- Method: PointTableMorph>>updateScrollPane (in category 'actions') -----
+ updateScrollPane
+ 	scrollPane vScrollBarValue: 1; vSetScrollDelta!

Item was added:
+ ----- Method: CartesianGraphMorph>>restoreInitialPosition (in category 'accessing cartesian bounds') -----
+ restoreInitialPosition
+ self initializeCartesianBounds; update
+ !

Item was added:
+ ----- Method: BarGraphMorph>>placeYLegends (in category 'building') -----
+ placeYLegends
+ self isVerticalGraph 
+ 	ifFalse: [(legends at: #y) do: [:each | each delete].
+ 		legends at: #y put: OrderedCollection new.
+ 		^self].
+ self placeYLegendsIncludeZero!

Item was added:
+ ----- Method: Player>>setXMin: (in category '*Etoys-graphing') -----
+ setXMin: aNumber
+ self setCostumeSlot: #xMin: toValue: aNumber!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>string:type:for: (in category 'instance creation') -----
+ string: aString type: aSymbol for: aMorph
+ "self string: 'Hello world!!' type: #speech for: Morph new openInHand"
+ ^(self string: aString type: aSymbol) target: aMorph!

Item was added:
+ ----- Method: Player>>setMyPointColor: (in category '*Etoys-graphing') -----
+ setMyPointColor: aColor
+ ^ self setCostumeSlot: #color: toValue: aColor
+ !

Item was added:
+ ----- Method: Player>>getPlayerAtBarIndex (in category '*Etoys-graphing') -----
+ getPlayerAtBarIndex
+ | current |
+ current := self currentBar.
+ ^current isNil ifTrue: [self presenter standardPlayer] ifFalse: [current assuredPlayer]
+ !

Item was added:
+ ----- Method: SpeechBubbleMorph>>fillStyle: (in category 'accessing') -----
+ fillStyle: aFillStyle
+ 	super fillStyle: aFillStyle.
+ 	self refresh!

Item was added:
+ ----- Method: BarGraphMorph>>barCount (in category 'accessing bars') -----
+ barCount
+ ^barMorphs size!

Item was added:
+ ----- Method: Player>>attachTo: (in category '*Etoys-SpeechBubbles') -----
+ attachTo: aPlayer
+ self sendMessageToCostume: #target: with: aPlayer costume renderedMorph
+ !

Item was added:
+ ----- Method: BarGraphMorph>>updateBars (in category 'updating') -----
+ updateBars
+ | index |
+ index := 0.
+ barMorphs do: [:each| each update: (index := index + 1)].
+ self changed!

Item was added:
+ ----- Method: BarGraphMorph>>graphDirection: (in category 'accessing') -----
+ graphDirection: aSymbol
+ "graphDirection must be either #vertical or #horizontal"
+ graphDirection := aSymbol.
+ self updateAll !

Item was added:
+ ----- Method: Player>>setMinorGrid: (in category '*Etoys-graphing') -----
+ setMinorGrid: aNumber
+ ^ self setCostumeSlot: #minorGrid: toValue: (aNumber max: 0) rounded!

Item was added:
+ ----- Method: PointMorph>>initialize (in category 'initialize-release') -----
+ initialize
+ 	super initialize.
+ 	self color: Color red; initializeForm; update!

Item was added:
+ ----- Method: CartesianGraphMorph>>initializeGrids (in category 'initialize-release') -----
+ initializeGrids
+ minorGrid := 1 at 1.
+ majorGrid := 5 at 5.
+ self initializeGridForm; drawGridForm!

Item was added:
+ ----- Method: CartesianGraphMorph>>majorGrid (in category 'accessing grid') -----
+ majorGrid
+ ^majorGrid!

Item was added:
+ ----- Method: DataGraphMorph>>openPointTable (in category 'actions') -----
+ openPointTable
+ (PointTableMorph on: self) openInHand!

Item was added:
+ ----- Method: Player>>getPlayerAtPointIndex (in category '*Etoys-graphing') -----
+ getPlayerAtPointIndex
+ | current |
+ current := self currentPoint.
+ ^current isNil ifTrue: [self presenter standardPlayer] ifFalse: [current assuredPlayer]
+ !

Item was added:
+ ----- Method: BarGraphMorph>>initializeBars (in category 'initialize-release') -----
+ initializeBars
+ barMorphs := OrderedCollection new.!

Item was added:
+ ----- Method: Player>>setMajorGrid: (in category '*Etoys-graphing') -----
+ setMajorGrid: aNumber
+ ^ self setCostumeSlot:  #majorGrid: toValue: (aNumber max: 0) rounded!

Item was added:
+ ----- Method: SpeechBubbleMorph>>refreshBalloon (in category 'refreshing') -----
+ refreshBalloon
+ 	balloon ifNotNil: [balloon delete].
+ 	balloon := nil.
+ 	self positionBalloon.
+ 	self addMorph: balloon!

Item was added:
+ ----- Method: Player>>openBarTable (in category '*Etoys-graphing') -----
+ openBarTable
+  self sendMessageToCostume: #openBarTable!

Item was added:
+ ----- Method: CartesianGraphMorph>>restoreDefaultGrids (in category 'accessing grid') -----
+ restoreDefaultGrids
+ self initializeGrids; updateBackground!

Item was added:
+ ----- Method: BarTableMorph>>initialize (in category 'initialize') -----
+ initialize
+ 	| data |
+ 	super initialize.
+ 	self borderWidth: 0;
+ 		
+ 		color: ((Color
+ 				r: 0.817
+ 				g: 0.864
+ 				b: 0.797)
+ 				mixed: 0.75
+ 				with: Color blue muchDarker);
+ 		 hResizing: #shrinkWrap;
+ 		 vResizing: #shrinkWrap;
+ 		 listDirection: #topToBottom;
+ 		 cornerStyle: #rounded.
+ 	data := graph bars collect: [:each | each barLabel -> each barValue].
+ 	numberOfRows := data size max: 10.
+ 	self initializeSubmorphsWithData: data!

Item was added:
+ ----- Method: CartesianGraphMorph>>drawMajorGridFrom:to:on: (in category 'building') -----
+ drawMajorGridFrom: p1 to: p2 on: aCanvas.
+ 	((gridForm boundingBox containsPoint: p1) and: [gridForm boundingBox containsPoint: p2])
+ 		ifFalse: [^self].
+ 	aCanvas
+ 				line: p1
+ 				to: p2
+ 				width: 1
+ 				color: majorGridColor 
+ 				stepWidth: 2
+ 				secondWidth: 1
+ 				secondColor: backgroundColor
+ 				secondStepWidth: 2!

Item was added:
+ ----- Method: Player>>setVectorAngle: (in category '*Etoys-graphing') -----
+ setVectorAngle: aNumber
+ | current |
+ current := self currentVector.
+ current isNil ifTrue: [^self].
+ current angle: aNumber!

Item was added:
+ ----- Method: BarTableMorph classSide>>on: (in category 'instance creation') -----
+ on: aDataGraphMorph
+ ^(self basicNew setGraph: aDataGraphMorph) initialize !

Item was added:
+ ----- Method: PointMorph>>remove (in category 'initialize-release') -----
+ remove
+ 	graph removePoint: self!

Item was added:
+ ----- Method: BarGraphMorph>>openBarTable (in category 'actions') -----
+ openBarTable
+ ^(BarTableMorph on: self) openInHand!

Item was added:
+ ----- Method: Morph>>thinkObject: (in category '*Etoys-SpeechBubbles') -----
+ thinkObject: aPlayer
+ self showObject: aPlayer inBubbleType: #thought!

Item was added:
+ ----- Method: BarTableMorph>>list (in category 'accessing') -----
+ list
+ 	^list!

Item was added:
+ ----- Method: SpeechBubbleMorph>>refreshTail (in category 'refreshing') -----
+ refreshTail
+ 	tail ifNotNil: [tail delete].
+ 	tail := nil.
+ 	self positionTail.
+ 	self addMorph: tail!

Item was added:
+ ----- Method: Morph class>>additionsToViewerCategorySpeechBubbles (in category '*Etoys-SpeechBubbles') -----
+ additionsToViewerCategorySpeechBubbles
+ 	^#(
+ 		#'speech bubbles' 
+ 		(
+ 			(command sayText: '' String)
+ 			(command thinkText: '' String)
+ 			(command sayNumber: '' Number)
+ 			(command thinkNumber: '' Number)
+ 			(command sayGraphic: '' Graphic)
+ 			(command thinkGraphic: '' Graphic)
+ 			(command sayObject: '' Player)
+ 			(command thinkObject: '' Player)
+ 			(command stopSayingOrThinking '')
+ 			(slot bubble '' Player readOnly Player getBubble Player unused)		
+ 		))!

Item was changed:
  SystemOrganization addCategory: #'EToys-Kedama'!
  SystemOrganization addCategory: #'Etoys-Buttons'!
  SystemOrganization addCategory: #'Etoys-CustomEvents'!
  SystemOrganization addCategory: #'Etoys-Experimental'!
  SystemOrganization addCategory: #'Etoys-Help'!
  SystemOrganization addCategory: #'Etoys-Outliner'!
  SystemOrganization addCategory: #'Etoys-Protocols'!
  SystemOrganization addCategory: #'Etoys-Protocols-Type Vocabularies'!
  SystemOrganization addCategory: #'Etoys-Scratch'!
  SystemOrganization addCategory: #'Etoys-Scripting'!
  SystemOrganization addCategory: #'Etoys-Scripting Support'!
  SystemOrganization addCategory: #'Etoys-Scripting Tiles'!
  SystemOrganization addCategory: #'Etoys-Stacks'!
  SystemOrganization addCategory: #'Etoys-StarSqueak'!
  SystemOrganization addCategory: #'Etoys-Tile Scriptors'!
  SystemOrganization addCategory: #'Etoys-Widgets'!
+ SystemOrganization addCategory: #'Etoys-SpeechBubbles'!
+ SystemOrganization addCategory: #'Etoys-Graphing'!

Item was added:
+ ----- Method: Player>>getLegendSpacing (in category '*Etoys-graphing') -----
+ getLegendSpacing
+ ^ self sendMessageToCostume: #legendSpacing!

Item was added:
+ ----- Method: BarTableMorph>>rowsFilled (in category 'accessing') -----
+ rowsFilled
+ ^self rows size!

Item was added:
+ ----- Method: PointMorph>>pointX (in category 'accessing') -----
+ pointX
+ ^self point x!

Item was added:
+ ----- Method: PointTableMorph>>newTextMorph (in category 'building') -----
+ newTextMorph
+ 	^TextMorph new autoFit: false;
+ 		 extent: self textMorphWidth @ 23;
+ 		 borderWidth: 1;
+ 		 backgroundColor: Color white;
+ 		crPassesFocus: true;
+ 		highlightsOnFocus: true;
+ 		yourself!

Item was added:
+ ----- Method: Player>>setBarLabel: (in category '*Etoys-graphing') -----
+ setBarLabel: aString
+ | selector |
+ selector := #barLabelAt:put:.
+ (self costumeRespondingTo: selector) ifNotNilDo: [:c | c perform: selector withArguments: {self getBarIndex. aString}]!

Item was added:
+ ----- Method: CartesianGraphMorph>>xMinorGrid: (in category 'accessing grid') -----
+ xMinorGrid: aNumber
+ self minorGrid: (aNumber max: 0) rounded @ self minorGrid y.!

Item was added:
+ ----- Method: BarMorph>>remove (in category 'initialize-release') -----
+ remove
+ 	graph removeBar: self!

Item was added:
+ ----- Method: Player>>addVector (in category '*Etoys-graphing') -----
+ addVector
+ 	self sendMessageToCostume: #addVector.
+ 	self vectorIndex: self getVectorCount!

Item was added:
+ ----- Method: Player>>setMyPointX: (in category '*Etoys-graphing') -----
+ setMyPointX: aNumber
+ ^ self setCostumeSlot: #pointX: toValue: aNumber
+ !

Item was added:
+ ----- Method: Player>>getTerminalPointY (in category '*Etoys-graphing') -----
+ getTerminalPointY
+ | current |
+ current := self currentVector.
+ ^current isNil ifTrue: [nil] ifFalse: [current terminalPointY]!

Item was added:
+ ----- Method: SpeechBubbleMorph>>type (in category 'accessing') -----
+ type
+ ^type!

Item was added:
+ ----- Method: Player>>setDistanceBetweenBars: (in category '*Etoys-graphing') -----
+ setDistanceBetweenBars: aNumber
+ ^ self setCostumeSlot: #distanceBetweenBars: toValue: aNumber!

Item was added:
+ ----- Method: SpeechBubbleMorph>>extent: (in category 'accessing') -----
+ extent: aPoint
+ | width height |
+ width := aPoint x max: self minimumAcceptedWidth.
+ height := aPoint y max: self minimumAcceptedHeight.
+ super extent: width @ height.
+ self refresh.
+ target notNil ifTrue: [self positionMyselfAccordingToTarget]!

Item was added:
+ ----- Method: Player>>setYMajorGrid: (in category '*Etoys-graphing') -----
+ setYMajorGrid: aNumber
+ self setCostumeSlot: #yMajorGrid: toValue: aNumber!

Item was added:
+ ----- Method: Player>>setMyTerminalPointX: (in category '*Etoys-graphing') -----
+ setMyTerminalPointX: aNumber
+ self setCostumeSlot: #terminalPointX: toValue: aNumber
+ !

Item was added:
+ ----- Method: BarGraphMorph classSide>>additionsToViewerCategoryPlotLegends (in category 'viewer categories') -----
+ additionsToViewerCategoryPlotLegends
+ "This is just to override the #'plot - legends' category (notice the space after grid)"
+ ^#(#'plot - legends ' (
+ #(slot spacing '' Number readWrite Player getLegendSpacing Player setLegendSpacing:  )
+ ))!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>form:type: (in category 'instance creation') -----
+ form: aForm type: aSymbol
+ ^(self basicNew setMorph: (SketchMorph withForm: aForm) type: aSymbol) initialize!

Item was added:
+ ----- Method: CartesianGraphMorph>>xMajorGrid: (in category 'accessing grid') -----
+ xMajorGrid: aNumber
+ self majorGrid: (aNumber max: 0) rounded @ self majorGrid y.!

Item was added:
+ ----- Method: BarGraphMorph classSide>>additionsToViewerCategoryPlotGrid (in category 'viewer categories') -----
+ additionsToViewerCategoryPlotGrid
+ "This is just to override the #'plot - grid' category (notice the space after grid)"
+ ^#(#'plot - grid ' (
+ #(slot majorGrid '' Number readWrite Player getMajorGrid Player setMajorGrid:  )
+ #(slot minorGrid '' Number readWrite Player getMinorGrid Player setMinorGrid:  )
+ #(command restoreDefaultGrids '' )
+ ))!

Item was added:
+ ----- Method: Player>>getMyPointY (in category '*Etoys-graphing') -----
+ getMyPointY
+ ^ self getValueFromCostume: #pointY!

Item was added:
+ ----- Method: CartesianGraphMorph>>xMajorGrid (in category 'accessing grid') -----
+ xMajorGrid
+ ^self majorGrid x!

Item was added:
+ ----- Method: Player>>addBar (in category '*Etoys-graphing') -----
+ addBar
+ 	self  sendMessageToCostume: #addBar.
+ 	self setBarIndex: self getBarCount!

Item was added:
+ ----- Method: BarGraphMorph>>centerFor:index: (in category 'calculations') -----
+ centerFor: aNumber index: index
+ "Returns the correct center for a bar morph depending on its index and its value"
+ | x y |
+ self isVerticalGraph
+ ifTrue: [x := self axisXPos + (self distanceBetweenBars * index).
+ 	y := (self cartesianYToPixel: aNumber / 2) rounded]
+ ifFalse: [x := (self cartesianXToPixel: aNumber / 2) rounded.
+ 	y := self axisYPos - (self distanceBetweenBars * index)].
+ ^x at y!

Item was added:
+ ----- Method: BarTableMorph>>initializeSubmorphsWithData: (in category 'building') -----
+ initializeSubmorphsWithData: data 
+ 	"data should be a collection of points."
+ 	self addMorphBack: self makeColumnNames;
+ 		
+ 		addMorphBack: (self makeListWithData: data);
+ 		 addMorphBack: ((SimpleButtonMorph newWithLabel: '-') color: (Color
+ 				r: 0.4
+ 				g: 0.8
+ 				b: 0.6) lighter;
+ 			 borderWidth: 2;
+ 			 width: 129;
+ 			 target: self;
+ 			 actionSelector: #removeRow);
+ 		 addMorphBack: (Morph new color: Color transparent;
+ 			 extent: 10 @ 3);
+ 		 addMorphBack: ((SimpleButtonMorph newWithLabel: '+') color: (Color
+ 				r: 0.4
+ 				g: 0.8
+ 				b: 0.6) lighter;
+ 			 borderWidth: 2;
+ 			 width: 129;
+ 			 target: self;
+ 			 actionSelector: #addRow);
+ 		 addMorphBack: (Morph new color: Color transparent;
+ 			 extent: 10 @ 3);
+ 		 addMorphBack: ((SimpleButtonMorph newWithLabel: 'Apply') width: 129;
+ 			 target: self;
+ 			 actionSelector: #apply)!

Item was added:
+ ----- Method: BarGraphMorph>>placeYLegendsIncludeZero (in category 'building') -----
+ placeYLegendsIncludeZero
+ "Almost like super>>#placeYLegends but this includes the zero"
+ | index yLegends legendPos legend |
+ index := 0.
+ yLegends := legends at: #y.
+ cartesianBounds top ceiling to: cartesianBounds bottom floor do: [:y | 
+ 		| pos |
+ 		pos := self cartesianYToPixel: y.
+ 		(y isDivisibleBy: legendSpacing y)
+ 			ifTrue: [
+ 			legendPos := (self preferredPositionForYLegend: y asString at: pos).
+ 			legendPos notNil ifTrue: [
+ 				legend := yLegends at: (index := index + 1) ifAbsent: [yLegends add: StringMorph new].
+ 				self addMorph: legend.
+ 				legend contents: y asString; position: legendPos; color: axisColor]]].
+ yLegends isEmpty ifFalse: [
+ yLegends from: index + 1 to: yLegends size do: [:each| each delete].
+ yLegends removeLast: (yLegends size - index)]!

Item was added:
+ ----- Method: CartesianGraphMorph>>yMajorGrid (in category 'accessing grid') -----
+ yMajorGrid
+ ^self majorGrid y!

Item was added:
+ ----- Method: Player>>setMinorGridColor: (in category '*Etoys-graphing') -----
+ setMinorGridColor: aColor
+ ^ self setCostumeSlot: #minorGridColor: toValue: aColor!

Item was added:
+ ----- Method: SpeechBubbleMorph>>msgMorphExtent (in category 'accessing') -----
+ msgMorphExtent
+ ^self msgMorph fullBounds extent!

Item was added:
+ ----- Method: CartesianGraphMorph>>yLegendSpacing (in category 'accessing legends') -----
+ yLegendSpacing
+ ^self legendSpacing y!

Item was added:
+ ----- Method: VectorMorph>>color: (in category 'accessing') -----
+ color: aColor
+ 	self borderColor: aColor.
+ 	super color: aColor.!

Item was added:
+ ----- Method: VectorMorph>>terminalPointY: (in category 'accessing') -----
+ terminalPointY: aNumber
+ terminalPoint := terminalPoint x @ aNumber.
+ self update.!

Item was added:
+ ----- Method: Player>>getMyVectorMagnitude (in category '*Etoys-graphing') -----
+ getMyVectorMagnitude
+ ^ self getValueFromCostume: #magnitude!

Item was added:
+ ----- Method: Player>>setBarColor: (in category '*Etoys-graphing') -----
+ setBarColor: aColor
+ | selector |
+ selector := #barColorAt:put:.
+ (self costumeRespondingTo: selector) ifNotNilDo: [:c | c perform: selector withArguments: {self getBarIndex. aColor}]!

Item was added:
+ ----- Method: Player>>sayNumber: (in category '*Etoys-SpeechBubbles') -----
+ sayNumber: aNumber
+ self costume renderedMorph say: aNumber asString!

Item was added:
+ ----- Method: CartesianGraphMorph>>drawOn: (in category 'drawing') -----
+ drawOn: aCanvas
+ super drawOn: aCanvas.
+ aCanvas drawImage: gridForm at: bounds topLeft.
+ aCanvas frameRectangle: bounds color: self borderColor.!

Item was added:
+ ----- Method: Player>>setTerminalPointX: (in category '*Etoys-graphing') -----
+ setTerminalPointX: aNumber
+ | current |
+ current := self currentVector.
+ current isNil ifTrue: [^self].
+ current terminalPointX: aNumber!

Item was added:
+ ----- Method: CartesianGraphMorph>>xMinorGrid (in category 'accessing grid') -----
+ xMinorGrid
+ ^self minorGrid x!

Item was added:
+ ----- Method: Player>>getPointY (in category '*Etoys-graphing') -----
+ getPointY
+ | current |
+ current := self currentPoint.
+ ^current isNil ifTrue: [nil] ifFalse: [current pointY]!

Item was added:
+ ----- Method: CartesianGraphMorph>>yLegendSpacing: (in category 'accessing legends') -----
+ yLegendSpacing: aNumber
+ self legendSpacing: (self legendSpacing x @ (aNumber max: 0) rounded )!

Item was added:
+ ----- Method: BarGraphMorph>>range: (in category 'accessing range') -----
+ range: anInterval
+ self cartesianBounds: ((anInterval first @ anInterval first) corner: (anInterval last @ anInterval last)).!

Item was added:
+ ----- Method: PointTableMorph>>makeRow: (in category 'building') -----
+ makeRow: aPoint 
+ 	^ AlignmentMorph newRow color: Color transparent;
+ 		 addMorphBack: (self newTextMorph
+ 			contents: (aPoint isNil
+ 					ifTrue: ['']
+ 					ifFalse: [aPoint x isInteger ifFalse: [aPoint x printShowingDecimalPlaces: 2] ifTrue: [aPoint x asString]]);
+ 			 wrapFlag: true);
+ 		 addMorphBack: (self newTextMorph
+ 			contents: (aPoint isNil
+ 					ifTrue: ['']
+ 					ifFalse: [aPoint y isInteger ifFalse: [aPoint y printShowingDecimalPlaces: 2] ifTrue: [aPoint y asString]]);
+ 			 wrapFlag: true) !

Item was added:
+ ----- Method: PointMorph>>privatePosition: (in category 'private') -----
+ privatePosition: aPoint
+ ^super position: aPoint!

Item was added:
+ ----- Method: CartesianGraphMorph>>yMinorGrid (in category 'accessing grid') -----
+ yMinorGrid
+ ^self minorGrid y!

Item was added:
+ ----- Method: CartesianGraphMorph>>backgroundColor (in category 'accessing colors') -----
+ backgroundColor
+ ^backgroundColor!

Item was added:
+ ----- Method: BarGraphMorph>>axisXPos (in category 'calculations') -----
+ axisXPos
+ "Returns the horizontal position of the axis. It makes sure that the legends fit in this space"
+ | font |
+ font := TextStyle defaultFont.
+ ^self left + ((font widthOfString: self range last ceiling asString) max: (font widthOfString: self range first floor asString)) + 5!

Item was added:
+ ----- Method: Player>>setXLegendSpacing: (in category '*Etoys-graphing') -----
+ setXLegendSpacing: anInteger
+ self setCostumeSlot: #xLegendSpacing: toValue: anInteger !

Item was added:
+ ----- Method: BarGraphMorph>>addBar: (in category 'accessing bars') -----
+ addBar: aBarMorph
+ self addMorph: aBarMorph.
+ barMorphs add: aBarMorph.
+ self changed.
+ ^aBarMorph!

Item was added:
+ ----- Method: BarMorph>>barValue: (in category 'accessing') -----
+ barValue: aNumber
+ value := aNumber.
+ self privateExtent: (graph extentFor: value);
+ 		privateCenter: (graph centerFor: value index: index);
+ 		updateLabel.!

Item was added:
+ ----- Method: BarMorph>>privatePosition: (in category 'private') -----
+ privatePosition: aPoint
+ super position: aPoint!

Item was added:
+ ----- Method: VectorMorph>>angle (in category 'accessing') -----
+ angle
+ "Returns an angle in degrees from 0 to 360"
+ | angle diff | 
+ diff := terminalPoint - initialPoint.
+ diff x = 0 ifTrue: [diff y >= 0 ifTrue: [^90] ifFalse: [^270]].
+ angle := (diff y abs / diff x abs) arcTan radiansToDegrees.
+ diff x > 0 ifTrue: [
+ 	diff y >= 0 ifFalse: [angle := 360 - angle]
+ ]
+ ifFalse: [
+ 	diff y >= 0 ifTrue: [angle := 180 - angle] ifFalse: [angle := 180 + angle]
+ ].
+ ^angle!

Item was added:
+ ----- Method: Player>>rowIndex: (in category '*Etoys-graphing') -----
+ rowIndex: aNumber
+ self costume renderedMorph setProperty: #rowIndex toValue: aNumber.!

Item was added:
+ ----- Method: SpeechBubbleMorph>>stepTime (in category 'stepping') -----
+ stepTime
+ ^stepTime !

Item was added:
+ ----- Method: Player>>sayGraphic: (in category '*Etoys-SpeechBubbles') -----
+ sayGraphic: aGraphic
+ self costume renderedMorph sayGraphic: aGraphic!

Item was added:
+ ----- Method: Player>>restoreInitialPosition (in category '*Etoys-graphing') -----
+ restoreInitialPosition
+ ^ self sendMessageToCostume: #restoreInitialPosition !

Item was added:
+ ----- Method: BarGraphMorph>>legendSpacing (in category 'accessing legends') -----
+ legendSpacing
+ ^self isVerticalGraph ifTrue: [super legendSpacing y] ifFalse: [super legendSpacing x]!

Item was added:
+ ----- Method: PointTableMorph classSide>>additionsToViewerCategories (in category 'viewer categories') -----
+ additionsToViewerCategories
+ ^ #(
+ (#plot (
+ #(command apply '' )
+ #(command addRow '' )
+ #(command removeRow '' )
+ #(slot rowCount '' Number readOnly Player getRowCount Player unused )
+ #(slot rowIndex '' Number readWrite Player getRowIndex Player setRowIndex:  )
+ #(slot rowX '' Number readWrite Player getRowX Player setRowX:  )
+ #(slot rowY '' Number readWrite Player getRowY Player setRowY:  )
+ #(slot rowsFilled '' Number readOnly Player getRowsFilled Player unused )
+ ))
+ 
+ )!

Item was added:
+ ----- Method: CartesianGraphMorph>>axisColor: (in category 'accessing colors') -----
+ axisColor: aColor
+ axisColor := aColor.
+ self updateBackground.!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>form:type:for: (in category 'instance creation') -----
+ form: aForm type: aSymbol for: aMorph
+ ^(self form: aForm type: aSymbol) target: aMorph!

Item was added:
+ ----- Method: VectorMorph>>color (in category 'accessing') -----
+ color
+ 	^borderColor!

Item was added:
+ ----- Method: PointMorph>>setGraph:point: (in category 'private') -----
+ setGraph: aDataGraphMorph point: aPoint 
+ graph := aDataGraphMorph.
+ point := aPoint.!

Item was added:
+ ----- Method: Morph>>showObject:inBubbleType: (in category '*Etoys-SpeechBubbles') -----
+ showObject: aPlayer inBubbleType: typeSymbol
+ | currentBubble morph |
+ morph := aPlayer costume renderedMorph.
+ currentBubble := self bubble.
+ currentBubble notNil ifTrue: [
+ 	(currentBubble msgMorph = morph and: [currentBubble type = typeSymbol and: [currentBubble isInWorld]]) ifTrue: [^self].
+ 	currentBubble delete].
+ self setProperty: #bubble toValue: (SpeechBubbleMorph morph: morph  type: typeSymbol for: self).!

Item was added:
+ ----- Method: CartesianGraphMorph>>updateAxes (in category 'updating') -----
+ updateAxes
+ 	| axisPos |
+ 	axisPos := self cartesianPointToPixel: 0 at 0.
+ 	verticalAxis vertices at: 1 put: axisPos x @ self bottom.
+ 	verticalAxis vertices at: 2 put: axisPos x @ self top.
+ 	verticalAxis borderColor: axisColor.
+ 	verticalAxis computeBounds.
+ 	horizontalAxis vertices at: 1 put: self left @ axisPos y.
+ 	horizontalAxis vertices at: 2 put: self right @ axisPos y.
+ 	horizontalAxis borderColor: axisColor.
+ 	horizontalAxis computeBounds!

Item was added:
+ ----- Method: CartesianGraphMorph>>cartesianXToRelativePixel: (in category 'calculations') -----
+ cartesianXToRelativePixel: aNumber
+ 
+ 	^ (aNumber - cartesianBounds left * bounds width / cartesianBounds width) rounded.
+ !

Item was added:
+ ----- Method: Player>>setBarValue: (in category '*Etoys-graphing') -----
+ setBarValue: aNumber
+ | selector |
+ selector := #barValueAt:put:.
+ (self costumeRespondingTo: selector) ifNotNilDo: [:c | c perform: selector withArguments: {self getBarIndex. aNumber}]!

Item was added:
+ ----- Method: Player>>setMyPointY: (in category '*Etoys-graphing') -----
+ setMyPointY: aNumber
+ ^ self setCostumeSlot: #pointY: toValue: aNumber
+ !

Item was added:
+ ----- Method: SpeechBubbleMorph>>step (in category 'stepping') -----
+ step
+ (target isNil or: [lastHash = (lastHash := target boundsSignatureHash)])
+ 		ifTrue: [self incrementStepTime]
+ 		ifFalse: [stepTime := self minimumStepTime].
+ 
+ target notNil ifTrue: [
+ target isInWorld ifFalse: [^self delete].
+ self positionMyselfAccordingToTarget].
+ 
+ "This will keep the correct extent if the graphic changed"
+ self msgMorph notNil ifTrue: [
+ (self balloon fullBounds containsRect: self msgMorph fullBounds)
+ 	ifFalse: [self extent: 1 at 1]]
+ !

Item was added:
+ ----- Method: CartesianGraphMorph>>minorGridColor (in category 'accessing colors') -----
+ minorGridColor
+ ^minorGridColor!

Item was added:
+ ----- Method: CartesianGraphMorph>>updateAll (in category 'updating') -----
+ updateAll
+ self updateBackground; changed!

Item was added:
+ ----- Method: CartesianGraphMorph>>cartesianYToPixel: (in category 'calculations') -----
+ cartesianYToPixel: aNumber
+ 	^ (bounds bottom - (aNumber - cartesianBounds top * bounds height / cartesianBounds height)) rounded.
+ !

Item was added:
+ ----- Method: SpeechBubbleMorph>>refreshMsgMorph (in category 'refreshing') -----
+ refreshMsgMorph
+ 	self msgMorph owner = self ifFalse: [^self delete].
+ 	self positionMsgMorph.
+ 	self addMorph: self msgMorph!

Item was added:
+ ----- Method: VectorMorph>>privateCenter: (in category 'private') -----
+ privateCenter: aPoint
+ self privatePosition: (aPoint - (self extent // 2))!

Item was added:
+ ----- Method: BarMorph>>setGraph:label:value:index: (in category 'private') -----
+ setGraph: aBarGraphMorph label: aSymbol value: aNumber index: anotherNumber
+ graph := aBarGraphMorph.
+ label := aSymbol.
+ value := aNumber.
+ index := anotherNumber!

Item was added:
+ ----- Method: VectorMorph>>from:to: (in category 'accessing') -----
+ from: startPoint to: endPoint
+ 	"We don't calculate clipped vector, otherwise the arrow may be misplaced when part of the vector extremity is outisde the drawing area'"
+ 	vertices at: 1 put: startPoint asIntegerPoint .
+ 	vertices at: 2 put: endPoint  asIntegerPoint.
+ 	self computeBounds
+ !

Item was added:
+ ----- Method: DataGraphMorph classSide>>additionsToViewerCategoryPlotVectors (in category 'viewer categories') -----
+ additionsToViewerCategoryPlotVectors
+ ^#(#'plot - vectors' (
+ #(slot vectorIndex '' Number  readWrite Player getVectorIndex Player setVectorIndex:  )
+ #(command removeVectorAt: '' Number )
+ #(command removeAllVectors '')
+ #(command removeCurrentVector '')
+ #(command addVector '')
+ #(slot initialPointX '' Number readWrite Player getInitialPointX Player setInitialPointX:  )
+ #(slot initialPointY '' Number readWrite Player getInitialPointY Player setInitialPointY:  )
+ #(slot terminalPointX '' Number readWrite Player getTerminalPointX Player setTerminalPointX:  )
+ #(slot terminalPointY '' Number readWrite Player getTerminalPointY Player setTerminalPointY:  )
+ #(slot vectorMagnitude '' Number readWrite Player getVectorMagnitude Player setVectorMagnitude:  )
+ #(slot vectorAngle '' Number readWrite Player getVectorAngle Player setVectorAngle:  )
+ #(slot vectorCount '' Number readOnly Player getVectorCount Player unused  )
+ #(slot vectorColor '' Color readWrite Player getVectorColor Player setVectorColor:  )
+ #(slot playerAtVectorIndex '' Player readWrite Player getPlayerAtVectorIndex  unused unused)
+ ))!

Item was added:
+ ----- Method: CartesianGraphMorph>>initializeAxes (in category 'initialize-release') -----
+ initializeAxes
+ 	verticalAxis := PolygonMorph arrowPrototype arrowSpec: 8 @ 4; lineBorderWidth: 1.
+ 	horizontalAxis := PolygonMorph arrowPrototype arrowSpec: 8 @ 4; lineBorderWidth: 1.
+ 	self addMorph: horizontalAxis;
+ 		 addMorph: verticalAxis. 
+ 	self updateAxes !

Item was added:
+ ----- Method: PointMorph>>update (in category 'updating') -----
+ update
+ self penUpWhile: [self point: point].
+ !

Item was added:
+ ----- Method: Player>>setMyTerminalPointY: (in category '*Etoys-graphing') -----
+ setMyTerminalPointY: aNumber
+ self setCostumeSlot: #terminalPointY: toValue: aNumber
+ !

Item was added:
+ ----- Method: CartesianGraphMorph>>drawVerticalGridOn: (in category 'building') -----
+ drawVerticalGridOn: aCanvas
+ cartesianBounds left ceiling to: cartesianBounds right floor do: [:x | 
+ 		| gridPos |
+ 		gridPos := self cartesianXToRelativePixel: x.
+ 		(x isDivisibleBy: minorGrid x)
+ 			ifTrue: [self drawMinorGridFrom: gridPos @ (gridForm height - 1) to: gridPos @ 0 on: aCanvas].
+ 		(x isDivisibleBy: majorGrid x)
+ 			ifTrue: [self drawMajorGridFrom: gridPos @ (gridForm height - 1) to: gridPos @ 0 on: aCanvas].
+ 		].!

Item was added:
+ ----- Method: SpeechBubbleMorph>>positionMyselfAccordingToTarget (in category 'stepping') -----
+ positionMyselfAccordingToTarget
+ 	| newCenter newOwner |
+ 	"Modify mi position"
+ 	newCenter := target topRendererOrSelf center - (0 @ ((target topRendererOrSelf height + self height) / 2)).
+ 	self privatePosition: newCenter - (self extent // 2).
+ 	"Don't forget to check if my owner is still the right one. Maybe the morph was inside a Playfield and the user grabed it and put it in the World"
+ 	newOwner := target ownerThatIsA: PasteUpMorph.
+ 	self owner ~= newOwner ifTrue: [newOwner addMorph: self]!

Item was added:
+ ----- Method: Player>>getInitialPointY (in category '*Etoys-graphing') -----
+ getInitialPointY
+ | current |
+ current := self currentVector.
+ ^current isNil ifTrue: [nil] ifFalse: [current initialPointY]!

Item was added:
+ ----- Method: Player>>restoreDefaultGrids (in category '*Etoys-graphing') -----
+ restoreDefaultGrids
+ ^ self sendMessageToCostume: #restoreDefaultGrids.!

Item was added:
+ ----- Method: Player>>moveRight: (in category '*Etoys-graphing') -----
+ moveRight: aNumber
+ ^ self sendMessageToCostume: #move: with: aNumber @ 0!

Item was added:
+ ----- Method: Player>>setMyInitialPointX: (in category '*Etoys-graphing') -----
+ setMyInitialPointX: aNumber
+ self setCostumeSlot: #initialPointX: toValue: aNumber
+ !

Item was added:
+ ----- Method: Player>>setVectorMagnitude: (in category '*Etoys-graphing') -----
+ setVectorMagnitude: aNumber
+ | current |
+ current := self currentVector.
+ current isNil ifTrue: [^self].
+ current magnitude: aNumber!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>speakingForm (in category 'forms') -----
+ speakingForm
+ "
+ speakingForm := nil
+ "
+ ^speakingForm ifNil: [speakingForm := (Form
+ 	extent: 56 at 51
+ 	depth: 16
+ 	fromArray: #( 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 98303 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 98303 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 98303 2147450879 2147450879 2147418113 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 65537 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 98303 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 98303 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 65537 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0)
+ 	offset: 0 at 0)]!

Item was added:
+ ----- Method: PointTableMorph>>makeColumnNames (in category 'building') -----
+ makeColumnNames
+ 	| columnName |
+ 	columnName := [:contents | self newTextMorph contents: contents; wrapFlag: true; autoFit: true; backgroundColor: Color transparent; borderWidth: 0; centered].
+ 	^ AlignmentMorph newRow color: Color transparent;
+ 		addMorphBack: self makeSpacer;
+ 		addMorphBack: (columnName value: 'x');
+ 		addMorphBack: self makeSpacer;
+ 		addMorphBack: (columnName value: 'y');
+ 		addMorphBack: self makeSpacer;
+ 		addMorphBack: (Morph new color: Color transparent; extent: 20 at 1)!

Item was added:
+ ----- Method: Player>>getYLegendSpacing (in category '*Etoys-graphing') -----
+ getYLegendSpacing
+ ^ self getValueFromCostume: #yLegendSpacing!

Item was added:
+ ----- Method: CartesianGraphMorph>>minorGrid: (in category 'accessing grid') -----
+ minorGrid: aPoint
+ self controlGriddingParameter: aPoint.
+ minorGrid := aPoint.
+ self updateBackground!

Item was added:
+ ----- Method: Player>>getBarIndex (in category '*Etoys-graphing') -----
+ getBarIndex
+ self barIndex > self getBarCount ifTrue: [self barIndex: self getBarCount].
+ ^ self barIndex!

Item was added:
+ ----- Method: BarMorph>>update (in category 'initialize-release') -----
+ update
+ self update: index!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>additionsToViewerCategoryBubble (in category 'viewer categories') -----
+ additionsToViewerCategoryBubble
+ 	"Answer viewer additions for the 'bubble' category"
+ 
+ 	^#(
+ 		bubble 
+ 		(
+ 			(command attachTo: '' Player)
+ 			(command stopAttaching '')
+ 			(slot attachment '' Player readOnly Player getAttachment Player unused)		
+ 		)
+ 	)
+ !

Item was added:
+ ----- Method: CartesianGraphMorph>>yMin (in category 'accessing cartesian bounds') -----
+ yMin
+ ^self cartesianBounds top!

Item was added:
+ ----- Method: PointTableMorph>>rowYAt:put: (in category 'accessing') -----
+ rowYAt: pointIndex put: aNumber
+ | count |
+ count := 0.
+ self list submorphs do: [:each|
+ 	(each isAlignmentMorph and: [ each submorphs first isTextMorph])
+ 	 ifTrue: [
+ 		count := count + 1.
+ 		count = pointIndex ifTrue: [
+ 			each submorphs second contentsWrapped: aNumber asString.
+ 			^self
+ 			]			
+ 		]
+ 	]!

Item was added:
+ ----- Method: BarTableMorph>>removeRow (in category 'actions') -----
+ removeRow
+ 	| |
+ 	numberOfRows <= 1 ifTrue: [^self].
+ 	numberOfRows := numberOfRows - 1.
+ 	list removeMorph: list submorphs last.
+ 	self updateScrollPane!

Item was added:
+ ----- Method: Morph>>stopSayingOrThinking (in category '*Etoys-SpeechBubbles') -----
+ stopSayingOrThinking
+ | currentBubble |
+ currentBubble := self bubble.
+ currentBubble isNil ifTrue: [^self].
+ currentBubble delete!

Item was added:
+ ----- Method: VectorMorph classSide>>graph:initialPoint:terminalPoint: (in category 'instance creation') -----
+ graph: aDataGraphMorph initialPoint: aPoint terminalPoint: anotherPoint
+ ^(self basicNew setGraph: aDataGraphMorph initialPoint: aPoint terminalPoint: anotherPoint) initialize!

Item was added:
+ ----- Method: Player>>thinkObject: (in category '*Etoys-SpeechBubbles') -----
+ thinkObject: aPlayer
+ self costume renderedMorph thinkObject: aPlayer!

Item was added:
+ ----- Method: Player>>addRow (in category '*Etoys-graphing') -----
+ addRow
+ ^ self sendMessageToCostume: #addRow!

Item was added:
+ ----- Method: PointMorph>>dismissViaHalo (in category 'initialize-release') -----
+ dismissViaHalo
+ 	self remove.
+ 	super dismissViaHalo!

Item was added:
+ ----- Method: PointTableMorph>>textMorphWidth (in category 'private') -----
+ textMorphWidth
+ ^75!

Item was added:
+ ----- Method: Player>>getVectorColor (in category '*Etoys-graphing') -----
+ getVectorColor
+ | current |
+ current := self currentVector.
+ ^current isNil ifTrue: [Color black] ifFalse: [current color]!

Item was added:
+ ----- Method: SpeechBubbleMorph>>tail (in category 'accessing') -----
+ tail
+ ^tail ifNil: [
+ 	| tailForm |
+ 	tailForm := self selectedTailForm deepCopy.
+ 	
+ 	"This will paint both forms correctly"
+ 	tailForm floodFill: self color at: tailForm center + (6 at -15).
+ 
+ 	"In the #thought case, we also need to paint the little bubbles"
+ 	type = #thought ifTrue: [
+ 		tailForm floodFill: self color at: tailForm center + (-7 at 7);
+ 				floodFill: self color at: tailForm center + (-22 at 20)
+ 	].
+ 
+ 	tail := SketchMorph withForm: tailForm]!

Item was added:
+ ----- Method: CartesianGraphMorph>>majorGrid: (in category 'accessing grid') -----
+ majorGrid: aPoint
+ self controlGriddingParameter: aPoint.
+ majorGrid := aPoint.
+ self updateBackground !

Item was added:
+ ----- Method: CartesianGraphMorph>>move: (in category 'moving') -----
+ move: aPoint
+ cartesianBounds := cartesianBounds translateBy: aPoint.
+ self translateTurtleTrailsBy: aPoint; update!

Item was added:
+ ----- Method: CartesianGraphMorph>>yMin: (in category 'accessing cartesian bounds') -----
+ yMin: aNumber
+ [self cartesianBounds: ((self cartesianBounds origin x @ aNumber) corner: self cartesianBounds corner)]
+ 	on: Error do: [:err| self inform: err description]!

Item was added:
+ ----- Method: SpeechBubbleMorph>>keyStroke:morph: (in category 'event handling') -----
+ keyStroke: anEvent morph: aMorph 
+ 	| string |
+ 	(self msgMorph isKindOf: UserText) ifFalse: [^self].
+ 
+ 	string := self msgMorph contents.
+ 
+ 	"Update text width if necessary. Make sure we keep the selection at the end of the text so that the user can keep modifying"
+ 	self msgMorph width > 300
+ 		ifTrue: [self msgMorph contents: string wrappedTo: 300.
+ 			self msgMorph editor selectFrom: string size + 1 to: string size].
+ 
+ 	"Update my extent"
+ 	self extent: self msgMorphExtent + (20 @ self tailHeight + 20).
+ !

Item was added:
+ ----- Method: PointMorph>>position: (in category 'accessing') -----
+ position: aPoint
+ owner isNil ifFalse: [point := (graph relativePixelToCartesianPoint: aPoint + (self extent // 2) - graph topLeft)].
+ ^super position: aPoint!

Item was added:
+ ----- Method: DataGraphMorph>>pointCount (in category 'accessing points') -----
+ pointCount
+ ^pointMorphs size!

Item was added:
+ ----- Method: BarGraphMorph>>max: (in category 'accessing range') -----
+ max: aNumber
+ self range: (self range first to: aNumber)!

Item was added:
+ ----- Method: BarGraphMorph>>addCustomMenuItems:hand: (in category 'menus') -----
+ addCustomMenuItems: aMenu hand: aHandMorph
+ aMenu add: 'open bar table' target: self action: #openBarTable!

Item was added:
+ ----- Method: BarMorph>>dismissViaHalo (in category 'initialize-release') -----
+ dismissViaHalo
+ 	self remove.
+ 	super dismissViaHalo!

Item was added:
+ ----- Method: Player>>removeBar (in category '*Etoys-graphing') -----
+ removeBar
+ ^self sendMessageToCostume: #removeBar!

Item was added:
+ ----- Method: Player>>setMyVectorColor: (in category '*Etoys-graphing') -----
+ setMyVectorColor: aColor
+ self setCostumeSlot: #color: toValue: aColor
+ !

Item was added:
+ ----- Method: BarMorph>>position: (in category 'accessing') -----
+ position: aPoint
+ super position: aPoint.
+ self update!

Item was added:
+ ----- Method: DataGraphMorph>>pointAt: (in category 'accessing points') -----
+ pointAt: index
+ ^(pointMorphs at: index) !

Item was added:
+ ----- Method: PointTableMorph>>makeSpacer (in category 'building') -----
+ makeSpacer
+ 	^ AlignmentMorph newVariableTransparentSpacer!

Item was added:
+ ----- Method: Player>>getAttachment (in category '*Etoys-SpeechBubbles') -----
+ getAttachment
+ 	^ [(self sendMessageToCostume: #target) assuredPlayer]
+ 		on: Error
+ 		do: [self presenter standardPlayer] !

Item was added:
+ ----- Method: BarTableMorph>>setGraph: (in category 'private') -----
+ setGraph: aDataGraphMorph
+ graph := aDataGraphMorph!

Item was added:
+ ----- Method: CartesianGraphMorph>>yMax: (in category 'accessing cartesian bounds') -----
+ yMax: aNumber
+ [self cartesianBounds: (self cartesianBounds origin corner: (self cartesianBounds corner x @ aNumber))]
+ 	on: Error do: [:err| self inform: err description]..!

Item was added:
+ SketchMorph subclass: #PointMorph
+ 	instanceVariableNames: 'graph cartesianPosition point'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Etoys-Graphing'!
+ 
+ !PointMorph commentStamp: 'Richo 4/17/2010 21:06' prior: 0!
+ This object is used by DataGraphMorph to draw points. It needs to know the graph in which it is plotted to be able to update its position whenever necessary.!

Item was added:
+ ----- Method: CartesianGraphMorph>>initializeGridForm (in category 'initialize-release') -----
+ initializeGridForm
+ gridForm := Form extent: self extent depth: 32.!

Item was added:
+ ----- Method: BarGraphMorph classSide>>initialize (in category 'class initialization') -----
+ initialize
+ "self initialize"
+ super initialize.
+ Vocabulary addStandardVocabulary: (SymbolListType new vocabularyName: #GraphDirection;
+ 			 symbols: #(#horizontal #vertical )).!

Item was added:
+ ----- Method: BarMorph>>updateLabel (in category 'accessing') -----
+ updateLabel
+ 	labelMorph contents: label.
+ 	graph isVerticalGraph
+ 		ifTrue: [value >= 0
+ 				ifTrue: [labelMorph center: self bottomCenter + (0 @ 10)]
+ 				ifFalse: [labelMorph center: self topCenter - (0 @ 10)]]
+ 		ifFalse: [value <= 0
+ 				ifTrue: [labelMorph center: self rightCenter + ((labelMorph width / 2) rounded + 3 @ 0)]
+ 				ifFalse: [labelMorph center: self leftCenter - ((labelMorph width / 2) rounded + 3 @ 0).
+ 						labelMorph left <= graph left
+ 							ifTrue: [labelMorph left: self right + 3]]].
+ 	self addMorph: labelMorph.!

Item was added:
+ ----- Method: CartesianGraphMorph>>placeAxes (in category 'building') -----
+ placeAxes
+ 	| axisPos |
+ 	axisPos := self cartesianPointToPixel: 0 at 0.
+ 	verticalAxis vertices at: 1 put: axisPos x @ self bottom.
+ 	verticalAxis vertices at: 2 put: axisPos x @ self top.
+ 	verticalAxis borderColor: axisColor.
+ 	verticalAxis computeBounds.
+ 	horizontalAxis vertices at: 1 put: self left @ axisPos y.
+ 	horizontalAxis vertices at: 2 put: self right @ axisPos y.
+ 	horizontalAxis borderColor: axisColor.
+ 	horizontalAxis computeBounds!

Item was added:
+ ----- Method: DataGraphMorph>>addCustomMenuItems:hand: (in category 'menus') -----
+ addCustomMenuItems: aMenu hand: aHandMorph
+ aMenu add: 'open point table' target: self action: #openPointTable!

Item was added:
+ ----- Method: Player>>setYLegendSpacing: (in category '*Etoys-graphing') -----
+ setYLegendSpacing: anInteger
+ self setCostumeSlot: #yLegendSpacing: toValue: anInteger!

Item was added:
+ ----- Method: CartesianGraphMorph>>drawHorizontalGridOn: (in category 'building') -----
+ drawHorizontalGridOn: aCanvas
+ cartesianBounds top ceiling to: cartesianBounds bottom floor do: [:y | 
+ 		| gridPos |
+ 		gridPos := self cartesianYToRelativePixel: y.
+ 		(y isDivisibleBy: minorGrid y) 
+ 			ifTrue: [self drawMinorGridFrom: 0 @ gridPos to: (gridForm width - 1) @ gridPos on: aCanvas].
+ 		(y isDivisibleBy: majorGrid y) 
+ 			ifTrue: [self drawMajorGridFrom: 0 @ gridPos to: (gridForm width - 1) @ gridPos on: aCanvas].
+ 		].!

Item was added:
+ ----- Method: CartesianGraphMorph>>drawGridForm (in category 'building') -----
+ drawGridForm
+ | aCanvas |
+ "For performance, I keep the background in a separate form and redraw it only when it's necessary (i.e. changing the gridding parameters or the extent of the morph)"
+ gridForm isNil ifTrue: [^self].
+ aCanvas := gridForm getCanvas.
+ aCanvas fillColor: backgroundColor .
+ self drawVerticalGridOn: aCanvas; drawHorizontalGridOn: aCanvas!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>string: (in category 'instance creation') -----
+ string: aString 
+ ^self string: aString type: #speech!

Item was added:
+ ----- Method: Player>>getTerminalPointX (in category '*Etoys-graphing') -----
+ getTerminalPointX
+ | current |
+ current := self currentVector.
+ ^current isNil ifTrue: [nil] ifFalse: [current terminalPointX]!

Item was added:
+ ----- Method: CartesianGraphMorph>>relativePixelToCartesianX: (in category 'calculations') -----
+ relativePixelToCartesianX: anInteger
+ ^cartesianBounds left + (anInteger * cartesianBounds width / bounds width)!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>morph:type:for: (in category 'instance creation') -----
+ morph: aMorph type: aSymbol for: targetMorph
+ ^(self morph: aMorph type: aSymbol) target: targetMorph!

Item was added:
+ ----- Method: Player>>getMyPointX (in category '*Etoys-graphing') -----
+ getMyPointX
+ ^ self getValueFromCostume: #pointX!

Item was added:
+ ----- Method: Player>>getPointCount (in category '*Etoys-graphing') -----
+ getPointCount
+ ^self getValueFromCostume: #pointCount!

Item was added:
+ ----- Method: Player>>setMyInitialPointY: (in category '*Etoys-graphing') -----
+ setMyInitialPointY: aNumber
+ self setCostumeSlot: #initialPointY: toValue: aNumber
+ !

Item was added:
+ ----- Method: VectorMorph>>remove (in category 'initialize-release') -----
+ remove
+ 	graph removeVector: self!

Item was added:
+ ----- Method: DataGraphMorph>>pointAt:ifAbsent: (in category 'accessing points') -----
+ pointAt: index ifAbsent: aBlock
+ | m |
+ m := pointMorphs at: index ifAbsent: [nil].
+ ^m isNil ifTrue: [aBlock value] ifFalse: [m]
+ !

Item was added:
+ ----- Method: Player>>vectorIndex: (in category '*Etoys-graphing') -----
+ vectorIndex: aNumber
+ self costume renderedMorph setProperty: #vectorIndex toValue: aNumber.!

Item was added:
+ ----- Method: DataGraphMorph>>addPoint: (in category 'accessing points') -----
+ addPoint: aPointMorph
+ self addMorph: aPointMorph.
+ pointMorphs add: aPointMorph.!

Item was added:
+ ----- Method: Player>>getYMax (in category '*Etoys-graphing') -----
+ getYMax
+ ^ self getValueFromCostume: #yMax!

Item was added:
+ ----- Method: SpeechBubbleMorph>>msgMorph (in category 'accessing') -----
+ msgMorph
+ ^msgMorph isNil ifTrue: [nil] ifFalse: [msgMorph topRendererOrSelf]!

Item was added:
+ ----- Method: BarMorph classSide>>graph:label:value:index: (in category 'instance creation') -----
+ graph: aBarGraphMorph label: aSymbol value: aNumber index: anotherNumber
+ ^(self basicNew setGraph: aBarGraphMorph label: aSymbol value: aNumber index: anotherNumber) initialize!

Item was added:
+ ----- Method: DataGraphMorph>>removePoint: (in category 'accessing points') -----
+ removePoint: aPoint
+ 	| p |
+ 	p := pointMorphs select: [:each| each = aPoint].
+ 	p isEmpty ifTrue: [^self error: 'Point not found'].
+ 	pointMorphs remove: p anyOne delete.!

Item was added:
+ ----- Method: DataGraphMorph>>updateVectors (in category 'updating') -----
+ updateVectors
+ 	"Updates the position of each vector"
+ 	vectorMorphs do: [:each | each update].
+ 	self changed!

Item was added:
+ ----- Method: PointMorph>>color (in category 'accessing') -----
+ color
+ 	^ color!

Item was added:
+ ----- Method: DataGraphMorph>>initializeToStandAlone (in category 'initialize') -----
+ initializeToStandAlone
+ 	"Answer an instance of the receiver suitable for placing in a parts bin for authors"
+ 	
+ 	self initialize.!

Item was added:
+ ----- Method: Player>>getPointIndex (in category '*Etoys-graphing') -----
+ getPointIndex
+ self pointIndex > self getPointCount ifTrue: [self pointIndex: self getPointCount].
+ ^ self pointIndex!

Item was added:
+ ----- Method: Player>>setRowX: (in category '*Etoys-graphing') -----
+ setRowX: aNumber
+ | selector |
+ selector := #rowXAt:put:.
+ (self costumeRespondingTo: selector) ifNotNilDo: [:c | c perform: selector withArguments: {self getRowIndex. aNumber}]!

Item was added:
+ ----- Method: Player>>setMax: (in category '*Etoys-graphing') -----
+ setMax: aNumber
+ self setCostumeSlot: #max: toValue: aNumber!

Item was added:
+ ----- Method: Player>>getPointX (in category '*Etoys-graphing') -----
+ getPointX
+ | current |
+ current := self currentPoint.
+ ^current isNil ifTrue: [nil] ifFalse: [current pointX]!

Item was added:
+ ----- Method: BarGraphMorph>>placeXLegends (in category 'building') -----
+ placeXLegends
+ self isVerticalGraph 
+ 	ifTrue: [(legends at: #x) do: [:each | each delete].
+ 		legends at: #x put: OrderedCollection new.
+ 		^self].
+ super placeXLegends!

Item was added:
+ ----- Method: SpeechBubbleMorph>>initialize (in category 'initialize-release') -----
+ initialize
+ super initialize.
+ stepTime := self minimumStepTime.
+ self positionBalloon; positionTail; positionMsgMorph.
+ self addMorph: self balloon; addMorph: self tail; addMorph: self msgMorph.
+ self extent: self msgMorphExtent + (20 @ self tailHeight + 20); color: Color white.!

Item was added:
+ ----- Method: SpeechBubbleMorph>>delete (in category 'initialize-release') -----
+ delete
+ 	super delete.
+ 	target := msgMorph := type := nil.
+ !

Item was added:
+ ----- Method: Player>>removeCurrentVector (in category '*Etoys-graphing') -----
+ removeCurrentVector
+ self vectorIndex = 0 ifTrue: [^self].
+ self sendMessageToCostume: #removeVectorAt: with: self vectorIndex.
+ self setVectorIndex: self vectorIndex - 1!

Item was added:
+ ----- Method: SpeechBubbleMorph>>positionMsgMorph (in category 'initialize-release') -----
+ positionMsgMorph
+ | diff |
+ diff := self msgMorph center - self msgMorph fullBounds center.
+ self msgMorph center: self center - (0 @ self tailHeight / 2) + diff.!

Item was added:
+ ----- Method: PointMorph>>initializeForm (in category 'initialize-release') -----
+ initializeForm
+ | tempForm |
+ tempForm := (Form extent: 6 at 6 depth: 32).
+ tempForm getCanvas fillOval: tempForm boundingBox color: self color.
+ 
+ self form: tempForm!

Item was added:
+ ----- Method: CartesianGraphMorph>>controlLegendSpacing: (in category 'controlling errors') -----
+ controlLegendSpacing: aPoint
+ | |
+ (aPoint x isInteger and: [aPoint y isInteger]) ifFalse: [^self error: 'Legend spacing must be natural numbers'].
+ (aPoint x < 0 or: [aPoint y < 0]) ifTrue: [^self error: 'Legend spacing must be natural numbers'].!

Item was added:
+ ----- Method: BarGraphMorph classSide>>defaultNameStemForInstances (in category 'parts bin') -----
+ defaultNameStemForInstances
+ 	^ 'Bar Graph' !

Item was added:
+ ----- Method: Player>>currentVector (in category '*Etoys-graphing') -----
+ currentVector
+ | selector |
+ selector := #vectorAt:ifAbsent:.
+ ^(self costumeRespondingTo: selector) ifNotNilDo: [:c | c perform: selector withArguments: {self vectorIndex. [nil]}]!

Item was added:
+ ----- Method: Player>>setLegendSpacing: (in category '*Etoys-graphing') -----
+ setLegendSpacing: aNumber
+ ^ self setCostumeSlot: #legendSpacing: toValue: (aNumber max: 0) rounded!

Item was added:
+ ----- Method: Player>>removeBarAt: (in category '*Etoys-graphing') -----
+ removeBarAt: aNumber
+ (aNumber > self getBarCount or: [aNumber <= 0])
+ 	ifTrue: [^self].
+ self  sendMessageToCostume: #removeBarAt: with: aNumber.
+ self getBarIndex = aNumber ifTrue: [self setBarIndex: self getBarIndex - 1]!

Item was added:
+ ----- Method: Player>>getMyVectorAngle (in category '*Etoys-graphing') -----
+ getMyVectorAngle
+ ^ self getValueFromCostume: #angle!

Item was added:
+ ----- Method: CartesianGraphMorph>>minorGridColor: (in category 'accessing colors') -----
+ minorGridColor: aColor
+ minorGridColor := aColor.
+ self updateBackground.!

Item was added:
+ ----- Method: BarGraphMorph>>legendSpacing: (in category 'accessing legends') -----
+ legendSpacing: aNumber
+ super legendSpacing: aNumber at aNumber!

Item was added:
+ ----- Method: DataGraphMorph classSide>>descriptionForPartsBin (in category 'parts bin') -----
+ descriptionForPartsBin
+ 	^ self
+ 		partName: 'Graph'
+ 		categories: #('Tools' )
+ 		documentation: ''
+ !

Item was added:
+ ----- Method: BarGraphMorph>>updateAll (in category 'updating') -----
+ updateAll
+ super updateAll.
+ self updateBars; changed!

Item was added:
+ ----- Method: BarGraphMorph>>max (in category 'accessing range') -----
+ max
+ ^self range last!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>string:type: (in category 'instance creation') -----
+ string: aString type: aSymbol
+ "self string: 'Hello world!!' type: #speech"
+ | text instance |
+ text := (UserText new contents: aString) centered.
+ text width > 300 ifTrue: [text contents: aString wrappedTo: 300].
+ text on: #keyStroke send: #keyStroke:morph: to: (instance := self basicNew).
+ ^(instance setMorph: text type: aSymbol) initialize!

Item was added:
+ ----- Method: BarGraphMorph>>bars (in category 'accessing bars') -----
+ bars
+ ^barMorphs!

Item was added:
+ ----- Method: Player>>getXMajorGrid (in category '*Etoys-graphing') -----
+ getXMajorGrid
+ ^ self getValueFromCostume: #xMajorGrid!

Item was added:
+ ----- Method: VectorMorph>>magnitude (in category 'accessing') -----
+ magnitude
+ | diff |
+ diff := terminalPoint - initialPoint.
+ ^(diff x squared + diff y squared) sqrt!

Item was added:
+ ----- Method: BarGraphMorph>>removeBarAt: (in category 'accessing bars') -----
+ removeBarAt: index 
+ 	| m |
+ 	m := barMorphs at: index ifAbsent: [^self error: 'Bar not found'].
+ 	m delete.
+ 	barMorphs removeAt: index.
+ 	self updateBars!

Item was added:
+ ----- Method: Player>>getMax (in category '*Etoys-graphing') -----
+ getMax
+ ^self sendMessageToCostume: #max!

Item was added:
+ ----- Method: BarGraphMorph classSide>>includeInNewMorphMenu (in category 'new-morph participation') -----
+ includeInNewMorphMenu
+ 	"Return true for all classes that can be instantiated from the menu"
+ 	^ true!

Item was added:
+ ----- Method: VectorMorph>>angle: (in category 'accessing') -----
+ angle: degrees
+ | o a magnitude |
+ magnitude := self magnitude.
+ o := degrees degreesToRadians sin * magnitude.
+ a := degrees degreesToRadians cos * magnitude.
+ terminalPoint := (initialPoint + (a at o)).
+ self update.!

Item was added:
+ ----- Method: Player>>getYMajorGrid (in category '*Etoys-graphing') -----
+ getYMajorGrid
+ ^ self getValueFromCostume: #yMajorGrid!

Item was added:
+ ----- Method: BarGraphMorph>>barLabelAt: (in category 'accessing bars') -----
+ barLabelAt: barIndex
+ | current |
+ current := self barAt: barIndex ifAbsent: [^nil].
+ ^current barLabel!

Item was added:
+ ----- Method: DataGraphMorph>>updatePoints (in category 'updating') -----
+ updatePoints
+ 	"Updates the position of each point"
+ 	pointMorphs do: [:each | each update].
+ 	self changed!

Item was added:
+ ----- Method: VectorMorph>>initialPointY (in category 'accessing') -----
+ initialPointY
+ ^initialPoint y!

Item was added:
+ ----- Method: DataGraphMorph>>initializePoints (in category 'initialize') -----
+ initializePoints
+ pointMorphs := OrderedCollection new!

Item was added:
+ ----- Method: CartesianGraphMorph>>majorGridColor: (in category 'accessing colors') -----
+ majorGridColor: aColor
+ majorGridColor := aColor.
+ self updateBackground.!

Item was added:
+ ----- Method: CartesianGraphMorph>>axisColor (in category 'accessing colors') -----
+ axisColor
+ ^axisColor!

Item was added:
+ ----- Method: CartesianGraphMorph>>cartesianPointToPixel: (in category 'calculations') -----
+ cartesianPointToPixel: aPoint
+ ^(self cartesianXToPixel: aPoint x) @ (self cartesianYToPixel: aPoint y)!

Item was added:
+ ----- Method: SpeechBubbleMorph>>incrementStepTime (in category 'stepping') -----
+ incrementStepTime
+ 	stepTime := (stepTime + 1) min: self maximumStepTime!

Item was added:
+ ----- Method: BarGraphMorph>>minorGrid: (in category 'accessing grid') -----
+ minorGrid: aNumber
+ super minorGrid: aNumber at aNumber!

Item was added:
+ ----- Method: Player>>removePoint (in category '*Etoys-graphing') -----
+ removePoint
+ ^ self  sendMessageToCostume: #removePoint!

Item was added:
+ ----- Method: VectorMorph>>privatePosition: (in category 'private') -----
+ privatePosition: aPoint
+ ^super position: aPoint!

Item was added:
+ ----- Method: Player>>getXMinorGrid (in category '*Etoys-graphing') -----
+ getXMinorGrid
+ ^ self getValueFromCostume: #xMinorGrid!

Item was added:
+ ----- Method: DataGraphMorph>>updateAll (in category 'updating') -----
+ updateAll
+ super updateAll.
+ self updatePoints; updateVectors; changed!

Item was added:
+ ----- Method: Player>>move: (in category '*Etoys-graphing') -----
+ move: aNumber
+ ^ self sendMessageToCostume: #move: with: aNumber!

Item was added:
+ ----- Method: Player>>stopSayingOrThinking (in category '*Etoys-SpeechBubbles') -----
+ stopSayingOrThinking
+ self costume renderedMorph stopSayingOrThinking!

Item was added:
+ ----- Method: BarTableMorph>>rowValueAt:put: (in category 'accessing') -----
+ rowValueAt: barIndex put: aNumber
+ | count |
+ count := 0.
+ self list submorphs do: [:each|
+ 	(each isAlignmentMorph and: [ each submorphs first isTextMorph])
+ 	 ifTrue: [
+ 		count := count + 1.
+ 		count = barIndex ifTrue: [
+ 			each submorphs second contentsWrapped: aNumber asString.
+ 			^self
+ 			]			
+ 		]
+ 	]!

Item was added:
+ ----- Method: CartesianGraphMorph>>extent: (in category 'accessing') -----
+ extent: newExtent
+ "I resize all forms to the newExtent, but (since this method is called in #initialize) I check that backbroundForm was properly initialized before, otherwise it throws an error"
+ super extent: newExtent.
+ gridForm isNil ifTrue: [^self].
+ self initializeGridForm; update!

Item was added:
+ ----- Method: Player>>getYMinorGrid (in category '*Etoys-graphing') -----
+ getYMinorGrid
+ ^ self getValueFromCostume: #yMinorGrid!

Item was added:
+ ----- Method: BarMorph>>extent: (in category 'accessing') -----
+ extent: aPoint
+ super extent: aPoint.
+ owner notNil ifTrue: [self update].
+ !

Item was added:
+ ----- Method: Morph>>sayGraphic: (in category '*Etoys-SpeechBubbles') -----
+ sayGraphic: aForm
+ self showGraphic: aForm inBubbleType: #speech!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>thinkingForm (in category 'forms') -----
+ thinkingForm
+ "
+ thinkingForm := nil
+ thinkingForm
+ "
+ ^thinkingForm ifNil: [thinkingForm := (Form
+ 	extent: 56 at 49
+ 	depth: 16
+ 	fromArray: #( 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 65537 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 65537 65537 65537 65537 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 65537 65537 2147450879 2147450879 2147450879 65537 65537 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 1 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 1 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 1 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 65537 65537 65537 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 1 65537 65537 65537 65537 65537 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 65537 65537 98303 2147450879 2147418113 65537 65537 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147418113 65537 65536 1 65537 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 65536 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65536 0 65537 65537 65537 2147450879 2147450879 2147450879 65537 65537 65537 0 0 0 0 0 0 0 0 0 1 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65536 0 0 1 65537 65537 65537 65537 65537 65537 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 1 65537 65537 65537 65536 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 98303 2147450879 2147450879 2147450879 2147450879 2147450879 2147418113 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 98303 2147450879 2147450879 2147450879 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 65537 65536 0 1 65537 98303 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 65537 65537 65537 65536 0 65537 65537 98303 2147450879 2147418113 65537 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 65537 65536 0 0 65537 65537 65537 65537 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147418113 65537 0 0 0 65537 65537 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 2147450879 2147450879 2147450879 2147450879 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 65537 98303 2147450879 2147450879 2147418113 65537 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 2147450879 2147450879 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 65537 65537 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 65537 65537 65536 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0)
+ 	offset: 0 at 0)]!

Item was added:
+ ----- Method: SpeechBubbleMorph>>positionTail (in category 'initialize-release') -----
+ positionTail
+ self tail position: self bottomCenter - (0 @ self tailHeight + 2)!

Item was added:
+ ----- Method: BarGraphMorph>>majorGrid: (in category 'accessing grid') -----
+ majorGrid: aNumber
+ super majorGrid: aNumber at aNumber!

Item was added:
+ ----- Method: Player>>getInitialPointX (in category '*Etoys-graphing') -----
+ getInitialPointX
+ | current |
+ current := self currentVector.
+ ^current isNil ifTrue: [nil] ifFalse: [current initialPointX]!

Item was added:
+ ----- Method: CartesianGraphMorph>>initializeLegendSpacing (in category 'initialize-release') -----
+ initializeLegendSpacing
+ 	legendSpacing := 5 at 5!

Item was added:
+ ----- Method: BarGraphMorph>>isVerticalGraph (in category 'testing') -----
+ isVerticalGraph
+ ^graphDirection = #vertical!

Item was added:
+ ----- Method: Player>>getMyTerminalPointY (in category '*Etoys-graphing') -----
+ getMyTerminalPointY
+ ^ self getValueFromCostume: #terminalPointY!

Item was added:
+ ----- Method: Player>>getYMin (in category '*Etoys-graphing') -----
+ getYMin
+ 	^self getValueFromCostume: #yMin!

Item was added:
+ ----- Method: Player>>getDistanceBetweenBars (in category '*Etoys-graphing') -----
+ getDistanceBetweenBars 
+ ^ self sendMessageToCostume: #distanceBetweenBars!

Item was added:
+ ----- Method: Player>>removeAllVectors (in category '*Etoys-graphing') -----
+ removeAllVectors.
+ self vectorIndex: 0.
+ ^ self sendMessageToCostume: #removeAllVectors!

Item was added:
+ ----- Method: PointTableMorph>>apply (in category 'actions') -----
+ apply
+ | newRows oldPoint newPoint |
+ newRows := self rows.
+ 1 to: newRows size do: [:i|
+ 	oldPoint := graph pointAt: i ifAbsent: [nil].
+ 	newPoint := newRows at: i.
+ 	oldPoint isNil
+ 	ifTrue: [graph addPoint: (PointMorph graph: graph point: newPoint)]
+ 	ifFalse: [oldPoint pointX: newPoint x; pointY: newPoint y]
+ 	].
+ newRows size < graph pointCount
+ 	ifTrue: [graph removePointsFrom: newRows size + 1 to: graph pointCount].!

Item was added:
+ ----- Method: PointTableMorph>>rowYAt: (in category 'accessing') -----
+ rowYAt: pointIndex
+ | count |
+ count := 0.
+ self list submorphs do: [:each|
+ 	(each isAlignmentMorph and: [ each submorphs first isTextMorph])
+ 	 ifTrue: [
+ 		count := count + 1.
+ 		count = pointIndex ifTrue: [
+ 			^[each submorphs second getNumericValue] on: Error do: [0].
+ 			]			
+ 		]
+ 	]!

Item was added:
+ ----- Method: BarMorph>>barValue (in category 'accessing') -----
+ barValue
+ ^value!

Item was added:
+ ----- Method: Player>>stopAttaching (in category '*Etoys-SpeechBubbles') -----
+ stopAttaching
+ 	self sendMessageToCostume: #target: with: nil!

Item was added:
+ ----- Method: Player>>setMyBarLabel: (in category '*Etoys-graphing') -----
+ setMyBarLabel: aString
+ ^ self setCostumeSlot: #barLabel: toValue: aString
+ !

Item was added:
+ ----- Method: CartesianGraphMorph>>relativePixelToCartesianPoint: (in category 'calculations') -----
+ relativePixelToCartesianPoint: aPoint
+ ^(self relativePixelToCartesianX: aPoint x) @ (self relativePixelToCartesianY: aPoint y)
+ !

Item was added:
+ ----- Method: CartesianGraphMorph>>cartesianBounds: (in category 'accessing cartesian bounds') -----
+ cartesianBounds: aRectangle
+ self controlCartesianBounds: aRectangle. 
+ cartesianBounds := aRectangle.
+ self update!

Item was added:
+ ----- Method: Player>>moveDown: (in category '*Etoys-graphing') -----
+ moveDown: aNumber
+ ^ self sendMessageToCostume: #move: with: 0 @ (aNumber negated)!

Item was added:
+ ----- Method: CartesianGraphMorph>>placeYLegends (in category 'building') -----
+ placeYLegends
+ 
+ | index yLegends legendPos legend |
+ index := 0.
+ yLegends := legends at: #y.
+ cartesianBounds top ceiling to: cartesianBounds bottom floor do: [:y | 
+ 		| pos |
+ 		pos := self cartesianYToPixel: y.
+ 		(y ~= 0 and: [(y isDivisibleBy: legendSpacing y)])
+ 			ifTrue: [
+ 			legendPos := (self preferredPositionForYLegend: y asString at: pos).
+ 			legendPos notNil ifTrue: [
+ 				legend := yLegends at: (index := index + 1) ifAbsent: [yLegends add: StringMorph new].
+ 				self addMorph: legend.
+ 				legend contents: y asString; position: legendPos; color: axisColor]]].
+ yLegends isEmpty ifFalse: [
+ yLegends from: index + 1 to: yLegends size do: [:each| each delete].
+ yLegends removeLast: (yLegends size - index)]!

Item was added:
+ ----- Method: DataGraphMorph>>initialize (in category 'initialize') -----
+ initialize
+ super initialize.
+ self
+ 	initializePoints;
+ 	initializeVectors.
+ !

Item was added:
+ ----- Method: Player>>removeAllPoints (in category '*Etoys-graphing') -----
+ removeAllPoints
+ self pointIndex: 0.
+ ^ self sendMessageToCostume: #removeAllPoints!

Item was added:
+ ----- Method: Player>>setRowY: (in category '*Etoys-graphing') -----
+ setRowY: aNumber
+ | selector |
+ selector := #rowYAt:put:.
+ (self costumeRespondingTo: selector) ifNotNilDo: [:c | c perform: selector withArguments: {self getRowIndex. aNumber}]!

Item was added:
+ ----- Method: Player>>sayText: (in category '*Etoys-SpeechBubbles') -----
+ sayText: aString
+ self costume renderedMorph say: aString!

Item was added:
+ ----- Method: Player>>getRowIndex (in category '*Etoys-graphing') -----
+ getRowIndex
+ | rowCount |
+ (rowCount := self getRowCount) ifNil: [^0].
+ self rowIndex > rowCount ifTrue: [self rowIndex: self getRowCount].
+ ^ self rowIndex!

Item was added:
+ ----- Method: VectorMorph>>magnitude: (in category 'accessing') -----
+ magnitude: magnitude
+ | o a degrees |
+ degrees := self angle.
+ o := degrees degreesToRadians sin * magnitude.
+ a := degrees degreesToRadians cos * magnitude.
+ terminalPoint := (initialPoint + (a at o)).
+ self update.!

Item was added:
+ ----- Method: Player>>getVectorMagnitude (in category '*Etoys-graphing') -----
+ getVectorMagnitude
+ | current |
+ current := self currentVector.
+ ^current isNil ifTrue: [nil] ifFalse: [current magnitude]!

Item was added:
+ ----- Method: SpeechBubbleMorph>>minimumAcceptedWidth (in category 'accessing') -----
+ minimumAcceptedWidth
+ ^ 175 max: self msgMorph fullBounds width + 20!

Item was added:
+ ----- Method: Player>>setRowIndex: (in category '*Etoys-graphing') -----
+ setRowIndex: aNumber 
+ | rowCount |
+ ((rowCount := self getRowCount) isNil or: [rowCount = 0]) ifTrue: [^self].
+ self rowIndex: aNumber - 1 \\ self getRowCount + 1!

Item was added:
+ ----- Method: CartesianGraphMorph>>yMajorGrid: (in category 'accessing grid') -----
+ yMajorGrid: aNumber
+ self majorGrid: self majorGrid x @ ((aNumber max: 0) rounded).!

Item was added:
+ ----- Method: VectorMorph>>initialPointY: (in category 'accessing') -----
+ initialPointY: aNumber
+ | angle magnitude |
+ angle := self angle.
+ magnitude := self magnitude.
+ initialPoint := initialPoint x @ aNumber.
+ self angle: angle; magnitude: magnitude!

Item was added:
+ ----- Method: Player>>setXMax: (in category '*Etoys-graphing') -----
+ setXMax: aNumber
+ self setCostumeSlot: #xMax: toValue: aNumber!

Item was added:
+ ----- Method: BarGraphMorph>>min (in category 'accessing range') -----
+ min
+ ^self range first!

Item was added:
+ ----- Method: Player>>removeCurrentPoint (in category '*Etoys-graphing') -----
+ removeCurrentPoint
+ self getPointIndex = 0 ifTrue: [^self].
+ self sendMessageToCostume: #removePointAt: with: self getPointIndex.
+ self setPointIndex: self getPointIndex - 1!

Item was added:
+ ----- Method: VectorMorph>>update (in category 'update') -----
+ update
+ self penUpWhile: [self from: (graph cartesianPointToPixel: initialPoint) to: (graph cartesianPointToPixel: terminalPoint)]!

Item was added:
+ ----- Method: DataGraphMorph>>removeAllVectors (in category 'accessing vectors') -----
+ removeAllVectors
+ 	vectorMorphs do: [:each| each delete].
+ 	self initializeVectors!

Item was added:
+ ----- Method: Player>>thinkNumber: (in category '*Etoys-SpeechBubbles') -----
+ thinkNumber: aNumber
+ self costume renderedMorph think: aNumber asString!

Item was added:
+ ----- Method: BarGraphMorph>>drawGridForm (in category 'building') -----
+ drawGridForm
+ | aCanvas |
+ "For performance, I keep the background in a separate form and redraw it only when it's necessary (i.e. changing the gridding parameters or the extent of the morph)"
+ gridForm isNil ifTrue: [^self].
+ aCanvas := gridForm getCanvas.
+ aCanvas fillColor: backgroundColor .
+ self isVerticalGraph ifTrue: [self drawHorizontalGridOn: aCanvas] ifFalse: [self drawVerticalGridOn: aCanvas]!

Item was added:
+ ----- Method: Player>>getMin (in category '*Etoys-graphing') -----
+ getMin
+ ^self  sendMessageToCostume: #min!

Item was added:
+ ----- Method: CartesianGraphMorph>>minorGrid (in category 'accessing grid') -----
+ minorGrid
+ ^minorGrid!

Item was added:
+ ----- Method: Player>>thinkText: (in category '*Etoys-SpeechBubbles') -----
+ thinkText: aString
+ self costume renderedMorph think: aString!

Item was added:
+ ----- Method: Player>>setMyBarColor: (in category '*Etoys-graphing') -----
+ setMyBarColor: aColor
+ ^ self setCostumeSlot: #color: toValue: aColor
+ !

Item was added:
+ ----- Method: DataGraphMorph>>removeAllPoints (in category 'accessing points') -----
+ removeAllPoints
+ 	pointMorphs do: [:each| each delete].
+ 	self initializePoints	!

Item was added:
+ ----- Method: BarTableMorph>>rowCount (in category 'accessing') -----
+ rowCount
+ ^(list submorphs select: [:each| each isAlignmentMorph and: [each submorphs first isTextMorph]]) size!

Item was added:
+ ----- Method: SpeechBubbleMorph>>containsPoint: (in category 'testing') -----
+ containsPoint: aPoint
+ ^ (self bounds containsPoint: aPoint) and:
+ 	  [(self imageForm isTransparentAt: aPoint - bounds origin) not]
+ !

Item was added:
+ ----- Method: BarTableMorph>>addRow (in category 'actions') -----
+ addRow
+ 	| |
+ 	numberOfRows := numberOfRows + 1.
+ 	list addMorph: (self makeRow: nil)   asElementNumber: numberOfRows + 1.
+ 	self updateScrollPane.!

Item was added:
+ ----- Method: Player>>setYMinorGrid: (in category '*Etoys-graphing') -----
+ setYMinorGrid: aNumber
+ self setCostumeSlot: #yMinorGrid: toValue: aNumber!

Item was added:
+ ----- Method: Player>>moveUp: (in category '*Etoys-graphing') -----
+ moveUp: aNumber
+ ^ self sendMessageToCostume: #move: with: 0 @ aNumber!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>supplementaryPartsDescriptions (in category 'parts bin') -----
+ supplementaryPartsDescriptions
+ 	"Answer a list of DescriptionForPartsBin objects that characterize objects that this class wishes to contribute to Stationery bins *other* than by the standard default #newStandAlone protocol"
+ 
+ 	^ {
+ 	DescriptionForPartsBin
+ 		formalName: 'Speech bubble' translatedNoop
+ 		categoryList: #('Just for Fun')
+ 		documentation: '' translatedNoop
+ 		globalReceiverSymbol: #SpeechBubbleMorph
+ 		nativitySelector: #speechPrototype.
+ 
+ 	DescriptionForPartsBin
+ 		formalName: 'Thought bubble' translatedNoop
+ 		categoryList: #('Just for Fun')
+ 		documentation: '' translatedNoop
+ 		globalReceiverSymbol: #SpeechBubbleMorph
+ 		nativitySelector: #thoughtPrototype.
+ 
+ 	DescriptionForPartsBin
+ 		formalName: 'Speech bubble (graphic)' translatedNoop
+ 		categoryList: #('Just for Fun')
+ 		documentation: '' translatedNoop
+ 		globalReceiverSymbol: #SpeechBubbleMorph
+ 		nativitySelector: #speechGraphicPrototype.
+ 
+ 	DescriptionForPartsBin
+ 		formalName: 'Thought bubble (graphic)' translatedNoop
+ 		categoryList: #('Just for Fun')
+ 		documentation: '' translatedNoop
+ 		globalReceiverSymbol: #SpeechBubbleMorph
+ 		nativitySelector: #thoughtGraphicPrototype.
+ }
+ !

Item was added:
+ ----- Method: VectorMorph>>dismissViaHalo (in category 'initialize-release') -----
+ dismissViaHalo
+ 	self remove.
+ 	super dismissViaHalo!

Item was added:
+ ----- Method: CartesianGraphMorph>>updateBackground (in category 'updating') -----
+ updateBackground
+ self drawGridForm; placeAxes; placeXLegends; placeYLegends; changed!

Item was added:
+ ----- Method: BarGraphMorph>>barAt:put: (in category 'accessing bars') -----
+ barAt: index put: aBarMorph
+ "
+ (barMorphs at: index ifAbsent: [^self error: 'Bar not found']) bar: anAssociation."
+ barMorphs at: index put: aBarMorph!

Item was added:
+ ----- Method: VectorMorph>>setGraph:initialPoint:terminalPoint: (in category 'private') -----
+ setGraph: aDataGraphMorph initialPoint: aPoint terminalPoint: anotherPoint
+ graph := aDataGraphMorph.
+ initialPoint := aPoint.
+ terminalPoint := anotherPoint!

Item was added:
+ ----- Method: Player>>setPointX: (in category '*Etoys-graphing') -----
+ setPointX: aNumber
+ | current |
+ current := self currentPoint.
+ ^current isNil ifTrue: [nil] ifFalse: [current pointX: aNumber]!

Item was added:
+ ----- Method: Player>>removePointAt: (in category '*Etoys-graphing') -----
+ removePointAt: aNumber
+ (aNumber > self getPointCount or: [aNumber <= 0])
+ 	ifTrue: [^self].
+ self sendMessageToCostume: #removePointAt: with: aNumber.
+ self getPointIndex = aNumber ifTrue: [self setPointIndex: self getPointIndex - 1]!

Item was added:
+ ----- Method: VectorMorph>>position: (in category 'accessing') -----
+ position: aPoint
+ super position: aPoint.
+ self update!

Item was added:
+ ----- Method: Player>>pointIndex: (in category '*Etoys-graphing') -----
+ pointIndex: aNumber
+ self costume renderedMorph setProperty: #pointIndex toValue: aNumber.!

Item was added:
+ ----- Method: CartesianGraphMorph>>backgroundColor: (in category 'accessing colors') -----
+ backgroundColor: aColor
+ backgroundColor := aColor.
+ self updateBackground.!

Item was added:
+ ----- Method: BarGraphMorph>>initializeDistanceBetweenBars (in category 'initialize-release') -----
+ initializeDistanceBetweenBars
+ 	distanceBetweenBars := 45
+ !

Item was added:
+ ----- Method: SpeechBubbleMorph>>selectedTailForm (in category 'accessing') -----
+ selectedTailForm
+ 	^type caseOf: {
+ 		[#speech] -> [self class speakingForm].
+ 		[#thought] -> [self class thinkingForm].
+ 		} otherwise: [self error: 'Wrong type']!

Item was added:
+ ----- Method: Player>>getBarLabel (in category '*Etoys-graphing') -----
+ getBarLabel
+ ^self sendMessageToCostume: #barLabelAt: with: self getBarIndex.
+ !

Item was changed:
+ ----- Method: Player>>getBackgroundColor (in category '*Etoys-graphing') -----
+ getBackgroundColor 
+ ^ self getValueFromCostume: #backgroundColor!
- ----- Method: Player>>getBackgroundColor (in category 'scripts-standard') -----
- getBackgroundColor
- 	"Answer the background color; the costume is presumed to be a TextMorph"
- 
- 	^  self costume renderedMorph backgroundColor ifNil: [Color transparent]!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>speechGraphicPrototype (in category 'parts bin') -----
+ speechGraphicPrototype
+ 	^self form: (ScriptingSystem formAtKey: 'Painting') type: #speech!

Item was added:
+ ----- Method: Player>>setMyVectorAngle: (in category '*Etoys-graphing') -----
+ setMyVectorAngle: aNumber
+ self setCostumeSlot: #angle: toValue: aNumber
+ !

Item was added:
+ ----- Method: BarGraphMorph>>barValueAt: (in category 'accessing bars') -----
+ barValueAt: barIndex
+ | current |
+ current := self barAt: barIndex ifAbsent: [^nil].
+ ^current barValue!

Item was added:
+ ----- Method: BarGraphMorph>>removeBarsFrom:to: (in category 'accessing bars') -----
+ removeBarsFrom: start to: stop
+ | removed |
+ removed := OrderedCollection new.
+ start to: stop do: [:i|
+ 	removed add: (barMorphs at: i) delete.
+ 	].
+ barMorphs removeAllFoundIn: removed.
+ self updateBars.!

Item was added:
+ ----- Method: BarTableMorph>>rowLabelAt: (in category 'accessing') -----
+ rowLabelAt: barIndex
+ | count |
+ count := 0.
+ self list submorphs do: [:each |
+ 	(each isAlignmentMorph and: [ each submorphs first isTextMorph])
+ 	 ifTrue: [
+ 		count := count + 1.
+ 		count = barIndex ifTrue: [
+ 			^each submorphs first contents asString
+ 			]
+ 		]
+ 	]!

Item was added:
+ ----- Method: Player>>getPointColor (in category '*Etoys-graphing') -----
+ getPointColor
+ | current |
+ current := self currentPoint.
+ ^current isNil ifTrue: [Color black] ifFalse: [current color]!

Item was added:
+ ----- Method: BarTableMorph>>rows (in category 'accessing') -----
+ rows
+ "Searches across the submorphs and returns an array of points with the data written by the user"
+ 	| data firstSubmorph secondSubmorph label value |
+ 	data := OrderedCollection new.
+ 	list
+ 		submorphsDo: [:morph | morph isAlignmentMorph
+ 				ifTrue: [
+ 					label := value := nil.
+ 					firstSubmorph := morph submorphs first.
+ 					secondSubmorph := morph submorphs second.
+ 					firstSubmorph isTextMorph
+ 						ifTrue: [firstSubmorph contents asString = ''
+ 								ifFalse: [label := firstSubmorph contents asString]].
+ 					secondSubmorph isTextMorph
+ 						ifTrue: [secondSubmorph contents asString = ''
+ 								ifFalse: [value := secondSubmorph getNumericValue]].
+ 					(label notNil
+ 							and: [value isNumber])
+ 						ifTrue: [data add: label -> value]]].
+ 	^ data!

Item was added:
+ ----- Method: BarTableMorph>>updateScrollPane (in category 'actions') -----
+ updateScrollPane
+ 	scrollPane "hHideScrollBar;" vScrollBarValue: 1; vSetScrollDelta!

Item was added:
+ ----- Method: BarGraphMorph>>addBar (in category 'accessing bars') -----
+ addBar
+ | m index label |
+ index := self barCount + 1.
+ label := (($A to: $Z) at: index ifAbsent: [$#]) asString.
+ m := BarMorph graph: self label: label value: 1 index: index.
+ ^self addBar: m!

Item was added:
+ ----- Method: SpeechBubbleMorph>>drawBalloonOn:in: (in category 'drawing') -----
+ drawBalloonOn: aCanvas in: sourceRect
+ | cornerBounds rect1 rect2 |
+ cornerBounds := self class topLeftCornerForm boundingBox.
+ aCanvas translucentImage: self class topLeftCornerForm at: sourceRect topLeft;
+ 		translucentImage: self class topRightCornerForm at: sourceRect topRight - (cornerBounds width @ 0);
+ 		translucentImage: self class bottomLeftCornerForm at: sourceRect bottomLeft - (0 @ (cornerBounds height));
+ 		translucentImage: self class bottomRightCornerForm at: sourceRect bottomRight - cornerBounds extent.
+ 
+ rect1 := sourceRect topLeft + (cornerBounds width @ 1) corner: sourceRect bottomRight - (cornerBounds width @ 1).
+ rect2 := sourceRect topLeft + (1 @ cornerBounds height) corner: sourceRect bottomRight - (1 @ cornerBounds height).
+ aCanvas fillRectangle: rect1 color: Color white; fillRectangle: rect2 color: Color white.
+ aCanvas line: rect1 topLeft to: rect1 topRight width: 2 color: Color black;
+ 		line: rect1 bottomLeft to: rect1 bottomRight width: 2 color: Color black;
+ 		line: rect2 topLeft to: rect2 bottomLeft width: 2 color: Color black;
+ 		line: rect2 topRight to: rect2 bottomRight width: 2 color: Color black.
+ !

Item was added:
+ ----- Method: Player>>getXLegendSpacing (in category '*Etoys-graphing') -----
+ getXLegendSpacing
+ ^ self getValueFromCostume: #xLegendSpacing!

Item was added:
+ ----- Method: CartesianGraphMorph>>xMin (in category 'accessing cartesian bounds') -----
+ xMin
+ ^self cartesianBounds left!

Item was added:
+ CartesianGraphMorph subclass: #BarGraphMorph
+ 	instanceVariableNames: 'barMorphs distanceBetweenBars graphType graphDirection'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Etoys-Graphing'!

Item was added:
+ ----- Method: PointTableMorph>>initialize (in category 'initialize') -----
+ initialize
+ 	| data |
+ 	super initialize.
+ 	self borderWidth: 0;
+ 		
+ 		color: ((Color
+ 				r: 0.817
+ 				g: 0.864
+ 				b: 0.797)
+ 				mixed: 0.75
+ 				with: Color blue muchDarker);
+ 		 hResizing: #shrinkWrap;
+ 		 vResizing: #shrinkWrap;
+ 		 listDirection: #topToBottom;
+ 		 cornerStyle: #rounded.
+ 	data := graph points collect: [:each | each pointX @ each pointY].
+ 	numberOfRows := data size max: 10.
+ 	self initializeSubmorphsWithData: data!

Item was added:
+ ----- Method: DataGraphMorph>>removePointAt: (in category 'accessing points') -----
+ removePointAt: index
+ 	| p |
+ 	p := pointMorphs at: index ifAbsent: [^self error: 'Point not found'].
+ 	p delete.
+ 	pointMorphs removeAt: index.!

Item was added:
+ ----- Method: Player>>setMajorGridColor: (in category '*Etoys-graphing') -----
+ setMajorGridColor: aColor
+ ^ self setCostumeSlot: #majorGridColor: toValue: aColor!

Item was added:
+ ----- Method: Player>>setMyBarValue: (in category '*Etoys-graphing') -----
+ setMyBarValue: aNumber
+ ^ self setCostumeSlot: #barValue: toValue: aNumber
+ !

Item was added:
+ ----- Method: Player>>currentBar (in category '*Etoys-graphing') -----
+ currentBar
+ | selector |
+ selector := #barAt:ifAbsent:.
+ ^(self costumeRespondingTo: selector) ifNotNilDo: [:c | c perform: selector withArguments: {self getBarIndex. [nil]}]!

Item was added:
+ ----- Method: CartesianGraphMorph>>yMax (in category 'accessing cartesian bounds') -----
+ yMax
+ ^self cartesianBounds bottom!

Item was added:
+ ----- Method: PointTableMorph classSide>>on: (in category 'instance creation') -----
+ on: aDataGraphMorph
+ ^(self basicNew setGraph: aDataGraphMorph) initialize !

Item was added:
+ ----- Method: CartesianGraphMorph>>preferredPositionForYLegend:at: (in category 'building') -----
+ preferredPositionForYLegend: legendString at: gridPos
+ "The preferred position is at the left of the vertical axis and above the major grid.
+ If nothing can be drawn return nil"
+ | preferredPosition font axis |
+ axis :=  verticalAxis center x.
+ font := TextStyle defaultFont.
+ preferredPosition := (axis - (font widthOfString: legendString)) @ (gridPos - (font height / 2)).
+ "If the legend height doesn't fit inside the form"
+ (preferredPosition y < self top)
+ 	ifTrue: [^ nil "Draw nothing"].
+ "If the axis is not visible"
+ (axis < self left or: [axis > self right])
+ 	ifTrue: [^self left + 3 @ preferredPosition y].
+ "If the axis is close to the left so the legend width doesn't fit inside the form"
+ (preferredPosition x < self left)
+ 	ifTrue: [^(axis + 3 @ preferredPosition y) ].
+ "If the preferred position is perfect :)"
+ ^preferredPosition!

Item was added:
+ ----- Method: PointTableMorph>>list (in category 'accessing') -----
+ list
+ 	^list!

Item was added:
+ ----- Method: Player>>setYMin: (in category '*Etoys-graphing') -----
+ setYMin: aNumber
+ self setCostumeSlot: #yMin: toValue: aNumber!

Item was added:
+ ----- Method: CartesianGraphMorph>>drawSubmorphsOn: (in category 'drawing') -----
+ drawSubmorphsOn: aCanvas 
+ 	"Display submorphs back to front"
+ 
+ 	| drawBlock |
+ 	submorphs isEmpty ifTrue: [^self].
+ 	drawBlock := [:canvas | submorphs reverseDo: [:m | canvas fullDrawMorph: m]].
+ 	self clipSubmorphs 
+ 		ifTrue: [aCanvas clipBy: self clippingBounds during: drawBlock]
+ 		ifFalse: [drawBlock value: aCanvas]!

Item was added:
+ ----- Method: PointTableMorph>>rowsFilled (in category 'accessing') -----
+ rowsFilled
+ ^ self rows size!

Item was added:
+ ----- Method: PointTableMorph>>rowXAt:put: (in category 'accessing') -----
+ rowXAt: pointIndex put: aNumber
+ | count |
+ count := 0.
+ self list submorphs do: [:each|
+ 	(each isAlignmentMorph and: [ each submorphs first isTextMorph])
+ 	 ifTrue: [
+ 		count := count + 1.
+ 		count = pointIndex ifTrue: [
+ 			each submorphs first contentsWrapped: aNumber asString.
+ 			^self
+ 			]			
+ 		]
+ 	]!

Item was added:
+ ----- Method: SpeechBubbleMorph>>target: (in category 'accessing') -----
+ target: aMorph
+ 	target := aMorph.
+ 	target notNil ifTrue: [self positionMyselfAccordingToTarget ]!

Item was added:
+ ----- Method: SpeechBubbleMorph>>balloon (in category 'accessing') -----
+ balloon
+ 	^balloon ifNil: [
+ 		| balloonForm |
+ 		balloonForm := Form extent: self extent - (0 @ self tailHeight) depth: 16.
+ 		self drawBalloonOn: balloonForm getCanvas in: balloonForm boundingBox.
+ 		balloonForm floodFill: self color at: balloonForm center.
+ 		balloon := (SketchMorph withForm: balloonForm).
+ 	]!

Item was added:
+ ----- Method: CartesianGraphMorph classSide>>additionsToViewerCategoryPlotCoordinateSystem (in category 'viewer categories') -----
+ additionsToViewerCategoryPlotCoordinateSystem
+ ^#(#'plot - coordinate system' (
+ #(command moveLeft: '' Number)
+ #(command moveRight: '' Number)
+ #(command moveUp: '' Number)
+ #(command moveDown: '' Number)
+ #(command restoreInitialPosition '')
+ #(slot xMax '' Number readWrite Player getXMax Player setXMax:  )
+ #(slot xMin '' Number readWrite Player getXMin Player setXMin:  )
+ #(slot yMax '' Number readWrite Player getYMax Player setYMax:  )
+ #(slot yMin '' Number readWrite Player getYMin Player setYMin:  )
+ ))!

Item was added:
+ ----- Method: Player>>getMyBarValue (in category '*Etoys-graphing') -----
+ getMyBarValue
+ ^ self getValueFromCostume: #barValue!

Item was added:
+ ----- Method: BarTableMorph>>rowLabelAt:put: (in category 'accessing') -----
+ rowLabelAt: barIndex put: aString
+ | count |
+ count := 0.
+ self list submorphs do: [:each|
+ 	(each isAlignmentMorph and: [ each submorphs first isTextMorph])
+ 	 ifTrue: [
+ 		count := count + 1.
+ 		count = barIndex ifTrue: [
+ 			each submorphs first contentsWrapped: aString asString.
+ 			^self
+ 			]			
+ 		]
+ 	]!

Item was added:
+ ----- Method: DataGraphMorph>>addPoint (in category 'accessing points') -----
+ addPoint
+ self addPoint: (PointMorph graph: self point: 0 at 0).
+ !

Item was added:
+ ----- Method: Player>>getPlayerAtVectorIndex (in category '*Etoys-graphing') -----
+ getPlayerAtVectorIndex
+ | current |
+ current := self currentVector.
+ ^current isNil ifTrue: [self presenter standardPlayer] ifFalse: [current assuredPlayer]
+ !

Item was added:
+ ----- Method: PointMorph classSide>>defaultNameStemForInstances (in category 'as yet unclassified') -----
+ defaultNameStemForInstances
+ 	^ 'Point' !

Item was added:
+ PolygonMorph subclass: #VectorMorph
+ 	instanceVariableNames: 'graph initialPoint terminalPoint'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Etoys-Graphing'!
+ 
+ !VectorMorph commentStamp: 'Richo 4/18/2010 00:23' prior: 0!
+ This object is used by DataGraphMorph to draw vectors. It needs to know the graph in which it is plotted to be able to update its position whenever necessary.!

Item was added:
+ ----- Method: DataGraphMorph classSide>>examplePoints (in category 'examples') -----
+ examplePoints
+ "To watch the example simply execute (Cmd-d):
+ 
+ self examplePoints
+ 
+ "
+ | graph | 
+ 
+ "Creating the morph and opening it in the world"
+ graph := DataGraphMorph new.
+ graph openInHand.
+ 
+ "Setting the grid parameters"
+ graph minorGrid: 2 at 3.
+ graph majorGrid: 4 at 6.
+ 
+ "Setting the legend spacing"
+ graph legendSpacing: 8 at 6.
+ 
+ "Setting the x/y range"
+ graph cartesianBounds: ((-15 at -15) corner: (15 at 15)).
+ 
+ "Changing the default colors"
+ graph backgroundColor: Color black.
+ graph minorGridColor: Color cyan.
+ graph majorGridColor: Color magenta.
+ graph axisColor: Color white.
+ 
+ "Ploting a sine wave"
+ -15 to: 15 by: 0.5 do: [:x|
+ 	graph addPoint: x @ (x sin).
+ ].!

Item was added:
+ ----- Method: VectorMorph>>initialPointX (in category 'accessing') -----
+ initialPointX
+ ^initialPoint x!

Item was added:
+ ----- Method: Player>>setVectorIndex: (in category '*Etoys-graphing') -----
+ setVectorIndex: aNumber
+ self getVectorCount = 0 ifTrue: [^self].
+ self vectorIndex: aNumber - 1 \\ self getVectorCount + 1!

Item was added:
+ ----- Method: SpeechBubbleMorph>>color: (in category 'accessing') -----
+ color: aColor
+ 	super color: aColor.
+ 	self refresh!

Item was added:
+ ----- Method: BarGraphMorph>>restoreInitialPosition (in category 'accessing range') -----
+ restoreInitialPosition
+ self range: (-1 to: 19); update!

Item was added:
+ ----- Method: BarTableMorph>>newTextMorph (in category 'building') -----
+ newTextMorph
+ 	^ TextMorph new autoFit: false;
+ 		 extent: self textMorphWidth @ 23;
+ 		 borderWidth: 1;
+ 		 backgroundColor: Color white;
+ 		crPassesFocus: true;
+ 		highlightsOnFocus: true;
+ 		 yourself!

Item was added:
+ ----- Method: PointTableMorph>>initializeSubmorphsWithData: (in category 'building') -----
+ initializeSubmorphsWithData: data 
+ 	"data should be a collection of points."
+ 	self addMorphBack: self makeColumnNames;
+ 		
+ 		addMorphBack: (self makeListWithData: data);
+ 		 addMorphBack: ((SimpleButtonMorph newWithLabel: '-') color: (Color
+ 				r: 0.4
+ 				g: 0.8
+ 				b: 0.6) lighter;
+ 			 borderWidth: 2;
+ 			 width: (self textMorphWidth * 2) + 29;
+ 			 target: self;
+ 			 actionSelector: #removeRow);
+ 		 addMorphBack: (Morph new color: Color transparent;
+ 			 extent: 10 @ 3);
+ 		 addMorphBack: ((SimpleButtonMorph newWithLabel: '+') color: (Color
+ 				r: 0.4
+ 				g: 0.8
+ 				b: 0.6) lighter;
+ 			 borderWidth: 2;
+ 			 width:  (self textMorphWidth * 2) + 29;
+ 			 target: self;
+ 			 actionSelector: #addRow);
+ 		 addMorphBack: (Morph new color: Color transparent;
+ 			 extent: 10 @ 3);
+ 		 addMorphBack: ((SimpleButtonMorph newWithLabel: 'Apply') width:  (self textMorphWidth * 2) + 29;
+ 			 target: self;
+ 			 actionSelector: #apply)!

Item was added:
+ ----- Method: SpeechBubbleMorph classSide>>bottomLeftCornerForm (in category 'forms') -----
+ bottomLeftCornerForm
+ ^self topLeftCornerForm flipBy: #vertical centerAt: self topLeftCornerForm boundingBox topCenter!

Item was added:
+ ----- Method: CartesianGraphMorph>>legendSpacing (in category 'accessing legends') -----
+ legendSpacing
+ ^legendSpacing!

Item was added:
+ ----- Method: Player>>setPointY: (in category '*Etoys-graphing') -----
+ setPointY: aNumber
+ | current |
+ current := self currentPoint.
+ ^current isNil ifTrue: [nil] ifFalse: [current pointY: aNumber]!

Item was added:
+ ----- Method: Player>>getMyBarColor (in category '*Etoys-graphing') -----
+ getMyBarColor
+ ^ self getValueFromCostume: #color!

Item was added:
+ ----- Method: BarGraphMorph classSide>>additionsToViewerCategoryPlotBars (in category 'viewer categories') -----
+ additionsToViewerCategoryPlotBars
+ ^#(#'plot - bars' (
+ #(slot playerAtBarIndex '' Player readWrite Player getPlayerAtBarIndex  unused unused)
+ #(slot graphDirection '' GraphDirection  readWrite Player getGraphDirection Player setGraphDirection:  )
+ #(slot barIndex '' Number  readWrite Player getBarIndex Player setBarIndex:  )
+ #(command removeBarAt: '' Number )
+ #(command removeAllBars '')
+ #(command removeCurrentBar '')
+ #(command addBar '')
+ #(slot barValue '' Number readWrite Player getBarValue Player setBarValue:  )
+ #(slot barLabel '' String readWrite Player getBarLabel Player setBarLabel:  )
+ #(command openBarTable '')
+ #(slot barCount '' Number readOnly Player getBarCount Player unused  )
+ #(slot barColor '' Color readWrite Player getBarColor Player setBarColor:  )
+ #(slot distanceBetweenBars '' Number readWrite Player getDistanceBetweenBars Player setDistanceBetweenBars:  )
+ ))!

Item was added:
+ ----- Method: CartesianGraphMorph classSide>>additionsToViewerCategoryPlotColors (in category 'viewer categories') -----
+ additionsToViewerCategoryPlotColors
+ ^#(#'plot - colors' (
+ #(slot axisColor '' Color readWrite Player getAxisColor Player setAxisColor:  )
+ #(slot backgroundColor '' Color readWrite Player getBackgroundColor Player setBackgroundColor:  )
+ #(slot majorGridColor '' Color readWrite Player getMajorGridColor Player setMajorGridColor:  )
+ #(slot minorGridColor '' Color readWrite Player getMinorGridColor Player setMinorGridColor:  )
+ #(command restoreDefaultColors '' )
+ ))!

Item was added:
+ ----- Method: Player>>setGraphDirection: (in category '*Etoys-graphing') -----
+ setGraphDirection: aSymbol
+ 	self setCostumeSlot: #graphDirection: toValue: aSymbol!

Item was added:
+ ----- Method: SpeechBubbleMorph>>string (in category 'accessing') -----
+ string
+ ^(msgMorph isKindOf: UserText) ifTrue: [msgMorph contents]!

Item was added:
+ ----- Method: Player>>getBarCount (in category '*Etoys-graphing') -----
+ getBarCount
+ ^ self getValueFromCostume: #barCount!

Item was added:
+ ----- Method: BarGraphMorph>>majorGrid (in category 'accessing grid') -----
+ majorGrid
+ ^self isVerticalGraph ifTrue: [super majorGrid y] ifFalse: [super majorGrid x]!

Item was added:
+ ----- Method: BarTableMorph classSide>>includeInNewMorphMenu (in category 'as yet unclassified') -----
+ includeInNewMorphMenu
+ 	"Return true for all classes that can be instantiated from the menu"
+ 	^ false!

Item was added:
+ ----- Method: VectorMorph>>terminalPointX: (in category 'accessing') -----
+ terminalPointX: aNumber
+ terminalPoint := aNumber @ terminalPoint y.
+ self update.!

Item was added:
+ ----- Method: Player>>getMyTerminalPointX (in category '*Etoys-graphing') -----
+ getMyTerminalPointX
+ ^ self getValueFromCostume: #terminalPointX!

Item was added:
+ ----- Method: Player>>barIndex: (in category '*Etoys-graphing') -----
+ barIndex: aNumber
+ self costume renderedMorph setProperty: #barIndex toValue: aNumber.!

Item was added:
+ ----- Method: Player>>setPointColor: (in category '*Etoys-graphing') -----
+ setPointColor: aColor
+ | current |
+ current := self currentPoint.
+ ^current isNil ifTrue: [nil] ifFalse: [current color: aColor]!

Item was added:
+ ----- Method: Player>>barIndex (in category '*Etoys-graphing') -----
+ barIndex
+ ^self costume renderedMorph valueOfProperty: #barIndex ifAbsent: [self getBarCount > 0 ifTrue: [1] ifFalse: [0]].!

Item was added:
+ ----- Method: CartesianGraphMorph>>initializeLegends (in category 'initialize-release') -----
+ initializeLegends
+ 	legends := Dictionary new at: #x put: OrderedCollection new;
+ 				 at: #y put: OrderedCollection new;
+ 				 yourself.
+ 	self placeXLegends; placeYLegends !

Item was added:
+ ----- Method: Player>>getVectorCount (in category '*Etoys-graphing') -----
+ getVectorCount
+ ^self getValueFromCostume: #vectorCount!



More information about the etoys-dev mailing list