License | MIT |
---|---|
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Core definitions of shake-plus.
Synopsis
- class MonadIO m => MonadAction m where
- liftAction :: Action a -> m a
- class Monad m => MonadRules m where
- newtype UnliftAction m = UnliftAction {
- unliftAction :: forall a. m a -> Action a
- class MonadAction m => MonadUnliftAction m where
- withRunInAction :: ((forall a. m a -> Action a) -> Action b) -> m b
- withUnliftAction :: MonadUnliftAction m => (UnliftAction m -> Action a) -> m a
- askUnliftAction :: MonadUnliftAction m => m (UnliftAction m)
- toAction :: MonadUnliftAction m => m a -> m (Action a)
- data RAction r a
- data ShakePlus r a
- runRAction :: MonadAction m => env -> RAction env a -> m a
- runShakePlus :: MonadRules m => env -> ShakePlus env a -> m a
- parallel :: MonadUnliftAction m => [m a] -> m [a]
- forP :: MonadUnliftAction m => [a] -> (a -> m b) -> m [b]
- par :: MonadUnliftAction m => m a -> m b -> m (a, b)
- data Action a
- data Rules a
- type FilePattern = String
- type family RuleResult key
- type ShakeValue a = (Show a, Typeable a, Eq a, Hashable a, Binary a, NFData a)
- shake :: ShakeOptions -> Rules () -> IO ()
- shakeArgs :: ShakeOptions -> Rules () -> IO ()
- shakeOptions :: ShakeOptions
- 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
Documentation
class MonadIO m => MonadAction m where Source #
Monads in which Action
s may be embedded.
liftAction :: Action a -> m a Source #
Instances
MonadAction Action Source # | |
Defined in Development.Shake.Plus.Core liftAction :: Action a -> Action a Source # | |
MonadAction (RAction r) Source # | |
Defined in Development.Shake.Plus.Core liftAction :: Action a -> RAction r a Source # | |
MonadAction m => MonadAction (ReaderT r m) Source # | |
Defined in Development.Shake.Plus.Core liftAction :: Action a -> ReaderT r m a Source # |
class Monad m => MonadRules m where Source #
Instances
MonadRules Rules Source # | |
MonadRules (ShakePlus r) Source # | |
MonadRules m => MonadRules (ReaderT r m) Source # | |
newtype UnliftAction m Source #
UnliftAction | |
|
class MonadAction m => MonadUnliftAction m where Source #
Monads which allow their actions to be run in Action
.
For the same reasons as MonadUnliftIO
this is limited to ReaderT
and IdentityT
transformers on top of Action
.
Nothing
withRunInAction :: ((forall a. m a -> Action a) -> Action b) -> m b Source #
Instances
MonadUnliftAction Action Source # | |
Defined in Development.Shake.Plus.Core | |
MonadUnliftAction (RAction r) Source # | |
Defined in Development.Shake.Plus.Core | |
MonadUnliftAction m => MonadUnliftAction (ReaderT r m) Source # | |
Defined in Development.Shake.Plus.Core |
withUnliftAction :: MonadUnliftAction m => (UnliftAction m -> Action a) -> m a Source #
askUnliftAction :: MonadUnliftAction m => m (UnliftAction m) Source #
toAction :: MonadUnliftAction m => m a -> m (Action a) Source #
Concrete Action
runner, hardcoded to `ReaderT r Action a`.
Instances
MonadReader r (RAction r) Source # | |
Monad (RAction r) Source # | |
Functor (RAction r) Source # | |
MonadFail (RAction r) Source # | |
Defined in Development.Shake.Plus.Core | |
Applicative (RAction r) Source # | |
MonadIO (RAction r) Source # | |
Defined in Development.Shake.Plus.Core | |
MonadThrow (RAction r) Source # | |
Defined in Development.Shake.Plus.Core | |
MonadUnliftAction (RAction r) Source # | |
Defined in Development.Shake.Plus.Core | |
MonadAction (RAction r) Source # | |
Defined in Development.Shake.Plus.Core liftAction :: Action a -> RAction r a Source # |
Concrete Rules
collector, hardcoded to `ReaderT r Rules a`.
Instances
MonadReader r (ShakePlus r) Source # | |
Monad (ShakePlus r) Source # | |
Functor (ShakePlus r) Source # | |
Applicative (ShakePlus r) Source # | |
Defined in Development.Shake.Plus.Core | |
MonadIO (ShakePlus r) Source # | |
Defined in Development.Shake.Plus.Core | |
MonadThrow (ShakePlus r) Source # | |
Defined in Development.Shake.Plus.Core | |
MonadRules (ShakePlus r) Source # | |
runRAction :: MonadAction m => env -> RAction env a -> m a Source #
Run an RAction
with an environment, consuming it for a result.
runShakePlus :: MonadRules m => env -> ShakePlus env a -> m a Source #
parallel :: MonadUnliftAction m => [m a] -> m [a] Source #
Unlifted parallel
.
forP :: MonadUnliftAction m => [a] -> (a -> m b) -> m [b] Source #
Unlifted forP
.
par :: MonadUnliftAction m => m a -> m b -> m (a, b) Source #
Unlifted par
.
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
Monad Action | |
Functor Action | |
MonadFail Action | |
Defined in Development.Shake.Internal.Core.Types | |
Applicative Action | |
MonadIO Action | |
Defined in Development.Shake.Internal.Core.Types | |
MonadUnliftAction Action Source # | |
Defined in Development.Shake.Plus.Core | |
MonadAction Action Source # | |
Defined in Development.Shake.Plus.Core liftAction :: Action a -> Action a Source # | |
MonadTempDir Action | |
Defined in Development.Shake.Command runWithTempDir :: (FilePath -> Action a) -> Action a runWithTempFile :: (FilePath -> Action a) -> Action a | |
Semigroup a => Semigroup (Action a) | |
Monoid a => Monoid (Action a) | |
CmdResult r => CmdArguments (Action r) | |
Defined in Development.Shake.Command cmdArguments :: CmdArgument -> Action r # |
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
Monad Rules | |
Functor Rules | |
MonadFix Rules | |
Defined in Development.Shake.Internal.Core.Rules | |
MonadFail Rules | |
Defined in Development.Shake.Internal.Core.Rules | |
Applicative Rules | |
MonadIO Rules | |
Defined in Development.Shake.Internal.Core.Rules | |
MonadRules Rules Source # | |
Semigroup a => Semigroup (Rules a) | |
(Semigroup a, Monoid a) => Monoid (Rules a) | |
type FilePattern = String #
A type synonym for file patterns, containing //
and *
. For the syntax
and semantics of FilePattern
see ?==
.
Most normaliseEx
d FilePath
values are suitable as FilePattern
values which match
only that specific file. On Windows \
is treated as equivalent to /
.
You can write FilePattern
values as a literal string, or build them
up using the operators <.>
, </>
and <//>
. However, beware that:
- On Windows, use
<.>
from Development.Shake.FilePath instead of from System.FilePath - otherwise"//*" <.> exe
results in"//*\\.exe"
. - If the second argument of
</>
has a leading path separator (namely/
) then the second argument will be returned.
type family RuleResult key #
The type mapping between the key
or a rule and the resulting value
.
See addBuiltinRule
and apply
.
Instances
type RuleResult FileQ | |
Defined in Development.Shake.Internal.Rules.File type RuleResult FileQ = FileR | |
type RuleResult DoesDirectoryExistQ | |
Defined in Development.Shake.Internal.Rules.Directory type RuleResult DoesDirectoryExistQ = DoesDirectoryExistA | |
type RuleResult DoesFileExistQ | |
Defined in Development.Shake.Internal.Rules.Directory type RuleResult DoesFileExistQ = DoesFileExistA | |
type RuleResult GetDirectoryContentsQ | |
Defined in Development.Shake.Internal.Rules.Directory type RuleResult GetDirectoryContentsQ = GetDirectoryA | |
type RuleResult GetDirectoryDirsQ | |
Defined in Development.Shake.Internal.Rules.Directory type RuleResult GetDirectoryDirsQ = GetDirectoryA | |
type RuleResult GetDirectoryFilesQ | |
Defined in Development.Shake.Internal.Rules.Directory type RuleResult GetDirectoryFilesQ = GetDirectoryA | |
type RuleResult GetEnvQ | |
Defined in Development.Shake.Internal.Rules.Directory type RuleResult GetEnvQ = GetEnvA | |
type RuleResult FilesQ | |
Defined in Development.Shake.Internal.Rules.Files type RuleResult FilesQ = FilesA | |
type RuleResult AlwaysRerunQ | |
Defined in Development.Shake.Internal.Rules.Rerun type RuleResult AlwaysRerunQ = () | |
type RuleResult Config | |
Defined in Development.Shake.Config | |
type RuleResult ConfigKeys | |
Defined in Development.Shake.Config | |
type RuleResult Forward | |
Defined in Development.Shake.Forward type RuleResult Forward = Forward | |
type RuleResult (OracleQ a) | |
Defined in Development.Shake.Internal.Rules.Oracle |
type ShakeValue a = (Show a, Typeable a, Eq a, Hashable a, Binary a, NFData a) #
Define an alias for the six type classes required for things involved in Shake rules.
Using this alias requires the ConstraintKinds
extension.
To define your own values meeting the necessary constraints it is convenient to use the extensions
GeneralizedNewtypeDeriving
and DeriveDataTypeable
to write:
newtype MyType = MyType (String, Bool) deriving (Show, Typeable, Eq, Hashable, Binary, NFData)
Shake needs these instances on keys and values. They are used for:
Show
is used to print out keys in errors, profiling, progress messages and diagnostics.Typeable
is used because Shake indexes its database by the type of the key and value involved in the rule (overlap is not allowed for type classes and not allowed in Shake either).Eq
andHashable
are used on keys in order to build hash maps from keys to values.Eq
is used on values to test if the value has changed or not (this is used to support unchanging rebuilds, where Shake can avoid rerunning rules if it runs a dependency, but it turns out that no changes occurred.) TheHashable
instances are only use at runtime (never serialised to disk), so they do not have to be stable across runs. Hashable on values is not used, and only required for a consistent interface.Binary
is used to serialize keys and values into Shake's build database; this lets Shake cache values across runs and implement unchanging rebuilds.NFData
is used to avoid space and thunk leaks, especially when Shake is parallelized.
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
.
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
.
shakeOptions :: ShakeOptions #
The default set of ShakeOptions
.
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 # |