On 24 May 2010 22:11, Stéphane Ducasse <stephane.duca...@inria.fr> wrote:
>> Ok. Let me start.
>
> Excellent I want to learn.
> And I will ask cyrille to read all that.
> The first things is that we should get Rome working then we fix the api.
>
>
>> Rome/Athens adds variouls extension methods to classes which are
>> involved with graphics.
>> Here is one of them:
>>
>> GradientFillStyle>>installOnRomePluginCanvas: aCanvas
>>       | colorStops i |
>>       colorStops := WordArray new: colorRamp size * 3.
>>       i := 0.
>>       colorRamp do: [:stop |
>>               colorStops at: (i:=i+1) put: (stop key * 65536.0) rounded.
>>               colorStops at: (i:=i+1) put: stop value privateRGB.
>>               colorStops at: (i:=i+1) put: stop value privateAlpha].
>>       radial == true
>>               ifTrue: [
>>                       aCanvas primFillRadialGradientOriginX: origin x asFloat
>>                               y: origin y asFloat
>>                               directionX: direction x asFloat
>>                               y: direction y asFloat
>>                               normalX: self normal x asFloat
>>                               y: self normal y asFloat
>>                               colorStops: colorStops]
>>               ifFalse: [
>>                       aCanvas primFillLinearGradientOriginX: origin x asFloat
>>                               y: origin y asFloat
>>                               directionX: direction x asFloat
>>                               y: direction y asFloat
>>                               colorStops: colorStops]
>>
>> Good:
>> - a conversion method is context sensitive (it takes a canvas as an argument)
>> Bad:
>> - this conversion method will work only for Rome plugin and nothing else.
>
> how to you see that?
>

Well, consider this:

   colorRamp do: [:stop |
      colorStops at: (i:=i+1) put: (stop key * 65536.0) rounded.
      colorStops at: (i:=i+1) put: stop value privateRGB.
      colorStops at: (i:=i+1) put: stop value privateAlpha].

most likely, this will be inappropriate for anything else than RomePlugin.
While, of course each kind of canvas could implement own
#primFillLinearGradientOriginX: y:directionX: y: colorStops:
except that it should not be a prim, and then it will waste time converting
color stops again - into a form, which fits best for its own needs.
So, why using 2 conversions, where 1 is enough? :)

In same way, #asFloat may be not necessary, because canvas could
accept integers as well as floats,
so converting everything to floats is just a waste of time.

>
>> This means, that if i'd want to use different canvas, i will need to
>> add another method
>> which will perform a conversion.
>
> you lost me there. But I ;m sure that you will explain it to me :)
>

I meant that i would need to add the
GradientFillStyle>>installOnRomeGLCanvas: aCanvas
instead of reusing the code.

>
>> But this can be avoided, if we provide a generic canvas method to
>> create a gradient fills.
>> Then this method could be renamed to #installOnRomeCanvas:
>> and implementation will consist of messages, sent to canvas to build a
>> gradient fill.
>
> do you have a sketch that I follow the example 100%
>

GradientFillStyle>>installOnRomeCanvas: aCanvas
  ^ aCanvas cacheAt: self ifAbsentPut: [ aCanvas gradientFill: #linear
origin: ... colors: ... ]

and generally, a persistent resources (or ones which may change, but rarely)
could use a following pattern:

Something>>installOnRomeCanvas: aCanvas
  self isChanged ifTrue: [ aCanvas invalidateCache: self ].
  ^ aCanvas cacheAt: self ifAbsentPut: [ aCanvas createSomething: ... ]

Then, after heating-up, it will run at maximum efficiency by using a cached
(and already converted resources) instead of performing conversions each time.

>> Another example:
>>
>> asRomeFill , asRomeFont
>>
>> - this is bad.
>> Its not a context-sensitive. And therefore , an implementation of
>> these methods assumes that it will provide
>> the most suitable conversion of fill or font for Rome backend.
>> But depending on backend, it may not be the case!
>> So, all methods like this, should always use a canvas as argument and
>> talk back to canvas
>> to perform a conversion.
>
> I see we need a factory and the canvas will play this role.
>

Yes.


> Stef
>>
>>> Stef
>>>
>>>
>>> _______________________________________________
>>> Pharo-project mailing list
>>> Pharo-project@lists.gforge.inria.fr
>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>>
>>
>>
>> --
>> Best regards,
>> Igor Stasenko AKA sig.
>>
>> _______________________________________________
>> Pharo-project mailing list
>> Pharo-project@lists.gforge.inria.fr
>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>
>
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>



-- 
Best regards,
Igor Stasenko AKA sig.

_______________________________________________
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