-- Using code from http://hackage.haskell.org/package/benchpress module Main where import System.CPUTime (getCPUTime) import Data.Time.Clock (getCurrentTime, diffUTCTime, NominalDiffTime) import System.Environment (getArgs) import System.Cmd (system) import Text.Printf main :: IO () main = do args <- getArgs case args of [] -> putStrLn "Usage: htime \"command line command\" (between quotes)" l -> run (system (unwords l)) >>= printStats return () run :: IO a -> IO (Double, Double) run t = do startWall <- getCurrentTime startCpu <- getCPUTime _ <- t endCpu <- getCPUTime endWall <- getCurrentTime return ( picosToMillis $! endCpu - startCpu , secsToMillis $! endWall `diffUTCTime` startWall) printStats :: (Double, Double) -> IO () printStats = putStrLn . showStats showStats :: (Double, Double) -> String showStats (cpu, wall) = "\nCPU\t" ++ show cpu ++ "\nWall\t" ++ show wall ++ " ms. " ++ showReadableStats wall -- show millisecond data in a more readable way showReadableStats :: Double -> String showReadableStats wall | wall > 3600000 = let hours = floor (wall / 3600000) :: Int mins = round ((wall - ((fromIntegral hours)*3600000)) / 60000) :: Int in printf "\nWall\t%d:%d hours" hours mins | wall > 60000 = printf "\nWall\t%.3f min." (wall / 60000) | wall > 1000 = printf "\nWall\t%.2f sec." (wall / 1000) | otherwise = "" -- | Converts picoseconds to milliseconds. picosToMillis :: Integer -> Double picosToMillis t = realToFrac t / (10^(9 :: Int)) -- | Converts seconds to milliseconds. secsToMillis :: NominalDiffTime -> Double secsToMillis t = realToFrac t * (10^(3 :: Int))