{-# LANGUAGE DeriveAnyClass #-}

module Hercules.API.Agent.Evaluate.EvaluateEvent.PushedAll where

import Hercules.API.Prelude

-- | Indicates that all derivations have been pushed to a cache.
data PushedAll = PushedAll
  { PushedAll -> Text
cache :: Text
  }
  deriving ((forall x. PushedAll -> Rep PushedAll x)
-> (forall x. Rep PushedAll x -> PushedAll) -> Generic PushedAll
forall x. Rep PushedAll x -> PushedAll
forall x. PushedAll -> Rep PushedAll x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PushedAll x -> PushedAll
$cfrom :: forall x. PushedAll -> Rep PushedAll x
Generic, Int -> PushedAll -> ShowS
[PushedAll] -> ShowS
PushedAll -> String
(Int -> PushedAll -> ShowS)
-> (PushedAll -> String)
-> ([PushedAll] -> ShowS)
-> Show PushedAll
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PushedAll] -> ShowS
$cshowList :: [PushedAll] -> ShowS
show :: PushedAll -> String
$cshow :: PushedAll -> String
showsPrec :: Int -> PushedAll -> ShowS
$cshowsPrec :: Int -> PushedAll -> ShowS
Show, PushedAll -> PushedAll -> Bool
(PushedAll -> PushedAll -> Bool)
-> (PushedAll -> PushedAll -> Bool) -> Eq PushedAll
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PushedAll -> PushedAll -> Bool
$c/= :: PushedAll -> PushedAll -> Bool
== :: PushedAll -> PushedAll -> Bool
$c== :: PushedAll -> PushedAll -> Bool
Eq, PushedAll -> ()
(PushedAll -> ()) -> NFData PushedAll
forall a. (a -> ()) -> NFData a
rnf :: PushedAll -> ()
$crnf :: PushedAll -> ()
NFData, [PushedAll] -> Encoding
[PushedAll] -> Value
PushedAll -> Encoding
PushedAll -> Value
(PushedAll -> Value)
-> (PushedAll -> Encoding)
-> ([PushedAll] -> Value)
-> ([PushedAll] -> Encoding)
-> ToJSON PushedAll
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PushedAll] -> Encoding
$ctoEncodingList :: [PushedAll] -> Encoding
toJSONList :: [PushedAll] -> Value
$ctoJSONList :: [PushedAll] -> Value
toEncoding :: PushedAll -> Encoding
$ctoEncoding :: PushedAll -> Encoding
toJSON :: PushedAll -> Value
$ctoJSON :: PushedAll -> Value
ToJSON, Value -> Parser [PushedAll]
Value -> Parser PushedAll
(Value -> Parser PushedAll)
-> (Value -> Parser [PushedAll]) -> FromJSON PushedAll
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PushedAll]
$cparseJSONList :: Value -> Parser [PushedAll]
parseJSON :: Value -> Parser PushedAll
$cparseJSON :: Value -> Parser PushedAll
FromJSON)