{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Haxl.Core.Run
( runHaxl
, runHaxlWithWrites
) where
import Control.Concurrent.STM
import Control.Exception as Exception
import Control.Monad
import Data.IORef
import Text.Printf
import Unsafe.Coerce
import Haxl.Core.DataCache
import Haxl.Core.Exception
import Haxl.Core.Flags
import Haxl.Core.Monad
import Haxl.Core.Fetch
import Haxl.Core.Profile
import Haxl.Core.RequestStore as RequestStore
import Haxl.Core.Stats
import Haxl.Core.Util
import qualified Data.HashTable.IO as H
runHaxl:: forall u w a. Env u w -> GenHaxl u w a -> IO a
runHaxl env haxl = fst <$> runHaxlWithWrites env haxl
runHaxlWithWrites :: forall u w a. Env u w -> GenHaxl u w a -> IO (a, [w])
runHaxlWithWrites env@Env{..} haxl = do
result@IVar{ivarRef = resultRef} <- newIVar
ifTraceLog <- do
if trace flags < 3
then return $ \_ -> return ()
else do
start <- getTimestamp
return $ \s -> do
now <- getTimestamp
let t = fromIntegral (now - start) / 1000.0 :: Double
printf "%.1fms: %s" t (s :: String)
let
schedule :: Env u w -> JobList u w -> GenHaxl u w b -> IVar u w b -> IO ()
schedule env@Env{..} rq (GenHaxl run) ivar@IVar{ivarRef = !ref} = do
ifTraceLog $ printf "schedule: %d\n" (1 + lengthJobList rq)
let {-# INLINE result #-}
result r = do
e <- readIORef ref
case e of
IVarFull _ ->
reschedule env rq
IVarEmpty haxls -> do
writeIORef ref (IVarFull r)
if ref == unsafeCoerce resultRef
then
case rq of
JobNil -> return ()
_ -> modifyIORef' runQueueRef (appendJobList rq)
else reschedule env (appendJobList haxls rq)
r <-
if report flags >= 4
then Exception.try $ profileCont run env
else Exception.try $ run env
case r of
Left e -> do
rethrowAsyncExceptions e
result (ThrowIO e)
Right (Done a) -> do
wt <- readIORef writeLogsRef
result (Ok a wt)
Right (Throw ex) -> do
wt <- readIORef writeLogsRef
result (ThrowHaxl ex wt)
Right (Blocked i fn) -> do
addJob env (toHaxl fn) ivar i
reschedule env rq
reschedule :: Env u w -> JobList u w -> IO ()
reschedule env@Env{..} haxls = do
case haxls of
JobNil -> do
rq <- readIORef runQueueRef
case rq of
JobNil -> emptyRunQueue env
JobCons env' a b c -> do
writeIORef runQueueRef JobNil
schedule env' c a b
JobCons env' a b c ->
schedule env' c a b
emptyRunQueue :: Env u w -> IO ()
emptyRunQueue env@Env{..} = do
ifTraceLog $ printf "emptyRunQueue\n"
haxls <- checkCompletions env
case haxls of
JobNil -> checkRequestStore env
_ -> reschedule env haxls
checkRequestStore :: Env u w -> IO ()
checkRequestStore env@Env{..} = do
ifTraceLog $ printf "checkRequestStore\n"
reqStore <- readIORef reqStoreRef
if RequestStore.isEmpty reqStore
then waitCompletions env
else do
ifTraceLog $ printf "performFetches %d\n" (RequestStore.getSize reqStore)
writeIORef reqStoreRef noRequests
performRequestStore env reqStore
when (caching flags == 0) $ do
let DataCache dc = dataCache
H.foldM (\_ (k, _) -> H.delete dc k) () dc
emptyRunQueue env
checkCompletions :: Env u w -> IO (JobList u w)
checkCompletions Env{..} = do
ifTraceLog $ printf "checkCompletions\n"
comps <- atomicallyOnBlocking (LogicBug ReadingCompletionsFailedRun) $ do
c <- readTVar completions
writeTVar completions []
return c
case comps of
[] -> return JobNil
_ -> do
ifTraceLog $ printf "%d complete\n" (length comps)
let
getComplete (CompleteReq a IVar{ivarRef = !cr} allocs) = do
when (allocs < 0) $ do
cur <- getAllocationCounter
setAllocationCounter (cur + allocs)
r <- readIORef cr
case r of
IVarFull _ -> do
ifTraceLog $ printf "existing result\n"
return JobNil
IVarEmpty cv -> do
writeIORef cr (IVarFull (eitherToResult a))
return cv
jobs <- mapM getComplete comps
return (foldr appendJobList JobNil jobs)
waitCompletions :: Env u w -> IO ()
waitCompletions env@Env{..} = do
ifTraceLog $ printf "waitCompletions\n"
let
wrapped = atomicallyOnBlocking (LogicBug ReadingCompletionsFailedRun)
doWait = wrapped $ do
c <- readTVar completions
when (null c) retry
doWaitProfiled = do
queueEmpty <- null <$> wrapped (readTVar completions)
when queueEmpty $ do
waitingOn <- readIORef submittedReqsRef
queueEmpty2 <- null <$> wrapped (readTVar completions)
when queueEmpty2 $ do
start <- getTimestamp
doWait
end <- getTimestamp
let fw = FetchWait
{ fetchWaitReqs = getSummaryMapFromRCMap waitingOn
, fetchWaitStart = start
, fetchWaitDuration = (end-start)
}
modifyIORef' statsRef $ \(Stats s) -> Stats (fw:s)
if report flags >= 2
then doWaitProfiled
else doWait
emptyRunQueue env
schedule env JobNil haxl result
r <- readIORef resultRef
case r of
IVarEmpty _ -> throwIO (CriticalError "runHaxl: missing result")
IVarFull (Ok a wt) -> do
wtNoMemo <- readIORef writeLogsRefNoMemo
return (a, flattenWT (wt `appendWTs` wtNoMemo))
IVarFull (ThrowHaxl e _wt) -> throwIO e
IVarFull (ThrowIO e) -> throwIO e
data ReadingCompletionsFailedRun = ReadingCompletionsFailedRun
deriving Show
instance Exception ReadingCompletionsFailedRun