{-# LANGUAGE DeriveAnyClass             #-}
{-# LANGUAGE DeriveFunctor              #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE DerivingStrategies         #-}
{-# LANGUAGE ExistentialQuantification  #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables        #-}

module Development.IDE.Graph.Internal.Types where

import           Control.Applicative
import           Control.Concurrent.Extra
import           Control.Monad.Catch
-- Needed in GHC 8.6.5
import           Control.Monad.Fail
import           Control.Monad.IO.Class
import           Control.Monad.Trans.Reader
import           Data.Aeson                            (FromJSON, ToJSON)
import qualified Data.ByteString                       as BS
import           Data.Dynamic
import qualified Data.HashMap.Strict                   as Map
import           Data.IORef
import           Data.IntSet                           (IntSet)
import           Data.Maybe
import           Data.Typeable
import           Development.IDE.Graph.Classes
import           Development.IDE.Graph.Internal.Ids
import           Development.IDE.Graph.Internal.Intern
import           GHC.Generics                          (Generic)
import           System.Time.Extra                     (Seconds)


unwrapDynamic :: forall a . Typeable a => Dynamic -> a
unwrapDynamic :: Dynamic -> a
unwrapDynamic Dynamic
x = a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
msg) (Maybe a -> a) -> Maybe a -> a
forall a b. (a -> b) -> a -> b
$ Dynamic -> Maybe a
forall a. Typeable a => Dynamic -> Maybe a
fromDynamic Dynamic
x
    where msg :: [Char]
msg = [Char]
"unwrapDynamic failed: Expected " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ TypeRep -> [Char]
forall a. Show a => a -> [Char]
show (Proxy a -> TypeRep
forall k (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (Proxy a
forall k (t :: k). Proxy t
Proxy :: Proxy a)) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
                [Char]
", but got " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ TypeRep -> [Char]
forall a. Show a => a -> [Char]
show (Dynamic -> TypeRep
dynTypeRep Dynamic
x)

---------------------------------------------------------------------
-- RULES

type TheRules = Map.HashMap TypeRep Dynamic

newtype Rules a = Rules (ReaderT SRules IO a)
    deriving newtype (Applicative Rules
a -> Rules a
Applicative Rules
-> (forall a b. Rules a -> (a -> Rules b) -> Rules b)
-> (forall a b. Rules a -> Rules b -> Rules b)
-> (forall a. a -> Rules a)
-> Monad Rules
Rules a -> (a -> Rules b) -> Rules b
Rules a -> Rules b -> Rules b
forall a. a -> Rules a
forall a b. Rules a -> Rules b -> Rules b
forall a b. Rules a -> (a -> Rules b) -> Rules b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> Rules a
$creturn :: forall a. a -> Rules a
>> :: Rules a -> Rules b -> Rules b
$c>> :: forall a b. Rules a -> Rules b -> Rules b
>>= :: Rules a -> (a -> Rules b) -> Rules b
$c>>= :: forall a b. Rules a -> (a -> Rules b) -> Rules b
$cp1Monad :: Applicative Rules
Monad, Functor Rules
a -> Rules a
Functor Rules
-> (forall a. a -> Rules a)
-> (forall a b. Rules (a -> b) -> Rules a -> Rules b)
-> (forall a b c. (a -> b -> c) -> Rules a -> Rules b -> Rules c)
-> (forall a b. Rules a -> Rules b -> Rules b)
-> (forall a b. Rules a -> Rules b -> Rules a)
-> Applicative Rules
Rules a -> Rules b -> Rules b
Rules a -> Rules b -> Rules a
Rules (a -> b) -> Rules a -> Rules b
(a -> b -> c) -> Rules a -> Rules b -> Rules c
forall a. a -> Rules a
forall a b. Rules a -> Rules b -> Rules a
forall a b. Rules a -> Rules b -> Rules b
forall a b. Rules (a -> b) -> Rules a -> Rules b
forall a b c. (a -> b -> c) -> Rules a -> Rules b -> Rules c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: Rules a -> Rules b -> Rules a
$c<* :: forall a b. Rules a -> Rules b -> Rules a
*> :: Rules a -> Rules b -> Rules b
$c*> :: forall a b. Rules a -> Rules b -> Rules b
liftA2 :: (a -> b -> c) -> Rules a -> Rules b -> Rules c
$cliftA2 :: forall a b c. (a -> b -> c) -> Rules a -> Rules b -> Rules c
<*> :: Rules (a -> b) -> Rules a -> Rules b
$c<*> :: forall a b. Rules (a -> b) -> Rules a -> Rules b
pure :: a -> Rules a
$cpure :: forall a. a -> Rules a
$cp1Applicative :: Functor Rules
Applicative, a -> Rules b -> Rules a
(a -> b) -> Rules a -> Rules b
(forall a b. (a -> b) -> Rules a -> Rules b)
-> (forall a b. a -> Rules b -> Rules a) -> Functor Rules
forall a b. a -> Rules b -> Rules a
forall a b. (a -> b) -> Rules a -> Rules b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Rules b -> Rules a
$c<$ :: forall a b. a -> Rules b -> Rules a
fmap :: (a -> b) -> Rules a -> Rules b
$cfmap :: forall a b. (a -> b) -> Rules a -> Rules b
Functor, Monad Rules
Monad Rules -> (forall a. IO a -> Rules a) -> MonadIO Rules
IO a -> Rules a
forall a. IO a -> Rules a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> Rules a
$cliftIO :: forall a. IO a -> Rules a
$cp1MonadIO :: Monad Rules
MonadIO, Monad Rules
Monad Rules -> (forall a. [Char] -> Rules a) -> MonadFail Rules
[Char] -> Rules a
forall a. [Char] -> Rules a
forall (m :: * -> *).
Monad m -> (forall a. [Char] -> m a) -> MonadFail m
fail :: [Char] -> Rules a
$cfail :: forall a. [Char] -> Rules a
$cp1MonadFail :: Monad Rules
MonadFail)

data SRules = SRules {
    SRules -> Dynamic
rulesExtra   :: !Dynamic,
    SRules -> IORef [Action ()]
rulesActions :: !(IORef [Action ()]),
    SRules -> IORef TheRules
rulesMap     :: !(IORef TheRules)
    }


---------------------------------------------------------------------
-- ACTIONS

newtype Action a = Action {Action a -> ReaderT SAction IO a
fromAction :: ReaderT SAction IO a}
    deriving newtype (Applicative Action
a -> Action a
Applicative Action
-> (forall a b. Action a -> (a -> Action b) -> Action b)
-> (forall a b. Action a -> Action b -> Action b)
-> (forall a. a -> Action a)
-> Monad Action
Action a -> (a -> Action b) -> Action b
Action a -> Action b -> Action b
forall a. a -> Action a
forall a b. Action a -> Action b -> Action b
forall a b. Action a -> (a -> Action b) -> Action b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> Action a
$creturn :: forall a. a -> Action a
>> :: Action a -> Action b -> Action b
$c>> :: forall a b. Action a -> Action b -> Action b
>>= :: Action a -> (a -> Action b) -> Action b
$c>>= :: forall a b. Action a -> (a -> Action b) -> Action b
$cp1Monad :: Applicative Action
Monad, Functor Action
a -> Action a
Functor Action
-> (forall a. a -> Action a)
-> (forall a b. Action (a -> b) -> Action a -> Action b)
-> (forall a b c.
    (a -> b -> c) -> Action a -> Action b -> Action c)
-> (forall a b. Action a -> Action b -> Action b)
-> (forall a b. Action a -> Action b -> Action a)
-> Applicative Action
Action a -> Action b -> Action b
Action a -> Action b -> Action a
Action (a -> b) -> Action a -> Action b
(a -> b -> c) -> Action a -> Action b -> Action c
forall a. a -> Action a
forall a b. Action a -> Action b -> Action a
forall a b. Action a -> Action b -> Action b
forall a b. Action (a -> b) -> Action a -> Action b
forall a b c. (a -> b -> c) -> Action a -> Action b -> Action c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: Action a -> Action b -> Action a
$c<* :: forall a b. Action a -> Action b -> Action a
*> :: Action a -> Action b -> Action b
$c*> :: forall a b. Action a -> Action b -> Action b
liftA2 :: (a -> b -> c) -> Action a -> Action b -> Action c
$cliftA2 :: forall a b c. (a -> b -> c) -> Action a -> Action b -> Action c
<*> :: Action (a -> b) -> Action a -> Action b
$c<*> :: forall a b. Action (a -> b) -> Action a -> Action b
pure :: a -> Action a
$cpure :: forall a. a -> Action a
$cp1Applicative :: Functor Action
Applicative, a -> Action b -> Action a
(a -> b) -> Action a -> Action b
(forall a b. (a -> b) -> Action a -> Action b)
-> (forall a b. a -> Action b -> Action a) -> Functor Action
forall a b. a -> Action b -> Action a
forall a b. (a -> b) -> Action a -> Action b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Action b -> Action a
$c<$ :: forall a b. a -> Action b -> Action a
fmap :: (a -> b) -> Action a -> Action b
$cfmap :: forall a b. (a -> b) -> Action a -> Action b
Functor, Monad Action
Monad Action -> (forall a. IO a -> Action a) -> MonadIO Action
IO a -> Action a
forall a. IO a -> Action a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> Action a
$cliftIO :: forall a. IO a -> Action a
$cp1MonadIO :: Monad Action
MonadIO, Monad Action
Monad Action -> (forall a. [Char] -> Action a) -> MonadFail Action
[Char] -> Action a
forall a. [Char] -> Action a
forall (m :: * -> *).
Monad m -> (forall a. [Char] -> m a) -> MonadFail m
fail :: [Char] -> Action a
$cfail :: forall a. [Char] -> Action a
$cp1MonadFail :: Monad Action
MonadFail, Monad Action
e -> Action a
Monad Action
-> (forall e a. Exception e => e -> Action a) -> MonadThrow Action
forall e a. Exception e => e -> Action a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
throwM :: e -> Action a
$cthrowM :: forall e a. Exception e => e -> Action a
$cp1MonadThrow :: Monad Action
MonadThrow, MonadThrow Action
MonadThrow Action
-> (forall e a.
    Exception e =>
    Action a -> (e -> Action a) -> Action a)
-> MonadCatch Action
Action a -> (e -> Action a) -> Action a
forall e a. Exception e => Action a -> (e -> Action a) -> Action a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
catch :: Action a -> (e -> Action a) -> Action a
$ccatch :: forall e a. Exception e => Action a -> (e -> Action a) -> Action a
$cp1MonadCatch :: MonadThrow Action
MonadCatch, MonadCatch Action
MonadCatch Action
-> (forall b.
    ((forall a. Action a -> Action a) -> Action b) -> Action b)
-> (forall b.
    ((forall a. Action a -> Action a) -> Action b) -> Action b)
-> (forall a b c.
    Action a
    -> (a -> ExitCase b -> Action c)
    -> (a -> Action b)
    -> Action (b, c))
-> MonadMask Action
Action a
-> (a -> ExitCase b -> Action c)
-> (a -> Action b)
-> Action (b, c)
((forall a. Action a -> Action a) -> Action b) -> Action b
((forall a. Action a -> Action a) -> Action b) -> Action b
forall b.
((forall a. Action a -> Action a) -> Action b) -> Action b
forall a b c.
Action a
-> (a -> ExitCase b -> Action c)
-> (a -> Action b)
-> Action (b, c)
forall (m :: * -> *).
MonadCatch m
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
    m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
generalBracket :: Action a
-> (a -> ExitCase b -> Action c)
-> (a -> Action b)
-> Action (b, c)
$cgeneralBracket :: forall a b c.
Action a
-> (a -> ExitCase b -> Action c)
-> (a -> Action b)
-> Action (b, c)
uninterruptibleMask :: ((forall a. Action a -> Action a) -> Action b) -> Action b
$cuninterruptibleMask :: forall b.
((forall a. Action a -> Action a) -> Action b) -> Action b
mask :: ((forall a. Action a -> Action a) -> Action b) -> Action b
$cmask :: forall b.
((forall a. Action a -> Action a) -> Action b) -> Action b
$cp1MonadMask :: MonadCatch Action
MonadMask)

data SAction = SAction {
    SAction -> Database
actionDatabase :: !Database,
    SAction -> IORef ResultDeps
actionDeps     :: !(IORef ResultDeps)
    }

getDatabase :: Action Database
getDatabase :: Action Database
getDatabase = ReaderT SAction IO Database -> Action Database
forall a. ReaderT SAction IO a -> Action a
Action (ReaderT SAction IO Database -> Action Database)
-> ReaderT SAction IO Database -> Action Database
forall a b. (a -> b) -> a -> b
$ (SAction -> Database) -> ReaderT SAction IO Database
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks SAction -> Database
actionDatabase

---------------------------------------------------------------------
-- DATABASE

newtype Step = Step Int
    deriving newtype (Step -> Step -> Bool
(Step -> Step -> Bool) -> (Step -> Step -> Bool) -> Eq Step
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Step -> Step -> Bool
$c/= :: Step -> Step -> Bool
== :: Step -> Step -> Bool
$c== :: Step -> Step -> Bool
Eq,Eq Step
Eq Step
-> (Step -> Step -> Ordering)
-> (Step -> Step -> Bool)
-> (Step -> Step -> Bool)
-> (Step -> Step -> Bool)
-> (Step -> Step -> Bool)
-> (Step -> Step -> Step)
-> (Step -> Step -> Step)
-> Ord Step
Step -> Step -> Bool
Step -> Step -> Ordering
Step -> Step -> Step
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 :: Step -> Step -> Step
$cmin :: Step -> Step -> Step
max :: Step -> Step -> Step
$cmax :: Step -> Step -> Step
>= :: Step -> Step -> Bool
$c>= :: Step -> Step -> Bool
> :: Step -> Step -> Bool
$c> :: Step -> Step -> Bool
<= :: Step -> Step -> Bool
$c<= :: Step -> Step -> Bool
< :: Step -> Step -> Bool
$c< :: Step -> Step -> Bool
compare :: Step -> Step -> Ordering
$ccompare :: Step -> Step -> Ordering
$cp1Ord :: Eq Step
Ord,Eq Step
Eq Step -> (Int -> Step -> Int) -> (Step -> Int) -> Hashable Step
Int -> Step -> Int
Step -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Step -> Int
$chash :: Step -> Int
hashWithSalt :: Int -> Step -> Int
$chashWithSalt :: Int -> Step -> Int
$cp1Hashable :: Eq Step
Hashable)

data Key = forall a . (Typeable a, Eq a, Hashable a, Show a) => Key a

instance Eq Key where
    Key a
a == :: Key -> Key -> Bool
== Key a
b = a -> Maybe a
forall a. a -> Maybe a
Just a
a Maybe a -> Maybe a -> Bool
forall a. Eq a => a -> a -> Bool
== a -> Maybe a
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
b

instance Hashable Key where
    hashWithSalt :: Int -> Key -> Int
hashWithSalt Int
i (Key a
x) = Int -> (TypeRep, a) -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
i (a -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf a
x, a
x)

instance Show Key where
    show :: Key -> [Char]
show (Key a
x) = a -> [Char]
forall a. Show a => a -> [Char]
show a
x

newtype Value = Value Dynamic

data Database = Database {
    Database -> Dynamic
databaseExtra           :: Dynamic,
    Database -> TheRules
databaseRules           :: TheRules,
    Database -> IORef Step
databaseStep            :: !(IORef Step),
    -- Hold the lock while mutating Ids/Values
    Database -> Lock
databaseLock            :: !Lock,
    Database -> IORef (Intern Key)
databaseIds             :: !(IORef (Intern Key)),
    Database -> Ids (Key, Status)
databaseValues          :: !(Ids (Key, Status)),
    Database -> Ids IntSet
databaseReverseDeps     :: !(Ids IntSet),
    Database -> Lock
databaseReverseDepsLock :: !Lock
    }

data Status
    = Clean Result
    | Dirty (Maybe Result)
    | Running (IO ()) Result (Maybe Result)

getResult :: Status -> Maybe Result
getResult :: Status -> Maybe Result
getResult (Clean Result
re)         = Result -> Maybe Result
forall a. a -> Maybe a
Just Result
re
getResult (Dirty Maybe Result
m_re)       = Maybe Result
m_re
getResult (Running IO ()
_ Result
_ Maybe Result
m_re) = Maybe Result
m_re

data Result = Result {
    Result -> Value
resultValue     :: !Value,
    Result -> Step
resultBuilt     :: !Step, -- ^ the step when it was last recomputed
    Result -> Step
resultChanged   :: !Step, -- ^ the step when it last changed
    Result -> Step
resultVisited   :: !Step, -- ^ the step when it was last looked up
    Result -> ResultDeps
resultDeps      :: !ResultDeps,
    Result -> Seconds
resultExecution :: !Seconds, -- ^ How long it took, last time it ran
    Result -> ByteString
resultData      :: BS.ByteString
    }

data ResultDeps = UnknownDeps | AlwaysRerunDeps ![Id] | ResultDeps ![Id]

getResultDepsDefault :: [Id] -> ResultDeps -> [Id]
getResultDepsDefault :: [Int] -> ResultDeps -> [Int]
getResultDepsDefault [Int]
_ (ResultDeps [Int]
ids)      = [Int]
ids
getResultDepsDefault [Int]
_ (AlwaysRerunDeps [Int]
ids) = [Int]
ids
getResultDepsDefault [Int]
def ResultDeps
UnknownDeps         = [Int]
def

mapResultDeps :: ([Id] -> [Id]) -> ResultDeps -> ResultDeps
mapResultDeps :: ([Int] -> [Int]) -> ResultDeps -> ResultDeps
mapResultDeps [Int] -> [Int]
f (ResultDeps [Int]
ids)      = [Int] -> ResultDeps
ResultDeps ([Int] -> ResultDeps) -> [Int] -> ResultDeps
forall a b. (a -> b) -> a -> b
$ [Int] -> [Int]
f [Int]
ids
mapResultDeps [Int] -> [Int]
f (AlwaysRerunDeps [Int]
ids) = [Int] -> ResultDeps
AlwaysRerunDeps ([Int] -> ResultDeps) -> [Int] -> ResultDeps
forall a b. (a -> b) -> a -> b
$ [Int] -> [Int]
f [Int]
ids
mapResultDeps [Int] -> [Int]
_ ResultDeps
UnknownDeps           = ResultDeps
UnknownDeps

instance Semigroup ResultDeps where
    ResultDeps
UnknownDeps <> :: ResultDeps -> ResultDeps -> ResultDeps
<> ResultDeps
x = ResultDeps
x
    ResultDeps
x <> ResultDeps
UnknownDeps = ResultDeps
x
    AlwaysRerunDeps [Int]
ids <> ResultDeps
x = [Int] -> ResultDeps
AlwaysRerunDeps ([Int]
ids [Int] -> [Int] -> [Int]
forall a. Semigroup a => a -> a -> a
<> [Int] -> ResultDeps -> [Int]
getResultDepsDefault [] ResultDeps
x)
    ResultDeps
x <> AlwaysRerunDeps [Int]
ids = [Int] -> ResultDeps
AlwaysRerunDeps ([Int] -> ResultDeps -> [Int]
getResultDepsDefault [] ResultDeps
x [Int] -> [Int] -> [Int]
forall a. Semigroup a => a -> a -> a
<> [Int]
ids)
    ResultDeps [Int]
ids <> ResultDeps [Int]
ids' = [Int] -> ResultDeps
ResultDeps ([Int]
ids [Int] -> [Int] -> [Int]
forall a. Semigroup a => a -> a -> a
<> [Int]
ids')

instance Monoid ResultDeps where
    mempty :: ResultDeps
mempty = ResultDeps
UnknownDeps

---------------------------------------------------------------------
-- Running builds

-- | What mode a rule is running in, passed as an argument to 'BuiltinRun'.
data RunMode
    = RunDependenciesSame -- ^ My dependencies have not changed.
    | RunDependenciesChanged -- ^ At least one of my dependencies from last time have changed, or I have no recorded dependencies.
      deriving (RunMode -> RunMode -> Bool
(RunMode -> RunMode -> Bool)
-> (RunMode -> RunMode -> Bool) -> Eq RunMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RunMode -> RunMode -> Bool
$c/= :: RunMode -> RunMode -> Bool
== :: RunMode -> RunMode -> Bool
$c== :: RunMode -> RunMode -> Bool
Eq,Int -> RunMode -> [Char] -> [Char]
[RunMode] -> [Char] -> [Char]
RunMode -> [Char]
(Int -> RunMode -> [Char] -> [Char])
-> (RunMode -> [Char])
-> ([RunMode] -> [Char] -> [Char])
-> Show RunMode
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
showList :: [RunMode] -> [Char] -> [Char]
$cshowList :: [RunMode] -> [Char] -> [Char]
show :: RunMode -> [Char]
$cshow :: RunMode -> [Char]
showsPrec :: Int -> RunMode -> [Char] -> [Char]
$cshowsPrec :: Int -> RunMode -> [Char] -> [Char]
Show)

instance NFData RunMode where rnf :: RunMode -> ()
rnf RunMode
x = RunMode
x RunMode -> () -> ()
`seq` ()

-- | How the output of a rule has changed.
data RunChanged
    = ChangedNothing -- ^ Nothing has changed.
    | ChangedStore -- ^ The stored value has changed, but in a way that should be considered identical (used rarely).
    | ChangedRecomputeSame -- ^ I recomputed the value and it was the same.
    | ChangedRecomputeDiff -- ^ I recomputed the value and it was different.
      deriving (RunChanged -> RunChanged -> Bool
(RunChanged -> RunChanged -> Bool)
-> (RunChanged -> RunChanged -> Bool) -> Eq RunChanged
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RunChanged -> RunChanged -> Bool
$c/= :: RunChanged -> RunChanged -> Bool
== :: RunChanged -> RunChanged -> Bool
$c== :: RunChanged -> RunChanged -> Bool
Eq,Int -> RunChanged -> [Char] -> [Char]
[RunChanged] -> [Char] -> [Char]
RunChanged -> [Char]
(Int -> RunChanged -> [Char] -> [Char])
-> (RunChanged -> [Char])
-> ([RunChanged] -> [Char] -> [Char])
-> Show RunChanged
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
showList :: [RunChanged] -> [Char] -> [Char]
$cshowList :: [RunChanged] -> [Char] -> [Char]
show :: RunChanged -> [Char]
$cshow :: RunChanged -> [Char]
showsPrec :: Int -> RunChanged -> [Char] -> [Char]
$cshowsPrec :: Int -> RunChanged -> [Char] -> [Char]
Show,(forall x. RunChanged -> Rep RunChanged x)
-> (forall x. Rep RunChanged x -> RunChanged) -> Generic RunChanged
forall x. Rep RunChanged x -> RunChanged
forall x. RunChanged -> Rep RunChanged x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RunChanged x -> RunChanged
$cfrom :: forall x. RunChanged -> Rep RunChanged x
Generic)
      deriving anyclass (Value -> Parser [RunChanged]
Value -> Parser RunChanged
(Value -> Parser RunChanged)
-> (Value -> Parser [RunChanged]) -> FromJSON RunChanged
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [RunChanged]
$cparseJSONList :: Value -> Parser [RunChanged]
parseJSON :: Value -> Parser RunChanged
$cparseJSON :: Value -> Parser RunChanged
FromJSON, [RunChanged] -> Encoding
[RunChanged] -> Value
RunChanged -> Encoding
RunChanged -> Value
(RunChanged -> Value)
-> (RunChanged -> Encoding)
-> ([RunChanged] -> Value)
-> ([RunChanged] -> Encoding)
-> ToJSON RunChanged
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [RunChanged] -> Encoding
$ctoEncodingList :: [RunChanged] -> Encoding
toJSONList :: [RunChanged] -> Value
$ctoJSONList :: [RunChanged] -> Value
toEncoding :: RunChanged -> Encoding
$ctoEncoding :: RunChanged -> Encoding
toJSON :: RunChanged -> Value
$ctoJSON :: RunChanged -> Value
ToJSON)

instance NFData RunChanged where rnf :: RunChanged -> ()
rnf RunChanged
x = RunChanged
x RunChanged -> () -> ()
`seq` ()

-- | The result of 'BuiltinRun'.
data RunResult value = RunResult
    {RunResult value -> RunChanged
runChanged :: RunChanged
        -- ^ How has the 'RunResult' changed from what happened last time.
    ,RunResult value -> ByteString
runStore   :: BS.ByteString
        -- ^ The value to store in the Shake database.
    ,RunResult value -> value
runValue   :: value
        -- ^ The value to return from 'Development.Shake.Rule.apply'.
    } deriving a -> RunResult b -> RunResult a
(a -> b) -> RunResult a -> RunResult b
(forall a b. (a -> b) -> RunResult a -> RunResult b)
-> (forall a b. a -> RunResult b -> RunResult a)
-> Functor RunResult
forall a b. a -> RunResult b -> RunResult a
forall a b. (a -> b) -> RunResult a -> RunResult b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> RunResult b -> RunResult a
$c<$ :: forall a b. a -> RunResult b -> RunResult a
fmap :: (a -> b) -> RunResult a -> RunResult b
$cfmap :: forall a b. (a -> b) -> RunResult a -> RunResult b
Functor

instance NFData value => NFData (RunResult value) where
    rnf :: RunResult value -> ()
rnf (RunResult RunChanged
x1 ByteString
x2 value
x3) = RunChanged -> ()
forall a. NFData a => a -> ()
rnf RunChanged
x1 () -> () -> ()
`seq` ByteString
x2 ByteString -> () -> ()
`seq` value -> ()
forall a. NFData a => a -> ()
rnf value
x3

---------------------------------------------------------------------
-- INSTANCES

instance Semigroup a => Semigroup (Rules a) where
    Rules a
a <> :: Rules a -> Rules a -> Rules a
<> Rules a
b = (a -> a -> a) -> Rules a -> Rules a -> Rules a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>) Rules a
a Rules a
b

instance Monoid a => Monoid (Rules a) where
    mempty :: Rules a
mempty = a -> Rules a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Monoid a => a
mempty