{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
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.Typeable
import qualified Data.HashMap.Strict as HashMap
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
let (ProfileCurrent prevProfKey prevProfLabel) = profCurrent env
if prevProfLabel == l
then
m env
else do
key <- atomicModifyIORef' (profRef env) $ \p ->
case HashMap.lookup (l, prevProfKey) (profileTree p) of
Just k -> (p, k)
Nothing -> (p
{ profileTree = HashMap.insert
(l, prevProfKey)
(profileNextKey p)
(profileTree p)
, profileNextKey = profileNextKey p + 1 }, profileNextKey p)
runProfileData l key m False env
{-# INLINE collectProfileData #-}
runProfileData
:: ProfileLabel
-> ProfileKey
-> (Env u w -> IO (Result u w a))
-> Bool
-> Env u w
-> IO (Result u w a)
runProfileData l key m isCont env = do
t0 <- getTimestamp
a0 <- getAllocationCounter
let
nextCurrent = ProfileCurrent
{ profCurrentKey = key
, profCurrentLabel = l }
caller = profCurrentKey (profCurrent env)
r <- m env{profCurrent=nextCurrent}
a1 <- getAllocationCounter
t1 <- getTimestamp
modifyProfileData env key caller (a0 - a1) (t1-t0) (if isCont then 0 else 1)
setAllocationCounter a1
case r of
Done a -> return (Done a)
Throw e -> return (Throw e)
Blocked ivar k -> return (Blocked ivar (Cont $ runCont (toHaxl k)))
where
runCont (GenHaxl h) = GenHaxl $ runProfileData l key h True
{-# INLINE runProfileData #-}
modifyProfileData
:: Env u w
-> ProfileKey
-> ProfileKey
-> AllocCount
-> Microseconds
-> LabelHitCount
-> IO ()
modifyProfileData env key caller allocs t labelIncrement = do
modifyIORef' (profRef env) $ \ p ->
p { profile =
HashMap.insertWith updEntry key newEntry .
HashMap.insertWith updCaller caller newCaller $
profile p }
where newEntry =
emptyProfileData
{ profileAllocs = allocs
, profileLabelHits = labelIncrement
, profileTime = t
}
updEntry _ old =
old
{ profileAllocs = profileAllocs old + allocs
, profileLabelHits = profileLabelHits old + labelIncrement
, profileTime = profileTime old + t
}
newCaller =
emptyProfileData { profileAllocs = -allocs
, profileTime = -t
}
updCaller _ old =
old { profileAllocs = profileAllocs old - allocs
, profileTime = profileTime old - t
}
profileCont
:: (Env u w -> IO (Result u w a))
-> Env u w
-> IO (Result u w a)
profileCont m env = do
t0 <- getTimestamp
a0 <- getAllocationCounter
r <- m env
a1 <- getAllocationCounter
t1 <- getTimestamp
let
allocs = a0 - a1
t = t0 - t1
newEntry = emptyProfileData
{ profileAllocs = allocs
, profileTime = t
}
updEntry _ old = old
{ profileAllocs = profileAllocs old + allocs
, profileTime = profileTime old + t
}
profKey = profCurrentKey (profCurrent env)
modifyIORef' (profRef env) $ \ p ->
p { profile =
HashMap.insertWith updEntry profKey newEntry $
profile p }
setAllocationCounter a1
return r
{-# INLINE profileCont #-}
incrementMemoHitCounterFor :: Env u w -> CallId -> Bool -> IO ()
incrementMemoHitCounterFor env callId wasCached = do
modifyIORef' (profRef env) $ \p -> p {
profile = HashMap.insertWith
upd
(profCurrentKey $ profCurrent env)
(emptyProfileData { profileMemos = [val] })
(profile p)
}
where
val = ProfileMemo callId wasCached
upd _ old = old { profileMemos = val : profileMemos old }
{-# NOINLINE addProfileFetch #-}
addProfileFetch
:: forall r u w a . (DataSourceName r, Eq (r a), Hashable (r a), Typeable (r a))
=> Env u w -> r a -> CallId -> Bool -> IO ()
addProfileFetch env _req cid wasCached = do
c <- getAllocationCounter
let (ProfileCurrent profKey _) = profCurrent env
modifyIORef' (profRef env) $ \ p ->
let
val = ProfileFetch cid (memoKey env) wasCached
upd _ old = old { profileFetches = val : profileFetches old }
in p { profile =
HashMap.insertWith
upd
profKey
(emptyProfileData { profileFetches = [val] })
(profile p)
}
setAllocationCounter c