{-# LINE 1 "src/NanoVG/Internal.chs" #-}
module NanoVG.Internal
( FileName(..)
, Image(..)
, Context(..)
, Transformation(..)
, Extent(..)
, Color(..)
, Paint(..)
, Solidity(..)
, LineCap(..)
, Winding(..)
, beginFrame
, cancelFrame
, endFrame
, rgb
, rgbf
, rgba
, rgbaf
, lerpRGBA
, transRGBA
, transRGBAf
, hsl
, hsla
, save
, restore
, reset
, strokeColor
, strokePaint
, fillColor
, fillPaint
, miterLimit
, strokeWidth
, lineCap
, lineJoin
, globalAlpha
, resetTransform
, transform
, translate
, rotate
, skewX
, skewY
, scale
, currentTransform
, transformIdentity
, transformTranslate
, transformScale
, transformRotate
, transformSkewX
, transformSkewY
, transformMultiply
, transformPremultiply
, transformInverse
, transformPoint
, degToRad
, radToDeg
, createImage
, createImageMem
, createImageRGBA
, updateImage
, imageSize
, deleteImage
, linearGradient
, boxGradient
, radialGradient
, imagePattern
, scissor
, intersectScissor
, resetScissor
, beginPath
, moveTo
, lineTo
, bezierTo
, quadTo
, arcTo
, closePath
, pathWinding
, arc
, rect
, roundedRect
, ellipse
, circle
, fill
, stroke
, V2(..)
, V3(..)
, V4(..)
, M23
) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import Foreign.C.Types
import NanoVG.Internal.Color
import NanoVG.Internal.Context
import NanoVG.Internal.FixedVector
import NanoVG.Internal.Image
import NanoVG.Internal.Paint
import NanoVG.Internal.Path
import NanoVG.Internal.Scissor
import NanoVG.Internal.State
import NanoVG.Internal.Style
import NanoVG.Internal.Transformation
import NanoVG.Internal.Types
{-# LINE 113 "src/NanoVG/Internal.chs" #-}
data Solidity = Solid
| Hole
deriving (Show,Read,Eq,Ord)
instance Enum Solidity where
succ Solid = Hole
succ Hole = error "Solidity.succ: Hole has no successor"
pred Hole = Solid
pred Solid = error "Solidity.pred: Solid has no predecessor"
enumFromTo from to = go from
where
end = fromEnum to
go v = case compare (fromEnum v) end of
LT -> v : go (succ v)
EQ -> [v]
GT -> []
enumFrom from = enumFromTo from Hole
fromEnum Solid = 1
fromEnum Hole = 2
toEnum 1 = Solid
toEnum 2 = Hole
toEnum unmatched = error ("Solidity.toEnum: Cannot match " ++ show unmatched)
{-# LINE 119 "src/NanoVG/Internal.chs" #-}
beginFrame :: (Context) -> (CInt) -> (CInt) -> (Float) -> IO ()
beginFrame a1 a2 a3 a4 =
let {a1' = id a1} in
let {a2' = fromIntegral a2} in
let {a3' = fromIntegral a3} in
let {a4' = realToFrac a4} in
beginFrame'_ a1' a2' a3' a4' >>
return ()
{-# LINE 133 "src/NanoVG/Internal.chs" #-}
cancelFrame :: (Context) -> IO ()
cancelFrame a1 =
let {a1' = id a1} in
cancelFrame'_ a1' >>
return ()
{-# LINE 137 "src/NanoVG/Internal.chs" #-}
endFrame :: (Context) -> IO ()
endFrame a1 =
let {a1' = id a1} in
endFrame'_ a1' >>
return ()
{-# LINE 141 "src/NanoVG/Internal.chs" #-}
foreign import ccall unsafe "NanoVG/Internal.chs.h nvgBeginFrame"
beginFrame'_ :: ((Context) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CFloat -> (IO ())))))
foreign import ccall unsafe "NanoVG/Internal.chs.h nvgCancelFrame"
cancelFrame'_ :: ((Context) -> (IO ()))
foreign import ccall unsafe "NanoVG/Internal.chs.h nvgEndFrame"
endFrame'_ :: ((Context) -> (IO ()))