uniform-shake-0.1.5.1: uniform wrapper for shake
Safe HaskellSafe-Inferred
LanguageHaskell2010

Uniform.Shake

Synopsis

Documentation

class Path2nd a c where Source #

Minimal complete definition

stripProperPrefixP, replaceDirectoryP

Methods

stripProperPrefixP :: Path a b -> Path a c -> Path Rel c Source #

makeRelativeP :: Path a Dir -> Path a c -> Path Rel c Source #

replaceDirectoryP :: Path a Dir -> Path a Dir -> Path a c -> Path a c Source #

strip the first (the prefix) and add the second to the third

Instances

Instances details
Path2nd a Dir Source # 
Instance details

Defined in Uniform.Shake

Path2nd a File Source # 
Instance details

Defined in Uniform.Shake

getFilesToBake :: Text -> Path Abs Dir -> [FilePattern] -> Action [Path Rel File] Source #

get all files according to the FilePattern (see Shake docs) in the given directory but excludes all filepath which contain one of the strings in the first argument to allow directories which are not baked

takeBaseName :: FilePath -> String #

Get the base name, without an extension or path.

takeBaseName "/directory/file.ext" == "file"
takeBaseName "file/test.txt" == "test"
takeBaseName "dave.ext" == "dave"
takeBaseName "" == ""
takeBaseName "test" == "test"
takeBaseName (addTrailingPathSeparator x) == ""
takeBaseName "file/file.tar.gz" == "file.tar"

splitPath :: FilePath -> [FilePath] #

Split a path by the directory separator.

splitPath "/directory/file.ext" == ["/","directory/","file.ext"]
concat (splitPath x) == x
splitPath "test//item/" == ["test//","item/"]
splitPath "test/item/file" == ["test/","item/","file"]
splitPath "" == []
Windows: splitPath "c:\\test\\path" == ["c:\\","test\\","path"]
Posix:   splitPath "/file/test" == ["/","file/","test"]

data Action a #

The Action monad, use liftIO to raise IO actions into it, and need to execute files. Action values are used by addUserRule and action. The Action monad tracks the dependencies of a rule. To raise an exception call error, fail or liftIO . throwIO.

The Action type is both a Monad and Applicative. Anything that is depended upon applicatively will have its dependencies run in parallel. For example need ["a"] *> 'need ["b"] is equivalent to need ["a", "b"].

Instances

Instances details
MonadFail Action 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

fail :: String -> Action a #

MonadIO Action 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

liftIO :: IO a -> Action a #

Applicative Action 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

pure :: a -> Action a #

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

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

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

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

Functor Action 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

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

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

Monad Action 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

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

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

return :: a -> Action a #

MonadTempDir Action 
Instance details

Defined in Development.Shake.Command

Monoid a => Monoid (Action a) 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

mempty :: Action a #

mappend :: Action a -> Action a -> Action a #

mconcat :: [Action a] -> Action a #

Semigroup a => Semigroup (Action a) 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

(<>) :: Action a -> Action a -> Action a #

sconcat :: NonEmpty (Action a) -> Action a #

stimes :: Integral b => b -> Action a -> Action a #

CmdResult r => CmdArguments (Action r) 
Instance details

Defined in Development.Shake.Command

data Rules a #

Define a set of rules. Rules can be created with calls to functions such as %> or action. Rules are combined with either the Monoid instance, or (more commonly) the Monad instance and do notation. To define your own custom types of rule, see Development.Shake.Rule.

Instances

Instances details
MonadFail Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

fail :: String -> Rules a #

MonadFix Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

mfix :: (a -> Rules a) -> Rules a #

MonadIO Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

liftIO :: IO a -> Rules a #

Applicative Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

pure :: a -> Rules a #

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

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

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

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

Functor Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

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

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

Monad Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

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

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

return :: a -> Rules a #

(Semigroup a, Monoid a) => Monoid (Rules a) 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

mempty :: Rules a #

mappend :: Rules a -> Rules a -> Rules a #

mconcat :: [Rules a] -> Rules a #

Semigroup a => Semigroup (Rules a) 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

(<>) :: Rules a -> Rules a -> Rules a #

sconcat :: NonEmpty (Rules a) -> Rules a #

stimes :: Integral b => b -> Rules a -> Rules a #

shakeArgs :: ShakeOptions -> Rules () -> IO () #

Run a build system using command line arguments for configuration. The available flags are those from shakeOptDescrs, along with a few additional make compatible flags that are not represented in ShakeOptions, such as --print-directory. If there are no file arguments then the Rules are used directly, otherwise the file arguments are wanted (after calling withoutActions). As an example:

main = shakeArgs shakeOptions{shakeFiles = "_make", shakeProgress = progressSimple} $ do
    phony "clean" $ removeFilesAfter "_make" ["//*"]
    want ["_make/neil.txt","_make/emily.txt"]
    "_make/*.txt" %> \out ->
        ... build action here ...

