path-tagged-0.1.0.0: A wrapper around the @path@ library, tagged with semantic name.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Path.Tagged.IO

Synopsis

Actions on directories

createDir :: MonadIO m => PathTo e b Dir -> m () Source #

ensureDir :: MonadIO m => PathTo e b Dir -> m () Source #

removeDir :: MonadIO m => PathTo entity b Dir -> m () Source #

removeDirRecur :: MonadIO m => PathTo entity b Dir -> m () Source #

removePathForcibly :: MonadIO m => PathTo e b t -> m () Source #

renameDir :: MonadIO m => PathTo e b Dir -> PathTo e b' Dir -> m () Source #

renamePath :: MonadIO m => PathTo e b t -> PathTo e b' t -> m () Source #

copyDirRecur :: (MonadIO m, MonadCatch m) => PathTo e0 b0 Dir -> PathTo e1 b1 Dir -> m () Source #

copyDirRecur' :: (MonadIO m, MonadCatch m) => PathTo e0 b0 Dir -> PathTo e1 b1 Dir -> m () Source #

Walking directory trees

data WalkAction b Source #

Instances

Instances details
Show (WalkAction b) Source # 
Instance details

Defined in Path.Tagged.IO

Eq (WalkAction b) Source # 
Instance details

Defined in Path.Tagged.IO

Methods

(==) :: WalkAction b -> WalkAction b -> Bool #

(/=) :: WalkAction b -> WalkAction b -> Bool #

Ord (WalkAction b) Source # 
Instance details

Defined in Path.Tagged.IO

walkDir :: MonadIO m => (forall dir. PathTo dir Abs Dir -> [PathTo Unknown Abs Dir] -> [PathTo Unknown Abs File] -> m (WalkAction Abs)) -> PathTo e b Dir -> m () Source #

walkDirRel :: MonadIO m => (forall dir. PathTo dir (RelTo e) Dir -> [PathTo Unknown (RelTo dir) Dir] -> [PathTo Unknown (RelTo dir) File] -> m (WalkAction (RelTo dir))) -> PathTo e b Dir -> m () Source #

walkDirAccum :: (MonadIO m, Monoid o) => Maybe (forall dir. PathTo dir Abs Dir -> [PathTo Unknown Abs Dir] -> [PathTo Unknown Abs File] -> m (WalkAction Abs)) -> (forall dir. PathTo dir Abs Dir -> [PathTo Unknown Abs Dir] -> [PathTo Unknown Abs File] -> m o) -> PathTo e b Dir -> m o Source #

walkDirAccumRel :: (MonadIO m, Monoid o) => Maybe (forall dir. PathTo dir (RelTo e) Dir -> [PathTo Unknown (RelTo dir) Dir] -> [PathTo Unknown (RelTo dir) File] -> m (WalkAction (RelTo dir))) -> (forall dir. PathTo dir (RelTo e) Dir -> [PathTo Unknown (RelTo dir) Dir] -> [PathTo Unknown (RelTo dir) File] -> m o) -> PathTo e b Dir -> m o Source #

Current working directory

getCurrentDir :: forall m. MonadIO m => m (PathTo Cwd Abs Dir) Source #

setCurrentDir :: MonadIO m => PathTo e b Dir -> m () Source #

withCurrentDir :: (MonadIO m, MonadMask m) => PathTo e b Dir -> m a -> m a Source #

Pre-defined directories

data PredefinedDir Source #

Constructors

Home 
AppUserData 
UserDocs 
TempDir 
Cwd 

Instances

Instances details
Generic PredefinedDir Source # 
Instance details

Defined in Path.Tagged.IO

Associated Types

type Rep PredefinedDir :: Type -> Type #

Show PredefinedDir Source # 
Instance details

Defined in Path.Tagged.IO

Eq PredefinedDir Source # 
Instance details

Defined in Path.Tagged.IO

Ord PredefinedDir Source # 
Instance details

Defined in Path.Tagged.IO

type Rep PredefinedDir Source # 
Instance details

Defined in Path.Tagged.IO

