Safe Haskell | None |
---|---|
Language | Haskell2010 |
Types for monitoring files and directories.
Synopsis
- data RootedGlob = RootedGlob FilePathRoot Glob
- data FilePathRoot
- data Glob
- data MonitorFilePath
- data MonitorKindFile
- data MonitorKindDir
- monitorFile :: FilePath -> MonitorFilePath
- monitorFileHashed :: FilePath -> MonitorFilePath
- monitorNonExistentFile :: FilePath -> MonitorFilePath
- monitorFileExistence :: FilePath -> MonitorFilePath
- monitorDirectory :: FilePath -> MonitorFilePath
- monitorNonExistentDirectory :: FilePath -> MonitorFilePath
- monitorDirectoryExistence :: FilePath -> MonitorFilePath
- monitorFileOrDirectory :: FilePath -> MonitorFilePath
- monitorFileGlob :: RootedGlob -> MonitorFilePath
- monitorFileGlobExistence :: RootedGlob -> MonitorFilePath
- monitorFileSearchPath :: [FilePath] -> FilePath -> [MonitorFilePath]
- monitorFileHashedSearchPath :: [FilePath] -> FilePath -> [MonitorFilePath]
Globs with respect to a root
data RootedGlob Source #
A file path specified by globbing, relative to some root directory.
RootedGlob | |
|
Instances
data FilePathRoot Source #
FilePathRelative | |
FilePathRoot FilePath | e.g. |
FilePathHomeDir |
Instances
Parsec FilePathRoot Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types parsec :: CabalParsing m => m FilePathRoot Source # | |||||
Pretty FilePathRoot Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types pretty :: FilePathRoot -> Doc Source # prettyVersioned :: CabalSpecVersion -> FilePathRoot -> Doc Source # | |||||
Structured FilePathRoot Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types structure :: Proxy FilePathRoot -> Structure Source # structureHash' :: Tagged FilePathRoot MD5 | |||||
Binary FilePathRoot Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Generic FilePathRoot Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types
from :: FilePathRoot -> Rep FilePathRoot x # to :: Rep FilePathRoot x -> FilePathRoot # | |||||
Show FilePathRoot Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types showsPrec :: Int -> FilePathRoot -> ShowS # show :: FilePathRoot -> String # showList :: [FilePathRoot] -> ShowS # | |||||
Eq FilePathRoot Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types (==) :: FilePathRoot -> FilePathRoot -> Bool # (/=) :: FilePathRoot -> FilePathRoot -> Bool # | |||||
type Rep FilePathRoot Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types type Rep FilePathRoot = D1 ('MetaData "FilePathRoot" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.0.0-be97" '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))) |
A filepath specified by globbing.
Instances
Parsec Glob Source # | |||||
Defined in Distribution.Simple.Glob.Internal parsec :: CabalParsing m => m Glob Source # | |||||
Pretty Glob Source # | |||||
Defined in Distribution.Simple.Glob.Internal | |||||
Structured Glob Source # | |||||
Defined in Distribution.Simple.Glob.Internal | |||||
Binary Glob Source # | |||||
Generic Glob Source # | |||||
Defined in Distribution.Simple.Glob.Internal
| |||||
Show Glob Source # | |||||
Eq Glob Source # | |||||
type Rep Glob Source # | |||||
Defined in Distribution.Simple.Glob.Internal type Rep Glob = D1 ('MetaData "Glob" "Distribution.Simple.Glob.Internal" "Cabal-3.14.0.0-be97" 'False) ((C1 ('MetaCons "GlobDir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GlobPieces) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Glob)) :+: C1 ('MetaCons "GlobDirRecursive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GlobPieces))) :+: (C1 ('MetaCons "GlobFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GlobPieces)) :+: C1 ('MetaCons "GlobDirTrailing" 'PrefixI 'False) (U1 :: Type -> Type))) |
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
Structured MonitorFilePath Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types structure :: Proxy MonitorFilePath -> Structure Source # structureHash' :: Tagged MonitorFilePath MD5 | |||||
Binary MonitorFilePath Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Generic MonitorFilePath Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types
from :: MonitorFilePath -> Rep MonitorFilePath x # to :: Rep MonitorFilePath x -> MonitorFilePath # | |||||
Show MonitorFilePath Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types showsPrec :: Int -> MonitorFilePath -> ShowS # show :: MonitorFilePath -> String # showList :: [MonitorFilePath] -> ShowS # | |||||
Eq MonitorFilePath Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types (==) :: MonitorFilePath -> MonitorFilePath -> Bool # (/=) :: MonitorFilePath -> MonitorFilePath -> Bool # | |||||
type Rep MonitorFilePath Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types type Rep MonitorFilePath = D1 ('MetaData "MonitorFilePath" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.0.0-be97" '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
Structured MonitorKindFile Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types structure :: Proxy MonitorKindFile -> Structure Source # structureHash' :: Tagged MonitorKindFile MD5 | |||||
Binary MonitorKindFile Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Generic MonitorKindFile Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types
from :: MonitorKindFile -> Rep MonitorKindFile x # to :: Rep MonitorKindFile x -> MonitorKindFile # | |||||
Show MonitorKindFile Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types showsPrec :: Int -> MonitorKindFile -> ShowS # show :: MonitorKindFile -> String # showList :: [MonitorKindFile] -> ShowS # | |||||
Eq MonitorKindFile Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types (==) :: MonitorKindFile -> MonitorKindFile -> Bool # (/=) :: MonitorKindFile -> MonitorKindFile -> Bool # | |||||
type Rep MonitorKindFile Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types type Rep MonitorKindFile = D1 ('MetaData "MonitorKindFile" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.0.0-be97" '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
Structured MonitorKindDir Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types structure :: Proxy MonitorKindDir -> Structure Source # structureHash' :: Tagged MonitorKindDir MD5 | |||||
Binary MonitorKindDir Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Generic MonitorKindDir Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types
from :: MonitorKindDir -> Rep MonitorKindDir x # to :: Rep MonitorKindDir x -> MonitorKindDir # | |||||
Show MonitorKindDir Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types showsPrec :: Int -> MonitorKindDir -> ShowS # show :: MonitorKindDir -> String # showList :: [MonitorKindDir] -> ShowS # | |||||
Eq MonitorKindDir Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types (==) :: MonitorKindDir -> MonitorKindDir -> Bool # (/=) :: MonitorKindDir -> MonitorKindDir -> Bool # | |||||
type Rep MonitorKindDir Source # | |||||
Defined in Distribution.Simple.FileMonitor.Types type Rep MonitorKindDir = D1 ('MetaData "MonitorKindDir" "Distribution.Simple.FileMonitor.Types" "Cabal-3.14.0.0-be97" '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.