MorphicGreeting (was Re: [Newbies] "Smart Paper"?

Edgar J. De Cleene edgardec2001 at yahoo.com.ar
Sun Jul 6 10:56:15 UTC 2008




El 7/6/08 7:36 AM, "Prashanth Hebbar" <hebbarp at gmail.com> escribió:

> Edgar:
> 
> That's a cute kitten! I am interested in looking into the project file. Can
> you send it to me or let me know how best to source it.
> 
> Regards,

Here the fileOut of original 2002  project.
Was one of my first on Squeak.
Later or tomorrow i look in back ups , have some older of how to read the
colors from external ascii file and have Squeak "learn" this new colors.
Could be useful to some...

Works with GreetingMorph new, the pict and the midi should be on the same
Squeak folder.
Somewhere I have a modern version for explore the computer for files...

I on a half hour and then I start to watch formula one

Edgar

-------------- next part --------------
'From Squeak3.8 of ''5 May 2005'' [latest update: #6665] on 6 July 2008 at 7:48:04 am'!
BorderedMorph subclass: #GreetingMorph
	instanceVariableNames: 'music greetString image'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Greeting'!

!GreetingMorph methodsFor: 'stepping' stamp: 'EDC 8/21/2002 17:40'!
step
| x y n each |
 submorphs size = 0 ifTrue: [ self  doGreet].
n _ (1 to: submorphs size) atRandom.
each  _ submorphs at: n.
each class == ImageMorph ifTrue: [^self].
x  _ (20 to: 730) atRandom.
 y  _ (20 to: 470) atRandom.
each position: x at y.
each comeToFront.
self refreshWorld
! !

!GreetingMorph methodsFor: 'stepping' stamp: 'EDC 7/20/2002 07:20'!
stepTime
	"Answer the desired time between steps in milliseconds."

	^ 1000! !

!GreetingMorph methodsFor: 'initialization' stamp: 'EDC 7/20/2002 15:41'!
backColor: aColor

self color: aColor! !

!GreetingMorph methodsFor: 'initialization' stamp: 'EDC 7/21/2002 06:25'!
chooseColor
| buttons file rgb linea valores b max paleta maxX x y cuenta |
paleta _ PasteUpMorph new.
paleta layoutPolicy: nil.
paleta hResizing: #rigid.
paleta vResizing: #rigid.
paleta borderWidth: 2.
paleta borderColor: Color black.
paleta color: Color white.
paleta openInWorld.
maxX _ 0.

x _ 0.
y _ 0.
cuenta _ 0.
	
	buttons _ OrderedCollection new.
	file _ FileStream oldFileNamed: 'ColoresCrayon.text'.
[file atEnd] whileFalse: [  linea_ file nextLine.
valores _ linea findTokens: Character space. 
rgb _ valores collect: [:each| (each asInteger / 65535) asFloat].
linea_ file nextLine.
b _ (SimpleButtonMorph new label: linea;
					
					color:  (Color fromArray: rgb);
					 target: self;
 actionSelector: #backColor:;
					
					arguments: (Array
							with: (Color fromArray: rgb)) ).
buttons add: b].
b _ (SimpleButtonMorph new label: 'Enough Fun ?';
					color:  Color white;
					 target: self;
 actionSelector: #killFrontDialog).
buttons add: b.
"Compute the max width"
	max _ 0.
	buttons do: [:each | max _ each width max: max].
	"Set all widths to the max value"
	buttons do: [:each | each width: max].


	buttons
		reverseDo: [:each | 
each position: x at y.
	paleta addMorph: each.
cuenta < 7
ifTrue: [x _ x + each width.
cuenta _ cuenta + 1]
ifFalse: [y _ y + each height.
x > maxX
ifTrue: [maxX _ x].
x _ 0.
cuenta _ 0.
]].
maxX _ maxX + 10 .
y _ y + 10.
paleta extent: maxX @ y.
paleta position: 30 at 30 .
paleta becomeLikeAHolder.
! !

!GreetingMorph methodsFor: 'initialization' stamp: 'EDC 7/22/2002 08:08'!
chooseMidi
| f score fileName |
fileName _ Utilities chooseFileWithSuffixFromList: #('.mid' '.midi')
					withCaption: 'Choose a MIDI file to open'.
	(fileName isNil or: [ fileName == #none ])
		ifTrue: [^ self inform: 'No .mid/.midi files found in the Squeak directory'].
f _ FileStream readOnlyFileNamed: fileName.
	score _ (MIDIFileReader new readMIDIFrom: f binary) asScore.
	f close.
music _ ScorePlayer onScore: score.
! !

!GreetingMorph methodsFor: 'initialization' stamp: 'EDC 12/31/2002 14:39'!
choosePhoto
	| fileName  |
	fileName _ Utilities chooseFileWithSuffixFromList: #('.jpg' '.gif' ) withCaption: 'Choose a graphic file to open'.
	(fileName isNil
			or: [fileName == #none])
		ifTrue: [^ self inform: 'No .jpg/.gif files found in the Squeak directory'].
	image _ (Form fromFileNamed: fileName) asMorph.
	self addMorphCentered: image! !

!GreetingMorph methodsFor: 'initialization' stamp: 'EDC 12/31/2002 11:52'!
crayonColorsDefine
	| stolenData |
	stolenData _ #(65535 55705 45875 #Apricot 0 58982 58982 #Aquamarine 55705 19661 0 #Bittersweet 19005 19661 51773 #Blue 32768 40632 47185 #Blue #Gray 0 45219 41287 #Blue #Green 5898 0 21626 #Blue #Violet 44564 0 0 #Brick 32768 9830 0 #Brown 38666 16384 0 #Burnt #Sienna 65535 49151 49151 #Carnation 32768 3277 0 #Chinese #Red 45875 13107 2621 #Copper 41942 37355 65535 #Cornflower 0 24248 0 #Forest #Green 65535 52428 0 #Gold 65535 49151 13107 #Goldenrod 39321 39321 39321 #Gray 22937 36700 40632 #Gray #Blue 0 53739 0 #Green 0 39321 41287 #Green #Blue 52428 65535 0 #Green #Yellow 65535 45875 65535 #Lavender 65535 65535 19661 #Lemon 65535 0 65535 #Magenta 46530 16384 0 #Mahogany 65535 49151 6554 #Maize 51117 0 17039 #Maroon 65535 22937 14418 #Melon 0 5243 26214 #Midnight 55049 0 30801 #Mulberry 0 0 38010 #Navy 55049 55049 17694 #Olive 65535 39321 0 #Orange 65535 6554 0 #Orange #Red 65535 49151 0 #Orange #Yellow 65535 32768 65535 #Orchid 65535 52428 42598 #Peach 45875 45875 55705 #Periwinkle 4587 26869 15728 #Pine #Green 18350 0 26214 #Plum 15728 0 21627 #Purple 45219 17694 0 #Raw #Sienna 21627 5243 0 #Raw #Umber 57671 0 0 #Red 65535 16384 0 #Red #Orange 57015 0 47841 #Red #Violet 65535 32768 45875 #Rose 65535 39321 32768 #Salmon 0 65535 26214 #Seafoam 30146 9830 13107 #Sepia 42598 42598 42598 #Silver 47185 60292 65535 #Sky 0 65535 0 #Spring #Green 57015 18350 0 #Swamp #Fire 47841 25559 0 #Tan 0 52428 52428 #Turquoise 13107 0 21627 #Violet #Blue 58982 0 65535 #Violet #Red 65535 65535 0 #Yellow 45875 65535 0 #Yellow #Green 65535 42598 0 #Yellow #Orange ).
^ stolenData! !

!GreetingMorph methodsFor: 'initialization' stamp: 'EDC 12/31/2002 14:45'!
doGreet
	| greetWords cartel |
	music reset.
	music resumePlaying.
	self center: Display center.
	self toggleStickiness.
	self addMorphCentered: image.
	greetWords _ greetString findTokens: Character space.
	greetWords
		do: [:greet | 
			cartel _ TTSampleStringMorph new initializeToStandAlone.
			cartel string: greet.
			cartel center: self center.
			cartel bottom: self bottom + 10.
			self addMorphBack: cartel.
			self openInWorld]! !

!GreetingMorph methodsFor: 'initialization' stamp: 'EDC 8/21/2002 17:25'!
initialize
	super initialize.
	self extent: 750 @ 490.
	self color: Color paleBlue.
	self borderWidth: 2.
	
	greetString _ FillInTheBlank request: 'Please, type your message' initialAnswer: 'Edgar, from SqueakRos, say long life and prosperity.'.
self choosePhoto.
	self chooseMidi.
	self doGreet! !

!GreetingMorph methodsFor: 'initialization' stamp: 'EDC 7/21/2002 06:05'!
killFrontDialog
| dialog |
.
dialog _ ActiveWorld submorphs
				detect: [:m | m class == PasteUpMorph].
dialog delete.! !

!GreetingMorph methodsFor: 'menu' stamp: 'EDC 7/21/2002 06:20'!
addCustomMenuItems: aCustomMenu hand: aHandMorph 
	"Include our modest command set in the ctrl-menu"
	super addCustomMenuItems: aCustomMenu hand: aHandMorph.
	aCustomMenu addLine.
	self addMenuItemsTo: aCustomMenu hand: aHandMorph! !

!GreetingMorph methodsFor: 'menu' stamp: 'EDC 7/22/2002 08:03'!
addMenuItemsTo: aMenu hand: aHandMorph 
	aMenu
		add: 'new background color'
		target: self
		action: #chooseColor.
	aMenu
		add: 'new midi music.'
		target: self
		action: #chooseMidi.
	aMenu
		add: 'save this greet'
		target: self
		action: #saveMorph! !

!GreetingMorph methodsFor: 'fileIn/out' stamp: 'EDC 7/22/2002 08:12'!
saveMorph
self stopStepping.
	submorphs _ EmptyArray.
	^ self saveOnFile! !

!GreetingMorph methodsFor: 'event handling' stamp: 'EDC 5/17/2002 05:34'!
handlesMouseDown: evt 
	"Prevent stray clicks from picking up the whole game in MVC."
	^ Smalltalk isMorphic not
		or: [evt yellowButtonPressed]! !

!GreetingMorph methodsFor: 'event handling' stamp: 'EDC 5/17/2002 05:32'!
mouseDown: evt 
	| menu |
	evt yellowButtonPressed
		ifFalse: [^ self].
	menu _ MenuMorph new defaultTarget: self.
	self addMenuItemsTo: menu hand: evt hand.
	menu popUpEvent: evt in: self world! !

!GreetingMorph methodsFor: 'accessing' stamp: 'EDC 12/31/2002 14:37'!
greetString
	"Answer the value of greetString"

	^ greetString! !

!GreetingMorph methodsFor: 'accessing' stamp: 'EDC 12/31/2002 14:37'!
greetString: anObject
	"Set the value of greetString"

	greetString _ anObject! !

!GreetingMorph methodsFor: 'accessing' stamp: 'EDC 12/31/2002 14:37'!
image
	"Answer the value of image"

	^ image! !

!GreetingMorph methodsFor: 'accessing' stamp: 'EDC 12/31/2002 14:37'!
image: anObject
	"Set the value of image"

	image _ anObject! !

!GreetingMorph methodsFor: 'accessing' stamp: 'EDC 12/31/2002 14:37'!
music
	"Answer the value of music"

	^ music! !

!GreetingMorph methodsFor: 'accessing' stamp: 'EDC 12/31/2002 14:37'!
music: anObject
	"Set the value of music"

	music _ anObject! !



More information about the Beginners mailing list