> 
> I tried (one of these felt very satisfying):
> * Morph>>on:send:to:, which sounded good, but never got called
> * intercepting Morph>>processEvent:using: (which I was told was not a good 
> idea)
> * (after seeking help), locking the submorphs and overriding the dozen or so 
> event-related methods in the chain from my morph to TextMorphForShout (the 
> Morph that actually handles the text and input).
> * subclassing TextMorphForShout and then subclassing PluggableShoutMorph to 
> use that subclass.


If you use NewTextMorph it becomes trivial, because it uses Announcements to 
announce editions, enter and escape.

| m newTextMorph  |

SmalltalkEditor initialize.
TextEditor initialize.
Editor initialize.

m := Morph new.
m class
        compile:'changeColor
                self fillStyle: Color random.
                self extent: self submorphs anyOne extent .
                self changed';
        compile: 'rollbackMorphClass
                self delete .
                self class
                        removeSelector: #changeColor;
                        removeSelector: #rollbackMorphClass. '.
newTextMorph := NewTextMorph new.
newTextMorph
        padding: 0 ;
        borderWidth: 0 ;
        fillStyle: Color transparent ;
        onEscapeSend: #rollbackMorphClass to: m;
        onAcceptSend: #changeColor to: m;
        onEditionSend:#changeColor to: m ;      
        readOnly: false ;
        announcesEditions: true;
        autoFit: true .
m
        addMorph: newTextMorph;
        perform: #changeColor ;
        openInWorld.
_______________________________________________
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Reply via email to