type Rep PredefinedDir = D1 ('MetaData "PredefinedDir" "Path.Tagged.IO" "path-tagged-0.1.0.0-FFPUlr6bBoZ95OWscTAxp" 'False) ((C1 ('MetaCons "Home" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AppUserData" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UserDocs" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TempDir" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cwd" 'PrefixI 'False) (U1 :: Type -> Type))))

type family WithPredefined p = w | w -> p where ... Source #

data XdgDirectory #

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

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: directory-1.3.7.0

Instances

Instances details
Bounded XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

Enum XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

Read XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

Show XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

Eq XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

Ord XdgDirectory 
Instance details

Defined in System.Directory.Internal.Common

type family WithXdg xdg = p | p -> xdg where ... Source #

class KnownXdgDirectory xdg Source #

Minimal complete definition

xdgDirectory#

Instances

Instances details
KnownXdgDirectory 'XdgCache Source # 
Instance details

Defined in Path.Tagged.IO

KnownXdgDirectory 'XdgConfig Source # 
Instance details

Defined in Path.Tagged.IO

KnownXdgDirectory 'XdgData Source # 
Instance details

Defined in Path.Tagged.IO

getXdgBaseDir :: forall xdg m. (KnownXdgDirectory xdg, MonadIO m) => m (PathTo xdg Abs Dir) Source #

getXdgDir :: forall xdg e m. (KnownXdgDirectory xdg, MonadIO m) => PathTo e (RelTo (WithXdg xdg)) Dir -> m (PathTo e Abs Dir) Source #

Path transformation

class AnyPathTo path where Source #

Associated Types

type PathTag path :: Type Source #

type AbsPath path :: Type Source #

type RelPathTo' k (e :: k) path :: Type Source #

Methods

canonicalizePath :: MonadIO m => path -> m (AbsPath path) Source #

makeAbsolute :: MonadIO m => path -> m (AbsPath path) Source #

makeRelative :: MonadThrow m => PathTo (e :: PathTag path) Abs Dir -> path -> m (RelPathTo e path) Source #

makeRelativeToCurrentDir :: MonadIO m => path -> m (RelPathTo' (PathTag path) Cwd path) Source #

Instances

Instances details
AnyPathTo (PathTo e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

Associated Types

type PathTag (PathTo e b Dir) Source #

type AbsPath (PathTo e b Dir) Source #

type RelPathTo' k e (PathTo e b Dir) Source #

Methods

canonicalizePath :: MonadIO m => PathTo e b Dir -> m (AbsPath (PathTo e b Dir)) Source #

makeAbsolute :: MonadIO m => PathTo e b Dir -> m (AbsPath (PathTo e b Dir)) Source #

makeRelative :: forall m (e0 :: PathTag (PathTo e b Dir)). MonadThrow m => PathTo e0 Abs Dir -> PathTo e b Dir -> m (RelPathTo e0 (PathTo e b Dir)) Source #

makeRelativeToCurrentDir :: MonadIO m => PathTo e b Dir -> m (RelPathTo' (PathTag (PathTo e b Dir)) Cwd (PathTo e b Dir)) Source #

AnyPathTo (PathTo e b File) Source # 
Instance details

Defined in Path.Tagged.IO

Associated Types

type PathTag (PathTo e b File) Source #

type AbsPath (PathTo e b File) Source #

type RelPathTo' k e (PathTo e b File) Source #

Methods

canonicalizePath :: MonadIO m => PathTo e b File -> m (AbsPath (PathTo e b File)) Source #

makeAbsolute :: MonadIO m => PathTo e b File -> m (AbsPath (PathTo e b File)) Source #

makeRelative :: forall m (e0 :: PathTag (PathTo e b File)). MonadThrow m => PathTo e0 Abs Dir -> PathTo e b File -> m (RelPathTo e0 (PathTo e b File)) Source #

makeRelativeToCurrentDir :: MonadIO m => PathTo e b File -> m (RelPathTo' (PathTag (PathTo e b File)) Cwd (PathTo e b File)) Source #

AnyPathTo (SomeBase e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

Associated Types

type PathTag (SomeBase e b Dir) Source #

type AbsPath (SomeBase e b Dir) Source #

type RelPathTo' k e (SomeBase e b Dir) Source #

AnyPathTo (SomeBase e b File) Source # 
Instance details

Defined in Path.Tagged.IO

Associated Types

type PathTag (SomeBase e b File) Source #

type AbsPath (SomeBase e b File) Source #

type RelPathTo' k e (SomeBase e b File) Source #

type RelPathTo (e :: k) path = RelPathTo' k e path Source #

resolveFile :: forall e e0 m. MonadIO m => PathTo e0 Abs Dir -> FilePath -> m (PathTo e Abs File) Source #

resolveFile' :: forall e m. MonadIO m => FilePath -> m (PathTo e Abs File) Source #

resolveDir :: forall e e0 m. MonadIO m => PathTo e0 Abs Dir -> FilePath -> m (PathTo e Abs Dir) Source #

resolveDir' :: forall e m. MonadIO m => FilePath -> m (PathTo e Abs Dir) Source #

Actions on Files

removeFile :: MonadIO m => PathTo e b File -> m () Source #

renameFile :: MonadIO m => PathTo e b0 File -> PathTo e b1 File -> m () Source #

copyFile :: MonadIO m => PathTo e0 b0 File -> PathTo e1 b1 File -> m () Source #

findFile :: MonadIO m => [PathTo dir b Dir] -> PathTo e (RelTo dir) File -> m (Maybe (PathTo e Abs File)) Source #

findFiles :: MonadIO m => [PathTo dir b Dir] -> PathTo e (RelTo dir) File -> m [PathTo e Abs File] Source #

findFilesWith :: MonadIO m => (PathTo e Abs File -> m Bool) -> [PathTo dir b Dir] -> PathTo e (RelTo dir) File -> m [PathTo e Abs File] Source #

Symbolic links

createFileLink :: MonadIO m => PathTo e b0 File -> PathTo e b1 File -> m () Source #

createDirLink :: MonadIO m => PathTo e b0 Dir -> PathTo e b1 Dir -> m () Source #

removeDirLink :: MonadIO m => PathTo e b0 Dir -> m () Source #

isSymlink :: MonadIO m => PathTo e b t -> m Bool Source #

Temporary files and directories

withTempFile :: forall e e0 b m a. (MonadIO m, MonadMask m) => PathTo e0 b Dir -> String -> (PathTo e Abs File -> Handle -> m a) -> m a Source #

withTempDir :: (MonadIO m, MonadMask m) => PathTo e b Dir -> String -> (PathTo TempDir Abs Dir -> m a) -> m a Source #

withSystemTempFile :: forall e m a. (MonadIO m, MonadMask m) => String -> (PathTo e Abs File -> Handle -> m a) -> m a Source #

openTempFile :: forall e e0 b m. MonadIO m => PathTo e0 b Dir -> String -> m (PathTo e Abs File, Handle) Source #

openBinaryTempFile :: forall e e0 b m. MonadIO m => PathTo e0 b Dir -> String -> m (PathTo e Abs File, Handle) Source #

Existence tests

forgivingAbsence :: (MonadIO m, MonadCatch m) => m a -> m (Maybe a) #

If argument of the function throws a doesNotExistErrorType, Nothing is returned (other exceptions propagate). Otherwise the result is returned inside a Just.

Since: path-io-0.3.0

ignoringAbsence :: (MonadIO m, MonadCatch m) => m a -> m () #

The same as forgivingAbsence, but ignores result.

Since: path-io-0.3.1

Permissions

setPermissions :: MonadIO m => PathTo e b t -> Permissions -> m () Source #

copyPermissions :: MonadIO m => PathTo e0 b0 t0 -> PathTo e1 b1 t1 -> m () Source #

Timestamps

getAccessTime :: MonadIO m => PathTo entity pk t -> m UTCTime Source #

setAccessTime :: MonadIO m => PathTo entity pk t -> UTCTime -> m () Source #

setModificationTime :: MonadIO m => PathTo entity pk t -> UTCTime -> m () Source #