module Standard( standard, fast ) where import System.FilePath import Shellish import Benchmark hiding ( darcs ) import Control.Monad( forM_, mapM_, forM, filterM, when ) import Control.Monad.Trans( liftIO ) import qualified Control.Monad.State as MS check :: BenchmarkCmd () check darcs _ = do cd "repo" darcs [ "check", "--no-test" ] return () repair :: BenchmarkCmd () repair darcs _ = do cd "repo" darcs [ "repair" ] return () annotate :: BenchmarkCmd () annotate darcs tr = do cd "repo" whenM ((not . or) `fmap` mapM test_e files) $ fail "no files to annotate" sequence [ whenM (test_e f) $ (darcs [ "annotate", f ] >> return ()) | f <- files ] return () where files = maybe id (:) (trAnnotate tr) [ "Setup.hs", "Setup.lhs" ] get :: [String] -> BenchmarkCmd () get param darcs _ = do darcs $ "get" : param ++ ["repo", "get"] return () pull :: Int -> BenchmarkCmd () pull n darcs _ = do cd "repo" rm_f "_darcs/patches/unrevert" darcs [ "unpull", "--last", show n, "--all" ] reset -- the benchmark starts here darcs [ "pull", "--all" ] return () -- Oh my eyes! Oh noes! Horrible! darcs_wh :: [String] -> BenchmarkCmd () darcs_wh param darcs _ = do state <- MS.get newstate <- liftIO $ catch (MS.execStateT (darcs $ "whatsnew" : param) state) (\_ -> return state) MS.put newstate wh :: BenchmarkCmd () wh darcs tr = do cd "repo" darcs_wh [] darcs tr return () wh_mod :: BenchmarkCmd () wh_mod darcs tr = do cd "repo" files <- filterM test_f =<< ls "." when (null files) $ fail "no files to modify in repo root!" forM files $ \f -> mv f $ f <.> "__foo__" darcs_wh [] darcs tr forM files $ \f -> mv (f <.> "__foo__") f return () wh_l :: BenchmarkCmd () wh_l darcs tr = do cd "repo" darcs_wh [ "--look-for-adds" ] darcs tr return () -- | n patches for each file record_mod :: BenchmarkCmd () record_mod darcs _ = do cd "repo" files <- filterM test_f =<< ls "." forM_ files $ \f -> liftIO (appendFile f "x") darcs [ "record", "-A", "me", "--all", "-m", "test record", "--no-test"] darcs [ "obliterate", "--last=1", "--all" ] return () revert_mod :: BenchmarkCmd () revert_mod darcs _ = do cd "repo" files <- filterM test_f =<< ls "." forM_ files $ \f -> liftIO (appendFile f "foo") darcs [ "revert", "--all" ] return () revert_unrevert :: BenchmarkCmd () revert_unrevert darcs _ = do cd "repo" files <- filterM test_f =<< ls "." forM_ files $ \f -> liftIO (appendFile f (show "foo")) darcs [ "revert", "--all" ] darcs [ "unrevert", "--all" ] darcs [ "revert", "--all" ] return () fast :: [ Benchmark () ] fast = [ Destructive Seconds "get (full)" $ get [] , Destructive Seconds "get (lazy)" $ get ["--lazy"] , Idempotent Seconds "pull 100" $ pull 100 , Idempotent MilliSeconds "wh" wh , Idempotent MilliSeconds "wh mod" wh_mod , Idempotent MilliSeconds "wh -l" wh_l , Idempotent MilliSeconds "record mod" $ record_mod , Idempotent MilliSeconds "revert mod" revert_mod , Idempotent MilliSeconds "(un)revert mod" revert_unrevert ] standard :: [ Benchmark () ] standard = fast ++ [ Idempotent Seconds "check" check , Idempotent Seconds "repair" repair , Idempotent Seconds "annotate" annotate , Idempotent Seconds "pull 1000" $ pull 1000 ]