Hi Phil. Excellent summary of the current mess!

Yes, TextMorphs are the "views" , Editors handle the
insertion/selection/menu logic, and Paragraphs lay out the text.

I've replaced Paragraph, with Pango Layouts to reuse a more
customizable layout engine, until some kind soul rewrites completely
Paragraph (and friends) to be as easy to use (and powerfull) as Pango
(which i doubt it will happen in the next decade).


Denis, unfortunately i had to handle other stuff related to my phd,
and still couldn't release Gaucho/Shapes, I'm working on it now again.
Here's a presentation i gave @ the pharo conf [1]. Glad to hear that
you want to try to use it for Presently, will be out soon.

[1] 
http://app.sliderocket.com:80/app/FullPlayer.aspx?id=fcff251e-29cd-49eb-89b3-e33349139ddf




On Fri, Jul 20, 2012 at 4:26 PM, p...@highoctane.be <p...@highoctane.be> wrote:
> So, there is the damn caret drawing code:
>
> Paragraph>>displaySelectionInLine: line on: aCanvas
> | leftX rightX w caretColor |
> selectionStart ifNil: [^self]. "No selection"
> aCanvas isShadowDrawing ifTrue: [ ^self ]. "don't draw selection with shadow"
> selectionStart = selectionStop
> ifTrue:
> ["Only show caret on line where clicked"
>
> selectionStart textLine ~= line ifTrue: [^self]]
> ifFalse:
> ["Test entire selection before or after here"
>
> (selectionStop stringIndex < line first
> or: [selectionStart stringIndex > (line last + 1)]) ifTrue: [^self]. "No 
> selection on this line"
> (selectionStop stringIndex = line first
> and: [selectionStop textLine ~= line]) ifTrue: [^self]. "Selection ends on 
> line above"
> (selectionStart stringIndex = (line last + 1)
> and: [selectionStop textLine ~= line]) ifTrue: [^self]]. "Selection begins on 
> line below"
> leftX := (selectionStart stringIndex < line first
> ifTrue: [line ]
> ifFalse: [selectionStart ])left.
> rightX := (selectionStop stringIndex > (line last + 1) or:
> [selectionStop stringIndex = (line last + 1)
> and: [selectionStop textLine ~= line]])
> ifTrue: [line right]
> ifFalse: [selectionStop left].
> selectionStart = selectionStop
> ifTrue:
> [rightX := rightX + 1.
> w := self caretWidth.
> caretRect := (leftX-w) @ line top corner: (rightX+w)@ line bottom.
> self showCaret ifFalse:[^self].
> caretColor := self insertionPointColor.
> 1 to: w
> do:
> [:i |
> "Draw caret triangles at top and bottom"
>
> aCanvas fillRectangle: ((leftX - w + i - 1) @ (line top + i - 1)
> extent: ((w - i) * 2 + 3) @ 1)
> color: caretColor.
> aCanvas fillRectangle: ((leftX - w + i - 1) @ (line bottom - i)
> extent: ((w - i) * 2 + 3) @ 1)
> color: caretColor].
> aCanvas fillRectangle: (leftX @ line top corner: rightX @ line bottom)
> color: caretColor]
> ifFalse:
> [caretRect := nil.
> aCanvas fillRectangle: (leftX @ line top corner: rightX @ line bottom)
> color: self selectionColor]
>
>
>
>
> Paragraph class>>insertionPointColor has the color. I was fed up of blue, 
> turned it red :-)
> This one is hardcoded and could take a hint from the selection color 
> twiceDarker for example.
>
> Phil
>
> 2012/7/20 Denis Kudriashov <dionisi...@gmail.com<mailto:dionisi...@gmail.com>>
> Hello
>
> 2012/7/20 Fernando Olivero 
> <fernando.oliv...@usi.ch<mailto:fernando.oliv...@usi.ch>>
> Hi Sean, you can take a look at Athens-PangoCairo (in squeaksource).
>
> Using NativeBoost, i'm using the Pango layout library [1], and the
> Pango-Cairo binding [2],  to avoid laying out text using the outdated
> (and messy) stuff in the image.
>
> Check out the classes: ParagraphDescription & AthensPangoCairoParagraph.
>
> I'm using them as the basis for the TextShape,LabelShape, and
> EditableTextShape in Shapes / Gaucho ( using TextEditor,
> SingleLineEditor ).
>
> Maybe somebody can do the same for Morphic? use Pango to layout the
> text, and code a new TextMorph on top of it?
>
> How I can try your code?
> Do you have ready image to play with it?
>
> I am very interested with clean and simple alternative to morphic. I want it 
> for Presenty framework.
>
> (But I really like morphic as live user interface environment)
>
> Best regards,
> Denis
>
>
>
>
>
>
> --
> Philippe Back
> Dramatic Performance Improvements
> Mob: +32(0) 478 650 140 | Fax: +32 (0) 70 408 027 Mail: 
> p...@highoctane.be<mailto:p...@highoctane.be> | Web: http://philippeback.eu | 
> Blog: http://philippeback.be
>
> High Octane SPRL
> rue cour Boisacq 101
> 1301 Bierges
> Belgium

Reply via email to