Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
ProtoMorph
Last updated at 8:20 pm UTC on 7 January 2022
http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20030213/a0c164a7/MinimalProtoMorph.1.obj

A ProtoMorph is a kind of minimal Morph object clone obtained by running an initially empty subclass of Object in terms of methods. The methods are added as needed.

ProtoMorph was used as a tool to develop Bricks, initial code below.

It is supposed to work like a Morph object. It initially has no Morph methods. The doesNotUnderstand mechanism is used to copy and compile methods from class Morph as they are needed.

A ProtoMorph object is a sibling of a Morph object.


The original code from 2003
'From Squeak3.4gamma of ''7 January 2003'' [latest update: #5169] on 13 February 2003 at 2:22:56 am'!
Object subclass: #ProtoMorph
	instanceVariableNames: 'bounds owner submorphs fullBounds color extension '
	classVariableNames: 'EmptyArray '
	poolDictionaries: ''
	category: 'Morphic-Proto'!

!ProtoMorph methodsFor: 'error handling' stamp: 'tb 2/13/2003 01:40'!
cloneSelector: sel

	self class removeSelector: sel.
	self class copy: sel from: Morph.
	"(ChangeSet allInstances detect: [:ea | ea name = 'Morphic-Changes']) fileOut."
! !

!ProtoMorph methodsFor: 'error handling' stamp: 'tb 2/13/2003 00:40'!
doesNotUnderstand: aMessage 

	Morph sourceCodeAt: (aMessage selector) ifAbsent: [ super doesNotUnderstand: aMessage].
	self cloneSelector: (aMessage selector).
	^self perform: (aMessage selector) withArguments: (aMessage arguments).
	! !

!ProtoMorph methodsFor: 'genie-processing' stamp: 'tb 2/12/2003 23:21'!
defaultGestureDictionaryOrName
	"This method returns the default gesture dictionary name for the instances 
	of a Morph class. (It's also possible to directly return a dictionary but it's much
	more flexible to return the name).
	This generic implementation returns the class name if there is a dictionary 
	exported under this name. If not, it tries the name of the superclass, etc."

	| class |
	self gestureHandler ~~ self 
		ifTrue: [^ self gestureHandler defaultGestureDictionaryOrName].

	class _ self class.
	[class ~= Object and: 
		[(CRDictionary exportedName: class name asSymbol) isNil]] whileTrue:
			[class _ class superclass].
	
	^ (CRDictionary exportedName: class name asSymbol) isNil
		ifTrue: [self class name asSymbol]
		ifFalse: [class name asSymbol].! !


!ProtoMorph class methodsFor: 'class initialization' stamp: 'tb 2/13/2003 01:26'!
initialize

	EmptyArray := #().
	self buildSelectorFaults! !

!ProtoMorph class methodsFor: 'instance creation' stamp: 'tb 2/12/2003 22:40'!
new

	^ super new initialize! !

!ProtoMorph class methodsFor: 'instance creation' stamp: 'tb 2/12/2003 22:42'!
newBounds: bounds

	^ self new privateBounds: bounds! !

!ProtoMorph class methodsFor: 'instance creation' stamp: 'tb 2/12/2003 22:43'!
newBounds: bounds color: color

	^ (self new privateBounds: bounds) privateColor: color
! !

!ProtoMorph class methodsFor: 'instance creation' stamp: 'tb 2/12/2003 22:43'!
newSticky

	^ self new beSticky! !

!ProtoMorph class methodsFor: 'debugging' stamp: 'tb 2/13/2003 00:45'!
buildSelectorFaults

	Morph methodDictionary keys do: [:sel |
		((Object methodDictionary includesKey: sel) and: 
			[(self methodDictionary includesKey: sel) not]) ifTrue:
		[
			| src header |
			header := Morph methodHeaderFor: sel.
			src := (header, ' self cloneSelector: ', (sel printString), '. ^self ', header).
			self compile: src classified: 'object-overrides'.
		]
	]

			! !

ProtoMorph initialize!


Using the code in Squeak 5.2


The steps below describe some adaptions when working with the code above in Squeak 5.2.



Frist step - File in the slightly modified code


In Squeak 5.2 #defaultGestureDictionaryOrName is no longer called.
So this method has been removed from the code copied in again below.

ProtoMorph has on the instance side

ProtoMorph has on the class side

'From Squeak3.4gamma of ''7 January 2003'' [latest update: #5169] on 13 February 2003 at 2:22:56 am'!
Object subclass: #ProtoMorph
	instanceVariableNames: 'bounds owner submorphs fullBounds color extension '
	classVariableNames: 'EmptyArray '
	poolDictionaries: ''
	category: 'Morphic-Proto'!

!ProtoMorph methodsFor: 'error handling' stamp: 'tb 2/13/2003 01:40'!
cloneSelector: sel

	self class removeSelector: sel.
	self class copy: sel from: Morph.
	"(ChangeSet allInstances detect: [:ea | ea name = 'Morphic-Changes']) fileOut."
! !

!ProtoMorph methodsFor: 'error handling' stamp: 'tb 2/13/2003 00:40'!
doesNotUnderstand: aMessage 

	Morph sourceCodeAt: (aMessage selector) ifAbsent: [ super doesNotUnderstand: aMessage].
	self cloneSelector: (aMessage selector).
	^self perform: (aMessage selector) withArguments: (aMessage arguments).
	! !

!ProtoMorph class methodsFor: 'class initialization' stamp: 'tb 2/13/2003 01:26'!
initialize

	EmptyArray := #().
	self buildSelectorFaults! !

!ProtoMorph class methodsFor: 'instance creation' stamp: 'tb 2/12/2003 22:40'!
new

	^ super new initialize! !

!ProtoMorph class methodsFor: 'instance creation' stamp: 'tb 2/12/2003 22:42'!
newBounds: bounds

	^ self new privateBounds: bounds! !

!ProtoMorph class methodsFor: 'instance creation' stamp: 'tb 2/12/2003 22:43'!
newBounds: bounds color: color

	^ (self new privateBounds: bounds) privateColor: color
! !

!ProtoMorph class methodsFor: 'instance creation' stamp: 'tb 2/12/2003 22:43'!
newSticky

	^ self new beSticky! !

!ProtoMorph class methodsFor: 'debugging' stamp: 'tb 2/13/2003 00:45'!
buildSelectorFaults

	Morph methodDictionary keys do: [:sel |
		((Object methodDictionary includesKey: sel) and: 
			[(self methodDictionary includesKey: sel) not]) ifTrue:
		[
			| src header |
			header := Morph methodHeaderFor: sel.
			src := (header, ' self cloneSelector: ', (sel printString), '. ^self ', header).
			self compile: src classified: 'object-overrides'.
		]
	]

			! !

ProtoMorph initialize!



2nd step - get methods from class Morph


Execute some Morphic code snippets but for ProtoMorph
 ProtoMorph new inspect

and
 ProtoMorph new color: Color red.

You will note in the SystemBrowser that the ProtoMorph class now has got a number of methods. But the code snippets will not succeed.

One reason is that the instance variable 'bounds' is nil.

If you follow this up you will note that the #initialize method is missing in ProtoMorph. It was not copied because it did not go through the method copying process as ProtoMorph understands #initialize.

So the #initialize method has to be copied manually from the class Morph.


After adding the #initialize method run

 ((Morph new extent: 120@100) addMorph: ProtoMorph new) openInHand

Two debugger windows come up but also the result so far, see picture

Morph_with_ProtoMorph_object_1.png

..... to be continued.


Manually copy method #step

Simplified version of

 indicateKeyboardFocus

	^ false

on the class side, category 'preferences'