module Effectful.FileSystem
  ( -- * Effect
    FileSystem

    -- ** Handlers
  , runFileSystem

    -- * Actions on directories
  , createDirectory
  , createDirectoryIfMissing
  , removeDirectory
  , removeDirectoryRecursive
  , removePathForcibly
  , renameDirectory
  , listDirectory
  , getDirectoryContents

    -- ** Current working directory
  , getCurrentDirectory
  , setCurrentDirectory
  , withCurrentDirectory

    -- * Pre-defined directories
  , getHomeDirectory
  , getXdgDirectory
  , getXdgDirectoryList
  , getAppUserDataDirectory
  , getUserDocumentsDirectory
  , getTemporaryDirectory

    -- * Actions on files
  , removeFile
  , renameFile
  , renamePath
  , copyFile
  , copyFileWithMetadata
  , getFileSize
  , canonicalizePath
  , makeAbsolute
  , makeRelativeToCurrentDirectory

    -- * Existence tests
  , doesPathExist
  , doesFileExist
  , doesDirectoryExist
  , findExecutable
  , findExecutables
  , findExecutablesInDirectories
  , findFile
  , findFiles
  , findFileWith
  , findFilesWith

    -- * Symbolic links
  , createFileLink
  , createDirectoryLink
  , removeDirectoryLink
  , pathIsSymbolicLink
  , getSymbolicLinkTarget

    -- * Permissions
  , getPermissions
  , setPermissions
  , copyPermissions

    -- * Timestamps
  , getAccessTime
  , getModificationTime
  , setAccessTime
  , setModificationTime

    -- * Re-exports

    -- ** Pre-defined directories
  , D.XdgDirectory(..)
  , D.XdgDirectoryList(..)

    -- ** Existence tests
  , D.exeExtension

    -- ** Permissions
  , D.Permissions
  , D.emptyPermissions
  , D.readable
  , D.writable
  , D.executable
  , D.searchable
  , D.setOwnerReadable
  , D.setOwnerWritable
  , D.setOwnerExecutable
  , D.setOwnerSearchable
  ) where

import Data.Time (UTCTime)
import qualified System.Directory as D

import Effectful
import Effectful.Dispatch.Static
import Effectful.FileSystem.Effect

----------------------------------------
-- Actions on directories

-- | Lifted 'D.createDirectory'.
createDirectory :: FileSystem :> es => FilePath -> Eff es ()
createDirectory :: FilePath -> Eff es ()
createDirectory = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO ()
D.createDirectory

-- | Lifted 'D.createDirectoryIfMissing'.
createDirectoryIfMissing :: FileSystem :> es => Bool -> FilePath -> Eff es ()
createDirectoryIfMissing :: Bool -> FilePath -> Eff es ()
createDirectoryIfMissing Bool
doCreateParents =
  IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> FilePath -> IO ()
D.createDirectoryIfMissing Bool
doCreateParents

-- | Lifted 'D.removeDirectory'.
removeDirectory :: FileSystem :> es => FilePath -> Eff es ()
removeDirectory :: FilePath -> Eff es ()
removeDirectory = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO ()
D.removeDirectory

-- | Lifted 'D.removeDirectoryRecursive'.
removeDirectoryRecursive :: FileSystem :> es => FilePath -> Eff es ()
removeDirectoryRecursive :: FilePath -> Eff es ()
removeDirectoryRecursive = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO ()
D.removeDirectoryRecursive

-- | Lifted 'D.removePathForcibly'.
removePathForcibly :: FileSystem :> es => FilePath -> Eff es ()
removePathForcibly :: FilePath -> Eff es ()
removePathForcibly = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO ()
D.removePathForcibly

-- | Lifted 'D.renameDirectory'.
renameDirectory :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
renameDirectory :: FilePath -> FilePath -> Eff es ()
renameDirectory FilePath
old = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath -> IO ()
D.renameDirectory FilePath
old

