#if __GLASGOW_HASKELL__ >= 701
#endif
module System.Win32.Types
( module System.Win32.Types
, nullPtr
) where
import Control.Exception (throwIO)
import Data.Bits (shiftL, shiftR, (.|.), (.&.))
import Data.Char (isSpace)
import Data.Int (Int32, Int64)
import Data.Maybe (fromMaybe)
import Data.Word (Word, Word8, Word16, Word32, Word64)
import Foreign.C.Error (getErrno, errnoToIOError)
import Foreign.C.String (newCWString, withCWStringLen)
import Foreign.C.String (peekCWString, peekCWStringLen, withCWString)
import Foreign.C.Types (CChar, CUChar, CWchar)
import Foreign.ForeignPtr (ForeignPtr, newForeignPtr, newForeignPtr_)
import Foreign.Ptr (FunPtr, Ptr, nullPtr)
import Numeric (showHex)
import System.IO.Error (ioeSetErrorString)
import System.IO.Unsafe (unsafePerformIO)
#if MIN_VERSION_base(4,7,0)
import Data.Bits (finiteBitSize)
#else
import Data.Bits (Bits, bitSize)
finiteBitSize :: (Bits a) => a -> Int
finiteBitSize = bitSize
#endif
#include "windows_cconv.h"
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 UINT_PTR = Word
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
maybePtr = fromMaybe nullPtr
ptrToMaybe :: Ptr a -> Maybe (Ptr a)
ptrToMaybe p = if p == nullPtr then Nothing else Just p
maybeNum :: Num a => Maybe a -> a
maybeNum = fromMaybe 0
numToMaybe :: (Eq a, Num a) => a -> Maybe a
numToMaybe n = if n == 0 then Nothing else Just n
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
withTString = withCWString
withTStringLen = withCWStringLen
peekTString = peekCWString
peekTStringLen = peekCWStringLen
newTString = newCWString
type HANDLE = Ptr ()
type ForeignHANDLE = ForeignPtr ()
newForeignHANDLE :: HANDLE -> IO ForeignHANDLE
newForeignHANDLE = newForeignPtr deleteObjectFinaliser
handleToWord :: HANDLE -> UINT_PTR
handleToWord = castPtrToUINTPtr
type HKEY = ForeignHANDLE
type PKEY = HANDLE
nullHANDLE :: HANDLE
nullHANDLE = nullPtr
type MbHANDLE = Maybe HANDLE
type HINSTANCE = Ptr ()
type MbHINSTANCE = Maybe HINSTANCE
type HMODULE = Ptr ()
type MbHMODULE = Maybe HMODULE
nullFinalHANDLE :: ForeignPtr a
nullFinalHANDLE = unsafePerformIO (newForeignPtr_ nullPtr)
iNVALID_HANDLE_VALUE :: HANDLE
iNVALID_HANDLE_VALUE = castUINTPtrToPtr (1)
type ErrCode = DWORD
failIf :: (a -> Bool) -> String -> IO a -> IO a
failIf p wh act = do
v <- act
if p v then errorWin wh else return v
failIf_ :: (a -> Bool) -> String -> IO a -> IO ()
failIf_ p wh act = do
v <- act
if p v then errorWin wh else return ()
failIfNull :: String -> IO (Ptr a) -> IO (Ptr a)
failIfNull = failIf (== nullPtr)
failIfZero :: (Eq a, Num a) => String -> IO a -> IO a
failIfZero = failIf (== 0)
failIfFalse_ :: String -> IO Bool -> IO ()
failIfFalse_ = failIf_ not
failUnlessSuccess :: String -> IO ErrCode -> IO ()
failUnlessSuccess fn_name act = do
r <- act
if r == 0 then return () else failWith fn_name r
failUnlessSuccessOr :: ErrCode -> String -> IO ErrCode -> IO Bool
failUnlessSuccessOr val fn_name act = do
r <- act
if r == 0 then return False
else if r == val then return True
else failWith fn_name r
errorWin :: String -> IO a
errorWin fn_name = do
err_code <- getLastError
failWith fn_name err_code
failWith :: String -> ErrCode -> IO a
failWith fn_name err_code = do
c_msg <- getErrorMessage err_code
msg <- if c_msg == nullPtr
then return $ "Error 0x" ++ Numeric.showHex err_code ""
else do msg <- peekTString c_msg
_ <- localFree c_msg
return msg
c_maperrno
errno <- getErrno
let msg' = reverse $ dropWhile isSpace $ reverse msg
ioerror = errnoToIOError fn_name errno Nothing Nothing
`ioeSetErrorString` msg'
throwIO ioerror
foreign import ccall unsafe "maperrno"
c_maperrno :: IO ()
ddwordToDwords :: DDWORD -> (DWORD,DWORD)
ddwordToDwords n =
(fromIntegral (n `shiftR` finiteBitSize (undefined :: DWORD))
,fromIntegral (n .&. fromIntegral (maxBound :: DWORD)))
dwordsToDdword:: (DWORD,DWORD) -> DDWORD
dwordsToDdword (hi,low) = (fromIntegral low) .|. (fromIntegral hi `shiftL` finiteBitSize hi)
foreign import ccall "HsWin32.h &DeleteObjectFinaliser"
deleteObjectFinaliser :: FunPtr (Ptr a -> IO ())
foreign import WINDOWS_CCONV unsafe "windows.h LocalFree"
localFree :: Ptr a -> IO (Ptr a)
foreign import WINDOWS_CCONV unsafe "windows.h GetLastError"
getLastError :: IO ErrCode
foreign import ccall unsafe "errors.h"
getErrorMessage :: DWORD -> IO LPWSTR
foreign import ccall unsafe "HsWin32.h"
lOWORD :: DWORD -> WORD
foreign import ccall unsafe "HsWin32.h"
hIWORD :: DWORD -> WORD
foreign import ccall unsafe "HsWin32.h"
castUINTPtrToPtr :: UINT_PTR -> Ptr a
foreign import ccall unsafe "HsWin32.h"
castPtrToUINTPtr :: Ptr s -> UINT_PTR
type LCID = DWORD
type LANGID = WORD
type SortID = WORD
foreign import ccall unsafe "HsWin32.h prim_MAKELCID"
mAKELCID :: LANGID -> SortID -> LCID
foreign import ccall unsafe "HsWin32.h prim_LANGIDFROMLCID"
lANGIDFROMLCID :: LCID -> LANGID
foreign import ccall unsafe "HsWin32.h prim_SORTIDFROMLCID"
sORTIDFROMLCID :: LCID -> SortID
type SubLANGID = WORD
type PrimaryLANGID = WORD
foreign import ccall unsafe "HsWin32.h prim_MAKELANGID"
mAKELANGID :: PrimaryLANGID -> SubLANGID -> LANGID
foreign import ccall unsafe "HsWin32.h prim_PRIMARYLANGID"
pRIMARYLANGID :: LANGID -> PrimaryLANGID
foreign import ccall unsafe "HsWin32.h prim_SUBLANGID"
sUBLANGID :: LANGID -> SubLANGID