This build system will default to building neil.txt and emily.txt, while showing progress messages, and putting the Shake files in locations such as _make/.database. Some example command line flags:

  • main --no-progress will turn off progress messages.
  • main -j6 will build on 6 threads.
  • main --help will display a list of supported flags.
  • main clean will not build anything, but will remove the _make directory, including the any shakeFiles.
  • main _make/henry.txt will not build neil.txt or emily.txt, but will instead build henry.txt.

shake :: ShakeOptions -> Rules () -> IO () #

Main entry point for running Shake build systems. For an example see the top of the module Development.Shake. Use ShakeOptions to specify how the system runs, and Rules to specify what to build. The function will throw an exception if the build fails.

To use command line flags to modify ShakeOptions see shakeArgs.

data ShakeOptions #

Options to control the execution of Shake, usually specified by overriding fields in shakeOptions:

 shakeOptions{shakeThreads=4, shakeReport=["report.html"]}

The Data instance for this type reports the shakeProgress and shakeOutput fields as having the abstract type Hidden, because Data cannot be defined for functions or TypeReps.

Constructors

ShakeOptions 

Fields

  • shakeFiles :: FilePath

    Defaults to .shake. The directory used for storing Shake metadata files. All metadata files will be named shakeFiles/.shake.file-name, for some file-name. If the shakeFiles directory does not exist it will be created. If set to "/dev/null" then no shakeFiles are read or written (even on Windows).

  • shakeThreads :: Int

    Defaults to 1. Maximum number of rules to run in parallel, similar to make --jobs=N. For many build systems, a number equal to or slightly less than the number of physical processors works well. Use 0 to match the detected number of processors (when 0, getShakeOptions will return the number of threads used).

  • shakeVersion :: String

    Defaults to "1". The version number of your build rules. Change the version number to force a complete rebuild, such as when making significant changes to the rules that require a wipe. The version number should be set in the source code, and not passed on the command line.

  • shakeVerbosity :: Verbosity

    Defaults to Info. What level of messages should be printed out.

  • shakeStaunch :: Bool

    Defaults to False. Operate in staunch mode, where building continues even after errors, similar to make --keep-going.

  • shakeReport :: [FilePath]

    Defaults to []. Write a profiling report to a file, showing which rules rebuilt, why, and how much time they took. Useful for improving the speed of your build systems. If the file extension is .json it will write JSON data; if .js it will write Javascript; if .trace it will write trace events (load into about://tracing in Chrome); otherwise it will write HTML.

  • shakeLint :: Maybe Lint

    Defaults to Nothing. Perform sanity checks during building, see Lint for details.

  • shakeLintInside :: [FilePath]

    Directories in which the files will be tracked by the linter.

  • shakeLintIgnore :: [FilePattern]

    File patterns which are ignored from linter tracking, a bit like calling trackAllow in every rule.

  • shakeLintWatch :: [FilePattern]

    File patterns whose modification causes an error. Raises an error even if shakeLint is Nothing.

  • shakeCommandOptions :: [CmdOption]

    Defaults to []. Additional options to be passed to all command invocations.

  • shakeFlush :: Maybe Seconds

    Defaults to Just 10. How often to flush Shake metadata files in seconds, or Nothing to never flush explicitly. It is possible that on abnormal termination (not Haskell exceptions) any rules that completed in the last shakeFlush seconds will be lost.

  • shakeRebuild :: [(Rebuild, FilePattern)]

    What to rebuild

  • shakeAbbreviations :: [(String, String)]

    Defaults to []. A list of substrings that should be abbreviated in status messages, and their corresponding abbreviation. Commonly used to replace the long paths (e.g. .make/i586-linux-gcc/output) with an abbreviation (e.g. $OUT).

  • shakeStorageLog :: Bool

    Defaults to False. Write a message to shakeFiles/.shake.storage.log whenever a storage event happens which may impact on the current stored progress. Examples include database version number changes, database compaction or corrupt files.

  • shakeLineBuffering :: Bool

    Defaults to True. Change stdout and stderr to line buffering while running Shake.

  • shakeTimings :: Bool

    Defaults to False. Print timing information for each stage at the end.

  • shakeRunCommands :: Bool

    Default to True. Should you run command line actions, set to False to skip actions whose output streams and exit code are not used. Useful for profiling the non-command portion of the build system.

  • shakeChange :: Change

    Default to ChangeModtime. How to check if a file has changed, see Change for details.

  • shakeCreationCheck :: Bool

    Default to True. After running a rule to create a file, is it an error if the file does not exist. Provided for compatibility with make and ninja (which have ugly file creation semantics).

  • shakeLiveFiles :: [FilePath]

    Default to []. After the build system completes, write a list of all files which were live in that run, i.e. those which Shake checked were valid or rebuilt. Produces best answers if nothing rebuilds.

  • shakeVersionIgnore :: Bool

    Defaults to False. Ignore any differences in shakeVersion.

  • shakeColor :: Bool

    Defaults to False. Whether to colorize the output.

  • shakeShare :: Maybe FilePath

    Defaults to Nothing. Whether to use and store outputs in a shared directory.

  • shakeCloud :: [String]

    Defaults to []. Cloud servers to talk to forming a shared cache.

  • shakeSymlink :: Bool

    Defaults to False. Use symlinks for shakeShare if they are available. If this setting is True (even if symlinks are not available) then files will be made read-only to avoid inadvertantly poisoning the shared cache. Note the links are actually hard links, not symlinks.

  • shakeNeedDirectory :: Bool

    Defaults to False. Is depending on a directory an error (default), or it is permitted with undefined results. Provided for compatibility with ninja.

  • shakeAllowRedefineRules :: Bool

    Whether to allow calling addBuiltinRule for the same key more than once

  • shakeProgress :: IO Progress -> IO ()

    Defaults to no action. A function called when the build starts, allowing progress to be reported. The function is called on a separate thread, and that thread is killed when the build completes. For applications that want to display progress messages, progressSimple is often sufficient, but more advanced users should look at the Progress data type.

  • shakeOutput :: Verbosity -> String -> IO ()

    Defaults to writing using putStrLn. A function called to output messages from Shake, along with the Verbosity at which that message should be printed. This function will be called atomically from all other shakeOutput functions. The Verbosity will always be greater than or higher than shakeVerbosity.

  • shakeTrace :: String -> String -> Bool -> IO ()

    Defaults to doing nothing. Called for each call of traced, with the key, the command and True for starting, False for stopping.

  • shakeExtra :: HashMap TypeRep Dynamic

    This a map which can be used to store arbitrary extra information that a user may need when writing rules. The key of each entry must be the dynTypeRep of the value. Insert values using addShakeExtra and retrieve them using getShakeExtra. The correct way to use this field is to define a hidden newtype for the key, so that conflicts cannot occur.

Instances

Instances details
Data ShakeOptions 
Instance details

Defined in Development.Shake.Internal.Options

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ShakeOptions -> c ShakeOptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ShakeOptions #

toConstr :: ShakeOptions -> Constr #

dataTypeOf :: ShakeOptions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ShakeOptions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShakeOptions) #