-- | Lifted 'D.listDirectory'.
listDirectory :: FileSystem :> es => FilePath -> Eff es [FilePath]
listDirectory :: FilePath -> Eff es [FilePath]
listDirectory = IO [FilePath] -> Eff es [FilePath]
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO [FilePath] -> Eff es [FilePath])
-> (FilePath -> IO [FilePath]) -> FilePath -> Eff es [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO [FilePath]
D.listDirectory

-- | Lifted 'D.getDirectoryContents'.
getDirectoryContents :: FileSystem :> es => FilePath -> Eff es [FilePath]
getDirectoryContents :: FilePath -> Eff es [FilePath]
getDirectoryContents = IO [FilePath] -> Eff es [FilePath]
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO [FilePath] -> Eff es [FilePath])
-> (FilePath -> IO [FilePath]) -> FilePath -> Eff es [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO [FilePath]
D.getDirectoryContents

----------------------------------------
-- Current working directory

-- | Lifted 'D.getCurrentDirectory'.
getCurrentDirectory :: FileSystem :> es => Eff es FilePath
getCurrentDirectory :: Eff es FilePath
getCurrentDirectory = IO FilePath -> Eff es FilePath
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ IO FilePath
D.getCurrentDirectory

-- | Lifted 'D.setCurrentDirectory'.
setCurrentDirectory :: FileSystem :> es => FilePath -> Eff es ()
setCurrentDirectory :: FilePath -> Eff es ()
setCurrentDirectory = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO ()
D.setCurrentDirectory

-- | Lifted 'D.withCurrentDirectory'.
withCurrentDirectory :: FileSystem :> es => FilePath -> Eff es a -> Eff es a
withCurrentDirectory :: FilePath -> Eff es a -> Eff es a
withCurrentDirectory FilePath
path = (IO a -> IO a) -> Eff es a -> Eff es a
forall a b (es :: [Effect]).
HasCallStack =>
(IO a -> IO b) -> Eff es a -> Eff es b
unsafeLiftMapIO (FilePath -> IO a -> IO a
forall a. FilePath -> IO a -> IO a
D.withCurrentDirectory FilePath
path)

----------------------------------------
-- Pre-defined directories

-- | Lifted 'D.getHomeDirectory'.
getHomeDirectory :: FileSystem :> es => Eff es FilePath
getHomeDirectory :: Eff es FilePath
getHomeDirectory = IO FilePath -> Eff es FilePath
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ IO FilePath
D.getHomeDirectory

-- | Lifted 'D.getXdgDirectory'.
getXdgDirectory
  :: FileSystem :> es
  => D.XdgDirectory
  -> FilePath
  -> Eff es FilePath
getXdgDirectory :: XdgDirectory -> FilePath -> Eff es FilePath
getXdgDirectory XdgDirectory
xdgDir = IO FilePath -> Eff es FilePath
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO FilePath -> Eff es FilePath)
-> (FilePath -> IO FilePath) -> FilePath -> Eff es FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XdgDirectory -> FilePath -> IO FilePath
D.getXdgDirectory XdgDirectory
xdgDir

-- | Lifted 'D.getXdgDirectoryList'.
getXdgDirectoryList
  :: FileSystem :> es
  => D.XdgDirectoryList
  -> Eff es [FilePath]
getXdgDirectoryList :: XdgDirectoryList -> Eff es [FilePath]
getXdgDirectoryList = IO [FilePath] -> Eff es [FilePath]
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO [FilePath] -> Eff es [FilePath])
-> (XdgDirectoryList -> IO [FilePath])
-> XdgDirectoryList
-> Eff es [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XdgDirectoryList -> IO [FilePath]
D.getXdgDirectoryList

-- | Lifted 'D.getAppUserDataDirectory'.
getAppUserDataDirectory :: FileSystem :> es => FilePath -> Eff es FilePath
getAppUserDataDirectory :: FilePath -> Eff es FilePath
getAppUserDataDirectory = IO FilePath -> Eff es FilePath
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO FilePath -> Eff es FilePath)
-> (FilePath -> IO FilePath) -> FilePath -> Eff es FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
D.getAppUserDataDirectory

-- | Lifted 'D.getUserDocumentsDirectory'.
getUserDocumentsDirectory :: FileSystem :> es => Eff es FilePath
getUserDocumentsDirectory :: Eff es FilePath
getUserDocumentsDirectory = IO FilePath -> Eff es FilePath
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ IO FilePath
D.getUserDocumentsDirectory

-- | Lifted 'D.getTemporaryDirectory'.
getTemporaryDirectory :: FileSystem :> es => Eff es FilePath
getTemporaryDirectory :: Eff es FilePath
getTemporaryDirectory = IO FilePath -> Eff es FilePath
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ IO FilePath
D.getTemporaryDirectory

----------------------------------------
-- Actions on files

-- | Lifted 'D.removeFile'.
removeFile :: FileSystem :> es => FilePath -> Eff es ()
removeFile :: FilePath -> Eff es ()
removeFile = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO ()
D.removeFile

