module Development.Shake.Progress(
Progress(..),
progressSimple, progressDisplay, progressTitlebar, progressProgram,
ProgressEntry(..), progressReplay, writeProgressReport
) where
import Control.Applicative
import Data.Tuple.Extra
import Control.Exception.Extra
import Control.Monad
import System.Environment
import System.Directory
import System.Process
import System.FilePath
import Data.Char
import Data.Data
import Data.IORef
import Data.List
import Data.Maybe
import Data.Version
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as LBS
import Numeric.Extra
import General.Template
import System.IO.Unsafe
import Paths_shake
import System.Time.Extra
import Data.Monoid
import Prelude
#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
data Progress = Progress
{isFailure :: !(Maybe String)
,countSkipped :: !Int
,countBuilt :: !Int
,countUnknown :: !Int
,countTodo :: !Int
,timeSkipped :: !Double
,timeBuilt :: !Double
,timeUnknown :: !Double
,timeTodo :: !(Double,Int)
}
deriving (Eq,Ord,Show,Read,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)
}
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)
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
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))
formatMessage :: Double -> Double -> String
formatMessage secs perc =
(if isNaN secs || secs < 0 then "??s" else showMinSec $ ceiling secs) ++ " (" ++
(if isNaN perc || perc < 0 || perc > 100 then "??" else show $ floor perc) ++ "%)"
showMinSec :: Int -> String
showMinSec secs = (if m == 0 then "" else show m ++ "m" ++ ['0' | s < 10]) ++ show s ++ "s"
where (m,s) = divMod secs 60
liftA2' :: Applicative m => m a -> m b -> (a -> b -> c) -> m c
liftA2' a b f = liftA2 f a b
message :: Mealy (Double, Progress) (Double, Progress) -> Mealy (Double, Progress) (Double, Double, String)
message input = liftA3 (,,) time perc debug
where
progress = snd <$> input
secs = fst <$> input
debug = (\donePerSec ruleTime (todoKnown,todoUnknown) ->
"Progress: " ++
"((known=" ++ showDP 2 todoKnown ++ "s) + " ++
"(unknown=" ++ show todoUnknown ++ " * time=" ++ showDP 2 ruleTime ++ "s)) " ++
"(rate=" ++ showDP 2 donePerSec ++ "))")
<$> donePerSec <*> ruleTime <*> (timeTodo <$> progress)
done = timeBuilt <$> progress
donePerSec = iff ((==) 0 <$> done) (pure 1) perSecStable
where perSecStable = latch $ liftA2 (,) (uncurry (==) <$> oldMealy 0 done) perSecRaw
perSecRaw = decay 1.2 done secs
ruleTime = liftA2 weightedAverage
(f (decay 10) timeBuilt countBuilt)
(f (liftA2 (/)) (fst . timeTodo) (\Progress{..} -> countTodo snd timeTodo))
where
weightedAverage (w1,x1) (w2,x2)
| w1 == 0 && w2 == 0 = 0
| otherwise = ((w1 *. x1) + (w2 *. x2)) / intToDouble (w1+w2)
where i *. d = if i == 0 then 0 else intToDouble i * d
f divide time count = let xs = count <$> progress in liftA2 (,) xs $ divide (time <$> progress) (intToDouble <$> xs)
todo = f <$> progress <*> ruleTime
where f Progress{..} ruleTime = fst timeTodo + (fromIntegral (snd timeTodo) * ruleTime)
time = liftA2 (/) todo donePerSec
perc = iff ((==) 0 <$> done) (pure 0) $
liftA2' done todo $ \done todo -> 100 * done / (done + todo)
progressDisplay :: Double -> (String -> IO ()) -> IO Progress -> IO ()
progressDisplay sample disp prog = do
disp "Starting..."
time <- offsetTime
catchJust (\x -> if x == ThreadKilled then Just () else Nothing) (loop time $ message echoMealy) (const $ disp "Finished")
where
loop :: IO Double -> Mealy (Double, Progress) (Double, Double, String) -> IO ()
loop time mealy = do
sleep sample
p <- prog
t <- time
((secs,perc,debug), mealy) <- return $ runMealy mealy (t, p)
disp $ formatMessage secs perc ++ maybe "" (\err -> ", Failure! " ++ err) (isFailure p)
loop time mealy
data ProgressEntry = ProgressEntry
{idealSecs :: Double, idealPerc :: Double
,actualSecs :: Double, actualPerc :: Double
}
progressReplay :: [(Double, Progress)] -> [ProgressEntry]
progressReplay [] = []
progressReplay ps = snd $ mapAccumL f (message echoMealy) ps
where
end = fst $ last ps
f a (time,p) = (a2, ProgressEntry (end time) (time * 100 / end) secs perc)
where ((secs,perc,_),a2) = runMealy a (time,p)
writeProgressReport :: FilePath -> [(FilePath, [(Double, Progress)])] -> IO ()
writeProgressReport out (map (second progressReplay) -> xs)
| takeExtension out == ".js" = writeFile out $ "var shake = \n" ++ generateJSON xs
| takeExtension out == ".json" = writeFile out $ generateJSON xs
| out == "-" = putStr $ unlines $ generateSummary xs
| otherwise = LBS.writeFile out =<< generateHTML xs
generateSummary :: [(FilePath, [ProgressEntry])] -> [String]
generateSummary xs = flip concatMap xs $ \(file,xs) ->
["# " ++ file, f xs "Seconds" idealSecs actualSecs, f xs "Percent" idealPerc actualPerc]
where
levels = [100,90,80,50]
f xs lbl ideal actual = lbl ++ ": " ++ intercalate ", "
[show l ++ "% within " ++ show (ceiling $ maximum $ 0 : take ((length xs * l) `div` 100) diff) | l <- levels]
where diff = sort [abs $ ideal x actual x | x <- xs]
generateHTML :: [(FilePath, [ProgressEntry])] -> IO LBS.ByteString
generateHTML xs = do
htmlDir <- getDataFileName "html"
report <- LBS.readFile $ htmlDir </> "progress.html"
let f name | name == "progress-data.js" = return $ LBS.pack $ "var shake =\n" ++ generateJSON xs
| name == "version.js" = return $ LBS.pack $ "var version = " ++ show (showVersion version)
| otherwise = LBS.readFile $ htmlDir </> name
runTemplate f report
generateJSON :: [(FilePath, [ProgressEntry])] -> String
generateJSON = concat . jsonList . map ((++"}") . unlines . f)
where
f (file,ps) =
("{\"name\":" ++ show (takeFileName file) ++ ", \"values\":") :
indent (jsonList $ map g ps)
shw = showDP 1
g ProgressEntry{..} = jsonObject
[("idealSecs",shw idealSecs),("idealPerc",shw idealPerc)
,("actualSecs",shw actualSecs),("actualPerc",shw actualPerc)]
indent = map (" "++)
jsonList xs = zipWith (:) ('[':repeat ',') xs ++ ["]"]
jsonObject xs = "{" ++ intercalate ", " [show a ++ ":" ++ b | (a,b) <- xs] ++ "}"
xterm :: Bool
xterm = System.IO.Unsafe.unsafePerformIO $
catch_ (fmap ("xterm" `isPrefixOf`) $ getEnv "TERM") $
\e -> return False
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
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 ()
progressSimple :: IO Progress -> IO ()
progressSimple p = do
program <- progressProgram
progressDisplay 5 (\s -> progressTitlebar s >> program s) p