{-# LANGUAGE ForeignFunctionInterface #-} module DirectX9.Types ( module Data.Word, module Graphics.Win32, module System.Win32, module Foreign, module DirectX9.ComObject, HRESULT, HMONITOR, LPCVOID, RGNDATA(..), GUID(..), REFGUID, REFIID, LARGE_INTEGER, PVOID, LPDWORD, LPGUID, SIZE_T ) where import Data.Word ( Word ) import Graphics.Win32 ( HDC, HWND, POINT ) import System.Win32 ( HANDLE, LPVOID, DWORD, UINT, BOOL, INT, FLOAT , WORD, BYTE, LONG, LPCSTR, LPSTR, TCHAR, LPCTSTR , LPCWSTR ) import Foreign ( Word64, Ptr, Storable, sizeOf, alignment, poke, peek , nullPtr ) import DirectX9.ComObject type SIZE_T = Int type PVOID = LPVOID type LPDWORD=Ptr DWORD type HRESULT = Int type HMONITOR=HANDLE type LPCVOID = LPVOID data RGNDATA = RGNDATA data GUID = GUID deriving (Show,Eq,Ord) type REFGUID = Ptr GUID type REFIID = Ptr GUID type LPGUID = Ptr GUID type LARGE_INTEGER = Word64 instance Storable GUID where sizeOf = const 16 alignment = const 1 poke _ _ = return () peek _ = return GUID