Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data FileSystem :: Effect
- runFileSystem :: IOE :> es => Eff (FileSystem ': es) a -> Eff es a
- createDirectory :: FileSystem :> es => FilePath -> Eff es ()
- createDirectoryIfMissing :: FileSystem :> es => Bool -> FilePath -> Eff es ()
- removeDirectory :: FileSystem :> es => FilePath -> Eff es ()
- removeDirectoryRecursive :: FileSystem :> es => FilePath -> Eff es ()
- removePathForcibly :: FileSystem :> es => FilePath -> Eff es ()
- renameDirectory :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
- listDirectory :: FileSystem :> es => FilePath -> Eff es [FilePath]
- getDirectoryContents :: FileSystem :> es => FilePath -> Eff es [FilePath]
- getCurrentDirectory :: FileSystem :> es => Eff es FilePath
- setCurrentDirectory :: FileSystem :> es => FilePath -> Eff es ()
- withCurrentDirectory :: FileSystem :> es => FilePath -> Eff es a -> Eff es a
- getHomeDirectory :: FileSystem :> es => Eff es FilePath
- getXdgDirectory :: FileSystem :> es => XdgDirectory -> FilePath -> Eff es FilePath
- getXdgDirectoryList :: FileSystem :> es => XdgDirectoryList -> Eff es [FilePath]
- getAppUserDataDirectory :: FileSystem :> es => FilePath -> Eff es FilePath
- getUserDocumentsDirectory :: FileSystem :> es => Eff es FilePath
- getTemporaryDirectory :: FileSystem :> es => Eff es FilePath
- removeFile :: FileSystem :> es => FilePath -> Eff es ()
- renameFile :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
- renamePath :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
- copyFile :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
- copyFileWithMetadata :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
- getFileSize :: FileSystem :> es => FilePath -> Eff es Integer
- canonicalizePath :: FileSystem :> es => FilePath -> Eff es FilePath
- makeAbsolute :: FileSystem :> es => FilePath -> Eff es FilePath
- makeRelativeToCurrentDirectory :: FileSystem :> es => FilePath -> Eff es FilePath
- doesPathExist :: FileSystem :> es => FilePath -> Eff es Bool
- doesFileExist :: FileSystem :> es => FilePath -> Eff es Bool
- doesDirectoryExist :: FileSystem :> es => FilePath -> Eff es Bool
- findExecutable :: FileSystem :> es => String -> Eff es (Maybe FilePath)
- findExecutables :: FileSystem :> es => String -> Eff es [FilePath]
- findExecutablesInDirectories :: FileSystem :> es => [FilePath] -> String -> Eff es [FilePath]
- findFile :: FileSystem :> es => [FilePath] -> String -> Eff es (Maybe FilePath)
- findFiles :: FileSystem :> es => [FilePath] -> String -> Eff es [FilePath]
- findFileWith :: FileSystem :> es => (FilePath -> Eff es Bool) -> [FilePath] -> String -> Eff es (Maybe FilePath)
- findFilesWith :: FileSystem :> es => (FilePath -> Eff es Bool) -> [FilePath] -> String -> Eff es [FilePath]
- createFileLink :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
- createDirectoryLink :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
- removeDirectoryLink :: FileSystem :> es => FilePath -> Eff es ()
- pathIsSymbolicLink :: FileSystem :> es => FilePath -> Eff es Bool
- getSymbolicLinkTarget :: FileSystem :> es => FilePath -> Eff es FilePath
- getPermissions :: FileSystem :> es => FilePath -> Eff es Permissions
- setPermissions :: FileSystem :> es => FilePath -> Permissions -> Eff es ()
- copyPermissions :: FileSystem :> es => FilePath -> FilePath -> Eff es ()
- getAccessTime :: FileSystem :> es => FilePath -> Eff es UTCTime
- getModificationTime :: FileSystem :> es => FilePath -> Eff es UTCTime
- setAccessTime :: FileSystem :> es => FilePath -> UTCTime -> Eff es ()
- setModificationTime :: 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 :: Effect 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 :: IOE :> es => Eff (FileSystem ': es) a -> Eff es a Source #
Run the FileSystem
effect.
Actions on directories
createDirectory :: FileSystem :> es => FilePath -> Eff es () Source #
Lifted createDirectory
.
createDirectoryIfMissing :: FileSystem :> es => Bool -> FilePath -> Eff es () Source #
Lifted createDirectoryIfMissing
.
removeDirectory :: FileSystem :> es => FilePath -> Eff es () Source #
Lifted removeDirectory
.
removeDirectoryRecursive :: FileSystem :> es => FilePath -> Eff es () Source #
Lifted removeDirectoryRecursive
.
removePathForcibly :: FileSystem :> es => FilePath -> Eff es () Source #
Lifted removePathForcibly
.
renameDirectory :: FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted renameDirectory
.
listDirectory :: FileSystem :> es => FilePath -> Eff es [FilePath] Source #
Lifted listDirectory
.
getDirectoryContents :: FileSystem :> es => FilePath -> Eff es [FilePath] Source #
Lifted getDirectoryContents
.
Current working directory
getCurrentDirectory :: FileSystem :> es => Eff es FilePath Source #
Lifted getCurrentDirectory
.
setCurrentDirectory :: FileSystem :> es => FilePath -> Eff es () Source #
Lifted setCurrentDirectory
.
withCurrentDirectory :: FileSystem :> es => FilePath -> Eff es a -> Eff es a Source #
Lifted withCurrentDirectory
.
Pre-defined directories
getHomeDirectory :: FileSystem :> es => Eff es FilePath Source #
Lifted getHomeDirectory
.
getXdgDirectory :: FileSystem :> es => XdgDirectory -> FilePath -> Eff es FilePath Source #
Lifted getXdgDirectory
.
getXdgDirectoryList :: FileSystem :> es => XdgDirectoryList -> Eff es [FilePath] Source #
Lifted getXdgDirectoryList
.
getAppUserDataDirectory :: FileSystem :> es => FilePath -> Eff es FilePath Source #
Lifted getAppUserDataDirectory
.
getUserDocumentsDirectory :: FileSystem :> es => Eff es FilePath Source #
Lifted getUserDocumentsDirectory
.
getTemporaryDirectory :: FileSystem :> es => Eff es FilePath Source #
Lifted getTemporaryDirectory
.
Actions on files
removeFile :: FileSystem :> es => FilePath -> Eff es () Source #
Lifted removeFile
.
renameFile :: FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted renameFile
.
renamePath :: FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted renamePath
.
copyFileWithMetadata :: FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted copyFileWithMetadata
.
getFileSize :: FileSystem :> es => FilePath -> Eff es Integer Source #
Lifted getFileSize
.
canonicalizePath :: FileSystem :> es => FilePath -> Eff es FilePath Source #
Lifted canonicalizePath
.
makeAbsolute :: FileSystem :> es => FilePath -> Eff es FilePath Source #
Lifted makeAbsolute
.
makeRelativeToCurrentDirectory :: FileSystem :> es => FilePath -> Eff es FilePath Source #
Lifted makeRelativeToCurrentDirectory
.
Existence tests
doesPathExist :: FileSystem :> es => FilePath -> Eff es Bool Source #
Lifted doesPathExist
.
doesFileExist :: FileSystem :> es => FilePath -> Eff es Bool Source #
Lifted doesFileExist
.
doesDirectoryExist :: FileSystem :> es => FilePath -> Eff es Bool Source #
Lifted doesDirectoryExist
.
findExecutable :: FileSystem :> es => String -> Eff es (Maybe FilePath) Source #
Lifted findExecutable
.
findExecutables :: FileSystem :> es => String -> Eff es [FilePath] Source #
Lifted findExecutables
.
findExecutablesInDirectories :: FileSystem :> es => [FilePath] -> String -> Eff es [FilePath] Source #
Lifted findExecutablesInDirectories
.
findFile :: FileSystem :> es => [FilePath] -> String -> Eff es (Maybe FilePath) Source #
Lifted findFile
.
findFiles :: FileSystem :> es => [FilePath] -> String -> Eff es [FilePath] Source #
Lifted findFiles
.
findFileWith :: FileSystem :> es => (FilePath -> Eff es Bool) -> [FilePath] -> String -> Eff es (Maybe FilePath) Source #
Lifted findFileWith
.
findFilesWith :: FileSystem :> es => (FilePath -> Eff es Bool) -> [FilePath] -> String -> Eff es [FilePath] Source #
Lifted findFilesWith
.
Symbolic links
createFileLink :: FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted createFileLink
.
createDirectoryLink :: FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted createDirectoryLink
.
removeDirectoryLink :: FileSystem :> es => FilePath -> Eff es () Source #
Lifted removeDirectoryLink
.
pathIsSymbolicLink :: FileSystem :> es => FilePath -> Eff es Bool Source #
Lifted pathIsSymbolicLink
.
getSymbolicLinkTarget :: FileSystem :> es => FilePath -> Eff es FilePath Source #
Lifted getSymbolicLinkTarget
.
Permissions
getPermissions :: FileSystem :> es => FilePath -> Eff es Permissions Source #
Lifted getPermissions
.
setPermissions :: FileSystem :> es => FilePath -> Permissions -> Eff es () Source #
Lifted setPermissions
.
copyPermissions :: FileSystem :> es => FilePath -> FilePath -> Eff es () Source #
Lifted copyPermissions
.
Timestamps
getAccessTime :: FileSystem :> es => FilePath -> Eff es UTCTime Source #
Lifted getAccessTime
.
getModificationTime :: FileSystem :> es => FilePath -> Eff es UTCTime Source #
Lifted getModificationTime
.
setAccessTime :: FileSystem :> es => FilePath -> UTCTime -> Eff es () Source #
Lifted setAccessTime
.
setModificationTime :: 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
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 |
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
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 readsPrec :: Int -> ReadS Permissions # readList :: ReadS [Permissions] # readPrec :: ReadPrec Permissions # readListPrec :: ReadPrec [Permissions] # | |
Show Permissions | |
Defined in System.Directory.Internal.Common showsPrec :: Int -> Permissions -> ShowS # show :: Permissions -> String # showList :: [Permissions] -> ShowS # | |
Eq Permissions | |
Defined in System.Directory.Internal.Common (==) :: Permissions -> Permissions -> Bool # (/=) :: Permissions -> Permissions -> Bool # | |
Ord Permissions | |
Defined in System.Directory.Internal.Common 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 #