{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE NoImplicitPrelude #-} module System.FilePath.FilePather.Directory( createDirectory , createDirectoryIfMissing , removeDirectory , removeDirectoryRecursive , removePathForcibly , renameDirectory , listDirectory , getDirectoryContents , getCurrentDirectory , setCurrentDirectory , getHomeDirectory , withCurrentDirectory , getXdgDirectory , getAppUserDataDirectory , getUserDocumentsDirectory , getTemporaryDirectory , getXdgDirectoryList , removeFile , renameFile , renamePath , copyFile , copyFileWithMetadata , getFileSize , canonicalizePath , makeAbsolute , makeRelativeToCurrentDirectory , doesPathExist , doesFileExist , doesDirectoryExist , findExecutable , findExecutables , findExecutablesInDirectories , findFile , findFiles , findFileWith , findFilesWith , createFileLink , createDirectoryLink , removeDirectoryLink , pathIsSymbolicLink , getSymbolicLinkTarget , getPermissions , setPermissions , copyPermissions , getAccessTime , getModificationTime , setAccessTime , setModificationTime , module SD ) where import Control.Applicative ( Applicative(pure) ) import Control.Category ( Category((.)) ) import Control.Exception ( Exception ) import Control.Lens ( over, _Wrapped ) import Data.Maybe ( Maybe, maybe ) import Data.Bool ( Bool(..) ) import Data.Either ( Either(Right, Left), either ) import Data.Functor ( Functor(fmap) ) import Data.Time ( UTCTime ) import GHC.Num( Integer ) import qualified System.Directory as D import System.Directory as SD( XdgDirectory(..), XdgDirectoryList(..), exeExtension, Permissions(..), emptyPermissions, readable, writable, executable, searchable, setOwnerReadable, setOwnerWritable, setOwnerExecutable, setOwnerSearchable) import System.FilePath.FilePather.ReadFilePath ( ReadFilePathT1, ReadFilePathT, successReadFilePath, tryReadFilePath ) import System.FilePath ( FilePath ) import System.IO ( IO ) createDirectory :: Exception e => ReadFilePathT1 e IO createDirectory = tryReadFilePath D.createDirectory {-# INLINE createDirectory #-} createDirectoryIfMissing :: Exception e => Bool -> ReadFilePathT1 e IO createDirectoryIfMissing = tryReadFilePath . D.createDirectoryIfMissing {-# INLINE createDirectoryIfMissing #-} removeDirectory :: Exception e => ReadFilePathT1 e IO removeDirectory = tryReadFilePath D.removeDirectory {-# INLINE removeDirectory #-} removeDirectoryRecursive :: Exception e => ReadFilePathT1 e IO removeDirectoryRecursive = tryReadFilePath D.removeDirectoryRecursive {-# INLINE removeDirectoryRecursive #-} removePathForcibly :: Exception e => ReadFilePathT1 e IO removePathForcibly = tryReadFilePath D.removePathForcibly {-# INLINE removePathForcibly #-} renameDirectory :: Exception e => FilePath -> ReadFilePathT1 e IO renameDirectory = tryReadFilePath . D.renameDirectory {-# INLINE renameDirectory #-} listDirectory :: Exception e => ReadFilePathT e IO [FilePath] listDirectory = tryReadFilePath D.listDirectory {-# INLINE listDirectory #-} getDirectoryContents :: Exception e => ReadFilePathT e IO [FilePath] getDirectoryContents = tryReadFilePath D.listDirectory {-# INLINE getDirectoryContents #-} getCurrentDirectory :: Exception e => ReadFilePathT e IO FilePath getCurrentDirectory = tryReadFilePath (pure D.getCurrentDirectory) {-# INLINE getCurrentDirectory #-} setCurrentDirectory :: Exception e => ReadFilePathT e IO () setCurrentDirectory = tryReadFilePath D.setCurrentDirectory {-# INLINE setCurrentDirectory #-} getHomeDirectory :: Exception e => ReadFilePathT e IO FilePath getHomeDirectory = tryReadFilePath (pure D.getHomeDirectory) {-# INLINE getHomeDirectory #-} withCurrentDirectory :: Exception e => IO a -> ReadFilePathT e IO a withCurrentDirectory io = tryReadFilePath (`D.withCurrentDirectory` io) {-# INLINE withCurrentDirectory #-} getXdgDirectory :: Exception e => XdgDirectory -> ReadFilePathT e IO FilePath getXdgDirectory = tryReadFilePath . D.getXdgDirectory {-# INLINE getXdgDirectory #-} getAppUserDataDirectory :: Exception e => ReadFilePathT e IO FilePath getAppUserDataDirectory = tryReadFilePath D.getAppUserDataDirectory {-# INLINE getAppUserDataDirectory #-} getUserDocumentsDirectory :: Exception e => ReadFilePathT e IO FilePath getUserDocumentsDirectory = tryReadFilePath (pure D.getUserDocumentsDirectory) {-# INLINE getUserDocumentsDirectory #-} getTemporaryDirectory :: Exception e => ReadFilePathT e IO FilePath getTemporaryDirectory = tryReadFilePath (pure D.getTemporaryDirectory) {-# INLINE getTemporaryDirectory #-} getXdgDirectoryList :: Exception e => XdgDirectoryList -> ReadFilePathT e IO [FilePath] getXdgDirectoryList = tryReadFilePath . pure . D.getXdgDirectoryList {-# INLINE getXdgDirectoryList #-} removeFile :: Exception e => ReadFilePathT1 e IO removeFile = tryReadFilePath D.removeFile {-# INLINE removeFile #-} renameFile :: Exception e => FilePath -> ReadFilePathT1 e IO renameFile = tryReadFilePath . D.renameFile {-# INLINE renameFile #-} renamePath :: Exception e => FilePath -> ReadFilePathT1 e IO renamePath = tryReadFilePath . D.renamePath {-# INLINE renamePath #-} copyFile :: Exception e => FilePath -> ReadFilePathT1 e IO copyFile = tryReadFilePath . D.copyFile {-# INLINE copyFile #-} copyFileWithMetadata :: Exception e => FilePath -> ReadFilePathT1 e IO copyFileWithMetadata = tryReadFilePath . D.copyFileWithMetadata {-# INLINE copyFileWithMetadata #-} getFileSize :: Exception e => ReadFilePathT e IO Integer getFileSize = tryReadFilePath D.getFileSize {-# INLINE getFileSize #-} canonicalizePath :: Exception e => ReadFilePathT e IO FilePath canonicalizePath = tryReadFilePath D.canonicalizePath {-# INLINE canonicalizePath #-} makeAbsolute :: Exception e => ReadFilePathT e IO FilePath makeAbsolute = tryReadFilePath D.makeAbsolute {-# INLINE makeAbsolute #-} makeRelativeToCurrentDirectory :: Exception e => ReadFilePathT e IO FilePath makeRelativeToCurrentDirectory = tryReadFilePath D.makeRelativeToCurrentDirectory {-# INLINE makeRelativeToCurrentDirectory #-} doesPathExist :: ReadFilePathT e IO Bool doesPathExist = successReadFilePath D.doesPathExist {-# INLINE doesPathExist #-} doesFileExist :: ReadFilePathT e IO Bool doesFileExist = successReadFilePath D.doesFileExist {-# INLINE doesFileExist #-} doesDirectoryExist :: ReadFilePathT e IO Bool doesDirectoryExist = successReadFilePath D.doesDirectoryExist {-# INLINE doesDirectoryExist #-} findExecutable :: ReadFilePathT e IO (Maybe FilePath) findExecutable = successReadFilePath D.findExecutable {-# INLINE findExecutable #-} findExecutables :: ReadFilePathT e IO [FilePath] findExecutables = successReadFilePath D.findExecutables {-# INLINE findExecutables #-} findExecutablesInDirectories :: [FilePath] -> ReadFilePathT e IO [FilePath] findExecutablesInDirectories = successReadFilePath . D.findExecutablesInDirectories {-# INLINE findExecutablesInDirectories #-} findFile :: [FilePath] -> ReadFilePathT e IO (Maybe FilePath) findFile = successReadFilePath . D.findFile {-# INLINE findFile #-} findFiles :: [FilePath] -> ReadFilePathT e IO [FilePath] findFiles = successReadFilePath . D.findFiles {-# INLINE findFiles #-} findFileWith :: ReadFilePathT () IO () -> [FilePath] -> ReadFilePathT () IO FilePath findFileWith x ps = over _Wrapped (\k -> fmap (maybe (Left ()) Right) . D.findFileWith (fmap (either (\() -> False) (\() -> True)) . k) ps) x {-# INLINE findFileWith #-} findFilesWith :: ReadFilePathT () IO () -> [FilePath] -> ReadFilePathT e' IO [FilePath] findFilesWith x ps = over _Wrapped (\w -> fmap Right . D.findFilesWith (fmap (either (\() -> False) (\() -> True)) . w) ps) x {-# INLINE findFilesWith #-} createFileLink :: Exception e => FilePath -> ReadFilePathT1 e IO createFileLink = tryReadFilePath . D.createFileLink {-# INLINE createFileLink #-} createDirectoryLink :: Exception e => FilePath -> ReadFilePathT1 e IO createDirectoryLink = tryReadFilePath . D.createDirectoryLink {-# INLINE createDirectoryLink #-} removeDirectoryLink :: Exception e => ReadFilePathT1 e IO removeDirectoryLink = tryReadFilePath D.removeDirectoryLink {-# INLINE removeDirectoryLink #-} pathIsSymbolicLink :: Exception e => ReadFilePathT e IO Bool pathIsSymbolicLink = tryReadFilePath D.pathIsSymbolicLink {-# INLINE pathIsSymbolicLink #-} getSymbolicLinkTarget :: Exception e => ReadFilePathT e IO FilePath getSymbolicLinkTarget = tryReadFilePath D.getSymbolicLinkTarget {-# INLINE getSymbolicLinkTarget #-} getPermissions :: Exception e => ReadFilePathT e IO Permissions getPermissions = tryReadFilePath D.getPermissions {-# INLINE getPermissions #-} setPermissions :: Exception e => Permissions -> ReadFilePathT1 e IO setPermissions p = tryReadFilePath (`D.setPermissions` p) {-# INLINE setPermissions #-} copyPermissions :: Exception e => FilePath -> ReadFilePathT1 e IO copyPermissions = tryReadFilePath . D.copyPermissions {-# INLINE copyPermissions #-} getAccessTime :: Exception e => ReadFilePathT e IO UTCTime getAccessTime = tryReadFilePath D.getAccessTime {-# INLINE getAccessTime #-} getModificationTime :: Exception e => ReadFilePathT e IO UTCTime getModificationTime = tryReadFilePath D.getModificationTime {-# INLINE getModificationTime #-} setAccessTime :: Exception e => UTCTime -> ReadFilePathT1 e IO setAccessTime u = tryReadFilePath (`D.setAccessTime` u) {-# INLINE setAccessTime #-} setModificationTime :: Exception e => UTCTime -> ReadFilePathT1 e IO setModificationTime u = tryReadFilePath (`D.setModificationTime` u) {-# INLINE setModificationTime #-}