Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class Path2nd a c where
- ($-<.>) :: Path a File -> Text -> Path a File
- ($--<.>) :: Path a File -> Text -> Path a File
- replaceExtension' :: Text -> Path a File -> Path a File
- replaceExtension2 :: Text -> Path a File -> Path a File
- getDirectoryFilesP :: Path Abs Dir -> [FilePattern] -> Action [Path Rel File]
- copyFileChangedP :: Path Abs File -> Path Abs File -> Action ()
- runErr2action :: ErrIO a -> Action a
- getFilesToBake :: Text -> Path Abs Dir -> [FilePattern] -> Action [Path Rel File]
- module Uniform.Shake.Path
- takeBaseName :: FilePath -> String
- splitPath :: FilePath -> [FilePath]
- data Action a
- module UniformBase
- data Rules a
- shakeArgs :: ShakeOptions -> Rules () -> IO ()
- shake :: ShakeOptions -> Rules () -> IO ()
- data ShakeOptions = ShakeOptions {
- shakeFiles :: FilePath
- shakeThreads :: Int
- shakeVersion :: String
- shakeVerbosity :: Verbosity
- shakeStaunch :: Bool
- shakeReport :: [FilePath]
- shakeLint :: Maybe Lint
- shakeLintInside :: [FilePath]
- shakeLintIgnore :: [FilePattern]
- shakeLintWatch :: [FilePattern]
- shakeCommandOptions :: [CmdOption]
- shakeFlush :: Maybe Seconds
- shakeRebuild :: [(Rebuild, FilePattern)]
- shakeAbbreviations :: [(String, String)]
- shakeStorageLog :: Bool
- shakeLineBuffering :: Bool
- shakeTimings :: Bool
- shakeRunCommands :: Bool
- shakeChange :: Change
- shakeCreationCheck :: Bool
- shakeLiveFiles :: [FilePath]
- shakeVersionIgnore :: Bool
- shakeColor :: Bool
- shakeShare :: Maybe FilePath
- shakeCloud :: [String]
- shakeSymlink :: Bool
- shakeNeedDirectory :: Bool
- shakeAllowRedefineRules :: Bool
- shakeProgress :: IO Progress -> IO ()
- shakeOutput :: Verbosity -> String -> IO ()
- shakeTrace :: String -> String -> Bool -> IO ()
- shakeExtra :: HashMap TypeRep Dynamic
- shakeOptions :: ShakeOptions
- data Verbosity
- = Silent
- | Warn
- | Info
- | Verbose
- | Diagnostic
- data Lint
- need :: Partial => [FilePath] -> Action ()
- (%>) :: Located => FilePattern -> (FilePath -> Action ()) -> Rules ()
- (|%>) :: Located => [FilePattern] -> (FilePath -> Action ()) -> Rules ()
- want :: Partial => [FilePath] -> Rules ()
- phony :: Located => String -> Action () -> Rules ()
Documentation
class Path2nd a c where Source #
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
runErr2action :: ErrIO a -> Action a Source #
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
module Uniform.Shake.Path
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"]
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
is equivalent
to need
["a"] *> 'need ["b"]
.need
["a", "b"]
Instances
MonadFail Action | |
Defined in Development.Shake.Internal.Core.Types | |
MonadIO Action | |
Defined in Development.Shake.Internal.Core.Types | |
Applicative Action | |
Functor Action | |
Monad Action | |
MonadTempDir Action | |
Defined in Development.Shake.Command runWithTempDir :: (FilePath -> Action a) -> Action a runWithTempFile :: (FilePath -> Action a) -> Action a | |
Monoid a => Monoid (Action a) | |
Semigroup a => Semigroup (Action a) | |
CmdResult r => CmdArguments (Action r) | |
Defined in Development.Shake.Command cmdArguments :: CmdArgument -> Action r # |
module UniformBase
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
MonadFail Rules | |
Defined in Development.Shake.Internal.Core.Rules | |
MonadFix Rules | |
Defined in Development.Shake.Internal.Core.Rules | |
MonadIO Rules | |
Defined in Development.Shake.Internal.Core.Rules | |
Applicative Rules | |
Functor Rules | |
Monad Rules | |
(Semigroup a, Monoid a) => Monoid (Rules a) | |
Semigroup a => Semigroup (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 want
ed (after calling withoutActions
). As an example:
main =shakeArgs
shakeOptions
{shakeFiles
= "_make",shakeProgress
=progressSimple
} $ dophony
"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 anyshakeFiles
.main _make/henry.txt
will not buildneil.txt
oremily.txt
, but will instead buildhenry.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 TypeRep
s.
ShakeOptions | |
|
Instances
Data ShakeOptions | |
Defined in Development.Shake.Internal.Options 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 | |
Defined in Development.Shake.Internal.Options showsPrec :: Int -> ShakeOptions -> ShowS # show :: ShakeOptions -> String # showList :: [ShakeOptions] -> ShowS # |
shakeOptions :: ShakeOptions #
The default set of ShakeOptions
.
The verbosity data type, used by shakeVerbosity
.
Silent | Don't print any messages. |
Warn | Print errors and warnings. |
Info | Print errors, warnings and |
Verbose | Print errors, warnings, full command lines when running a |
Diagnostic | Print messages for virtually everything (mostly for debugging). |
Instances
Which lint checks to perform, used by shakeLint
.
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 |
LintFSATrace | Track which files are accessed by command line programs using fsatrace. |
Instances
Data Lint | |
Defined in Development.Shake.Internal.Options 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 # 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 | |
Enum Lint | |
Read Lint | |
Show Lint | |
Eq Lint | |
Ord 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
outneed
[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
outneed
[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.
want :: Partial => [FilePath] -> Rules () #
Require that the argument files are built by the rules, used to specify the target.
main =shake
shakeOptions
$ dowant
["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
.