Safe Haskell | None |
---|---|
Language | Haskell2010 |
A generic approach to building and caching file outputs.
This is a layer on top of Shake which enables build actions to be written in a "forwards" style. For example:
runPier $ action $ do contents <- lines <$> readArtifactA (externalFile "result.txt") let result = "result.tar" runCommand (output result) $ foldMap input contents <> prog "tar" (["-cf", result] ++ map pathIn contents)
This approach generally leads to simpler logic than backwards-defined build systems such as make or (normal) Shake, where each step of the build logic must be written as a new build rule.
Inputs and outputs of a command must be declared up-front, using the input
and output
functions respectively. This enables isolated, deterministic
build steps which are each run in their own temporary directory.
Output files are stored in the location
_pier/artifact/HASH/path/to/file
where HASH
is a string that uniquely determines the action generating
that file. In particular, there is no need to worry about choosing distinct names
for outputs of different commands.
Note that Forward
has similar motivation to this module,
but instead uses fsatrace
to detect what files changed after the fact.
Unfortunately, that approach is not portable. Additionally, it makes it
difficult to isolate steps and make the build more reproducible (for example,
to prevent the output of one step being mutated by a later one) since every
output file could potentially be an input to every action. Finally, by
explicitly declaring outputs we can detect sooner when a command doesn't
produce the files that we expect.
- artifactRules :: HandleTemps -> Rules ()
- data Artifact
- externalFile :: FilePath -> Artifact
- (/>) :: Artifact -> FilePath -> Artifact
- replaceArtifactExtension :: Artifact -> String -> Artifact
- readArtifact :: Artifact -> Action String
- readArtifactB :: Artifact -> Action ByteString
- doesArtifactExist :: Artifact -> Action Bool
- matchArtifactGlob :: Artifact -> FilePath -> Action [FilePath]
- unfreezeArtifacts :: IO ()
- callArtifact :: HandleTemps -> Set Artifact -> Artifact -> [String] -> IO ()
- writeArtifact :: FilePath -> String -> Action Artifact
- runCommand :: Output t -> Command -> Action t
- runCommand_ :: Command -> Action ()
- runCommandStdout :: Command -> Action String
- data Command
- message :: String -> Command
- data Output a
- output :: FilePath -> Output Artifact
- input :: Artifact -> Command
- inputs :: Set Artifact -> Command
- inputList :: [Artifact] -> Command
- shadow :: Artifact -> FilePath -> Command
- groupFiles :: Artifact -> [(FilePath, FilePath)] -> Action Artifact
- prog :: String -> [String] -> Command
- progA :: Artifact -> [String] -> Command
- progTemp :: FilePath -> [String] -> Command
- pathIn :: Artifact -> FilePath
- withCwd :: FilePath -> Command -> Command
- createDirectoryA :: FilePath -> Command
Rules
artifactRules :: HandleTemps -> Rules () Source #
Artifact
An Artifact
is a file or folder that was created by a build command.
externalFile :: FilePath -> Artifact Source #
Create an Artifact
from an input file to the build (for example, a
source file created by the user).
If it is a relative path, changes to the file will cause rebuilds of Commands and Rules that dependended on it.
(/>) :: Artifact -> FilePath -> Artifact infixr 5 Source #
Create a reference to a sub-file of the given Artifact
, which must
refer to a directory.
replaceArtifactExtension :: Artifact -> String -> Artifact Source #
Replace the extension of an Artifact. In particular,
pathIn (replaceArtifactExtension f ext) == replaceExtension (pathIn f) ext@
readArtifactB :: Artifact -> Action ByteString Source #
unfreezeArtifacts :: IO () Source #
Make all artifacts user-writable, so they can be deleted by `clean-all`.
callArtifact :: HandleTemps -> Set Artifact -> Artifact -> [String] -> IO () Source #
Creating artifacts
runCommand :: Output t -> Command -> Action t Source #
Run the given command, capturing the specified outputs.
runCommand_ :: Command -> Action () Source #
Run the given command without capturing its output. Can be used to check consistency of the outputs of previous commands.
Command outputs
The output of a given command.
Multiple outputs may be combined using the Applicative
instance.
output :: FilePath -> Output Artifact Source #
Register a single output of a command.
The input must be a relative path and nontrivial (i.e., not "."
or ""
).
Command inputs
shadow :: Artifact -> FilePath -> Command Source #
Make a "shadow" copy of the given input artifact's by create a symlink of this artifact (if it is a file) or of each sub-file (transitively, if it is a directory).
The result may be captured as output, for example when grouping multiple outputs of separate commands into a common directory structure.
groupFiles :: Artifact -> [(FilePath, FilePath)] -> Action Artifact Source #
Group source files by shadowing into a single directory.
Running commands
prog :: String -> [String] -> Command Source #
Run an external command-line program with the given arguments.
progA :: Artifact -> [String] -> Command Source #
Run an artifact as an command-line program with the given arguments.
progTemp :: FilePath -> [String] -> Command Source #
Run a command-line program with the given arguments, where the program was created by a previous program.
withCwd :: FilePath -> Command -> Command Source #
Runs a command within the given (relative) directory.
createDirectoryA :: FilePath -> Command Source #