{-# LANGUAGE TupleSections #-}
module Development.Shake.Internal.Args(
shakeOptDescrs,
shake,
shakeArgs, shakeArgsWith, shakeArgsOptionsWith
) where
import Development.Shake.Internal.Paths
import Development.Shake.Internal.Options
import Development.Shake.Internal.Core.Rules
import Development.Shake.Internal.Errors
import Development.Shake.Internal.CompactUI
import Development.Shake.Internal.Demo
import Development.Shake.Internal.Core.Action
import Development.Shake.FilePath
import Development.Shake.Internal.Rules.File
import Development.Shake.Internal.Progress
import Development.Shake.Database
import General.Timing
import General.Extra
import General.Thread
import General.GetOpt
import General.EscCodes
import Data.Tuple.Extra
import Control.DeepSeq
import Control.Exception.Extra
import Control.Monad
import Data.Either
import Data.List.Extra
import Data.Maybe
import System.Directory.Extra
import System.Environment
import System.Exit
import System.Time.Extra
shake :: ShakeOptions -> Rules () -> IO ()
shake :: ShakeOptions -> Rules () -> IO ()
shake ShakeOptions
opts Rules ()
rules = do
String -> IO ()
addTiming String
"Function shake"
([Any]
_, [IO ()]
after) <- ShakeOptions
-> Rules ()
-> (ShakeDatabase -> IO ([Any], [IO ()]))
-> IO ([Any], [IO ()])
forall a.
ShakeOptions -> Rules () -> (ShakeDatabase -> IO a) -> IO a
shakeWithDatabase ShakeOptions
opts Rules ()
rules ((ShakeDatabase -> IO ([Any], [IO ()])) -> IO ([Any], [IO ()]))
-> (ShakeDatabase -> IO ([Any], [IO ()])) -> IO ([Any], [IO ()])
forall a b. (a -> b) -> a -> b
$ \ShakeDatabase
db -> do
ShakeDatabase -> IO ()
shakeOneShotDatabase ShakeDatabase
db
ShakeDatabase -> [Action Any] -> IO ([Any], [IO ()])
forall a. ShakeDatabase -> [Action a] -> IO ([a], [IO ()])
shakeRunDatabase ShakeDatabase
db []
ShakeOptions -> [IO ()] -> IO ()
shakeRunAfter ShakeOptions
opts [IO ()]
after
shakeArgs :: ShakeOptions -> Rules () -> IO ()
shakeArgs :: ShakeOptions -> Rules () -> IO ()
shakeArgs ShakeOptions
opts Rules ()
rules = ShakeOptions
-> [OptDescr (Either String Any)]
-> ([Any] -> [String] -> IO (Maybe (Rules ())))
-> IO ()
forall a.
ShakeOptions
-> [OptDescr (Either String a)]
-> ([a] -> [String] -> IO (Maybe (Rules ())))
-> IO ()
shakeArgsWith ShakeOptions
opts [] [Any] -> [String] -> IO (Maybe (Rules ()))
forall (f :: * -> *) p.
Applicative f =>
p -> [String] -> f (Maybe (Rules ()))
f
where f :: p -> [String] -> f (Maybe (Rules ()))
f p
_ [String]
files = Maybe (Rules ()) -> f (Maybe (Rules ()))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (Rules ()) -> f (Maybe (Rules ())))
-> Maybe (Rules ()) -> f (Maybe (Rules ()))
forall a b. (a -> b) -> a -> b
$ Rules () -> Maybe (Rules ())
forall a. a -> Maybe a
Just (Rules () -> Maybe (Rules ())) -> Rules () -> Maybe (Rules ())
forall a b. (a -> b) -> a -> b
$ if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
files then Rules ()
rules else Partial => [String] -> Rules ()
[String] -> Rules ()
want [String]
files Rules () -> Rules () -> Rules ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Rules () -> Rules ()
forall a. Rules a -> Rules a
withoutActions Rules ()
rules
shakeArgsWith :: ShakeOptions -> [OptDescr (Either String a)] -> ([a] -> [String] -> IO (Maybe (Rules ()))) -> IO ()
shakeArgsWith :: ShakeOptions
-> [OptDescr (Either String a)]
-> ([a] -> [String] -> IO (Maybe (Rules ())))
-> IO ()
shakeArgsWith ShakeOptions
opt [OptDescr (Either String a)]
args [a] -> [String] -> IO (Maybe (Rules ()))
f = ShakeOptions
-> [OptDescr (Either String a)]
-> (ShakeOptions
-> [a] -> [String] -> IO (Maybe (ShakeOptions, Rules ())))
-> IO ()
forall a.
ShakeOptions
-> [OptDescr (Either String a)]
-> (ShakeOptions
-> [a] -> [String] -> IO (Maybe (ShakeOptions, Rules ())))
-> IO ()
shakeArgsOptionsWith ShakeOptions
opt [OptDescr (Either String a)]
args ((ShakeOptions
-> [a] -> [String] -> IO (Maybe (ShakeOptions, Rules ())))
-> IO ())
-> (ShakeOptions
-> [a] -> [String] -> IO (Maybe (ShakeOptions, Rules ())))
-> IO ()
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
so [a]
a [String]
b -> (Rules () -> (ShakeOptions, Rules ()))
-> Maybe (Rules ()) -> Maybe (ShakeOptions, Rules ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ShakeOptions
so,) (Maybe (Rules ()) -> Maybe (ShakeOptions, Rules ()))
-> IO (Maybe (Rules ())) -> IO (Maybe (ShakeOptions, Rules ()))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [a] -> [String] -> IO (Maybe (Rules ()))
f [a]
a [String]
b
shakeArgsOptionsWith
:: ShakeOptions
-> [OptDescr (Either String a)]
-> (ShakeOptions -> [a] -> [String] -> IO (Maybe (ShakeOptions, Rules ())))
-> IO ()
shakeArgsOptionsWith :: ShakeOptions
-> [OptDescr (Either String a)]
-> (ShakeOptions
-> [a] -> [String] -> IO (Maybe (ShakeOptions, Rules ())))
-> IO ()
shakeArgsOptionsWith ShakeOptions
baseOpts [OptDescr (Either String a)]
userOptions ShakeOptions
-> [a] -> [String] -> IO (Maybe (ShakeOptions, Rules ()))
rules = do
String -> IO ()
addTiming String
"shakeArgsWith"
let baseOpts2 :: [OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))]
baseOpts2 = [OptDescr (Either String a)]
-> [OptDescr
(Either String ([Extra], ShakeOptions -> ShakeOptions))]
-> [OptDescr
(Either String ([Extra], ShakeOptions -> ShakeOptions))]
forall b a. [OptDescr b] -> [OptDescr a] -> [OptDescr a]
removeOverlap [OptDescr (Either String a)]
userOptions ([OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))]
-> [OptDescr
(Either String ([Extra], ShakeOptions -> ShakeOptions))])
-> [OptDescr
(Either String ([Extra], ShakeOptions -> ShakeOptions))]
-> [OptDescr
(Either String ([Extra], ShakeOptions -> ShakeOptions))]
forall a b. (a -> b) -> a -> b
$ ((Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
-> OptDescr
(Either String ([Extra], ShakeOptions -> ShakeOptions)))
-> [(Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))]
-> [OptDescr
(Either String ([Extra], ShakeOptions -> ShakeOptions))]
forall a b. (a -> b) -> [a] -> [b]
map (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
-> OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
forall a b. (a, b) -> b
snd [(Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))]
shakeOptsEx
[String]
args <- IO [String]
getArgs
let ([Either ([Extra], ShakeOptions -> ShakeOptions) a]
flag1,[String]
files,[String]
errs) = [OptDescr
(Either String (Either ([Extra], ShakeOptions -> ShakeOptions) a))]
-> [String]
-> ([Either ([Extra], ShakeOptions -> ShakeOptions) a], [String],
[String])
forall a.
[OptDescr (Either String a)]
-> [String] -> ([a], [String], [String])
getOpt ([OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))]
baseOpts2 [OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))]
-> [OptDescr (Either String a)]
-> [OptDescr
(Either String (Either ([Extra], ShakeOptions -> ShakeOptions) a))]
forall a b.
[OptDescr (Either String a)]
-> [OptDescr (Either String b)]
-> [OptDescr (Either String (Either a b))]
`mergeOptDescr` [OptDescr (Either String a)]
userOptions) [String]
args
([([Extra], ShakeOptions -> ShakeOptions)]
self,[a]
user) = [Either ([Extra], ShakeOptions -> ShakeOptions) a]
-> ([([Extra], ShakeOptions -> ShakeOptions)], [a])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either ([Extra], ShakeOptions -> ShakeOptions) a]
flag1
([Extra]
flagsExtra,[ShakeOptions -> ShakeOptions]
flagsShake) = ([[Extra]] -> [Extra])
-> ([[Extra]], [ShakeOptions -> ShakeOptions])
-> ([Extra], [ShakeOptions -> ShakeOptions])
forall a a' b. (a -> a') -> (a, b) -> (a', b)
first [[Extra]] -> [Extra]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (([[Extra]], [ShakeOptions -> ShakeOptions])
-> ([Extra], [ShakeOptions -> ShakeOptions]))
-> ([[Extra]], [ShakeOptions -> ShakeOptions])
-> ([Extra], [ShakeOptions -> ShakeOptions])
forall a b. (a -> b) -> a -> b
$ [([Extra], ShakeOptions -> ShakeOptions)]
-> ([[Extra]], [ShakeOptions -> ShakeOptions])
forall a b. [(a, b)] -> ([a], [b])
unzip [([Extra], ShakeOptions -> ShakeOptions)]
self
progressReplays :: [String]
progressReplays = [String
x | ProgressReplay String
x <- [Extra]
flagsExtra]
progressRecords :: [String]
progressRecords = [String
x | ProgressRecord String
x <- [Extra]
flagsExtra]
changeDirectory :: Maybe String
changeDirectory = [String] -> Maybe String
forall a. [a] -> Maybe a
listToMaybe [String
x | ChangeDirectory String
x <- [Extra]
flagsExtra]
printDirectory :: Bool
printDirectory = Bool -> [Bool] -> Bool
forall a. a -> [a] -> a
lastDef Bool
False [Bool
x | PrintDirectory Bool
x <- [Extra]
flagsExtra]
shareRemoves :: [String]
shareRemoves = [String
x | ShareRemove String
x <- [Extra]
flagsExtra]
oshakeOpts :: ShakeOptions
oshakeOpts = (ShakeOptions -> (ShakeOptions -> ShakeOptions) -> ShakeOptions)
-> ShakeOptions -> [ShakeOptions -> ShakeOptions] -> ShakeOptions
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (((ShakeOptions -> ShakeOptions) -> ShakeOptions -> ShakeOptions)
-> ShakeOptions -> (ShakeOptions -> ShakeOptions) -> ShakeOptions
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ShakeOptions -> ShakeOptions) -> ShakeOptions -> ShakeOptions
forall a b. (a -> b) -> a -> b
($)) ShakeOptions
baseOpts [ShakeOptions -> ShakeOptions]
flagsShake
[String]
lintInside <- (String -> IO String) -> [String] -> IO [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> IO String
canonicalizePath ([String] -> IO [String]) -> [String] -> IO [String]
forall a b. (a -> b) -> a -> b
$ ShakeOptions -> [String]
shakeLintInside ShakeOptions
oshakeOpts
let shakeOpts :: ShakeOptions
shakeOpts = ShakeOptions
oshakeOpts {shakeLintInside :: [String]
shakeLintInside = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String
toStandard (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
addTrailingPathSeparator) [String]
lintInside
,shakeLintIgnore :: [String]
shakeLintIgnore = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
toStandard ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ ShakeOptions -> [String]
shakeLintIgnore ShakeOptions
oshakeOpts
,shakeOutput :: Verbosity -> String -> IO ()
shakeOutput = if ShakeOptions -> Bool
shakeColor ShakeOptions
oshakeOpts
then (Verbosity -> String -> IO ()) -> Verbosity -> String -> IO ()
outputColor (ShakeOptions -> Verbosity -> String -> IO ()
shakeOutput ShakeOptions
oshakeOpts)
else ShakeOptions -> Verbosity -> String -> IO ()
shakeOutput ShakeOptions
oshakeOpts
}
let putWhen :: Verbosity -> String -> IO ()
putWhen Verbosity
v String
msg = Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ShakeOptions -> Verbosity
shakeVerbosity ShakeOptions
oshakeOpts Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
v) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ ShakeOptions -> Verbosity -> String -> IO ()
shakeOutput ShakeOptions
oshakeOpts Verbosity
v String
msg
let putWhenLn :: Verbosity -> String -> IO ()
putWhenLn Verbosity
v String
msg = Verbosity -> String -> IO ()
putWhen Verbosity
v (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
msg String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
let showHelp :: Bool -> IO ()
showHelp Bool
long = do
String
progName <- IO String
getProgName
([String]
targets, [String]
helpSuffix) <- if Bool -> Bool
not Bool
long then ([String], [String]) -> IO ([String], [String])
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([], []) else
(SomeException -> IO ([String], [String]))
-> IO ([String], [String]) -> IO ([String], [String])
forall a. (SomeException -> IO a) -> IO a -> IO a
handleSynchronous (\SomeException
e -> do Verbosity -> String -> IO ()
putWhenLn Verbosity
Info (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Failure to collect targets: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ SomeException -> String
forall a. Show a => a -> String
show SomeException
e; ([String], [String]) -> IO ([String], [String])
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([], [])) (IO ([String], [String]) -> IO ([String], [String]))
-> IO ([String], [String]) -> IO ([String], [String])
forall a b. (a -> b) -> a -> b
$ do
Maybe (ShakeOptions, Rules ())
rs <- ShakeOptions
-> [a] -> [String] -> IO (Maybe (ShakeOptions, Rules ()))
rules ShakeOptions
shakeOpts [] []
case Maybe (ShakeOptions, Rules ())
rs of
Just (ShakeOptions
_, Rules ()
rs) -> do
[(String, Maybe String)]
xs <- ShakeOptions -> Rules () -> IO [(String, Maybe String)]
getTargets ShakeOptions
shakeOpts Rules ()
rs
[String]
helpSuffix <- ShakeOptions -> Rules () -> IO [String]
getHelpSuffix ShakeOptions
shakeOpts Rules ()
rs
([String], [String]) -> IO ([String], [String])
forall a. a -> IO a
evaluate (([String], [String]) -> IO ([String], [String]))
-> ([String], [String]) -> IO ([String], [String])
forall a b. (a -> b) -> a -> b
$ ([String], [String]) -> ([String], [String])
forall a. NFData a => a -> a
force ([String
" - " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
a String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> (String -> String) -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" (String
" - " String -> String -> String
forall a. [a] -> [a] -> [a]
++) Maybe String
b | (String
a,Maybe String
b) <- [(String, Maybe String)]
xs], [String]
helpSuffix)
Maybe (ShakeOptions, Rules ())
_ -> ([String], [String]) -> IO ([String], [String])
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([], [])
[String]
changes<- [String] -> IO [String]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([String] -> IO [String]) -> [String] -> IO [String]
forall a b. (a -> b) -> a -> b
$
let as :: [(String, String)]
as = ShakeOptions -> [(String, String)]
shakeOptionsFields ShakeOptions
baseOpts
bs :: [(String, String)]
bs = ShakeOptions -> [(String, String)]
shakeOptionsFields ShakeOptions
oshakeOpts
in [String
" - " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
lbl String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
v1 String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" => " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
v2 | Bool
long, ((String
lbl, String
v1), (String
_, String
v2)) <- [(String, String)]
-> [(String, String)] -> [((String, String), (String, String))]
forall a b. [a] -> [b] -> [(a, b)]
zip [(String, String)]
as [(String, String)]
bs, String
v1 String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
v2]
Verbosity -> String -> IO ()
putWhen Verbosity
Error (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$
(String
"Usage: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
progName String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" [options] [target] ...") String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
(if [OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))]
-> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))]
baseOpts2 then [] else String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: (if [OptDescr (Either String a)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [OptDescr (Either String a)]
userOptions then String
"Options:" else String
"Standard options:") String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))]
-> [String]
forall a. [OptDescr a] -> [String]
showOptDescr [OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))]
baseOpts2) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
(if [OptDescr (Either String a)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [OptDescr (Either String a)]
userOptions then [] else String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String
"Extra options:" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [OptDescr (Either String a)] -> [String]
forall a. [OptDescr a] -> [String]
showOptDescr [OptDescr (Either String a)]
userOptions) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
(if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
changes then [] else String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String
"Changed ShakeOptions:" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
changes) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
(if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
targets then [] else String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String
"Targets:" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
targets) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
(if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
helpSuffix then [] else String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
helpSuffix)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([String]
errs [String] -> [String] -> Bool
forall a. Eq a => a -> a -> Bool
/= []) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Verbosity -> String -> IO ()
putWhen Verbosity
Error (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
"shake: " String -> String -> String
forall a. [a] -> [a] -> [a]
++) ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String -> [String]
lines (String -> [String]) -> String -> [String]
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines [String]
errs
Bool -> IO ()
showHelp Bool
False
IO ()
forall a. IO a
exitFailure
if Extra
Help Extra -> [Extra] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Extra]
flagsExtra then
Bool -> IO ()
showHelp Bool
True
else if Extra
Version Extra -> [Extra] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Extra]
flagsExtra then
Verbosity -> String -> IO ()
putWhenLn Verbosity
Info (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Shake build system, version " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
shakeVersionString
else if Extra
NumericVersion Extra -> [Extra] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Extra]
flagsExtra then
Verbosity -> String -> IO ()
putWhenLn Verbosity
Info String
shakeVersionString
else if Extra
Demo Extra -> [Extra] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Extra]
flagsExtra then
Bool -> IO ()
demo (Bool -> IO ()) -> Bool -> IO ()
forall a b. (a -> b) -> a -> b
$ ShakeOptions -> Bool
shakeStaunch ShakeOptions
shakeOpts
else if Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
progressReplays then do
[(String, [(Double, Progress)])]
dat <- [String]
-> (String -> IO (String, [(Double, Progress)]))
-> IO [(String, [(Double, Progress)])]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [String]
progressReplays ((String -> IO (String, [(Double, Progress)]))
-> IO [(String, [(Double, Progress)])])
-> (String -> IO (String, [(Double, Progress)]))
-> IO [(String, [(Double, Progress)])]
forall a b. (a -> b) -> a -> b
$ \String
file -> do
String
src <- String -> IO String
readFile String
file
(String, [(Double, Progress)]) -> IO (String, [(Double, Progress)])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String
file, (String -> (Double, Progress)) -> [String] -> [(Double, Progress)]
forall a b. (a -> b) -> [a] -> [b]
map String -> (Double, Progress)
forall a. Read a => String -> a
read ([String] -> [(Double, Progress)])
-> [String] -> [(Double, Progress)]
forall a b. (a -> b) -> a -> b
$ String -> [String]
lines String
src)
[String] -> (String -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([String] -> Bool) -> [String] -> Bool
forall a b. (a -> b) -> a -> b
$ ShakeOptions -> [String]
shakeReport ShakeOptions
shakeOpts then [String
"-"] else ShakeOptions -> [String]
shakeReport ShakeOptions
shakeOpts) ((String -> IO ()) -> IO ()) -> (String -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \String
file -> do
Verbosity -> String -> IO ()
putWhenLn Verbosity
Info (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Writing report to " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
file
String -> [(String, [(Double, Progress)])] -> IO ()
writeProgressReport String
file [(String, [(Double, Progress)])]
dat
else do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Extra
Sleep Extra -> [Extra] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Extra]
flagsExtra) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Double -> IO ()
sleep Double
1
IO Double
start <- IO (IO Double)
offsetTime
IO ()
initDataDirectory
let redir :: IO a -> IO a
redir = (IO a -> IO a)
-> (String -> IO a -> IO a) -> Maybe String -> IO a -> IO a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IO a -> IO a
forall a. a -> a
id String -> IO a -> IO a
forall a. String -> IO a -> IO a
withCurrentDirectory Maybe String
changeDirectory
ShakeOptions
shakeOpts <- if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
progressRecords then ShakeOptions -> IO ShakeOptions
forall (f :: * -> *) a. Applicative f => a -> f a
pure ShakeOptions
shakeOpts else do
IO Double
t <- IO (IO Double)
offsetTime
ShakeOptions -> IO ShakeOptions
forall (f :: * -> *) a. Applicative f => a -> f a
pure ShakeOptions
shakeOpts{shakeProgress :: IO Progress -> IO ()
shakeProgress = \IO Progress
p ->
IO ((), ()) -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO ((), ()) -> IO ()) -> IO ((), ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ IO () -> IO () -> IO ((), ())
forall a b. IO a -> IO b -> IO (a, b)
withThreadsBoth (ShakeOptions -> IO Progress -> IO ()
shakeProgress ShakeOptions
shakeOpts IO Progress
p) (IO () -> IO ((), ())) -> IO () -> IO ((), ())
forall a b. (a -> b) -> a -> b
$
Double -> (String -> IO ()) -> IO Progress -> IO ()
progressDisplay Double
1 (IO () -> String -> IO ()
forall a b. a -> b -> a
const (IO () -> String -> IO ()) -> IO () -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()) (IO Progress -> IO ()) -> IO Progress -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Progress
p <- IO Progress
p
Double
t <- IO Double
t
[String] -> (String -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [String]
progressRecords ((String -> IO ()) -> IO ()) -> (String -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \String
file ->
String -> String -> IO ()
appendFile String
file (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ (Double, Progress) -> String
forall a. Show a => a -> String
show (Double
t,Progress
p) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
Progress -> IO Progress
forall (f :: * -> *) a. Applicative f => a -> f a
pure Progress
p
}
(Bool
ran,ShakeOptions
shakeOpts,Either SomeException ()
res) <- IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ())
forall a. IO a -> IO a
redir (IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ()))
-> IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ())
forall a b. (a -> b) -> a -> b
$ do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
printDirectory (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
String
curdir <- IO String
getCurrentDirectory
Verbosity -> String -> IO ()
putWhenLn Verbosity
Info (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"shake: In directory `" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
curdir String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'"
(ShakeOptions
shakeOpts, IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ())
ui) <- do
let compact :: Auto
compact = Auto -> [Auto] -> Auto
forall a. a -> [a] -> a
lastDef Auto
No [Auto
x | Compact Auto
x <- [Extra]
flagsExtra]
Bool
use <- if Auto
compact Auto -> Auto -> Bool
forall a. Eq a => a -> a -> Bool
== Auto
Auto then IO Bool
checkEscCodes else Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Auto
compact Auto -> Auto -> Bool
forall a. Eq a => a -> a -> Bool
== Auto
Yes
if Bool
use
then (IO ()
-> IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ()))
-> (ShakeOptions, IO ())
-> (ShakeOptions,
IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ()))
forall b b' a. (b -> b') -> (a, b) -> (a, b')
second IO ()
-> IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ())
forall a. IO () -> IO a -> IO a
withThreadSlave ((ShakeOptions, IO ())
-> (ShakeOptions,
IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ())))
-> IO (ShakeOptions, IO ())
-> IO
(ShakeOptions,
IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ()))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ShakeOptions -> IO (ShakeOptions, IO ())
compactUI ShakeOptions
shakeOpts
else (ShakeOptions,
IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ()))
-> IO
(ShakeOptions,
IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ()))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ShakeOptions
shakeOpts, IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ())
forall a. a -> a
id)
Maybe (ShakeOptions, Rules ())
rules <- ShakeOptions
-> [a] -> [String] -> IO (Maybe (ShakeOptions, Rules ()))
rules ShakeOptions
shakeOpts [a]
user [String]
files
IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ())
ui (IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ()))
-> IO (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ())
forall a b. (a -> b) -> a -> b
$ case Maybe (ShakeOptions, Rules ())
rules of
Maybe (ShakeOptions, Rules ())
Nothing -> (Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool
False, ShakeOptions
shakeOpts, () -> Either SomeException ()
forall a b. b -> Either a b
Right ())
Just (ShakeOptions
shakeOpts, Rules ()
rules) -> do
Either SomeException ()
res <- IO () -> IO (Either SomeException ())
forall a. IO a -> IO (Either SomeException a)
try_ (IO () -> IO (Either SomeException ()))
-> IO () -> IO (Either SomeException ())
forall a b. (a -> b) -> a -> b
$ ShakeOptions -> Rules () -> IO ()
shake ShakeOptions
shakeOpts (Rules () -> IO ()) -> Rules () -> IO ()
forall a b. (a -> b) -> a -> b
$
if Extra
NoBuild Extra -> [Extra] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Extra]
flagsExtra then
Rules () -> Rules ()
forall a. Rules a -> Rules a
withoutActions Rules ()
rules
else if Extra
ShareList Extra -> [Extra] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Extra]
flagsExtra Bool -> Bool -> Bool
||
Bool -> Bool
not ([String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
shareRemoves) Bool -> Bool -> Bool
||
Extra
ShareSanity Extra -> [Extra] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Extra]
flagsExtra then do
Action () -> Rules ()
forall a. Partial => Action a -> Rules ()
action (Action () -> Rules ()) -> Action () -> Rules ()
forall a b. (a -> b) -> a -> b
$ do
Bool -> Action () -> Action ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
shareRemoves) (Action () -> Action ()) -> Action () -> Action ()
forall a b. (a -> b) -> a -> b
$
[String] -> Action ()
actionShareRemove [String]
shareRemoves
Bool -> Action () -> Action ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Extra
ShareList Extra -> [Extra] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Extra]
flagsExtra)
Action ()
actionShareList
Bool -> Action () -> Action ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Extra
ShareSanity Extra -> [Extra] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Extra]
flagsExtra)
Action ()
actionShareSanity
Rules () -> Rules ()
forall a. Rules a -> Rules a
withoutActions Rules ()
rules
else
Rules ()
rules
(Bool, ShakeOptions, Either SomeException ())
-> IO (Bool, ShakeOptions, Either SomeException ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool
True, ShakeOptions
shakeOpts, Either SomeException ()
res)
if Bool -> Bool
not Bool
ran Bool -> Bool -> Bool
|| ShakeOptions -> Verbosity
shakeVerbosity ShakeOptions
shakeOpts Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
< Verbosity
Info Bool -> Bool -> Bool
|| Extra
NoTime Extra -> [Extra] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Extra]
flagsExtra then
(SomeException -> IO ())
-> (() -> IO ()) -> Either SomeException () -> IO ()
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either SomeException -> IO ()
forall e a. Exception e => e -> IO a
throwIO () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure Either SomeException ()
res
else
let esc :: Color -> String -> String
esc = if ShakeOptions -> Bool
shakeColor ShakeOptions
shakeOpts then Color -> String -> String
escape else \Color
_ String
x -> String
x
in case Either SomeException ()
res of
Left SomeException
err ->
if Extra
Exception Extra -> [Extra] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Extra]
flagsExtra then
SomeException -> IO ()
forall e a. Exception e => e -> IO a
throwIO SomeException
err
else do
Verbosity -> String -> IO ()
putWhenLn Verbosity
Error (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Color -> String -> String
esc Color
Red (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ SomeException -> String
forall a. Show a => a -> String
show SomeException
err
IO ()
forall a. IO a
exitFailure
Right () -> do
Double
tot <- IO Double
start
Verbosity -> String -> IO ()
putWhenLn Verbosity
Info (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Color -> String -> String
esc Color
Green (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
"Build completed in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Double -> String
showDuration Double
tot
shakeOptDescrs :: [OptDescr (Either String (ShakeOptions -> ShakeOptions))]
shakeOptDescrs :: [OptDescr (Either String (ShakeOptions -> ShakeOptions))]
shakeOptDescrs = [(([Extra], ShakeOptions -> ShakeOptions)
-> ShakeOptions -> ShakeOptions)
-> OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b.
(a -> b)
-> OptDescr (Either String a) -> OptDescr (Either String b)
fmapFmapOptDescr ([Extra], ShakeOptions -> ShakeOptions)
-> ShakeOptions -> ShakeOptions
forall a b. (a, b) -> b
snd OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
o | (Bool
True, OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
o) <- [(Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))]
shakeOptsEx]
data = ChangeDirectory FilePath
| Version
| NumericVersion
| PrintDirectory Bool
| Help
| Sleep
| NoTime
| Exception
| NoBuild
| ProgressRecord FilePath
| ProgressReplay FilePath
| Demo
| ShareList
| ShareSanity
| ShareRemove String
| Compact Auto
deriving Extra -> Extra -> Bool
(Extra -> Extra -> Bool) -> (Extra -> Extra -> Bool) -> Eq Extra
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Extra -> Extra -> Bool
$c/= :: Extra -> Extra -> Bool
== :: Extra -> Extra -> Bool
$c== :: Extra -> Extra -> Bool
Eq
data Auto = Yes | No | Auto
deriving Auto -> Auto -> Bool
(Auto -> Auto -> Bool) -> (Auto -> Auto -> Bool) -> Eq Auto
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Auto -> Auto -> Bool
$c/= :: Auto -> Auto -> Bool
== :: Auto -> Auto -> Bool
$c== :: Auto -> Auto -> Bool
Eq
escape :: Color -> String -> String
escape :: Color -> String -> String
escape Color
color String
x = Color -> String
escForeground Color
color String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
escNormal
outputColor :: (Verbosity -> String -> IO ()) -> Verbosity -> String -> IO ()
outputColor :: (Verbosity -> String -> IO ()) -> Verbosity -> String -> IO ()
outputColor Verbosity -> String -> IO ()
output Verbosity
v String
msg = Verbosity -> String -> IO ()
output Verbosity
v (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> String
color String
msg
where color :: String -> String
color = case Verbosity
v of
Verbosity
Silent -> String -> String
forall a. a -> a
id
Verbosity
Error -> Color -> String -> String
escape Color
Red
Verbosity
Warn -> Color -> String -> String
escape Color
Yellow
Verbosity
_ -> Color -> String -> String
escape Color
Blue
shakeOptsEx :: [(Bool, OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))]
shakeOptsEx :: [(Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))]
shakeOptsEx =
[OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"a" [String
"abbrev"] (String
-> String
-> ((String, String) -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b.
String
-> String -> ((String, String) -> b) -> ArgDescr (Either String b)
reqArgPair String
"abbrev" String
"FULL=SHORT" (((String, String) -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> ((String, String) -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \(String, String)
a ShakeOptions
s -> ShakeOptions
s{shakeAbbreviations :: [(String, String)]
shakeAbbreviations=ShakeOptions -> [(String, String)]
shakeAbbreviations ShakeOptions
s [(String, String)] -> [(String, String)] -> [(String, String)]
forall a. [a] -> [a] -> [a]
++ [(String, String)
a]}) String
"Use abbreviation in status messages."
,OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String (t, a -> a)))
extr (OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String [Extra])
-> String
-> OptDescr (Either String [Extra])
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"no-build"] ([Extra] -> ArgDescr (Either String [Extra])
forall b a. b -> ArgDescr (Either a b)
noArg [Extra
NoBuild]) String
"Don't build anything."
,OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String (t, a -> a)))
extr (OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String [Extra])
-> String
-> OptDescr (Either String [Extra])
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"C" [String
"directory"] (String -> (String -> [Extra]) -> ArgDescr (Either String [Extra])
forall b a. String -> (String -> b) -> ArgDescr (Either a b)
reqArg String
"DIRECTORY" ((String -> [Extra]) -> ArgDescr (Either String [Extra]))
-> (String -> [Extra]) -> ArgDescr (Either String [Extra])
forall a b. (a -> b) -> a -> b
$ \String
x -> [String -> Extra
ChangeDirectory String
x]) String
"Change to DIRECTORY before doing anything."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"color",String
"colour"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeColor :: Bool
shakeColor=Bool
True}) String
"Colorize the output."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"no-color",String
"no-colour"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeColor :: Bool
shakeColor=Bool
False}) String
"Don't colorize the output."
,OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String (t, a -> a)))
extr (OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String [Extra])
-> String
-> OptDescr (Either String [Extra])
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"compact"] (String
-> String -> (Auto -> [Extra]) -> ArgDescr (Either String [Extra])
forall b.
String -> String -> (Auto -> b) -> ArgDescr (Either String b)
optArgAuto String
"auto" String
"yes|no|auto" ((Auto -> [Extra]) -> ArgDescr (Either String [Extra]))
-> (Auto -> [Extra]) -> ArgDescr (Either String [Extra])
forall a b. (a -> b) -> a -> b
$ \Auto
x -> [Auto -> Extra
Compact Auto
x]) String
"Use a compact Bazel/Buck style output."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"d" [String
"debug"] (String
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. String -> (Maybe String -> b) -> ArgDescr (Either a b)
optArg String
"FILE" ((Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \Maybe String
x ShakeOptions
s -> ShakeOptions
s{shakeVerbosity :: Verbosity
shakeVerbosity=Verbosity
Diagnostic, shakeOutput :: Verbosity -> String -> IO ()
shakeOutput=(Verbosity -> String -> IO ())
-> Maybe String -> Verbosity -> String -> IO ()
outputDebug (ShakeOptions -> Verbosity -> String -> IO ()
shakeOutput ShakeOptions
s) Maybe String
x}) String
"Print lots of debugging information."
,OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String (t, a -> a)))
extr (OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String [Extra])
-> String
-> OptDescr (Either String [Extra])
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"demo"] ([Extra] -> ArgDescr (Either String [Extra])
forall b a. b -> ArgDescr (Either a b)
noArg [Extra
Demo]) String
"Run in demo mode."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"digest"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeChange :: Change
shakeChange=Change
ChangeDigest}) String
"Files change when digest changes."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"digest-and"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeChange :: Change
shakeChange=Change
ChangeModtimeAndDigest}) String
"Files change when modtime and digest change."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"digest-and-input"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeChange :: Change
shakeChange=Change
ChangeModtimeAndDigestInput}) String
"Files change on modtime (and digest for inputs)."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"digest-or"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeChange :: Change
shakeChange=Change
ChangeModtimeOrDigest}) String
"Files change when modtime or digest change."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"digest-not"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeChange :: Change
shakeChange=Change
ChangeModtime}) String
"Files change when modtime changes."
,OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String (t, a -> a)))
extr (OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String [Extra])
-> String
-> OptDescr (Either String [Extra])
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"exception"] ([Extra] -> ArgDescr (Either String [Extra])
forall b a. b -> ArgDescr (Either a b)
noArg [Extra
Exception]) String
"Throw exceptions directly."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"flush"] (Double
-> String
-> String
-> (Double -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b.
(Read a, Ord a, Show a) =>
a -> String -> String -> (a -> b) -> ArgDescr (Either String b)
reqIntArg Double
1 String
"flush" String
"N" (\Double
i ShakeOptions
s -> ShakeOptions
s{shakeFlush :: Maybe Double
shakeFlush=Double -> Maybe Double
forall a. a -> Maybe a
Just Double
i})) String
"Flush metadata every N seconds."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"never-flush"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeFlush :: Maybe Double
shakeFlush=Maybe Double
forall a. Maybe a
Nothing}) String
"Never explicitly flush metadata."
,OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String (t, a -> a)))
extr (OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String [Extra])
-> String
-> OptDescr (Either String [Extra])
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"h" [String
"help"] ([Extra] -> ArgDescr (Either String [Extra])
forall b a. b -> ArgDescr (Either a b)
noArg [Extra
Help]) String
"Print this message and exit."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"j" [String
"jobs"] (Int
-> String
-> String
-> (Maybe Int -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b.
(Read a, Ord a, Show a) =>
a
-> String -> String -> (Maybe a -> b) -> ArgDescr (Either String b)
optArgInt Int
0 String
"jobs" String
"N" ((Maybe Int -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (Maybe Int -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \Maybe Int
i ShakeOptions
s -> ShakeOptions
s{shakeThreads :: Int
shakeThreads=Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
0 Maybe Int
i}) String
"Allow N jobs/threads at once [default CPUs]."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"k" [String
"keep-going"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeStaunch :: Bool
shakeStaunch=Bool
True}) String
"Keep going when some targets can't be made."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"l" [String
"lint"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeLint :: Maybe Lint
shakeLint=Lint -> Maybe Lint
forall a. a -> Maybe a
Just Lint
LintBasic}) String
"Perform limited validation after the run."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"lint-watch"] (String
-> (String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. String -> (String -> b) -> ArgDescr (Either a b)
reqArg String
"PATTERN" ((String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \String
x ShakeOptions
s -> ShakeOptions
s{shakeLintWatch :: [String]
shakeLintWatch=ShakeOptions -> [String]
shakeLintWatch ShakeOptions
s [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
x]}) String
"Error if any of the patterns are created (expensive)."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"lint-fsatrace"] (String
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. String -> (Maybe String -> b) -> ArgDescr (Either a b)
optArg String
"DIR" ((Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \Maybe String
x ShakeOptions
s -> ShakeOptions
s{shakeLint :: Maybe Lint
shakeLint=Lint -> Maybe Lint
forall a. a -> Maybe a
Just Lint
LintFSATrace, shakeLintInside :: [String]
shakeLintInside=ShakeOptions -> [String]
shakeLintInside ShakeOptions
s [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"." Maybe String
x]}) String
"Use fsatrace to do validation [in current dir]."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"lint-ignore"] (String
-> (String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. String -> (String -> b) -> ArgDescr (Either a b)
reqArg String
"PATTERN" ((String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \String
x ShakeOptions
s -> ShakeOptions
s{shakeLintIgnore :: [String]
shakeLintIgnore=ShakeOptions -> [String]
shakeLintIgnore ShakeOptions
s [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
x]}) String
"Ignore any lint errors in these patterns."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"no-lint"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeLint :: Maybe Lint
shakeLint=Maybe Lint
forall a. Maybe a
Nothing}) String
"Turn off --lint."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"live"] (String
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. String -> (Maybe String -> b) -> ArgDescr (Either a b)
optArg String
"FILE" ((Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \Maybe String
x ShakeOptions
s -> ShakeOptions
s{shakeLiveFiles :: [String]
shakeLiveFiles=ShakeOptions -> [String]
shakeLiveFiles ShakeOptions
s [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"live.txt" Maybe String
x]}) String
"List the files that are live [to live.txt]."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"m" [String
"metadata"] (String
-> (String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. String -> (String -> b) -> ArgDescr (Either a b)
reqArg String
"PREFIX" ((String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \String
x ShakeOptions
s -> ShakeOptions
s{shakeFiles :: String
shakeFiles=String
x}) String
"Prefix for storing metadata files."
,OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String (t, a -> a)))
extr (OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String [Extra])
-> String
-> OptDescr (Either String [Extra])
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"numeric-version"] ([Extra] -> ArgDescr (Either String [Extra])
forall b a. b -> ArgDescr (Either a b)
noArg [Extra
NumericVersion]) String
"Print just the version number and exit."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"skip-commands"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeRunCommands :: Bool
shakeRunCommands=Bool
False}) String
"Try and avoid running external programs."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"B" [String
"rebuild"] (String
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. String -> (Maybe String -> b) -> ArgDescr (Either a b)
optArg String
"PATTERN" ((Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \Maybe String
x ShakeOptions
s -> ShakeOptions
s{shakeRebuild :: [(Rebuild, String)]
shakeRebuild=ShakeOptions -> [(Rebuild, String)]
shakeRebuild ShakeOptions
s [(Rebuild, String)] -> [(Rebuild, String)] -> [(Rebuild, String)]
forall a. [a] -> [a] -> [a]
++ [(Rebuild
RebuildNow, String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"**" Maybe String
x)]}) String
"If required, these files will rebuild even if nothing has changed."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"no-rebuild"] (String
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. String -> (Maybe String -> b) -> ArgDescr (Either a b)
optArg String
"PATTERN" ((Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \Maybe String
x ShakeOptions
s -> ShakeOptions
s{shakeRebuild :: [(Rebuild, String)]
shakeRebuild=ShakeOptions -> [(Rebuild, String)]
shakeRebuild ShakeOptions
s [(Rebuild, String)] -> [(Rebuild, String)] -> [(Rebuild, String)]
forall a. [a] -> [a] -> [a]
++ [(Rebuild
RebuildNormal, String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"**" Maybe String
x)]}) String
"If required, these files will rebuild only if things have changed (default)."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"skip"] (String
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. String -> (Maybe String -> b) -> ArgDescr (Either a b)
optArg String
"PATTERN" ((Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \Maybe String
x ShakeOptions
s -> ShakeOptions
s{shakeRebuild :: [(Rebuild, String)]
shakeRebuild=ShakeOptions -> [(Rebuild, String)]
shakeRebuild ShakeOptions
s [(Rebuild, String)] -> [(Rebuild, String)] -> [(Rebuild, String)]
forall a. [a] -> [a] -> [a]
++ [(Rebuild
RebuildLater, String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"**" Maybe String
x)]}) String
"Don't rebuild matching files this run."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"r" [String
"report",String
"profile"] (String
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. String -> (Maybe String -> b) -> ArgDescr (Either a b)
optArg String
"FILE" ((Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \Maybe String
x ShakeOptions
s -> ShakeOptions
s{shakeReport :: [String]
shakeReport=ShakeOptions -> [String]
shakeReport ShakeOptions
s [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"report.html" Maybe String
x]}) String
"Write out profiling information [to report.html]."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"no-reports"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeReport :: [String]
shakeReport=[]}) String
"Turn off --report."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"rule-version"] (String
-> (String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. String -> (String -> b) -> ArgDescr (Either a b)
reqArg String
"VERSION" ((String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \String
x ShakeOptions
s -> ShakeOptions
s{shakeVersion :: String
shakeVersion=String
x}) String
"Version of the build rules."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"no-rule-version"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeVersionIgnore :: Bool
shakeVersionIgnore=Bool
True}) String
"Ignore the build rules version."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"share"] (String
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. String -> (Maybe String -> b) -> ArgDescr (Either a b)
optArg String
"DIRECTORY" ((Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (Maybe String -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \Maybe String
x ShakeOptions
s -> ShakeOptions
s{shakeShare :: Maybe String
shakeShare=String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"" Maybe String
x, shakeChange :: Change
shakeChange=Change -> Change
ensureHash (Change -> Change) -> Change -> Change
forall a b. (a -> b) -> a -> b
$ ShakeOptions -> Change
shakeChange ShakeOptions
s}) String
"Shared cache location."
,OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall b. b -> (Bool, b)
hide (OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"share-list"] (([Extra], ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ([Extra
ShareList], ShakeOptions -> ShakeOptions
ensureShare)) String
"List the shared cache files."
,OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall b. b -> (Bool, b)
hide (OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"share-sanity"] (([Extra], ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ([Extra
ShareSanity], ShakeOptions -> ShakeOptions
ensureShare)) String
"Sanity check the shared cache files."
,OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall b. b -> (Bool, b)
hide (OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"share-remove"] ((Maybe String
-> Either String ([Extra], ShakeOptions -> ShakeOptions))
-> String
-> ArgDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
forall a. (Maybe String -> a) -> String -> ArgDescr a
OptArg (\Maybe String
x -> ([Extra], ShakeOptions -> ShakeOptions)
-> Either String ([Extra], ShakeOptions -> ShakeOptions)
forall a b. b -> Either a b
Right ([String -> Extra
ShareRemove (String -> Extra) -> String -> Extra
forall a b. (a -> b) -> a -> b
$ String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"**" Maybe String
x], ShakeOptions -> ShakeOptions
ensureShare)) String
"SUBSTRING") String
"Remove the shared cache keys."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"share-copy"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeSymlink :: Bool
shakeSymlink=Bool
False}) String
"Copy files into the cache."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"share-symlink"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeSymlink :: Bool
shakeSymlink=Bool
True}) String
"Symlink files into the cache."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"s" [String
"silent"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeVerbosity :: Verbosity
shakeVerbosity=Verbosity
Silent}) String
"Don't print anything."
,OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String (t, a -> a)))
extr (OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String [Extra])
-> String
-> OptDescr (Either String [Extra])
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"sleep"] ([Extra] -> ArgDescr (Either String [Extra])
forall b a. b -> ArgDescr (Either a b)
noArg [Extra
Sleep]) String
"Sleep for a second before building."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"S" [String
"no-keep-going",String
"stop"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeStaunch :: Bool
shakeStaunch=Bool
False}) String
"Turns off -k."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"storage"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeStorageLog :: Bool
shakeStorageLog=Bool
True}) String
"Write a storage log."
,OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall b. b -> (Bool, b)
both (OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"p" [String
"progress"] (ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> ArgDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
forall a a.
ArgDescr (Either a (a -> a))
-> ArgDescr (Either a ([Extra], a -> a))
progress (ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> ArgDescr
(Either String ([Extra], ShakeOptions -> ShakeOptions)))
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> ArgDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ Double
-> String
-> String
-> (Maybe Double -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b.
(Read a, Ord a, Show a) =>
a
-> String -> String -> (Maybe a -> b) -> ArgDescr (Either String b)
optArgInt Double
1 String
"progress" String
"N" ((Maybe Double -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (Maybe Double -> ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \Maybe Double
i ShakeOptions
s -> ShakeOptions
s{shakeProgress :: IO Progress -> IO ()
shakeProgress=Double -> IO Progress -> IO ()
prog (Double -> IO Progress -> IO ()) -> Double -> IO Progress -> IO ()
forall a b. (a -> b) -> a -> b
$ Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
5 Maybe Double
i}) String
"Show progress messages [every N secs, default 5]."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"no-progress"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeProgress :: IO Progress -> IO ()
shakeProgress=IO () -> IO Progress -> IO ()
forall a b. a -> b -> a
const (IO () -> IO Progress -> IO ()) -> IO () -> IO Progress -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()}) String
"Don't show progress messages."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"q" [String
"quiet"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeVerbosity :: Verbosity
shakeVerbosity=Verbosity -> (Int -> Int) -> Verbosity
move (ShakeOptions -> Verbosity
shakeVerbosity ShakeOptions
s) Int -> Int
forall a. Enum a => a -> a
pred}) String
"Print less (pass repeatedly for even less)."
,OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String (t, a -> a)))
extr (OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String [Extra])
-> String
-> OptDescr (Either String [Extra])
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"no-time"] ([Extra] -> ArgDescr (Either String [Extra])
forall b a. b -> ArgDescr (Either a b)
noArg [Extra
NoTime]) String
"Don't print build time."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"timings"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeTimings :: Bool
shakeTimings=Bool
True}) String
"Print phase timings."
,OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts (OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
-> String
-> OptDescr (Either String (ShakeOptions -> ShakeOptions))
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"V" [String
"verbose",String
"trace"] ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall b a. b -> ArgDescr (Either a b)
noArg ((ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions)))
-> (ShakeOptions -> ShakeOptions)
-> ArgDescr (Either String (ShakeOptions -> ShakeOptions))
forall a b. (a -> b) -> a -> b
$ \ShakeOptions
s -> ShakeOptions
s{shakeVerbosity :: Verbosity
shakeVerbosity=Verbosity -> (Int -> Int) -> Verbosity
move (ShakeOptions -> Verbosity
shakeVerbosity ShakeOptions
s) Int -> Int
forall a. Enum a => a -> a
succ}) String
"Print more (pass repeatedly for even more)."
,OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String (t, a -> a)))
extr (OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String [Extra])
-> String
-> OptDescr (Either String [Extra])
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"v" [String
"version"] ([Extra] -> ArgDescr (Either String [Extra])
forall b a. b -> ArgDescr (Either a b)
noArg [Extra
Version]) String
"Print the version number and exit."
,OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String (t, a -> a)))
extr (OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String [Extra])
-> String
-> OptDescr (Either String [Extra])
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"w" [String
"print-directory"] ([Extra] -> ArgDescr (Either String [Extra])
forall b a. b -> ArgDescr (Either a b)
noArg [Bool -> Extra
PrintDirectory Bool
True]) String
"Print the current directory."
,OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall t a.
OptDescr (Either String t)
-> (Bool, OptDescr (Either String (t, a -> a)))
extr (OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions))))
-> OptDescr (Either String [Extra])
-> (Bool,
OptDescr (Either String ([Extra], ShakeOptions -> ShakeOptions)))
forall a b. (a -> b) -> a -> b
$ String
-> [String]
-> ArgDescr (Either String [Extra])
-> String
-> OptDescr (Either String [Extra])
forall a. String -> [String] -> ArgDescr a -> String -> OptDescr a
Option String
"" [String
"no-print-directory"] ([Extra] -> ArgDescr (Either String [Extra])
forall b a. b -> ArgDescr (Either a b)
noArg [Bool -> Extra
PrintDirectory Bool
False]) String
"Turn off -w, even if it was turned on implicitly."
]
where
opts :: OptDescr (Either String t)
-> (Bool, OptDescr (Either String ([a], t)))
opts OptDescr (Either String t)
o = (Bool
True, (t -> ([a], t))
-> OptDescr (Either String t) -> OptDescr (Either String ([a], t))
forall a b.
(a -> b)
-> OptDescr (Either String a) -> OptDescr (Either String b)
fmapFmapOptDescr ([],) OptDescr (Either String t)
o)
extr :: OptDescr (Either String t)
-> (Bool, OptDescr (Either String (t, a -> a)))
extr OptDescr (Either String t)
o = (Bool
False, (t -> (t, a -> a))
-> OptDescr (Either String t)
-> OptDescr (Either String (t, a -> a))
forall a b.
(a -> b)
-> OptDescr (Either String a) -> OptDescr (Either String b)
fmapFmapOptDescr (,a -> a
forall a. a -> a
id) OptDescr (Either String t)
o)
both :: b -> (Bool, b)
both b
o = (Bool
True, b
o)
hide :: b -> (Bool, b)
hide b
o = (Bool
False, b
o)
move :: Verbosity -> (Int -> Int) -> Verbosity
move :: Verbosity -> (Int -> Int) -> Verbosity
move Verbosity
x Int -> Int
by = Int -> Verbosity
forall a. Enum a => Int -> a
toEnum (Int -> Verbosity) -> Int -> Verbosity
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (Verbosity -> Int
forall a. Enum a => a -> Int
fromEnum Verbosity
mx) (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int
forall a. Ord a => a -> a -> a
max (Verbosity -> Int
forall a. Enum a => a -> Int
fromEnum Verbosity
mn) (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int -> Int
by (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Verbosity -> Int
forall a. Enum a => a -> Int
fromEnum Verbosity
x
where (Verbosity
mn,Verbosity
mx) = (Verbosity -> Verbosity -> Verbosity
forall a. a -> a -> a
asTypeOf Verbosity
forall a. Bounded a => a
minBound Verbosity
x, Verbosity -> Verbosity -> Verbosity
forall a. a -> a -> a
asTypeOf Verbosity
forall a. Bounded a => a
maxBound Verbosity
x)
noArg :: b -> ArgDescr (Either a b)
noArg = Either a b -> ArgDescr (Either a b)
forall a. a -> ArgDescr a
NoArg (Either a b -> ArgDescr (Either a b))
-> (b -> Either a b) -> b -> ArgDescr (Either a b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Either a b
forall a b. b -> Either a b
Right
reqArg :: String -> (String -> b) -> ArgDescr (Either a b)
reqArg String
a String -> b
f = (String -> Either a b) -> String -> ArgDescr (Either a b)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg (b -> Either a b
forall a b. b -> Either a b
Right (b -> Either a b) -> (String -> b) -> String -> Either a b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> b
f) String
a
optArg :: String -> (Maybe String -> b) -> ArgDescr (Either a b)
optArg String
a Maybe String -> b
f = (Maybe String -> Either a b) -> String -> ArgDescr (Either a b)
forall a. (Maybe String -> a) -> String -> ArgDescr a
OptArg (b -> Either a b
forall a b. b -> Either a b
Right (b -> Either a b)
-> (Maybe String -> b) -> Maybe String -> Either a b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe String -> b
f) String
a
reqIntArg :: a -> String -> String -> (a -> b) -> ArgDescr (Either String b)
reqIntArg a
mn String
flag String
a a -> b
f = ((String -> Either String b)
-> String -> ArgDescr (Either String b))
-> String
-> (String -> Either String b)
-> ArgDescr (Either String b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (String -> Either String b) -> String -> ArgDescr (Either String b)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg String
a ((String -> Either String b) -> ArgDescr (Either String b))
-> (String -> Either String b) -> ArgDescr (Either String b)
forall a b. (a -> b) -> a -> b
$ \String
x -> case ReadS a
forall a. Read a => ReadS a
reads String
x of
[(a
i,String
"")] | a
i a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
mn -> b -> Either String b
forall a b. b -> Either a b
Right (a -> b
f a
i)
[(a, String)]
_ -> String -> Either String b
forall a b. a -> Either a b
Left (String -> Either String b) -> String -> Either String b
forall a b. (a -> b) -> a -> b
$ String
"the `--" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
flag String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' option requires a number, " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
mn String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" or above"
optArgInt :: a
-> String -> String -> (Maybe a -> b) -> ArgDescr (Either String b)
optArgInt a
mn String
flag String
a Maybe a -> b
f = ((Maybe String -> Either String b)
-> String -> ArgDescr (Either String b))
-> String
-> (Maybe String -> Either String b)
-> ArgDescr (Either String b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Maybe String -> Either String b)
-> String -> ArgDescr (Either String b)
forall a. (Maybe String -> a) -> String -> ArgDescr a
OptArg String
a ((Maybe String -> Either String b) -> ArgDescr (Either String b))
-> (Maybe String -> Either String b) -> ArgDescr (Either String b)
forall a b. (a -> b) -> a -> b
$ Either String b
-> (String -> Either String b) -> Maybe String -> Either String b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (b -> Either String b
forall a b. b -> Either a b
Right (Maybe a -> b
f Maybe a
forall a. Maybe a
Nothing)) ((String -> Either String b) -> Maybe String -> Either String b)
-> (String -> Either String b) -> Maybe String -> Either String b
forall a b. (a -> b) -> a -> b
$ \String
x -> case ReadS a
forall a. Read a => ReadS a
reads String
x of
[(a
i,String
"")] | a
i a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
mn -> b -> Either String b
forall a b. b -> Either a b
Right (Maybe a -> b
f (Maybe a -> b) -> Maybe a -> b
forall a b. (a -> b) -> a -> b
$ a -> Maybe a
forall a. a -> Maybe a
Just a
i)
[(a, String)]
_ -> String -> Either String b
forall a b. a -> Either a b
Left (String -> Either String b) -> String -> Either String b
forall a b. (a -> b) -> a -> b
$ String
"the `--" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
flag String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' option requires a number, " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
mn String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" or above"
optArgAuto :: String -> String -> (Auto -> b) -> ArgDescr (Either String b)
optArgAuto String
flag String
a Auto -> b
f = ((Maybe String -> Either String b)
-> String -> ArgDescr (Either String b))
-> String
-> (Maybe String -> Either String b)
-> ArgDescr (Either String b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Maybe String -> Either String b)
-> String -> ArgDescr (Either String b)
forall a. (Maybe String -> a) -> String -> ArgDescr a
OptArg String
a ((Maybe String -> Either String b) -> ArgDescr (Either String b))
-> (Maybe String -> Either String b) -> ArgDescr (Either String b)
forall a b. (a -> b) -> a -> b
$ Either String b
-> (String -> Either String b) -> Maybe String -> Either String b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (b -> Either String b
forall a b. b -> Either a b
Right (Auto -> b
f Auto
Yes)) ((String -> Either String b) -> Maybe String -> Either String b)
-> (String -> Either String b) -> Maybe String -> Either String b
forall a b. (a -> b) -> a -> b
$ \String
x -> case String
x of
String
"yes" -> b -> Either String b
forall a b. b -> Either a b
Right (b -> Either String b) -> b -> Either String b
forall a b. (a -> b) -> a -> b
$ Auto -> b
f Auto
Yes
String
"no" -> b -> Either String b
forall a b. b -> Either a b
Right (b -> Either String b) -> b -> Either String b
forall a b. (a -> b) -> a -> b
$ Auto -> b
f Auto
No
String
"auto" -> b -> Either String b
forall a b. b -> Either a b
Right (b -> Either String b) -> b -> Either String b
forall a b. (a -> b) -> a -> b
$ Auto -> b
f Auto
Auto
String
_ -> String -> Either String b
forall a b. a -> Either a b
Left (String -> Either String b) -> String -> Either String b
forall a b. (a -> b) -> a -> b
$ String
"the `--" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
flag String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' option requires yes|no|auto, but got " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
x
reqArgPair :: String
-> String -> ((String, String) -> b) -> ArgDescr (Either String b)
reqArgPair String
flag String
a (String, String) -> b
f = ((String -> Either String b)
-> String -> ArgDescr (Either String b))
-> String
-> (String -> Either String b)
-> ArgDescr (Either String b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (String -> Either String b) -> String -> ArgDescr (Either String b)
forall a. (String -> a) -> String -> ArgDescr a
ReqArg String
a ((String -> Either String b) -> ArgDescr (Either String b))
-> (String -> Either String b) -> ArgDescr (Either String b)
forall a b. (a -> b) -> a -> b
$ \String
x -> case (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'=') String
x of
(String
a,Char
'=':String
b) -> b -> Either String b
forall a b. b -> Either a b
Right (b -> Either String b) -> b -> Either String b
forall a b. (a -> b) -> a -> b
$ (String, String) -> b
f (String
a,String
b)
(String, String)
_ -> String -> Either String b
forall a b. a -> Either a b
Left (String -> Either String b) -> String -> Either String b
forall a b. (a -> b) -> a -> b
$ String
"the `--" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
flag String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' option requires an = in the argument"
progress :: ArgDescr (Either a (a -> a))
-> ArgDescr (Either a ([Extra], a -> a))
progress (OptArg Maybe String -> Either a (a -> a)
func String
msg) = ((Maybe String -> Either a ([Extra], a -> a))
-> String -> ArgDescr (Either a ([Extra], a -> a)))
-> String
-> (Maybe String -> Either a ([Extra], a -> a))
-> ArgDescr (Either a ([Extra], a -> a))
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Maybe String -> Either a ([Extra], a -> a))
-> String -> ArgDescr (Either a ([Extra], a -> a))
forall a. (Maybe String -> a) -> String -> ArgDescr a
OptArg String
msg ((Maybe String -> Either a ([Extra], a -> a))
-> ArgDescr (Either a ([Extra], a -> a)))
-> (Maybe String -> Either a ([Extra], a -> a))
-> ArgDescr (Either a ([Extra], a -> a))
forall a b. (a -> b) -> a -> b
$ \Maybe String
x -> case (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'=') (String -> (String, String))
-> Maybe String -> Maybe (String, String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Maybe String
x of
Just (String
"record",String
file) -> ([Extra], a -> a) -> Either a ([Extra], a -> a)
forall a b. b -> Either a b
Right ([String -> Extra
ProgressRecord (String -> Extra) -> String -> Extra
forall a b. (a -> b) -> a -> b
$ if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
file then String
"progress.txt" else String -> String
forall a. [a] -> [a]
tail String
file], a -> a
forall a. a -> a
id)
Just (String
"replay",String
file) -> ([Extra], a -> a) -> Either a ([Extra], a -> a)
forall a b. b -> Either a b
Right ([String -> Extra
ProgressReplay (String -> Extra) -> String -> Extra
forall a b. (a -> b) -> a -> b
$ if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
file then String
"progress.txt" else String -> String
forall a. [a] -> [a]
tail String
file], a -> a
forall a. a -> a
id)
Maybe (String, String)
_ -> ([],) ((a -> a) -> ([Extra], a -> a))
-> Either a (a -> a) -> Either a ([Extra], a -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String -> Either a (a -> a)
func Maybe String
x
progress ArgDescr (Either a (a -> a))
_ = SomeException -> ArgDescr (Either a ([Extra], a -> a))
forall a. SomeException -> a
throwImpure (SomeException -> ArgDescr (Either a ([Extra], a -> a)))
-> SomeException -> ArgDescr (Either a ([Extra], a -> a))
forall a b. (a -> b) -> a -> b
$ Partial => String -> SomeException
String -> SomeException
errorInternal String
"incomplete pattern, progress"
outputDebug :: (Verbosity -> String -> IO ())
-> Maybe String -> Verbosity -> String -> IO ()
outputDebug Verbosity -> String -> IO ()
output Maybe String
Nothing = Verbosity -> String -> IO ()
output
outputDebug Verbosity -> String -> IO ()
output (Just String
file) = \Verbosity
v String
msg -> do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
v Verbosity -> Verbosity -> Bool
forall a. Eq a => a -> a -> Bool
/= Verbosity
Diagnostic) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Verbosity -> String -> IO ()
output Verbosity
v String
msg
String -> String -> IO ()
appendFile String
file (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> String
removeEscCodes String
msg String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
prog :: Double -> IO Progress -> IO ()
prog Double
i IO Progress
p = do
String -> IO ()
program <- IO (String -> IO ())
progressProgram
Double -> (String -> IO ()) -> IO Progress -> IO ()
progressDisplay Double
i (\String
s -> String -> IO ()
progressTitlebar String
s IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO ()
program String
s) IO Progress
p
ensureHash :: Change -> Change
ensureHash Change
ChangeModtime = Change
ChangeModtimeAndDigest
ensureHash Change
ChangeModtimeAndDigestInput = Change
ChangeModtimeAndDigest
ensureHash Change
x = Change
x
ensureShare :: ShakeOptions -> ShakeOptions
ensureShare ShakeOptions
s = ShakeOptions
s{shakeShare :: Maybe String
shakeShare = String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"." (Maybe String -> String) -> Maybe String -> String
forall a b. (a -> b) -> a -> b
$ ShakeOptions -> Maybe String
shakeShare ShakeOptions
s}