{-# LANGUAGE DeriveDataTypeable, PatternGuards #-}
module Development.Shake.Internal.Options(
Progress(..), Verbosity(..), Rebuild(..), Lint(..), Change(..),
ShakeOptions(..), shakeOptions,
shakeRebuildApply, shakeAbbreviationsApply, shakeOptionsFields
) where
import Data.Data
import Data.List.Extra
import Data.Tuple.Extra
import Data.Maybe
import Data.Dynamic
import Control.Monad
import General.Extra
import System.Time.Extra
import qualified Data.HashMap.Strict as Map
import Development.Shake.Internal.FilePattern
import Development.Shake.Internal.Errors
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.UTF8 as UTF8
import Development.Shake.Internal.CmdOption
import Data.Semigroup
import Prelude
data Rebuild
= RebuildNow
| RebuildNormal
| RebuildLater
deriving (Rebuild -> Rebuild -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Rebuild -> Rebuild -> Bool
$c/= :: Rebuild -> Rebuild -> Bool
== :: Rebuild -> Rebuild -> Bool
$c== :: Rebuild -> Rebuild -> Bool
Eq,Eq Rebuild
Rebuild -> Rebuild -> Bool
Rebuild -> Rebuild -> Ordering
Rebuild -> Rebuild -> Rebuild
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Rebuild -> Rebuild -> Rebuild
$cmin :: Rebuild -> Rebuild -> Rebuild
max :: Rebuild -> Rebuild -> Rebuild
$cmax :: Rebuild -> Rebuild -> Rebuild
>= :: Rebuild -> Rebuild -> Bool
$c>= :: Rebuild -> Rebuild -> Bool
> :: Rebuild -> Rebuild -> Bool
$c> :: Rebuild -> Rebuild -> Bool
<= :: Rebuild -> Rebuild -> Bool
$c<= :: Rebuild -> Rebuild -> Bool
< :: Rebuild -> Rebuild -> Bool
$c< :: Rebuild -> Rebuild -> Bool
compare :: Rebuild -> Rebuild -> Ordering
$ccompare :: Rebuild -> Rebuild -> Ordering
Ord,Int -> Rebuild -> ShowS
[Rebuild] -> ShowS
Rebuild -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Rebuild] -> ShowS
$cshowList :: [Rebuild] -> ShowS
show :: Rebuild -> String
$cshow :: Rebuild -> String
showsPrec :: Int -> Rebuild -> ShowS
$cshowsPrec :: Int -> Rebuild -> ShowS
Show,ReadPrec [Rebuild]
ReadPrec Rebuild
Int -> ReadS Rebuild
ReadS [Rebuild]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Rebuild]
$creadListPrec :: ReadPrec [Rebuild]
readPrec :: ReadPrec Rebuild
$creadPrec :: ReadPrec Rebuild
readList :: ReadS [Rebuild]
$creadList :: ReadS [Rebuild]
readsPrec :: Int -> ReadS Rebuild
$creadsPrec :: Int -> ReadS Rebuild
Read,Typeable,Typeable Rebuild
Rebuild -> DataType
Rebuild -> Constr
(forall b. Data b => b -> b) -> Rebuild -> Rebuild
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Rebuild -> u
forall u. (forall d. Data d => d -> u) -> Rebuild -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Rebuild -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Rebuild -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Rebuild -> m Rebuild
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rebuild -> m Rebuild
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Rebuild
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Rebuild -> c Rebuild
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Rebuild)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rebuild)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rebuild -> m Rebuild
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rebuild -> m Rebuild
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rebuild -> m Rebuild
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rebuild -> m Rebuild
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Rebuild -> m Rebuild
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Rebuild -> m Rebuild
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Rebuild -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Rebuild -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Rebuild -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Rebuild -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Rebuild -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Rebuild -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Rebuild -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Rebuild -> r
gmapT :: (forall b. Data b => b -> b) -> Rebuild -> Rebuild
$cgmapT :: (forall b. Data b => b -> b) -> Rebuild -> Rebuild
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rebuild)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rebuild)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Rebuild)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Rebuild)
dataTypeOf :: Rebuild -> DataType
$cdataTypeOf :: Rebuild -> DataType
toConstr :: Rebuild -> Constr
$ctoConstr :: Rebuild -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Rebuild
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Rebuild
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Rebuild -> c Rebuild
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Rebuild -> c Rebuild
Data,Int -> Rebuild
Rebuild -> Int
Rebuild -> [Rebuild]
Rebuild -> Rebuild
Rebuild -> Rebuild -> [Rebuild]
Rebuild -> Rebuild -> Rebuild -> [Rebuild]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Rebuild -> Rebuild -> Rebuild -> [Rebuild]
$cenumFromThenTo :: Rebuild -> Rebuild -> Rebuild -> [Rebuild]
enumFromTo :: Rebuild -> Rebuild -> [Rebuild]
$cenumFromTo :: Rebuild -> Rebuild -> [Rebuild]
enumFromThen :: Rebuild -> Rebuild -> [Rebuild]
$cenumFromThen :: Rebuild -> Rebuild -> [Rebuild]
enumFrom :: Rebuild -> [Rebuild]
$cenumFrom :: Rebuild -> [Rebuild]
fromEnum :: Rebuild -> Int
$cfromEnum :: Rebuild -> Int
toEnum :: Int -> Rebuild
$ctoEnum :: Int -> Rebuild
pred :: Rebuild -> Rebuild
$cpred :: Rebuild -> Rebuild
succ :: Rebuild -> Rebuild
$csucc :: Rebuild -> Rebuild
Enum,Rebuild
forall a. a -> a -> Bounded a
maxBound :: Rebuild
$cmaxBound :: Rebuild
minBound :: Rebuild
$cminBound :: Rebuild
Bounded)
data Lint
= LintBasic
| LintFSATrace
deriving (Lint -> Lint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Lint -> Lint -> Bool
$c/= :: Lint -> Lint -> Bool
== :: Lint -> Lint -> Bool
$c== :: Lint -> Lint -> Bool
Eq,Eq Lint
Lint -> Lint -> Bool
Lint -> Lint -> Ordering
Lint -> Lint -> Lint
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Lint -> Lint -> Lint
$cmin :: Lint -> Lint -> Lint
max :: Lint -> Lint -> Lint
$cmax :: Lint -> Lint -> Lint
>= :: Lint -> Lint -> Bool
$c>= :: Lint -> Lint -> Bool
> :: Lint -> Lint -> Bool
$c> :: Lint -> Lint -> Bool
<= :: Lint -> Lint -> Bool
$c<= :: Lint -> Lint -> Bool
< :: Lint -> Lint -> Bool
$c< :: Lint -> Lint -> Bool
compare :: Lint -> Lint -> Ordering
$ccompare :: Lint -> Lint -> Ordering
Ord,Int -> Lint -> ShowS
[Lint] -> ShowS
Lint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Lint] -> ShowS
$cshowList :: [Lint] -> ShowS
show :: Lint -> String
$cshow :: Lint -> String
showsPrec :: Int -> Lint -> ShowS
$cshowsPrec :: Int -> Lint -> ShowS
Show,ReadPrec [Lint]
ReadPrec Lint
Int -> ReadS Lint
ReadS [Lint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Lint]
$creadListPrec :: ReadPrec [Lint]
readPrec :: ReadPrec Lint
$creadPrec :: ReadPrec Lint
readList :: ReadS [Lint]
$creadList :: ReadS [Lint]
readsPrec :: Int -> ReadS Lint
$creadsPrec :: Int -> ReadS Lint
Read,Typeable,Typeable Lint
Lint -> DataType
Lint -> Constr
(forall b. Data b => b -> b) -> Lint -> Lint
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Lint -> u
forall u. (forall d. Data d => d -> u) -> Lint -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Lint -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Lint -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Lint -> m Lint
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Lint -> m Lint
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Lint
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Lint -> c Lint
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Lint)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lint)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Lint -> m Lint
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Lint -> m Lint
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Lint -> m Lint
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Lint -> m Lint
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Lint -> m Lint
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Lint -> m Lint
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Lint -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Lint -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Lint -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Lint -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Lint -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Lint -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Lint -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Lint -> r
gmapT :: (forall b. Data b => b -> b) -> Lint -> Lint
$cgmapT :: (forall b. Data b => b -> b) -> Lint -> Lint
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lint)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lint)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Lint)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Lint)
dataTypeOf :: Lint -> DataType
$cdataTypeOf :: Lint -> DataType
toConstr :: Lint -> Constr
$ctoConstr :: Lint -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Lint
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Lint
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Lint -> c Lint
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Lint -> c Lint
Data,Int -> Lint
Lint -> Int
Lint -> [Lint]
Lint -> Lint
Lint -> Lint -> [Lint]
Lint -> Lint -> Lint -> [Lint]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Lint -> Lint -> Lint -> [Lint]
$cenumFromThenTo :: Lint -> Lint -> Lint -> [Lint]
enumFromTo :: Lint -> Lint -> [Lint]
$cenumFromTo :: Lint -> Lint -> [Lint]
enumFromThen :: Lint -> Lint -> [Lint]
$cenumFromThen :: Lint -> Lint -> [Lint]
enumFrom :: Lint -> [Lint]
$cenumFrom :: Lint -> [Lint]
fromEnum :: Lint -> Int
$cfromEnum :: Lint -> Int
toEnum :: Int -> Lint
$ctoEnum :: Int -> Lint
pred :: Lint -> Lint
$cpred :: Lint -> Lint
succ :: Lint -> Lint
$csucc :: Lint -> Lint
Enum,Lint
forall a. a -> a -> Bounded a
maxBound :: Lint
$cmaxBound :: Lint
minBound :: Lint
$cminBound :: Lint
Bounded)
data Change
= ChangeModtime
| ChangeDigest
| ChangeModtimeAndDigest
| ChangeModtimeAndDigestInput
| ChangeModtimeOrDigest
deriving (Change -> Change -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Change -> Change -> Bool
$c/= :: Change -> Change -> Bool
== :: Change -> Change -> Bool
$c== :: Change -> Change -> Bool
Eq,Eq Change
Change -> Change -> Bool
Change -> Change -> Ordering
Change -> Change -> Change
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Change -> Change -> Change
$cmin :: Change -> Change -> Change
max :: Change -> Change -> Change
$cmax :: Change -> Change -> Change
>= :: Change -> Change -> Bool
$c>= :: Change -> Change -> Bool
> :: Change -> Change -> Bool
$c> :: Change -> Change -> Bool
<= :: Change -> Change -> Bool
$c<= :: Change -> Change -> Bool
< :: Change -> Change -> Bool
$c< :: Change -> Change -> Bool
compare :: Change -> Change -> Ordering
$ccompare :: Change -> Change -> Ordering
Ord,Int -> Change -> ShowS
[Change] -> ShowS
Change -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Change] -> ShowS
$cshowList :: [Change] -> ShowS
show :: Change -> String
$cshow :: Change -> String
showsPrec :: Int -> Change -> ShowS
$cshowsPrec :: Int -> Change -> ShowS
Show,ReadPrec [Change]
ReadPrec Change
Int -> ReadS Change
ReadS [Change]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Change]
$creadListPrec :: ReadPrec [Change]
readPrec :: ReadPrec Change
$creadPrec :: ReadPrec Change
readList :: ReadS [Change]
$creadList :: ReadS [Change]
readsPrec :: Int -> ReadS Change
$creadsPrec :: Int -> ReadS Change
Read,Typeable,Typeable Change
Change -> DataType
Change -> Constr
(forall b. Data b => b -> b) -> Change -> Change
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Change -> u
forall u. (forall d. Data d => d -> u) -> Change -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Change -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Change -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Change -> m Change
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Change -> m Change
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Change
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Change -> c Change
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Change)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Change)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Change -> m Change
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Change -> m Change
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Change -> m Change
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Change -> m Change
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Change -> m Change
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Change -> m Change
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Change -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Change -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Change -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Change -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Change -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Change -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Change -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Change -> r
gmapT :: (forall b. Data b => b -> b) -> Change -> Change
$cgmapT :: (forall b. Data b => b -> b) -> Change -> Change
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Change)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Change)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Change)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Change)
dataTypeOf :: Change -> DataType
$cdataTypeOf :: Change -> DataType
toConstr :: Change -> Constr
$ctoConstr :: Change -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Change
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Change
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Change -> c Change
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Change -> c Change
Data,Int -> Change
Change -> Int
Change -> [Change]
Change -> Change
Change -> Change -> [Change]
Change -> Change -> Change -> [Change]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Change -> Change -> Change -> [Change]
$cenumFromThenTo :: Change -> Change -> Change -> [Change]
enumFromTo :: Change -> Change -> [Change]
$cenumFromTo :: Change -> Change -> [Change]
enumFromThen :: Change -> Change -> [Change]
$cenumFromThen :: Change -> Change -> [Change]
enumFrom :: Change -> [Change]
$cenumFrom :: Change -> [Change]
fromEnum :: Change -> Int
$cfromEnum :: Change -> Int
toEnum :: Int -> Change
$ctoEnum :: Int -> Change
pred :: Change -> Change
$cpred :: Change -> Change
succ :: Change -> Change
$csucc :: Change -> Change
Enum,Change
forall a. a -> a -> Bounded a
maxBound :: Change
$cmaxBound :: Change
minBound :: Change
$cminBound :: Change
Bounded)
data Progress = Progress
{Progress -> Maybe String
isFailure :: !(Maybe String)
,Progress -> Int
countSkipped :: {-# UNPACK #-} !Int
,Progress -> Int
countBuilt :: {-# UNPACK #-} !Int
,Progress -> Int
countUnknown :: {-# UNPACK #-} !Int
,Progress -> Int
countTodo :: {-# UNPACK #-} !Int
,Progress -> Seconds
timeSkipped :: {-# UNPACK #-} !Double
,Progress -> Seconds
timeBuilt :: {-# UNPACK #-} !Double
,Progress -> Seconds
timeUnknown :: {-# UNPACK #-} !Double
,Progress -> (Seconds, Int)
timeTodo :: {-# UNPACK #-} !(Double,Int)
}
deriving (Progress -> Progress -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Progress -> Progress -> Bool
$c/= :: Progress -> Progress -> Bool
== :: Progress -> Progress -> Bool
$c== :: Progress -> Progress -> Bool
Eq,Eq Progress
Progress -> Progress -> Bool
Progress -> Progress -> Ordering
Progress -> Progress -> Progress
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Progress -> Progress -> Progress
$cmin :: Progress -> Progress -> Progress
max :: Progress -> Progress -> Progress
$cmax :: Progress -> Progress -> Progress
>= :: Progress -> Progress -> Bool
$c>= :: Progress -> Progress -> Bool
> :: Progress -> Progress -> Bool
$c> :: Progress -> Progress -> Bool
<= :: Progress -> Progress -> Bool
$c<= :: Progress -> Progress -> Bool
< :: Progress -> Progress -> Bool
$c< :: Progress -> Progress -> Bool
compare :: Progress -> Progress -> Ordering
$ccompare :: Progress -> Progress -> Ordering
Ord,Int -> Progress -> ShowS
[Progress] -> ShowS
Progress -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Progress] -> ShowS
$cshowList :: [Progress] -> ShowS
show :: Progress -> String
$cshow :: Progress -> String
showsPrec :: Int -> Progress -> ShowS
$cshowsPrec :: Int -> Progress -> ShowS
Show,ReadPrec [Progress]
ReadPrec Progress
Int -> ReadS Progress
ReadS [Progress]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Progress]
$creadListPrec :: ReadPrec [Progress]
readPrec :: ReadPrec Progress
$creadPrec :: ReadPrec Progress
readList :: ReadS [Progress]
$creadList :: ReadS [Progress]
readsPrec :: Int -> ReadS Progress
$creadsPrec :: Int -> ReadS Progress
Read,Typeable Progress
Progress -> DataType
Progress -> Constr
(forall b. Data b => b -> b) -> Progress -> Progress
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Progress -> u
forall u. (forall d. Data d => d -> u) -> Progress -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Progress -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Progress -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Progress -> m Progress
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Progress -> m Progress
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Progress
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Progress -> c Progress
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Progress)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Progress)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Progress -> m Progress
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Progress -> m Progress
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Progress -> m Progress
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Progress -> m Progress
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Progress -> m Progress
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Progress -> m Progress
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Progress -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Progress -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Progress -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Progress -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Progress -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Progress -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Progress -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Progress -> r
gmapT :: (forall b. Data b => b -> b) -> Progress -> Progress
$cgmapT :: (forall b. Data b => b -> b) -> Progress -> Progress
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Progress)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Progress)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Progress)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Progress)
dataTypeOf :: Progress -> DataType
$cdataTypeOf :: Progress -> DataType
toConstr :: Progress -> Constr
$ctoConstr :: Progress -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Progress
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Progress
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Progress -> c Progress
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Progress -> c Progress
Data,Typeable)
instance Semigroup Progress where
Progress
a <> :: Progress -> Progress -> Progress
<> Progress
b = Progress
{isFailure :: Maybe String
isFailure = Progress -> Maybe String
isFailure Progress
a forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` Progress -> Maybe String
isFailure Progress
b
,countSkipped :: Int
countSkipped = Progress -> Int
countSkipped Progress
a forall a. Num a => a -> a -> a
+ Progress -> Int
countSkipped Progress
b
,countBuilt :: Int
countBuilt = Progress -> Int
countBuilt Progress
a forall a. Num a => a -> a -> a
+ Progress -> Int
countBuilt Progress
b
,countUnknown :: Int
countUnknown = Progress -> Int
countUnknown Progress
a forall a. Num a => a -> a -> a
+ Progress -> Int
countUnknown Progress
b
,countTodo :: Int
countTodo = Progress -> Int
countTodo Progress
a forall a. Num a => a -> a -> a
+ Progress -> Int
countTodo Progress
b
,timeSkipped :: Seconds
timeSkipped = Progress -> Seconds
timeSkipped Progress
a forall a. Num a => a -> a -> a
+ Progress -> Seconds
timeSkipped Progress
b
,timeBuilt :: Seconds
timeBuilt = Progress -> Seconds
timeBuilt Progress
a forall a. Num a => a -> a -> a
+ Progress -> Seconds
timeBuilt Progress
b
,timeUnknown :: Seconds
timeUnknown = Progress -> Seconds
timeUnknown Progress
a forall a. Num a => a -> a -> a
+ Progress -> Seconds
timeUnknown Progress
b
,timeTodo :: (Seconds, Int)
timeTodo = let (Seconds
a1,Int
a2) = Progress -> (Seconds, Int)
timeTodo Progress
a; (Seconds
b1,Int
b2) = Progress -> (Seconds, Int)
timeTodo Progress
b
x1 :: Seconds
x1 = Seconds
a1 forall a. Num a => a -> a -> a
+ Seconds
b1; x2 :: Int
x2 = Int
a2 forall a. Num a => a -> a -> a
+ Int
b2
in Seconds
x1 seq :: forall a b. a -> b -> b
`seq` Int
x2 seq :: forall a b. a -> b -> b
`seq` (Seconds
x1,Int
x2)
}
instance Monoid Progress where
mempty :: Progress
mempty = Maybe String
-> Int
-> Int
-> Int
-> Int
-> Seconds
-> Seconds
-> Seconds
-> (Seconds, Int)
-> Progress
Progress forall a. Maybe a
Nothing Int
0 Int
0 Int
0 Int
0 Seconds
0 Seconds
0 Seconds
0 (Seconds
0,Int
0)
mappend :: Progress -> Progress -> Progress
mappend = forall a. Semigroup a => a -> a -> a
(<>)
data ShakeOptions = ShakeOptions
{ShakeOptions -> String
shakeFiles :: FilePath
,ShakeOptions -> Int
shakeThreads :: Int
,ShakeOptions -> String
shakeVersion :: String
,ShakeOptions -> Verbosity
shakeVerbosity :: Verbosity
,ShakeOptions -> Bool
shakeStaunch :: Bool
,ShakeOptions -> [String]
shakeReport :: [FilePath]
,ShakeOptions -> Maybe Lint
shakeLint :: Maybe Lint
,ShakeOptions -> [String]
shakeLintInside :: [FilePath]
,ShakeOptions -> [String]
shakeLintIgnore :: [FilePattern]
,ShakeOptions -> [String]
shakeLintWatch :: [FilePattern]
,ShakeOptions -> [CmdOption]
shakeCommandOptions :: [CmdOption]
,ShakeOptions -> Maybe Seconds
shakeFlush :: Maybe Seconds
,ShakeOptions -> [(Rebuild, String)]
shakeRebuild :: [(Rebuild, FilePattern)]
,ShakeOptions -> [(String, String)]
shakeAbbreviations :: [(String,String)]
,ShakeOptions -> Bool
shakeStorageLog :: Bool
,ShakeOptions -> Bool
shakeLineBuffering :: Bool
,ShakeOptions -> Bool
shakeTimings :: Bool
,ShakeOptions -> Bool
shakeRunCommands :: Bool
,ShakeOptions -> Change
shakeChange :: Change
,ShakeOptions -> Bool
shakeCreationCheck :: Bool
,ShakeOptions -> [String]
shakeLiveFiles :: [FilePath]
,ShakeOptions -> Bool
shakeVersionIgnore :: Bool
,ShakeOptions -> Bool
shakeColor :: Bool
,ShakeOptions -> Maybe String
shakeShare :: Maybe FilePath
,ShakeOptions -> [String]
shakeCloud :: [String]
,ShakeOptions -> Bool
shakeSymlink :: Bool
,ShakeOptions -> Bool
shakeNeedDirectory :: Bool
,ShakeOptions -> Bool
shakeAllowRedefineRules :: Bool
,ShakeOptions -> IO Progress -> IO ()
shakeProgress :: IO Progress -> IO ()
,ShakeOptions -> Verbosity -> String -> IO ()
shakeOutput :: Verbosity -> String -> IO ()
,ShakeOptions -> String -> String -> Bool -> IO ()
shakeTrace :: String -> String -> Bool -> IO ()
, :: Map.HashMap TypeRep Dynamic
}
deriving Typeable
shakeOptions :: ShakeOptions
shakeOptions :: ShakeOptions
shakeOptions = String
-> Int
-> String
-> Verbosity
-> Bool
-> [String]
-> Maybe Lint
-> [String]
-> [String]
-> [String]
-> [CmdOption]
-> Maybe Seconds
-> [(Rebuild, String)]
-> [(String, String)]
-> Bool
-> Bool
-> Bool
-> Bool
-> Change
-> Bool
-> [String]
-> Bool
-> Bool
-> Maybe String
-> [String]
-> Bool
-> Bool
-> Bool
-> (IO Progress -> IO ())
-> (Verbosity -> String -> IO ())
-> (String -> String -> Bool -> IO ())
-> HashMap TypeRep Dynamic
-> ShakeOptions
ShakeOptions
String
".shake" Int
1 String
"1" Verbosity
Info Bool
False [] forall a. Maybe a
Nothing [] [] [] [] (forall a. a -> Maybe a
Just Seconds
10) [] [] Bool
False Bool
True Bool
False
Bool
True Change
ChangeModtime Bool
True [] Bool
False Bool
False forall a. Maybe a
Nothing [] Bool
False Bool
False Bool
False
(forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
(forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ ByteString -> IO ()
BS.putStrLn forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
UTF8.fromString)
(\String
_ String
_ Bool
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
forall k v. HashMap k v
Map.empty
fieldsShakeOptions :: [String]
fieldsShakeOptions =
[String
"shakeFiles", String
"shakeThreads", String
"shakeVersion", String
"shakeVerbosity", String
"shakeStaunch", String
"shakeReport"
,String
"shakeLint", String
"shakeLintInside", String
"shakeLintIgnore", String
"shakeLintWatch", String
"shakeCommandOptions"
,String
"shakeFlush", String
"shakeRebuild", String
"shakeAbbreviations", String
"shakeStorageLog"
,String
"shakeLineBuffering", String
"shakeTimings", String
"shakeRunCommands", String
"shakeChange", String
"shakeCreationCheck"
,String
"shakeLiveFiles", String
"shakeVersionIgnore", String
"shakeColor", String
"shakeShare", String
"shakeCloud", String
"shakeSymlink"
,String
"shakeNeedDirectory", String
"shakeCanRedefineRules"
,String
"shakeProgress", String
"shakeOutput", String
"shakeTrace", String
"shakeExtra"]
tyShakeOptions :: DataType
tyShakeOptions = String -> [Constr] -> DataType
mkDataType String
"Development.Shake.Types.ShakeOptions" [Constr
conShakeOptions]
conShakeOptions :: Constr
conShakeOptions = DataType -> String -> [String] -> Fixity -> Constr
mkConstr DataType
tyShakeOptions String
"ShakeOptions" [String]
fieldsShakeOptions Fixity
Prefix
unhide :: String
-> Int
-> String
-> Verbosity
-> Bool
-> [String]
-> Maybe Lint
-> [String]
-> [String]
-> [String]
-> [CmdOption]
-> Maybe Seconds
-> [(Rebuild, String)]
-> [(String, String)]
-> Bool
-> Bool
-> Bool
-> Bool
-> Change
-> Bool
-> [String]
-> Bool
-> Bool
-> Maybe String
-> [String]
-> Bool
-> Bool
-> Bool
-> Hidden (IO Progress -> IO ())
-> Hidden (Verbosity -> String -> IO ())
-> Hidden (String -> String -> Bool -> IO ())
-> Hidden (HashMap TypeRep Dynamic)
-> ShakeOptions
unhide String
x1 Int
x2 String
x3 Verbosity
x4 Bool
x5 [String]
x6 Maybe Lint
x7 [String]
x8 [String]
x9 [String]
x10 [CmdOption]
x11 Maybe Seconds
x12 [(Rebuild, String)]
x13 [(String, String)]
x14 Bool
x15 Bool
x16 Bool
x17 Bool
x18 Change
x19 Bool
x20 [String]
x21 Bool
x22 Bool
x23 Maybe String
x24 [String]
x25 Bool
x26 Bool
x27 Bool
x28 Hidden (IO Progress -> IO ())
y1 Hidden (Verbosity -> String -> IO ())
y2 Hidden (String -> String -> Bool -> IO ())
y3 Hidden (HashMap TypeRep Dynamic)
y4 =
String
-> Int
-> String
-> Verbosity
-> Bool
-> [String]
-> Maybe Lint
-> [String]
-> [String]
-> [String]
-> [CmdOption]
-> Maybe Seconds
-> [(Rebuild, String)]
-> [(String, String)]
-> Bool
-> Bool
-> Bool
-> Bool
-> Change
-> Bool
-> [String]
-> Bool
-> Bool
-> Maybe String
-> [String]
-> Bool
-> Bool
-> Bool
-> (IO Progress -> IO ())
-> (Verbosity -> String -> IO ())
-> (String -> String -> Bool -> IO ())
-> HashMap TypeRep Dynamic
-> ShakeOptions
ShakeOptions String
x1 Int
x2 String
x3 Verbosity
x4 Bool
x5 [String]
x6 Maybe Lint
x7 [String]
x8 [String]
x9 [String]
x10 [CmdOption]
x11 Maybe Seconds
x12 [(Rebuild, String)]
x13 [(String, String)]
x14 Bool
x15 Bool
x16 Bool
x17 Bool
x18 Change
x19 Bool
x20 [String]
x21 Bool
x22 Bool
x23 Maybe String
x24 [String]
x25 Bool
x26 Bool
x27 Bool
x28
(forall a. Hidden a -> a
fromHidden Hidden (IO Progress -> IO ())
y1) (forall a. Hidden a -> a
fromHidden Hidden (Verbosity -> String -> IO ())
y2) (forall a. Hidden a -> a
fromHidden Hidden (String -> String -> Bool -> IO ())
y3) (forall a. Hidden a -> a
fromHidden Hidden (HashMap TypeRep Dynamic)
y4)
instance Data ShakeOptions where
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ShakeOptions -> c ShakeOptions
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
k forall g. g -> c g
z (ShakeOptions String
x1 Int
x2 String
x3 Verbosity
x4 Bool
x5 [String]
x6 Maybe Lint
x7 [String]
x8 [String]
x9 [String]
x10 [CmdOption]
x11 Maybe Seconds
x12 [(Rebuild, String)]
x13 [(String, String)]
x14 Bool
x15 Bool
x16 Bool
x17 Bool
x18 Change
x19 Bool
x20 [String]
x21 Bool
x22 Bool
x23 Maybe String
x24 [String]
x25 Bool
x26 Bool
x27 Bool
x28 IO Progress -> IO ()
y1 Verbosity -> String -> IO ()
y2 String -> String -> Bool -> IO ()
y3 HashMap TypeRep Dynamic
y4) =
forall g. g -> c g
z String
-> Int
-> String
-> Verbosity
-> Bool
-> [String]
-> Maybe Lint
-> [String]
-> [String]
-> [String]
-> [CmdOption]
-> Maybe Seconds
-> [(Rebuild, String)]
-> [(String, String)]
-> Bool
-> Bool
-> Bool
-> Bool
-> Change
-> Bool
-> [String]
-> Bool
-> Bool
-> Maybe String
-> [String]
-> Bool
-> Bool
-> Bool
-> Hidden (IO Progress -> IO ())
-> Hidden (Verbosity -> String -> IO ())
-> Hidden (String -> String -> Bool -> IO ())
-> Hidden (HashMap TypeRep Dynamic)
-> ShakeOptions
unhide forall d b. Data d => c (d -> b) -> d -> c b
`k` String
x1 forall d b. Data d => c (d -> b) -> d -> c b
`k` Int
x2 forall d b. Data d => c (d -> b) -> d -> c b
`k` String
x3 forall d b. Data d => c (d -> b) -> d -> c b
`k` Verbosity
x4 forall d b. Data d => c (d -> b) -> d -> c b
`k` Bool
x5 forall d b. Data d => c (d -> b) -> d -> c b
`k` [String]
x6 forall d b. Data d => c (d -> b) -> d -> c b
`k` Maybe Lint
x7 forall d b. Data d => c (d -> b) -> d -> c b
`k` [String]
x8 forall d b. Data d => c (d -> b) -> d -> c b
`k` [String]
x9 forall d b. Data d => c (d -> b) -> d -> c b
`k` [String]
x10 forall d b. Data d => c (d -> b) -> d -> c b
`k` [CmdOption]
x11 forall d b. Data d => c (d -> b) -> d -> c b
`k`
Maybe Seconds
x12 forall d b. Data d => c (d -> b) -> d -> c b
`k` [(Rebuild, String)]
x13 forall d b. Data d => c (d -> b) -> d -> c b
`k` [(String, String)]
x14 forall d b. Data d => c (d -> b) -> d -> c b
`k` Bool
x15 forall d b. Data d => c (d -> b) -> d -> c b
`k` Bool
x16 forall d b. Data d => c (d -> b) -> d -> c b
`k` Bool
x17 forall d b. Data d => c (d -> b) -> d -> c b
`k` Bool
x18 forall d b. Data d => c (d -> b) -> d -> c b
`k` Change
x19 forall d b. Data d => c (d -> b) -> d -> c b
`k` Bool
x20 forall d b. Data d => c (d -> b) -> d -> c b
`k` [String]
x21 forall d b. Data d => c (d -> b) -> d -> c b
`k` Bool
x22 forall d b. Data d => c (d -> b) -> d -> c b
`k` Bool
x23 forall d b. Data d => c (d -> b) -> d -> c b
`k` Maybe String
x24 forall d b. Data d => c (d -> b) -> d -> c b
`k` [String]
x25 forall d b. Data d => c (d -> b) -> d -> c b
`k` Bool
x26 forall d b. Data d => c (d -> b) -> d -> c b
`k` Bool
x27 forall d b. Data d => c (d -> b) -> d -> c b
`k` Bool
x28 forall d b. Data d => c (d -> b) -> d -> c b
`k`
forall a. a -> Hidden a
Hidden IO Progress -> IO ()
y1 forall d b. Data d => c (d -> b) -> d -> c b
`k` forall a. a -> Hidden a
Hidden Verbosity -> String -> IO ()
y2 forall d b. Data d => c (d -> b) -> d -> c b
`k` forall a. a -> Hidden a
Hidden String -> String -> Bool -> IO ()
y3 forall d b. Data d => c (d -> b) -> d -> c b
`k` forall a. a -> Hidden a
Hidden HashMap TypeRep Dynamic
y4
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ShakeOptions
gunfold forall b r. Data b => c (b -> r) -> c r
k forall r. r -> c r
z Constr
_ = forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall b r. Data b => c (b -> r) -> c r
k forall a b. (a -> b) -> a -> b
$ forall r. r -> c r
z String
-> Int
-> String
-> Verbosity
-> Bool
-> [String]
-> Maybe Lint
-> [String]
-> [String]
-> [String]
-> [CmdOption]
-> Maybe Seconds
-> [(Rebuild, String)]
-> [(String, String)]
-> Bool
-> Bool
-> Bool
-> Bool
-> Change
-> Bool
-> [String]
-> Bool
-> Bool
-> Maybe String
-> [String]
-> Bool
-> Bool
-> Bool
-> Hidden (IO Progress -> IO ())
-> Hidden (Verbosity -> String -> IO ())
-> Hidden (String -> String -> Bool -> IO ())
-> Hidden (HashMap TypeRep Dynamic)
-> ShakeOptions
unhide
toConstr :: ShakeOptions -> Constr
toConstr ShakeOptions{} = Constr
conShakeOptions
dataTypeOf :: ShakeOptions -> DataType
dataTypeOf ShakeOptions
_ = DataType
tyShakeOptions
shakeOptionsFields :: ShakeOptions -> [(String, String)]
shakeOptionsFields :: ShakeOptions -> [(String, String)]
shakeOptionsFields = forall a b. Partial => [a] -> [b] -> [(a, b)]
zipExact [String]
fieldsShakeOptions forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a u. Data a => (forall d. Data d => d -> u) -> a -> [u]
gmapQ forall {a}. Typeable a => a -> String
f
where
f :: a -> String
f a
x | Just Int
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show (Int
x :: Int)
| Just String
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show (String
x :: FilePath)
| Just Verbosity
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show (Verbosity
x :: Verbosity)
| Just Change
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show (Change
x :: Change)
| Just Bool
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show (Bool
x :: Bool)
| Just [String]
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show ([String]
x :: [FilePath])
| Just [(Rebuild, String)]
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show ([(Rebuild, String)]
x :: [(Rebuild, FilePattern)])
| Just Maybe Lint
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show (Maybe Lint
x :: Maybe Lint)
| Just Maybe Seconds
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show (Maybe Seconds
x :: Maybe Double)
| Just Maybe String
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show (Maybe String
x :: Maybe String)
| Just [(String, String)]
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show ([(String, String)]
x :: [(String,String)])
| Just Hidden (IO Progress -> IO ())
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show (Hidden (IO Progress -> IO ())
x :: Hidden (IO Progress -> IO ()))
| Just Hidden (Verbosity -> String -> IO ())
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show (Hidden (Verbosity -> String -> IO ())
x :: Hidden (Verbosity -> String -> IO ()))
| Just Hidden (HashMap TypeRep Dynamic)
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show (Hidden (HashMap TypeRep Dynamic)
x :: Hidden (Map.HashMap TypeRep Dynamic))
| Just Hidden (String -> String -> Bool -> IO ())
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show (Hidden (String -> String -> Bool -> IO ())
x :: Hidden (String -> String -> Bool -> IO ()))
| Just [CmdOption]
x <- forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
x = forall a. Show a => a -> String
show ([CmdOption]
x :: [CmdOption])
| Bool
otherwise = forall a. SomeException -> a
throwImpure forall a b. (a -> b) -> a -> b
$ Partial => String -> SomeException
errorInternal forall a b. (a -> b) -> a -> b
$ String
"Error while showing ShakeOptions, missing alternative for " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall a. Typeable a => a -> TypeRep
typeOf a
x)
instance Show ShakeOptions where
show :: ShakeOptions -> String
show ShakeOptions
x = String
"ShakeOptions {" forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [[a]] -> [a]
intercalate String
", " (forall a b. (a -> b) -> [a] -> [b]
map (\(String
a,String
b) -> String
a forall a. [a] -> [a] -> [a]
++ String
" = " forall a. [a] -> [a] -> [a]
++ String
b) forall a b. (a -> b) -> a -> b
$ ShakeOptions -> [(String, String)]
shakeOptionsFields ShakeOptions
x) forall a. [a] -> [a] -> [a]
++ String
"}"
newtype Hidden a = Hidden {forall a. Hidden a -> a
fromHidden :: a}
deriving Typeable
instance Show (Hidden a) where show :: Hidden a -> String
show Hidden a
_ = String
"<hidden>"
instance Typeable a => Data (Hidden a) where
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Hidden a -> c (Hidden a)
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
_ forall g. g -> c g
z = forall g. g -> c g
z
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Hidden a)
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_ Constr
_ = forall a. Partial => String -> a
error String
"Development.Shake.Types.ShakeProgress: gunfold not implemented - data type has no constructors"
toConstr :: Hidden a -> Constr
toConstr Hidden a
_ = forall a. Partial => String -> a
error String
"Development.Shake.Types.ShakeProgress: toConstr not implemented - data type has no constructors"
dataTypeOf :: Hidden a -> DataType
dataTypeOf Hidden a
_ = DataType
tyHidden
tyHidden :: DataType
tyHidden = String -> [Constr] -> DataType
mkDataType String
"Development.Shake.Types.Hidden" []
data Verbosity
= Silent
| Error
| Warn
| Info
| Verbose
| Diagnostic
deriving (Verbosity -> Verbosity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Verbosity -> Verbosity -> Bool
$c/= :: Verbosity -> Verbosity -> Bool
== :: Verbosity -> Verbosity -> Bool
$c== :: Verbosity -> Verbosity -> Bool
Eq,Eq Verbosity
Verbosity -> Verbosity -> Bool
Verbosity -> Verbosity -> Ordering
Verbosity -> Verbosity -> Verbosity
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Verbosity -> Verbosity -> Verbosity
$cmin :: Verbosity -> Verbosity -> Verbosity
max :: Verbosity -> Verbosity -> Verbosity
$cmax :: Verbosity -> Verbosity -> Verbosity
>= :: Verbosity -> Verbosity -> Bool
$c>= :: Verbosity -> Verbosity -> Bool
> :: Verbosity -> Verbosity -> Bool
$c> :: Verbosity -> Verbosity -> Bool
<= :: Verbosity -> Verbosity -> Bool
$c<= :: Verbosity -> Verbosity -> Bool
< :: Verbosity -> Verbosity -> Bool
$c< :: Verbosity -> Verbosity -> Bool
compare :: Verbosity -> Verbosity -> Ordering
$ccompare :: Verbosity -> Verbosity -> Ordering
Ord,Int -> Verbosity -> ShowS
[Verbosity] -> ShowS
Verbosity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Verbosity] -> ShowS
$cshowList :: [Verbosity] -> ShowS
show :: Verbosity -> String
$cshow :: Verbosity -> String
showsPrec :: Int -> Verbosity -> ShowS
$cshowsPrec :: Int -> Verbosity -> ShowS
Show,ReadPrec [Verbosity]
ReadPrec Verbosity
Int -> ReadS Verbosity
ReadS [Verbosity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Verbosity]
$creadListPrec :: ReadPrec [Verbosity]
readPrec :: ReadPrec Verbosity
$creadPrec :: ReadPrec Verbosity
readList :: ReadS [Verbosity]
$creadList :: ReadS [Verbosity]
readsPrec :: Int -> ReadS Verbosity
$creadsPrec :: Int -> ReadS Verbosity
Read,Typeable,Typeable Verbosity
Verbosity -> DataType
Verbosity -> Constr
(forall b. Data b => b -> b) -> Verbosity -> Verbosity
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Verbosity -> u
forall u. (forall d. Data d => d -> u) -> Verbosity -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Verbosity
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Verbosity -> c Verbosity
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Verbosity)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Verbosity -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Verbosity -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Verbosity -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Verbosity -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
gmapT :: (forall b. Data b => b -> b) -> Verbosity -> Verbosity
$cgmapT :: (forall b. Data b => b -> b) -> Verbosity -> Verbosity
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Verbosity)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Verbosity)
dataTypeOf :: Verbosity -> DataType
$cdataTypeOf :: Verbosity -> DataType
toConstr :: Verbosity -> Constr
$ctoConstr :: Verbosity -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Verbosity
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Verbosity
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Verbosity -> c Verbosity
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Verbosity -> c Verbosity
Data,Int -> Verbosity
Verbosity -> Int
Verbosity -> [Verbosity]
Verbosity -> Verbosity
Verbosity -> Verbosity -> [Verbosity]
Verbosity -> Verbosity -> Verbosity -> [Verbosity]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Verbosity -> Verbosity -> Verbosity -> [Verbosity]
$cenumFromThenTo :: Verbosity -> Verbosity -> Verbosity -> [Verbosity]
enumFromTo :: Verbosity -> Verbosity -> [Verbosity]
$cenumFromTo :: Verbosity -> Verbosity -> [Verbosity]
enumFromThen :: Verbosity -> Verbosity -> [Verbosity]
$cenumFromThen :: Verbosity -> Verbosity -> [Verbosity]
enumFrom :: Verbosity -> [Verbosity]
$cenumFrom :: Verbosity -> [Verbosity]
fromEnum :: Verbosity -> Int
$cfromEnum :: Verbosity -> Int
toEnum :: Int -> Verbosity
$ctoEnum :: Int -> Verbosity
pred :: Verbosity -> Verbosity
$cpred :: Verbosity -> Verbosity
succ :: Verbosity -> Verbosity
$csucc :: Verbosity -> Verbosity
Enum,Verbosity
forall a. a -> a -> Bounded a
maxBound :: Verbosity
$cmaxBound :: Verbosity
minBound :: Verbosity
$cminBound :: Verbosity
Bounded)
shakeRebuildApply :: ShakeOptions -> (FilePath -> Rebuild)
shakeRebuildApply :: ShakeOptions -> String -> Rebuild
shakeRebuildApply ShakeOptions{shakeRebuild :: ShakeOptions -> [(Rebuild, String)]
shakeRebuild=[(Rebuild, String)]
rs}
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Rebuild, String)]
rs = forall a b. a -> b -> a
const Rebuild
RebuildNormal
| Bool
otherwise = \String
x -> forall a. a -> Maybe a -> a
fromMaybe Rebuild
RebuildNormal forall a b. (a -> b) -> a -> b
$ forall a b. (a -> Maybe b) -> [a] -> Maybe b
firstJust (\(Rebuild
r,String -> Bool
pat) -> if String -> Bool
pat String
x then forall a. a -> Maybe a
Just Rebuild
r else forall a. Maybe a
Nothing) [(Rebuild, String -> Bool)]
rs2
where rs2 :: [(Rebuild, String -> Bool)]
rs2 = forall a b. (a -> b) -> [a] -> [b]
map (forall b b' a. (b -> b') -> (a, b) -> (a, b')
second String -> String -> Bool
(?==)) forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse [(Rebuild, String)]
rs
shakeAbbreviationsApply :: ShakeOptions -> String -> String
shakeAbbreviationsApply :: ShakeOptions -> ShowS
shakeAbbreviationsApply ShakeOptions{shakeAbbreviations :: ShakeOptions -> [(String, String)]
shakeAbbreviations=[(String, String)]
abbrev}
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(String, String)]
abbrev = forall a. a -> a
id
| Bool
otherwise = ShowS
f
where
ordAbbrev :: [(String, String)]
ordAbbrev = forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (forall a. Num a => a -> a
negate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Int
length forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) [(String, String)]
abbrev
f :: ShowS
f [] = []
f String
x | (String
to,String
rest):[(String, String)]
_ <- [(String
to,String
rest) | (String
from,String
to) <- [(String, String)]
ordAbbrev, Just String
rest <- [forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix String
from String
x]] = String
to forall a. [a] -> [a] -> [a]
++ ShowS
f String
rest
f (Char
x:String
xs) = Char
x forall a. a -> [a] -> [a]
: ShowS
f String
xs