#if __GLASGOW_HASKELL__ >= 709
{-# LANGUAGE Safe #-}
#else
{-# LANGUAGE Trustworthy #-}
#endif
module Graphics.Win32.GDI.Path
( beginPath, closeFigure, endPath, fillPath, flattenPath
, pathToRegion, strokeAndFillPath, strokePath, widenPath
) where
import Graphics.Win32.GDI.Types
import System.Win32.Types
#include "windows_cconv.h"
beginPath :: HDC -> IO ()
beginPath :: HDC -> IO ()
beginPath HDC
dc =
String -> IO Bool -> IO ()
failIfFalse_ String
"BeginPath" (IO Bool -> IO ()) -> IO Bool -> IO ()
forall a b. (a -> b) -> a -> b
$ HDC -> IO Bool
c_BeginPath HDC
dc
foreign import WINDOWS_CCONV unsafe "windows.h BeginPath"
c_BeginPath :: HDC -> IO Bool
closeFigure :: HDC -> IO ()
closeFigure :: HDC -> IO ()
closeFigure HDC
dc =
String -> IO Bool -> IO ()
failIfFalse_ String
"CloseFigure" (IO Bool -> IO ()) -> IO Bool -> IO ()
forall a b. (a -> b) -> a -> b
$ HDC -> IO Bool
c_CloseFigure HDC
dc
foreign import WINDOWS_CCONV unsafe "windows.h CloseFigure"
c_CloseFigure :: HDC -> IO Bool
endPath :: HDC -> IO ()
endPath :: HDC -> IO ()
endPath HDC
dc =
String -> IO Bool -> IO ()
failIfFalse_ String
"EndPath" (IO Bool -> IO ()) -> IO Bool -> IO ()
forall a b. (a -> b) -> a -> b
$ HDC -> IO Bool
c_EndPath HDC
dc
foreign import WINDOWS_CCONV unsafe "windows.h EndPath"
c_EndPath :: HDC -> IO Bool
fillPath :: HDC -> IO ()
fillPath :: HDC -> IO ()
fillPath HDC
dc =
String -> IO Bool -> IO ()
failIfFalse_ String
"FillPath" (IO Bool -> IO ()) -> IO Bool -> IO ()
forall a b. (a -> b) -> a -> b
$ HDC -> IO Bool
c_FillPath HDC
dc
foreign import WINDOWS_CCONV unsafe "windows.h FillPath"
c_FillPath :: HDC -> IO Bool
flattenPath :: HDC -> IO ()
flattenPath :: HDC -> IO ()
flattenPath HDC
dc =
String -> IO Bool -> IO ()
failIfFalse_ String
"FlattenPath" (IO Bool -> IO ()) -> IO Bool -> IO ()
forall a b. (a -> b) -> a -> b
$ HDC -> IO Bool
c_FlattenPath HDC
dc
foreign import WINDOWS_CCONV unsafe "windows.h FlattenPath"
c_FlattenPath :: HDC -> IO Bool
pathToRegion :: HDC -> IO HRGN
pathToRegion :: HDC -> IO HRGN
pathToRegion HDC
dc = do
ptr <- String -> IO HDC -> IO HDC
forall a. String -> IO (Ptr a) -> IO (Ptr a)
failIfNull String
"PathToRegion" (IO HDC -> IO HDC) -> IO HDC -> IO HDC
forall a b. (a -> b) -> a -> b
$ HDC -> IO HDC
c_PathToRegion HDC
dc
newForeignHANDLE ptr
foreign import WINDOWS_CCONV unsafe "windows.h PathToRegion"
c_PathToRegion :: HDC -> IO PRGN
strokeAndFillPath :: HDC -> IO ()
strokeAndFillPath :: HDC -> IO ()
strokeAndFillPath HDC
dc =
String -> IO Bool -> IO ()
failIfFalse_ String
"StrokeAndFillPath" (IO Bool -> IO ()) -> IO Bool -> IO ()
forall a b. (a -> b) -> a -> b
$ HDC -> IO Bool
c_StrokeAndFillPath HDC
dc
foreign import WINDOWS_CCONV unsafe "windows.h StrokeAndFillPath"
c_StrokeAndFillPath :: HDC -> IO Bool
strokePath :: HDC -> IO ()
strokePath :: HDC -> IO ()
strokePath HDC
dc =
String -> IO Bool -> IO ()
failIfFalse_ String
"StrokePath" (IO Bool -> IO ()) -> IO Bool -> IO ()
forall a b. (a -> b) -> a -> b
$ HDC -> IO Bool
c_StrokePath HDC
dc
foreign import WINDOWS_CCONV unsafe "windows.h StrokePath"
c_StrokePath :: HDC -> IO Bool
widenPath :: HDC -> IO ()
widenPath :: HDC -> IO ()
widenPath HDC
dc =
String -> IO Bool -> IO ()
failIfFalse_ String
"WidenPath" (IO Bool -> IO ()) -> IO Bool -> IO ()
forall a b. (a -> b) -> a -> b
$ HDC -> IO Bool
c_WidenPath HDC
dc
foreign import WINDOWS_CCONV unsafe "windows.h WidenPath"
c_WidenPath :: HDC -> IO Bool