[etoys-dev] Etoys Inbox: GSoC-SpeechBubbles-Richo.6.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Aug 7 12:31:24 EDT 2010


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

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

Name: GSoC-SpeechBubbles-Richo.6
Author: Richo
Time: 9 July 2010, 8:30:55 pm
UUID: d439ca8c-9f39-f34e-99bc-c21d5eece5ea
Ancestors: GSoC-SpeechBubbles-Richo.5

* Added the posibility of taking the object from the bubble (using the "Pick up" button of the halo). Now when you pick up the object in the bubble, the bubble will disappear.
* Saying/thinking an object doesn't make a copy anymore.

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

SystemOrganization addCategory: #'GSoC-SpeechBubbles'!

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

----- Method: Player>>sayGraphic: (in category '*GSoC-SpeechBubbles') -----
sayGraphic: aGraphic
self costume renderedMorph sayGraphic: aGraphic!

----- Method: Player>>sayNumber: (in category '*GSoC-SpeechBubbles') -----
sayNumber: aNumber
self costume renderedMorph say: aNumber asString!

----- Method: Player>>sayObject: (in category '*GSoC-SpeechBubbles') -----
sayObject: aPlayer
self costume renderedMorph sayObject: aPlayer!

----- Method: Player>>sayText: (in category '*GSoC-SpeechBubbles') -----
sayText: aString
self costume renderedMorph say: aString!

----- Method: Player>>stopSayingOrThinking (in category '*GSoC-SpeechBubbles') -----
stopSayingOrThinking
self costume renderedMorph stopSayingOrThinking!

----- Method: Player>>thinkGraphic: (in category '*GSoC-SpeechBubbles') -----
thinkGraphic: aGraphic
self costume renderedMorph thinkGraphic: aGraphic!

----- Method: Player>>thinkNumber: (in category '*GSoC-SpeechBubbles') -----
thinkNumber: aNumber
self costume renderedMorph think: aNumber asString!

----- Method: Player>>thinkObject: (in category '*GSoC-SpeechBubbles') -----
thinkObject: aPlayer
self costume renderedMorph thinkObject: aPlayer!

----- Method: Player>>thinkText: (in category '*GSoC-SpeechBubbles') -----
thinkText: aString
self costume renderedMorph think: aString!

Player subclass: #SpeechBubblePlayer
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'GSoC-SpeechBubbles'!

----- Method: SpeechBubblePlayer classSide>>isUniClass (in category 'as yet unclassified') -----
isUniClass
	^ self ~~ self officialClass!

----- Method: SpeechBubblePlayer classSide>>officialClass (in category 'as yet unclassified') -----
officialClass
	^ SpeechBubblePlayer!

----- Method: SpeechBubblePlayer classSide>>wantsChangeSetLogging (in category 'as yet unclassified') -----
wantsChangeSetLogging
	^ (self == self officialClass
			or: [(self name beginsWith: self officialClass asString) not])
		or: [Preferences universalTiles]!

----- Method: SpeechBubblePlayer>>attachTo: (in category 'as yet unclassified') -----
attachTo: aPlayer
self costume renderedMorph target: aPlayer costume renderedMorph
!

----- Method: SpeechBubblePlayer>>getAttachment (in category 'as yet unclassified') -----
getAttachment
	^ [self costume renderedMorph target assuredPlayer]
		on: Error
		do: [self presenter standardPlayer] !

----- Method: SpeechBubblePlayer>>stopAttaching (in category 'as yet unclassified') -----
stopAttaching
	self costume renderedMorph target: nil!

----- Method: Morph class>>additionsToViewerCategorySpeechBubbles (in category '*GSoC-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)		
		))!

----- Method: Morph>>bubble (in category '*GSoC-SpeechBubbles') -----
bubble
	^self valueOfProperty: #bubble ifAbsent: [nil].!

----- Method: Morph>>say: (in category '*GSoC-SpeechBubbles') -----
say: aString
self showMessage: aString inBubbleType: #speech!

----- Method: Morph>>sayGraphic: (in category '*GSoC-SpeechBubbles') -----
sayGraphic: aForm
self showGraphic: aForm inBubbleType: #speech!

----- Method: Morph>>sayObject: (in category '*GSoC-SpeechBubbles') -----
sayObject: aPlayer
self showObject: aPlayer inBubbleType: #speech!

----- Method: Morph>>showGraphic:inBubbleType: (in category '*GSoC-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).!

----- Method: Morph>>showMessage:inBubbleType: (in category '*GSoC-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)!

----- Method: Morph>>showObject:inBubbleType: (in category '*GSoC-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).!

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

----- Method: Morph>>think: (in category '*GSoC-SpeechBubbles') -----
think: aString
self showMessage: aString inBubbleType: #thought!

----- Method: Morph>>thinkGraphic: (in category '*GSoC-SpeechBubbles') -----
thinkGraphic: aForm
self showGraphic: aForm inBubbleType: #thought!

----- Method: Morph>>thinkObject: (in category '*GSoC-SpeechBubbles') -----
thinkObject: aPlayer
self showObject: aPlayer inBubbleType: #thought!

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

----- 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)		
		)
	)
!

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

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

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

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

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

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

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

----- 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)]!

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

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

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

----- 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!

----- 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!

----- 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: #(#GSoC)
		documentation: '' translatedNoop
		globalReceiverSymbol: #SpeechBubbleMorph
		nativitySelector: #speechPrototype.

	DescriptionForPartsBin
		formalName: 'Thought bubble' translatedNoop
		categoryList: #(#GSoC)
		documentation: '' translatedNoop
		globalReceiverSymbol: #SpeechBubbleMorph
		nativitySelector: #thoughtPrototype.

	DescriptionForPartsBin
		formalName: 'Speech bubble (graphic)' translatedNoop
		categoryList: #(#GSoC)
		documentation: '' translatedNoop
		globalReceiverSymbol: #SpeechBubbleMorph
		nativitySelector: #speechGraphicPrototype.

	DescriptionForPartsBin
		formalName: 'Thought bubble (graphic)' translatedNoop
		categoryList: #(#GSoC)
		documentation: '' translatedNoop
		globalReceiverSymbol: #SpeechBubbleMorph
		nativitySelector: #thoughtGraphicPrototype.
}
!

----- 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)]!

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

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

----- 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)]!

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

----- 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).
	]!

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

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

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

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

----- 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.
!

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

----- 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]!

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

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

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

----- 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.!

----- 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).
!

----- Method: SpeechBubbleMorph>>maximumStepTime (in category 'stepping') -----
maximumStepTime
	^500!

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

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

----- Method: SpeechBubbleMorph>>minimumStepTime (in category 'stepping') -----
minimumStepTime
	^20!

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

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

----- Method: SpeechBubbleMorph>>newPlayerInstance (in category 'initialize-release') -----
newPlayerInstance
	^SpeechBubblePlayer newUserInstance
!

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

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

----- 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.!

----- 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]!

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

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

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

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

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

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

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

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

----- 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]]
!

----- Method: SpeechBubbleMorph>>stepTime (in category 'stepping') -----
stepTime
^stepTime !

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

----- 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]!

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

----- Method: SpeechBubbleMorph>>target (in category 'accessing') -----
target
	^target!

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

----- Method: SpeechBubbleMorph>>type (in category 'accessing') -----
type
^type!



More information about the etoys-dev mailing list