shake-plus-0.1.9.0: Re-export of Shake using well-typed paths and ReaderT.

Safe HaskellNone
LanguageHaskell2010

Development.Shake.Plus.Core

Synopsis

Documentation

class MonadIO m => MonadAction m where Source #

Monads in which Actions may be embedded.

Methods

liftAction :: Action a -> m a Source #

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

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

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

runSimpleShakePlus :: MonadIO m => ShakePlus LogFunc a -> m () Source #

Run a ShakePlus with just a LogFunc in the environment that logs to stderr.

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, MonadFail or liftIO . throwIO.

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

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

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

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.