-- | Lifted 'D.renameFile'.
renameFile :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
renameFile :: FilePath -> FilePath -> Eff es ()
renameFile FilePath
old = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath -> IO ()
D.renameFile FilePath
old

-- | Lifted 'D.renamePath'.
renamePath :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
renamePath :: FilePath -> FilePath -> Eff es ()
renamePath FilePath
old = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath -> IO ()
D.renamePath FilePath
old

-- | Lifted 'D.copyFile'.
copyFile :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
copyFile :: FilePath -> FilePath -> Eff es ()
copyFile FilePath
src = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath -> IO ()
D.copyFile FilePath
src

-- | Lifted 'D.copyFileWithMetadata'.
copyFileWithMetadata :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
copyFileWithMetadata :: FilePath -> FilePath -> Eff es ()
copyFileWithMetadata FilePath
src = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath -> IO ()
D.copyFileWithMetadata FilePath
src

-- | Lifted 'D.getFileSize'.
getFileSize :: FileSystem :> es => FilePath -> Eff es Integer
getFileSize :: FilePath -> Eff es Integer
getFileSize = IO Integer -> Eff es Integer
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Integer -> Eff es Integer)
-> (FilePath -> IO Integer) -> FilePath -> Eff es Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Integer
D.getFileSize

-- | Lifted 'D.canonicalizePath'.
canonicalizePath :: FileSystem :> es => FilePath -> Eff es FilePath
canonicalizePath :: FilePath -> Eff es FilePath
canonicalizePath = IO FilePath -> Eff es FilePath
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO FilePath -> Eff es FilePath)
-> (FilePath -> IO FilePath) -> FilePath -> Eff es FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
D.canonicalizePath

-- | Lifted 'D.makeAbsolute'.
makeAbsolute :: FileSystem :> es => FilePath -> Eff es FilePath
makeAbsolute :: FilePath -> Eff es FilePath
makeAbsolute = IO FilePath -> Eff es FilePath
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO FilePath -> Eff es FilePath)
-> (FilePath -> IO FilePath) -> FilePath -> Eff es FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
D.makeAbsolute

-- | Lifted 'D.makeRelativeToCurrentDirectory'.
makeRelativeToCurrentDirectory
  :: FileSystem :> es
  => FilePath
  -> Eff es FilePath
makeRelativeToCurrentDirectory :: FilePath -> Eff es FilePath
makeRelativeToCurrentDirectory = IO FilePath -> Eff es FilePath
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO FilePath -> Eff es FilePath)
-> (FilePath -> IO FilePath) -> FilePath -> Eff es FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
D.makeRelativeToCurrentDirectory

----------------------------------------
-- Existence tests

-- | Lifted 'D.doesPathExist'.
doesPathExist :: FileSystem :> es => FilePath -> Eff es Bool
doesPathExist :: FilePath -> Eff es Bool
doesPathExist = IO Bool -> Eff es Bool
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Bool -> Eff es Bool)
-> (FilePath -> IO Bool) -> FilePath -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Bool
D.doesPathExist

-- | Lifted 'D.doesFileExist'.
doesFileExist :: FileSystem :> es => FilePath -> Eff es Bool
doesFileExist :: FilePath -> Eff es Bool
doesFileExist = IO Bool -> Eff es Bool
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Bool -> Eff es Bool)
-> (FilePath -> IO Bool) -> FilePath -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Bool
D.doesFileExist

-- | Lifted 'D.doesDirectoryExist'.
doesDirectoryExist :: FileSystem :> es => FilePath -> Eff es Bool
doesDirectoryExist :: FilePath -> Eff es Bool
doesDirectoryExist = IO Bool -> Eff es Bool
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Bool -> Eff es Bool)
-> (FilePath -> IO Bool) -> FilePath -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Bool
D.doesDirectoryExist

-- | Lifted 'D.findExecutable'.
findExecutable :: FileSystem :> es => String -> Eff es (Maybe FilePath)
findExecutable :: FilePath -> Eff es (Maybe FilePath)
findExecutable = IO (Maybe FilePath) -> Eff es (Maybe FilePath)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (Maybe FilePath) -> Eff es (Maybe FilePath))
-> (FilePath -> IO (Maybe FilePath))
-> FilePath
-> Eff es (Maybe FilePath)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO (Maybe FilePath)
D.findExecutable

