{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
module Haxl.Core.Run
( runHaxl
, runHaxlWithWrites
) where
#if __GLASGOW_HASKELL__ <= 708
import Control.Applicative ((<$>))
#endif
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
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 resultRef) <- newIVar
let
schedule :: Env u w -> JobList u w -> GenHaxl u w b -> IVar u w b -> IO ()
schedule env@Env{..} rq (GenHaxl run) (IVar !ref) = do
ifTrace flags 3 $ printf "schedule: %d\n" (1 + lengthJobList rq)
let {-# INLINE result #-}
result r = do
e <- readIORef ref
case e of
IVarFull _ -> error "multiple put"
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 ivar fn) -> do
addJob env (toHaxl fn) (IVar ref) ivar
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
ifTrace flags 3 $ printf "emptyRunQueue\n"
haxls <- checkCompletions env
case haxls of
JobNil -> do
case pendingWaits of
[] -> checkRequestStore env
wait:waits -> do
ifTrace flags 3 $ printf "invoking wait\n"
wait
emptyRunQueue env { pendingWaits = waits }
_ -> reschedule env haxls
checkRequestStore :: Env u w -> IO ()
checkRequestStore env@Env{..} = do
reqStore <- readIORef reqStoreRef
if RequestStore.isEmpty reqStore
then waitCompletions env
else do
writeIORef reqStoreRef noRequests
(_, waits) <- performRequestStore 0 env reqStore
ifTrace flags 3 $ printf "performFetches: %d waits\n" (length waits)
when (caching flags == 0) $
writeIORef cacheRef emptyDataCache
emptyRunQueue env{ pendingWaits = waits ++ pendingWaits }
checkCompletions :: Env u w -> IO (JobList u w)
checkCompletions Env{..} = do
ifTrace flags 3 $ printf "checkCompletions\n"
comps <- atomically $ do
c <- readTVar completions
writeTVar completions []
return c
case comps of
[] -> return JobNil
_ -> do
ifTrace flags 3 $ printf "%d complete\n" (length comps)
let
getComplete (CompleteReq a (IVar cr) allocs) = do
when (allocs < 0) $ do
cur <- getAllocationCounter
setAllocationCounter (cur + allocs)
r <- readIORef cr
case r of
IVarFull _ -> do
ifTrace flags 3 $ 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
ifTrace flags 3 $ printf "waitCompletions\n"
atomically $ do
c <- readTVar completions
when (null c) retry
emptyRunQueue env
schedule env JobNil haxl result
r <- readIORef resultRef
case r of
IVarEmpty _ -> throwIO (CriticalError "runHaxl: missing result")
IVarFull (Ok a wt) -> return (a, flattenWT wt)
IVarFull (ThrowHaxl e _wt) -> throwIO e
IVarFull (ThrowIO e) -> throwIO e