Portability | portable |
---|---|
Stability | provisional |
Maintainer | Esa Ilari Vuokko <ei@vuokko.info> |
Safe Haskell | Trustworthy |
A collection of FFI declarations for interfacing with Win32.
- 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 HRESULT = LONG
- 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 :: (Eq a, 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 :: (Eq a, 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
- c_maperrno :: IO ()
- 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
- nullPtr :: Ptr a
Documentation
type LARGE_INTEGER = Int64Source
ptrToMaybe :: Ptr a -> Maybe (Ptr a)Source
numToMaybe :: (Eq a, Num a) => a -> Maybe aSource
peekTString :: LPCTSTR -> IO StringSource
newTString :: String -> IO LPCTSTRSource
type ForeignHANDLE = ForeignPtr ()Source
handleToWord :: HANDLE -> UINTSource
type HKEY = ForeignHANDLESource
type MbHINSTANCE = Maybe HINSTANCESource
c_maperrno :: IO ()Source
ddwordToDwords :: DDWORD -> (DWORD, DWORD)Source
dwordsToDdword :: (DWORD, DWORD) -> DDWORDSource
deleteObjectFinaliser :: FunPtr (Ptr a -> IO ())Source
getErrorMessage :: DWORD -> IO LPWSTRSource
castUINTToPtr :: UINT -> Ptr aSource
castPtrToUINT :: Ptr s -> UINTSource
castFunPtrToLONG :: FunPtr a -> LONGSource
lANGIDFROMLCID :: LCID -> LANGIDSource
sORTIDFROMLCID :: LCID -> SortIDSource
type PrimaryLANGID = WORDSource
mAKELANGID :: PrimaryLANGID -> SubLANGID -> LANGIDSource