cabal-install-3.8.1.0: The command-line interface for Cabal and Hackage.
Safe HaskellNone
LanguageHaskell2010

Distribution.Client.RebuildMonad

Description

An abstraction for re-running actions if values or files have changed.

This is not a full-blown make-style incremental build system, it's a bit more ad-hoc than that, but it's easier to integrate with existing code.

It's a convenient interface to the Distribution.Client.FileMonitor functions.

Synopsis

Rebuild monad

data Rebuild a Source #

A monad layered on top of IO to help with re-running actions when the input files and values they depend on change. The crucial operations are rerunIfChanged and monitorFiles.

Instances

Instances details
Monad Rebuild Source # 
Instance details

Defined in Distribution.Client.RebuildMonad

Methods

(>>=) :: Rebuild a -> (a -> Rebuild b) -> Rebuild b #

(>>) :: Rebuild a -> Rebuild b -> Rebuild b #

return :: a -> Rebuild a #

Functor Rebuild Source # 
Instance details

Defined in Distribution.Client.RebuildMonad

Methods

fmap :: (a -> b) -> Rebuild a -> Rebuild b #

(<$) :: a -> Rebuild b -> Rebuild a #

Applicative Rebuild Source # 
Instance details

Defined in Distribution.Client.RebuildMonad

Methods

pure :: a -> Rebuild a #

(<*>) :: Rebuild (a -> b) -> Rebuild a -> Rebuild b #

liftA2 :: (a -> b -> c) -> Rebuild a -> Rebuild b -> Rebuild c #

(*>) :: Rebuild a -> Rebuild b -> Rebuild b #

(<*) :: Rebuild a -> Rebuild b -> Rebuild a #

MonadIO Rebuild Source # 
Instance details

Defined in Distribution.Client.RebuildMonad

Methods

liftIO :: IO a -> Rebuild a #

runRebuild :: FilePath -> Rebuild a -> IO a Source #

Run a Rebuild IO action.

askRoot :: Rebuild FilePath Source #

The root that relative paths are interpreted as being relative to.

Setting up file monitoring

monitorFiles :: [MonitorFilePath] -> Rebuild () Source #

Use this within the body action of rerunIfChanged to declare that the action depends on the given files. This can be based on what the action actually did. It is these files that will be checked for changes next time rerunIfChanged is called for that FileMonitor.

Relative paths are interpreted as relative to an implicit root, ultimately passed in to runRebuild.

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
Eq MonitorFilePath Source # 
Instance details

Defined in Distribution.Client.FileMonitor

Show MonitorFilePath Source # 
Instance details

Defined in Distribution.Client.FileMonitor

Generic MonitorFilePath Source # 
Instance details

Defined in Distribution.Client.FileMonitor

Associated Types

type Rep MonitorFilePath :: Type -> Type #

Binary MonitorFilePath Source # 
Instance details

Defined in Distribution.Client.FileMonitor

Structured MonitorFilePath Source # 
Instance details

Defined in Distribution.Client.FileMonitor

type Rep MonitorFilePath Source # 
Instance details

Defined in Distribution.Client.FileMonitor

type Rep MonitorFilePath = D1 ('MetaData "MonitorFilePath" "Distribution.Client.FileMonitor" "cabal-install-3.8.1.0-7iNu5HGLMqL9QLfLAUJqbd" '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 FilePathGlob))))

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.

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.

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.

Monitoring file globs

monitorFileGlob :: FilePathGlob -> 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 :: FilePathGlob -> 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).

data FilePathGlob Source #

A file path specified by globbing

Instances

Instances details
Eq FilePathGlob Source # 
Instance details

Defined in Distribution.Client.Glob

Show FilePathGlob Source # 
Instance details

Defined in Distribution.Client.Glob

Generic FilePathGlob Source # 
Instance details

Defined in Distribution.Client.Glob

Associated Types

type Rep FilePathGlob :: Type -> Type #

Binary FilePathGlob Source # 
Instance details

Defined in Distribution.Client.Glob

Structured FilePathGlob Source # 
Instance details

Defined in Distribution.Client.Glob

Parsec FilePathGlob Source # 
Instance details

Defined in Distribution.Client.Glob

Pretty FilePathGlob Source # 
Instance details

Defined in Distribution.Client.Glob

type Rep FilePathGlob Source # 
Instance details

Defined in Distribution.Client.Glob

