pituicat/src/Affection/Draw.hs

72 lines
2.3 KiB
Haskell

{-# LANGUAGE RecordWildCards #-}
-- | Module for drawing primitives
module Affection.Draw
( drawRect
) where
import Affection.Types (DrawType(..), Affection, GeglRectangle(..), liftIO)
import Foreign.C.Types
import qualified BABL as B
import qualified GEGL as G
-- | Draw a rectangle on target buffer
drawRect
:: G.GeglBuffer -- ^ Target buffer
-> G.Color -- ^ Color to draw in
-> DrawType -- ^ Draw type
-> GeglRectangle -- ^ Dimensions of Rectangle
-> Affection a ()
drawRect buf color dt rect@G.GeglRectangle{..} =
liftIO $ G.iterateOver buf rect (B.PixelFormat B.RGBA B.CFdouble) G.GeglAccessReadWrite G.GeglAbyssNone $
(\(G.Pixel px py pc) ->
case dt of
Fill ->
let col = colorize pc color
in
G.Pixel px py col
Line width ->
if (px >= rectangleX && px <= (rectangleX + width) ||
px <= (rectangleX + rectangleWidth) && px >= (rectangleX + rectangleWidth - width)) &&
(py >= rectangleY && py <= (rectangleY + width) ||
py <= (rectangleY + rectangleHeight) && py >= (rectangleY + rectangleHeight - width))
then
let col = colorize pc color
in G.Pixel px py col
else
G.Pixel px py pc
)
-- | compute color for a single pixel
colorize
:: (G.ComponentValue, G.ComponentValue, G.ComponentValue, G.ComponentValue) -- ^ Pixel information in buffer
-> G.Color -- ^ Color to draw over
-> (G.ComponentValue, G.ComponentValue, G.ComponentValue, G.ComponentValue) -- ^ Resulting colour
colorize (rr, rg, rb, ra) col =
let (G.CVdouble (CDouble br)) = rr
(G.CVdouble (CDouble bg)) = rg
(G.CVdouble (CDouble bb)) = rb
(G.CVdouble (CDouble ba)) = ra
(cr, cg, cb) = case col of
G.RGBA r g b _ -> (r, g, b)
G.RGB r g b -> (r, g, b)
ca = case col of
G.RGBA _ _ _ a -> a
G.RGB _ _ _ -> 1
alpha = ca
dst_a = ba
da = alpha + dst_a * (1 - alpha)
a_term = dst_a * (1 - alpha)
red = cr * alpha + br * a_term
gre = cg * alpha + bg * a_term
blu = cb * alpha + bb * a_term
in
( G.CVdouble $ CDouble $ red / da
, G.CVdouble $ CDouble $ gre / da
, G.CVdouble $ CDouble $ blu / da
, G.CVdouble $ CDouble $ ca
)