directory-1.3.8.0: Platform-agnostic library for filesystem operations
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

Documentation

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: 1.3.2.0

Constructors

XdgDataDirs

For data files (e.g. images). It uses the XDG_DATA_DIRS environment variable. On non-Windows systems, the default is /usr/local/share/ and /usr/share/. On Windows, the default is %PROGRAMDATA% or %ALLUSERSPROFILE% (e.g. C:/ProgramData).

XdgConfigDirs

For configuration files. It uses the XDG_CONFIG_DIRS environment variable. On non-Windows systems, the default is /etc/xdg. On Windows, the default is %PROGRAMDATA% or %ALLUSERSPROFILE% (e.g. C:/ProgramData).

Instances

Instances details
Bounded XdgDirectoryList Source # 
Instance details

Defined in System.Directory.Internal.Common

Enum XdgDirectoryList Source # 
Instance details

Defined in System.Directory.Internal.Common

Read XdgDirectoryList Source # 
Instance details

Defined in System.Directory.Internal.Common

Show XdgDirectoryList Source # 
Instance details

Defined in System.Directory.Internal.Common

Eq XdgDirectoryList Source # 
Instance details

Defined in System.Directory.Internal.Common

Ord XdgDirectoryList Source # 
Instance details

Defined in System.Directory.Internal.Common

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: 1.2.3.0

Constructors

XdgData

For data files (e.g. images). It uses the XDG_DATA_HOME environment variable. On non-Windows systems, the default is ~/.local/share. On Windows, the default is %APPDATA% (e.g. C:/Users/<user>/AppData/Roaming). Can be considered as the user-specific equivalent of /usr/share.

XdgConfig

For configuration files. It uses the XDG_CONFIG_HOME environment variable. On non-Windows systems, the default is ~/.config. On Windows, the default is %APPDATA% (e.g. C:/Users/<user>/AppData/Roaming). Can be considered as the user-specific equivalent of /etc.

XdgCache

For non-essential files (e.g. cache). It uses the XDG_CACHE_HOME environment variable. On non-Windows systems, the default is ~/.cache. On Windows, the default is %LOCALAPPDATA% (e.g. C:/Users/<user>/AppData/Local). Can be considered as the user-specific equivalent of /var/cache.

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 XdgData. It uses the XDG_STATE_HOME environment variable. On non-Windows sytems, the default is ~/.local/state. On Windows, the default is %LOCALAPPDATA% (e.g. C:/Users/<user>/AppData/Local).

Since: 1.3.7.0

Instances

Instances details
Bounded XdgDirectory Source # 
Instance details

Defined in System.Directory.Internal.Common

Enum XdgDirectory Source # 
Instance details

Defined in System.Directory.Internal.Common

Read XdgDirectory Source # 
Instance details

Defined in System.Directory.Internal.Common

Show XdgDirectory Source # 
Instance details

Defined in System.Directory.Internal.Common

Eq XdgDirectory Source # 
Instance details

Defined in System.Directory.Internal.Common

Ord XdgDirectory Source # 
Instance details

Defined in System.Directory.Internal.Common

data FileType Source #

Constructors

File 
SymbolicLink

POSIX: either file or directory link; Windows: file link

Directory 
DirectoryLink

Windows only: directory link

Instances

Instances details
Bounded FileType Source # 
Instance details

Defined in System.Directory.Internal.Common

Enum FileType Source # 
Instance details

Defined in System.Directory.Internal.Common

Read FileType Source # 
Instance details

Defined in System.Directory.Internal.Common

Show FileType Source # 
Instance details

Defined in System.Directory.Internal.Common

Eq FileType Source # 
Instance details

Defined in System.Directory.Internal.Common

Ord FileType Source # 
Instance details

Defined in System.Directory.Internal.Common

newtype ListT m a Source #

A generator with side-effects.

Constructors

ListT 

Fields

listToListT :: Applicative m => [a] -> ListT m a Source #

liftJoinListT :: Monad m => m (ListT m a) -> ListT m a Source #

listTHead :: Functor m => ListT m a -> m (Maybe a) Source #

listTToList :: Monad m => ListT m a -> m [a] Source #

andM :: Monad m => m Bool -> m Bool -> m Bool Source #

tryIOErrorType :: (IOError -> Bool) -> IO a -> IO (Either IOError a) Source #

Similar to try but only catches a specify kind of IOError as specified by the predicate.

ignoreIOExceptions :: IO () -> IO () Source #

Attempt to perform the given action, silencing any IO exception thrown by it.

os :: String -> OsString Source #

Fallibly converts String to OsString. Only intended to be used on literals.

so :: OsString -> String Source #

Fallibly converts OsString to String. Only intended to be used on literals.

expandDots :: [OsPath] -> [OsPath] Source #

Given a list of path segments, expand . and ... The path segments must not contain path separators.

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.

emptyToCurDir :: OsPath -> OsPath Source #

Convert empty paths to the current directory, otherwise leave it unchanged.

simplifyPosix :: OsPath -> OsPath Source #

Similar to normalise but empty paths stay empty.

simplifyWindows :: OsPath -> OsPath Source #

Similar to normalise but:

  • empty paths stay empty,
  • parent dirs (..) are expanded, and
  • paths starting with \\?\ are preserved.

The goal is to preserve the meaning of paths better than normalise.

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.

fileTypeIsLink :: FileType -> Bool Source #

Return whether the given FileType is a link.

copyHandleData Source #

Arguments

:: Handle

Source handle

-> Handle

Destination handle

-> IO () 

Copy data from one handle to another until end of file.

type OsPath = OsString #

Type representing filenames/pathnames.

This type doesn't add any guarantees over OsString.

data 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

Instances details
Monoid OsString

"String-Concatenation" for OsString. This is not the same as (</>).

Instance details

Defined in System.OsString.Internal.Types

Semigroup OsString 
Instance details

Defined in System.OsString.Internal.Types

Generic OsString 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep OsString :: Type -> Type #

Methods

from :: OsString -> Rep OsString x #

to :: Rep OsString x -> OsString #

Show OsString

On windows, decodes as UCS-2. On unix prints the raw bytes without decoding.

Instance details

Defined in System.OsString.Internal.Types

NFData OsString 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: OsString -> () #

Eq OsString

Byte equality of the internal representation.

Instance details

Defined in System.OsString.Internal.Types

Ord OsString

Byte ordering of the internal representation.

Instance details

Defined in System.OsString.Internal.Types

Lift OsString 
Instance details

Defined in System.OsString.Internal.Types

Methods

lift :: Quote m => OsString -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => OsString -> Code m OsString #

type Rep OsString 
Instance details

Defined in System.OsString.Internal.Types

type Rep OsString = D1 ('MetaData "OsString" "System.OsString.Internal.Types" "filepath-1.4.100.0-8DUEpf9XxqDL7ps2eHvaDg" 'True) (C1 ('MetaCons "OsString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOsString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformString)))

simplify :: OsPath -> OsPath Source #

On POSIX, equivalent to simplifyPosix.

c_free :: Ptr a -> IO () 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.

copyFileContents Source #

Arguments

:: OsPath

Source filename

-> OsPath

Destination filename

-> IO () 

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.

getPath :: IO [OsPath] Source #

Get the contents of the PATH environment variable.

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.