{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Haxl.Core.Stats
(
Stats(..)
, FetchStats(..)
, Microseconds
, Timestamp
, getTimestamp
, emptyStats
, numRounds
, numFetches
, ppStats
, ppFetchStats
, Profile
, emptyProfile
, profile
, ProfileLabel
, ProfileData(..)
, emptyProfileData
, AllocCount
, MemoHitCount
, getAllocationCounter
, setAllocationCounter
) where
import Data.Aeson
import Data.HashMap.Strict (HashMap)
import Data.HashSet (HashSet)
import Data.Int
import Data.List (intercalate, maximumBy, minimumBy)
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid
#endif
import Data.Semigroup (Semigroup)
import Data.Ord (comparing)
import Data.Text (Text)
import Data.Time.Clock.POSIX
import Text.Printf
import qualified Data.HashMap.Strict as HashMap
import qualified Data.HashSet as HashSet
import qualified Data.Text as Text
#if __GLASGOW_HASKELL__ >= 710
import GHC.Conc (getAllocationCounter, setAllocationCounter)
#endif
type Microseconds = Int64
type Timestamp = Microseconds
getTimestamp :: IO Timestamp
getTimestamp = do
t <- getPOSIXTime
return (round (t * 1000000))
newtype Stats = Stats [FetchStats]
deriving (Show, ToJSON, Semigroup, Monoid)
ppStats :: Stats -> String
ppStats (Stats rss) =
intercalate "\n"
[ "["
++ [
if fetchWasRunning rs
(minStartTime + (t - 1) * usPerDash)
(minStartTime + t * usPerDash)
then '*'
else '-'
| t <- [1..numDashes]
]
++ "] " ++ show i ++ " - " ++ ppFetchStats rs
| (i, rs) <- zip [(1::Int)..] validFetchStats ]
where
isFetchStats FetchStats{} = True
isFetchStats _ = False
validFetchStats = filter isFetchStats (reverse rss)
numDashes = 50
minStartTime = fetchStart $ minimumBy (comparing fetchStart) validFetchStats
lastFs = maximumBy (comparing (\fs -> fetchStart fs + fetchDuration fs))
validFetchStats
usPerDash = (fetchStart lastFs + fetchDuration lastFs - minStartTime)
`div` numDashes
fetchWasRunning :: FetchStats -> Timestamp -> Timestamp -> Bool
fetchWasRunning fs t1 t2 =
(fetchStart fs + fetchDuration fs) >= t1 && fetchStart fs < t2
data FetchStats
= FetchStats
{ fetchDataSource :: Text
, fetchBatchSize :: {-# UNPACK #-} !Int
, fetchStart :: !Timestamp
, fetchDuration :: {-# UNPACK #-} !Microseconds
, fetchSpace :: {-# UNPACK #-} !Int64
, fetchFailures :: {-# UNPACK #-} !Int
}
| FetchCall
{ fetchReq :: String
, fetchStack :: [String]
}
deriving (Show)
ppFetchStats :: FetchStats -> String
ppFetchStats FetchStats{..} =
printf "%s: %d fetches (%.2fms, %d bytes, %d failures)"
(Text.unpack fetchDataSource) fetchBatchSize
(fromIntegral fetchDuration / 1000 :: Double) fetchSpace fetchFailures
ppFetchStats (FetchCall r ss) = show r ++ '\n':show ss
instance ToJSON FetchStats where
toJSON FetchStats{..} = object
[ "datasource" .= fetchDataSource
, "fetches" .= fetchBatchSize
, "start" .= fetchStart
, "duration" .= fetchDuration
, "allocation" .= fetchSpace
, "failures" .= fetchFailures
]
toJSON (FetchCall req strs) = object
[ "request" .= req
, "stack" .= strs
]
emptyStats :: Stats
emptyStats = Stats []
numRounds :: Stats -> Int
numRounds (Stats rs) = length rs
numFetches :: Stats -> Int
numFetches (Stats rs) = sum [ fetchBatchSize | FetchStats{..} <- rs ]
type ProfileLabel = Text
type AllocCount = Int64
type MemoHitCount = Int64
newtype Profile = Profile
{ profile :: HashMap ProfileLabel ProfileData
}
emptyProfile :: Profile
emptyProfile = Profile HashMap.empty
data ProfileData = ProfileData
{ profileAllocs :: {-# UNPACK #-} !AllocCount
, profileDeps :: HashSet ProfileLabel
, profileFetches :: HashMap Text Int
, profileMemoHits :: {-# UNPACK #-} !MemoHitCount
}
deriving Show
emptyProfileData :: ProfileData
emptyProfileData = ProfileData 0 HashSet.empty HashMap.empty 0
#if __GLASGOW_HASKELL__ < 710
getAllocationCounter :: IO Int64
getAllocationCounter = return 0
setAllocationCounter :: Int64 -> IO ()
setAllocationCounter _ = return ()
#endif