gmapT :: (forall b. Data b => b -> b) -> ShakeOptions -> ShakeOptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ShakeOptions -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ShakeOptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> ShakeOptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ShakeOptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ShakeOptions -> m ShakeOptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ShakeOptions -> m ShakeOptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ShakeOptions -> m ShakeOptions #

Show ShakeOptions 
Instance details

Defined in Development.Shake.Internal.Options

shakeOptions :: ShakeOptions #

The default set of ShakeOptions.

data Verbosity #

The verbosity data type, used by shakeVerbosity.

Constructors

Silent

Don't print any messages.

Warn

Print errors and warnings.

Info

Print errors, warnings and # command-name (for file-name) when running a traced command.

Verbose

Print errors, warnings, full command lines when running a command or cmd command and status messages when starting a rule.

Diagnostic

Print messages for virtually everything (mostly for debugging).

Instances

Instances details
Data Verbosity 
Instance details

Defined in Development.Shake.Internal.Options

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Verbosity -> c Verbosity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Verbosity #

toConstr :: Verbosity -> Constr #

dataTypeOf :: Verbosity -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Verbosity) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity) #

gmapT :: (forall b. Data b => b -> b) -> Verbosity -> Verbosity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Verbosity -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Verbosity -> r #

gmapQ :: (forall d. Data d => d -> u) -> Verbosity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Verbosity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Verbosity -> m Verbosity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Verbosity -> m Verbosity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Verbosity -> m Verbosity #

Bounded Verbosity 
Instance details

Defined in Development.Shake.Internal.Options

Enum Verbosity 
Instance details

Defined in Development.Shake.Internal.Options

Read Verbosity 
Instance details

Defined in Development.Shake.Internal.Options

Show Verbosity 
Instance details

Defined in Development.Shake.Internal.Options

Eq Verbosity 
Instance details

Defined in Development.Shake.Internal.Options

Ord Verbosity 
Instance details

Defined in Development.Shake.Internal.Options

data Lint #

Which lint checks to perform, used by shakeLint.

Constructors

LintBasic

The most basic form of linting. Checks that the current directory does not change and that results do not change after they are first written. Any calls to needed will assert that they do not cause a rule to be rebuilt.

LintFSATrace

