Cabal
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Simple.FileMonitor.Types

Description

Types for monitoring files and directories.

Synopsis

Globs with respect to a root

data RootedGlob Source #

A file path specified by globbing, relative to some root directory.

Constructors

RootedGlob 

Fields

Instances

Instances details
Parsec RootedGlob Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Methods

parsec :: CabalParsing m => m RootedGlob

Pretty RootedGlob Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Methods

pretty :: RootedGlob -> Doc

prettyVersioned :: CabalSpecVersion -> RootedGlob -> Doc

Structured RootedGlob Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Methods

structure :: Proxy RootedGlob -> Structure

structureHash' :: Tagged RootedGlob MD5

Generic RootedGlob Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Associated Types

type Rep RootedGlob :: Type -> Type #

Show RootedGlob Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Binary RootedGlob Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Eq RootedGlob Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep RootedGlob Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep RootedGlob = D1 ('MetaData "RootedGlob" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.1.0-inplace" 'False) (C1 ('MetaCons "RootedGlob" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePathRoot) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Glob)))

data FilePathRoot Source #

Constructors

FilePathRelative 
FilePathRoot FilePath

e.g. "/", "c:" or result of takeDrive

FilePathHomeDir 

Instances

Instances details
Parsec FilePathRoot Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Methods

parsec :: CabalParsing m => m FilePathRoot

Pretty FilePathRoot Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Methods

pretty :: FilePathRoot -> Doc

prettyVersioned :: CabalSpecVersion -> FilePathRoot -> Doc

Structured FilePathRoot Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Methods

structure :: Proxy FilePathRoot -> Structure

structureHash' :: Tagged FilePathRoot MD5

Generic FilePathRoot Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Associated Types

type Rep FilePathRoot :: Type -> Type #

Show FilePathRoot Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Binary FilePathRoot Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Eq FilePathRoot Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep FilePathRoot Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep FilePathRoot = D1 ('MetaData "FilePathRoot" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.1.0-inplace" 'False) (C1 ('MetaCons "FilePathRelative" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FilePathRoot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "FilePathHomeDir" 'PrefixI 'False) (U1 :: Type -> Type)))

data Glob Source #

A filepath specified by globbing.

Instances

Instances details
Parsec Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Methods

parsec :: CabalParsing m => m Glob

Pretty Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Methods

pretty :: Glob -> Doc

prettyVersioned :: CabalSpecVersion -> Glob -> Doc

Structured Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Methods

structure :: Proxy Glob -> Structure

structureHash' :: Tagged Glob MD5

Generic Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Associated Types

type Rep Glob :: Type -> Type #

Methods

from :: Glob -> Rep Glob x #

to :: Rep Glob x -> Glob #

Show Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Methods

showsPrec :: Int -> Glob -> ShowS #

show :: Glob -> String #

showList :: [Glob] -> ShowS #

Binary Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Methods

put :: Glob -> Put #

get :: Get Glob #

putList :: [Glob] -> Put #

Eq Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

Methods

(==) :: Glob -> Glob -> Bool #

(/=) :: Glob -> Glob -> Bool #

type Rep Glob Source # 
Instance details

Defined in Distribution.Simple.Glob.Internal

File monitoring

data MonitorFilePath Source #

A description of a file (or set of files) to monitor for changes.

Where file paths are relative they are relative to a common directory (e.g. project root), not necessarily the process current directory.

Instances

Instances details
Structured MonitorFilePath Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Methods

structure :: Proxy MonitorFilePath -> Structure

structureHash' :: Tagged MonitorFilePath MD5

Generic MonitorFilePath Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Associated Types

type Rep MonitorFilePath :: Type -> Type #

Show MonitorFilePath Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Binary MonitorFilePath Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Eq MonitorFilePath Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorFilePath Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorFilePath = D1 ('MetaData "MonitorFilePath" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.1.0-inplace" 'False) (C1 ('MetaCons "MonitorFile" 'PrefixI 'True) (S1 ('MetaSel ('Just "monitorKindFile") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MonitorKindFile) :*: (S1 ('MetaSel ('Just "monitorKindDir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MonitorKindDir) :*: S1 ('MetaSel ('Just "monitorPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FilePath))) :+: C1 ('MetaCons "MonitorFileGlob" 'PrefixI 'True) (S1 ('MetaSel ('Just "monitorKindFile") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MonitorKindFile) :*: (S1 ('MetaSel ('Just "monitorKindDir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MonitorKindDir) :*: S1 ('MetaSel ('Just "monitorPathGlob") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RootedGlob))))

data MonitorKindFile Source #

Instances

Instances details
Structured MonitorKindFile Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Methods

structure :: Proxy MonitorKindFile -> Structure

structureHash' :: Tagged MonitorKindFile MD5

Generic MonitorKindFile Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Associated Types

type Rep MonitorKindFile :: Type -> Type #

Show MonitorKindFile Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Binary MonitorKindFile Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Eq MonitorKindFile Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorKindFile Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorKindFile = D1 ('MetaData "MonitorKindFile" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.1.0-inplace" 'False) ((C1 ('MetaCons "FileExists" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FileModTime" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FileHashed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FileNotExists" 'PrefixI 'False) (U1 :: Type -> Type)))

data MonitorKindDir Source #

Instances

Instances details
Structured MonitorKindDir Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Methods

structure :: Proxy MonitorKindDir -> Structure

structureHash' :: Tagged MonitorKindDir MD5

Generic MonitorKindDir Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Associated Types

type Rep MonitorKindDir :: Type -> Type #

Show MonitorKindDir Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Binary MonitorKindDir Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

Eq MonitorKindDir Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorKindDir Source # 
Instance details

Defined in Distribution.Simple.FileMonitor.Types

type Rep MonitorKindDir = D1 ('MetaData "MonitorKindDir" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.1.0-inplace" 'False) (C1 ('MetaCons "DirExists" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DirModTime" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DirNotExists" 'PrefixI 'False) (U1 :: Type -> Type)))

Utility constructors of MonitorFilePath

monitorFile :: FilePath -> MonitorFilePath Source #

Monitor a single file for changes, based on its modification time. The monitored file is considered to have changed if it no longer exists or if its modification time has changed.

monitorFileHashed :: FilePath -> MonitorFilePath Source #

Monitor a single file for changes, based on its modification time and content hash. The monitored file is considered to have changed if it no longer exists or if its modification time and content hash have changed.

monitorNonExistentFile :: FilePath -> MonitorFilePath Source #

Monitor a single non-existent file for changes. The monitored file is considered to have changed if it exists.

monitorFileExistence :: FilePath -> MonitorFilePath Source #

Monitor a single file for existence only. The monitored file is considered to have changed if it no longer exists.

monitorDirectory :: FilePath -> MonitorFilePath Source #

Monitor a single directory for changes, based on its modification time. The monitored directory is considered to have changed if it no longer exists or if its modification time has changed.

monitorNonExistentDirectory :: FilePath -> MonitorFilePath Source #

Monitor a single non-existent directory for changes. The monitored directory is considered to have changed if it exists.

monitorDirectoryExistence :: FilePath -> MonitorFilePath Source #

Monitor a single directory for existence. The monitored directory is considered to have changed only if it no longer exists.

monitorFileOrDirectory :: FilePath -> MonitorFilePath Source #

Monitor a single file or directory for changes, based on its modification time. The monitored file is considered to have changed if it no longer exists or if its modification time has changed.

monitorFileGlob :: RootedGlob -> MonitorFilePath Source #

Monitor a set of files (or directories) identified by a file glob. The monitored glob is considered to have changed if the set of files matching the glob changes (i.e. creations or deletions), or for files if the modification time and content hash of any matching file has changed.

monitorFileGlobExistence :: RootedGlob -> MonitorFilePath Source #

Monitor a set of files (or directories) identified by a file glob for existence only. The monitored glob is considered to have changed if the set of files matching the glob changes (i.e. creations or deletions).

monitorFileSearchPath :: [FilePath] -> FilePath -> [MonitorFilePath] Source #

Creates a list of files to monitor when you search for a file which unsuccessfully looked in notFoundAtPaths before finding it at foundAtPath.

monitorFileHashedSearchPath :: [FilePath] -> FilePath -> [MonitorFilePath] Source #

Similar to monitorFileSearchPath, but also instructs us to monitor the hash of the found file.