Stability | unstable |
---|---|
Portability | unportable |
Safe Haskell | None |
Language | Haskell2010 |
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
- andM :: Monad m => m Bool -> m Bool -> m Bool
- copyHandleData :: Handle -> Handle -> IO ()
- dropSpecialDotDirs :: [OsPath] -> [OsPath]
- emptyListT :: forall (m :: Type -> Type) a. Applicative m => ListT m a
- emptyToCurDir :: OsPath -> OsPath
- expandDots :: [OsPath] -> [OsPath]
- fileTypeIsDirectory :: FileType -> Bool
- fileTypeIsLink :: FileType -> Bool
- ignoreIOExceptions :: IO () -> IO ()
- ioeAddLocation :: IOError -> String -> IOError
- ioeSetOsPath :: IOError -> OsPath -> IOError
- isNoFollow :: WhetherFollow -> Bool
- 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]
- listToListT :: forall (m :: Type -> Type) a. Applicative m => [a] -> ListT m a
- maybeToListT :: Applicative m => m (Maybe a) -> ListT m a
- normalisePathSeps :: OsPath -> OsPath
- normaliseTrailingSep :: OsPath -> OsPath
- os :: String -> OsString
- rightOrError :: Exception e => Either e a -> a
- sequenceWithIOErrors_ :: [IO ()] -> IO ()
- simplifyPosix :: OsPath -> OsPath
- simplifyWindows :: OsPath -> OsPath
- so :: OsString -> String
- specializeErrorString :: String -> (IOError -> Bool) -> IO a -> IO a
- tryIOErrorType :: (IOError -> Bool) -> IO a -> IO (Either IOError a)
- withBinaryFile :: OsPath -> IOMode -> (Handle -> IO r) -> IO r
- data FileType
- newtype ListT (m :: Type -> Type) a = ListT {}
- data Permissions = Permissions {
- readable :: Bool
- writable :: Bool
- executable :: Bool
- searchable :: Bool
- data WhetherFollow
- data XdgDirectory
- data XdgDirectoryList
- type OsPath = OsString
- data OsString
- accessTimeFromMetadata :: Metadata -> UTCTime
- allWriteMode :: FileMode
- atWhetherFollow :: WhetherFollow -> CInt
- c_AT_FDCWD :: Fd
- c_AT_SYMLINK_NOFOLLOW :: CInt
- c_PATH_MAX :: Maybe Int
- c_fchmodat :: Fd -> CString -> FileMode -> CInt -> IO CInt
- c_free :: Ptr a -> IO ()
- c_fstatat :: Fd -> CString -> Ptr CStat -> CInt -> IO CInt
- c_realpath :: CString -> CString -> IO CString
- c_unlinkat :: Fd -> CString -> CInt -> IO CInt
- canonicalizePathSimplify :: OsPath -> IO OsPath
- closeRaw :: RawHandle -> IO ()
- copyFileContents :: OsPath -> OsPath -> IO ()
- copyFileWithMetadataInternal :: (Metadata -> OsPath -> IO ()) -> (Metadata -> OsPath -> IO ()) -> OsPath -> OsPath -> IO ()
- copyGroupFromStatus :: FileStatus -> OsPath -> IO ()
- copyOwnerFromStatus :: FileStatus -> OsPath -> IO ()
- createDirectoryInternal :: OsPath -> IO ()
- createHardLink :: OsPath -> OsPath -> IO ()
- createSymbolicLink :: Bool -> OsPath -> OsPath -> IO ()
- defaultOpenFlags :: OpenFileFlags
- exeExtensionInternal :: OsString
- fileSizeFromMetadata :: Metadata -> Integer
- fileTypeFromMetadata :: Metadata -> FileType
- filesAlwaysRemovable :: Bool
- findExecutablesLazyInternal :: ([OsPath] -> OsString -> ListT IO OsPath) -> OsString -> ListT IO OsPath
- getAccessPermissions :: OsPath -> IO Permissions
- getAppUserDataDirectoryInternal :: OsPath -> IO OsPath
- getCurrentDirectoryInternal :: IO OsPath
- getDirectoryContentsInternal :: OsPath -> IO [OsPath]
- getEnvOs :: OsString -> IO OsString
- getFileMetadata :: OsPath -> IO Metadata
- getHomeDirectoryInternal :: IO OsPath
- getMetadataAt :: WhetherFollow -> Maybe RawHandle -> OsPath -> IO Metadata
- getPath :: IO [OsPath]
- getSymbolicLinkMetadata :: OsPath -> IO Metadata
- getTemporaryDirectoryInternal :: IO OsPath
- getUserDocumentsDirectoryInternal :: IO OsPath
- getXdgDirectoryFallback :: IO OsPath -> XdgDirectory -> IO OsPath
- getXdgDirectoryListFallback :: XdgDirectoryList -> IO [OsPath]
- hasWriteMode :: Mode -> Bool
- linkToDirectoryIsDirectory :: Bool
- lookupEnvOs :: OsString -> IO (Maybe OsString)
- modeFromMetadata :: Metadata -> Mode
- modificationTimeFromMetadata :: Metadata -> UTCTime
- openDirFromFd :: Fd -> IO DirStream
- openRaw :: WhetherFollow -> Maybe RawHandle -> OsPath -> IO RawHandle
- prependCurrentDirectory :: OsPath -> IO OsPath
- readDirStreamToEnd :: DirStream -> IO [OsPath]
- readDirToEnd :: RawHandle -> IO [OsPath]
- readSymbolicLink :: OsPath -> IO OsPath
- realPath :: OsPath -> IO OsPath
- removePathAt :: FileType -> Maybe RawHandle -> OsPath -> IO ()
- removePathInternal :: Bool -> OsPath -> IO ()
- renamePathInternal :: OsPath -> OsPath -> IO ()
- setAccessPermissions :: OsPath -> Permissions -> IO ()
- setCurrentDirectoryInternal :: OsPath -> IO ()
- setFileMode :: OsPath -> Mode -> IO ()
- setFilePermissions :: OsPath -> Mode -> IO ()
- setForceRemoveMode :: Mode -> Mode
- setModeAt :: WhetherFollow -> Maybe RawHandle -> OsPath -> Mode -> IO ()
- setTimes :: OsPath -> (Maybe POSIXTime, Maybe POSIXTime) -> IO ()
- setWriteMode :: Bool -> Mode -> Mode
- simplify :: OsPath -> OsPath
- tryCopyOwnerAndGroupFromStatus :: FileStatus -> OsPath -> IO ()
- withRealpath :: CString -> (CString -> IO a) -> IO a
- type Metadata = FileStatus
- type Mode = FileMode
- type RawHandle = Fd
Documentation
Copy data from one handle to another until end of file.
dropSpecialDotDirs :: [OsPath] -> [OsPath] Source #
emptyListT :: forall (m :: Type -> Type) a. Applicative m => ListT m a Source #
emptyToCurDir :: OsPath -> OsPath Source #
Convert empty paths to the current directory, otherwise leave it unchanged.
expandDots :: [OsPath] -> [OsPath] Source #
Given a list of path segments, expand .
and ..
. The path segments
must not contain path separators.
fileTypeIsDirectory :: FileType -> Bool Source #
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
.
ignoreIOExceptions :: IO () -> IO () Source #
Attempt to perform the given action, silencing any IO exception thrown by it.
isNoFollow :: WhetherFollow -> Bool Source #
listTToList :: Monad m => ListT m a -> m [a] Source #
listToListT :: forall (m :: Type -> Type) a. Applicative m => [a] -> ListT m a Source #
maybeToListT :: Applicative m => m (Maybe a) -> ListT m a Source #
normalisePathSeps :: OsPath -> OsPath Source #
Convert to the right kind of slashes.
normaliseTrailingSep :: OsPath -> OsPath Source #
Remove redundant trailing slashes and pick the right kind of slash.
os :: String -> OsString Source #
Fallibly converts String to OsString. Only intended to be used on literals.
rightOrError :: Exception e => Either e a -> a Source #
sequenceWithIOErrors_ :: [IO ()] -> IO () Source #
simplifyWindows :: OsPath -> OsPath Source #
so :: OsString -> String Source #
Fallibly converts OsString to String. Only intended to be used on literals.
File | |
SymbolicLink | POSIX: either file or directory link; Windows: file link |
Directory | |
DirectoryLink | Windows only: directory link |
Instances
Bounded FileType Source # | |
Enum FileType Source # | |
Defined in System.Directory.Internal.Common | |
Read FileType Source # | |
Show FileType Source # | |
Eq FileType Source # | |
Ord FileType Source # | |
Defined in System.Directory.Internal.Common |
data Permissions Source #
Permissions | |
|
Instances
Read Permissions Source # | |
Defined in System.Directory.Internal.Common readsPrec :: Int -> ReadS Permissions # readList :: ReadS [Permissions] # readPrec :: ReadPrec Permissions # readListPrec :: ReadPrec [Permissions] # | |
Show Permissions Source # | |
Defined in System.Directory.Internal.Common showsPrec :: Int -> Permissions -> ShowS # show :: Permissions -> String # showList :: [Permissions] -> ShowS # | |
Eq Permissions Source # | |
Defined in System.Directory.Internal.Common (==) :: Permissions -> Permissions -> Bool # (/=) :: Permissions -> Permissions -> Bool # | |
Ord Permissions Source # | |
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 # |
data WhetherFollow Source #
Instances
Show WhetherFollow Source # | |
Defined in System.Directory.Internal.Common showsPrec :: Int -> WhetherFollow -> ShowS # show :: WhetherFollow -> String # showList :: [WhetherFollow] -> ShowS # |
data XdgDirectory Source #
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 |
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 Source #
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
type OsPath = OsString Source #
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
NFData OsString | |||||
Defined in System.OsString.Internal.Types | |||||
Monoid OsString Source # | "String-Concatenation" for | ||||
Semigroup OsString Source # | |||||
Generic OsString Source # | |||||
Defined in System.OsString.Internal.Types
| |||||
Show OsString Source # | On windows, decodes as UCS-2. On unix prints the raw bytes without decoding. | ||||
Eq OsString Source # | Byte equality of the internal representation. | ||||
Ord OsString Source # | Byte ordering of the internal representation. | ||||
Defined in System.OsString.Internal.Types | |||||
Lift OsString | |||||
type Rep OsString Source # | |||||
Defined in System.OsString.Internal.Types type Rep OsString = D1 ('MetaData "OsString" "System.OsString.Internal.Types" "os-string-2.0.4-e0de" 'True) (C1 ('MetaCons "OsString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOsString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformString))) |
allWriteMode :: FileMode Source #
atWhetherFollow :: WhetherFollow -> CInt Source #
c_AT_FDCWD :: Fd Source #
c_PATH_MAX :: Maybe Int 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 #
copyGroupFromStatus :: FileStatus -> OsPath -> IO () Source #
copyOwnerFromStatus :: FileStatus -> OsPath -> IO () Source #
createDirectoryInternal :: OsPath -> IO () Source #
findExecutablesLazyInternal :: ([OsPath] -> OsString -> ListT IO OsPath) -> OsString -> ListT IO OsPath Source #
getHomeDirectoryInternal :: IO OsPath Source #
$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
.
getMetadataAt :: WhetherFollow -> Maybe RawHandle -> OsPath -> IO Metadata Source #
getXdgDirectoryFallback :: IO OsPath -> XdgDirectory -> IO OsPath Source #
hasWriteMode :: Mode -> Bool Source #
modeFromMetadata :: Metadata -> Mode Source #
openDirFromFd :: Fd -> IO DirStream Source #
prependCurrentDirectory :: OsPath -> IO OsPath Source #
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.
setAccessPermissions :: OsPath -> Permissions -> IO () Source #
setCurrentDirectoryInternal :: OsPath -> IO () Source #
setForceRemoveMode :: Mode -> Mode Source #
tryCopyOwnerAndGroupFromStatus :: FileStatus -> OsPath -> IO () Source #
type Metadata = FileStatus Source #