{-# LANGUAGE DeriveAnyClass #-}

module Hercules.API.Agent.Build.BuildEvent.Pushed where

import Hercules.API.Prelude

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