{-# LINE 1 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
{-# LANGUAGE Trustworthy #-}
module Graphics.Win32.GDI.Types
where
import System.Win32.Types
import Control.Monad( zipWithM_ )
import Foreign
{-# CFILES cbits/HsGDI.c #-}
type POINT =
( LONG
, LONG
)
sizeofPOINT :: Int
sizeofPOINT :: Int
sizeofPOINT = (Int
8)
{-# LINE 75 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
allocaPOINT :: (Ptr POINT -> IO a) -> IO a
allocaPOINT :: forall a. (Ptr POINT -> IO a) -> IO a
allocaPOINT =
Int -> (Ptr POINT -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
sizeofPOINT
peekPOINT :: Ptr POINT -> IO POINT
peekPOINT :: Ptr POINT -> IO POINT
peekPOINT Ptr POINT
p = do
x <- (\Ptr POINT
hsc_ptr -> Ptr POINT -> Int -> IO RegionType
forall b. Ptr b -> Int -> IO RegionType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr POINT
hsc_ptr Int
0) Ptr POINT
p
{-# LINE 83 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
y <- (\hsc_ptr -> peekByteOff hsc_ptr 4) p
{-# LINE 84 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
return (x,y)
pokePOINT :: Ptr POINT -> POINT -> IO ()
pokePOINT :: Ptr POINT -> POINT -> IO ()
pokePOINT Ptr POINT
p (RegionType
x,RegionType
y) = do
(\Ptr POINT
hsc_ptr -> Ptr POINT -> Int -> RegionType -> IO ()
forall b. Ptr b -> Int -> RegionType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr POINT
hsc_ptr Int
0) Ptr POINT
p RegionType
x
{-# LINE 89 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 4) p y
{-# LINE 90 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
withPOINT :: POINT -> (Ptr POINT -> IO a) -> IO a
withPOINT :: forall a. POINT -> (Ptr POINT -> IO a) -> IO a
withPOINT POINT
p Ptr POINT -> IO a
f =
(Ptr POINT -> IO a) -> IO a
forall a. (Ptr POINT -> IO a) -> IO a
allocaPOINT ((Ptr POINT -> IO a) -> IO a) -> (Ptr POINT -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \ Ptr POINT
ptr -> do
Ptr POINT -> POINT -> IO ()
pokePOINT Ptr POINT
ptr POINT
p
Ptr POINT -> IO a
f Ptr POINT
ptr
type RECT =
( LONG
, LONG
, LONG
, LONG
)
allocaRECT :: (Ptr RECT -> IO a) -> IO a
allocaRECT :: forall a. (Ptr RECT -> IO a) -> IO a
allocaRECT =
Int -> (Ptr RECT -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes ((Int
16))
{-# LINE 107 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
peekRECT :: Ptr RECT -> IO RECT
peekRECT :: Ptr RECT -> IO RECT
peekRECT Ptr RECT
p = do
left <- (\Ptr RECT
hsc_ptr -> Ptr RECT -> Int -> IO RegionType
forall b. Ptr b -> Int -> IO RegionType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr RECT
hsc_ptr Int
0) Ptr RECT
p
{-# LINE 111 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
top <- (\hsc_ptr -> peekByteOff hsc_ptr 4) p
{-# LINE 112 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
right <- (\hsc_ptr -> peekByteOff hsc_ptr 8) p
{-# LINE 113 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
bottom <- (\hsc_ptr -> peekByteOff hsc_ptr 12) p
{-# LINE 114 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
return (left, top, right, bottom)
pokeRECT :: Ptr RECT -> RECT -> IO ()
pokeRECT :: Ptr RECT -> RECT -> IO ()
pokeRECT Ptr RECT
p (RegionType
left, RegionType
top, RegionType
right, RegionType
bottom) = do
(\Ptr RECT
hsc_ptr -> Ptr RECT -> Int -> RegionType -> IO ()
forall b. Ptr b -> Int -> RegionType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr RECT
hsc_ptr Int
0) Ptr RECT
p RegionType
left
{-# LINE 119 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 4) p top
{-# LINE 120 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 8) p right
{-# LINE 121 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 12) p bottom
{-# LINE 122 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
type SIZE =
( LONG
, LONG
)
allocaSIZE :: (Ptr SIZE -> IO a) -> IO a
allocaSIZE :: forall a. (Ptr POINT -> IO a) -> IO a
allocaSIZE =
Int -> (Ptr POINT -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes ((Int
8))
{-# LINE 131 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
peekSIZE :: Ptr SIZE -> IO SIZE
peekSIZE :: Ptr POINT -> IO POINT
peekSIZE Ptr POINT
p = do
cx <- (\Ptr POINT
hsc_ptr -> Ptr POINT -> Int -> IO RegionType
forall b. Ptr b -> Int -> IO RegionType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr POINT
hsc_ptr Int
0) Ptr POINT
p
{-# LINE 135 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
cy <- (\hsc_ptr -> peekByteOff hsc_ptr 4) p
{-# LINE 136 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
return (cx,cy)
pokeSIZE :: Ptr SIZE -> SIZE -> IO ()
pokeSIZE :: Ptr POINT -> POINT -> IO ()
pokeSIZE Ptr POINT
p (RegionType
cx,RegionType
cy) = do
(\Ptr POINT
hsc_ptr -> Ptr POINT -> Int -> RegionType -> IO ()
forall b. Ptr b -> Int -> RegionType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr POINT
hsc_ptr Int
0) Ptr POINT
p RegionType
cx
{-# LINE 141 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 4) p cy
{-# LINE 142 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
withPOINTArray :: [POINT] -> (Ptr POINT -> Int -> IO a) -> IO a
withPOINTArray :: forall a. [POINT] -> (Ptr POINT -> Int -> IO a) -> IO a
withPOINTArray [POINT]
xs Ptr POINT -> Int -> IO a
f = Int -> (Ptr POINT -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (Int
sizeofPOINT Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
len) ((Ptr POINT -> IO a) -> IO a) -> (Ptr POINT -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \ Ptr POINT
ptr -> do
Ptr POINT -> [POINT] -> IO ()
pokePOINTArray Ptr POINT
ptr [POINT]
xs
Ptr POINT -> Int -> IO a
f Ptr POINT
ptr Int
len
where
len :: Int
len = [POINT] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [POINT]
xs
pokePOINTArray :: Ptr POINT -> [POINT] -> IO ()
pokePOINTArray :: Ptr POINT -> [POINT] -> IO ()
pokePOINTArray Ptr POINT
ptr [POINT]
xs = (Int -> POINT -> IO ()) -> [Int] -> [POINT] -> IO ()
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m ()
zipWithM_ (Ptr POINT -> Int -> POINT -> IO ()
setPOINT Ptr POINT
ptr) [Int
0..] [POINT]
xs
setPOINT :: Ptr POINT -> Int -> POINT -> IO ()
setPOINT :: Ptr POINT -> Int -> POINT -> IO ()
setPOINT Ptr POINT
ptr Int
off = Ptr POINT -> POINT -> IO ()
pokePOINT (Ptr POINT
ptr Ptr POINT -> Int -> Ptr POINT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
sizeofPOINT))
type LPRECT = Ptr RECT
type MbLPRECT = Maybe LPRECT
withRECT :: RECT -> (Ptr RECT -> IO a) -> IO a
withRECT :: forall a. RECT -> (Ptr RECT -> IO a) -> IO a
withRECT RECT
r Ptr RECT -> IO a
f =
(Ptr RECT -> IO a) -> IO a
forall a. (Ptr RECT -> IO a) -> IO a
allocaRECT ((Ptr RECT -> IO a) -> IO a) -> (Ptr RECT -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \ Ptr RECT
ptr -> do
Ptr RECT -> RECT -> IO ()
pokeRECT Ptr RECT
ptr RECT
r
Ptr RECT -> IO a
f Ptr RECT
ptr
getRECT :: LPRECT -> IO RECT
getRECT :: Ptr RECT -> IO RECT
getRECT = Ptr RECT -> IO RECT
peekRECT
type HBITMAP = HANDLE
type MbHBITMAP = Maybe HBITMAP
type HFONT = HANDLE
type MbHFONT = Maybe HFONT
type HCURSOR = HICON
type MbHCURSOR = Maybe HCURSOR
type HICON = HANDLE
type MbHICON = Maybe HICON
type HRGN = ForeignHANDLE
type PRGN = HANDLE
type MbHRGN = Maybe HRGN
type HPALETTE = HANDLE
type MbHPALETTE = Maybe HPALETTE
type HBRUSH = HANDLE
type MbHBRUSH = Maybe HBRUSH
type HPEN = HANDLE
type MbHPEN = Maybe HPEN
type HACCEL = HANDLE
type HDC = HANDLE
type MbHDC = Maybe HDC
type HDWP = HANDLE
type MbHDWP = Maybe HDWP
type HWND = HANDLE
type MbHWND = Maybe HWND
hWND_BOTTOM :: HWND
hWND_BOTTOM :: HWND
hWND_BOTTOM = UINT_PTR -> HWND
forall a. UINT_PTR -> Ptr a
castUINTPtrToPtr UINT_PTR
1
hWND_NOTOPMOST :: HWND
hWND_NOTOPMOST :: HWND
hWND_NOTOPMOST = UINT_PTR -> HWND
forall a. UINT_PTR -> Ptr a
castUINTPtrToPtr UINT_PTR
18446744073709551614
hWND_TOP :: HWND
hWND_TOP :: HWND
hWND_TOP = UINT_PTR -> HWND
forall a. UINT_PTR -> Ptr a
castUINTPtrToPtr UINT_PTR
0
hWND_TOPMOST :: HWND
hWND_TOPMOST :: HWND
hWND_TOPMOST = UINT_PTR -> HWND
forall a. UINT_PTR -> Ptr a
castUINTPtrToPtr UINT_PTR
18446744073709551615
{-# LINE 222 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
type HMENU = HANDLE
type MbHMENU = Maybe HMENU
type COLORREF = Word32
{-# LINE 231 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
foreign import ccall unsafe "HsGDI.h"
rgb :: BYTE -> BYTE -> BYTE -> COLORREF
foreign import ccall unsafe "HsGDI.h"
getRValue :: COLORREF -> BYTE
foreign import ccall unsafe "HsGDI.h"
getGValue :: COLORREF -> BYTE
foreign import ccall unsafe "HsGDI.h"
getBValue :: COLORREF -> BYTE
foreign import ccall unsafe "HsGDI.h"
pALETTERGB :: BYTE -> BYTE -> BYTE -> COLORREF
foreign import ccall unsafe "HsGDI.h"
pALETTEINDEX :: WORD -> COLORREF
type RasterOp3 = Word32
type RasterOp4 = Word32
foreign import ccall unsafe "HsGDI.h"
mAKEROP4 :: RasterOp3 -> RasterOp3 -> RasterOp4
type PolyFillMode = INT
aLTERNATE :: PolyFillMode
aLTERNATE :: RegionType
aLTERNATE = RegionType
1
wINDING :: PolyFillMode
wINDING :: RegionType
wINDING = RegionType
2
{-# LINE 269 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
type ArcDirection = INT
type MbArcDirection = Maybe ArcDirection
aD_COUNTERCLOCKWISE :: ArcDirection
aD_COUNTERCLOCKWISE :: RegionType
aD_COUNTERCLOCKWISE = RegionType
1
aD_CLOCKWISE :: ArcDirection
aD_CLOCKWISE :: RegionType
aD_CLOCKWISE = RegionType
2
{-# LINE 278 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
type GraphicsMode = DWORD
type MbGraphicsMode = Maybe GraphicsMode
gM_COMPATIBLE :: GraphicsMode
gM_COMPATIBLE :: UINT
gM_COMPATIBLE = UINT
1
gM_ADVANCED :: GraphicsMode
gM_ADVANCED :: UINT
gM_ADVANCED = UINT
2
{-# LINE 287 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
type BackgroundMode = INT
tRANSPARENT :: BackgroundMode
tRANSPARENT :: RegionType
tRANSPARENT = RegionType
1
oPAQUE :: BackgroundMode
oPAQUE :: RegionType
oPAQUE = RegionType
2
{-# LINE 295 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
type HatchStyle = INT
hS_HORIZONTAL :: HatchStyle
hS_HORIZONTAL :: RegionType
hS_HORIZONTAL = RegionType
0
hS_VERTICAL :: HatchStyle
hS_VERTICAL :: RegionType
hS_VERTICAL = RegionType
1
hS_FDIAGONAL :: HatchStyle
hS_FDIAGONAL :: RegionType
hS_FDIAGONAL = RegionType
2
hS_BDIAGONAL :: HatchStyle
hS_BDIAGONAL :: RegionType
hS_BDIAGONAL = RegionType
3
hS_CROSS :: HatchStyle
hS_CROSS :: RegionType
hS_CROSS = RegionType
4
hS_DIAGCROSS :: HatchStyle
hS_DIAGCROSS :: RegionType
hS_DIAGCROSS = RegionType
5
{-# LINE 307 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
type StretchBltMode = INT
bLACKONWHITE :: StretchBltMode
bLACKONWHITE = 1
wHITEONBLACK :: StretchBltMode
wHITEONBLACK :: RegionType
wHITEONBLACK = RegionType
2
cOLORONCOLOR :: StretchBltMode
cOLORONCOLOR :: RegionType
cOLORONCOLOR = RegionType
3
hALFTONE :: StretchBltMode
hALFTONE :: RegionType
hALFTONE = RegionType
4
sTRETCH_ANDSCANS :: StretchBltMode
sTRETCH_ANDSCANS :: RegionType
sTRETCH_ANDSCANS = RegionType
1
sTRETCH_ORSCANS :: StretchBltMode
sTRETCH_ORSCANS :: RegionType
sTRETCH_ORSCANS = RegionType
2
sTRETCH_DELETESCANS :: StretchBltMode
sTRETCH_DELETESCANS :: RegionType
sTRETCH_DELETESCANS = RegionType
3
{-# LINE 320 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
type TextAlignment = UINT
tA_NOUPDATECP :: TextAlignment
tA_NOUPDATECP = 0
tA_UPDATECP :: TextAlignment
tA_UPDATECP :: UINT
tA_UPDATECP = UINT
1
tA_LEFT :: TextAlignment
tA_LEFT :: UINT
tA_LEFT = UINT
0
tA_RIGHT :: TextAlignment
tA_RIGHT :: UINT
tA_RIGHT = UINT
2
tA_CENTER :: TextAlignment
tA_CENTER :: UINT
tA_CENTER = UINT
6
tA_TOP :: TextAlignment
tA_TOP :: UINT
tA_TOP = UINT
0
tA_BOTTOM :: TextAlignment
tA_BOTTOM :: UINT
tA_BOTTOM = UINT
8
tA_BASELINE :: TextAlignment
tA_BASELINE :: UINT
tA_BASELINE = 24
{-# LINE 334 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
type ClippingMode = INT
rGN_AND :: ClippingMode
rGN_AND = 1
rGN_OR :: ClippingMode
rGN_OR = 2
rGN_XOR :: ClippingMode
rGN_XOR :: RegionType
rGN_XOR = RegionType
3
rGN_DIFF :: ClippingMode
rGN_DIFF :: RegionType
rGN_DIFF = RegionType
4
rGN_COPY :: ClippingMode
rGN_COPY :: RegionType
rGN_COPY = RegionType
5
{-# LINE 345 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
type RegionType = INT
eRROR :: RegionType
eRROR :: RegionType
eRROR = RegionType
0
nULLREGION :: RegionType
nULLREGION :: RegionType
nULLREGION = RegionType
1
sIMPLEREGION :: RegionType
sIMPLEREGION :: RegionType
sIMPLEREGION = RegionType
2
cOMPLEXREGION :: RegionType
cOMPLEXREGION :: RegionType
cOMPLEXREGION = RegionType
3
{-# LINE 355 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
gDI_ERROR :: Num a => a
gDI_ERROR = 4294967295
{-# LINE 358 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
cLR_INVALID :: COLORREF
cLR_INVALID :: UINT
cLR_INVALID = UINT
4294967295
{-# LINE 361 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
oBJ_PEN :: UINT
oBJ_PEN :: UINT
oBJ_PEN = UINT
1
oBJ_BRUSH :: UINT
oBJ_BRUSH :: UINT
oBJ_BRUSH = UINT
2
oBJ_DC :: UINT
oBJ_DC :: UINT
oBJ_DC = UINT
3
oBJ_METADC :: UINT
oBJ_METADC :: UINT
oBJ_METADC = UINT
4
oBJ_PAL :: UINT
oBJ_PAL :: UINT
oBJ_PAL = UINT
5
oBJ_FONT :: UINT
oBJ_FONT :: UINT
oBJ_FONT = UINT
6
oBJ_BITMAP :: UINT
oBJ_BITMAP :: UINT
oBJ_BITMAP = UINT
7
oBJ_REGION :: UINT
oBJ_REGION :: UINT
oBJ_REGION = UINT
8
oBJ_METAFILE :: UINT
oBJ_METAFILE :: UINT
oBJ_METAFILE = UINT
9
oBJ_MEMDC :: UINT
oBJ_MEMDC :: UINT
oBJ_MEMDC = UINT
10
oBJ_EXTPEN :: UINT
oBJ_EXTPEN :: UINT
oBJ_EXTPEN = UINT
11
oBJ_ENHMETADC :: UINT
oBJ_ENHMETADC :: UINT
oBJ_ENHMETADC = UINT
12
oBJ_ENHMETAFILE :: UINT
oBJ_ENHMETAFILE :: UINT
oBJ_ENHMETAFILE = UINT
13
{-# LINE 379 "libraries\\Win32\\Graphics\\Win32\\GDI\\Types.hsc" #-}
foreign import ccall unsafe "HsGDI.h"
prim_ChildWindowFromPoint :: HWND -> Ptr POINT -> IO HWND
foreign import ccall unsafe "HsGDI.h"
prim_ChildWindowFromPointEx :: HWND -> Ptr POINT -> DWORD -> IO HWND
foreign import ccall unsafe "HsGDI.h"
prim_MenuItemFromPoint :: HWND -> HMENU -> Ptr POINT -> IO UINT