{-# LANGUAGE ForeignFunctionInterface #-} -- | DirectX9.D3D.Perf - d3d performance profiling helpers module DirectX9.D3D.Perf where import DirectX9.Types import DirectX9.D3D.Raw import Control.Exception ( bracket_ ) import Foreign.C.String ( withCWString ) import System.IO.Unsafe ( unsafePerformIO ) d3dPerfEnable :: Bool -> IO () d3dPerfEnable cond = c_D3DPERF_SetOptions (if cond then 0 else 1) -- | d3dPerfGroup creates an user-defined event for performance profiler. d3dPerfGroup :: Bool -> D3DCOLOR -> String -> IO b -> IO b d3dPerfGroup cond col msg act | not cond = act | otherwise = bracket_ (withCWString msg $ c_D3DPERF_BeginEvent col) (c_D3DPERF_EnvEvent) act -- | d3dPerfMarker creates a marker for performance profiler d3dPerfMarker :: Bool -> D3DCOLOR -> String -> IO () d3dPerfMarker cond col msg | not cond = return () | otherwise = (withCWString msg $ c_D3DPERF_SetMarker col) >> return () -- | d3dPerfPrint creates a marker for performance profiler d3dPerfPrint :: (Show a) => Bool -> D3DCOLOR -> a -> IO () d3dPerfPrint cond col msg | not cond = return () | otherwise = (withCWString (show msg) $ c_D3DPERF_SetMarker col) >> return () -- | d3dPerfTrace creates a marker for performance profiler, but it is pure unlike -- d3dPerfMarker. It makes use of unsafePerformIO and has same disadvantages as -- Debug.Trace.trace. d3dPerfTrace :: Bool -> D3DCOLOR -> String -> a -> a d3dPerfTrace cond col msg val | not cond = val | otherwise = unsafePerformIO $ (withCWString msg $ c_D3DPERF_SetMarker col) >> return val foreign import stdcall "fake.h D3DPERF_SetOptions" c_D3DPERF_SetOptions :: DWORD -> IO () foreign import stdcall "fake.h D3DPERF_GetStatus" c_D3DPERF_GetStatus :: IO () foreign import stdcall "fake.h D3DPERF_BeginEvent" c_D3DPERF_BeginEvent :: D3DCOLOR -> LPCWSTR -> IO Int foreign import stdcall "fake.h D3DPERF_EndEvent" c_D3DPERF_EnvEvent :: IO Int foreign import stdcall "fake.h D3DPERF_SetMarker" c_D3DPERF_SetMarker :: D3DCOLOR -> LPCWSTR -> IO ()