Stability | unstable |
---|---|
Portability | unportable |
Safe Haskell | Safe |
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
- newtype ListT m a = ListT {}
- 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 (Either IOError a)
- ignoreIOExceptions :: IO () -> IO ()
- specializeErrorString :: String -> (IOError -> Bool) -> IO a -> IO a
- ioeAddLocation :: IOError -> String -> IOError
- data FileType
- fileTypeIsDirectory :: FileType -> Bool
- fileTypeIsLink :: FileType -> Bool
- data Permissions = Permissions {
- readable :: Bool
- writable :: Bool
- executable :: Bool
- searchable :: Bool
- prependCurrentDirectoryWith :: IO FilePath -> FilePath -> IO FilePath
- copyFileContents :: FilePath -> FilePath -> IO ()
- copyFileToHandle :: FilePath -> Handle -> IO ()
- copyHandleData :: Handle -> Handle -> IO ()
- data XdgDirectory
- data XdgDirectoryList
- createDirectoryInternal :: FilePath -> IO ()
- removePathInternal :: Bool -> FilePath -> IO ()
- renamePathInternal :: FilePath -> FilePath -> IO ()
- c_free :: Ptr a -> IO ()
- c_PATH_MAX :: Maybe Int
- c_realpath :: CString -> CString -> IO CString
- withRealpath :: CString -> (CString -> IO a) -> IO a
- canonicalizePathWith :: ((FilePath -> IO FilePath) -> FilePath -> IO FilePath) -> FilePath -> IO FilePath
- canonicalizePathSimplify :: FilePath -> IO FilePath
- findExecutablesLazyInternal :: ([FilePath] -> String -> ListT IO FilePath) -> String -> ListT IO FilePath
- exeExtensionInternal :: String
- getDirectoryContentsInternal :: FilePath -> IO [FilePath]
- getCurrentDirectoryInternal :: IO FilePath
- prependCurrentDirectory :: FilePath -> IO FilePath
- setCurrentDirectoryInternal :: FilePath -> IO ()
- linkToDirectoryIsDirectory :: Bool
- createSymbolicLink :: Bool -> FilePath -> FilePath -> IO ()
- readSymbolicLink :: FilePath -> IO FilePath
- type Metadata = FileStatus
- getSymbolicLinkMetadata :: FilePath -> IO Metadata
- getFileMetadata :: FilePath -> IO Metadata
- fileTypeFromMetadata :: Metadata -> FileType
- fileSizeFromMetadata :: Metadata -> Integer
- accessTimeFromMetadata :: Metadata -> UTCTime
- modificationTimeFromMetadata :: Metadata -> UTCTime
- posix_accessTimeHiRes :: FileStatus -> POSIXTime
- posix_modificationTimeHiRes :: FileStatus -> POSIXTime
- type Mode = FileMode
- modeFromMetadata :: Metadata -> Mode
- allWriteMode :: FileMode
- hasWriteMode :: Mode -> Bool
- setWriteMode :: Bool -> Mode -> Mode
- setFileMode :: FilePath -> Mode -> IO ()
- setFilePermissions :: FilePath -> Mode -> IO ()
- getAccessPermissions :: FilePath -> IO Permissions
- setAccessPermissions :: FilePath -> Permissions -> IO ()
- copyOwnerFromStatus :: FileStatus -> FilePath -> IO ()
- copyGroupFromStatus :: FileStatus -> FilePath -> IO ()
- tryCopyOwnerAndGroupFromStatus :: FileStatus -> FilePath -> IO ()
- copyFileWithMetadataInternal :: (Metadata -> FilePath -> IO ()) -> (Metadata -> FilePath -> IO ()) -> FilePath -> FilePath -> IO ()
- setTimes :: FilePath -> (Maybe POSIXTime, Maybe POSIXTime) -> IO ()
- getPath :: IO [FilePath]
- getHomeDirectoryInternal :: IO FilePath
- getXdgDirectoryInternal :: IO FilePath -> XdgDirectory -> IO FilePath
- getXdgDirectoryListInternal :: XdgDirectoryList -> IO [FilePath]
- getAppUserDataDirectoryInternal :: FilePath -> IO FilePath
- getUserDocumentsDirectoryInternal :: IO FilePath
- getTemporaryDirectoryInternal :: IO FilePath
Documentation
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.
File | |
SymbolicLink | POSIX: either file or directory link; Windows: file link |
Directory | |
DirectoryLink | Windows only: directory link |
Instances
Bounded FileType # | |
Enum FileType # | |
Defined in System.Directory.Internal.Common 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 # | |
Defined in System.Directory.Internal.Common | |
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
.
data Permissions Source #
Permissions | |
|
Instances
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 # | |
Read Permissions # | |
Defined in System.Directory.Internal.Common | |
Show Permissions # | |
Defined in System.Directory.Internal.Common |
prependCurrentDirectoryWith :: IO FilePath -> 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)
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.
Copy all data from a file to a handle.
Copy data from one handle to another until end of file.
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
map to the same directory.
Since: directory-1.2.3.0
XdgData | For data files (e.g. images).
Defaults to |
XdgConfig | For configuration files.
Defaults to |
XdgCache | For non-essential files (e.g. cache).
Defaults to |
Instances
data XdgDirectoryList Source #
Search paths for various application data, as specified by the XDG Base Directory Specification.
Note: On Windows, XdgDataDirs
and XdgConfigDirs
yield the same result.
Since: directory-1.3.2.0
XdgDataDirs | For data files (e.g. images).
Defaults to |
XdgConfigDirs | For configuration files.
Defaults to |
Instances
createDirectoryInternal :: FilePath -> IO () Source #
c_PATH_MAX :: Maybe Int Source #
canonicalizePathWith :: ((FilePath -> IO FilePath) -> FilePath -> IO FilePath) -> FilePath -> IO FilePath Source #
findExecutablesLazyInternal :: ([FilePath] -> String -> ListT IO FilePath) -> String -> ListT IO FilePath Source #
setCurrentDirectoryInternal :: FilePath -> IO () Source #
type Metadata = FileStatus Source #
modeFromMetadata :: Metadata -> Mode Source #
hasWriteMode :: Mode -> Bool Source #
setAccessPermissions :: FilePath -> Permissions -> IO () Source #
copyOwnerFromStatus :: FileStatus -> FilePath -> IO () Source #
copyGroupFromStatus :: FileStatus -> FilePath -> IO () Source #
tryCopyOwnerAndGroupFromStatus :: FileStatus -> FilePath -> IO () Source #
copyFileWithMetadataInternal :: (Metadata -> FilePath -> IO ()) -> (Metadata -> FilePath -> IO ()) -> FilePath -> FilePath -> IO () Source #
getXdgDirectoryInternal :: IO FilePath -> XdgDirectory -> IO FilePath Source #