BitBlt looking for rule blitting an alpha mask + constant color

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
9 messages Options
Reply | Threaded
Open this post in threaded view
|

BitBlt looking for rule blitting an alpha mask + constant color

Igor Stasenko
 
Hello,

to what i see, there is no rule, which can use following formula:

result = constanColor * srcAlpha + (destColor * ( 1-srcAlpha))

where scrAlpha is taken from source form, and if source form is 8 bit
depth, it is assumed that form contains no RGB data, only alpha
channel.

A rule 41 is more generic, but requires to convert a source form to
32bpp before blitting :(
Maybe it worth modifying rule 41 to allow 8bit forms?
Or maybe its worth introducing a new one?
What you think?

This new rule is essentially useful for freetype plugin, which
receives an opacity mask from freetype library.
But unfortunately, because we don't have such rule,  we can't use a
bitmap, produced by freetype, directly unless converting it to 32bpp.
Or maybe we can, but looking at freetype font cache code, it seems
that every form is converted to 32bpp before placing in cache.

Being able to operate with 8bpp alpha-masks will reduce a memory
footprint & increase rendering speed considerably.

--
Best regards,
Igor Stasenko AKA sig.
Reply | Threaded
Open this post in threaded view
|

Re: BitBlt looking for rule blitting an alpha mask + constant color

Andreas.Raab
 
Easy. Make a color map that is set up such that

cmap := Bitmap new: 256.
0 to: 255 do:[:i|
   cmap at: i+1 put: (constColor alpha: i/255.0) pixelValue32.
].

Then BitBlt with that color map and Form blend. If you have more than 8
bit input, first create a ColorMap which extracts only the alpha component.

Cheers,
   - Andreas


Igor Stasenko wrote:

>  
> Hello,
>
> to what i see, there is no rule, which can use following formula:
>
> result = constanColor * srcAlpha + (destColor * ( 1-srcAlpha))
>
> where scrAlpha is taken from source form, and if source form is 8 bit
> depth, it is assumed that form contains no RGB data, only alpha
> channel.
>
> A rule 41 is more generic, but requires to convert a source form to
> 32bpp before blitting :(
> Maybe it worth modifying rule 41 to allow 8bit forms?
> Or maybe its worth introducing a new one?
> What you think?
>
> This new rule is essentially useful for freetype plugin, which
> receives an opacity mask from freetype library.
> But unfortunately, because we don't have such rule,  we can't use a
> bitmap, produced by freetype, directly unless converting it to 32bpp.
> Or maybe we can, but looking at freetype font cache code, it seems
> that every form is converted to 32bpp before placing in cache.
>
> Being able to operate with 8bpp alpha-masks will reduce a memory
> footprint & increase rendering speed considerably.
>
Reply | Threaded
Open this post in threaded view
|

Re: BitBlt looking for rule blitting an alpha mask + constant color

Igor Stasenko

2009/6/20 Andreas Raab <[hidden email]>:
>
> Easy. Make a color map that is set up such that
>
> cmap := Bitmap new: 256.
> 0 to: 255 do:[:i|
>  cmap at: i+1 put: (constColor alpha: i/255.0) pixelValue32.
> ].
>

That is possible, but the price is generating a color map each time
the color changes :(
Much less price than converting/using 32 bpp, but still is not perfect :)

> Then BitBlt with that color map and Form blend. If you have more than 8 bit
> input, first create a ColorMap which extracts only the alpha component.
>

I found that rule 41 accepts the 8bpp bitmaps, but the problems is,
that its blends with yellow color, no matter
what i put in "A" or "B" (see below).

this is a Form's subclass method:.

blitOn: destForm at: aPoint color: color width: w height: h
        | col bitBlt map |
        map := Bitmap new: 256.
"A" 0 to: 255 do:[:i | map at: i+1 put: i ].
        col := (color pixelValueForDepth: 32).
        bitBlt := GrafPort toForm: destForm.
        bitBlt colorMap: map.
       
        bitBlt combinationRule: 41.
        bitBlt sourceForm: self.
        bitBlt destOrigin: aPoint.
        bitBlt width: w; height: h.
        bitBlt sourceOrigin: 0@0.
        bitBlt
"B" copyBitsColor: 16r00FF00 "(col bitAnd: 16rFFFFFF)"
                alpha: 255 " (col bitAnd: 16rFF000000) >> 24 "
                gammaTable: nil
                ungammaTable: nil

Any advice, how to force rule 41 work correctly? Or it is impossible? :)

Btw, i don't sure that my VM (windoze) having latest & fixed rule 41.
I remember there were problems with it.

> Cheers,
>  - Andreas
>
>
> Igor Stasenko wrote:
>>
>>  Hello,
>>
>> to what i see, there is no rule, which can use following formula:
>>
>> result = constanColor * srcAlpha + (destColor * ( 1-srcAlpha))
>>
>> where scrAlpha is taken from source form, and if source form is 8 bit
>> depth, it is assumed that form contains no RGB data, only alpha
>> channel.
>>
>> A rule 41 is more generic, but requires to convert a source form to
>> 32bpp before blitting :(
>> Maybe it worth modifying rule 41 to allow 8bit forms?
>> Or maybe its worth introducing a new one?
>> What you think?
>>
>> This new rule is essentially useful for freetype plugin, which
>> receives an opacity mask from freetype library.
>> But unfortunately, because we don't have such rule,  we can't use a
>> bitmap, produced by freetype, directly unless converting it to 32bpp.
>> Or maybe we can, but looking at freetype font cache code, it seems
>> that every form is converted to 32bpp before placing in cache.
>>
>> Being able to operate with 8bpp alpha-masks will reduce a memory
>> footprint & increase rendering speed considerably.
>>
>



--
Best regards,
Igor Stasenko AKA sig.
Reply | Threaded
Open this post in threaded view
|

Re: BitBlt looking for rule blitting an alpha mask + constant color

Andreas.Raab
 
Igor Stasenko wrote:

> 2009/6/20 Andreas Raab <[hidden email]>:
>> Easy. Make a color map that is set up such that
>>
>> cmap := Bitmap new: 256.
>> 0 to: 255 do:[:i|
>>  cmap at: i+1 put: (constColor alpha: i/255.0) pixelValue32.
>> ].
>
> That is possible, but the price is generating a color map each time
> the color changes :(
> Much less price than converting/using 32 bpp, but still is not perfect :)

It's utterly trivial to cache it. If you're using this for font display
you'll only have a few colors to deal with so the cache won't be big.

> Any advice, how to force rule 41 work correctly? Or it is impossible? :)
>
> Btw, i don't sure that my VM (windoze) having latest & fixed rule 41.
> I remember there were problems with it.

I'm not sure what rule 41 does. The Windows VM contains whatever is in
VMMaker.

Cheers,
   - Andreas
Reply | Threaded
Open this post in threaded view
|

Re: BitBlt looking for rule blitting an alpha mask + constant color

Igor Stasenko

Alain, maybe you can help resolving the confusion?
I'm trying calling

copyBitsColor: argbColorSmallInteger alpha: argbAlphaSmallInteger
gammaTable: gammaByteArray ungammaTable: ungammaByteArray
        "This entry point to BitBlt supplies an extra argument to specify the
fore color
        argb value for operation 41. This is split into an alpha value and an
rgb value,
        so that both can be passed as smallIntegers to the primitive.
        rgbColorInteger must be a smallInteger between 0 and 16rFFFFFF.
        alpha must be a smallInteger between 0 and 16rFF."
        <primitive: 'primitiveCopyBits' module: 'BitBltPlugin'>


And plugin sources, which i have, indeed taking care of arguments and
setting the componentAlphaModeColor :

------------------
copyBitsLockedAndClipped
        "Perform the actual copyBits operation.
        Assume: Surfaces have been locked and clipping was performed."
        | done gammaLookupTableOop ungammaLookupTableOop |
        self inline: true.
        combinationRule = 41
                ifTrue:["fetch the forecolor into componentAlphaModeColor."
                        componentAlphaModeAlpha := 255.
                        componentAlphaModeColor := 16777215.
                        gammaLookupTable := nil.
                        ungammaLookupTable := nil.
                        interpreterProxy methodArgumentCount >= 2
                                ifTrue:[
                                        componentAlphaModeAlpha := interpreterProxy stackIntegerValue:
(interpreterProxy methodArgumentCount - 2).
                                        (interpreterProxy failed not)
                                                ifFalse: [^ interpreterProxy primitiveFail].
                                        componentAlphaModeColor := interpreterProxy stackIntegerValue:
(interpreterProxy methodArgumentCount - 1).
                                        (interpreterProxy failed not)
                                                ifFalse: [^ interpreterProxy primitiveFail].
                                        interpreterProxy methodArgumentCount = 4
                                                ifTrue:[
                                                        gammaLookupTableOop := interpreterProxy stackObjectValue: 1.
                                                        (interpreterProxy isBytes: gammaLookupTableOop)
                                                                ifTrue:[gammaLookupTable := interpreterProxy
firstIndexableField: gammaLookupTableOop.].
                                                        ungammaLookupTableOop := interpreterProxy stackObjectValue: 0.
                                                        (interpreterProxy isBytes: ungammaLookupTableOop)
                                                                ifTrue:[ungammaLookupTable := interpreterProxy
firstIndexableField: ungammaLookupTableOop]]]
                                ifFalse:[
                                        interpreterProxy methodArgumentCount = 1
                                                ifTrue: [
                                                        componentAlphaModeColor := interpreterProxy stackIntegerValue: 0.
                                                        (interpreterProxy failed not)
                                                                ifFalse: [^ interpreterProxy primitiveFail]]
                                                ifFalse:[^ interpreterProxy primitiveFail]]].
        "Try a shortcut for stuff that should be run as quickly as possible"
  done := self tryCopyingBitsQuickly.
        done ifTrue:[^nil].

        (combinationRule = 30) | (combinationRule = 31) ifTrue:
                ["Check and fetch source alpha parameter for alpha blend"
                interpreterProxy methodArgumentCount = 1
                        ifTrue: [sourceAlpha := interpreterProxy stackIntegerValue: 0.
                                        (interpreterProxy failed not and: [(sourceAlpha >= 0) &
(sourceAlpha <= 255)])
                                                ifFalse: [^ interpreterProxy primitiveFail]]
                        ifFalse: [^ interpreterProxy primitiveFail]].

        bitCount := 0.
        "Choose and perform the actual copy loop."
        self performCopyLoop.

        (combinationRule = 22) | (combinationRule = 32) ifTrue:
                ["zero width and height; return the count"
                affectedL := affectedR := affectedT := affectedB := 0].
        hDir > 0
                ifTrue: [affectedL := dx.
                                affectedR := dx + bbW]
                ifFalse: [affectedL := dx - bbW + 1.
                                affectedR := dx + 1].
        vDir > 0
                ifTrue: [affectedT := dy.
                                affectedB := dy + bbH]
                ifFalse: [affectedT := dy - bbH + 1.
                                affectedB := dy + 1]

-----------
blitting works, but color argument are totally ignored (yellow color
used instead, always!), while alpha - not.

It seems that either this stuff broken, or my VM sources are too outdated.

2009/6/20 Andreas Raab <[hidden email]>:

>
> Igor Stasenko wrote:
>>
>> 2009/6/20 Andreas Raab <[hidden email]>:
>>>
>>> Easy. Make a color map that is set up such that
>>>
>>> cmap := Bitmap new: 256.
>>> 0 to: 255 do:[:i|
>>>  cmap at: i+1 put: (constColor alpha: i/255.0) pixelValue32.
>>> ].
>>
>> That is possible, but the price is generating a color map each time
>> the color changes :(
>> Much less price than converting/using 32 bpp, but still is not perfect :)
>
> It's utterly trivial to cache it. If you're using this for font display
> you'll only have a few colors to deal with so the cache won't be big.
>
>> Any advice, how to force rule 41 work correctly? Or it is impossible? :)
>>
>> Btw, i don't sure that my VM (windoze) having latest & fixed rule 41.
>> I remember there were problems with it.
>
> I'm not sure what rule 41 does. The Windows VM contains whatever is in
> VMMaker.
>
> Cheers,
>  - Andreas
>