Track which files are accessed by command line programs using fsatrace.

Instances

Instances details
Data Lint 
Instance details

Defined in Development.Shake.Internal.Options

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Lint -> c Lint #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Lint #

toConstr :: Lint -> Constr #

dataTypeOf :: Lint -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Lint) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lint) #

gmapT :: (forall b. Data b => b -> b) -> Lint -> Lint #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Lint -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Lint -> r #

gmapQ :: (forall d. Data d => d -> u) -> Lint -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Lint -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Lint -> m Lint #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Lint -> m Lint #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Lint -> m Lint #

Bounded Lint 
Instance details

Defined in Development.Shake.Internal.Options

Enum Lint 
Instance details

Defined in Development.Shake.Internal.Options

Methods

succ :: Lint -> Lint #

pred :: Lint -> Lint #

toEnum :: Int -> Lint #

fromEnum :: Lint -> Int #

enumFrom :: Lint -> [Lint] #

enumFromThen :: Lint -> Lint -> [Lint] #

enumFromTo :: Lint -> Lint -> [Lint] #

enumFromThenTo :: Lint -> Lint -> Lint -> [Lint] #

Read Lint 
Instance details

Defined in Development.Shake.Internal.Options

Show Lint 
Instance details

Defined in Development.Shake.Internal.Options

Methods

showsPrec :: Int -> Lint -> ShowS #

show :: Lint -> String #

showList :: [Lint] -> ShowS #

Eq Lint 
Instance details

Defined in Development.Shake.Internal.Options

Methods

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

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

Ord Lint 
Instance details

Defined in Development.Shake.Internal.Options

Methods

compare :: Lint -> Lint -> Ordering #

(<) :: Lint -> Lint -> Bool #

(<=) :: Lint -> Lint -> Bool #

(>) :: Lint -> Lint -> Bool #

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

max :: Lint -> Lint -> Lint #

min :: Lint -> Lint -> Lint #

need :: Partial => [FilePath] -> Action () #

Add a dependency on the file arguments, ensuring they are built before continuing. The file arguments may be built in parallel, in any order. This function is particularly necessary when calling cmd or command. As an example:

"//*.rot13" %> \out -> do
    let src = dropExtension out
    need [src]
    cmd "rot13" [src] "-o" [out]

Usually need [foo,bar] is preferable to need [foo] >> need [bar] as the former allows greater parallelism, while the latter requires foo to finish building before starting to build bar.

This function should not be called with wildcards (e.g. *.txt - use getDirectoryFiles to expand them), environment variables (e.g. $HOME - use getEnv to expand them) or directories (directories cannot be tracked directly - track files within the directory instead).

(%>) :: Located => FilePattern -> (FilePath -> Action ()) -> Rules () infix 1 #

Define a rule that matches a FilePattern, see ?== for the pattern rules. Patterns with no wildcards have higher priority than those with wildcards, and no file required by the system may be matched by more than one pattern at the same priority (see priority and alternatives to modify this behaviour). This function will create the directory for the result file, if necessary.

"*.asm.o" %> \out -> do
    let src = dropExtension out
    need [src]
    cmd "as" [src] "-o" [out]

To define a build system for multiple compiled languages, we recommend using .asm.o, .cpp.o, .hs.o, to indicate which language produces an object file. I.e., the file foo.cpp produces object file foo.cpp.o.

Note that matching is case-sensitive, even on Windows.

If the Action completes successfully the file is considered up-to-date, even if the file has not changed.

(|%>) :: Located => [FilePattern] -> (FilePath -> Action ()) -> Rules () infix 1 #

Define a set of patterns, and if any of them match, run the associated rule. Defined in terms of %>. Think of it as the OR (||) equivalent of %>.

want :: Partial => [FilePath] -> Rules () #

Require that the argument files are built by the rules, used to specify the target.

main = shake shakeOptions $ do
   want ["Main.exe"]
   ...

This program will build Main.exe, given sufficient rules. All arguments to all want calls may be built in parallel, in any order.

This function is defined in terms of action and need, use action if you need more complex targets than want allows.

phony :: Located => String -> Action () -> Rules () #

Declare a Make-style phony action. A phony target does not name a file (despite living in the same namespace as file rules); rather, it names some action to be executed when explicitly requested. You can demand phony rules using want. (And need, although that's not recommended.)

Phony actions are intended to define recipes that can be executed by the user. If you need a phony action in a rule then every execution where that rule is required will rerun both the rule and the phony action. However, note that phony actions are never executed more than once in a single build run.

In make, the .PHONY attribute on non-file-producing rules has a similar effect. However, while in make it is acceptable to omit the .PHONY attribute as long as you don't create the file in question, a Shake rule which behaves this way will fail lint. For file-producing rules which should be rerun every execution of Shake, see alwaysRerun.