Win32-2.14.1.0: A binding to Windows Win32 API.
Copyright(c) Alastair Reid 1997-2003
LicenseBSD-style (see the file libraries/base/LICENSE)
MaintainerEsa Ilari Vuokko <ei@vuokko.info>
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Graphics.Win32.Window

Description

A collection of FFI declarations for interfacing with Win32.

Synopsis

Documentation

type ClassName = LPCTSTR Source #

mkClassName :: String -> ClassName Source #

type ClassStyle = UINT Source #

cS_VREDRAW :: ClassStyle Source #

cS_HREDRAW :: ClassStyle Source #

cS_OWNDC :: ClassStyle Source #

cS_CLASSDC :: ClassStyle Source #

cS_PARENTDC :: ClassStyle Source #

cS_SAVEBITS :: ClassStyle Source #

cS_DBLCLKS :: ClassStyle Source #

cS_BYTEALIGNCLIENT :: ClassStyle Source #

cS_BYTEALIGNWINDOW :: ClassStyle Source #

cS_NOCLOSE :: ClassStyle Source #

cS_GLOBALCLASS :: ClassStyle Source #

type WNDCLASS = (ClassStyle, HINSTANCE, Maybe HICON, Maybe HCURSOR, Maybe HBRUSH, Maybe LPCTSTR, ClassName) Source #

withWNDCLASS :: WNDCLASS -> (Ptr WNDCLASS -> IO a) -> IO a Source #

genericWndProc_p :: FunPtr WindowClosure Source #

registerClass :: WNDCLASS -> IO (Maybe ATOM) Source #

c_RegisterClass :: Ptr WNDCLASS -> IO ATOM Source #

unregisterClass :: ClassName -> HINSTANCE -> IO () Source #

type WindowStyle = DWORD Source #

wS_OVERLAPPED :: WindowStyle Source #

wS_POPUP :: WindowStyle Source #

wS_CHILD :: WindowStyle Source #

wS_CLIPSIBLINGS :: WindowStyle Source #

wS_CLIPCHILDREN :: WindowStyle Source #

wS_VISIBLE :: WindowStyle Source #

wS_DISABLED :: WindowStyle Source #

wS_MINIMIZE :: WindowStyle Source #

wS_MAXIMIZE :: WindowStyle Source #

wS_CAPTION :: WindowStyle Source #

wS_BORDER :: WindowStyle Source #

wS_DLGFRAME :: WindowStyle Source #

wS_VSCROLL :: WindowStyle Source #

wS_HSCROLL :: WindowStyle Source #

wS_SYSMENU :: WindowStyle Source #

type WindowStyleEx = DWORD Source #

wS_THICKFRAME :: WindowStyle Source #

wS_MINIMIZEBOX :: WindowStyle Source #

wS_EX_DLGMODALFRAME :: WindowStyleEx Source #

wS_MAXIMIZEBOX :: WindowStyle Source #

wS_EX_NOPARENTNOTIFY :: WindowStyleEx Source #

wS_GROUP :: WindowStyle Source #

wS_EX_TOPMOST :: WindowStyleEx Source #

wS_TABSTOP :: WindowStyle Source #

wS_EX_ACCEPTFILES :: WindowStyleEx Source #

wS_OVERLAPPEDWINDOW :: WindowStyle Source #

wS_EX_TRANSPARENT :: WindowStyleEx Source #

wS_POPUPWINDOW :: WindowStyle Source #

wS_EX_MDICHILD :: WindowStyleEx Source #

wS_CHILDWINDOW :: WindowStyle Source #

wS_EX_TOOLWINDOW :: WindowStyleEx Source #

wS_TILED :: WindowStyle Source #

wS_EX_WINDOWEDGE :: WindowStyleEx Source #

wS_ICONIC :: WindowStyle Source #

wS_EX_CLIENTEDGE :: WindowStyleEx Source #

wS_SIZEBOX :: WindowStyle Source #

wS_EX_CONTEXTHELP :: WindowStyleEx Source #

wS_TILEDWINDOW :: WindowStyle Source #

wS_EX_RIGHT :: WindowStyleEx Source #

wS_EX_LEFT :: WindowStyleEx Source #

wS_EX_RTLREADING :: WindowStyleEx Source #

cW_USEDEFAULT :: Pos Source #

wS_EX_LTRREADING :: WindowStyleEx Source #

wS_EX_LEFTSCROLLBAR :: WindowStyleEx Source #

wS_EX_RIGHTSCROLLBAR :: WindowStyleEx Source #

type Pos = Int Source #

