Stability | unstable |
---|---|
Portability | unportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
System.Directory.Internal
Description
Internal modules are always subject to change from version to version. The contents of this module are also platform-dependent, hence what is shown in the Hackage documentation may differ from what is actually available on your system.
Synopsis
- newtypeListT m a = ListT {}
- dataXdgDirectory
- dataXdgDirectoryList
- dataPermissions = Permissions {
- readable :: Bool
- writable :: Bool
- executable :: Bool
- searchable :: Bool
- dataWhetherFollow
- dataFileType
- withBinaryFile :: OsPath -> IOMode -> (Handle -> IO r) -> IO r
- os :: String -> OsString
- emptyListT :: Applicative m => ListT m a
- maybeToListT :: Applicative m => m (Maybe a) -> ListT m a
- listToListT :: Applicative m => [a] -> ListT m a
- liftJoinListT :: Monad m => m (ListT m a) -> ListT m a
- listTHead :: Functor m => ListT m a -> m (Maybe a)
- listTToList :: Monad m => ListT m a -> m [a]
- andM :: Monad m => m Bool -> m Bool -> m Bool
- sequenceWithIOErrors_ :: [IO ()] -> IO ()
- tryIOErrorType :: (IOError -> Bool) -> IO a -> IO (EitherIOError a)
- ignoreIOExceptions :: IO () -> IO ()
- specializeErrorString :: String -> (IOError -> Bool) -> IO a -> IO a
- ioeAddLocation :: IOError -> String -> IOError
- rightOrError :: Exception e => Either e a -> a
- so :: OsString -> String
- ioeSetOsPath :: IOError -> OsPath -> IOError
- dropSpecialDotDirs :: [OsPath] -> [OsPath]
- expandDots :: [OsPath] -> [OsPath]
- normalisePathSeps :: OsPath -> OsPath
- normaliseTrailingSep :: OsPath -> OsPath
- emptyToCurDir :: OsPath -> OsPath
- simplifyPosix :: OsPath -> OsPath
- simplifyWindows :: OsPath -> OsPath
- isNoFollow :: WhetherFollow -> Bool
- fileTypeIsDirectory :: FileType -> Bool
- fileTypeIsLink :: FileType -> Bool
- copyHandleData :: Handle -> Handle -> IO ()
- typeOsPath = OsString
- dataOsString
- c_AT_FDCWD :: Fd
- c_AT_SYMLINK_NOFOLLOW :: CInt
- atWhetherFollow :: WhetherFollow -> CInt
- defaultOpenFlags :: OpenFileFlags
- typeRawHandle = Fd
- openRaw :: WhetherFollow -> MaybeRawHandle -> OsPath -> IORawHandle
- closeRaw :: RawHandle -> IO ()
- createDirectoryInternal :: OsPath -> IO ()
- c_unlinkat :: Fd -> CString -> CInt -> IOCInt
- removePathAt :: FileType -> MaybeRawHandle -> OsPath -> IO ()
- removePathInternal :: Bool -> OsPath -> IO ()
- renamePathInternal :: OsPath -> OsPath -> IO ()
- filesAlwaysRemovable :: Bool
- simplify :: OsPath -> OsPath
- c_free :: Ptr a -> IO ()
- c_PATH_MAX :: MaybeInt
- c_realpath :: CString -> CString -> IOCString
- withRealpath :: CString -> (CString -> IO a) -> IO a
- realPath :: OsPath -> IOOsPath
- canonicalizePathSimplify :: OsPath -> IOOsPath
- findExecutablesLazyInternal :: ([OsPath] -> OsString -> ListTIOOsPath) -> OsString -> ListTIOOsPath
- exeExtensionInternal :: OsString
- openDirFromFd :: Fd -> IODirStream
- readDirStreamToEnd :: DirStream -> IO [OsPath]
- readDirToEnd :: RawHandle -> IO [OsPath]
- getDirectoryContentsInternal :: OsPath -> IO [OsPath]
- getCurrentDirectoryInternal :: IOOsPath
- prependCurrentDirectory :: OsPath -> IOOsPath
- setCurrentDirectoryInternal :: OsPath -> IO ()
- linkToDirectoryIsDirectory :: Bool
- createHardLink :: OsPath -> OsPath -> IO ()
- createSymbolicLink :: Bool -> OsPath -> OsPath -> IO ()
- readSymbolicLink :: OsPath -> IOOsPath
- typeMetadata = FileStatus
- c_fstatat :: Fd -> CString -> PtrCStat -> CInt -> IOCInt
- getMetadataAt :: WhetherFollow -> MaybeRawHandle -> OsPath -> IOMetadata
- getSymbolicLinkMetadata :: OsPath -> IOMetadata
- getFileMetadata :: OsPath -> IOMetadata
- fileTypeFromMetadata :: Metadata -> FileType
- fileSizeFromMetadata :: Metadata -> Integer
- accessTimeFromMetadata :: Metadata -> UTCTime
- modificationTimeFromMetadata :: Metadata -> UTCTime
- typeMode = FileMode
- modeFromMetadata :: Metadata -> Mode
- allWriteMode :: FileMode
- hasWriteMode :: Mode -> Bool
- setWriteMode :: Bool -> Mode -> Mode
- setForceRemoveMode :: Mode -> Mode
- c_fchmodat :: Fd -> CString -> FileMode -> CInt -> IOCInt
- setModeAt :: WhetherFollow -> MaybeRawHandle -> OsPath -> Mode -> IO ()
- setFileMode :: OsPath -> Mode -> IO ()
- setFilePermissions :: OsPath -> Mode -> IO ()
- getAccessPermissions :: OsPath -> IOPermissions
- setAccessPermissions :: OsPath -> Permissions -> IO ()
- copyOwnerFromStatus :: FileStatus -> OsPath -> IO ()
- copyGroupFromStatus :: FileStatus -> OsPath -> IO ()
- tryCopyOwnerAndGroupFromStatus :: FileStatus -> OsPath -> IO ()
- copyFileContents :: OsPath -> OsPath -> IO ()
- copyFileWithMetadataInternal :: (Metadata -> OsPath -> IO ()) -> (Metadata -> OsPath -> IO ()) -> OsPath -> OsPath -> IO ()
- setTimes :: OsPath -> (MaybePOSIXTime, MaybePOSIXTime) -> IO ()
- lookupEnvOs :: OsString -> IO (MaybeOsString)
- getEnvOs :: OsString -> IOOsString
- getPath :: IO [OsPath]
- getHomeDirectoryInternal :: IOOsPath
- getXdgDirectoryFallback :: IOOsPath -> XdgDirectory -> IOOsPath
- getXdgDirectoryListFallback :: XdgDirectoryList -> IO [OsPath]
- getAppUserDataDirectoryInternal :: OsPath -> IOOsPath
- getUserDocumentsDirectoryInternal :: IOOsPath
- getTemporaryDirectoryInternal :: IOOsPath
Documentation
A generator with side-effects.
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: 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: 1.3.7.0 |
Instances
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: 1.3.2.0
Constructors
XdgDataDirs | For data files (e.g. images). It uses the |
XdgConfigDirs | For configuration files. It uses the |
Instances
Constructors
Permissions | |
Fields
|
Instances
ReadPermissionsSource# | |
Defined in System.Directory.Internal.Common Methods readsPrec :: Int -> ReadSPermissions# readList :: ReadS [Permissions] # readPrec :: ReadPrecPermissions# readListPrec :: ReadPrec [Permissions] # | |
ShowPermissionsSource# | |
Defined in System.Directory.Internal.Common Methods showsPrec :: Int -> Permissions -> ShowS# show :: Permissions -> String# showList :: [Permissions] -> ShowS# | |
EqPermissionsSource# | |
Defined in System.Directory.Internal.Common | |
OrdPermissionsSource# | |
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# |
Constructors
NoFollow | |
FollowLinks |
Instances
ShowWhetherFollowSource# | |
Defined in System.Directory.Internal.Common Methods showsPrec :: Int -> WhetherFollow -> ShowS# show :: WhetherFollow -> String# showList :: [WhetherFollow] -> ShowS# |
Constructors
File | |
SymbolicLink | POSIX: either file or directory link; Windows: file link |
Directory | |
DirectoryLink | Windows only: directory link |
Instances
BoundedFileTypeSource# | |
EnumFileTypeSource# | |
ReadFileTypeSource# | |
ShowFileTypeSource# | |
EqFileTypeSource# | |
OrdFileTypeSource# | |
Defined in System.Directory.Internal.Common |
os :: String -> OsStringSource#
Fallibly converts String to OsString. Only intended to be used on literals.
emptyListT :: Applicative m => ListT m a Source#
maybeToListT :: Applicative m => m (Maybe a) -> ListT m a Source#
listToListT :: Applicative m => [a] -> ListT m a Source#
listTToList :: Monad m => ListT m a -> m [a] Source#
sequenceWithIOErrors_ :: [IO ()] -> IO () Source#
ignoreIOExceptions :: IO () -> IO () Source#
Attempt to perform the given action, silencing any IO exception thrown by it.
rightOrError :: Exception e => Either e a -> a Source#
so :: OsString -> StringSource#
Fallibly converts OsString to String. Only intended to be used on literals.
dropSpecialDotDirs :: [OsPath] -> [OsPath] Source#
expandDots :: [OsPath] -> [OsPath] Source#
Given a list of path segments, expand .
and ..
. The path segments must not contain path separators.
normalisePathSeps :: OsPath -> OsPathSource#
Convert to the right kind of slashes.
normaliseTrailingSep :: OsPath -> OsPathSource#
Remove redundant trailing slashes and pick the right kind of slash.
emptyToCurDir :: OsPath -> OsPathSource#
Convert empty paths to the current directory, otherwise leave it unchanged.
fileTypeIsDirectory :: FileType -> BoolSource#
Check whether the given FileType
is considered a directory by the operating system. This affects the choice of certain functions e.g. removeDirectory
vs removeFile
.
Copy data from one handle to another until end of file.
Type representing filenames/pathnames.
This type doesn't add any guarantees over OsString
.
Newtype representing short operating system specific strings.
Internally this is either WindowsString
or PosixString
, depending on the platform. Both use unpinned ShortByteString
for efficiency.
The constructor is only exported via System.OsString.Internal.Types, since dealing with the internals isn't generally recommended, but supported in case you need to write platform specific code.
Instances
MonoidOsString | "String-Concatenation" for |
SemigroupOsString | |
GenericOsString | |
ShowOsString | On windows, decodes as UCS-2. On unix prints the raw bytes without decoding. |
NFDataOsString | |
Defined in System.OsString.Internal.Types | |
EqOsString | Byte equality of the internal representation. |
OrdOsString | Byte ordering of the internal representation. |
Defined in System.OsString.Internal.Types | |
LiftOsString | |
typeRepOsString | |
Defined in System.OsString.Internal.Types typeRepOsString = D1 ('MetaData "OsString" "System.OsString.Internal.Types" "filepath-1.4.100.4" 'True) (C1 ('MetaCons "OsString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOsString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0PlatformString))) |
createDirectoryInternal :: OsPath -> IO () Source#
findExecutablesLazyInternal :: ([OsPath] -> OsString -> ListTIOOsPath) -> OsString -> ListTIOOsPathSource#
prependCurrentDirectory :: OsPath -> IOOsPathSource#
Convert a path into an absolute path. If the given path is relative, the current directory is prepended and the path may or may not be simplified. If the path is already absolute, the path is returned unchanged. The function preserves the presence or absence of the trailing path separator.
If the path is already absolute, the operation never fails. Otherwise, the operation may throw exceptions.
Empty paths are treated as the current directory.
setCurrentDirectoryInternal :: OsPath -> IO () Source#
typeMetadata = FileStatusSource#
getMetadataAt :: WhetherFollow -> MaybeRawHandle -> OsPath -> IOMetadataSource#
hasWriteMode :: Mode -> BoolSource#
setAccessPermissions :: OsPath -> Permissions -> IO () Source#
copyOwnerFromStatus :: FileStatus -> OsPath -> IO () Source#
copyGroupFromStatus :: FileStatus -> OsPath -> IO () Source#
tryCopyOwnerAndGroupFromStatus :: FileStatus -> OsPath -> IO () Source#
Truncate the destination file and then copy the contents of the source file to the destination file. If the destination file already exists, its attributes shall remain unchanged. Otherwise, its attributes are reset to the defaults.
copyFileWithMetadataInternal :: (Metadata -> OsPath -> IO ()) -> (Metadata -> OsPath -> IO ()) -> OsPath -> OsPath -> IO () Source#
getHomeDirectoryInternal :: IOOsPathSource#
$HOME is preferred, because the user has control over it. However, POSIX doesn't define it as a mandatory variable, so fall back to getpwuid_r
.