{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP, OverloadedStrings #-}
module Criterion.IO
(
header
, headerRoot
, critVersion
, hGetRecords
, hPutRecords
, readRecords
, writeRecords
, ReportFileContents
, readJSONReports
, writeJSONReports
) where
import qualified Data.Aeson as Aeson
import Data.Binary (Binary(..), encode)
#if MIN_VERSION_binary(0, 6, 3)
import Data.Binary.Get (runGetOrFail)
#else
import Data.Binary.Get (runGetState)
#endif
import Data.Binary.Put (putByteString, putWord16be, runPut)
import qualified Data.ByteString.Char8 as B
import Criterion.Types (Report(..))
import Data.List (intercalate)
import Data.Version (Version(..))
import Paths_criterion (version)
import System.IO (Handle, IOMode(..), withFile, hPutStrLn, stderr)
import qualified Data.ByteString.Lazy as L
header :: L.ByteString
header = runPut $ do
putByteString (B.pack headerRoot)
mapM_ (putWord16be . fromIntegral) (versionBranch version)
headerRoot :: String
headerRoot = "criterion"
critVersion :: String
critVersion = intercalate "." $ map show $ versionBranch version
hGetRecords :: Binary a => Handle -> IO (Either String [a])
hGetRecords handle = do
bs <- L.hGet handle (fromIntegral (L.length header))
if bs == header
then Right `fmap` readAll handle
else return $ Left $ "unexpected header, expected criterion version: "++show (versionBranch version)
hPutRecords :: Binary a => Handle -> [a] -> IO ()
hPutRecords handle rs = do
L.hPut handle header
mapM_ (L.hPut handle . encode) rs
readRecords :: Binary a => FilePath -> IO (Either String [a])
readRecords path = withFile path ReadMode hGetRecords
writeRecords :: Binary a => FilePath -> [a] -> IO ()
writeRecords path rs = withFile path WriteMode (flip hPutRecords rs)
#if MIN_VERSION_binary(0, 6, 3)
readAll :: Binary a => Handle -> IO [a]
readAll handle = do
let go bs
| L.null bs = return []
| otherwise = case runGetOrFail get bs of
Left (_, _, err) -> fail err
Right (bs', _, a) -> (a:) `fmap` go bs'
go =<< L.hGetContents handle
#else
readAll :: Binary a => Handle -> IO [a]
readAll handle = do
let go i bs
| L.null bs = return []
| otherwise =
let (a, bs', i') = runGetState get bs i
in (a:) `fmap` go i' bs'
go 0 =<< L.hGetContents handle
#endif
type ReportFileContents = (String,String,[Report])
readJSONReports :: FilePath -> IO (Either String ReportFileContents)
readJSONReports path =
do bstr <- L.readFile path
let res = Aeson.eitherDecode bstr
case res of
Left _ -> return res
Right (tg,vers,_)
| tg == headerRoot && vers == critVersion -> return res
| otherwise ->
do hPutStrLn stderr $ "Warning, readJSONReports: mismatched header, expected "
++ show (headerRoot,critVersion) ++ " received " ++ show (tg,vers)
return res
writeJSONReports :: FilePath -> [Report] -> IO ()
writeJSONReports fn rs =
let payload :: ReportFileContents
payload = (headerRoot, critVersion, rs)
in L.writeFile fn $ Aeson.encode payload