Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
LearnMorphic.st
Last updated at 3:20 pm UTC on 30 June 2018
"Classes used in the active essay Programming Morphs


Flasher is used as well but that is in the image.
"
Morph subclass: #FollowerMorph
	instanceVariableNames: 'morphToFollow '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'LearnMorphic'!
!FollowerMorph commentStamp: '<historical>' prior: 0!
A morph that follows around another morph.  Or at least, it should -- can you fix it?
!


!FollowerMorph methodsFor: 'initialization' stamp: 'ls 6/12/2001 01:50'!
morphToFollow: aMorph
	"set which morph this morph should follow around the screen"
	morphToFollow := aMorph! !

Morph subclass: #KeyControlledMorph
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'LearnMorphic'!
!KeyControlledMorph commentStamp: '<historical>' prior: 0!
A morph  that moves around according to key presses.  Or at least it should.  Can you fix it?!


Morph subclass: #LetterShowingMorph
	instanceVariableNames: 'theLetter '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'LearnMorphic'!
!LetterShowingMorph commentStamp: '<historical>' prior: 0!
A morph that displays the last character typed by the user while pointing at the morph.!


!LetterShowingMorph methodsFor: 'initialization' stamp: 'ls 6/12/2001 01:29'!
initialize
	super initialize.
	theLetter := $A.! !


!LetterShowingMorph methodsFor: 'drawing' stamp: 'ls 6/12/2001 01:31'!
drawOn: aCanvas
	aCanvas frameRectangle: self bounds width: 1 color: self color.
	aCanvas
		text: theLetter asString
		bounds: (self topLeft + (10@10) corner: self bottomRight)
		font: nil
		color: self color.! !


!LetterShowingMorph methodsFor: 'the letter' stamp: 'ls 6/12/2001 01:32'!
newLetter: aCharacter
	"change the letter that is being displayed"
	theLetter := aCharacter.
	self changed.! !


!LetterShowingMorph methodsFor: 'event handling' stamp: 'ls 6/12/2001 01:38'!
handleKeystroke: evt
	self newLetter: evt keyCharacter! !

!LetterShowingMorph methodsFor: 'event handling' stamp: 'ls 6/12/2001 01:40'!
handlesMouseOver: evt
	^true! !

!LetterShowingMorph methodsFor: 'event handling' stamp: 'ls 6/12/2001 01:40'!
mouseEnter: evt
	"grab keyboard events"
	evt hand newKeyboardFocus: self.
! !

!LetterShowingMorph methodsFor: 'event handling' stamp: 'ls 6/12/2001 01:34'!
mouseLeave: evt
	"ignore keyboard events"
	evt hand newKeyboardFocus: nil.! !


Morph subclass: #ToggleMorph
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'LearnMorphic'!
!ToggleMorph commentStamp: '<historical>' prior: 0!
A morph that switches between white and black when it is clicked with the yellow button.  Well, at least, it *should* swtich back and forth, but it doesn't yet.  Can you finish this class?!