1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255 256 257 258 259 260 261 262 263 264 265 266 267 268 269 270 271 272 273 274 275 276 277
|
{-# LANGUAGE DeriveDataTypeable, RecordWildCards, CPP, ForeignFunctionInterface, ScopedTypeVariables #-}
-- | Progress tracking
module Development.Shake.Progress(
Progress(..),
progressSimple, progressDisplay, progressTitlebar, progressProgram,
progressDisplayTester -- INTERNAL FOR TESTING ONLY
) where
import Control.Applicative
import Control.Concurrent
import Control.Exception
import Control.Monad
import System.Environment
import System.Directory
import System.Process
import Data.Char
import Data.Data
import Data.IORef
import Data.List
import Data.Maybe
import Data.Monoid
import qualified Data.ByteString.Char8 as BS
import General.Base
import System.IO.Unsafe
#ifdef mingw32_HOST_OS
import Foreign
import Foreign.C.Types
type LPCSTR = Ptr CChar
foreign import stdcall "Windows.h SetConsoleTitleA" c_setConsoleTitle :: LPCSTR -> IO Bool
#endif
---------------------------------------------------------------------
-- PROGRESS TYPES - exposed to the user
-- | Information about the current state of the build, obtained by passing a callback function
-- to 'Development.Shake.shakeProgress'. Typically a program will use 'progressDisplay' to poll this value and produce
-- status messages, which is implemented using this data type.
data Progress = Progress
{isFailure :: !(Maybe String) -- ^ Starts out 'Nothing', becomes 'Just' a target name if a rule fails.
,countSkipped :: {-# UNPACK #-} !Int -- ^ Number of rules which were required, but were already in a valid state.
,countBuilt :: {-# UNPACK #-} !Int -- ^ Number of rules which were have been built in this run.
,countUnknown :: {-# UNPACK #-} !Int -- ^ Number of rules which have been built previously, but are not yet known to be required.
,countTodo :: {-# UNPACK #-} !Int -- ^ Number of rules which are currently required (ignoring dependencies that do not change), but not built.
,timeSkipped :: {-# UNPACK #-} !Double -- ^ Time spent building 'countSkipped' rules in previous runs.
,timeBuilt :: {-# UNPACK #-} !Double -- ^ Time spent building 'countBuilt' rules.
,timeUnknown :: {-# UNPACK #-} !Double -- ^ Time spent building 'countUnknown' rules in previous runs.
,timeTodo :: {-# UNPACK #-} !(Double,Int) -- ^ Time spent building 'countTodo' rules in previous runs, plus the number which have no known time (have never been built before).
}
deriving (Eq,Ord,Show,Data,Typeable)
instance Monoid Progress where
mempty = Progress Nothing 0 0 0 0 0 0 0 (0,0)
mappend a b = Progress
{isFailure = isFailure a `mplus` isFailure b
,countSkipped = countSkipped a + countSkipped b
,countBuilt = countBuilt a + countBuilt b
,countUnknown = countUnknown a + countUnknown b
,countTodo = countTodo a + countTodo b
,timeSkipped = timeSkipped a + timeSkipped b
,timeBuilt = timeBuilt a + timeBuilt b
,timeUnknown = timeUnknown a + timeUnknown b
,timeTodo = let (a1,a2) = timeTodo a; (b1,b2) = timeTodo b
x1 = a1 + b1; x2 = a2 + b2
in x1 `seq` x2 `seq` (x1,x2)
}
---------------------------------------------------------------------
-- MEALY TYPE - for writing the progress functions
-- See <http://hackage.haskell.org/package/machines-0.2.3.1/docs/Data-Machine-Mealy.html>
-- | A machine that takes inputs and produces outputs
newtype Mealy i a = Mealy {runMealy :: i -> (a, Mealy i a)}
instance Functor (Mealy i) where
fmap f (Mealy m) = Mealy $ \i -> case m i of
(x, m) -> (f x, fmap f m)
instance Applicative (Mealy i) where
pure x = let r = Mealy (const (x, r)) in r
Mealy mf <*> Mealy mx = Mealy $ \i -> case mf i of
(f, mf) -> case mx i of
(x, mx) -> (f x, mf <*> mx)
echoMealy :: Mealy i i
echoMealy = Mealy $ \i -> (i, echoMealy)
scanMealy :: (a -> b -> a) -> a -> Mealy i b -> Mealy i a
scanMealy f z (Mealy m) = Mealy $ \i -> case m i of
(x, m) -> let z2 = f z x in (z2, scanMealy f z2 m)
---------------------------------------------------------------------
-- MEALY UTILITIES
oldMealy :: a -> Mealy i a -> Mealy i (a,a)
oldMealy old = scanMealy (\(_,old) new -> (old,new)) (old,old)
latch :: Mealy i (Bool, a) -> Mealy i a
latch s = fromJust <$> scanMealy f Nothing s
where f old (b,v) = Just $ if b then fromMaybe v old else v
iff :: Mealy i Bool -> Mealy i a -> Mealy i a -> Mealy i a
iff c t f = (\c t f -> if c then t else f) <$> c <*> t <*> f
posMealy :: Mealy i Int
posMealy = scanMealy (+) 0 $ pure 1
-- decay'd division, compute a/b, with a decay of f
-- r' is the new result, r is the last result
-- r ~= a / b
-- r' = r*b + f*(a'-a)
-- -------------
-- b + f*(b'-b)
-- when f == 1, r == r'
--
-- both streams must only ever increase
decay :: Double -> Mealy i Double -> Mealy i Double -> Mealy i Double
decay f a b = scanMealy step 0 $ (,) <$> oldMealy 0 a <*> oldMealy 0 b
where step r ((a,a'),(b,b')) =((r*b) + f*(a'-a)) / (b + f*(b'-b))
fromInt :: Int -> Double
fromInt = fromInteger . toInteger
---------------------------------------------------------------------
-- MESSAGE GENERATOR
message :: Double -> Mealy Progress Progress -> Mealy Progress String
message sample progress = (\time perc -> time ++ " (" ++ perc ++ "%)") <$> time <*> perc
where
-- Number of seconds work completed in this build run
-- Ignores timeSkipped which would be more truthful, but it makes the % drop sharply
-- which isn't what users want
done = timeBuilt <$> progress
-- Work done per second, don't divide by 0 and don't update if 'done' doesn't change
donePerSec = iff ((==) 0 <$> done) (pure 1) perSecStable
where perSecStable = latch $ liftA2 (,) (uncurry (==) <$> oldMealy 0 done) perSecRaw
perSecRaw = decay 1.2 done secs
secs = ((*) sample . fromInt) <$> posMealy
-- Predicted build time for a rule that has never been built before
-- The high decay means if a build goes in "phases" - lots of source files, then lots of compiling
-- we reach a reasonable number fairly quickly, without bouncing too much
ruleTime = liftA2 weightedAverage
(f (decay 10) timeBuilt countBuilt)
(f (liftA2 (/)) (fst . timeTodo) (\Progress{..} -> countTodo - snd timeTodo))
-- don't call decay on todo, since it goes up and down (as things get done)
where
weightedAverage (w1,x1) (w2,x2)
| w1 == 0 && w2 == 0 = 0
| otherwise = ((fromInt w1 * x1) + (fromInt w2 * x2)) / fromInt (w1+w2)
f divide time count = let xs = count <$> progress in liftA2 (,) xs $ divide (time <$> progress) (fromInt <$> xs)
-- Number of seconds work remaining, ignoring multiple threads
todo = f <$> progress <*> ruleTime
where f Progress{..} ruleTime = fst timeTodo + (fromIntegral (snd timeTodo) * ruleTime)
-- Display information
time = flip fmap (liftA2 (/) todo donePerSec) $ \guess ->
let (mins,secs) = divMod (ceiling guess) (60 :: Int)
in (if mins == 0 then "" else show mins ++ "m" ++ ['0' | secs < 10]) ++ show secs ++ "s"
perc = iff ((==) 0 <$> done) (pure "0") $
liftA2' done todo $ \done todo -> show (floor (100 * done / (done + todo)) :: Int)
---------------------------------------------------------------------
-- EXPOSED FUNCTIONS
-- | Given a sampling interval (in seconds) and a way to display the status message,
-- produce a function suitable for using as 'Development.Shake.shakeProgress'.
-- This function polls the progress information every /n/ seconds, produces a status
-- message and displays it using the display function.
--
-- Typical status messages will take the form of @1m25s (15%)@, indicating that the build
-- is predicted to complete in 1 minute 25 seconds (85 seconds total), and 15% of the necessary build time has elapsed.
-- This function uses past observations to predict future behaviour, and as such, is only
-- guessing. The time is likely to go up as well as down, and will be less accurate from a
-- clean build (as the system has fewer past observations).
--
-- The current implementation is to predict the time remaining (based on 'timeTodo') and the
-- work already done ('timeBuilt'). The percentage is then calculated as @remaining / (done + remaining)@,
-- while time left is calculated by scaling @remaining@ by the observed work rate in this build,
-- roughly @done / time_elapsed@.
progressDisplay :: Double -> (String -> IO ()) -> IO Progress -> IO ()
progressDisplay = progressDisplayer True
-- | Version of 'progressDisplay' that omits the sleep
progressDisplayTester :: Double -> (String -> IO ()) -> IO Progress -> IO ()
progressDisplayTester = progressDisplayer False
progressDisplayer :: Bool -> Double -> (String -> IO ()) -> IO Progress -> IO ()
progressDisplayer sleep sample disp prog = do
disp "Starting..." -- no useful info at this stage
catchJust (\x -> if x == ThreadKilled then Just () else Nothing) (loop $ message sample echoMealy) (const $ disp "Finished")
where
loop :: Mealy Progress String -> IO ()
loop mealy = do
when sleep $ threadDelay $ ceiling $ sample * 1000000
p <- prog
(msg, mealy) <- return $ runMealy mealy p
disp $ msg ++ maybe "" (\err -> ", Failure! " ++ err) (isFailure p)
loop mealy
{-# NOINLINE xterm #-}
xterm :: Bool
xterm = System.IO.Unsafe.unsafePerformIO $
-- Terminal.app uses "xterm-256color" as its env variable
Control.Exception.catch (fmap ("xterm" `isPrefixOf`) $ getEnv "TERM") $
\(e :: SomeException) -> return False
-- | Set the title of the current console window to the given text. If the
-- environment variable @$TERM@ is set to @xterm@ this uses xterm escape sequences.
-- On Windows, if not detected as an xterm, this function uses the @SetConsoleTitle@ API.
progressTitlebar :: String -> IO ()
progressTitlebar x
| xterm = BS.putStr $ BS.pack $ "\ESC]0;" ++ x ++ "\BEL"
#ifdef mingw32_HOST_OS
| otherwise = BS.useAsCString (BS.pack x) $ \x -> c_setConsoleTitle x >> return ()
#else
| otherwise = return ()
#endif
-- | Call the program @shake-progress@ if it is on the @$PATH@. The program is called with
-- the following arguments:
--
-- * @--title=string@ - the string passed to @progressProgram@.
--
-- * @--state=Normal@, or one of @NoProgress@, @Normal@, or @Error@ to indicate
-- what state the progress bar should be in.
--
-- * @--value=25@ - the percent of the build that has completed, if not in @NoProgress@ state.
--
-- The program will not be called consecutively with the same @--state@ and @--value@ options.
--
-- Windows 7 or higher users can get taskbar progress notifications by placing the following
-- program in their @$PATH@: <https://github.com/ndmitchell/shake/releases>.
progressProgram :: IO (String -> IO ())
progressProgram = do
exe <- findExecutable "shake-progress"
case exe of
Nothing -> return $ const $ return ()
Just exe -> do
ref <- newIORef Nothing
return $ \msg -> do
let failure = " Failure! " `isInfixOf` msg
let perc = let (a,b) = break (== '%') msg
in if null b then "" else reverse $ takeWhile isDigit $ reverse a
let key = (failure, perc)
same <- atomicModifyIORef ref $ \old -> (Just key, old == Just key)
let state = if perc == "" then "NoProgress" else if failure then "Error" else "Normal"
rawSystem exe $ ["--title=" ++ msg, "--state=" ++ state] ++ ["--value=" ++ perc | perc /= ""]
return ()
-- | A simple method for displaying progress messages, suitable for using as 'Development.Shake.shakeProgress'.
-- This function writes the current progress to the titlebar every five seconds using 'progressTitlebar',
-- and calls any @shake-progress@ program on the @$PATH@ using 'progressProgram'.
progressSimple :: IO Progress -> IO ()
progressSimple p = do
program <- progressProgram
progressDisplay 5 (\s -> progressTitlebar s >> program s) p
|