{-# 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
, roundedRectVarying
, ellipse
, circle
, fill
, stroke
, BlendFactor(..)
, CompositeOperation(..)
, globalCompositeOperation
, globalCompositeBlendFunc
, globalCompositeBlendFuncSeparate
, 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.GlobalComposite
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 121 "src/NanoVG/Internal.chs" #-}
data Solidity = Solid
| Hole
deriving (Show,Read,Eq,Ord)
instance Enum Solidity where
succ :: Solidity -> Solidity
succ Solidity
Solid = Solidity
Hole
succ Solidity
Hole = String -> Solidity
forall a. HasCallStack => String -> a
error String
"Solidity.succ: Hole has no successor"
pred :: Solidity -> Solidity
pred Solidity
Hole = Solidity
Solid
pred Solidity
Solid = String -> Solidity
forall a. HasCallStack => String -> a
error String
"Solidity.pred: Solid has no predecessor"
enumFromTo :: Solidity -> Solidity -> [Solidity]
enumFromTo Solidity
from Solidity
to = Solidity -> [Solidity]
forall t. Enum t => t -> [t]
go Solidity
from
where
end :: Int
end = Solidity -> Int
forall a. Enum a => a -> Int
fromEnum Solidity
to
go :: t -> [t]
go t
v = case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (t -> Int
forall a. Enum a => a -> Int
fromEnum t
v) Int
end of
Ordering
LT -> t
v t -> [t] -> [t]
forall a. a -> [a] -> [a]
: t -> [t]
go (t -> t
forall a. Enum a => a -> a
succ t
v)
EQ -> [v]
Ordering
GT -> []
enumFrom :: Solidity -> [Solidity]
enumFrom Solidity
from = Solidity -> Solidity -> [Solidity]
forall a. Enum a => a -> a -> [a]
enumFromTo Solidity
from Solidity
Hole
fromEnum Solid = 1
fromEnum Hole = 2
toEnum 1 = Solid
toEnum 2 = Hole
toEnum unmatched = error ("Solidity.toEnum: Cannot match " ++ show unmatched)
{-# LINE 127 "src/NanoVG/Internal.chs" #-}
beginFrame :: (Context) -> (Float) -> (Float) -> (Float) -> IO ()
beginFrame a1 a2 a3 a4 =
let {a1' = id a1} in
let {a2' = realToFrac a2} in
let {a3' = realToFrac a3} in
let {a4' = realToFrac a4} in
beginFrame'_ a1' a2' a3' a4' >>
return ()
endFrame :: Context -> IO ()
{-# LINE 141 "src/NanoVG/Internal.chs" #-}
cancelFrame :: (Context) -> IO ()
cancelFrame a1 =
let {a1' = id a1} in
cancelFrame'_ a1' >>
return ()
{-# LINE 145 "src/NanoVG/Internal.chs" #-}
endFrame :: (Context) -> IO ()
endFrame a1 =
let {a1' = id a1} in
endFrame'_ a1' >>
return ()
{-# LINE 149 "src/NanoVG/Internal.chs" #-}
foreign import ccall unsafe "NanoVG/Internal.chs.h nvgBeginFrame"
beginFrame'_ :: ((Context) -> (C2HSImp.CFloat -> (C2HSImp.CFloat -> (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 ()))