|
Graphics.Win32.Window | Portability | portable | Stability | provisional | Maintainer | Esa Ilari Vuokko <ei@vuokko.info> |
|
|
|
Description |
A collection of FFI declarations for interfacing with Win32.
|
|
|
Documentation |
|
type ClassName = LPCTSTR |
|
mkClassName :: String -> ClassName |
|
type ClassStyle = UINT |
|
cS_VREDRAW :: ClassStyle |
|
cS_HREDRAW :: ClassStyle |
|
cS_OWNDC :: ClassStyle |
|
cS_CLASSDC :: ClassStyle |
|
cS_PARENTDC :: ClassStyle |
|
cS_SAVEBITS :: ClassStyle |
|
cS_DBLCLKS :: ClassStyle |
|
cS_BYTEALIGNCLIENT :: ClassStyle |
|
cS_BYTEALIGNWINDOW :: ClassStyle |
|
cS_NOCLOSE :: ClassStyle |
|
cS_GLOBALCLASS :: ClassStyle |
|
type WNDCLASS = (ClassStyle, HINSTANCE, Maybe HICON, Maybe HCURSOR, Maybe HBRUSH, Maybe LPCTSTR, ClassName) |
|
withWNDCLASS :: WNDCLASS -> (Ptr WNDCLASS -> IO a) -> IO a |
|
genericWndProc_p :: FunPtr WindowClosure |
|
registerClass :: WNDCLASS -> IO (Maybe ATOM) |
|
c_RegisterClass :: Ptr WNDCLASS -> IO ATOM |
|
unregisterClass :: ClassName -> HINSTANCE -> IO () |
|
type WindowStyle = DWORD |
|
wS_OVERLAPPED :: WindowStyle |
|
wS_POPUP :: WindowStyle |
|
wS_CHILD :: WindowStyle |
|
wS_CLIPSIBLINGS :: WindowStyle |
|
wS_CLIPCHILDREN :: WindowStyle |
|
wS_VISIBLE :: WindowStyle |
|
wS_DISABLED :: WindowStyle |
|
wS_MINIMIZE :: WindowStyle |
|
wS_MAXIMIZE :: WindowStyle |
|
wS_CAPTION :: WindowStyle |
|
wS_BORDER :: WindowStyle |
|
wS_DLGFRAME :: WindowStyle |
|
wS_VSCROLL :: WindowStyle |
|
wS_HSCROLL :: WindowStyle |
|
wS_SYSMENU :: WindowStyle |
|
wS_THICKFRAME :: WindowStyle |
|
wS_MINIMIZEBOX :: WindowStyle |
|
wS_MAXIMIZEBOX :: WindowStyle |
|
wS_GROUP :: WindowStyle |
|
wS_TABSTOP :: WindowStyle |
|
wS_OVERLAPPEDWINDOW :: WindowStyle |
|
wS_POPUPWINDOW :: WindowStyle |
|
wS_CHILDWINDOW :: WindowStyle |
|
wS_TILED :: WindowStyle |
|
wS_ICONIC :: WindowStyle |
|
wS_SIZEBOX :: WindowStyle |
|
wS_TILEDWINDOW :: WindowStyle |
|
type WindowStyleEx = DWORD |
|
wS_EX_DLGMODALFRAME :: WindowStyleEx |
|
wS_EX_NOPARENTNOTIFY :: WindowStyleEx |
|
wS_EX_TOPMOST :: WindowStyleEx |
|
wS_EX_ACCEPTFILES :: WindowStyleEx |
|
wS_EX_TRANSPARENT :: WindowStyleEx |
|
wS_EX_MDICHILD :: WindowStyleEx |
|
wS_EX_TOOLWINDOW :: WindowStyleEx |
|
wS_EX_WINDOWEDGE :: WindowStyleEx |
|
wS_EX_CLIENTEDGE :: WindowStyleEx |
|
wS_EX_CONTEXTHELP :: WindowStyleEx |
|
wS_EX_RIGHT :: WindowStyleEx |
|
wS_EX_LEFT :: WindowStyleEx |
|
wS_EX_RTLREADING :: WindowStyleEx |
|
wS_EX_LTRREADING :: WindowStyleEx |
|
wS_EX_LEFTSCROLLBAR :: WindowStyleEx |
|
wS_EX_RIGHTSCROLLBAR :: WindowStyleEx |
|
wS_EX_CONTROLPARENT :: WindowStyleEx |
|
wS_EX_STATICEDGE :: WindowStyleEx |
|
wS_EX_APPWINDOW :: WindowStyleEx |
|
wS_EX_OVERLAPPEDWINDOW :: WindowStyleEx |
|
wS_EX_PALETTEWINDOW :: WindowStyleEx |
|
cW_USEDEFAULT :: Pos |
|
type Pos = Int |
|
type MbPos = Maybe Pos |
|
maybePos :: Maybe Pos -> Pos |
|
type WindowClosure = HWND -> WindowMessage -> WPARAM -> LPARAM -> IO LRESULT |
|
mkWindowClosure :: WindowClosure -> IO (FunPtr WindowClosure) |
|
setWindowClosure :: HWND -> WindowClosure -> IO () |
|
c_SetWindowLong :: HWND -> INT -> LONG -> IO LONG |
|
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 |
|
c_GetClientRect :: HWND -> Ptr RECT -> IO Bool |
|
getWindowRect :: HWND -> IO RECT |
|
c_GetWindowRect :: HWND -> Ptr RECT -> IO Bool |
|
invalidateRect :: Maybe HWND -> Maybe LPRECT -> Bool -> IO () |
|
c_InvalidateRect :: HWND -> LPRECT -> Bool -> IO Bool |
|
screenToClient :: HWND -> POINT -> IO POINT |
|
c_ScreenToClient :: HWND -> Ptr POINT -> IO Bool |
|
clientToScreen :: HWND -> POINT -> IO POINT |
|
c_ClientToScreen :: HWND -> Ptr POINT -> IO Bool |
|
setWindowText :: HWND -> String -> IO () |
|
c_SetWindowText :: HWND -> LPCTSTR -> IO Bool |
|
type PAINTSTRUCT = (HDC, Bool, RECT) |
|
type LPPAINTSTRUCT = Addr |
|
sizeofPAINTSTRUCT :: DWORD |
|
allocaPAINTSTRUCT :: (LPPAINTSTRUCT -> IO a) -> IO a |
|
beginPaint :: HWND -> LPPAINTSTRUCT -> IO HDC |
|
c_BeginPaint :: HWND -> LPPAINTSTRUCT -> IO HDC |
|
endPaint :: HWND -> LPPAINTSTRUCT -> IO () |
|
type ShowWindowControl = DWORD |
|
sW_HIDE :: ShowWindowControl |
|
sW_SHOWNORMAL :: ShowWindowControl |
|
sW_SHOWMINIMIZED :: ShowWindowControl |
|
sW_SHOWMAXIMIZED :: ShowWindowControl |
|
sW_MAXIMIZE :: ShowWindowControl |
|
sW_SHOWNOACTIVATE :: ShowWindowControl |
|
sW_SHOW :: ShowWindowControl |
|
sW_MINIMIZE :: ShowWindowControl |
|
sW_SHOWMINNOACTIVE :: ShowWindowControl |
|
sW_SHOWNA :: ShowWindowControl |
|
sW_RESTORE :: ShowWindowControl |
|
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 |
|
anyPopup :: 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 |
|
childWindowFromPoint :: HWND -> POINT -> IO (Maybe HWND) |
|
childWindowFromPointEx :: HWND -> POINT -> DWORD -> IO (Maybe HWND) |
|
closeWindow :: HWND -> IO () |
|
deferWindowPos :: HDWP -> HWND -> HWND -> Int -> Int -> Int -> Int -> SetWindowPosFlags -> IO HDWP |
|
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 |
|
findWindow :: String -> String -> IO (Maybe HWND) |
|
c_FindWindow :: LPCTSTR -> LPCTSTR -> IO HWND |
|
findWindowEx :: HWND -> HWND -> String -> String -> IO (Maybe HWND) |
|
c_FindWindowEx :: HWND -> HWND -> LPCTSTR -> LPCTSTR -> IO HWND |
|
flashWindow :: HWND -> Bool -> IO Bool |
|
moveWindow :: HWND -> Int -> Int -> Int -> Int -> Bool -> IO () |
|
c_MoveWindow :: HWND -> Int -> Int -> Int -> Int -> Bool -> IO Bool |
|
getDesktopWindow :: IO HWND |
|
getForegroundWindow :: IO HWND |
|
getParent :: HWND -> IO HWND |
|
c_GetParent :: HWND -> IO HWND |
|
getTopWindow :: HWND -> IO HWND |
|
c_GetTopWindow :: HWND -> IO HWND |
|
type SetWindowPosFlags = UINT |
|
sWP_NOSIZE :: SetWindowPosFlags |
|
sWP_NOMOVE :: SetWindowPosFlags |
|
sWP_NOZORDER :: SetWindowPosFlags |
|
sWP_NOREDRAW :: SetWindowPosFlags |
|
sWP_NOACTIVATE :: SetWindowPosFlags |
|
sWP_FRAMECHANGED :: SetWindowPosFlags |
|
sWP_SHOWWINDOW :: SetWindowPosFlags |
|
sWP_HIDEWINDOW :: SetWindowPosFlags |
|
sWP_NOCOPYBITS :: SetWindowPosFlags |
|
sWP_NOOWNERZORDER :: SetWindowPosFlags |
|
sWP_NOSENDCHANGING :: SetWindowPosFlags |
|
sWP_DRAWFRAME :: SetWindowPosFlags |
|
sWP_NOREPOSITION :: SetWindowPosFlags |
|
type GetDCExFlags = DWORD |
|
dCX_WINDOW :: GetDCExFlags |
|
dCX_CACHE :: GetDCExFlags |
|
dCX_CLIPCHILDREN :: GetDCExFlags |
|
dCX_CLIPSIBLINGS :: GetDCExFlags |
|
dCX_PARENTCLIP :: GetDCExFlags |
|
dCX_EXCLUDERGN :: GetDCExFlags |
|
dCX_INTERSECTRGN :: GetDCExFlags |
|
dCX_LOCKWINDOWUPDATE :: GetDCExFlags |
|
getDCEx :: HWND -> HRGN -> GetDCExFlags -> IO HDC |
|
c_GetDCEx :: HWND -> PRGN -> GetDCExFlags -> IO HDC |
|
getDC :: Maybe HWND -> IO HDC |
|
c_GetDC :: HWND -> IO HDC |
|
getWindowDC :: Maybe HWND -> IO HDC |
|
c_GetWindowDC :: HWND -> IO HDC |
|
releaseDC :: Maybe HWND -> HDC -> IO () |
|
c_ReleaseDC :: HWND -> HDC -> IO Bool |
|
getDCOrgEx :: HDC -> IO POINT |
|
c_GetDCOrgEx :: HDC -> Ptr POINT -> IO Bool |
|
hideCaret :: HWND -> IO () |
|
c_HideCaret :: HWND -> IO Bool |
|
showCaret :: HWND -> IO () |
|
c_ShowCaret :: HWND -> IO Bool |
|
createCaret :: HWND -> HBITMAP -> Maybe INT -> Maybe INT -> IO () |
|
c_CreateCaret :: HWND -> HBITMAP -> INT -> INT -> 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 |
|
type LPMSG = Addr |
|
allocaMessage :: (LPMSG -> IO a) -> IO a |
|
getMessage :: LPMSG -> Maybe HWND -> IO Bool |
|
c_GetMessage :: LPMSG -> HWND -> UINT -> UINT -> IO LONG |
|
peekMessage :: LPMSG -> Maybe HWND -> UINT -> UINT -> UINT -> IO () |
|
c_PeekMessage :: LPMSG -> HWND -> UINT -> UINT -> UINT -> IO LONG |
|
translateMessage :: LPMSG -> IO BOOL |
|
updateWindow :: HWND -> IO () |
|
c_UpdateWindow :: HWND -> IO Bool |
|
dispatchMessage :: LPMSG -> IO LONG |
|
sendMessage :: HWND -> WindowMessage -> WPARAM -> LPARAM -> IO LRESULT |
|
Produced by Haddock version 0.8 |