wS_EX_CONTROLPARENT :: WindowStyleEx Source #

type MbPos = Maybe Pos Source #

wS_EX_STATICEDGE :: WindowStyleEx Source #

maybePos :: Maybe Pos -> Pos Source #

wS_EX_APPWINDOW :: WindowStyleEx Source #

wS_EX_OVERLAPPEDWINDOW :: WindowStyleEx Source #

type WindowClosure = HWND -> WindowMessage -> WPARAM -> LPARAM -> IO LRESULT Source #

wS_EX_PALETTEWINDOW :: WindowStyleEx Source #

mkWindowClosure :: WindowClosure -> IO (FunPtr WindowClosure) Source #

mkCIntPtr :: FunPtr a -> CIntPtr Source #

setWindowClosure :: HWND -> WindowClosure -> IO (Maybe (FunPtr WindowClosure)) Source #

The standard C wndproc for every window class registered by registerClass is a C function pointer provided with this library. It in turn delegates to a Haskell function pointer stored in gWLP_USERDATA. This action creates that function pointer. All Haskell function pointers must be freed in order to allow the objects they close over to be garbage collected. Consequently, if you are replacing a window closure previously set via this method or indirectly with createWindow or createWindowEx you must free it. This action returns a function pointer to the old window closure for you to free. The current window closure is freed automatically by defWindowProc when it receives wM_NCDESTROY .

c_SetWindowLongPtr :: HWND -> INT -> LONG_PTR -> IO LONG_PTR Source #

c_GetWindowLongPtr :: HANDLE -> INT -> IO LONG_PTR Source #

createWindow :: ClassName -> String -> WindowStyle -> Maybe Pos -> Maybe Pos -> Maybe Pos -> Maybe Pos -> Maybe HWND -> Maybe HMENU -> HINSTANCE -> WindowClosure -> IO HWND Source #

Creates a window with a default extended window style. If you create many windows over the life of your program, WindowClosure may leak memory. Be sure to delegate to defWindowProc for wM_NCDESTROY and see defWindowProc and setWindowClosure for details.

createWindowEx :: WindowStyle -> ClassName -> String -> WindowStyle -> Maybe Pos -> Maybe Pos -> Maybe Pos -> Maybe Pos -> Maybe HWND -> Maybe HMENU -> HINSTANCE -> WindowClosure -> IO HWND Source #

Creates a window and allows your to specify the extended window style. If you create many windows over the life of your program, WindowClosure may leak memory. Be sure to delegate to defWindowProc for wM_NCDESTROY and see defWindowProc and setWindowClosure for details.

c_CreateWindowEx :: WindowStyle -> ClassName -> LPCTSTR -> WindowStyle -> Pos -> Pos -> Pos -> Pos -> HWND -> HMENU -> HINSTANCE -> LPVOID -> IO HWND Source #

defWindowProc :: Maybe HWND -> WindowMessage -> WPARAM -> LPARAM -> IO LRESULT Source #

Delegates to the Win32 default window procedure. If you are using a window created by createWindow , createWindowEx or on which you have called setWindowClosure , please note that the window will leak memory once it is destroyed unless you call freeWindowProc when it receives wM_NCDESTROY . If you wish to do this, instead of using this function directly, you can delegate to defWindowProcSafe which will handle it for you. As an alternative, you can manually retrieve the window closure function pointer and free it after the window has been destroyed. Check the implementation of freeWindowProc for a guide.

defWindowProcSafe :: Maybe HWND -> WindowMessage -> WPARAM -> LPARAM -> IO LRESULT Source #

Delegates to the standard default window procedure, but if it receives the wM_NCDESTROY message it first frees the window closure to allow the closure and any objects it closes over to be garbage collected. wM_NCDESTROY is the last message a window receives prior to being deleted.

c_DefWindowProc :: HWND -> WindowMessage -> WPARAM -> LPARAM -> IO LRESULT Source #

freeWindowProc :: HWND -> IO () Source #

Frees a function pointer to the window closure which has been set directly by setWindowClosure or indirectly by createWindowEx . You should call this function in your window closure's wM_NCDESTROY case unless you delegate that case to defWindowProc (e.g. as part of the default).

getClientRect :: HWND -> IO RECT Source #

c_GetClientRect :: HWND -> Ptr RECT -> IO Bool Source #

getWindowRect :: HWND -> IO RECT Source #

c_GetWindowRect :: HWND -> Ptr RECT -> IO Bool Source #

invalidateRect :: Maybe HWND -> Maybe LPRECT -> Bool -> IO () Source #