-- | Lifted 'D.findExecutables'.
findExecutables :: FileSystem :> es => String -> Eff es [FilePath]
findExecutables :: FilePath -> Eff es [FilePath]
findExecutables = IO [FilePath] -> Eff es [FilePath]
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO [FilePath] -> Eff es [FilePath])
-> (FilePath -> IO [FilePath]) -> FilePath -> Eff es [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO [FilePath]
D.findExecutables

-- | Lifted 'D.findExecutablesInDirectories'.
findExecutablesInDirectories
  :: FileSystem :> es
  => [FilePath]
  -> String
  -> Eff es [FilePath]
findExecutablesInDirectories :: [FilePath] -> FilePath -> Eff es [FilePath]
findExecutablesInDirectories [FilePath]
dirs =
  IO [FilePath] -> Eff es [FilePath]
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO [FilePath] -> Eff es [FilePath])
-> (FilePath -> IO [FilePath]) -> FilePath -> Eff es [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> FilePath -> IO [FilePath]
D.findExecutablesInDirectories [FilePath]
dirs

-- | Lifted 'D.findFile'.
findFile :: FileSystem :> es => [FilePath] -> String -> Eff es (Maybe FilePath)
findFile :: [FilePath] -> FilePath -> Eff es (Maybe FilePath)
findFile [FilePath]
dirs = IO (Maybe FilePath) -> Eff es (Maybe FilePath)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (Maybe FilePath) -> Eff es (Maybe FilePath))
-> (FilePath -> IO (Maybe FilePath))
-> FilePath
-> Eff es (Maybe FilePath)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> FilePath -> IO (Maybe FilePath)
D.findFile [FilePath]
dirs

-- | Lifted 'D.findFiles'.
findFiles :: FileSystem :> es => [FilePath] -> String -> Eff es [FilePath]
findFiles :: [FilePath] -> FilePath -> Eff es [FilePath]
findFiles [FilePath]
dirs = IO [FilePath] -> Eff es [FilePath]
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO [FilePath] -> Eff es [FilePath])
-> (FilePath -> IO [FilePath]) -> FilePath -> Eff es [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> FilePath -> IO [FilePath]
D.findFiles [FilePath]
dirs

-- | Lifted 'D.findFileWith'.
findFileWith
  :: FileSystem :> es
  => (FilePath -> Eff es Bool)
  -> [FilePath]
  -> String
  -> Eff es (Maybe FilePath)
findFileWith :: (FilePath -> Eff es Bool)
-> [FilePath] -> FilePath -> Eff es (Maybe FilePath)
findFileWith FilePath -> Eff es Bool
p [FilePath]
dirs FilePath
n = ((forall r. Eff es r -> IO r) -> IO (Maybe FilePath))
-> Eff es (Maybe FilePath)
forall (es :: [Effect]) a.
HasCallStack =>
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
unsafeSeqUnliftIO (((forall r. Eff es r -> IO r) -> IO (Maybe FilePath))
 -> Eff es (Maybe FilePath))
-> ((forall r. Eff es r -> IO r) -> IO (Maybe FilePath))
-> Eff es (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
  (FilePath -> IO Bool)
-> [FilePath] -> FilePath -> IO (Maybe FilePath)
D.findFileWith (Eff es Bool -> IO Bool
forall r. Eff es r -> IO r
unlift (Eff es Bool -> IO Bool)
-> (FilePath -> Eff es Bool) -> FilePath -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Eff es Bool
p) [FilePath]
dirs FilePath
n

-- | Lifted 'D.findFilesWith'.
findFilesWith
  :: FileSystem :> es
  => (FilePath -> Eff es Bool)
  -> [FilePath]
  -> String
  -> Eff es [FilePath]
findFilesWith :: (FilePath -> Eff es Bool)
-> [FilePath] -> FilePath -> Eff es [FilePath]
findFilesWith FilePath -> Eff es Bool
p [FilePath]
dirs FilePath
ns = ((forall r. Eff es r -> IO r) -> IO [FilePath])
-> Eff es [FilePath]
forall (es :: [Effect]) a.
HasCallStack =>
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
unsafeSeqUnliftIO (((forall r. Eff es r -> IO r) -> IO [FilePath])
 -> Eff es [FilePath])
-> ((forall r. Eff es r -> IO r) -> IO [FilePath])
-> Eff es [FilePath]
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
  (FilePath -> IO Bool) -> [FilePath] -> FilePath -> IO [FilePath]
D.findFilesWith (Eff es Bool -> IO Bool
forall r. Eff es r -> IO r
unlift (Eff es Bool -> IO Bool)
-> (FilePath -> Eff es Bool) -> FilePath -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Eff es Bool
p) [FilePath]
dirs FilePath
ns

----------------------------------------
-- Symbolic links

-- | Lifted 'D.createFileLink'.
createFileLink :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
createFileLink :: FilePath -> FilePath -> Eff es ()
createFileLink FilePath
target = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath -> IO ()
D.createFileLink FilePath
target

-- | Lifted 'D.createDirectoryLink'.
createDirectoryLink :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
createDirectoryLink :: FilePath -> FilePath -> Eff es ()
createDirectoryLink FilePath
target = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath -> IO ()
D.createDirectoryLink FilePath
target

-- | Lifted 'D.removeDirectoryLink'.
removeDirectoryLink :: FileSystem :> es => FilePath -> Eff es ()
removeDirectoryLink :: FilePath -> Eff es ()
removeDirectoryLink = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO ()
D.removeDirectoryLink

-- | Lifted 'D.pathIsSymbolicLink'.
pathIsSymbolicLink :: FileSystem :> es => FilePath -> Eff es Bool
pathIsSymbolicLink :: FilePath -> Eff es Bool
pathIsSymbolicLink = IO Bool -> Eff es Bool
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Bool -> Eff es Bool)
-> (FilePath -> IO Bool) -> FilePath -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Bool
D.pathIsSymbolicLink

-- | Lifted 'D.getSymbolicLinkTarget'.
getSymbolicLinkTarget :: FileSystem :> es => FilePath -> Eff es FilePath
getSymbolicLinkTarget :: FilePath -> Eff es FilePath
getSymbolicLinkTarget = IO FilePath -> Eff es FilePath
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO FilePath -> Eff es FilePath)
-> (FilePath -> IO FilePath) -> FilePath -> Eff es FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
D.getSymbolicLinkTarget

