Phil

Sorry for the state of the system. We are cleaning slowly.
Now what would be good is that if you could enhance the class comments.
Igor started to write a new paragraph (or text representation) I guess that he 
needs some help/feedback.
Igor should be back from holiday so ping him please :).

Stef

> Ah, the morass into which I am currently digging...
> 
> Well, if we look at it for a while, it becomes a tad clearer.
> 
> PluggableTextMorph is just a shell for a TextMorph.
> 
> The TextMorph basically displays a Text (which can be styled with 
> TextAttributes)
> 
> When moving into edition, there is an editor known by the TextMorph but this 
> is not an editor like I understood it, but rather a helper object that will 
> come handy with TextMorph>>handleInteraction: interactionBlock
> 
> Inside handleInteraction, there is that editor and paragraph and then a call 
> to interaction blockValue.
> 
> And the interactionBlock is containing a bunch of various things that 
> delegate the real editing work to the editor.
> 
> Like in aTextMorph>>handleInteraction: [editor mouseUp: evt]
> 
> If you then look into the editor (mostly SmalltalkEditor right now in the 
> image), you see a quite large method for that mouseUp: evt handling. And lots 
> of other things.
> 
> There should be a cleanup occuring in the Editor -> TextEditor -> 
> SmalltalkEditor hierarchy.
> 
> The TextEditor knows a bit too much and I am currently implementing a child 
> of TextEditor to have a simple, clean editor that does only the basics for my 
> purpose. Once I am please with it, it may become an interesting child of 
> Editor (maybe the TextEditor itself, with TextEditor renamed to something 
> else (for example, TextEditor has something with codeCompletionAround).
> 
> TextEditor and friends do have a ton of class side methods with all the 
> commands, keystrokes, and menu entries. Very important to grasp how that 
> works.
> 
> The TextMorph>>editorClass returns the editor class to use. Currently the 
> SmalltalkEditor (yikes!)
> 
> If gets taken in TextMorph>>installEditorToReplace: priorEditor, where we get 
> editor := self editorClass forMorph: self.
> 
> digging further, we get TextEditor>>forMorph: aMorph returning
> 
> ^self basicNew initWithMorph: aMorph.
> 
> and ... we'll get there! ... TextEditor>>initWithMorph: aMorph
> 
>       super initialize.
>       morph := aMorph.
>       self resetState.
> 
> So, we now have both linked. 
> 
> That dance occurs everytime we get something occuring to the TextMorph.
> 
> >>handleEvent: anEvent will do anEvent sendTo: self and then the usual:
> 
> evt sendTo: anObject, which will handle the event with ^anObjject 
> handleMouseUp, donw, ...
> 
> That is where we get back to the self handleInteraction: evt which calls the 
> [editor mouseUp: evt]  through the TextMorph handleInteraction.
> 
> An interesting bit occurs with the TextMorph>>yellowActivity; shiftKeyState 
> for the menus (and the PragmaMenuBuilder and strings like 'smalltalkMenu' 
> looking into SmallTalk editor for menu entries (Class side, yellowButtonMenu 
> and shifted friend).
> 
> That's it for editor, except we need to say a word on its lifecyle:
> 
> It gets created and destroyed all the time: created with TextMorph>>hasFocus, 
> going away with keyBoardFocusChange
> 
> 
> Then for Paragraph, just realize that Paragraphis something to be used like;
> 
> Paragraph new
>   compose: text "Coming from the TextMorph"
>   style: textStyle copy "always copy these beasties"
>   from: 1
>   in (0@0 extent: extX@extY);
>   adjustRightX;
>   ...
> 
> So, the Paragraph is composing the text into an area, taking into account the 
> styles that are in the text The TextStyle is the default style, it can be 
> overriden by some TextAttribute.
> 
> And that's where the TextMorph>>drawOn: aCanvas comes into play.
> 
> if will invoke Canvas>>paragraph: which will draw the text.
> 
> This will lead us to CharacterScanner and friends (CompositionScanner) and 
> TextComposer depending on it.
> 
> look for composeLineFrom: to: .... or composeAllLines.
> 
> This will call Paragraph>>composeAll
> 
> ^self multiComposeLinesFrom: firstCharIndex
> to: text size
> delta: 0
> into: OrderedCollection new "Ah, there we will end up into"
> priorLines: Array new
> atY: container top.
> 
> 
> So, it may be interesting to see how Paragraph works, but paragraph has 
> nothing to do with Editor.
> 
> Paragraph renders the text if an editing change has to be shown display wise. 
> But doesn't know about the Editor.
> 
> TextMorph uses TextMorph>>updateFromParagraph and >>fit to do the stuff.
> 
> In CharacterScanner you can find interesting display code:
> 
> CharacterScanner>>basicScanCharactersFrom: startIndex
>   to: stopIndex
>   in: sourceString
>   rightX: rightX
>   stopConditions: stops "this one still a tad foggy to me"
>   kern: kernDelta
> 
> There is a primitive rendering a char down there. This is all for StrikeFont. 
> I don't know how TrueType is supported but there are 
> 
> As you are doing Vim keystrokes, check TextMorph>>basicKeyStroke that does 
> the same dance as the mouse events but invokes 
> 
> self handleInteraction: [editor keystroke evt] 
> self updateFromParagraph.
> super keystroke: evt.
> 
> So, hope this makes it all a bit clearer.
> 
> All of the PluggableTextMorph story builds upon all of the above to ensure a 
> scrolling window and widget pluggability. Which I do not care at this point 
> since I am designing a specific UI for a game.
> 
> Phil
> 
> 2012/7/18 Stéphane Ducasse <stephane.duca...@inria.fr>
> 
> On Jul 16, 2012, at 9:38 PM, Sean P. DeNigris wrote:
> 
> > For VimPharo, I want to have a different cursor depending on whether a tool
> > is in insert or normal mode.
> >
> > I tried a handful of ways, but they all failed or worked
> > partially/inconsistently. Here's some of them:
> > * add the state to the paragraph, but the entire paragraph gets replaced
> > during the life of the tool, so the state gets lost
> > * add the state to the editor, but the situation is the same
> > * add the state to PluggableTextMorph, override and access it from
> > TextMorphForEditView>>updateFromParagraph. This was an extreme PITA and got
> > me very acquainted with the emergency evaluator. It "worked", but only after
> > using the arrows a bit.
> >
> > Does anyone have any idea where I might hook in?
> >
> > <rant>I find the whole text system very confusing. What the heck does a
> > paragraph know about insertion points?? A view has one paragraph object,
> > even if there are several paragraphs (as understood by the rest of humanity
> > as a block of text with breaks between the adjoining ones. Editors and
> > Paragraphs are thrown out and replaced on a whim. I'm finding it very hard
> > to understand and modify</rant>
> 
> I got burned by that when I worked on my botanics env….
> it was terrible.
> 
> >
> > Thanks,
> > Sean
> >
> > --
> > View this message in context: 
> > http://forum.world.st/Customizing-the-Caret-of-a-PluggableTextMorph-tp4640245.html
> > Sent from the Pharo Smalltalk mailing list archive at Nabble.com.
> >
> 
> 
> 
> 
> 


Reply via email to