c_InvalidateRect :: HWND -> LPRECT -> Bool -> IO Bool Source #

screenToClient :: HWND -> POINT -> IO POINT Source #

c_ScreenToClient :: HWND -> Ptr POINT -> IO Bool Source #

clientToScreen :: HWND -> POINT -> IO POINT Source #

c_ClientToScreen :: HWND -> Ptr POINT -> IO Bool Source #

setWindowText :: HWND -> String -> IO () Source #

c_SetWindowText :: HWND -> LPCTSTR -> IO Bool Source #

getWindowText :: HWND -> Int -> IO String Source #

c_GetWindowText :: HWND -> LPTSTR -> Int -> IO Int Source #

getWindowTextLength :: HWND -> IO Int Source #

c_GetWindowTextLength :: HWND -> IO Int Source #

type PAINTSTRUCT = (HDC, Bool, RECT) Source #

type LPPAINTSTRUCT = Addr Source #

sizeofPAINTSTRUCT :: DWORD Source #

allocaPAINTSTRUCT :: (LPPAINTSTRUCT -> IO a) -> IO a Source #

beginPaint :: HWND -> LPPAINTSTRUCT -> IO HDC Source #

c_BeginPaint :: HWND -> LPPAINTSTRUCT -> IO HDC Source #

endPaint :: HWND -> LPPAINTSTRUCT -> IO () Source #

type ShowWindowControl = DWORD Source #

sW_HIDE :: ShowWindowControl Source #

sW_SHOWNORMAL :: ShowWindowControl Source #

sW_SHOWMINIMIZED :: ShowWindowControl Source #

sW_SHOWMAXIMIZED :: ShowWindowControl Source #

sW_MAXIMIZE :: ShowWindowControl Source #

sW_SHOWNOACTIVATE :: ShowWindowControl Source #

sW_SHOW :: ShowWindowControl Source #

sW_MINIMIZE :: ShowWindowControl Source #

showWindow :: HWND -> ShowWindowControl -> IO Bool Source #

sW_SHOWMINNOACTIVE :: ShowWindowControl Source #

isWindowVisible :: HWND -> IO Bool Source #

sW_SHOWNA :: ShowWindowControl Source #

sW_RESTORE :: ShowWindowControl Source #

adjustWindowRect :: RECT -> WindowStyle -> Bool -> IO RECT Source #

c_AdjustWindowRect :: Ptr RECT -> WindowStyle -> Bool -> IO Bool Source #

adjustWindowRectEx :: RECT -> WindowStyle -> Bool -> WindowStyleEx -> IO RECT Source #

c_AdjustWindowRectEx :: Ptr RECT -> WindowStyle -> Bool -> WindowStyleEx -> IO Bool Source #

anyPopup :: IO Bool Source #

arrangeIconicWindows :: HWND -> IO () Source #

c_ArrangeIconicWindows :: HWND -> IO Bool Source #

beginDeferWindowPos :: Int -> IO HDWP Source #

c_BeginDeferWindowPos :: Int -> IO HDWP Source #

bringWindowToTop :: HWND -> IO () Source #

c_BringWindowToTop :: HWND -> IO Bool Source #

childWindowFromPoint :: HWND -> POINT -> IO (Maybe HWND) Source #

childWindowFromPointEx :: HWND -> POINT -> DWORD -> IO (Maybe HWND) Source #

closeWindow :: HWND -> IO () Source #

deferWindowPos :: HDWP -> HWND -> HWND -> Int -> Int -> Int -> Int -> SetWindowPosFlags -> IO HDWP Source #

c_DeferWindowPos :: HDWP -> HWND -> HWND -> Int -> Int -> Int -> Int -> SetWindowPosFlags -> IO HDWP Source #

destroyWindow :: HWND -> IO () Source #

c_DestroyWindow :: HWND -> IO Bool Source #

endDeferWindowPos :: HDWP -> IO () Source #

c_EndDeferWindowPos :: HDWP -> IO Bool Source #

findWindow :: Maybe String -> Maybe String -> IO (Maybe HWND) Source #

findWindowByName :: String -> IO (Maybe HWND) Source #

Deprecated: Use 'findWindow Nothing' instead.

c_FindWindow :: LPCTSTR -> LPCTSTR -> IO HWND Source #

findWindowEx :: Maybe HWND -> Maybe HWND -> Maybe String -> Maybe String -> IO (Maybe HWND) Source #

c_FindWindowEx :: HWND -> HWND -> LPCTSTR -> LPCTSTR -> IO HWND Source #

