-- GENERATED by C->Haskell Compiler, version 0.28.1 Switcheroo, 1 April 2016 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/NanoVG/Internal/Paint.chs" #-}
{-# LANGUAGE RecordWildCards #-}
module NanoVG.Internal.Paint where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable as C2HSImp



import Control.Applicative (pure)
import Foreign.C.Types
import Foreign.Marshal.Alloc
import Foreign.Marshal.Utils
import Foreign.Ptr
import Foreign.Storable
import NanoVG.Internal.Color
import NanoVG.Internal.Context
import NanoVG.Internal.FixedVector
import NanoVG.Internal.Transformation
import NanoVG.Internal.Types





{-# LINE 19 "src/NanoVG/Internal/Paint.chs" #-}


{-# LINE 20 "src/NanoVG/Internal/Paint.chs" #-}

type PaintPtr = C2HSImp.Ptr (Paint)
{-# LINE 21 "src/NanoVG/Internal/Paint.chs" #-}


newtype Extent = Extent (V2 CFloat) deriving (Show,Read,Eq,Ord)

instance Storable Extent where
  sizeOf _ = sizeOf (0 :: CFloat) * 2
  alignment _ = alignment (0 :: CFloat)
  peek p =
    do let p' = castPtr p :: Ptr CFloat
       a <- peekElemOff p' 0
       b <- peekElemOff p' 1
       pure (Extent (V2 a b))
  poke p (Extent (V2 a b)) =
    do let p' = castPtr p :: Ptr CFloat
       pokeElemOff p' 0 a
       pokeElemOff p' 1 b

data Paint =
  Paint {xform :: Transformation
        ,extent :: Extent
        ,radius :: !CFloat
        ,feather :: !CFloat
        ,innerColor :: !Color
        ,outerColor :: !Color
        ,image :: !Image} deriving (Show,Read,Eq,Ord)

instance Storable Paint where
  sizeOf _ = 76
  alignment _ = 4
  peek p =
    do xform <- peek (castPtr (p `plusPtr` (0)))
       extent <- peek (castPtr (p `plusPtr` (24)))
       radius <- (\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO C2HSImp.CFloat}) p
       feather <- (\ptr -> do {C2HSImp.peekByteOff ptr 36 :: IO C2HSImp.CFloat}) p
       innerColor <- peek (castPtr (p `plusPtr` 40))
       outerColor <- peek (castPtr (p `plusPtr` 56))
       image <- peek (castPtr (p `plusPtr` 72))
       pure (Paint xform extent radius feather innerColor outerColor (Image image))
  poke p (Paint{..}) =
    do poke (castPtr (p `plusPtr` (0))) xform
       poke (castPtr (p `plusPtr` (24))) extent
       (\ptr val -> do {C2HSImp.pokeByteOff ptr 32 (val :: C2HSImp.CFloat)}) p radius
       (\ptr val -> do {C2HSImp.pokeByteOff ptr 36 (val :: C2HSImp.CFloat)}) p feather
       poke (castPtr (p `plusPtr` 40)) innerColor
       poke (castPtr (p `plusPtr` 56)) outerColor
       poke (castPtr (p `plusPtr` 72)) (imageHandle image)

-- | Creates and returns a linear gradient. Parameters (sx,sy)-(ex,ey) specify the start and end coordinates
-- of the linear gradient, icol specifies the start color and ocol the end color.
-- The gradient is transformed by the current transform when it is passed to 'fillPaint' or 'strokePaint'.
linearGradient :: (Context) -> (CFloat) -> (CFloat) -> (CFloat) -> (CFloat) -> (Color) -> (Color) -> IO ((Paint))
linearGradient a1 a2 a3 a4 a5 a6 a7 =
  let {a1' = id a1} in 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  let {a5' = realToFrac a5} in 
  with a6 $ \a6' -> 
  with a7 $ \a7' -> 
  alloca $ \a8' -> 
  linearGradient'_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  peek  a8'>>= \a8'' -> 
  return (a8'')

{-# LINE 72 "src/NanoVG/Internal/Paint.chs" #-}


-- | Creates and returns a box gradient. Box gradient is a feathered rounded rectangle, it is useful for rendering
-- drop shadows or highlights for boxes. Parameters (x,y) define the top-left corner of the rectangle,
-- (w,h) define the size of the rectangle, r defines the corner radius, and f feather. Feather defines how blurry
-- the border of the rectangle is. Parameter icol specifies the inner color and ocol the outer color of the gradient.
-- The gradient is transformed by the current transform when it is passed to 'fillPaint' or 'strokePaint'.
boxGradient :: (Context) -> (CFloat) -> (CFloat) -> (CFloat) -> (CFloat) -> (CFloat) -> (CFloat) -> (Color) -> (Color) -> IO ((Paint))
boxGradient a1 a2 a3 a4 a5 a6 a7 a8 a9 =
  let {a1' = id a1} in 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  let {a7' = realToFrac a7} in 
  with a8 $ \a8' -> 
  with a9 $ \a9' -> 
  alloca $ \a10' -> 
  boxGradient'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>
  peek  a10'>>= \a10'' -> 
  return (a10'')

{-# LINE 80 "src/NanoVG/Internal/Paint.chs" #-}


-- | Creates and returns a radial gradient. Parameters (cx,cy) specify the center, inr and outr specify
-- the inner and outer radius of the gradient, icol specifies the start color and ocol the end color.
-- The gradient is transformed by the current transform when it is passed to 'fillPaint' or 'strokePaint'.
radialGradient :: (Context) -> (CFloat) -> (CFloat) -> (CFloat) -> (CFloat) -> (Color) -> (Color) -> IO ((Paint))
radialGradient a1 a2 a3 a4 a5 a6 a7 =
  let {a1' = id a1} in 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  let {a5' = realToFrac a5} in 
  with a6 $ \a6' -> 
  with a7 $ \a7' -> 
  alloca $ \a8' -> 
  radialGradient'_ a1' a2' a3' a4' a5' a6' a7' a8' >>
  peek  a8'>>= \a8'' -> 
  return (a8'')

{-# LINE 86 "src/NanoVG/Internal/Paint.chs" #-}


-- | Creates and returns an image patter. Parameters (ox,oy) specify the left-top location of the image pattern,
-- (ex,ey) the size of one image, angle rotation around the top-left corner, image is handle to the image to render.
-- The gradient is transformed by the current transform when it is passed to 'fillPaint' or 'strokePaint'.
imagePattern :: (Context) -> (CFloat) -> (CFloat) -> (CFloat) -> (CFloat) -> (CFloat) -> (Image) -> (CFloat) -> IO ((Paint))
imagePattern a1 a2 a3 a4 a5 a6 a7 a8 =
  let {a1' = id a1} in 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  let {a7' = imageHandle a7} in 
  let {a8' = realToFrac a8} in 
  alloca $ \a9' -> 
  imagePattern'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>
  peek  a9'>>= \a9'' -> 
  return (a9'')

{-# LINE 92 "src/NanoVG/Internal/Paint.chs" #-}


foreign import ccall unsafe "NanoVG/Internal/Paint.chs.h nvgLinearGradient_"
  linearGradient'_ :: ((Context) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> ((ColorPtr) -> ((ColorPtr) -> ((PaintPtr) -> (IO ())))))))))

foreign import ccall unsafe "NanoVG/Internal/Paint.chs.h nvgBoxGradient_"
  boxGradient'_ :: ((Context) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> ((ColorPtr) -> ((ColorPtr) -> ((PaintPtr) -> (IO ())))))))))))

foreign import ccall unsafe "NanoVG/Internal/Paint.chs.h nvgRadialGradient_"
  radialGradient'_ :: ((Context) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> ((ColorPtr) -> ((ColorPtr) -> ((PaintPtr) -> (IO ())))))))))

foreign import ccall unsafe "NanoVG/Internal/Paint.chs.h nvgImagePattern_"
  imagePattern'_ :: ((Context) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (C2HSImp.CInt -> (C2HSImp.CFloat -> ((PaintPtr) -> (IO ()))))))))))