[FIX] TransfoimingAMorphFix

Lic. Edgar J. De Cleene edgardec2001 at yahoo.com.ar
Wed Aug 21 21:14:03 UTC 2002


NISHIHARA Satoshi writes

> I'm using Squeak3.2-4956.image with Mac OS 8.5.1J and
> Windows XP v.2002, and get the same error. Please sure
> to drop the rotated child morph to the rotated parent
> morph, and drag/scale/rotate child morph.

Today I load Squeak3.2-4956.image
I send the following.
EllipseMorph with a star rotated inside. I don't have any problem.



>defining MatrixTransform2x3>>restoreEndianness
>(from another #restoreEndianness)

Yes this is Ned advice, and on my running Macs OS 9.1 works fine

Morphic-Greeting.st. Load this first.
GreetinMorph.morph.

I delete TTSampleStringMorph and recreate on load for endianess problem.

I hope Satoshi san enjoy the greet, and with guru figure how encapsulate all
in one morph (Yes I could use a project with changes), but If I can
encapsulate midi and jpg why not code ?.

I know in Japan you see the sun light before me.

Saludos desde Rosario, Argentina.

Edgar



-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/octet-stream
Size: 2955 bytes
Desc: not available
Url : http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20020821/2e9e1515/attachment.obj
-------------- next part --------------
BorderedMorph subclass: #GreetingMorph
	instanceVariableNames: 'music greetString '
	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: '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: '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 8/21/2002 17:24'!
choosePhoto
| fileName foto |
fileName _ Utilities chooseFileWithSuffixFromList: #('.jpg' '.gif')
					withCaption: 'Choose a graphic file to open'.
	(fileName isNil or: [ fileName == #none ])
		ifTrue: [^ self inform: 'No .mid/.midi files found in the Squeak directory'].
foto _ (Form fromFileNamed: fileName) asMorph.
self addMorphCentered: foto
! !

!GreetingMorph methodsFor: 'initialization' stamp: 'EDC 7/22/2002 08:25'!
doGreet
	| greetWords cartel |
	music reset.
	music resumePlaying.
self position: 18 @ 0.
	self toggleStickiness.
	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: '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! !
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/octet-stream
Size: 15374 bytes
Desc: not available
Url : http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20020821/2e9e1515/attachment-0001.obj


More information about the Squeak-dev mailing list