module DirectX9.D3D.X.Misc where import DirectX9.Error import DirectX9.D3D import DirectX9.D3D.X.Import import DirectX9.D3D.X.Raw import Foreign ( alloca, castPtr, peekArray ) import Foreign.C.String ( withCWString, peekCAString, peekCWString ) type XBuffer = ComObject ID3DXBuffer withXBufferLen :: XBuffer -> (Int -> Ptr a -> IO b) -> IO b withXBufferLen buf act = withCom buf $ \buf -> do ptr <- c_ID3DXBuffer_GetBufferPointer buf len <- c_ID3DXBuffer_GetBufferSize buf act (fromIntegral len) (castPtr ptr) withXBuffer :: XBuffer -> (Ptr a -> IO b) -> IO b withXBuffer buf act = withXBufferLen buf (const act) {-peekArrayFromXBuffer :: (Storable a) => XBuffer -> IO [a] peekArrayFromXBuffer buf = withXBufferLen buf $ \len content -> peekArray (div len size) content -} peekCAStringFromXBuffer :: XBuffer -> IO String peekCAStringFromXBuffer buf = withXBuffer buf peekCAString peekCWStringFromXBuffer :: XBuffer -> IO String peekCWStringFromXBuffer buf = withXBuffer buf peekCWString d3dxMatrixPerspectiveFovLH :: Float -> Float -> Float -> Float -> IO D3DMATRIX d3dxMatrixPerspectiveFovLH fov aspect zn zf = alloca $ \mat -> c_D3DXMatrixPerspectiveFovLH mat fov aspect zn zf >>= peek d3dxMatrixTranslation :: Float -> Float -> Float -> IO D3DMATRIX d3dxMatrixTranslation x y z = alloca $ \mat -> c_D3DXMatrixTranslation mat x y z >>= peek d3dxMatrixRotationYawPitchRoll :: Float -> Float -> Float -> IO D3DMATRIX d3dxMatrixRotationYawPitchRoll y p r = alloca $ \mat -> c_D3DXMatrixRotationYawPitchRoll mat y p r >>= peek d3dxCreateTextureFromFile :: Device -> String -> IO Texture d3dxCreateTextureFromFile dev name = withCom dev $ \dev -> withCWString name $ \name -> alloca $ \ret -> do hrFail "D3DXCreateTextureFromFile" $ c_D3DXCreateTextureFromFile dev name ret peek ret >>= comMake