Win32-2.1.0.0: A binding to part of the Win32 libraryContentsIndex
System.Win32.Types
Portabilityportable
Stabilityprovisional
MaintainerEsa Ilari Vuokko <ei@vuokko.info>
Description
A collection of FFI declarations for interfacing with Win32.
Documentation
type BOOL = Bool
type BYTE = Word8
type UCHAR = CUChar
type USHORT = Word16
type UINT = Word32
type INT = Int32
type WORD = Word16
type DWORD = Word32
type LONG = Int32
type FLOAT = Float
type LARGE_INTEGER = Int64
type DDWORD = Word64
type MbString = Maybe String
type MbINT = Maybe INT
type ATOM = UINT
type WPARAM = UINT
type LPARAM = LONG
type LRESULT = LONG
type SIZE_T = DWORD
type MbATOM = Maybe ATOM
type Addr = Ptr ()
type LPVOID = Ptr ()
type LPBOOL = Ptr BOOL
type LPBYTE = Ptr BYTE
type PUCHAR = Ptr UCHAR
type LPDWORD = Ptr DWORD
type LPSTR = Ptr CChar
type LPCSTR = LPSTR
type LPWSTR = Ptr CWchar
type LPCWSTR = LPWSTR
type LPTSTR = Ptr TCHAR
type LPCTSTR = LPTSTR
type LPCTSTR_ = LPCTSTR
maybePtr :: Maybe (Ptr a) -> Ptr a
ptrToMaybe :: Ptr a -> Maybe (Ptr a)
maybeNum :: Num a => Maybe a -> a
numToMaybe :: Num a => a -> Maybe a
type MbLPVOID = Maybe LPVOID
type MbLPCSTR = Maybe LPCSTR
type MbLPCTSTR = Maybe LPCTSTR
withTString :: String -> (LPTSTR -> IO a) -> IO a
withTStringLen :: String -> ((LPTSTR, Int) -> IO a) -> IO a
peekTString :: LPCTSTR -> IO String
peekTStringLen :: (LPCTSTR, Int) -> IO String
newTString :: String -> IO LPCTSTR
type TCHAR = CWchar
type HANDLE = Ptr ()
type ForeignHANDLE = ForeignPtr ()
newForeignHANDLE :: HANDLE -> IO ForeignHANDLE
handleToWord :: HANDLE -> UINT
type HKEY = ForeignHANDLE
type PKEY = HANDLE
nullHANDLE :: HANDLE
type MbHANDLE = Maybe HANDLE
type HINSTANCE = Ptr ()
type MbHINSTANCE = Maybe HINSTANCE
type HMODULE = Ptr ()
type MbHMODULE = Maybe HMODULE
nullFinalHANDLE :: ForeignPtr a
iNVALID_HANDLE_VALUE :: HANDLE
type ErrCode = DWORD
failIf :: (a -> Bool) -> String -> IO a -> IO a
failIf_ :: (a -> Bool) -> String -> IO a -> IO ()
failIfNull :: String -> IO (Ptr a) -> IO (Ptr a)
failIfZero :: Num a => String -> IO a -> IO a
failIfFalse_ :: String -> IO Bool -> IO ()
failUnlessSuccess :: String -> IO ErrCode -> IO ()
failUnlessSuccessOr :: ErrCode -> String -> IO ErrCode -> IO Bool
errorWin :: String -> IO a
failWith :: String -> ErrCode -> IO a
ddwordToDwords :: DDWORD -> (DWORD, DWORD)
dwordsToDdword :: (DWORD, DWORD) -> DDWORD
deleteObjectFinaliser :: FunPtr (Ptr a -> IO ())
localFree :: Ptr a -> IO (Ptr a)
getLastError :: IO ErrCode
getErrorMessage :: DWORD -> IO LPWSTR
lOWORD :: DWORD -> WORD
hIWORD :: DWORD -> WORD
castUINTToPtr :: UINT -> Ptr a
castPtrToUINT :: Ptr s -> UINT
castFunPtrToLONG :: FunPtr a -> LONG
type LCID = DWORD
type LANGID = WORD
type SortID = WORD
mAKELCID :: LANGID -> SortID -> LCID
lANGIDFROMLCID :: LCID -> LANGID
sORTIDFROMLCID :: LCID -> SortID
type SubLANGID = WORD
type PrimaryLANGID = WORD
mAKELANGID :: PrimaryLANGID -> SubLANGID -> LANGID
pRIMARYLANGID :: LANGID -> PrimaryLANGID
sUBLANGID :: LANGID -> SubLANGID
Produced by Haddock version 0.8