type Rep FilePathGlob = D1 ('MetaData "FilePathGlob" "Distribution.Client.Glob" "cabal-install-3.8.1.0-7iNu5HGLMqL9QLfLAUJqbd" 'False) (C1 ('MetaCons "FilePathGlob" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePathRoot) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePathGlobRel)))

data FilePathRoot Source #

Constructors

FilePathRelative 
FilePathRoot FilePath

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

FilePathHomeDir 

Instances

Instances details
Eq FilePathRoot Source # 
Instance details

Defined in Distribution.Client.Glob

Show FilePathRoot Source # 
Instance details

Defined in Distribution.Client.Glob

Generic FilePathRoot Source # 
Instance details

Defined in Distribution.Client.Glob

Associated Types

type Rep FilePathRoot :: Type -> Type #

Binary FilePathRoot Source # 
Instance details

Defined in Distribution.Client.Glob

Structured FilePathRoot Source # 
Instance details

Defined in Distribution.Client.Glob

Parsec FilePathRoot Source # 
Instance details

Defined in Distribution.Client.Glob

Pretty FilePathRoot Source # 
Instance details

Defined in Distribution.Client.Glob

type Rep FilePathRoot Source # 
Instance details

Defined in Distribution.Client.Glob

type Rep FilePathRoot = D1 ('MetaData "FilePathRoot" "Distribution.Client.Glob" "cabal-install-3.8.1.0-7iNu5HGLMqL9QLfLAUJqbd" '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 FilePathGlobRel Source #

Constructors

GlobDir !Glob !FilePathGlobRel 
GlobFile !Glob 
GlobDirTrailing

trailing dir, a glob ending in /

Instances

Instances details
Eq FilePathGlobRel Source # 
Instance details

Defined in Distribution.Client.Glob

Show FilePathGlobRel Source # 
Instance details

Defined in Distribution.Client.Glob

Generic FilePathGlobRel Source # 
Instance details

Defined in Distribution.Client.Glob

Associated Types

type Rep FilePathGlobRel :: Type -> Type #

Binary FilePathGlobRel Source # 
Instance details

Defined in Distribution.Client.Glob

Structured FilePathGlobRel Source # 
Instance details

Defined in Distribution.Client.Glob

Parsec FilePathGlobRel Source # 
Instance details

Defined in Distribution.Client.Glob

Pretty FilePathGlobRel Source # 
Instance details

Defined in Distribution.Client.Glob

type Rep FilePathGlobRel Source # 
Instance details

Defined in Distribution.Client.Glob

type Rep FilePathGlobRel = D1 ('MetaData "FilePathGlobRel" "Distribution.Client.Glob" "cabal-install-3.8.1.0-7iNu5HGLMqL9QLfLAUJqbd" 'False) (C1 ('MetaCons "GlobDir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Glob) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FilePathGlobRel)) :+: (C1 ('MetaCons "GlobFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Glob)) :+: C1 ('MetaCons "GlobDirTrailing" 'PrefixI 'False) (U1 :: Type -> Type)))

data GlobPiece Source #

A piece of a globbing pattern

Constructors

WildCard 
Literal String 
Union [Glob] 

Instances

Instances details
Eq GlobPiece Source # 
Instance details

Defined in Distribution.Client.Glob

Show GlobPiece Source # 
Instance details

Defined in Distribution.Client.Glob

Generic GlobPiece Source # 
Instance details

Defined in Distribution.Client.Glob

Associated Types

type Rep GlobPiece :: Type -> Type #

Binary GlobPiece Source # 
Instance details

Defined in Distribution.Client.Glob

Structured GlobPiece Source # 
Instance details

Defined in Distribution.Client.Glob

type Rep GlobPiece Source # 
Instance details

Defined in Distribution.Client.Glob

type Rep GlobPiece = D1 ('MetaData "GlobPiece" "Distribution.Client.Glob" "cabal-install-3.8.1.0-7iNu5HGLMqL9QLfLAUJqbd" 'False) (C1 ('MetaCons "WildCard" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Literal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "Union" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Glob]))))

Using a file monitor

data FileMonitor a b Source #

A monitor for detecting changes to a set of files. It can be used to efficiently test if any of a set of files (specified individually or by glob patterns) has changed since some snapshot. In addition, it also checks for changes in a value (of type a), and when there are no changes in either it returns a saved value (of type b).

The main use case looks like this: suppose we have some expensive action that depends on certain pure inputs and reads some set of files, and produces some pure result. We want to avoid re-running this action when it would produce the same result. So we need to monitor the files the action looked at, the other pure input values, and we need to cache the result. Then at some later point, if the input value didn't change, and none of the files changed, then we can re-use the cached result rather than re-running the action.

This can be achieved using a FileMonitor. Each FileMonitor instance saves state in a disk file, so the file for that has to be specified, making sure it is unique. The pattern is to use checkFileMonitorChanged to see if there's been any change. If there is, re-run the action, keeping track of the files, then use updateFileMonitor to record the current set of files to monitor, the current input value for the action, and the result of the action.

The typical occurrence of this pattern is captured by rerunIfChanged and the Rebuild monad. More complicated cases may need to use checkFileMonitorChanged and updateFileMonitor directly.

Constructors

FileMonitor 

Fields

newFileMonitor Source #

Arguments

:: Eq a 
=> FilePath

The file to cache the state of the file monitor. Must be unique.

-> FileMonitor a b 

Define a new file monitor.

It's best practice to define file monitor values once, and then use the same value for checkFileMonitorChanged and updateFileMonitor as this ensures you get the same types a and b for reading and writing.

The path of the file monitor itself must be unique because it keeps state on disk and these would clash.

rerunIfChanged :: (Binary a, Structured a, Binary b, Structured b) => Verbosity -> FileMonitor a b -> a -> Rebuild b -> Rebuild b Source #

This captures the standard use pattern for a FileMonitor: given a monitor, an action and the input value the action depends on, either re-run the action to get its output, or if the value and files the action depends on have not changed then return a previously cached action result.

The result is still in the Rebuild monad, so these can be nested.

Do not share FileMonitors between different uses of rerunIfChanged.

Utils

delayInitSharedResource :: forall a. IO a -> Rebuild (Rebuild a) Source #

When using rerunIfChanged for each element of a list of actions, it is sometimes the case that each action needs to make use of some resource. e.g.

sequence
  [ rerunIfChanged verbosity monitor key $ do
      resource <- mkResource
      ... -- use the resource
  | ... ]

For efficiency one would like to share the resource between the actions but the straightforward way of doing this means initialising it every time even when no actions need re-running.

resource <- mkResource
sequence
  [ rerunIfChanged verbosity monitor key $ do
      ... -- use the resource
  | ... ]

This utility allows one to get the best of both worlds:

getResource <- delayInitSharedResource mkResource
sequence
  [ rerunIfChanged verbosity monitor key $ do
      resource <- getResource
      ... -- use the resource
  | ... ]

delayInitSharedResources :: forall k v. Ord k => (k -> IO v) -> Rebuild (k -> Rebuild v) Source #

Much like delayInitSharedResource but for a keyed set of resources.

getResource <- delayInitSharedResource mkResource
sequence
  [ rerunIfChanged verbosity monitor key $ do
      resource <- getResource key
      ... -- use the resource
  | ... ]

matchFileGlob :: FilePathGlob -> Rebuild [FilePath] Source #

Utility to match a file glob against the file system, starting from a given root directory. The results are all relative to the given root.

Since this operates in the Rebuild monad, it also monitors the given glob for changes.

monitorDirectoryStatus :: FilePath -> Rebuild Bool Source #

Monitor a directory as in monitorDirectory if it currently exists or as monitorNonExistentDirectory if it does not.

doesFileExistMonitored :: FilePath -> Rebuild Bool Source #

Like doesFileExist, but in the Rebuild monad. This does NOT track the contents of FilePath; use need in that case.

need :: FilePath -> Rebuild () Source #

Monitor a single file

needIfExists :: FilePath -> Rebuild () Source #

Monitor a file if it exists; otherwise check for when it gets created. This is a bit better for recompilation avoidance because sometimes users give bad package metadata, and we don't want to repeatedly rebuild in this case (which we would if we need'ed a non-existent file).

findFileWithExtensionMonitored :: [String] -> [FilePath] -> FilePath -> Rebuild (Maybe FilePath) Source #

Like findFileWithExtension, but in the Rebuild monad.

findFirstFileMonitored :: forall a. (a -> FilePath) -> [a] -> Rebuild (Maybe a) Source #

Like findFirstFile, but in the Rebuild monad.