{-# OPTIONS_GHC -Wno-redundant-constraints #-}
module Effectful.FileSystem.PathWriter.Static
(
PathWriter,
createDirectory,
createDirectoryIfMissing,
removeDirectory,
removeDirectoryRecursive,
removePathForcibly,
renameDirectory,
setCurrentDirectory,
withCurrentDirectory,
removeFile,
renameFile,
renamePath,
copyFile,
copyFileWithMetadata,
createFileLink,
createDirectoryLink,
removeDirectoryLink,
setPermissions,
copyPermissions,
setAccessTime,
setModificationTime,
runPathWriter,
CopyDirConfig (..),
Overwrite (..),
TargetName (..),
Utils.defaultCopyDirConfig,
copyDirectoryRecursive,
copyDirectoryRecursiveConfig,
copySymbolicLink,
Utils._OverwriteNone,
Utils._OverwriteDirectories,
Utils._OverwriteAll,
Utils._TargetNameSrc,
Utils._TargetNameLiteral,
Utils._TargetNameDest,
removeFileIfExists,
removeFileIfExists_,
removeDirectoryIfExists,
removeDirectoryIfExists_,
removeDirectoryRecursiveIfExists,
removeDirectoryRecursiveIfExists_,
removePathForciblyIfExists,
removePathForciblyIfExists_,
removeSymbolicLink,
removeSymbolicLinkIfExists,
removeSymbolicLinkIfExists_,
OsPath,
IOException,
Permissions,
UTCTime (..),
)
where
import Control.Exception (IOException)
import Control.Exception.Utils (onSyncException)
import Control.Monad (unless, void, when)
import Data.Foldable (for_, traverse_)
import Data.Functor (($>))
import Data.IORef (modifyIORef', newIORef, readIORef)
import Data.Time (UTCTime (UTCTime, utctDay, utctDayTime))
import Effectful
( Dispatch (Static),
DispatchOf,
Eff,
Effect,
IOE,
type (:>),
)
import Effectful.Dispatch.Static
( HasCallStack,
SideEffects (WithSideEffects),
StaticRep,
evalStaticRep,
seqUnliftIO,
unsafeEff,
unsafeEff_,
)
import Effectful.Exception (mask_)
import Effectful.FileSystem.PathReader.Static
( PathReader,
PathType (PathTypeDirectory, PathTypeSymbolicLink),
)
import Effectful.FileSystem.PathReader.Static qualified as PR
import Effectful.FileSystem.PathWriter.Utils
( CopyDirConfig (MkCopyDirConfig, overwrite, targetName),
Overwrite (OverwriteAll, OverwriteDirectories, OverwriteNone),
TargetName (TargetNameDest, TargetNameLiteral, TargetNameSrc),
)
import Effectful.FileSystem.PathWriter.Utils qualified as Utils
import FileSystem.IO qualified as FS.IO
import FileSystem.OsPath (OsPath, (</>))
import Optics.Core ((^.))
import System.Directory (Permissions)
import System.Directory.OsPath qualified as Dir
import System.IO.Error qualified as Error
import System.OsPath qualified as FP
data PathWriter :: Effect
type instance DispatchOf PathWriter = Static WithSideEffects
data instance StaticRep PathWriter = MkPathWriter
runPathWriter :: (HasCallStack, IOE :> es) => Eff (PathWriter : es) a -> Eff es a
runPathWriter :: forall (es :: [Effect]) a.
(HasCallStack, IOE :> es) =>
Eff (PathWriter : es) a -> Eff es a
runPathWriter = StaticRep PathWriter -> Eff (PathWriter : es) a -> Eff es a
forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect])
a.
(HasCallStack, DispatchOf e ~ 'Static sideEffects,
MaybeIOE sideEffects es) =>
StaticRep e -> Eff (e : es) a -> Eff es a
evalStaticRep StaticRep PathWriter
MkPathWriter
createDirectory ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
Eff es ()
createDirectory :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
createDirectory = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> IO ()
Dir.createDirectory
createDirectoryIfMissing ::
( HasCallStack,
PathWriter :> es
) =>
Bool ->
OsPath ->
Eff es ()
createDirectoryIfMissing :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
Bool -> OsPath -> Eff es ()
createDirectoryIfMissing Bool
b = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> OsPath -> IO ()
Dir.createDirectoryIfMissing Bool
b
removeDirectory ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
Eff es ()
removeDirectory :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removeDirectory = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> IO ()
Dir.removeDirectory
removeDirectoryRecursive ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
Eff es ()
removeDirectoryRecursive :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removeDirectoryRecursive = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> IO ()
Dir.removeDirectoryRecursive
removePathForcibly ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
Eff es ()
removePathForcibly :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removePathForcibly = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> IO ()
Dir.removePathForcibly
renameDirectory ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
OsPath ->
Eff es ()
renameDirectory :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
renameDirectory OsPath
p = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> OsPath -> IO ()
Dir.renameDirectory OsPath
p
setCurrentDirectory ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
Eff es ()
setCurrentDirectory :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
setCurrentDirectory = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> IO ()
Dir.setCurrentDirectory
withCurrentDirectory ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
Eff es a ->
Eff es a
withCurrentDirectory :: forall (es :: [Effect]) a.
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es a -> Eff es a
withCurrentDirectory OsPath
p Eff es a
m =
(Env es -> IO a) -> Eff es a
forall (es :: [Effect]) a. (Env es -> IO a) -> Eff es a
unsafeEff ((Env es -> IO a) -> Eff es a) -> (Env es -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \Env es
env -> Env es -> ((forall r. Eff es r -> IO r) -> IO a) -> IO a
forall (es :: [Effect]) a.
HasCallStack =>
Env es -> ((forall r. Eff es r -> IO r) -> IO a) -> IO a
seqUnliftIO Env es
env (((forall r. Eff es r -> IO r) -> IO a) -> IO a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$
\forall r. Eff es r -> IO r
runInIO -> OsPath -> IO a -> IO a
forall a. OsPath -> IO a -> IO a
Dir.withCurrentDirectory OsPath
p (Eff es a -> IO a
forall r. Eff es r -> IO r
runInIO Eff es a
m)
removeFile ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
Eff es ()
removeFile :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removeFile = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> IO ()
Dir.removeFile
renameFile ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
OsPath ->
Eff es ()
renameFile :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
renameFile OsPath
p = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> OsPath -> IO ()
Dir.renameFile OsPath
p
renamePath ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
OsPath ->
Eff es ()
renamePath :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
renamePath OsPath
p = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> OsPath -> IO ()
Dir.renamePath OsPath
p
copyFile ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
OsPath ->
Eff es ()
copyFile :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
copyFile OsPath
p = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> OsPath -> IO ()
Dir.copyFile OsPath
p
copyFileWithMetadata ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
OsPath ->
Eff es ()
copyFileWithMetadata :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
copyFileWithMetadata OsPath
p = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> OsPath -> IO ()
Dir.copyFileWithMetadata OsPath
p
createFileLink ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
OsPath ->
Eff es ()
createFileLink :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
createFileLink OsPath
p = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> OsPath -> IO ()
Dir.createFileLink OsPath
p
createDirectoryLink ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
OsPath ->
Eff es ()
createDirectoryLink :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
createDirectoryLink OsPath
p = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> OsPath -> IO ()
Dir.createDirectoryLink OsPath
p
removeDirectoryLink ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
Eff es ()
removeDirectoryLink :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removeDirectoryLink = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> IO ()
Dir.removeDirectoryLink
setPermissions ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
Permissions ->
Eff es ()
setPermissions :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Permissions -> Eff es ()
setPermissions OsPath
p = 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
. OsPath -> Permissions -> IO ()
Dir.setPermissions OsPath
p
copyPermissions ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
OsPath ->
Eff es ()
copyPermissions :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
copyPermissions OsPath
p = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (OsPath -> IO ()) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> OsPath -> IO ()
Dir.copyPermissions OsPath
p
setAccessTime ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
UTCTime ->
Eff es ()
setAccessTime :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> UTCTime -> Eff es ()
setAccessTime OsPath
p = 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
. OsPath -> UTCTime -> IO ()
Dir.setAccessTime OsPath
p
setModificationTime ::
( HasCallStack,
PathWriter :> es
) =>
OsPath ->
UTCTime ->
Eff es ()
setModificationTime :: forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> UTCTime -> Eff es ()
setModificationTime OsPath
p = 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
. OsPath -> UTCTime -> IO ()
Dir.setModificationTime OsPath
p
removeFileIfExists_ ::
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
OsPath ->
Eff es ()
removeFileIfExists_ :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es ()
removeFileIfExists_ = Eff es Bool -> Eff es ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Eff es Bool -> Eff es ())
-> (OsPath -> Eff es Bool) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es Bool
removeFileIfExists
removeFileIfExists ::
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
OsPath ->
Eff es Bool
removeFileIfExists :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es Bool
removeFileIfExists = (OsPath -> Eff es Bool)
-> (OsPath -> Eff es ()) -> OsPath -> Eff es Bool
forall (es :: [Effect]).
(OsPath -> Eff es Bool)
-> (OsPath -> Eff es ()) -> OsPath -> Eff es Bool
removeIfExists OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
OsPath -> Eff es Bool
PR.doesFileExist OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removeFile
removeDirectoryIfExists_ ::
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
OsPath ->
Eff es ()
removeDirectoryIfExists_ :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es ()
removeDirectoryIfExists_ = Eff es Bool -> Eff es ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Eff es Bool -> Eff es ())
-> (OsPath -> Eff es Bool) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es Bool
removeDirectoryIfExists
removeDirectoryIfExists ::
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
OsPath ->
Eff es Bool
removeDirectoryIfExists :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es Bool
removeDirectoryIfExists = (OsPath -> Eff es Bool)
-> (OsPath -> Eff es ()) -> OsPath -> Eff es Bool
forall (es :: [Effect]).
(OsPath -> Eff es Bool)
-> (OsPath -> Eff es ()) -> OsPath -> Eff es Bool
removeIfExists OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
OsPath -> Eff es Bool
PR.doesDirectoryExist OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removeDirectory
removeDirectoryRecursiveIfExists_ ::
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
OsPath ->
Eff es ()
removeDirectoryRecursiveIfExists_ :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es ()
removeDirectoryRecursiveIfExists_ = Eff es Bool -> Eff es ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Eff es Bool -> Eff es ())
-> (OsPath -> Eff es Bool) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es Bool
removeDirectoryRecursiveIfExists
removeDirectoryRecursiveIfExists ::
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
OsPath ->
Eff es Bool
removeDirectoryRecursiveIfExists :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es Bool
removeDirectoryRecursiveIfExists =
(OsPath -> Eff es Bool)
-> (OsPath -> Eff es ()) -> OsPath -> Eff es Bool
forall (es :: [Effect]).
(OsPath -> Eff es Bool)
-> (OsPath -> Eff es ()) -> OsPath -> Eff es Bool
removeIfExists OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
OsPath -> Eff es Bool
PR.doesDirectoryExist OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removeDirectoryRecursive
removePathForciblyIfExists_ ::
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
OsPath ->
Eff es ()
removePathForciblyIfExists_ :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es ()
removePathForciblyIfExists_ = Eff es Bool -> Eff es ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Eff es Bool -> Eff es ())
-> (OsPath -> Eff es Bool) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es Bool
removePathForciblyIfExists
removePathForciblyIfExists ::
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
OsPath ->
Eff es Bool
removePathForciblyIfExists :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es Bool
removePathForciblyIfExists =
(OsPath -> Eff es Bool)
-> (OsPath -> Eff es ()) -> OsPath -> Eff es Bool
forall (es :: [Effect]).
(OsPath -> Eff es Bool)
-> (OsPath -> Eff es ()) -> OsPath -> Eff es Bool
removeIfExists OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
OsPath -> Eff es Bool
PR.doesPathExist OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removePathForcibly
removeSymbolicLinkIfExists_ ::
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
OsPath ->
Eff es ()
removeSymbolicLinkIfExists_ :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es ()
removeSymbolicLinkIfExists_ = Eff es Bool -> Eff es ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Eff es Bool -> Eff es ())
-> (OsPath -> Eff es Bool) -> OsPath -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es Bool
removeSymbolicLinkIfExists
removeSymbolicLinkIfExists ::
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
OsPath ->
Eff es Bool
removeSymbolicLinkIfExists :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es Bool
removeSymbolicLinkIfExists =
(OsPath -> Eff es Bool)
-> (OsPath -> Eff es ()) -> OsPath -> Eff es Bool
forall (es :: [Effect]).
(OsPath -> Eff es Bool)
-> (OsPath -> Eff es ()) -> OsPath -> Eff es Bool
removeIfExists OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
OsPath -> Eff es Bool
PR.doesSymbolicLinkExist OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es ()
removeSymbolicLink
removeIfExists ::
(OsPath -> Eff es Bool) ->
(OsPath -> Eff es ()) ->
OsPath ->
Eff es Bool
removeIfExists :: forall (es :: [Effect]).
(OsPath -> Eff es Bool)
-> (OsPath -> Eff es ()) -> OsPath -> Eff es Bool
removeIfExists OsPath -> Eff es Bool
existsFn OsPath -> Eff es ()
deleteFn OsPath
f = do
exists <- OsPath -> Eff es Bool
existsFn OsPath
f
if exists
then deleteFn f $> True
else pure False
copyDirectoryRecursive ::
forall es.
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
OsPath ->
OsPath ->
Eff es ()
copyDirectoryRecursive :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
copyDirectoryRecursive = CopyDirConfig -> OsPath -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
CopyDirConfig -> OsPath -> OsPath -> Eff es ()
copyDirectoryRecursiveConfig CopyDirConfig
Utils.defaultCopyDirConfig
copyDirectoryRecursiveConfig ::
forall es.
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
CopyDirConfig ->
OsPath ->
OsPath ->
Eff es ()
copyDirectoryRecursiveConfig :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
CopyDirConfig -> OsPath -> OsPath -> Eff es ()
copyDirectoryRecursiveConfig CopyDirConfig
config OsPath
src OsPath
destRoot = do
String -> PathType -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
String -> PathType -> OsPath -> Eff es ()
PR.throwIfWrongPathType String
"copyDirectoryRecursiveConfig" PathType
PathTypeDirectory OsPath
src
String -> PathType -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
String -> PathType -> OsPath -> Eff es ()
PR.throwIfWrongPathType String
"copyDirectoryRecursiveConfig" PathType
PathTypeDirectory OsPath
destRoot
let dest :: OsPath
dest = case CopyDirConfig
config CopyDirConfig
-> Optic' A_Lens NoIx CopyDirConfig TargetName -> TargetName
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx CopyDirConfig TargetName
#targetName of
TargetName
TargetNameSrc ->
let
(OsPath
_, OsPath
name) = OsPath -> (OsPath, OsPath)
FP.splitFileName (OsPath -> OsPath
FP.dropTrailingPathSeparator OsPath
src)
in OsPath
destRoot OsPath -> OsPath -> OsPath
</> OsPath
name
TargetNameLiteral OsPath
p -> OsPath
destRoot OsPath -> OsPath -> OsPath
</> OsPath
p
TargetName
TargetNameDest -> OsPath
destRoot
case CopyDirConfig
config CopyDirConfig
-> Optic' A_Lens NoIx CopyDirConfig Overwrite -> Overwrite
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx CopyDirConfig Overwrite
#overwrite of
Overwrite
OverwriteNone -> OsPath -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
copyDirectoryNoOverwrite OsPath
src OsPath
dest
Overwrite
OverwriteDirectories -> Bool -> OsPath -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
Bool -> OsPath -> OsPath -> Eff es ()
copyDirectoryOverwrite Bool
False OsPath
src OsPath
dest
Overwrite
OverwriteAll -> Bool -> OsPath -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
Bool -> OsPath -> OsPath -> Eff es ()
copyDirectoryOverwrite Bool
True OsPath
src OsPath
dest
copyDirectoryOverwrite ::
forall es.
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
Bool ->
OsPath ->
OsPath ->
Eff es ()
copyDirectoryOverwrite :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
Bool -> OsPath -> OsPath -> Eff es ()
copyDirectoryOverwrite Bool
overwriteFiles OsPath
src OsPath
dest = do
copiedFilesRef <- IO (IORef [OsPath]) -> Eff es (IORef [OsPath])
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (IORef [OsPath]) -> Eff es (IORef [OsPath]))
-> IO (IORef [OsPath]) -> Eff es (IORef [OsPath])
forall a b. (a -> b) -> a -> b
$ [OsPath] -> IO (IORef [OsPath])
forall a. a -> IO (IORef a)
newIORef []
createdDirsRef <- unsafeEff_ $ newIORef []
copiedSymlinksRef <- unsafeEff_ $ newIORef []
destExists <- PR.doesDirectoryExist dest
let checkFileOverwrites =
if Bool -> Bool
not Bool
overwriteFiles
then \OsPath
f -> do
exists <- OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
OsPath -> Eff es Bool
PR.doesFileExist OsPath
f
when exists $
FS.IO.throwPathIOError
f
"copyDirectoryOverwrite"
Error.alreadyExistsErrorType
"Attempted file overwrite when CopyDirConfig.overwriteFiles is false"
else Eff es () -> OsPath -> Eff es ()
forall a b. a -> b -> a
const (() -> Eff es ()
forall a. a -> Eff es a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
checkSymlinkOverwrites =
if Bool -> Bool
not Bool
overwriteFiles
then \OsPath
f -> do
exists <- OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
OsPath -> Eff es Bool
PR.doesSymbolicLinkExist OsPath
f
when exists $
FS.IO.throwPathIOError
f
"copyDirectoryOverwrite"
Error.alreadyExistsErrorType
"Attempted symlink overwrite when CopyDirConfig.overwriteFiles is false"
else Eff es () -> OsPath -> Eff es ()
forall a b. a -> b -> a
const (() -> Eff es ()
forall a. a -> Eff es a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
copyFiles = do
(subFiles, subDirs, symlinks) <- OsPath -> Eff es ([OsPath], [OsPath], [OsPath])
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
OsPath -> Eff es ([OsPath], [OsPath], [OsPath])
PR.listDirectoryRecursiveSymbolicLink OsPath
src
unless destExists $ createDirectory dest
for_ subDirs $ \OsPath
d -> do
let d' :: OsPath
d' = OsPath
dest OsPath -> OsPath -> OsPath
</> OsPath
d
dExists <- OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
OsPath -> Eff es Bool
PR.doesDirectoryExist OsPath
d'
unless dExists $ do
createDirectoryIfMissing False d'
unsafeEff_ $ modifyIORef' createdDirsRef (d' :)
for_ subFiles $ \OsPath
f -> do
let f' :: OsPath
f' = OsPath
dest OsPath -> OsPath -> OsPath
</> OsPath
f
OsPath -> Eff es ()
checkFileOverwrites OsPath
f'
OsPath -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
copyFileWithMetadata (OsPath
src OsPath -> OsPath -> OsPath
</> OsPath
f) OsPath
f'
IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> IO () -> Eff es ()
forall a b. (a -> b) -> a -> b
$ IORef [OsPath] -> ([OsPath] -> [OsPath]) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' IORef [OsPath]
copiedFilesRef (OsPath
f' OsPath -> [OsPath] -> [OsPath]
forall a. a -> [a] -> [a]
:)
for_ symlinks $ \OsPath
s -> do
let s' :: OsPath
s' = OsPath
dest OsPath -> OsPath -> OsPath
</> OsPath
s
OsPath -> Eff es ()
checkSymlinkOverwrites OsPath
s'
OsPath -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
copySymbolicLink (OsPath
src OsPath -> OsPath -> OsPath
</> OsPath
s) OsPath
s'
IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> IO () -> Eff es ()
forall a b. (a -> b) -> a -> b
$ IORef [OsPath] -> ([OsPath] -> [OsPath]) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' IORef [OsPath]
copiedSymlinksRef (OsPath
s' OsPath -> [OsPath] -> [OsPath]
forall a. a -> [a] -> [a]
:)
cleanup =
if Bool
destExists
then do
IO [OsPath] -> Eff es [OsPath]
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IORef [OsPath] -> IO [OsPath]
forall a. IORef a -> IO a
readIORef IORef [OsPath]
copiedFilesRef) Eff es [OsPath] -> ([OsPath] -> Eff es ()) -> Eff es ()
forall a b. Eff es a -> (a -> Eff es b) -> Eff es b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (OsPath -> Eff es ()) -> [OsPath] -> Eff es ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removeFile
IO [OsPath] -> Eff es [OsPath]
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IORef [OsPath] -> IO [OsPath]
forall a. IORef a -> IO a
readIORef IORef [OsPath]
createdDirsRef) Eff es [OsPath] -> ([OsPath] -> Eff es ()) -> Eff es ()
forall a b. Eff es a -> (a -> Eff es b) -> Eff es b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (OsPath -> Eff es ()) -> [OsPath] -> Eff es ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removeDirectory
IO [OsPath] -> Eff es [OsPath]
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IORef [OsPath] -> IO [OsPath]
forall a. IORef a -> IO a
readIORef IORef [OsPath]
copiedSymlinksRef) Eff es [OsPath] -> ([OsPath] -> Eff es ()) -> Eff es ()
forall a b. Eff es a -> (a -> Eff es b) -> Eff es b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (OsPath -> Eff es ()) -> [OsPath] -> Eff es ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es ()
removeSymbolicLink
else OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removeDirectoryRecursive OsPath
dest
copyFiles `onSyncException` mask_ cleanup
copyDirectoryNoOverwrite ::
forall es.
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
OsPath ->
OsPath ->
Eff es ()
copyDirectoryNoOverwrite :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
copyDirectoryNoOverwrite OsPath
src OsPath
dest = do
destExists <- OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
OsPath -> Eff es Bool
PR.doesDirectoryExist OsPath
dest
when destExists $
FS.IO.throwPathIOError
dest
"copyDirectoryNoOverwrite"
Error.alreadyExistsErrorType
"Attempted directory overwrite when CopyDirConfig.overwrite is OverwriteNone"
let copyFiles = do
(subFiles, subDirs, symlinks) <- OsPath -> Eff es ([OsPath], [OsPath], [OsPath])
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
OsPath -> Eff es ([OsPath], [OsPath], [OsPath])
PR.listDirectoryRecursiveSymbolicLink OsPath
src
createDirectory dest
traverse_ (createDirectoryIfMissing True . (dest </>)) subDirs
for_ subFiles $ \OsPath
f -> OsPath -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
copyFileWithMetadata (OsPath
src OsPath -> OsPath -> OsPath
</> OsPath
f) (OsPath
dest OsPath -> OsPath -> OsPath
</> OsPath
f)
for_ symlinks $ \OsPath
s -> OsPath -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
copySymbolicLink (OsPath
src OsPath -> OsPath -> OsPath
</> OsPath
s) (OsPath
dest OsPath -> OsPath -> OsPath
</> OsPath
s)
cleanup = OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removeDirectoryRecursive OsPath
dest
copyFiles `onSyncException` mask_ cleanup
removeSymbolicLink ::
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
OsPath ->
Eff es ()
removeSymbolicLink :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> Eff es ()
removeSymbolicLink OsPath
p = do
String -> PathType -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
String -> PathType -> OsPath -> Eff es ()
PR.throwIfWrongPathType String
"removeSymbolicLink" PathType
PathTypeSymbolicLink OsPath
p
OsPath -> Eff es Bool
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
OsPath -> Eff es Bool
PR.pathIsSymbolicDirectoryLink OsPath
p Eff es Bool -> (Bool -> Eff es ()) -> Eff es ()
forall a b. Eff es a -> (a -> Eff es b) -> Eff es b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
True -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removeDirectoryLink OsPath
p
Bool
False -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> Eff es ()
removeFile OsPath
p
copySymbolicLink ::
( HasCallStack,
PathReader :> es,
PathWriter :> es
) =>
OsPath ->
OsPath ->
Eff es ()
copySymbolicLink :: forall (es :: [Effect]).
(HasCallStack, PathReader :> es, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
copySymbolicLink OsPath
src OsPath
dest = do
String -> PathType -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
String -> PathType -> OsPath -> Eff es ()
PR.throwIfWrongPathType String
"copySymbolicLink" PathType
PathTypeSymbolicLink OsPath
src
target <- OsPath -> Eff es OsPath
forall (es :: [Effect]).
(HasCallStack, PathReader :> es) =>
OsPath -> Eff es OsPath
PR.getSymbolicLinkTarget OsPath
src
PR.pathIsSymbolicDirectoryLink src >>= \case
Bool
True -> OsPath -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
createDirectoryLink OsPath
target OsPath
dest
Bool
False -> OsPath -> OsPath -> Eff es ()
forall (es :: [Effect]).
(HasCallStack, PathWriter :> es) =>
OsPath -> OsPath -> Eff es ()
createFileLink OsPath
target OsPath
dest