{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DerivingStrategies #-} module Hercules.API.Build.DerivationInfo.DerivationInput where import Data.OpenApi qualified as O3 import Hercules.API.Derivation (DerivationStatus) import Hercules.API.Prelude data DerivationInput = DerivationInput { DerivationInput -> DerivationStatus derivationStatus :: DerivationStatus, DerivationInput -> Text derivationPath :: Text, DerivationInput -> Text outputName :: Text, DerivationInput -> Text outputPath :: Text } deriving ((forall x. DerivationInput -> Rep DerivationInput x) -> (forall x. Rep DerivationInput x -> DerivationInput) -> Generic DerivationInput forall x. Rep DerivationInput x -> DerivationInput forall x. DerivationInput -> Rep DerivationInput x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cfrom :: forall x. DerivationInput -> Rep DerivationInput x from :: forall x. DerivationInput -> Rep DerivationInput x $cto :: forall x. Rep DerivationInput x -> DerivationInput to :: forall x. Rep DerivationInput x -> DerivationInput Generic, Int -> DerivationInput -> ShowS [DerivationInput] -> ShowS DerivationInput -> String (Int -> DerivationInput -> ShowS) -> (DerivationInput -> String) -> ([DerivationInput] -> ShowS) -> Show DerivationInput forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> DerivationInput -> ShowS showsPrec :: Int -> DerivationInput -> ShowS $cshow :: DerivationInput -> String show :: DerivationInput -> String $cshowList :: [DerivationInput] -> ShowS showList :: [DerivationInput] -> ShowS Show, DerivationInput -> DerivationInput -> Bool (DerivationInput -> DerivationInput -> Bool) -> (DerivationInput -> DerivationInput -> Bool) -> Eq DerivationInput forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: DerivationInput -> DerivationInput -> Bool == :: DerivationInput -> DerivationInput -> Bool $c/= :: DerivationInput -> DerivationInput -> Bool /= :: DerivationInput -> DerivationInput -> Bool Eq) deriving anyclass (DerivationInput -> () (DerivationInput -> ()) -> NFData DerivationInput forall a. (a -> ()) -> NFData a $crnf :: DerivationInput -> () rnf :: DerivationInput -> () NFData, [DerivationInput] -> Value [DerivationInput] -> Encoding DerivationInput -> Value DerivationInput -> Encoding (DerivationInput -> Value) -> (DerivationInput -> Encoding) -> ([DerivationInput] -> Value) -> ([DerivationInput] -> Encoding) -> ToJSON DerivationInput forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a $ctoJSON :: DerivationInput -> Value toJSON :: DerivationInput -> Value $ctoEncoding :: DerivationInput -> Encoding toEncoding :: DerivationInput -> Encoding $ctoJSONList :: [DerivationInput] -> Value toJSONList :: [DerivationInput] -> Value $ctoEncodingList :: [DerivationInput] -> Encoding toEncodingList :: [DerivationInput] -> Encoding ToJSON, Value -> Parser [DerivationInput] Value -> Parser DerivationInput (Value -> Parser DerivationInput) -> (Value -> Parser [DerivationInput]) -> FromJSON DerivationInput forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a $cparseJSON :: Value -> Parser DerivationInput parseJSON :: Value -> Parser DerivationInput $cparseJSONList :: Value -> Parser [DerivationInput] parseJSONList :: Value -> Parser [DerivationInput] FromJSON, Proxy DerivationInput -> Declare (Definitions Schema) NamedSchema (Proxy DerivationInput -> Declare (Definitions Schema) NamedSchema) -> ToSchema DerivationInput forall a. (Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a $cdeclareNamedSchema :: Proxy DerivationInput -> Declare (Definitions Schema) NamedSchema declareNamedSchema :: Proxy DerivationInput -> Declare (Definitions Schema) NamedSchema ToSchema, Typeable DerivationInput Typeable DerivationInput => (Proxy DerivationInput -> Declare (Definitions Schema) NamedSchema) -> ToSchema DerivationInput Proxy DerivationInput -> Declare (Definitions Schema) NamedSchema forall a. Typeable a => (Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a $cdeclareNamedSchema :: Proxy DerivationInput -> Declare (Definitions Schema) NamedSchema declareNamedSchema :: Proxy DerivationInput -> Declare (Definitions Schema) NamedSchema O3.ToSchema)