| Stability | unstable |
|---|---|
| Portability | unportable |
| Safe Haskell | Safe |
| 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
- tryIOErrorType :: (IOError -> Bool) -> IO a -> IO (Either IOError a)
- tryIOErrorType :: (IOError -> Bool) -> IO a -> IO (Either IOError a)
- specializeErrorString :: String -> (IOError -> Bool) -> IO a -> IO a
- specializeErrorString :: String -> (IOError -> Bool) -> IO a -> IO a
- ioeAddLocation :: IOError -> String -> IOError
- ioeAddLocation :: IOError -> String -> IOError
- data FileType
- fileTypeIsDirectory :: FileType -> Bool
- fileTypeIsDirectory :: FileType -> Bool
- data Permissions = Permissions {
- readable :: Bool
- writable :: Bool
- executable :: Bool
- searchable :: Bool
- getCurrentDirectory :: IO FilePath
- getCurrentDirectory :: IO FilePath
- prependCurrentDirectory :: FilePath -> IO FilePath
- prependCurrentDirectory :: FilePath -> IO FilePath
- c_free :: Ptr a -> IO ()
- c_PATH_MAX :: Maybe Int
- c_PATH_MAX :: Maybe Int
- c_realpath :: CString -> CString -> IO CString
- withRealpath :: CString -> (CString -> IO a) -> IO a
- withRealpath :: CString -> (CString -> IO a) -> IO a
- type Metadata = FileStatus
- getSymbolicLinkMetadata :: FilePath -> IO Metadata
- getSymbolicLinkMetadata :: FilePath -> IO Metadata
- getFileMetadata :: FilePath -> IO Metadata
- getFileMetadata :: FilePath -> IO Metadata
- fileTypeFromMetadata :: Metadata -> FileType
- fileTypeFromMetadata :: Metadata -> FileType
- fileSizeFromMetadata :: Metadata -> Integer
- fileSizeFromMetadata :: Metadata -> Integer
- accessTimeFromMetadata :: Metadata -> UTCTime
- accessTimeFromMetadata :: Metadata -> UTCTime
- modificationTimeFromMetadata :: Metadata -> UTCTime
- modificationTimeFromMetadata :: Metadata -> UTCTime
- posix_accessTimeHiRes :: FileStatus -> POSIXTime
- posix_modificationTimeHiRes :: FileStatus -> POSIXTime
- posix_accessTimeHiRes :: FileStatus -> POSIXTime
- posix_modificationTimeHiRes :: FileStatus -> POSIXTime
- type Mode = FileMode
- modeFromMetadata :: Metadata -> Mode
- modeFromMetadata :: Metadata -> Mode
- allWriteMode :: FileMode
- allWriteMode :: FileMode
- hasWriteMode :: Mode -> Bool
- hasWriteMode :: Mode -> Bool
- setWriteMode :: Bool -> Mode -> Mode
- setWriteMode :: Bool -> Mode -> Mode
- setFileMode :: FilePath -> Mode -> IO ()
- setFileMode :: FilePath -> Mode -> IO ()
- setFilePermissions :: FilePath -> Mode -> IO ()
- setFilePermissions :: FilePath -> Mode -> IO ()
- getAccessPermissions :: FilePath -> IO Permissions
- getAccessPermissions :: FilePath -> IO Permissions
- setAccessPermissions :: FilePath -> Permissions -> IO ()
- setAccessPermissions :: FilePath -> Permissions -> IO ()
- data CTimeSpec = CTimeSpec EpochTime CLong
- c_AT_FDCWD :: CInt
- c_AT_FDCWD :: CInt
- utimeOmit :: CTimeSpec
- utimeOmit :: CTimeSpec
- toCTimeSpec :: POSIXTime -> CTimeSpec
- toCTimeSpec :: POSIXTime -> CTimeSpec
- c_utimensat :: CInt -> CString -> Ptr CTimeSpec -> CInt -> IO CInt
Documentation
Constructors
| File | |
| SymbolicLink | POSIX: either file or directory link; Windows: file link |
| Directory | |
| DirectoryLink | Windows only |
Instances
| Bounded FileType # | |
| Enum FileType # | |
Methods succ :: FileType -> FileType Source # pred :: FileType -> FileType Source # toEnum :: Int -> FileType Source # fromEnum :: FileType -> Int Source # enumFrom :: FileType -> [FileType] Source # enumFromThen :: FileType -> FileType -> [FileType] Source # enumFromTo :: FileType -> FileType -> [FileType] Source # enumFromThenTo :: FileType -> FileType -> FileType -> [FileType] Source # | |
| Eq FileType # | |
| Ord FileType # | |
| Read FileType # | |
| Show FileType # | |
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.
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.
data Permissions Source #
Constructors
| Permissions | |
Fields
| |
Instances
| Eq Permissions # | |
| Ord Permissions # | |
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 # | |
| Read Permissions # | |
| Show Permissions # | |
getCurrentDirectory :: IO FilePath Source #
Obtain the current working directory as an absolute path.
In a multithreaded program, the current working directory is a global state
shared among all threads of the process. Therefore, when performing
filesystem operations from multiple threads, it is highly recommended to
use absolute rather than relative paths (see: makeAbsolute).
The operation may fail with:
HardwareFaultA physical I/O error has occurred.[EIO]isDoesNotExistErrororNoSuchThingThere is no path referring to the working directory.[EPERM, ENOENT, ESTALE...]isPermissionErrororPermissionDeniedThe process has insufficient privileges to perform the operation.[EACCES]ResourceExhaustedInsufficient resources are available to perform the operation.UnsupportedOperationThe operating system has no notion of current working directory.
getCurrentDirectory :: IO FilePath Source #
Obtain the current working directory as an absolute path.
In a multithreaded program, the current working directory is a global state
shared among all threads of the process. Therefore, when performing
filesystem operations from multiple threads, it is highly recommended to
use absolute rather than relative paths (see: makeAbsolute).
The operation may fail with:
HardwareFaultA physical I/O error has occurred.[EIO]isDoesNotExistErrororNoSuchThingThere is no path referring to the working directory.[EPERM, ENOENT, ESTALE...]isPermissionErrororPermissionDeniedThe process has insufficient privileges to perform the operation.[EACCES]ResourceExhaustedInsufficient resources are available to perform the operation.UnsupportedOperationThe operating system has no notion of current working directory.
prependCurrentDirectory :: FilePath -> IO FilePath Source #
Convert a path into an absolute path. If the given path is relative, the current directory is prepended. 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 fail with the same exceptions as getCurrentDirectory.
(internal API)
prependCurrentDirectory :: FilePath -> IO FilePath Source #
Convert a path into an absolute path. If the given path is relative, the current directory is prepended. 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 fail with the same exceptions as getCurrentDirectory.
(internal API)
c_PATH_MAX :: Maybe Int Source #
c_PATH_MAX :: Maybe Int Source #
type Metadata = FileStatus Source #
modeFromMetadata :: Metadata -> Mode Source #
modeFromMetadata :: Metadata -> Mode Source #
hasWriteMode :: Mode -> Bool Source #
hasWriteMode :: Mode -> Bool Source #
setAccessPermissions :: FilePath -> Permissions -> IO () Source #
setAccessPermissions :: FilePath -> Permissions -> IO () Source #
Instances
| Storable CTimeSpec # | |
Methods sizeOf :: CTimeSpec -> Int Source # alignment :: CTimeSpec -> Int Source # peekElemOff :: Ptr CTimeSpec -> Int -> IO CTimeSpec Source # pokeElemOff :: Ptr CTimeSpec -> Int -> CTimeSpec -> IO () Source # peekByteOff :: Ptr b -> Int -> IO CTimeSpec Source # pokeByteOff :: Ptr b -> Int -> CTimeSpec -> IO () Source # | |
c_AT_FDCWD :: CInt Source #
c_AT_FDCWD :: CInt Source #
toCTimeSpec :: POSIXTime -> CTimeSpec Source #
toCTimeSpec :: POSIXTime -> CTimeSpec Source #