shake-plus-0.3.4.0: Re-export of Shake using well-typed paths and ReaderT.
LicenseMIT
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Development.Shake.Plus.Core

Description

Core definitions of shake-plus.

Synopsis

Documentation

class MonadIO m => MonadAction m where Source #

Monads in which Actions may be embedded.

Methods

liftAction :: Action a -> m a Source #

Instances

Instances details
MonadAction Action Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

liftAction :: Action a -> Action a Source #

MonadAction (RAction r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

liftAction :: Action a -> RAction r a Source #

MonadAction m => MonadAction (ReaderT r m) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

liftAction :: Action a -> ReaderT r m a Source #

class Monad m => MonadRules m where Source #

Methods

liftRules :: Rules a -> m a Source #

Instances

Instances details
MonadRules Rules Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

liftRules :: Rules a -> Rules a Source #

MonadRules (ShakePlus r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

liftRules :: Rules a -> ShakePlus r a Source #

MonadRules m => MonadRules (ReaderT r m) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

liftRules :: Rules a -> ReaderT r m a Source #

newtype UnliftAction m Source #

Constructors

UnliftAction 

Fields

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.

Minimal complete definition

Nothing

Methods

withRunInAction :: ((forall a. m a -> Action a) -> Action b) -> m b Source #

Instances

Instances details
MonadUnliftAction Action Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

withRunInAction :: ((forall a. Action a -> Action a) -> Action b) -> Action b Source #

MonadUnliftAction (RAction r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

withRunInAction :: ((forall a. RAction r a -> Action a) -> Action b) -> RAction r b Source #

MonadUnliftAction m => MonadUnliftAction (ReaderT r m) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

withRunInAction :: ((forall a. ReaderT r m a -> Action a) -> Action b) -> ReaderT r m b Source #

data RAction r a Source #

Concrete Action runner, hardcoded to `ReaderT r Action a`.

Instances

Instances details
MonadReader r (RAction r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

ask :: RAction r r #

local :: (r -> r) -> RAction r a -> RAction r a #

reader :: (r -> a) -> RAction r a #

Monad (RAction r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

(>>=) :: RAction r a -> (a -> RAction r b) -> RAction r b #

(>>) :: RAction r a -> RAction r b -> RAction r b #

return :: a -> RAction r a #

Functor (RAction r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

fmap :: (a -> b) -> RAction r a -> RAction r b #

(<$) :: a -> RAction r b -> RAction r a #

MonadFail (RAction r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

fail :: String -> RAction r a #

Applicative (RAction r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

pure :: a -> RAction r a #

(<*>) :: RAction r (a -> b) -> RAction r a -> RAction r b #

liftA2 :: (a -> b -> c) -> RAction r a -> RAction r b -> RAction r c #

(*>) :: RAction r a -> RAction r b -> RAction r b #

(<*) :: RAction r a -> RAction r b -> RAction r a #

MonadIO (RAction r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

liftIO :: IO a -> RAction r a #

MonadThrow (RAction r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

throwM :: Exception e => e -> RAction r a #

MonadUnliftAction (RAction r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

withRunInAction :: ((forall a. RAction r a -> Action a) -> Action b) -> RAction r b Source #

MonadAction (RAction r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

liftAction :: Action a -> RAction r a Source #

data ShakePlus r a Source #

Concrete Rules collector, hardcoded to `ReaderT r Rules a`.

Instances

Instances details
MonadReader r (ShakePlus r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

ask :: ShakePlus r r #

local :: (r -> r) -> ShakePlus r a -> ShakePlus r a #

reader :: (r -> a) -> ShakePlus r a #

Monad (ShakePlus r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

(>>=) :: ShakePlus r a -> (a -> ShakePlus r b) -> ShakePlus r b #

(>>) :: ShakePlus r a -> ShakePlus r b -> ShakePlus r b #

return :: a -> ShakePlus r a #

Functor (ShakePlus r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

fmap :: (a -> b) -> ShakePlus r a -> ShakePlus r b #

(<$) :: a -> ShakePlus r b -> ShakePlus r a #

Applicative (ShakePlus r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

pure :: a -> ShakePlus r a #

(<*>) :: ShakePlus r (a -> b) -> ShakePlus r a -> ShakePlus r b #

liftA2 :: (a -> b -> c) -> ShakePlus r a -> ShakePlus r b -> ShakePlus r c #

(*>) :: ShakePlus r a -> ShakePlus r b -> ShakePlus r b #

(<*) :: ShakePlus r a -> ShakePlus r b -> ShakePlus r a #

MonadIO (ShakePlus r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

liftIO :: IO a -> ShakePlus r a #

MonadThrow (ShakePlus r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

throwM :: Exception e => e -> ShakePlus r a #

MonadRules (ShakePlus r) Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

liftRules :: Rules a -> ShakePlus r a 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 #

Run a ShakePlus with an environment, consuming it for some Shake Rules.

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.

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
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 #

Functor Action 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

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

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

MonadFail Action 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

fail :: String -> 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 #

MonadIO Action 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

liftIO :: IO a -> Action a #

MonadUnliftAction Action Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

withRunInAction :: ((forall a. Action a -> Action a) -> Action b) -> Action b Source #

MonadAction Action Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

liftAction :: Action a -> Action a Source #

MonadTempDir Action 
Instance details

Defined in Development.Shake.Command

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 #

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 #

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
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 #

Functor Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

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

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

MonadFix Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

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

MonadFail Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

fail :: String -> 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 #

MonadIO Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

liftIO :: IO a -> Rules a #

MonadRules Rules Source # 
Instance details

Defined in Development.Shake.Plus.Core

Methods

liftRules :: Rules a -> Rules a Source #

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 #

(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 #

type FilePattern = String #

A type synonym for file patterns, containing // and *. For the syntax and semantics of FilePattern see ?==.

Most normaliseExd 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

Instances details
type RuleResult FileQ 
Instance details

Defined in Development.Shake.Internal.Rules.File

type RuleResult FileQ = FileR
type RuleResult DoesDirectoryExistQ 
Instance details

Defined in Development.Shake.Internal.Rules.Directory

type RuleResult DoesDirectoryExistQ = DoesDirectoryExistA
type RuleResult DoesFileExistQ 
Instance details

Defined in Development.Shake.Internal.Rules.Directory

type RuleResult DoesFileExistQ = DoesFileExistA
type RuleResult GetDirectoryContentsQ 
Instance details

Defined in Development.Shake.Internal.Rules.Directory

type RuleResult GetDirectoryContentsQ = GetDirectoryA
type RuleResult GetDirectoryDirsQ 
Instance details

Defined in Development.Shake.Internal.Rules.Directory

type RuleResult GetDirectoryDirsQ = GetDirectoryA
type RuleResult GetDirectoryFilesQ 
Instance details

Defined in Development.Shake.Internal.Rules.Directory

type RuleResult GetDirectoryFilesQ = GetDirectoryA
type RuleResult GetEnvQ 
Instance details

Defined in Development.Shake.Internal.Rules.Directory

type RuleResult GetEnvQ = GetEnvA
type RuleResult FilesQ 
Instance details

Defined in Development.Shake.Internal.Rules.Files

type RuleResult FilesQ = FilesA
type RuleResult AlwaysRerunQ 
Instance details

Defined in Development.Shake.Internal.Rules.Rerun

type RuleResult AlwaysRerunQ = ()
type RuleResult Config 
Instance details

Defined in Development.Shake.Config

type RuleResult Config = Maybe String
type RuleResult ConfigKeys 
Instance details

Defined in Development.Shake.Config

type RuleResult ConfigKeys = [String]
type RuleResult Forward 
Instance details

Defined in Development.Shake.Forward

type RuleResult Forward = Forward
type RuleResult (OracleQ a) 
Instance details

Defined in Development.Shake.Internal.Rules.Oracle

type RuleResult (OracleQ a) = OracleA (RuleResult a)

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 and Hashable 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.) The Hashable 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 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.

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 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