diff options
-rw-r--r-- | hakyll.cabal | 4 | ||||
-rw-r--r-- | src/Hakyll.hs | 4 | ||||
-rw-r--r-- | src/Hakyll/Commands.hs | 8 | ||||
-rw-r--r-- | src/Hakyll/Core/Compiler/Internal.hs | 5 | ||||
-rw-r--r-- | src/Hakyll/Core/Configuration.hs | 4 | ||||
-rw-r--r-- | src/Hakyll/Core/File.hs | 89 | ||||
-rw-r--r-- | src/Hakyll/Core/Runtime.hs | 7 | ||||
-rw-r--r-- | src/Hakyll/Core/Store.hs | 14 | ||||
-rw-r--r-- | src/Hakyll/Core/Util/File.hs | 13 | ||||
-rw-r--r-- | src/Hakyll/Core/Writable/CopyFile.hs | 43 | ||||
-rw-r--r-- | tests/Hakyll/Core/Provider/Tests.hs | 3 | ||||
-rw-r--r-- | tests/Hakyll/Core/Rules/Tests.hs | 5 | ||||
-rw-r--r-- | tests/Hakyll/Core/Runtime/Tests.hs | 11 | ||||
-rw-r--r-- | tests/Hakyll/Core/Store/Tests.hs | 7 | ||||
-rw-r--r-- | tests/Hakyll/Core/UnixFilter/Tests.hs | 4 | ||||
-rw-r--r-- | tests/Hakyll/Web/Template/Context/Tests.hs | 5 | ||||
-rw-r--r-- | tests/Hakyll/Web/Template/Tests.hs | 6 | ||||
-rw-r--r-- | tests/TestSuite/Util.hs | 56 |
18 files changed, 180 insertions, 108 deletions
diff --git a/hakyll.cabal b/hakyll.cabal index 4191a2a..1159e7b 100644 --- a/hakyll.cabal +++ b/hakyll.cabal @@ -106,6 +106,7 @@ Library pandoc >= 1.9.3 && < 1.10, parsec >= 3.0 && < 3.2, process >= 1.0 && < 1.2, + random >= 1.0 && < 1.1, regex-base >= 0.93 && < 0.94, regex-tdfa >= 1.1 && < 1.2, tagsoup >= 0.12.6 && < 0.13, @@ -117,6 +118,7 @@ Library Hakyll.Core.Compiler Hakyll.Core.Configuration Hakyll.Core.Dependencies + Hakyll.Core.File Hakyll.Core.Identifier Hakyll.Core.Identifier.Pattern Hakyll.Core.Item @@ -125,7 +127,6 @@ Library Hakyll.Core.Rules Hakyll.Core.Util.String Hakyll.Core.Writable - Hakyll.Core.Writable.CopyFile Hakyll.Main Hakyll.Web.CompressCss Hakyll.Web.Feed @@ -211,6 +212,7 @@ Test-suite hakyll-tests pandoc >= 1.9.3 && < 1.10, parsec >= 3.0 && < 3.2, process >= 1.0 && < 1.2, + random >= 1.0 && < 1.1, regex-base >= 0.93 && < 0.94, regex-tdfa >= 1.1 && < 1.2, tagsoup >= 0.12.6 && < 0.13, diff --git a/src/Hakyll.hs b/src/Hakyll.hs index 1131772..90b56f9 100644 --- a/src/Hakyll.hs +++ b/src/Hakyll.hs @@ -4,6 +4,7 @@ module Hakyll ( module Hakyll.Core.Compiler , module Hakyll.Core.Configuration + , module Hakyll.Core.File , module Hakyll.Core.Identifier , module Hakyll.Core.Identifier.Pattern , module Hakyll.Core.Item @@ -16,7 +17,6 @@ module Hakyll , module Hakyll.Core.Util.File , module Hakyll.Core.Util.String , module Hakyll.Core.Writable - , module Hakyll.Core.Writable.CopyFile , module Hakyll.Main , module Hakyll.Web.CompressCss , module Hakyll.Web.Feed @@ -36,6 +36,7 @@ module Hakyll -------------------------------------------------------------------------------- import Hakyll.Core.Compiler import Hakyll.Core.Configuration +import Hakyll.Core.File import Hakyll.Core.Identifier import Hakyll.Core.Identifier.Pattern import Hakyll.Core.Item @@ -48,7 +49,6 @@ import Hakyll.Core.UnixFilter import Hakyll.Core.Util.File import Hakyll.Core.Util.String import Hakyll.Core.Writable -import Hakyll.Core.Writable.CopyFile import Hakyll.Main import Hakyll.Web.CompressCss import Hakyll.Web.Feed diff --git a/src/Hakyll/Commands.hs b/src/Hakyll/Commands.hs index b7e85bc..61e40b8 100644 --- a/src/Hakyll/Commands.hs +++ b/src/Hakyll/Commands.hs @@ -13,9 +13,6 @@ module Hakyll.Commands -------------------------------------------------------------------------------- -import Control.Monad (when) -import System.Directory (doesDirectoryExist, - removeDirectoryRecursive) import System.Exit (exitWith) import System.Process (system) @@ -26,6 +23,7 @@ import Hakyll.Core.Configuration import Hakyll.Core.Logger (Verbosity) import Hakyll.Core.Rules import Hakyll.Core.Runtime +import Hakyll.Core.Util.File -------------------------------------------------------------------------------- @@ -59,11 +57,11 @@ clean :: Configuration -> IO () clean conf = do remove $ destinationDirectory conf remove $ storeDirectory conf + remove $ tmpDirectory conf where remove dir = do putStrLn $ "Removing " ++ dir ++ "..." - exists <- doesDirectoryExist dir - when exists $ removeDirectoryRecursive dir + removeDirectory dir -------------------------------------------------------------------------------- diff --git a/src/Hakyll/Core/Compiler/Internal.hs b/src/Hakyll/Core/Compiler/Internal.hs index 6e07602..be49e9f 100644 --- a/src/Hakyll/Core/Compiler/Internal.hs +++ b/src/Hakyll/Core/Compiler/Internal.hs @@ -34,6 +34,7 @@ import qualified Data.Set as S -------------------------------------------------------------------------------- +import Hakyll.Core.Configuration import Hakyll.Core.Dependencies import Hakyll.Core.Identifier import Hakyll.Core.Identifier.Pattern @@ -47,7 +48,9 @@ import Hakyll.Core.Store -------------------------------------------------------------------------------- -- | Environment in which a compiler runs data CompilerRead = CompilerRead - { -- | Underlying identifier + { -- | Main configuration + compilerConfig :: Configuration + , -- | Underlying identifier compilerUnderlying :: Identifier , -- | Resource provider compilerProvider :: Provider diff --git a/src/Hakyll/Core/Configuration.hs b/src/Hakyll/Core/Configuration.hs index 86898dc..47de700 100644 --- a/src/Hakyll/Core/Configuration.hs +++ b/src/Hakyll/Core/Configuration.hs @@ -18,6 +18,8 @@ data Configuration = Configuration destinationDirectory :: FilePath , -- | Directory where hakyll's internal store is kept storeDirectory :: FilePath + , -- | Directory in which some temporary files will be kept + tmpDirectory :: FilePath , -- | Directory where hakyll finds the files to compile. This is @.@ by -- default. providerDirectory :: FilePath @@ -61,6 +63,7 @@ defaultConfiguration :: Configuration defaultConfiguration = Configuration { destinationDirectory = "_site" , storeDirectory = "_cache" + , tmpDirectory = "_cache/tmp" , providerDirectory = "." , ignoreFile = ignoreFile' , deployCommand = "echo 'No deploy command specified'" @@ -83,6 +86,7 @@ shouldIgnoreFile :: Configuration -> FilePath -> Bool shouldIgnoreFile conf path = destinationDirectory conf `isPrefixOf` path' || storeDirectory conf `isPrefixOf` path' || + tmpDirectory conf `isPrefixOf` path' || ignoreFile conf path' where path' = normalise path diff --git a/src/Hakyll/Core/File.hs b/src/Hakyll/Core/File.hs new file mode 100644 index 0000000..a7b4a35 --- /dev/null +++ b/src/Hakyll/Core/File.hs @@ -0,0 +1,89 @@ +-------------------------------------------------------------------------------- +-- | Exports simple compilers to just copy files +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module Hakyll.Core.File + ( CopyFile (..) + , copyFileCompiler + , TmpFile (..) + , newTmpFile + ) where + + +-------------------------------------------------------------------------------- +import Control.Applicative ((<$>)) +import Data.Binary (Binary (..)) +import Data.Typeable (Typeable) +import System.Directory (copyFile, doesFileExist, + renameFile) +import System.FilePath ((</>)) +import System.Random (randomIO) + + +-------------------------------------------------------------------------------- +import Hakyll.Core.Compiler +import Hakyll.Core.Compiler.Internal +import Hakyll.Core.Configuration +import Hakyll.Core.Identifier +import Hakyll.Core.Item +import qualified Hakyll.Core.Store as Store +import Hakyll.Core.Util.File +import Hakyll.Core.Writable + + +-------------------------------------------------------------------------------- +-- | This will copy any file directly by using a system call +data CopyFile = CopyFile + deriving (Show, Eq, Ord, Typeable) + + +-------------------------------------------------------------------------------- +instance Binary CopyFile where + put CopyFile = return () + get = return CopyFile + + +-------------------------------------------------------------------------------- +instance Writable CopyFile where + write dst item = copyFile (toFilePath $ itemIdentifier item) dst + + +-------------------------------------------------------------------------------- +copyFileCompiler :: Compiler (Item CopyFile) +copyFileCompiler = makeItem CopyFile + + +-------------------------------------------------------------------------------- +newtype TmpFile = TmpFile FilePath + deriving (Typeable) + + +-------------------------------------------------------------------------------- +instance Binary TmpFile where + put _ = return () + get = error $ + "Hakyll.Core.File.TmpFile: You tried to load a TmpFile, however, " ++ + "this is not possible since these are deleted as soon as possible." + + +-------------------------------------------------------------------------------- +instance Writable TmpFile where + write dst (Item _ (TmpFile fp)) = renameFile fp dst + + +-------------------------------------------------------------------------------- +-- | Create a tmp file +newTmpFile :: String -- ^ Suffix and extension + -> Compiler TmpFile -- ^ Resulting tmp path +newTmpFile suffix = do + path <- mkPath + compilerUnsafeIO $ makeDirectories path + debugCompiler $ "newTmpFile " ++ path + return $ TmpFile path + where + mkPath = do + rand <- compilerUnsafeIO $ randomIO :: Compiler Int + tmp <- tmpDirectory . compilerConfig <$> compilerAsk + let path = tmp </> Store.hash [show rand] ++ "-" ++ suffix + exists <- compilerUnsafeIO $ doesFileExist path + if exists then mkPath else return path diff --git a/src/Hakyll/Core/Runtime.hs b/src/Hakyll/Core/Runtime.hs index e052f37..4755a6a 100644 --- a/src/Hakyll/Core/Runtime.hs +++ b/src/Hakyll/Core/Runtime.hs @@ -85,6 +85,10 @@ run config verbosity rules = do Right (_, s, _) -> do Store.set store factsKey $ runtimeFacts s + + Logger.debug logger "Removing tmp directory..." + removeDirectory $ tmpDirectory config + Logger.flush logger return ruleSet where @@ -180,7 +184,8 @@ chase trail id' let compiler = todo M.! id' read' = CompilerRead - { compilerUnderlying = id' + { compilerConfig = config + , compilerUnderlying = id' , compilerProvider = provider , compilerUniverse = M.keysSet universe , compilerRoutes = routes diff --git a/src/Hakyll/Core/Store.hs b/src/Hakyll/Core/Store.hs index 231da2a..63dd64c 100644 --- a/src/Hakyll/Core/Store.hs +++ b/src/Hakyll/Core/Store.hs @@ -9,6 +9,7 @@ module Hakyll.Core.Store , set , get , delete + , hash ) where @@ -144,12 +145,13 @@ delete store identifier = do -------------------------------------------------------------------------------- -hash :: [String] -> String -hash = concatMap (printf "%02x") . B.unpack . - MD5.hash . T.encodeUtf8 . T.pack . intercalate "/" - - --------------------------------------------------------------------------------- -- | Delete a file unless it doesn't exist... deleteFile :: FilePath -> IO () deleteFile = handle (\(_ :: IOException) -> return ()) . removeFile + + +-------------------------------------------------------------------------------- +-- | Mostly meant for internal usage +hash :: [String] -> String +hash = concatMap (printf "%02x") . B.unpack . + MD5.hash . T.encodeUtf8 . T.pack . intercalate "/" diff --git a/src/Hakyll/Core/Util/File.hs b/src/Hakyll/Core/Util/File.hs index 6d6b5c2..0e34d7c 100644 --- a/src/Hakyll/Core/Util/File.hs +++ b/src/Hakyll/Core/Util/File.hs @@ -3,14 +3,16 @@ module Hakyll.Core.Util.File ( makeDirectories , getRecursiveContents + , removeDirectory ) where -------------------------------------------------------------------------------- import Control.Applicative ((<$>)) -import Control.Monad (forM) +import Control.Monad (forM, when) import System.Directory (createDirectoryIfMissing, - doesDirectoryExist, getDirectoryContents) + doesDirectoryExist, getDirectoryContents, + removeDirectoryRecursive) import System.FilePath (takeDirectory, (</>)) @@ -42,3 +44,10 @@ getRecursiveContents top = go "" else return [rel] return $ concat paths + + +-------------------------------------------------------------------------------- +removeDirectory :: FilePath -> IO () +removeDirectory fp = do + e <- doesDirectoryExist fp + when e $ removeDirectoryRecursive fp diff --git a/src/Hakyll/Core/Writable/CopyFile.hs b/src/Hakyll/Core/Writable/CopyFile.hs deleted file mode 100644 index 58397ac..0000000 --- a/src/Hakyll/Core/Writable/CopyFile.hs +++ /dev/null @@ -1,43 +0,0 @@ --------------------------------------------------------------------------------- --- | Exports simple compilers to just copy files -{-# LANGUAGE DeriveDataTypeable #-} -{-# LANGUAGE GeneralizedNewtypeDeriving #-} -module Hakyll.Core.Writable.CopyFile - ( CopyFile (..) - , copyFileCompiler - ) where - - --------------------------------------------------------------------------------- -import Data.Binary (Binary (..)) -import Data.Typeable (Typeable) -import System.Directory (copyFile) - - --------------------------------------------------------------------------------- -import Hakyll.Core.Compiler -import Hakyll.Core.Identifier -import Hakyll.Core.Item -import Hakyll.Core.Writable - - --------------------------------------------------------------------------------- --- | This will copy any file directly by using a system call -data CopyFile = CopyFile - deriving (Show, Eq, Ord, Typeable) - - --------------------------------------------------------------------------------- -instance Binary CopyFile where - put CopyFile = return () - get = return CopyFile - - --------------------------------------------------------------------------------- -instance Writable CopyFile where - write dst item = copyFile (toFilePath $ itemIdentifier item) dst - - --------------------------------------------------------------------------------- -copyFileCompiler :: Compiler (Item CopyFile) -copyFileCompiler = makeItem CopyFile diff --git a/tests/Hakyll/Core/Provider/Tests.hs b/tests/Hakyll/Core/Provider/Tests.hs index e1f9083..5fd9c0d 100644 --- a/tests/Hakyll/Core/Provider/Tests.hs +++ b/tests/Hakyll/Core/Provider/Tests.hs @@ -26,7 +26,8 @@ tests = testGroup "Hakyll.Core.Provider.Tests" -------------------------------------------------------------------------------- case01 :: Assertion -case01 = withTestStore $ \store -> do +case01 = do + store <- newTestStore provider <- newTestProvider store assert $ resourceExists provider "example.md" diff --git a/tests/Hakyll/Core/Rules/Tests.hs b/tests/Hakyll/Core/Rules/Tests.hs index d6fec31..631e082 100644 --- a/tests/Hakyll/Core/Rules/Tests.hs +++ b/tests/Hakyll/Core/Rules/Tests.hs @@ -14,12 +14,12 @@ import Test.HUnit (Assertion, assert, (@=?)) -------------------------------------------------------------------------------- import Hakyll.Core.Compiler +import Hakyll.Core.File import Hakyll.Core.Identifier import Hakyll.Core.Identifier.Pattern import Hakyll.Core.Routes import Hakyll.Core.Rules import Hakyll.Core.Rules.Internal -import Hakyll.Core.Writable.CopyFile import Hakyll.Web.Pandoc import TestSuite.Util @@ -33,7 +33,8 @@ tests = testGroup "Hakyll.Core.Rules.Tests" -------------------------------------------------------------------------------- rulesTest :: Assertion -rulesTest = withTestStore $ \store -> do +rulesTest = do + store <- newTestStore provider <- newTestProvider store ruleSet <- runRules rules provider let identifiers = S.fromList $ map fst $ rulesCompilers ruleSet diff --git a/tests/Hakyll/Core/Runtime/Tests.hs b/tests/Hakyll/Core/Runtime/Tests.hs index 4b41bf5..c68d99e 100644 --- a/tests/Hakyll/Core/Runtime/Tests.hs +++ b/tests/Hakyll/Core/Runtime/Tests.hs @@ -25,8 +25,8 @@ tests = testGroup "Hakyll.Core.Runtime.Tests" $ fromAssertions "run" [case01] -------------------------------------------------------------------------------- case01 :: Assertion -case01 = withTestConfiguration $ \config -> do - _ <- run config Logger.Error $ do +case01 = do + _ <- run testConfiguration Logger.Error $ do match "*.md" $ do route $ setExtension "html" compile $ do @@ -40,8 +40,11 @@ case01 = withTestConfiguration $ \config -> do items <- loadAllSnapshots "*.md" "raw" makeItem $ concat $ map itemBody (items :: [Item String]) - example <- readFile $ destinationDirectory config </> "example.html" + example <- readFile $ + destinationDirectory testConfiguration </> "example.html" lines example @?= ["<p>This is an example.</p>"] - bodies <- readFile $ destinationDirectory config </> "bodies.txt" + bodies <- readFile $ destinationDirectory testConfiguration </> "bodies.txt" head (lines bodies) @?= "This is an example." + + cleanTestEnv diff --git a/tests/Hakyll/Core/Store/Tests.hs b/tests/Hakyll/Core/Store/Tests.hs index 11a1a63..19b268b 100644 --- a/tests/Hakyll/Core/Store/Tests.hs +++ b/tests/Hakyll/Core/Store/Tests.hs @@ -38,7 +38,7 @@ simpleSetGet = Q.monadicIO $ do Q.run $ Store.set store key (value :: String) value' <- Q.run $ Store.get store key Q.assert $ Store.Found value == value' - Q.run cleanTestStore + Q.run cleanTestEnv -------------------------------------------------------------------------------- @@ -52,12 +52,13 @@ persistentSetGet = Q.monadicIO $ do store2 <- Q.run newTestStore value' <- Q.run $ Store.get store2 key Q.assert $ Store.Found value == value' - Q.run cleanTestStore + Q.run cleanTestEnv -------------------------------------------------------------------------------- wrongType :: H.Assertion -wrongType = withTestStore $ \store -> do +wrongType = do + store <- newTestStore -- Store a string and try to fetch an int Store.set store ["foo", "bar"] ("qux" :: String) value <- Store.get store ["foo", "bar"] :: IO (Store.Result Int) diff --git a/tests/Hakyll/Core/UnixFilter/Tests.hs b/tests/Hakyll/Core/UnixFilter/Tests.hs index c3e1c99..350c857 100644 --- a/tests/Hakyll/Core/UnixFilter/Tests.hs +++ b/tests/Hakyll/Core/UnixFilter/Tests.hs @@ -27,11 +27,13 @@ tests = testGroup "Hakyll.Core.UnixFilter.Tests" -------------------------------------------------------------------------------- unixFilterRev :: H.Assertion -unixFilterRev = withTestStore $ \store -> do +unixFilterRev = do + store <- newTestStore provider <- newTestProvider store output <- testCompilerDone store provider "russian.md" compiler expected <- testCompilerDone store provider "russian.md" getResourceString H.assert $ rev (itemBody expected) == lines (itemBody output) + cleanTestEnv where compiler = getResourceString >>= withItemBody (unixFilter "rev" []) rev = map reverse . lines diff --git a/tests/Hakyll/Web/Template/Context/Tests.hs b/tests/Hakyll/Web/Template/Context/Tests.hs index f2fb42a..5533c71 100644 --- a/tests/Hakyll/Web/Template/Context/Tests.hs +++ b/tests/Hakyll/Web/Template/Context/Tests.hs @@ -29,7 +29,8 @@ tests = testGroup "Hakyll.Core.Template.Context.Tests" -------------------------------------------------------------------------------- testDateField :: Assertion -testDateField = withTestStore $ \store -> do +testDateField = do + store <- newTestStore provider <- newTestProvider store date1 <- testContextDone store provider "example.md" "date" $ @@ -41,6 +42,8 @@ testDateField = withTestStore $ \store -> do dateField "date" "%B %e, %Y" date2 @=? "August 26, 2010" + cleanTestEnv + -------------------------------------------------------------------------------- testContextDone :: Store -> Provider -> Identifier -> String diff --git a/tests/Hakyll/Web/Template/Tests.hs b/tests/Hakyll/Web/Template/Tests.hs index 6c5c77a..fce5503 100644 --- a/tests/Hakyll/Web/Template/Tests.hs +++ b/tests/Hakyll/Web/Template/Tests.hs @@ -30,11 +30,13 @@ tests = testGroup "Hakyll.Core.Template.Tests" -------------------------------------------------------------------------------- case01 :: Assertion -case01 = withTestStore $ \store -> do +case01 = do + store <- newTestStore provider <- newTestProvider store out <- resourceString provider "template.html.out" - tpl <- testCompilerDone store provider "template.html" $ templateCompiler + tpl <- testCompilerDone store provider "template.html" $ + templateCompiler item <- testCompilerDone store provider "example.md" $ pandocCompiler >>= applyTemplate (itemBody tpl) testContext diff --git a/tests/TestSuite/Util.hs b/tests/TestSuite/Util.hs index 91f4339..6cef730 100644 --- a/tests/TestSuite/Util.hs +++ b/tests/TestSuite/Util.hs @@ -3,19 +3,17 @@ module TestSuite.Util ( fromAssertions , newTestStore - , cleanTestStore - , withTestStore , newTestProvider , testCompiler , testCompilerDone - , withTestConfiguration + , testConfiguration + , cleanTestEnv ) where -------------------------------------------------------------------------------- import Data.Monoid (mempty) import qualified Data.Set as S -import System.Directory (removeDirectoryRecursive) import Test.Framework import Test.Framework.Providers.HUnit import Test.HUnit hiding (Test) @@ -30,6 +28,7 @@ import qualified Hakyll.Core.Logger as Logger import Hakyll.Core.Provider import Hakyll.Core.Store (Store) import qualified Hakyll.Core.Store as Store +import Hakyll.Core.Util.File -------------------------------------------------------------------------------- @@ -42,26 +41,13 @@ fromAssertions name = -------------------------------------------------------------------------------- newTestStore :: IO Store -newTestStore = Store.new True "_teststore" - - --------------------------------------------------------------------------------- -cleanTestStore :: IO () -cleanTestStore = removeDirectoryRecursive "_teststore" - - --------------------------------------------------------------------------------- -withTestStore :: (Store -> IO a) -> IO a -withTestStore f = do - store <- newTestStore - result <- f store - cleanTestStore - return result +newTestStore = Store.new True $ storeDirectory testConfiguration -------------------------------------------------------------------------------- newTestProvider :: Store -> IO Provider -newTestProvider store = newProvider store (const False) "tests/data" +newTestProvider store = newProvider store (const False) $ + providerDirectory testConfiguration -------------------------------------------------------------------------------- @@ -70,7 +56,8 @@ testCompiler :: Store -> Provider -> Identifier -> Compiler a testCompiler store provider underlying compiler = do logger <- Logger.new Logger.Error let read' = CompilerRead - { compilerUnderlying = underlying + { compilerConfig = testConfiguration + , compilerUnderlying = underlying , compilerProvider = provider , compilerUniverse = S.empty , compilerRoutes = mempty @@ -99,15 +86,18 @@ testCompilerDone store provider underlying compiler = do -------------------------------------------------------------------------------- -withTestConfiguration :: (Configuration -> IO a) -> IO a -withTestConfiguration f = do - x <- f config - removeDirectoryRecursive $ destinationDirectory config - removeDirectoryRecursive $ storeDirectory config - return x - where - config = defaultConfiguration - { destinationDirectory = "_testsite" - , storeDirectory = "_teststore" - , providerDirectory = "tests/data" - } +testConfiguration :: Configuration +testConfiguration = defaultConfiguration + { destinationDirectory = "_testsite" + , storeDirectory = "_teststore" + , tmpDirectory = "_testtmp" + , providerDirectory = "tests/data" + } + + +-------------------------------------------------------------------------------- +cleanTestEnv :: IO () +cleanTestEnv = do + removeDirectory $ destinationDirectory testConfiguration + removeDirectory $ storeDirectory testConfiguration + removeDirectory $ tmpDirectory testConfiguration |