pier-core-0.3.0.0: A library for writing forwards-declared build systems in haskell.

Safe HaskellNone
LanguageHaskell2010

Pier.Core.Artifact

Contents

Description

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 (external "result.txt")
    let result = "result.tar"
    runCommandOutput 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.

Synopsis

Rules

newtype SharedCache Source #

Constructors

SharedCache FilePath 

Artifact

data Artifact Source #

An Artifact is a file or folder that was created by a build command.

Instances
Eq Artifact Source # 
Instance details

Defined in Pier.Core.Internal.Store

Ord Artifact Source # 
Instance details

Defined in Pier.Core.Internal.Store

Show Artifact Source # 
Instance details

Defined in Pier.Core.Internal.Store

Generic Artifact Source # 
Instance details

Defined in Pier.Core.Internal.Store

Associated Types

type Rep Artifact :: * -> * #

Methods

from :: Artifact -> Rep Artifact x #

to :: Rep Artifact x -> Artifact #

Binary Artifact Source # 
Instance details

Defined in Pier.Core.Internal.Store

Methods

put :: Artifact -> Put #

get :: Get Artifact #

putList :: [Artifact] -> Put #

NFData Artifact Source # 
Instance details

Defined in Pier.Core.Internal.Store

Methods

rnf :: Artifact -> () #

Hashable Artifact Source # 
Instance details

Defined in Pier.Core.Internal.Store

Methods

hashWithSalt :: Int -> Artifact -> Int #

hash :: Artifact -> Int #

type Rep Artifact Source # 
Instance details

Defined in Pier.Core.Internal.Store

external :: 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@

readArtifact :: Artifact -> Action String Source #

Read the contents of an Artifact.

unfreezeArtifacts :: IO () Source #

Make all artifacts user-writable, so they can be deleted by `clean-all`.

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.

data Command Source #

A hermetic build step. Consists of a sequence of calls to message, 'prog'/'progA'/'progTemp', andor shadow, which may be combined using <>mappend. Also specifies the input Artifacts that are used by those commands.

Instances
Eq Command Source # 
Instance details

Defined in Pier.Core.Artifact

Methods

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

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

Generic Command Source # 
Instance details

Defined in Pier.Core.Artifact

Associated Types

type Rep Command :: * -> * #

Methods

from :: Command -> Rep Command x #

to :: Rep Command x -> Command #

Semigroup Command Source # 
Instance details

Defined in Pier.Core.Artifact

Monoid Command Source # 
Instance details

Defined in Pier.Core.Artifact

Binary Command Source # 
Instance details

Defined in Pier.Core.Artifact

Methods

put :: Command -> Put #

get :: Get Command #

putList :: [Command] -> Put #

NFData Command Source # 
Instance details

Defined in Pier.Core.Artifact

Methods

rnf :: Command -> () #

Hashable Command Source # 
Instance details

Defined in Pier.Core.Artifact

Methods

hashWithSalt :: Int -> Command -> Int #

hash :: Command -> Int #

type Rep Command Source # 
Instance details

Defined in Pier.Core.Artifact

message :: String -> Command Source #

Prints a status message for the user when this command runs.

Command outputs

data Output a Source #

The output of a given command.

Multiple outputs may be combined using the Applicative instance.

Instances
Functor Output Source # 
Instance details

Defined in Pier.Core.Artifact

Methods

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

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

Applicative Output Source # 
Instance details

Defined in Pier.Core.Artifact

Methods

pure :: a -> Output a #

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

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

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

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

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

input :: Artifact -> Command Source #

Specify that an Artifact should be made available to program calls within this Command.

Note that the order does not matter; `input f <> cmd === cmd <> input f`.

inputs :: Set Artifact -> Command Source #

Specify that a set of Artifacts should be made available to program calls within this Command.

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.

pathIn :: Artifact -> FilePath Source #

Returns the relative path to an Artifact within the sandbox, when provided to a Command by input.

withCwd :: FilePath -> Command -> Command Source #

Runs a command within the given (relative) directory.