Safe Haskell | None |
---|---|
Language | GHC2021 |
Effectful.FileSystem.PathReader.Static
Description
Provides a static effect for the readable portion of System.Directory's interface. For the static interface of the entire System.Directory interface, see https://hackage.haskell.org/package/effectful-2.2.2.0/docs/Effectful-FileSystem.html.
Since: 0.1
Synopsis
- data PathReader (a :: Type -> Type) b
- listDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es [OsPath]
- getDirectoryContents :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es [OsPath]
- getCurrentDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => Eff es OsPath
- getHomeDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => Eff es OsPath
- getXdgDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => XdgDirectory -> OsPath -> Eff es OsPath
- getXdgDirectoryList :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => XdgDirectoryList -> Eff es [OsPath]
- getAppUserDataDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath
- getUserDocumentsDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => Eff es OsPath
- getTemporaryDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => Eff es OsPath
- getFileSize :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Integer
- canonicalizePath :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath
- makeAbsolute :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath
- makeRelativeToCurrentDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath
- doesPathExist :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Bool
- doesFileExist :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Bool
- doesDirectoryExist :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Bool
- findExecutable :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es (Maybe OsPath)
- findExecutables :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es [OsPath]
- findExecutablesInDirectories :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => [OsPath] -> OsPath -> Eff es [OsPath]
- findFileWith :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => (OsPath -> Eff es Bool) -> [OsPath] -> OsPath -> Eff es (Maybe OsPath)
- findFilesWith :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => (OsPath -> Eff es Bool) -> [OsPath] -> OsPath -> Eff es [OsPath]
- pathIsSymbolicLink :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Bool
- getSymbolicLinkTarget :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath
- getPermissions :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Permissions
- getAccessTime :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es UTCTime
- getModificationTime :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es UTCTime
- runPathReader :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => Eff (PathReader ': es) a -> Eff es a
- findFile :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => [OsPath] -> OsPath -> Eff es (Maybe OsPath)
- findFiles :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => [OsPath] -> OsPath -> Eff es [OsPath]
- getXdgData :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath
- getXdgConfig :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath
- getXdgCache :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath
- getXdgState :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath
- data PathType
- displayPathType :: IsString a => PathType -> a
- getPathType :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es PathType
- isPathType :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => PathType -> OsPath -> Eff es Bool
- throwIfWrongPathType :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => String -> PathType -> OsPath -> Eff es ()
- expandTilde :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath
- forExpandedTilde :: forall (es :: [Effect]) a. (HasCallStack, PathReader :> es) => OsPath -> (OsPath -> Eff es a) -> Eff es a
- onExpandedTilde :: forall (es :: [Effect]) a. (HasCallStack, PathReader :> es) => (OsPath -> Eff es a) -> OsPath -> Eff es a
- listDirectoryRecursive :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es ([OsPath], [OsPath])
- listDirectoryRecursiveSymbolicLink :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es ([OsPath], [OsPath], [OsPath])
- doesSymbolicLinkExist :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Bool
- pathIsSymbolicDirectoryLink :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Bool
- pathIsSymbolicFileLink :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Bool
- type OsPath = OsString
- data Permissions
- data UTCTime = UTCTime {
- utctDay :: Day
- utctDayTime :: DiffTime
- data XdgDirectory
- data XdgDirectoryList
Effect
data PathReader (a :: Type -> Type) b Source #
Static effect for reading paths.
Since: 0.1
Instances
type DispatchOf PathReader Source # | |
Defined in Effectful.FileSystem.PathReader.Static | |
data StaticRep PathReader Source # | |
Defined in Effectful.FileSystem.PathReader.Static |
Functions
listDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es [OsPath] Source #
Lifted listDirectory
.
Since: 0.1
getDirectoryContents :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es [OsPath] Source #
Lifted getDirectoryContents
.
Since: 0.1
getCurrentDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => Eff es OsPath Source #
Lifted getCurrentDirectory
.
Since: 0.1
getHomeDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => Eff es OsPath Source #
Lifted getHomeDirectory
.
Since: 0.1
getXdgDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => XdgDirectory -> OsPath -> Eff es OsPath Source #
Lifted getXdgDirectory
.
Since: 0.1
getXdgDirectoryList :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => XdgDirectoryList -> Eff es [OsPath] Source #
Lifted getXdgDirectoryList
.
Since: 0.1
getAppUserDataDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath Source #
Lifted getAppUserDataDirectory
.
Since: 0.1
getUserDocumentsDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => Eff es OsPath Source #
Lifted getUserDocumentsDirectory
.
Since: 0.1
getTemporaryDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => Eff es OsPath Source #
Lifted getTemporaryDirectory
.
Since: 0.1
getFileSize :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Integer Source #
Lifted getFileSize
.
Since: 0.1
canonicalizePath :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath Source #
Lifted canonicalizePath
.
Since: 0.1
makeAbsolute :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath Source #
Lifted makeAbsolute
.
Since: 0.1
makeRelativeToCurrentDirectory :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath Source #
Lifted makeRelativeToCurrentDirectory
.
Since: 0.1
doesPathExist :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Bool Source #
Lifted doesPathExist
.
Since: 0.1
doesFileExist :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Bool Source #
Lifted doesFileExist
.
Since: 0.1
doesDirectoryExist :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Bool Source #
Lifted doesDirectoryExist
.
Since: 0.1
findExecutable :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es (Maybe OsPath) Source #
Lifted findExecutable
.
Since: 0.1
findExecutables :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es [OsPath] Source #
Lifted findExecutables
.
Since: 0.1
findExecutablesInDirectories :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => [OsPath] -> OsPath -> Eff es [OsPath] Source #
Lifted findExecutablesInDirectories
.
Since: 0.1
findFileWith :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => (OsPath -> Eff es Bool) -> [OsPath] -> OsPath -> Eff es (Maybe OsPath) Source #
Lifted findFileWith
.
Since: 0.1
findFilesWith :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => (OsPath -> Eff es Bool) -> [OsPath] -> OsPath -> Eff es [OsPath] Source #
Lifted findFilesWith
.
Since: 0.1
pathIsSymbolicLink :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Bool Source #
Lifted pathIsSymbolicLink
.
Since: 0.1
getSymbolicLinkTarget :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath Source #
Lifted getSymbolicLinkTarget
.
Since: 0.1
getPermissions :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Permissions Source #
Lifted getPermissions
.
Since: 0.1
getAccessTime :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es UTCTime Source #
Lifted getAccessTime
.
Since: 0.1
getModificationTime :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es UTCTime Source #
Lifted getModificationTime
.
Since: 0.1
Handlers
runPathReader :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => Eff (PathReader ': es) a -> Eff es a Source #
Runs an PathReader
effect in IO.
Since: 0.1
Functions
findFile :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => [OsPath] -> OsPath -> Eff es (Maybe OsPath) Source #
Search through the given list of directories for the given file.
The behavior is equivalent to findFileWith
, returning only the first
occurrence. Details can be found in the documentation of findFileWith
.
Since: 0.1
findFiles :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => [OsPath] -> OsPath -> Eff es [OsPath] Source #
Search through the given list of directories for the given file and returns all paths where the given file exists.
The behavior is equivalent to findFilesWith
. Details can be found in the
documentation of findFilesWith
.
Since: 0.1
XDG Utils
getXdgData :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath Source #
Retrieves the XDG data directory e.g. ~/.local/share
.
Since: 0.1
getXdgConfig :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath Source #
Retrieves the XDG config directory e.g. ~/.config
.
Since: 0.1
getXdgCache :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath Source #
Retrieves the XDG cache directory e.g. ~/.cache
.
Since: 0.1
getXdgState :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es OsPath Source #
Retrieves the XDG state directory e.g. ~/.local/state
.
Since: 0.1
Path Types
Path type.
Since: fs-utils-0.1
Constructors
PathTypeFile | Since: fs-utils-0.1 |
PathTypeDirectory | Since: fs-utils-0.1 |
PathTypeSymbolicLink | Since: fs-utils-0.1 |
PathTypeOther | Since: fs-utils-0.1 |
Instances
NFData PathType | Since: fs-utils-0.1 | ||||
Defined in FileSystem.PathType | |||||
Bounded PathType | Since: fs-utils-0.1 | ||||
Enum PathType | Since: fs-utils-0.1 | ||||
Defined in FileSystem.PathType | |||||
Generic PathType | |||||
Defined in FileSystem.PathType Associated Types
| |||||
Show PathType | Since: fs-utils-0.1 | ||||
Eq PathType | Since: fs-utils-0.1 | ||||
Ord PathType | Since: fs-utils-0.1 | ||||
Defined in FileSystem.PathType | |||||
type Rep PathType | Since: fs-utils-0.1 | ||||
Defined in FileSystem.PathType type Rep PathType = D1 ('MetaData "PathType" "FileSystem.PathType" "fs-utils-0.1-539e06479b7c961598a9ab40b37c6d853cab165be3a31b07a164625401edfdce" 'False) ((C1 ('MetaCons "PathTypeFile" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PathTypeDirectory" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PathTypeSymbolicLink" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PathTypeOther" 'PrefixI 'False) (U1 :: Type -> Type))) |
Functions
displayPathType :: IsString a => PathType -> a Source #
String representation of PathType
.
Since: fs-utils-0.1
getPathType :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es PathType Source #
Returns the type for a given path without following symlinks.
Throws IOException
if the path does not exist or the type cannot be
detected.
Since: 0.1
Arguments
:: forall (es :: [Effect]). (HasCallStack, PathReader :> es) | |
=> PathType | Expected path type. |
-> OsPath | |
-> Eff es Bool |
Checks that the path type matches the expectation. Throws
IOException
if the path does not exist or the type cannot be detected.
Since: 0.1
Arguments
:: forall (es :: [Effect]). (HasCallStack, PathReader :> es) | |
=> String | The location for the thrown exception (e.g. function name) |
-> PathType | Expected path type |
-> OsPath | Path |
-> Eff es () |
Throws IOException
if the path does not exist or the expected path type
does not match actual.
Since: 0.1
Tilde expansion
Arguments
:: forall (es :: [Effect]). (HasCallStack, PathReader :> es) | |
=> OsPath | Path to potentially expand. |
-> Eff es OsPath |
onExpandedTilde
that simply returns the expanded path.
Since: 0.1
Arguments
:: forall (es :: [Effect]) a. (HasCallStack, PathReader :> es) | |
=> OsPath | Path to potentially expand. |
-> (OsPath -> Eff es a) | Action to run on the expanded path. |
-> Eff es a |
Flipped onExpandedTilde
.
Since: 0.1
Arguments
:: forall (es :: [Effect]) a. (HasCallStack, PathReader :> es) | |
=> (OsPath -> Eff es a) | Action to run on the expanded path. |
-> OsPath | Path to potentially expand. |
-> Eff es a |
Expands a "tilde prefix" (~) with the home directory, running the
action on the result. Throws an exception if the OsPath
contains any
other tildes i.e. the only expansions we allow are:
"~/..."
"~"
"~\..."
(windows only)
If the path contains no tildes, it is handled normally.
Since: 0.1
Misc
listDirectoryRecursive Source #
Arguments
:: forall (es :: [Effect]). (HasCallStack, PathReader :> es) | |
=> OsPath | Root path. |
-> Eff es ([OsPath], [OsPath]) | (files, directories) |
Retrieves the recursive directory contents; splits the sub folders and directories apart.
Since: 0.1
listDirectoryRecursiveSymbolicLink Source #
Arguments
:: forall (es :: [Effect]). (HasCallStack, PathReader :> es) | |
=> OsPath | Root path. |
-> Eff es ([OsPath], [OsPath], [OsPath]) | (files, directories, symbolic links) |
Like listDirectoryRecursive
except symbolic links are not traversed
i.e. they are returned separately.
Since: 0.1
doesSymbolicLinkExist :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Bool Source #
Returns true if the path is a symbolic link. Does not traverse the link.
Since: 0.1
pathIsSymbolicDirectoryLink :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Bool Source #
Returns true if p
is a symbolic link and it points to an extant
directory. Throws an exception if the path is not a symbolic link or the
target does not exist.
This function and pathIsSymbolicFileLink
are intended to distinguish file
and directory links on Windows. This matters for knowing when to use:
createFileLink
vs.createDirectoryLink
removeFile
vs.removeDirectoryLink
Suppose we want to copy an arbitrary path p
. We first determine that
p
is a symlink via doesSymbolicLinkExist
. If
pathIsSymbolicDirectoryLink
returns true then we know we should use
Effects.FileSystem.PathWriter's createDirectoryLink
. Otherwise we can
fall back to createFileLink
.
Because this relies on the symlink's target, this is best effort, and it is
possible pathIsSymbolicDirectoryLink
and pathIsSymbolicFileLink
both
return false.
Note that Posix makes no distinction between file and directory symbolic links. Thus if your system only has to work on Posix, you probably don't need this function.
Since: 0.1
pathIsSymbolicFileLink :: forall (es :: [Effect]). (HasCallStack, PathReader :> es) => OsPath -> Eff es Bool Source #
Like pathIsSymbolicDirectoryLink
but for files.
Since: 0.1
Re-exports
Type representing filenames/pathnames.
This type doesn't add any guarantees over OsString
.
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 # |
This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.
Constructors
UTCTime | |
Fields
|
Instances
NFData UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime | |
Data UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UTCTime -> c UTCTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UTCTime # toConstr :: UTCTime -> Constr # dataTypeOf :: UTCTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UTCTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UTCTime) # gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r # gmapQ :: (forall d. Data d => d -> u) -> UTCTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UTCTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # | |
Eq UTCTime | |
Ord UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime | |
ISO8601 UTCTime |
|
Defined in Data.Time.Format.ISO8601 Methods |
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 |