| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Effectful.FileSystem
Synopsis
- data FileSystem (a :: Type -> Type) b
- runFileSystem :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => Eff (FileSystem ': es) a -> Eff es a
- createDirectory :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es ()
- createDirectoryIfMissing :: forall (es :: [Effect]). FileSystem :> es => Bool -> FilePath -> Eff es ()
- removeDirectory :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es ()
- removeDirectoryRecursive :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es ()
- removePathForcibly :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es ()
- renameDirectory :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es ()
- listDirectory :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es [FilePath]
- getDirectoryContents :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es [FilePath]
- getCurrentDirectory :: forall (es :: [Effect]). FileSystem :> es => Eff es FilePath
- setCurrentDirectory :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es ()
- withCurrentDirectory :: forall (es :: [Effect]) a. FileSystem :> es => FilePath -> Eff es a -> Eff es a
- getHomeDirectory :: forall (es :: [Effect]). FileSystem :> es => Eff es FilePath
- getXdgDirectory :: forall (es :: [Effect]). FileSystem :> es => XdgDirectory -> FilePath -> Eff es FilePath
- getXdgDirectoryList :: forall (es :: [Effect]). FileSystem :> es => XdgDirectoryList -> Eff es [FilePath]
- getAppUserDataDirectory :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es FilePath
- getUserDocumentsDirectory :: forall (es :: [Effect]). FileSystem :> es => Eff es FilePath
- getTemporaryDirectory :: forall (es :: [Effect]). FileSystem :> es => Eff es FilePath
- removeFile :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es ()
- renameFile :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es ()
- renamePath :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es ()
- copyFile :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es ()
- copyFileWithMetadata :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es ()
- getFileSize :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es Integer
- canonicalizePath :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es FilePath
- makeAbsolute :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es FilePath
- makeRelativeToCurrentDirectory :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es FilePath
- doesPathExist :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es Bool
- doesFileExist :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es Bool
- doesDirectoryExist :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es Bool
- findExecutable :: forall (es :: [Effect]). FileSystem :> es => String -> Eff es (Maybe FilePath)
- findExecutables :: forall (es :: [Effect]). FileSystem :> es => String -> Eff es [FilePath]
- findExecutablesInDirectories :: forall (es :: [Effect]). FileSystem :> es => [FilePath] -> String -> Eff es [FilePath]
- findFile :: forall (es :: [Effect]). FileSystem :> es => [FilePath] -> String -> Eff es (Maybe FilePath)
- findFiles :: forall (es :: [Effect]). FileSystem :> es => [FilePath] -> String -> Eff es [FilePath]
- findFileWith :: forall (es :: [Effect]). FileSystem :> es => (FilePath -> Eff es Bool) -> [FilePath] -> String -> Eff es (Maybe FilePath)
- findFilesWith :: forall (es :: [Effect]). FileSystem :> es => (FilePath -> Eff es Bool) -> [FilePath] -> String -> Eff es [FilePath]
- createFileLink :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es ()
- createDirectoryLink :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es ()
- removeDirectoryLink :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es ()
- pathIsSymbolicLink :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es Bool
- getSymbolicLinkTarget :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es FilePath
- getPermissions :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es Permissions
- setPermissions :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Permissions -> Eff es ()
- copyPermissions :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es ()
- getAccessTime :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es UTCTime
- getModificationTime :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es UTCTime
- setAccessTime :: forall (es :: [Effect]). FileSystem :> es => FilePath -> UTCTime -> Eff es ()
- setModificationTime :: forall (es :: [Effect]). FileSystem :> es => FilePath -> UTCTime -> Eff es ()
- data XdgDirectory
- data XdgDirectoryList
- exeExtension :: String
- data Permissions
- emptyPermissions :: Permissions
- readable :: Permissions -> Bool
- writable :: Permissions -> Bool
- executable :: Permissions -> Bool
- searchable :: Permissions -> Bool
- setOwnerReadable :: Bool -> Permissions -> Permissions
- setOwnerWritable :: Bool -> Permissions -> Permissions
- setOwnerExecutable :: Bool -> Permissions -> Permissions
- setOwnerSearchable :: Bool -> Permissions -> Permissions
Effect
data FileSystem (a :: Type -> Type) b Source #
An effect for interacting with the filesystem.
Instances
| type DispatchOf FileSystem Source # | |
Defined in Effectful.FileSystem.Effect | |
| data StaticRep FileSystem Source # | |
Defined in Effectful.FileSystem.Effect | |
Handlers
runFileSystem :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => Eff (FileSystem ': es) a -> Eff es a Source #
Run the FileSystem effect.
Actions on directories
createDirectory :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es () Source #
Lifted createDirectory.
createDirectoryIfMissing :: forall (es :: [Effect]). FileSystem :> es => Bool -> FilePath -> Eff es () Source #
Lifted createDirectoryIfMissing.
removeDirectory :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es () Source #
Lifted removeDirectory.
removeDirectoryRecursive :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es () Source #
Lifted removeDirectoryRecursive.
removePathForcibly :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es () Source #
Lifted removePathForcibly.
renameDirectory :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted renameDirectory.
listDirectory :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es [FilePath] Source #
Lifted listDirectory.
getDirectoryContents :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es [FilePath] Source #
Lifted getDirectoryContents.
Current working directory
getCurrentDirectory :: forall (es :: [Effect]). FileSystem :> es => Eff es FilePath Source #
Lifted getCurrentDirectory.
setCurrentDirectory :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es () Source #
Lifted setCurrentDirectory.
withCurrentDirectory :: forall (es :: [Effect]) a. FileSystem :> es => FilePath -> Eff es a -> Eff es a Source #
Lifted withCurrentDirectory.
Pre-defined directories
getHomeDirectory :: forall (es :: [Effect]). FileSystem :> es => Eff es FilePath Source #
Lifted getHomeDirectory.
getXdgDirectory :: forall (es :: [Effect]). FileSystem :> es => XdgDirectory -> FilePath -> Eff es FilePath Source #
Lifted getXdgDirectory.
getXdgDirectoryList :: forall (es :: [Effect]). FileSystem :> es => XdgDirectoryList -> Eff es [FilePath] Source #
Lifted getXdgDirectoryList.
getAppUserDataDirectory :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es FilePath Source #
Lifted getAppUserDataDirectory.
getUserDocumentsDirectory :: forall (es :: [Effect]). FileSystem :> es => Eff es FilePath Source #
Lifted getUserDocumentsDirectory.
getTemporaryDirectory :: forall (es :: [Effect]). FileSystem :> es => Eff es FilePath Source #
Lifted getTemporaryDirectory.
Actions on files
removeFile :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es () Source #
Lifted removeFile.
renameFile :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted renameFile.
renamePath :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted renamePath.
copyFile :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted copyFile.
copyFileWithMetadata :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted copyFileWithMetadata.
getFileSize :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es Integer Source #
Lifted getFileSize.
canonicalizePath :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es FilePath Source #
Lifted canonicalizePath.
makeAbsolute :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es FilePath Source #
Lifted makeAbsolute.
makeRelativeToCurrentDirectory :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es FilePath Source #
Lifted makeRelativeToCurrentDirectory.
Existence tests
doesPathExist :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es Bool Source #
Lifted doesPathExist.
doesFileExist :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es Bool Source #
Lifted doesFileExist.
doesDirectoryExist :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es Bool Source #
Lifted doesDirectoryExist.
findExecutable :: forall (es :: [Effect]). FileSystem :> es => String -> Eff es (Maybe FilePath) Source #
Lifted findExecutable.
findExecutables :: forall (es :: [Effect]). FileSystem :> es => String -> Eff es [FilePath] Source #
Lifted findExecutables.
findExecutablesInDirectories :: forall (es :: [Effect]). FileSystem :> es => [FilePath] -> String -> Eff es [FilePath] Source #
Lifted findExecutablesInDirectories.
findFile :: forall (es :: [Effect]). FileSystem :> es => [FilePath] -> String -> Eff es (Maybe FilePath) Source #
Lifted findFile.
findFiles :: forall (es :: [Effect]). FileSystem :> es => [FilePath] -> String -> Eff es [FilePath] Source #
Lifted findFiles.
findFileWith :: forall (es :: [Effect]). FileSystem :> es => (FilePath -> Eff es Bool) -> [FilePath] -> String -> Eff es (Maybe FilePath) Source #
Lifted findFileWith.
findFilesWith :: forall (es :: [Effect]). FileSystem :> es => (FilePath -> Eff es Bool) -> [FilePath] -> String -> Eff es [FilePath] Source #
Lifted findFilesWith.
Symbolic links
createFileLink :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted createFileLink.
createDirectoryLink :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted createDirectoryLink.
removeDirectoryLink :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es () Source #
Lifted removeDirectoryLink.
pathIsSymbolicLink :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es Bool Source #
Lifted pathIsSymbolicLink.
getSymbolicLinkTarget :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es FilePath Source #
Lifted getSymbolicLinkTarget.
Permissions
getPermissions :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es Permissions Source #
Lifted getPermissions.
setPermissions :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Permissions -> Eff es () Source #
Lifted setPermissions.
copyPermissions :: forall (es :: [Effect]). FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted copyPermissions.
Timestamps
getAccessTime :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es UTCTime Source #
Lifted getAccessTime.
getModificationTime :: forall (es :: [Effect]). FileSystem :> es => FilePath -> Eff es UTCTime Source #
Lifted getModificationTime.
setAccessTime :: forall (es :: [Effect]). FileSystem :> es => FilePath -> UTCTime -> Eff es () Source #
Lifted setAccessTime.
setModificationTime :: forall (es :: [Effect]). FileSystem :> es => FilePath -> UTCTime -> Eff es () Source #
Lifted setModificationTime.
Re-exports
Pre-defined directories
data XdgDirectory #
Special directories for storing user-specific application data, configuration, and cache files, as specified by the XDG Base Directory Specification.
Note: On Windows, XdgData and XdgConfig usually map to the same
directory.
Since: directory-1.2.3.0
Constructors
| XdgData | For data files (e.g. images).
It uses the |
| XdgConfig | For configuration files.
It uses the |
| XdgCache | For non-essential files (e.g. cache).
It uses the |
| XdgState | For data that should persist between (application) restarts,
but that is not important or portable enough to the user that it
should be stored in Since: directory-1.3.7.0 |
Instances
data XdgDirectoryList #
Search paths for various application data, as specified by the XDG Base Directory Specification.
The list of paths is split using searchPathSeparator,
which on Windows is a semicolon.
Note: On Windows, XdgDataDirs and XdgConfigDirs usually yield the same
result.
Since: directory-1.3.2.0
Constructors
| XdgDataDirs | For data files (e.g. images).
It uses the |
| XdgConfigDirs | For configuration files.
It uses the |
Instances
Existence tests
exeExtension :: String #
Filename extension for executable files (including the dot if any)
(usually "" on POSIX systems and ".exe" on Windows or OS/2).
Since: directory-1.2.4.0
Permissions
data Permissions #
Instances
| Read Permissions | |
Defined in System.Directory.Internal.Common Methods readsPrec :: Int -> ReadS Permissions # readList :: ReadS [Permissions] # readPrec :: ReadPrec Permissions # readListPrec :: ReadPrec [Permissions] # | |
| Show Permissions | |
Defined in System.Directory.Internal.Common Methods showsPrec :: Int -> Permissions -> ShowS # show :: Permissions -> String # showList :: [Permissions] -> ShowS # | |
| Eq Permissions | |
Defined in System.Directory.Internal.Common | |
| Ord Permissions | |
Defined in System.Directory.Internal.Common Methods compare :: Permissions -> Permissions -> Ordering # (<) :: Permissions -> Permissions -> Bool # (<=) :: Permissions -> Permissions -> Bool # (>) :: Permissions -> Permissions -> Bool # (>=) :: Permissions -> Permissions -> Bool # max :: Permissions -> Permissions -> Permissions # min :: Permissions -> Permissions -> Permissions # | |
readable :: Permissions -> Bool #
writable :: Permissions -> Bool #
executable :: Permissions -> Bool #
searchable :: Permissions -> Bool #
setOwnerReadable :: Bool -> Permissions -> Permissions #
setOwnerWritable :: Bool -> Permissions -> Permissions #
setOwnerExecutable :: Bool -> Permissions -> Permissions #
setOwnerSearchable :: Bool -> Permissions -> Permissions #