flashWindow :: HWND -> Bool -> IO Bool Source #

moveWindow :: HWND -> Int -> Int -> Int -> Int -> Bool -> IO () Source #

c_MoveWindow :: HWND -> Int -> Int -> Int -> Int -> Bool -> IO Bool Source #

getDesktopWindow :: IO HWND Source #

getForegroundWindow :: IO HWND Source #

getParent :: HWND -> IO HWND Source #

c_GetParent :: HWND -> IO HWND Source #

getTopWindow :: HWND -> IO HWND Source #

c_GetTopWindow :: HWND -> IO HWND Source #

type SetWindowPosFlags = UINT Source #

sWP_NOSIZE :: SetWindowPosFlags Source #

sWP_NOMOVE :: SetWindowPosFlags Source #

sWP_NOZORDER :: SetWindowPosFlags Source #

sWP_NOREDRAW :: SetWindowPosFlags Source #

sWP_NOACTIVATE :: SetWindowPosFlags Source #

sWP_FRAMECHANGED :: SetWindowPosFlags Source #

sWP_SHOWWINDOW :: SetWindowPosFlags Source #

sWP_HIDEWINDOW :: SetWindowPosFlags Source #

sWP_NOCOPYBITS :: SetWindowPosFlags Source #

sWP_NOOWNERZORDER :: SetWindowPosFlags Source #

type GetDCExFlags = DWORD Source #

sWP_NOSENDCHANGING :: SetWindowPosFlags Source #

dCX_WINDOW :: GetDCExFlags Source #

sWP_DRAWFRAME :: SetWindowPosFlags Source #

dCX_CACHE :: GetDCExFlags Source #

sWP_NOREPOSITION :: SetWindowPosFlags Source #

dCX_CLIPCHILDREN :: GetDCExFlags Source #

dCX_CLIPSIBLINGS :: GetDCExFlags Source #

dCX_PARENTCLIP :: GetDCExFlags Source #

dCX_EXCLUDERGN :: GetDCExFlags Source #

dCX_INTERSECTRGN :: GetDCExFlags Source #

getDCEx :: HWND -> HRGN -> GetDCExFlags -> IO HDC Source #

dCX_LOCKWINDOWUPDATE :: GetDCExFlags Source #

c_GetDCEx :: HWND -> PRGN -> GetDCExFlags -> IO HDC Source #

getDC :: Maybe HWND -> IO HDC Source #

c_GetDC :: HWND -> IO HDC Source #

getWindowDC :: Maybe HWND -> IO HDC Source #

c_GetWindowDC :: HWND -> IO HDC Source #

releaseDC :: Maybe HWND -> HDC -> IO () Source #

c_ReleaseDC :: HWND -> HDC -> IO Bool Source #

getDCOrgEx :: HDC -> IO POINT Source #

c_GetDCOrgEx :: HDC -> Ptr POINT -> IO Bool Source #

hideCaret :: HWND -> IO () Source #

c_HideCaret :: HWND -> IO Bool Source #

showCaret :: HWND -> IO () Source #

c_ShowCaret :: HWND -> IO Bool Source #

createCaret :: HWND -> HBITMAP -> Maybe INT -> Maybe INT -> IO () Source #

c_CreateCaret :: HWND -> HBITMAP -> INT -> INT -> IO Bool Source #

destroyCaret :: IO () Source #

c_DestroyCaret :: IO Bool Source #

getCaretPos :: IO POINT Source #

c_GetCaretPos :: Ptr POINT -> IO Bool Source #

setCaretPos :: POINT -> IO () Source #

c_SetCaretPos :: LONG -> LONG -> IO Bool Source #

type LPMSG = Addr Source #

allocaMessage :: (LPMSG -> IO a) -> IO a Source #

getMessage :: LPMSG -> Maybe HWND -> IO Bool Source #

c_GetMessage :: LPMSG -> HWND -> UINT -> UINT -> IO LONG Source #

peekMessage :: LPMSG -> Maybe HWND -> UINT -> UINT -> UINT -> IO () Source #

c_PeekMessage :: LPMSG -> HWND -> UINT -> UINT -> UINT -> IO LONG Source #

translateMessage :: LPMSG -> IO BOOL Source #

updateWindow :: HWND -> IO () Source #

c_UpdateWindow :: HWND -> IO Bool Source #

dispatchMessage :: LPMSG -> IO LONG Source #

sendMessage :: HWND -> WindowMessage -> WPARAM -> LPARAM -> IO LRESULT Source #

AltStyle によって変換されたページ (->オリジナル) /