{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Haxl.Core.Profile
( withLabel
, withFingerprintLabel
, addProfileFetch
, incrementMemoHitCounterFor
, collectProfileData
, profileCont
) where
import Data.IORef
import Data.Hashable
#if __GLASGOW_HASKELL__ < 804
import Data.Monoid
#endif
import Data.Text (Text)
import Data.Typeable
import qualified Data.HashMap.Strict as HashMap
import qualified Data.HashSet as HashSet
import GHC.Exts
import qualified Data.Text as Text
import Haxl.Core.DataSource
import Haxl.Core.Flags
import Haxl.Core.Stats
import Haxl.Core.Monad
withLabel :: ProfileLabel -> GenHaxl u w a -> GenHaxl u w a
withLabel l (GenHaxl m) = GenHaxl $ \env ->
if report (flags env) < 4
then m env
else collectProfileData l m env
withFingerprintLabel :: Addr# -> Addr# -> GenHaxl u w a -> GenHaxl u w a
withFingerprintLabel mnPtr nPtr (GenHaxl m) = GenHaxl $ \env ->
if report (flags env) < 4
then m env
else collectProfileData
(Text.unpackCString# mnPtr <> "." <> Text.unpackCString# nPtr)
m env
collectProfileData
:: ProfileLabel
-> (Env u w -> IO (Result u w a))
-> Env u w
-> IO (Result u w a)
collectProfileData l m env = do
a0 <- getAllocationCounter
r <- m env{profLabel=l}
a1 <- getAllocationCounter
modifyProfileData env l (a0 - a1)
setAllocationCounter a1
case r of
Done a -> return (Done a)
Throw e -> return (Throw e)
Blocked ivar k -> return (Blocked ivar (Cont (withLabel l (toHaxl k))))
{-# INLINE collectProfileData #-}
modifyProfileData :: Env u w -> ProfileLabel -> AllocCount -> IO ()
modifyProfileData env label allocs =
modifyIORef' (profRef env) $ \ p ->
p { profile =
HashMap.insertWith updEntry label newEntry .
HashMap.insertWith updCaller caller newCaller $
profile p }
where caller = profLabel env
newEntry =
emptyProfileData
{ profileAllocs = allocs
, profileDeps = HashSet.singleton caller }
updEntry _ old =
old { profileAllocs = profileAllocs old + allocs
, profileDeps = HashSet.insert caller (profileDeps old) }
newCaller =
emptyProfileData { profileAllocs = -allocs }
updCaller _ old =
old { profileAllocs = profileAllocs old - allocs }
profileCont
:: (Env u w -> IO (Result u w a))
-> Env u w
-> IO (Result u w a)
profileCont m env = do
a0 <- getAllocationCounter
r <- m env
a1 <- getAllocationCounter
let
allocs = a0 - a1
newEntry = emptyProfileData { profileAllocs = allocs }
updEntry _ old = old { profileAllocs = profileAllocs old + allocs }
modifyIORef' (profRef env) $ \ p ->
p { profile =
HashMap.insertWith updEntry (profLabel env) newEntry $
profile p }
setAllocationCounter a1
return r
{-# INLINE profileCont #-}
incrementMemoHitCounterFor :: ProfileLabel -> Profile -> Profile
incrementMemoHitCounterFor lbl p =
p { profile = HashMap.adjust incrementMemoHitCounter lbl (profile p) }
incrementMemoHitCounter :: ProfileData -> ProfileData
incrementMemoHitCounter pd = pd { profileMemoHits = succ (profileMemoHits pd) }
{-# NOINLINE addProfileFetch #-}
addProfileFetch
:: forall r u w a . (DataSourceName r, Eq (r a), Hashable (r a), Typeable (r a))
=> Env u w -> r a -> IO ()
addProfileFetch env _req = do
c <- getAllocationCounter
modifyIORef' (profRef env) $ \ p ->
let
dsName :: Text
dsName = dataSourceName (Proxy :: Proxy r)
upd :: ProfileData -> ProfileData
upd d = d { profileFetches =
HashMap.insertWith (+) dsName 1 (profileFetches d) }
in p { profile = HashMap.adjust upd (profLabel env) (profile p) }
setAllocationCounter c