{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE StandaloneDeriving #-} module Test.Hspec.Dirstream ( -- Functions to generate a `Spec` testFiles , testFilesIO , testFilesErr , testFilesPredicate -- * Helper functions for dealing with file extensions , F.extension , Test.Hspec.Dirstream.hasExtension ) where import Data.DirStream import Data.Text (Text) import qualified Filesystem.Path.CurrentOS as F import Pipes import qualified Pipes.Prelude as P import Pipes.Safe import System.FilePath import Test.Hspec import Test.Hspec.Core.Spec deriving instance MonadCatch (SpecM a) deriving instance MonadThrow (SpecM a) deriving instance MonadMask (SpecM a) deriving instance MonadIO (SpecM a) hasExtension :: Text -> F.FilePath -> Bool hasExtension = flip F.hasExtension mapS :: (a -> SpecM () ()) -> Proxy () a y' y (SafeT (SpecM ())) r mapS = P.mapM_ . (lift .) paths :: MonadSafe m => String -> (F.FilePath -> Bool) -> Producer String m () paths dir p = every (childOf path) >-> P.filter p >-> P.map F.encodeString where path = F.decodeString dir -- | Helper function to generate a spec. The spec runs on the given directory, -- filtering by the given function. It then compares their output to the text of -- the file with @.out@ as the new extension. -- -- As an example, consider the directory structure -- -- > test/data -- > ├── file.hs -- > └── file.out -- -- If we have a function called @formatFile@ and we run -- -- > testFiles "test/data" (hasExtension "hs") formatFile -- -- This would read @test\/data\/file.hs@, format the file if it can, and compare -- the output to the contents of @test\/data\/file.out@. testFiles :: (Eq a, Show a) => FilePath -- ^ Base directory -> (F.FilePath -> Bool) -- ^ Filter on file extensions -> (String -> Either a String) -- ^ Function to process a file -> SpecWith () testFiles dir p f = runSafeT $ runEffect $ paths dir p >-> mapS (testFile f) -- | A version of the above where the return value can be any 'IO'. testFilesIO :: FilePath -> (F.FilePath -> Bool) -> (String -> IO String) -> SpecWith () testFilesIO dir p f = runSafeT $ runEffect $ paths dir p >-> mapS (testFileIO f) -- | This function checks that each file returns a value satisfying the -- predicate. testFilesPredicate :: (Show a, Eq a) => FilePath -- ^ Directory containing test data -> (F.FilePath -> Bool) -- ^ Filter on file extensions -> (String -> a) -- ^ Function to process the string -> (a -> Bool) -- ^ Predicate to check the result -> SpecWith () testFilesPredicate dir p f pr = runSafeT $ runEffect $ paths dir p >-> mapS (testFilePredicate f pr) testFileIO :: (String -> IO String) -> String -> SpecWith () testFileIO fun f = it f $ do sample <- readFile f expected <- readFile (replaceExtension f ".out") fun sample >>= (`shouldBe` expected) -- | This function simply tests that each file returns a 'Left' value and that -- the error message contained therein matches the contents of the appropriate -- file. testFilesErr :: (Show b, Eq b) => FilePath -> (F.FilePath -> Bool) -> (String -> Either String b) -> SpecWith () testFilesErr dir p f = runSafeT $ runEffect $ paths dir p >-> mapS (testFileErr f) testFilePredicate :: (Eq a, Show a) => (String -> a) -> (a -> Bool) -> String -> SpecWith () testFilePredicate fun p f = it f $ do sample <- readFile f fun sample `shouldSatisfy` p testFileErr :: (Eq b, Show b) => (String -> Either String b) -> String -> SpecWith () testFileErr fun f = it f $ do sample <- readFile f expected <- readFile (replaceExtension f ".out") fun sample `shouldBe` Left expected testFile :: (Eq a, Show a) => (String -> Either a String) -> String -> SpecWith () testFile fun f = it f $ do sample <- readFile f expected <- readFile (replaceExtension f ".out") fun sample `shouldBe` Right expected