{-# OPTIONS_HADDOCK hide #-} module Polysemy.Test.Files where import qualified Data.Text as Text import qualified Data.Text.IO as Text import Path (Abs, Dir, File, Path, Rel, parent, reldir, toFilePath, (</>)) import Path.IO (createDirIfMissing) tempPath :: Path Abs Dir -> Path Rel b -> Path Abs b tempPath :: Path Abs Dir -> Path Rel b -> Path Abs b tempPath Path Abs Dir base Path Rel b path = Path Abs Dir base Path Abs Dir -> Path Rel b -> Path Abs b forall b t. Path b Dir -> Path Rel t -> Path b t </> [reldir|temp|] Path Rel Dir -> Path Rel b -> Path Rel b forall b t. Path b Dir -> Path Rel t -> Path b t </> Path Rel b path tempDir :: Member (Embed IO) r => Path Abs Dir -> Path Rel Dir -> Sem r (Path Abs Dir) tempDir :: Path Abs Dir -> Path Rel Dir -> Sem r (Path Abs Dir) tempDir Path Abs Dir base Path Rel Dir path = do IO () -> Sem r () forall (m :: * -> *) (r :: [(* -> *) -> * -> *]) a. Member (Embed m) r => m a -> Sem r a embed (Bool -> Path Abs Dir -> IO () forall (m :: * -> *) b. MonadIO m => Bool -> Path b Dir -> m () createDirIfMissing @IO Bool True Path Abs Dir fullPath) pure Path Abs Dir fullPath where fullPath :: Path Abs Dir fullPath = Path Abs Dir -> Path Rel Dir -> Path Abs Dir forall b. Path Abs Dir -> Path Rel b -> Path Abs b tempPath Path Abs Dir base Path Rel Dir path readFile :: Member (Embed IO) r => Path Abs File -> Sem r Text readFile :: Path Abs File -> Sem r Text readFile Path Abs File path = IO Text -> Sem r Text forall (m :: * -> *) (r :: [(* -> *) -> * -> *]) a. Member (Embed m) r => m a -> Sem r a embed (FilePath -> IO Text Text.readFile (Path Abs File -> FilePath forall b t. Path b t -> FilePath toFilePath Path Abs File path)) tempFile :: Member (Embed IO) r => Path Abs Dir -> [Text] -> Path Rel File -> Sem r (Path Abs File) tempFile :: Path Abs Dir -> [Text] -> Path Rel File -> Sem r (Path Abs File) tempFile Path Abs Dir base [Text] content Path Rel File path = do Sem r (Path Abs Dir) -> Sem r () forall (f :: * -> *) a. Functor f => f a -> f () void (Path Abs Dir -> Path Rel Dir -> Sem r (Path Abs Dir) forall (r :: [(* -> *) -> * -> *]). Member (Embed IO) r => Path Abs Dir -> Path Rel Dir -> Sem r (Path Abs Dir) tempDir Path Abs Dir base (Path Rel File -> Path Rel Dir forall b t. Path b t -> Path b Dir parent Path Rel File path)) Path Abs File fullPath Path Abs File -> Sem r () -> Sem r (Path Abs File) forall (f :: * -> *) a b. Functor f => a -> f b -> f a <$ IO () -> Sem r () forall (m :: * -> *) (r :: [(* -> *) -> * -> *]) a. Member (Embed m) r => m a -> Sem r a embed (FilePath -> Text -> IO () Text.writeFile (Path Abs File -> FilePath forall b t. Path b t -> FilePath toFilePath Path Abs File fullPath) (Text -> [Text] -> Text Text.intercalate Text "\n" [Text] content)) where fullPath :: Path Abs File fullPath = Path Abs Dir -> Path Rel File -> Path Abs File forall b. Path Abs Dir -> Path Rel b -> Path Abs b tempPath Path Abs Dir base Path Rel File path tempFileContent :: Member (Embed IO) r => Path Abs Dir -> Path Rel File -> Sem r Text tempFileContent :: Path Abs Dir -> Path Rel File -> Sem r Text tempFileContent Path Abs Dir base Path Rel File path = Path Abs File -> Sem r Text forall (r :: [(* -> *) -> * -> *]). Member (Embed IO) r => Path Abs File -> Sem r Text readFile (Path Abs Dir -> Path Rel File -> Path Abs File forall b. Path Abs Dir -> Path Rel b -> Path Abs b tempPath Path Abs Dir base Path Rel File path) fixturePath :: Path Abs Dir -> Path Rel p -> Sem r (Path Abs p) fixturePath :: Path Abs Dir -> Path Rel p -> Sem r (Path Abs p) fixturePath Path Abs Dir base Path Rel p path = do Path Abs p -> Sem r (Path Abs p) forall (m :: * -> *) a. Monad m => a -> m a return (Path Abs p -> Sem r (Path Abs p)) -> Path Abs p -> Sem r (Path Abs p) forall a b. (a -> b) -> a -> b $ Path Abs Dir base Path Abs Dir -> Path Rel p -> Path Abs p forall b t. Path b Dir -> Path Rel t -> Path b t </> [reldir|fixtures|] Path Rel Dir -> Path Rel p -> Path Rel p forall b t. Path b Dir -> Path Rel t -> Path b t </> Path Rel p path fixture :: Member (Embed IO) r => Path Abs Dir -> Path Rel File -> Sem r Text fixture :: Path Abs Dir -> Path Rel File -> Sem r Text fixture Path Abs Dir base Path Rel File subPath = do Path Abs File -> Sem r Text forall (r :: [(* -> *) -> * -> *]). Member (Embed IO) r => Path Abs File -> Sem r Text readFile (Path Abs File -> Sem r Text) -> Sem r (Path Abs File) -> Sem r Text forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b =<< Path Abs Dir -> Path Rel File -> Sem r (Path Abs File) forall p (r :: [(* -> *) -> * -> *]). Path Abs Dir -> Path Rel p -> Sem r (Path Abs p) fixturePath Path Abs Dir base Path Rel File subPath