Copyright | (c) Alastair Reid, 1997-2003 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | Esa Ilari Vuokko <ei@vuokko.info> |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell98 |
A collection of FFI declarations for interfacing with Win32.
Documentation
mkClassName :: String -> ClassName
type ClassStyle = UINT
type WNDCLASS = (ClassStyle, HINSTANCE, Maybe HICON, Maybe HCURSOR, Maybe HBRUSH, Maybe LPCTSTR, ClassName)
registerClass :: WNDCLASS -> IO (Maybe ATOM)
c_RegisterClass :: Ptr WNDCLASS -> IO ATOM
unregisterClass :: ClassName -> HINSTANCE -> IO ()
type WindowStyle = DWORD
type WindowStyleEx = DWORD
cW_USEDEFAULT :: Pos
type WindowClosure = HWND -> WindowMessage -> WPARAM -> LPARAM -> IO LRESULT
setWindowClosure :: HWND -> WindowClosure -> IO ()
createWindow :: ClassName -> String -> WindowStyle -> Maybe Pos -> Maybe Pos -> Maybe Pos -> Maybe Pos -> Maybe HWND -> Maybe HMENU -> HINSTANCE -> WindowClosure -> IO HWND
createWindowEx :: WindowStyle -> ClassName -> String -> WindowStyle -> Maybe Pos -> Maybe Pos -> Maybe Pos -> Maybe Pos -> Maybe HWND -> Maybe HMENU -> HINSTANCE -> WindowClosure -> IO HWND
c_CreateWindowEx :: WindowStyle -> ClassName -> LPCTSTR -> WindowStyle -> Pos -> Pos -> Pos -> Pos -> HWND -> HMENU -> HINSTANCE -> LPVOID -> IO HWND
defWindowProc :: Maybe HWND -> WindowMessage -> WPARAM -> LPARAM -> IO LRESULT
c_DefWindowProc :: HWND -> WindowMessage -> WPARAM -> LPARAM -> IO LRESULT
getClientRect :: HWND -> IO RECT
getWindowRect :: HWND -> IO RECT
screenToClient :: HWND -> POINT -> IO POINT
clientToScreen :: HWND -> POINT -> IO POINT
setWindowText :: HWND -> String -> IO ()
c_SetWindowText :: HWND -> LPCTSTR -> IO Bool
type PAINTSTRUCT = (HDC, Bool, RECT)
type LPPAINTSTRUCT = Addr
allocaPAINTSTRUCT :: (LPPAINTSTRUCT -> IO a) -> IO a
beginPaint :: HWND -> LPPAINTSTRUCT -> IO HDC
c_BeginPaint :: HWND -> LPPAINTSTRUCT -> IO HDC
endPaint :: HWND -> LPPAINTSTRUCT -> IO ()
type ShowWindowControl = DWORD
showWindow :: HWND -> ShowWindowControl -> IO Bool
adjustWindowRect :: RECT -> WindowStyle -> Bool -> IO RECT
c_AdjustWindowRect :: Ptr RECT -> WindowStyle -> Bool -> IO Bool
adjustWindowRectEx :: RECT -> WindowStyle -> Bool -> WindowStyleEx -> IO RECT
c_AdjustWindowRectEx :: Ptr RECT -> WindowStyle -> Bool -> WindowStyleEx -> IO Bool
arrangeIconicWindows :: HWND -> IO ()
c_ArrangeIconicWindows :: HWND -> IO Bool
beginDeferWindowPos :: Int -> IO HDWP
c_BeginDeferWindowPos :: Int -> IO HDWP
bringWindowToTop :: HWND -> IO ()
c_BringWindowToTop :: HWND -> IO Bool
closeWindow :: HWND -> IO ()
c_DeferWindowPos :: HDWP -> HWND -> HWND -> Int -> Int -> Int -> Int -> SetWindowPosFlags -> IO HDWP
destroyWindow :: HWND -> IO ()
c_DestroyWindow :: HWND -> IO Bool
endDeferWindowPos :: HDWP -> IO ()
c_EndDeferWindowPos :: HDWP -> IO Bool
c_FindWindow :: LPCTSTR -> LPCTSTR -> IO HWND
flashWindow :: HWND -> Bool -> IO Bool
c_GetParent :: HWND -> IO HWND
getTopWindow :: HWND -> IO HWND
c_GetTopWindow :: HWND -> IO HWND
type SetWindowPosFlags = UINT
type GetDCExFlags = DWORD
getWindowDC :: Maybe HWND -> IO HDC
c_GetWindowDC :: HWND -> IO HDC
c_ReleaseDC :: HWND -> HDC -> IO Bool
getDCOrgEx :: HDC -> IO POINT
c_HideCaret :: HWND -> IO Bool
c_ShowCaret :: HWND -> IO Bool
destroyCaret :: IO ()
c_DestroyCaret :: IO Bool
getCaretPos :: IO POINT
c_GetCaretPos :: Ptr POINT -> IO Bool
setCaretPos :: POINT -> IO ()
c_SetCaretPos :: LONG -> LONG -> IO Bool
allocaMessage :: (LPMSG -> IO a) -> IO a
translateMessage :: LPMSG -> IO BOOL
updateWindow :: HWND -> IO ()
c_UpdateWindow :: HWND -> IO Bool
dispatchMessage :: LPMSG -> IO LONG
sendMessage :: HWND -> WindowMessage -> WPARAM -> LPARAM -> IO LRESULT