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 | Haskell2010 |
A collection of FFI declarations for interfacing with Win32.
Synopsis
- type LPTSTR = Ptr TCHAR
- type DDWORD = Word64
- type UCHAR = CUChar
- type WORD = Word16
- type LPCWSTR = LPWSTR
- type LPCSTR = LPSTR
- type LPSTR = Ptr CChar
- type LPDWORD = Ptr DWORD
- type LPVOID = Ptr ()
- type LPCTSTR = LPTSTR
- type LPWSTR = Ptr CWchar
- type HANDLE = Ptr ()
- type ErrCode = DWORD
- type ULONG = Word32
- type UINT = Word32
- type DWORD = Word32
- type BYTE = Word8
- type LPBOOL = Ptr BOOL
- type BOOL = Bool
- type Addr = Ptr ()
- type SHORT = Int16
- type INT = Int32
- type ATOM = WORD
- type LONG = Int32
- type LRESULT = LONG_PTR
- type WPARAM = UINT_PTR
- type HINSTANCE = Ptr ()
- type LONG_PTR = CIntPtr
- type LPARAM = LONG_PTR
- type LCID = DWORD
- type LANGID = WORD
- type SortID = WORD
- type SubLANGID = WORD
- type PrimaryLANGID = WORD
- type ULONG_PTR = CUIntPtr
- type SIZE_T = ULONG_PTR
- type HKEY = ForeignHANDLE
- type PKEY = HANDLE
- type LPBYTE = Ptr BYTE
- type TCHAR = CWchar
- type HMODULE = Ptr ()
- type LPCTSTR_ = LPCTSTR
- type LARGE_INTEGER = Int64
- type DWORD32 = Word32
- type DWORD64 = Word64
- type DWORD_PTR = ULONG_PTR
- type USHORT = Word16
- type FLOAT = Float
- type INT32 = Int32
- type INT64 = Int64
- type LONG32 = Int32
- type LONG64 = Int64
- type UINT32 = Word32
- type UINT64 = Word64
- type ULONG32 = Word32
- type ULONG64 = Word64
- type INT_PTR = Ptr CInt
- type UINT_PTR = Word
- type HALF_PTR = Ptr INT32
- type MbString = Maybe String
- type MbINT = Maybe INT
- type MbATOM = Maybe ATOM
- type HRESULT = LONG
- type PUCHAR = Ptr UCHAR
- type MbLPVOID = Maybe LPVOID
- type MbLPCSTR = Maybe LPCSTR
- type MbLPCTSTR = Maybe LPCTSTR
- type ForeignHANDLE = ForeignPtr ()
- type MbHANDLE = Maybe HANDLE
- type MbHINSTANCE = Maybe HINSTANCE
- type MbHMODULE = Maybe HMODULE
- try :: String -> (LPTSTR -> UINT -> IO UINT) -> UINT -> IO String
- getLastError :: IO ErrCode
- c_maperrno_func :: ErrCode -> IO Errno
- nullHANDLE :: HANDLE
- iNVALID_HANDLE_VALUE :: HANDLE
- failWith :: String -> ErrCode -> IO a
- getErrorMessage :: DWORD -> IO LPWSTR
- 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
- ddwordToDwords :: DDWORD -> (DWORD, DWORD)
- dwordsToDdword :: (DWORD, DWORD) -> DDWORD
- setLastError :: ErrCode -> IO ()
- c_get_osfhandle :: CInt -> IO HANDLE
- maybePtr :: Maybe (Ptr a) -> Ptr a
- newTString :: String -> IO LPCTSTR
- withTString :: String -> (LPTSTR -> IO a) -> IO a
- ptrToMaybe :: Ptr a -> Maybe (Ptr a)
- peekTString :: LPCTSTR -> IO String
- numToMaybe :: (Eq a, Num a) => a -> Maybe a
- maybeNum :: Num a => Maybe a -> a
- errorWin :: String -> IO a
- castUINTPtrToPtr :: UINT_PTR -> Ptr a
- mAKELCID :: LANGID -> SortID -> LCID
- lANGIDFROMLCID :: LCID -> LANGID
- sORTIDFROMLCID :: LCID -> SortID
- mAKELANGID :: PrimaryLANGID -> SubLANGID -> LANGID
- pRIMARYLANGID :: LANGID -> PrimaryLANGID
- sUBLANGID :: LANGID -> SubLANGID
- peekTStringLen :: (LPCTSTR, Int) -> IO String
- newForeignHANDLE :: HANDLE -> IO ForeignHANDLE
- withTStringLen :: String -> ((LPTSTR, Int) -> IO a) -> IO a
- eRROR_INSUFFICIENT_BUFFER :: ErrCode
- deleteObjectFinaliser :: FunPtr (Ptr a -> IO ())
- handleToWord :: HANDLE -> UINT_PTR
- castPtrToUINTPtr :: Ptr s -> UINT_PTR
- nullHINSTANCE :: HINSTANCE
- nullFinalHANDLE :: ForeignPtr a
- _open_osfhandle :: CIntPtr -> CInt -> IO CInt
- hANDLEToHandle :: HANDLE -> IO Handle
- withHandleToHANDLE :: Handle -> (HANDLE -> IO a) -> IO a
- withHandleToHANDLEPosix :: Handle -> (HANDLE -> IO a) -> IO a
- withHandleToHANDLENative :: Handle -> (HANDLE -> IO a) -> IO a
- withStablePtr :: a -> (StablePtr a -> IO b) -> IO b
- failIfNeg :: (Num a, Ord a) => String -> IO a -> IO a
- eRROR_MOD_NOT_FOUND :: ErrCode
- eRROR_PROC_NOT_FOUND :: ErrCode
- localFree :: Ptr a -> IO (Ptr a)
- lOWORD :: DWORD -> WORD
- hIWORD :: DWORD -> WORD
- nullPtr :: Ptr a
Documentation
type PrimaryLANGID = WORD Source #
type HKEY = ForeignHANDLE Source #
type LARGE_INTEGER = Int64 Source #
type ForeignHANDLE = ForeignPtr () Source #
type MbHINSTANCE = Maybe HINSTANCE Source #
getLastError :: IO ErrCode Source #
nullHANDLE :: HANDLE Source #
setLastError :: ErrCode -> IO () Source #
castUINTPtrToPtr :: UINT_PTR -> Ptr a Source #
lANGIDFROMLCID :: LCID -> LANGID Source #
sORTIDFROMLCID :: LCID -> SortID Source #
mAKELANGID :: PrimaryLANGID -> SubLANGID -> LANGID Source #
pRIMARYLANGID :: LANGID -> PrimaryLANGID Source #
newForeignHANDLE :: HANDLE -> IO ForeignHANDLE Source #
handleToWord :: HANDLE -> UINT_PTR Source #
castPtrToUINTPtr :: Ptr s -> UINT_PTR Source #
nullFinalHANDLE :: ForeignPtr a Source #
hANDLEToHandle :: HANDLE -> IO Handle Source #
Create a Haskell Handle
from a Windows HANDLE
.
Beware that this function allocates a new file descriptor. A consequence of
this is that calling hANDLEToHandle
on the standard Windows handles will
not give you stdin
, stdout
, or stderr
. For example, if you
run this code:
import Graphics.Win32.Misc
stdoutHANDLE <- getStdHandle sTD_OUTPUT_HANDLE
stdout2 <- hANDLEToHandle
stdoutHANDLE
Then although you can use stdout2
to write to standard output, it is not
the case that
.stdout
== stdout2