{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveDataTypeable, ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Development.Shake.Internal.Rules.Rerun(
defaultRuleRerun, alwaysRerun
) where
import Development.Shake.Internal.Core.Rules
import Development.Shake.Internal.Core.Types
import Development.Shake.Internal.Core.Build
import Development.Shake.Internal.Core.Action
import Development.Shake.Classes
import qualified Data.ByteString as BS
import General.Binary
newtype AlwaysRerunQ = AlwaysRerunQ ()
deriving (Typeable,AlwaysRerunQ -> AlwaysRerunQ -> Bool
(AlwaysRerunQ -> AlwaysRerunQ -> Bool)
-> (AlwaysRerunQ -> AlwaysRerunQ -> Bool) -> Eq AlwaysRerunQ
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AlwaysRerunQ -> AlwaysRerunQ -> Bool
$c/= :: AlwaysRerunQ -> AlwaysRerunQ -> Bool
== :: AlwaysRerunQ -> AlwaysRerunQ -> Bool
$c== :: AlwaysRerunQ -> AlwaysRerunQ -> Bool
Eq,Int -> AlwaysRerunQ -> Int
AlwaysRerunQ -> Int
(Int -> AlwaysRerunQ -> Int)
-> (AlwaysRerunQ -> Int) -> Hashable AlwaysRerunQ
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: AlwaysRerunQ -> Int
$chash :: AlwaysRerunQ -> Int
hashWithSalt :: Int -> AlwaysRerunQ -> Int
$chashWithSalt :: Int -> AlwaysRerunQ -> Int
Hashable,Get AlwaysRerunQ
[AlwaysRerunQ] -> Put
AlwaysRerunQ -> Put
(AlwaysRerunQ -> Put)
-> Get AlwaysRerunQ
-> ([AlwaysRerunQ] -> Put)
-> Binary AlwaysRerunQ
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [AlwaysRerunQ] -> Put
$cputList :: [AlwaysRerunQ] -> Put
get :: Get AlwaysRerunQ
$cget :: Get AlwaysRerunQ
put :: AlwaysRerunQ -> Put
$cput :: AlwaysRerunQ -> Put
Binary,ByteString -> AlwaysRerunQ
AlwaysRerunQ -> Builder
(AlwaysRerunQ -> Builder)
-> (ByteString -> AlwaysRerunQ) -> BinaryEx AlwaysRerunQ
forall a. (a -> Builder) -> (ByteString -> a) -> BinaryEx a
getEx :: ByteString -> AlwaysRerunQ
$cgetEx :: ByteString -> AlwaysRerunQ
putEx :: AlwaysRerunQ -> Builder
$cputEx :: AlwaysRerunQ -> Builder
BinaryEx,AlwaysRerunQ -> ()
(AlwaysRerunQ -> ()) -> NFData AlwaysRerunQ
forall a. (a -> ()) -> NFData a
rnf :: AlwaysRerunQ -> ()
$crnf :: AlwaysRerunQ -> ()
NFData)
instance Show AlwaysRerunQ where show :: AlwaysRerunQ -> String
show AlwaysRerunQ
_ = String
"alwaysRerun"
type instance RuleResult AlwaysRerunQ = ()
alwaysRerun :: Action ()
alwaysRerun :: Action ()
alwaysRerun = do
Action ()
historyDisable
AlwaysRerunQ -> Action ()
forall key value.
(Partial, RuleResult key ~ value, ShakeValue key,
Typeable value) =>
key -> Action value
apply1 (AlwaysRerunQ -> Action ()) -> AlwaysRerunQ -> Action ()
forall a b. (a -> b) -> a -> b
$ () -> AlwaysRerunQ
AlwaysRerunQ ()
defaultRuleRerun :: Rules ()
defaultRuleRerun :: Rules ()
defaultRuleRerun =
BuiltinLint AlwaysRerunQ ()
-> BuiltinIdentity AlwaysRerunQ ()
-> BuiltinRun AlwaysRerunQ ()
-> Rules ()
forall key value.
(RuleResult key ~ value, ShakeValue key, BinaryEx key,
Typeable value, NFData value, Show value, Partial) =>
BuiltinLint key value
-> BuiltinIdentity key value -> BuiltinRun key value -> Rules ()
addBuiltinRuleEx BuiltinLint AlwaysRerunQ ()
forall key value. BuiltinLint key value
noLint BuiltinIdentity AlwaysRerunQ ()
forall key value. BuiltinIdentity key value
noIdentity (BuiltinRun AlwaysRerunQ () -> Rules ())
-> BuiltinRun AlwaysRerunQ () -> Rules ()
forall a b. (a -> b) -> a -> b
$
\AlwaysRerunQ{} Maybe ByteString
_ RunMode
_ -> RunResult () -> Action (RunResult ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RunResult () -> Action (RunResult ()))
-> RunResult () -> Action (RunResult ())
forall a b. (a -> b) -> a -> b
$ RunChanged -> ByteString -> () -> RunResult ()
forall value. RunChanged -> ByteString -> value -> RunResult value
RunResult RunChanged
ChangedRecomputeDiff ByteString
BS.empty ()