--
Best regards,
Igor Stasenko AKA sig.
Reply | Threaded
Open this post in threaded view
|

Re: BitBlt looking for rule blitting an alpha mask + constant color

Juan Vuletich-4
In reply to this post by Andreas.Raab
 
Hi Folks,

Andreas Raab wrote:

>
> Igor Stasenko wrote:
>> 2009/6/20 Andreas Raab <[hidden email]>:
>>> Easy. Make a color map that is set up such that
>>>
>>> cmap := Bitmap new: 256.
>>> 0 to: 255 do:[:i|
>>>  cmap at: i+1 put: (constColor alpha: i/255.0) pixelValue32.
>>> ].
>>
>> That is possible, but the price is generating a color map each time
>> the color changes :(
>> Much less price than converting/using 32 bpp, but still is not
>> perfect :)
>
> It's utterly trivial to cache it. If you're using this for font
> display you'll only have a few colors to deal with so the cache won't
> be big.

You can see how to do all this in Cuis. It is what I do for font
rendering. Take a look at GrafPort >> installStrikeFont:foregroundColor:
. This works ok with source forms of any depth. For 8 bpp (and lower),
it is considered to hold opacity (i.e. 1-alpha). It is trivial to adjust
the colormaps for alpha instead. Take a look at the execution path for
"(Preferences subPixelRenderFonts and: [ foregroundColor = Color black
or: [ Preferences subPixelRenderColorFonts ]]) ifTrue: [". I use two
passes of bitblt. The first one is rgbMul, the second is rgbAdd.
Together they do the proper AA as you specified it. This only works for
destForm of 16 or 32 bpp. On 8bpp or less destination, I just use paint
rule.

If you want to test it with a soureForm that includes only opecity, evaluate
    StrikeFont allInstances do: [ :f | f
        setGlyphsDepthAtMost: 4 ].

You'll see that it works ok for any font color / background color
combination.

Cheers,
Juan Vuletich
Reply | Threaded
Open this post in threaded view
|

Re: BitBlt looking for rule blitting an alpha mask + constant color

Igor Stasenko
 


2009/6/20 Juan Vuletich <[hidden email]>

Hi Folks,


Andreas Raab wrote:

Igor Stasenko wrote:
2009/6/20 Andreas Raab <[hidden email]>:
Easy. Make a color map that is set up such that

cmap := Bitmap new: 256.
0 to: 255 do:[:i|
 cmap at: i+1 put: (constColor alpha: i/255.0) pixelValue32.
].

That is possible, but the price is generating a color map each time
the color changes :(
Much less price than converting/using 32 bpp, but still is not perfect :)

It's utterly trivial to cache it. If you're using this for font display you'll only have a few colors to deal with so the cache won't be big.

You can see how to do all this in Cuis. It is what I do for font rendering. Take a look at GrafPort >> installStrikeFont:foregroundColor: . This works ok with source forms of any depth. For 8 bpp (and lower), it is considered to hold opacity (i.e. 1-alpha). It is trivial to adjust the colormaps for alpha instead. Take a look at the execution path for "(Preferences subPixelRenderFonts and: [ foregroundColor = Color black or: [ Preferences subPixelRenderColorFonts ]]) ifTrue: [". I use two passes of bitblt. The first one is rgbMul, the second is rgbAdd. Together they do the proper AA as you specified it. This only works for destForm of 16 or 32 bpp. On 8bpp or less destination, I just use paint rule.

If you want to test it with a soureForm that includes only opecity, evaluate
  StrikeFont allInstances do: [ :f | f
      setGlyphsDepthAtMost: 4 ].

You'll see that it works ok for any font color / background color combination.

Thanks for reply, Juan.
Yes, i did the color mapping and using rule 24 to blit the 8-bit opacity maps.
But i'm still unhappy with that: there is no reason for doing that , if rule 41 would work as expected :(
 

Cheers,
Juan Vuletich



--
Best regards,
Igor Stasenko AKA sig.
Reply | Threaded
Open this post in threaded view
|

Re: BitBlt looking for rule blitting an alpha mask + constant color

Juan Vuletich-4
 
Igor Stasenko wrote:

>
> 2009/6/20 Juan Vuletich <[hidden email] <mailto:[hidden email]>>
>
>
>     Hi Folks,
>
>
>     Andreas Raab wrote:
>
>         ...
>         It's utterly trivial to cache it. If you're using this for
>         font display you'll only have a few colors to deal with so the
>         cache won't be big.
>
>
>     You can see how to do all this in Cuis. It is what I do for font
>     rendering. Take a look at GrafPort >>
>     installStrikeFont:foregroundColor: . This works ok with source
>     forms of any depth. For 8 bpp (and lower), it is considered to
>     hold opacity (i.e. 1-alpha). It is trivial to adjust the colormaps
>     for alpha instead. Take a look at the execution path for
>     "(Preferences subPixelRenderFonts and: [ foregroundColor = Color
>     black or: [ Preferences subPixelRenderColorFonts ]]) ifTrue: [". I
>     use two passes of bitblt. The first one is rgbMul, the second is
>     rgbAdd. Together they do the proper AA as you specified it. This
>     only works for destForm of 16 or 32 bpp. On 8bpp or less
>     destination, I just use paint rule.
>
>     If you want to test it with a soureForm that includes only
>     opecity, evaluate
>       StrikeFont allInstances do: [ :f | f
>           setGlyphsDepthAtMost: 4 ].
>
>     You'll see that it works ok for any font color / background color
>     combination.
>
>
> Thanks for reply, Juan.
> Yes, i did the color mapping and using rule 24 to blit the 8-bit
> opacity maps.

You're right. The 'extra' stuff in Cuis is for subpixel AA. Many people
feels it makes stuff look nicer, and FreeType does it nicely. It would
be great if you implemented it as an option.

> But i'm still unhappy with that: there is no reason for doing that ,
> if rule 41 would work as expected :(

Rule 41 needs a bmp with alpha (not opacity). That makes it impossible
to use the same form for any bitdepth, with or without subpixel or whole
pixel AA.
My "two pass" approach is way more flexible. Play a bit with text
rendering in Cuis. Experiment with fonts of different bit depths, on
various Display depths, with the #subPixelRenderFonts and
#subPixelRenderColorFonts preferences, and with various fonts /
background colors. I believe I finally got it right, and that my
approach deserves being used for rendering FreeType fonts too. I believe
the flexibility outweighs the performance penalty of the second pass
(that is not needed for black text, btw).

Cheers,
Juan Vuletich
Reply | Threaded
Open this post in threaded view
|

Re: BitBlt looking for rule blitting an alpha mask + constant color

Igor Stasenko

2009/6/21 Juan Vuletich <[hidden email]>:

>
> Igor Stasenko wrote:
>>
>> 2009/6/20 Juan Vuletich <[hidden email] <mailto:[hidden email]>>
>>
>>
>>    Hi Folks,
>>
>>
>>    Andreas Raab wrote:
>>
>>        ...
>>        It's utterly trivial to cache it. If you're using this for
>>        font display you'll only have a few colors to deal with so the
>>        cache won't be big.
>>
>>
>>    You can see how to do all this in Cuis. It is what I do for font
>>    rendering. Take a look at GrafPort >>
>>    installStrikeFont:foregroundColor: . This works ok with source
>>    forms of any depth. For 8 bpp (and lower), it is considered to
>>    hold opacity (i.e. 1-alpha). It is trivial to adjust the colormaps
>>    for alpha instead. Take a look at the execution path for
>>    "(Preferences subPixelRenderFonts and: [ foregroundColor = Color
>>    black or: [ Preferences subPixelRenderColorFonts ]]) ifTrue: [". I
>>    use two passes of bitblt. The first one is rgbMul, the second is
>>    rgbAdd. Together they do the proper AA as you specified it. This
>>    only works for destForm of 16 or 32 bpp. On 8bpp or less
>>    destination, I just use paint rule.
>>
>>    If you want to test it with a soureForm that includes only
>>    opecity, evaluate
>>      StrikeFont allInstances do: [ :f | f
>>          setGlyphsDepthAtMost: 4 ].
>>
>>    You'll see that it works ok for any font color / background color
>>    combination.
>>
>>
>> Thanks for reply, Juan.
>> Yes, i did the color mapping and using rule 24 to blit the 8-bit opacity
>> maps.
>
> You're right. The 'extra' stuff in Cuis is for subpixel AA. Many people
> feels it makes stuff look nicer, and FreeType does it nicely. It would be
> great if you implemented it as an option.
>
>> But i'm still unhappy with that: there is no reason for doing that , if
>> rule 41 would work as expected :(
>
> Rule 41 needs a bmp with alpha (not opacity). That makes it impossible to
> use the same form for any bitdepth, with or without subpixel or whole pixel
> AA.
> My "two pass" approach is way more flexible. Play a bit with text rendering
> in Cuis. Experiment with fonts of different bit depths, on various Display
> depths, with the #subPixelRenderFonts and #subPixelRenderColorFonts
> preferences, and with various fonts / background colors. I believe I finally
> got it right, and that my approach deserves being used for rendering
> FreeType fonts too. I believe the flexibility outweighs the performance
> penalty of the second pass (that is not needed for black text, btw).
>

I will turn my eyes to subpixel(s) and other fancy stuff, after i will
have a basic case working.
For me its important to have a most common case to work fast. For
other cases (if nowaday users want to use a monochrome displays, or
8bit displays - well, such users require an urgent medication, instead
of software  :)

> Cheers,
> Juan Vuletich
>



--
Best regards,
Igor Stasenko AKA sig.