{-# LANGUAGE DataKinds #-} module Cachix.Types.Deploy where import Data.HashMap.Strict import Data.Swagger (ToSchema) import Deriving.Aeson import Protolude data Deploy = Deploy { Deploy -> HashMap Text Text agents :: HashMap Text Text, Deploy -> Maybe (HashMap Text Text) rollbackScript :: Maybe (HashMap Text Text) } deriving (Int -> Deploy -> ShowS [Deploy] -> ShowS Deploy -> String (Int -> Deploy -> ShowS) -> (Deploy -> String) -> ([Deploy] -> ShowS) -> Show Deploy forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Deploy -> ShowS showsPrec :: Int -> Deploy -> ShowS $cshow :: Deploy -> String show :: Deploy -> String $cshowList :: [Deploy] -> ShowS showList :: [Deploy] -> ShowS Show, Deploy -> Deploy -> Bool (Deploy -> Deploy -> Bool) -> (Deploy -> Deploy -> Bool) -> Eq Deploy forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: Deploy -> Deploy -> Bool == :: Deploy -> Deploy -> Bool $c/= :: Deploy -> Deploy -> Bool /= :: Deploy -> Deploy -> Bool Eq, (forall x. Deploy -> Rep Deploy x) -> (forall x. Rep Deploy x -> Deploy) -> Generic Deploy forall x. Rep Deploy x -> Deploy forall x. Deploy -> Rep Deploy x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cfrom :: forall x. Deploy -> Rep Deploy x from :: forall x. Deploy -> Rep Deploy x $cto :: forall x. Rep Deploy x -> Deploy to :: forall x. Rep Deploy x -> Deploy Generic, Maybe Deploy Value -> Parser [Deploy] Value -> Parser Deploy (Value -> Parser Deploy) -> (Value -> Parser [Deploy]) -> Maybe Deploy -> FromJSON Deploy forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> Maybe a -> FromJSON a $cparseJSON :: Value -> Parser Deploy parseJSON :: Value -> Parser Deploy $cparseJSONList :: Value -> Parser [Deploy] parseJSONList :: Value -> Parser [Deploy] $comittedField :: Maybe Deploy omittedField :: Maybe Deploy FromJSON, Proxy Deploy -> Declare (Definitions Schema) NamedSchema (Proxy Deploy -> Declare (Definitions Schema) NamedSchema) -> ToSchema Deploy forall a. (Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a $cdeclareNamedSchema :: Proxy Deploy -> Declare (Definitions Schema) NamedSchema declareNamedSchema :: Proxy Deploy -> Declare (Definitions Schema) NamedSchema ToSchema) deriving ([Deploy] -> Value [Deploy] -> Encoding Deploy -> Bool Deploy -> Value Deploy -> Encoding (Deploy -> Value) -> (Deploy -> Encoding) -> ([Deploy] -> Value) -> ([Deploy] -> Encoding) -> (Deploy -> Bool) -> ToJSON Deploy forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> (a -> Bool) -> ToJSON a $ctoJSON :: Deploy -> Value toJSON :: Deploy -> Value $ctoEncoding :: Deploy -> Encoding toEncoding :: Deploy -> Encoding $ctoJSONList :: [Deploy] -> Value toJSONList :: [Deploy] -> Value $ctoEncodingList :: [Deploy] -> Encoding toEncodingList :: [Deploy] -> Encoding $comitField :: Deploy -> Bool omitField :: Deploy -> Bool ToJSON) via CustomJSON '[OmitNothingFields] Deploy