module DirectX9.Error where import Control.Monad ( when ) import DirectX9.Types #include "windows.h" #include "fix_decl.h" #include "d3d9.h" #include "fix_decl_x.h" #include "d3dx9.h" isHrFailed :: HRESULT -> Bool isHrFailed i = i<0 isHrSuccess :: [HRESULT] -> HRESULT -> Bool isHrSuccess ok res = elem res ok hrTranslate :: HRESULT -> String hrTranslate r = case lookup r errorText of Just x -> x Nothing -> "Unknown HRESULT (" ++ show r ++ ")" hrFailIf :: (HRESULT -> Bool) -> String -> IO HRESULT -> IO HRESULT hrFailIf f c a = do e <- a when (f e) $ fail $ c ++ ": " ++ hrTranslate e return e hrFail :: String -> IO HRESULT -> IO HRESULT hrFail = hrFailIf isHrFailed hrSuccess :: [HRESULT] -> String -> IO HRESULT -> IO HRESULT hrSuccess ok = hrFailIf (isHrSuccess ok) #{enum HRESULT, , d3D_OK = D3D_OK , d3DOK_NOAUTOGEN = D3DOK_NOAUTOGEN , d3DERR_CONFLICTINGRENDERSTATE = D3DERR_CONFLICTINGRENDERSTATE , d3DERR_CONFLICTINGTEXTUREFILTER = D3DERR_CONFLICTINGTEXTUREFILTER , d3DERR_CONFLICTINGTEXTUREPALETTE = D3DERR_CONFLICTINGTEXTUREPALETTE , d3DERR_DEVICELOST = D3DERR_DEVICELOST , d3DERR_DEVICENOTRESET = D3DERR_DEVICENOTRESET , d3DERR_DRIVERINTERNALERROR = D3DERR_DRIVERINTERNALERROR , d3DERR_DRIVERINVALIDCALL = D3DERR_DRIVERINVALIDCALL , d3DERR_INVALIDCALL = D3DERR_INVALIDCALL , d3DERR_INVALIDDEVICE = D3DERR_INVALIDDEVICE , d3DERR_MOREDATA = D3DERR_MOREDATA , d3DERR_NOTAVAILABLE = D3DERR_NOTAVAILABLE , d3DERR_NOTFOUND = D3DERR_NOTFOUND , d3DERR_OUTOFVIDEOMEMORY = D3DERR_OUTOFVIDEOMEMORY , d3DERR_TOOMANYOPERATIONS = D3DERR_TOOMANYOPERATIONS , d3DERR_UNSUPPORTEDALPHAARG = D3DERR_UNSUPPORTEDALPHAARG , d3DERR_UNSUPPORTEDALPHAOPERATION = D3DERR_UNSUPPORTEDALPHAOPERATION , d3DERR_UNSUPPORTEDCOLORARG = D3DERR_UNSUPPORTEDCOLORARG , d3DERR_UNSUPPORTEDCOLOROPERATION = D3DERR_UNSUPPORTEDCOLOROPERATION , d3DERR_UNSUPPORTEDFACTORVALUE = D3DERR_UNSUPPORTEDFACTORVALUE , d3DERR_UNSUPPORTEDTEXTUREFILTER = D3DERR_UNSUPPORTEDTEXTUREFILTER , d3DERR_WASSTILLDRAWING = D3DERR_WASSTILLDRAWING , d3DERR_WRONGTEXTUREFORMAT = D3DERR_WRONGTEXTUREFORMAT , e_FAIL = E_FAIL , e_INVALIDARG = E_INVALIDARG , e_NOINTERFACE = E_NOINTERFACE , e_NOTIMPL = E_NOTIMPL , e_OUTOFMEMORY = E_OUTOFMEMORY , s_OK = S_OK ,d3DXERR_CANNOTMODIFYINDEXBUFFER = D3DXERR_CANNOTMODIFYINDEXBUFFER ,d3DXERR_INVALIDMESH = D3DXERR_INVALIDMESH ,d3DXERR_CANNOTATTRSORT = D3DXERR_CANNOTATTRSORT ,d3DXERR_SKINNINGNOTSUPPORTED = D3DXERR_SKINNINGNOTSUPPORTED ,d3DXERR_TOOMANYINFLUENCES = D3DXERR_TOOMANYINFLUENCES ,d3DXERR_INVALIDDATA = D3DXERR_INVALIDDATA ,d3DXERR_LOADEDMESHASNODATA = D3DXERR_LOADEDMESHASNODATA ,d3DXERR_DUPLICATENAMEDFRAGMENT = D3DXERR_DUPLICATENAMEDFRAGMENT ,d3DXERR_CANNOTREMOVELASTITEM = D3DXERR_CANNOTREMOVELASTITEM } -- , e_INVALIDCALL =E_INVALIDCALL errorText :: [(HRESULT,String)] errorText = [ (d3D_OK,"No error occurred."), (d3DOK_NOAUTOGEN,"Autogeneration of MIPMAPs failed for this format"), (d3DERR_CONFLICTINGRENDERSTATE,"The currently set render states cannot be used together."), (d3DERR_CONFLICTINGTEXTUREFILTER,"The current texture filters cannot be used together."), (d3DERR_CONFLICTINGTEXTUREPALETTE,"The current textures cannot be used simultaneously."), (d3DERR_DEVICELOST,"The device has been lost but cannot be reset at this time. Therefore, rendering is not possible."), (d3DERR_DEVICENOTRESET,"The device has been lost but can be reset at this time."), (d3DERR_DRIVERINTERNALERROR,"Internal driver error"), (d3DERR_DRIVERINVALIDCALL,"Not used."), (d3DERR_INVALIDCALL,"Invalid methodcall."), (d3DERR_INVALIDDEVICE,"The requested device type is not valid."), (d3DERR_MOREDATA,"There is more data available than the specified buffer size can hold."), (d3DERR_NOTAVAILABLE,"This device does not support the queried technique."), (d3DERR_NOTFOUND,"The requested item was not found."), (d3DERR_OUTOFVIDEOMEMORY,"Direct3D does not have enough display memory to perform the operation."), (d3DERR_TOOMANYOPERATIONS,"The application is requesting more texture-filtering operations than the device supports."), (d3DERR_UNSUPPORTEDALPHAARG,"The device does not support a specified texture-blending argument for the alpha channel."), (d3DERR_UNSUPPORTEDALPHAOPERATION,"The device does not support a specified texture-blending operation for the alpha channel."), (d3DERR_UNSUPPORTEDCOLORARG,"The device does not support a specified texture-blending argument for color values."), (d3DERR_UNSUPPORTEDCOLOROPERATION,"The device does not support a specified texture-blending operation for color values."), (d3DERR_UNSUPPORTEDFACTORVALUE,"The device does not support the specified texture factor value. Not used; provided only to support older drivers."), (d3DERR_UNSUPPORTEDTEXTUREFILTER,"The device does not support the specified texture filter."), (d3DERR_WASSTILLDRAWING,"The previous blit operation that is transferring information to or from this surface is incomplete."), (d3DERR_WRONGTEXTUREFORMAT,"The pixel format of the texture surface is not valid."), (e_FAIL,"An undetermined error occurred."), (e_INVALIDARG,"An invalid parameter was passed to the returning function."), -- (e_INVALIDCALL,"The method call is invalid. For example, a method's parameter may have an invalid value."), (e_NOINTERFACE,"No object interface is available."), (e_NOTIMPL,"Not implemented."), (e_OUTOFMEMORY, "Not enough memory."), (s_OK, "No error occurred.") ]