----------------------------------------
-- Permissions

-- | Lifted 'D.getPermissions'.
getPermissions :: FileSystem :> es => FilePath -> Eff es D.Permissions
getPermissions :: FilePath -> Eff es Permissions
getPermissions = IO Permissions -> Eff es Permissions
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO Permissions -> Eff es Permissions)
-> (FilePath -> IO Permissions) -> FilePath -> Eff es Permissions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Permissions
D.getPermissions

-- | Lifted 'D.setPermissions'.
setPermissions :: FileSystem :> es => FilePath -> D.Permissions -> Eff es ()
setPermissions :: FilePath -> Permissions -> Eff es ()
setPermissions FilePath
path = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (Permissions -> IO ()) -> Permissions -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Permissions -> IO ()
D.setPermissions FilePath
path

-- | Lifted 'D.copyPermissions'.
copyPermissions :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
copyPermissions :: FilePath -> FilePath -> Eff es ()
copyPermissions FilePath
src = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (FilePath -> IO ()) -> FilePath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath -> IO ()
D.copyPermissions FilePath
src

----------------------------------------
-- Timestamps

-- | Lifted 'D.getAccessTime'.
getAccessTime :: FileSystem :> es => FilePath -> Eff es UTCTime
getAccessTime :: FilePath -> Eff es UTCTime
getAccessTime = IO UTCTime -> Eff es UTCTime
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO UTCTime -> Eff es UTCTime)
-> (FilePath -> IO UTCTime) -> FilePath -> Eff es UTCTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO UTCTime
D.getAccessTime

-- | Lifted 'D.getModificationTime'.
getModificationTime :: FileSystem :> es => FilePath -> Eff es UTCTime
getModificationTime :: FilePath -> Eff es UTCTime
getModificationTime = IO UTCTime -> Eff es UTCTime
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO UTCTime -> Eff es UTCTime)
-> (FilePath -> IO UTCTime) -> FilePath -> Eff es UTCTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO UTCTime
D.getModificationTime

-- | Lifted 'D.setAccessTime'.
setAccessTime :: FileSystem :> es => FilePath -> UTCTime -> Eff es ()
setAccessTime :: FilePath -> UTCTime -> Eff es ()
setAccessTime FilePath
path = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (UTCTime -> IO ()) -> UTCTime -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> UTCTime -> IO ()
D.setAccessTime FilePath
path

-- | Lifted 'D.setModificationTime'.
setModificationTime :: FileSystem :> es => FilePath -> UTCTime -> Eff es ()
setModificationTime :: FilePath -> UTCTime -> Eff es ()
setModificationTime FilePath
path = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (UTCTime -> IO ()) -> UTCTime -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> UTCTime -> IO ()
D.setModificationTime FilePath
path