module Development.Shake.Internal.Core.Run(
run,
Action, actionOnException, actionFinally, apply, apply1, traced,
getShakeOptions, getProgress,
getVerbosity, putLoud, putNormal, putQuiet, withVerbosity, quietly,
Resource, newResource, newResourceIO, withResource, withResources, newThrottle, newThrottleIO,
newCache, newCacheIO,
unsafeExtraThread, unsafeAllowApply,
parallel,
orderOnlyAction,
runAfter
) where
import Control.Exception.Extra
import Control.Applicative
import Data.Tuple.Extra
import Control.Concurrent.Extra
import Control.Monad.Extra
import Control.Monad.IO.Class
import Data.Typeable.Extra
import Data.Function
import Data.Either.Extra
import Data.List.Extra
import qualified Data.HashMap.Strict as Map
import Data.Dynamic
import Data.Maybe
import Data.IORef
import System.Directory
import System.IO.Extra
import System.Time.Extra
import Numeric.Extra
import qualified Data.ByteString as BS
import Development.Shake.Classes
import Development.Shake.Internal.Core.Types
import Development.Shake.Internal.Core.Action
import Development.Shake.Internal.Core.Rules
import Development.Shake.Internal.Core.Pool
import Development.Shake.Internal.Core.Database
import Development.Shake.Internal.Core.Monad
import Development.Shake.Internal.Resource
import Development.Shake.Internal.Value
import Development.Shake.Internal.Profile
import Development.Shake.Internal.Options
import Development.Shake.Internal.Errors
import General.Timing
import General.Extra
import General.Concurrent
import General.Cleanup
import Prelude
run :: ShakeOptions -> Rules () -> IO ()
run opts@ShakeOptions{..} rs = (if shakeLineBuffering then lineBuffering else id) $ do
opts@ShakeOptions{..} <- if shakeThreads /= 0 then return opts else do p <- getProcessorCount; return opts{shakeThreads=p}
start <- offsetTime
(actions, ruleinfo, userRules) <- runRules opts rs
outputLocked <- do
lock <- newLock
return $ \v msg -> withLock lock $ shakeOutput v msg
let diagnostic | shakeVerbosity < Diagnostic = const $ return ()
| otherwise = \act -> do v <- act; outputLocked Diagnostic $ "% " ++ v
let output v = outputLocked v . shakeAbbreviationsApply opts
diagnostic $ return "Starting run"
except <- newIORef (Nothing :: Maybe (String, ShakeException))
let raiseError err
| not shakeStaunch = throwIO err
| otherwise = do
let named = shakeAbbreviationsApply opts . shakeExceptionTarget
atomicModifyIORef except $ \v -> (Just $ fromMaybe (named err, err) v, ())
curdir <- getCurrentDirectory
diagnostic $ return "Starting run 2"
checkShakeExtra shakeExtra
after <- newIORef []
absent <- newIORef []
withCleanup $ \cleanup -> do
_ <- addCleanup cleanup $ do
when shakeTimings printTimings
resetTimings
withNumCapabilities shakeThreads $ do
diagnostic $ return "Starting run 3"
withDatabase opts diagnostic (Map.map builtinKey ruleinfo) $ \database -> do
wait <- newBarrier
let getProgress = do
failure <- fmap fst <$> readIORef except
stats <- progress database
return stats{isFailure=failure}
tid <- flip forkFinally (const $ signalBarrier wait ()) $
shakeProgress getProgress
_ <- addCleanup cleanup $ do
killThread tid
void $ timeout 1000000 $ waitBarrier wait
addTiming "Running rules"
runPool (shakeThreads == 1) shakeThreads $ \pool -> do
let s0 = Global database pool cleanup start ruleinfo output opts diagnostic curdir after absent getProgress userRules
let s1 = newLocal emptyStack shakeVerbosity
forM_ actions $ \act ->
addPoolLowPriority pool $ runAction s0 s1 act $ \x -> case x of
Left e -> raiseError =<< shakeException s0 ["Top-level action/want"] e
Right x -> return x
maybe (return ()) (throwIO . snd) =<< readIORef except
assertFinishedDatabase database
let putWhen lvl msg = when (shakeVerbosity >= lvl) $ output lvl msg
when (null actions) $
putWhen Normal "Warning: No want/action statements, nothing to do"
when (isJust shakeLint) $ do
addTiming "Lint checking"
lintCurrentDirectory curdir "After completion"
absent <- readIORef absent
checkValid database (runLint ruleinfo) absent
putWhen Loud "Lint checking succeeded"
when (shakeReport /= []) $ do
addTiming "Profile report"
report <- toReport database
forM_ shakeReport $ \file -> do
putWhen Normal $ "Writing report to " ++ file
writeProfile file report
when (shakeLiveFiles /= []) $ do
addTiming "Listing live"
live <- listLive database
let specialIsFileKey t = show (fst $ splitTyConApp t) == "FileQ"
let liveFiles = [show k | k <- live, specialIsFileKey $ typeKey k]
forM_ shakeLiveFiles $ \file -> do
putWhen Normal $ "Writing live list to " ++ file
(if file == "-" then putStr else writeFile file) $ unlines liveFiles
sequence_ . reverse =<< readIORef after
checkShakeExtra :: Map.HashMap TypeRep Dynamic -> IO ()
checkShakeExtra mp = do
let bad = [(k,t) | (k,v) <- Map.toList mp, let t = dynTypeRep v, t /= k]
case bad of
(k,t):xs -> errorStructured "Invalid Map in shakeExtra"
[("Key",Just $ show k),("Value type",Just $ show t)]
(if null xs then "" else "Plus " ++ show (length xs) ++ " other keys")
_ -> return ()
lintCurrentDirectory :: FilePath -> String -> IO ()
lintCurrentDirectory old msg = do
now <- getCurrentDirectory
when (old /= now) $ errorStructured
"Lint checking error - current directory has changed"
[("When", Just msg)
,("Wanted",Just old)
,("Got",Just now)]
""
lineBuffering :: IO a -> IO a
lineBuffering act = do
out <- hGetBuffering stdout
err <- hGetBuffering stderr
hSetBuffering stdout LineBuffering
hSetBuffering stderr LineBuffering
act `finally` do
hSetBuffering stdout out
hSetBuffering stderr err
apply :: (RuleResult key ~ value, ShakeValue key, ShakeValue value) => [key] -> Action [value]
apply (ks :: [key]) = withResultType $ \(p :: Maybe (Action [value])) -> do
liftIO $ mapM_ (evaluate . rnf) ks
let tk = typeRep (Proxy :: Proxy key)
tv = typeRep (Proxy :: Proxy value)
Global{..} <- Action getRO
block <- Action $ getsRW localBlockApply
whenJust block $ liftIO . errorNoApply tk (show <$> listToMaybe ks)
case Map.lookup tk globalRules of
Nothing -> liftIO $ errorNoRuleToBuildType tk (show <$> listToMaybe ks) (Just tv)
Just BuiltinRule{builtinResult=tv2} | tv /= tv2 -> errorInternal $ "result type does not match, " ++ show tv ++ " vs " ++ show tv2
_ -> fmap (map fromValue) $ applyKeyValue $ map newKey ks
applyKeyValue :: [Key] -> Action [Value]
applyKeyValue [] = return []
applyKeyValue ks = do
global@Global{..} <- Action getRO
stack <- Action $ getsRW localStack
(dur, dep, vs) <- Action $ captureRAW $ build globalPool globalDatabase (BuildKey $ runKey global) stack ks
Action $ modifyRW $ \s -> s{localDiscount=localDiscount s + dur, localDepends=dep : localDepends s}
return vs
runKey :: Global -> Stack -> Step -> Key -> Maybe (Result BS.ByteString) -> Bool -> Capture (Either SomeException (Bool, BS.ByteString, Result Value))
runKey global@Global{globalOptions=ShakeOptions{..},..} stack step k r dirtyChildren continue = do
let tk = typeKey k
BuiltinRule{..} <- case Map.lookup tk globalRules of
Nothing -> errorNoRuleToBuildType tk (Just $ show k) Nothing
Just r -> return r
let s = newLocal stack shakeVerbosity
time <- offsetTime
runAction global s (do
res <- builtinRun k (fmap result r) dirtyChildren
liftIO $ evaluate $ rnf res
when (Just LintFSATrace == shakeLint) trackCheckUsed
Action $ fmap ((,) res) getRW) $ \x -> case x of
Left e -> do
e <- if isNothing shakeLint then return e else handle return $
do lintCurrentDirectory globalCurDir $ "Running " ++ show k; return e
continue . Left . toException =<< shakeException global (showStack stack) e
Right (RunResult{..}, Local{..})
| runChanged == ChangedNothing || runChanged == ChangedStore, Just r <- r ->
continue $ Right (runChanged == ChangedStore, runStore, r{result = runValue})
| otherwise -> do
dur <- time
let c | Just r <- r, runChanged == ChangedRecomputeSame = changed r
| otherwise = step
continue $ Right $ (,,) True runStore Result
{result = runValue
,changed = c
,built = step
,depends = reverse localDepends
,execution = doubleToFloat $ dur localDiscount
,traces = reverse localTraces}
runLint :: Map.HashMap TypeRep BuiltinRule -> Key -> Value -> IO (Maybe String)
runLint mp k v = case Map.lookup (typeKey k) mp of
Nothing -> return Nothing
Just BuiltinRule{..} -> builtinLint k v
shakeException :: Global -> [String] -> SomeException -> IO ShakeException
shakeException Global{globalOptions=ShakeOptions{..},..} stk e@(SomeException inner) = case cast inner of
Just e@ShakeException{} -> return e
Nothing -> do
e <- return $ ShakeException (last $ "Unknown call stack" : stk) stk e
when (shakeStaunch && shakeVerbosity >= Quiet) $
globalOutput Quiet $ show e ++ "Continuing due to staunch mode"
return e
apply1 :: (RuleResult key ~ value, ShakeValue key, ShakeValue value) => key -> Action value
apply1 = fmap head . apply . return
newResource :: String -> Int -> Rules Resource
newResource name mx = liftIO $ newResourceIO name mx
newThrottle :: String -> Int -> Double -> Rules Resource
newThrottle name count period = liftIO $ newThrottleIO name count period
withResource :: Resource -> Int -> Action a -> Action a
withResource r i act = do
Global{..} <- Action getRO
liftIO $ globalDiagnostic $ return $ show r ++ " waiting to acquire " ++ show i
offset <- liftIO offsetTime
Action $ captureRAW $ \continue -> acquireResource r globalPool i $ continue $ Right ()
res <- Action $ tryRAW $ fromAction $ blockApply ("Within withResource using " ++ show r) $ do
offset <- liftIO offset
liftIO $ globalDiagnostic $ return $ show r ++ " acquired " ++ show i ++ " in " ++ showDuration offset
Action $ modifyRW $ \s -> s{localDiscount = localDiscount s + offset}
act
liftIO $ releaseResource r globalPool i
liftIO $ globalDiagnostic $ return $ show r ++ " released " ++ show i
Action $ either throwRAW return res
withResources :: [(Resource, Int)] -> Action a -> Action a
withResources res act
| (r,i):_ <- filter ((< 0) . snd) res = error $ "You cannot acquire a negative quantity of " ++ show r ++ ", requested " ++ show i
| otherwise = f $ groupBy ((==) `on` fst) $ sortBy (compare `on` fst) res
where
f [] = act
f (r:rs) = withResource (fst $ head r) (sum $ map snd r) $ f rs
newCacheIO :: (Eq k, Hashable k) => (k -> Action v) -> IO (k -> Action v)
newCacheIO act = do
var <- newVar Map.empty
return $ \key ->
join $ liftIO $ modifyVar var $ \mp -> case Map.lookup key mp of
Just bar -> return $ (,) mp $ do
res <- liftIO $ testFence bar
(res,offset) <- case res of
Just res -> return (res, 0)
Nothing -> do
pool <- Action $ getsRO globalPool
offset <- liftIO offsetTime
Action $ captureRAW $ \k -> waitFence bar $ \v ->
addPoolMediumPriority pool $ do offset <- liftIO offset; k $ Right (v,offset)
case res of
Left err -> Action $ throwRAW err
Right (deps,v) -> do
Action $ modifyRW $ \s -> s{localDepends = deps ++ localDepends s, localDiscount = localDiscount s + offset}
return v
Nothing -> do
bar <- newFence
return $ (,) (Map.insert key bar mp) $ do
pre <- Action $ getsRW localDepends
res <- Action $ tryRAW $ fromAction $ act key
case res of
Left err -> do
liftIO $ signalFence bar $ Left err
Action $ throwRAW err
Right v -> do
post <- Action $ getsRW localDepends
let deps = take (length post length pre) post
liftIO $ signalFence bar $ Right (deps, v)
return v
newCache :: (Eq k, Hashable k) => (k -> Action v) -> Rules (k -> Action v)
newCache = liftIO . newCacheIO
unsafeExtraThread :: Action a -> Action a
unsafeExtraThread act = Action $ do
Global{..} <- getRO
stop <- liftIO $ increasePool globalPool
res <- tryRAW $ fromAction $ blockApply "Within unsafeExtraThread" act
liftIO stop
captureRAW $ \continue -> (if isLeft res then addPoolHighPriority else addPoolMediumPriority) globalPool $ continue res
parallel :: [Action a] -> Action [a]
parallel [] = return []
parallel [x] = fmap return x
parallel acts = Action $ do
global@Global{..} <- getRO
local <- getRW
todo :: Var (Maybe Int) <- liftIO $ newVar $ Just $ length acts
results :: [IORef (Maybe (Either SomeException (Local, a)))] <- liftIO $ replicateM (length acts) $ newIORef Nothing
(locals, results) <- captureRAW $ \continue -> do
let resume = do
res <- liftIO $ sequence . catMaybes <$> mapM readIORef results
continue $ fmap unzip res
liftIO $ forM_ (zip acts results) $ \(act, result) -> do
let act2 = do
whenM (liftIO $ isNothing <$> readVar todo) $
fail "parallel, one has already failed"
res <- act
old <- Action getRW
return (old, res)
addPoolMediumPriority globalPool $ runAction global local act2 $ \res -> do
writeIORef result $ Just res
modifyVar_ todo $ \v -> case v of
Nothing -> return Nothing
Just i | i == 1 || isLeft res -> do resume; return Nothing
Just i -> return $ Just $ i 1
modifyRW $ \root -> Local
{localStack = localStack root
,localVerbosity = localVerbosity root
,localBlockApply = localBlockApply root
,localDepends = localDepends root ++ concatMap localDepends locals
,localDiscount = localDiscount root + maximum (0:map localDiscount locals)
,localTraces = localTraces root ++ concatMap localTraces locals
,localTrackAllows = localTrackAllows root ++ concatMap localTrackAllows locals
,localTrackUsed = localTrackUsed root ++ concatMap localTrackUsed locals
}
return results
orderOnlyAction :: Action a -> Action a
orderOnlyAction act = Action $ do
pre <- getsRW localDepends
res <- fromAction act
modifyRW $ \s -> s{localDepends=pre}
return res