{-# LANGUAGE FlexibleContexts #-} import Criterion.Main (defaultMain, bgroup, nfIO, bench) import GHC.IO.Exception (IOException(..)) import Control.DeepSeq (NFData(..)) import Data.Either (Either(..)) import System.IO (FilePath) import qualified System.IO.ExceptionFree as ExceptionFree instance NFData IOException where rnf ex = rnf (show ex) -- | Filesizes used in the bench data FixtureSize = KB1 | KB10 | KB100 | MB1 | MB10 deriving (Read, Show, Enum, Bounded) -- | Type of read file data Method = Original | ExceptionFree deriving (Read, Show, Enum, Bounded) -- | Class to encapsulate how to run readfile class HasReadFileIO m where run :: m -> FilePath -> IO (Either IOError String) instance HasReadFileIO Method where run Original path = Right <$> readFile path run ExceptionFree path = ExceptionFree.readFile path -- | Build the path to a fixture file (from project root) buildFilePath :: FixtureSize -> FilePath buildFilePath fs = "bench/fixtures/example-" <> show fs <> ".txt" main = defaultMain [ bgroup "readFile" [ bench (show method <> "-" <> show fSize) (nfIO (run method $ buildFilePath fSize)) | fSize <- [minBound :: FixtureSize ..], method <- [minBound :: Method ..] ] ]