module Chiasma.Test.File(
tempDirIO,
tempDir,
fixture,
) where
import System.Directory (canonicalizePath, createDirectoryIfMissing, removePathForcibly)
import System.FilePath ((</>))
testDir :: Text -> IO FilePath
testDir :: Text -> IO FilePath
testDir Text
prefix = FilePath -> IO FilePath
canonicalizePath (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"test" FilePath -> FilePath -> FilePath
</> Text -> FilePath
forall a. ToString a => a -> FilePath
toString Text
prefix
tempDirIO :: Text -> FilePath -> IO FilePath
tempDirIO :: Text -> FilePath -> IO FilePath
tempDirIO Text
prefix FilePath
path = do
FilePath
base <- Text -> IO FilePath
testDir Text
prefix
let dir :: FilePath
dir = FilePath
base FilePath -> FilePath -> FilePath
</> FilePath
"temp"
FilePath -> IO ()
removePathForcibly FilePath
dir
Bool -> FilePath -> IO ()
createDirectoryIfMissing Bool
False FilePath
dir
let absPath :: FilePath
absPath = FilePath
dir FilePath -> FilePath -> FilePath
</> FilePath
path
Bool -> FilePath -> IO ()
createDirectoryIfMissing Bool
True FilePath
absPath
return FilePath
absPath
tempDir :: MonadIO m => Text -> FilePath -> m FilePath
tempDir :: Text -> FilePath -> m FilePath
tempDir Text
prefix FilePath
path =
IO FilePath -> m FilePath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FilePath -> m FilePath) -> IO FilePath -> m FilePath
forall a b. (a -> b) -> a -> b
$ Text -> FilePath -> IO FilePath
tempDirIO Text
prefix FilePath
path
fixture :: MonadIO m => Text -> FilePath -> m FilePath
fixture :: Text -> FilePath -> m FilePath
fixture Text
prefix FilePath
path = do
FilePath
base <- IO FilePath -> m FilePath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FilePath -> m FilePath) -> IO FilePath -> m FilePath
forall a b. (a -> b) -> a -> b
$ Text -> IO FilePath
testDir Text
prefix
return $ FilePath
base FilePath -> FilePath -> FilePath
</> FilePath
"fixtures" FilePath -> FilePath -> FilePath
</> FilePath
path