module Hasura.Metadata.DTO.Metadata (MetadataDTO (..)) where
import Autodocodec
( Autodocodec (Autodocodec),
HasCodec (codec),
dimapCodec,
disjointEitherCodec,
named,
(<?>),
)
import Autodocodec.OpenAPI ()
import Data.Aeson (FromJSON, ToJSON)
import Data.OpenApi qualified as OpenApi
import Hasura.Metadata.DTO.MetadataV1 (MetadataV1)
import Hasura.Metadata.DTO.MetadataV2 (MetadataV2)
import Hasura.Metadata.DTO.MetadataV3 (MetadataV3)
import Hasura.Prelude
data MetadataDTO = V1 MetadataV1 | V2 MetadataV2 | V3 MetadataV3
deriving stock (Int -> MetadataDTO -> ShowS
[MetadataDTO] -> ShowS
MetadataDTO -> String
(Int -> MetadataDTO -> ShowS)
-> (MetadataDTO -> String)
-> ([MetadataDTO] -> ShowS)
-> Show MetadataDTO
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MetadataDTO -> ShowS
showsPrec :: Int -> MetadataDTO -> ShowS
$cshow :: MetadataDTO -> String
show :: MetadataDTO -> String
$cshowList :: [MetadataDTO] -> ShowS
showList :: [MetadataDTO] -> ShowS
Show, MetadataDTO -> MetadataDTO -> Bool
(MetadataDTO -> MetadataDTO -> Bool)
-> (MetadataDTO -> MetadataDTO -> Bool) -> Eq MetadataDTO
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MetadataDTO -> MetadataDTO -> Bool
== :: MetadataDTO -> MetadataDTO -> Bool
$c/= :: MetadataDTO -> MetadataDTO -> Bool
/= :: MetadataDTO -> MetadataDTO -> Bool
Eq, (forall x. MetadataDTO -> Rep MetadataDTO x)
-> (forall x. Rep MetadataDTO x -> MetadataDTO)
-> Generic MetadataDTO
forall x. Rep MetadataDTO x -> MetadataDTO
forall x. MetadataDTO -> Rep MetadataDTO x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MetadataDTO -> Rep MetadataDTO x
from :: forall x. MetadataDTO -> Rep MetadataDTO x
$cto :: forall x. Rep MetadataDTO x -> MetadataDTO
to :: forall x. Rep MetadataDTO x -> MetadataDTO
Generic)
deriving (Value -> Parser [MetadataDTO]
Value -> Parser MetadataDTO
(Value -> Parser MetadataDTO)
-> (Value -> Parser [MetadataDTO]) -> FromJSON MetadataDTO
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser MetadataDTO
parseJSON :: Value -> Parser MetadataDTO
$cparseJSONList :: Value -> Parser [MetadataDTO]
parseJSONList :: Value -> Parser [MetadataDTO]
FromJSON, [MetadataDTO] -> Value
[MetadataDTO] -> Encoding
MetadataDTO -> Value
MetadataDTO -> Encoding
(MetadataDTO -> Value)
-> (MetadataDTO -> Encoding)
-> ([MetadataDTO] -> Value)
-> ([MetadataDTO] -> Encoding)
-> ToJSON MetadataDTO
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: MetadataDTO -> Value
toJSON :: MetadataDTO -> Value
$ctoEncoding :: MetadataDTO -> Encoding
toEncoding :: MetadataDTO -> Encoding
$ctoJSONList :: [MetadataDTO] -> Value
toJSONList :: [MetadataDTO] -> Value
$ctoEncodingList :: [MetadataDTO] -> Encoding
toEncodingList :: [MetadataDTO] -> Encoding
ToJSON, Typeable MetadataDTO
Typeable MetadataDTO
-> (Proxy MetadataDTO -> Declare (Definitions Schema) NamedSchema)
-> ToSchema MetadataDTO
Proxy MetadataDTO -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a
-> (Proxy a -> Declare (Definitions Schema) NamedSchema)
-> ToSchema a
$cdeclareNamedSchema :: Proxy MetadataDTO -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy MetadataDTO -> Declare (Definitions Schema) NamedSchema
OpenApi.ToSchema) via (Autodocodec MetadataDTO)
instance HasCodec MetadataDTO where
codec :: JSONCodec MetadataDTO
codec =
Text -> JSONCodec MetadataDTO -> JSONCodec MetadataDTO
forall input output.
Text -> ValueCodec input output -> ValueCodec input output
named Text
"Metadata"
(JSONCodec MetadataDTO -> JSONCodec MetadataDTO)
-> JSONCodec MetadataDTO -> JSONCodec MetadataDTO
forall a b. (a -> b) -> a -> b
$ (Either MetadataV1 (Either MetadataV2 MetadataV3) -> MetadataDTO)
-> (MetadataDTO
-> Either MetadataV1 (Either MetadataV2 MetadataV3))
-> Codec
Value
(Either MetadataV1 (Either MetadataV2 MetadataV3))
(Either MetadataV1 (Either MetadataV2 MetadataV3))
-> JSONCodec MetadataDTO
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Either MetadataV1 (Either MetadataV2 MetadataV3) -> MetadataDTO
decode MetadataDTO -> Either MetadataV1 (Either MetadataV2 MetadataV3)
encode
(Codec
Value
(Either MetadataV1 (Either MetadataV2 MetadataV3))
(Either MetadataV1 (Either MetadataV2 MetadataV3))
-> JSONCodec MetadataDTO)
-> Codec
Value
(Either MetadataV1 (Either MetadataV2 MetadataV3))
(Either MetadataV1 (Either MetadataV2 MetadataV3))
-> JSONCodec MetadataDTO
forall a b. (a -> b) -> a -> b
$ Codec Value MetadataV1 MetadataV1
-> Codec
Value (Either MetadataV2 MetadataV3) (Either MetadataV2 MetadataV3)
-> Codec
Value
(Either MetadataV1 (Either MetadataV2 MetadataV3))
(Either MetadataV1 (Either MetadataV2 MetadataV3))
forall context input1 output1 input2 output2.
Codec context input1 output1
-> Codec context input2 output2
-> Codec context (Either input1 input2) (Either output1 output2)
disjointEitherCodec
(forall value. HasCodec value => JSONCodec value
codec @MetadataV1)
( Codec Value MetadataV2 MetadataV2
-> Codec Value MetadataV3 MetadataV3
-> Codec
Value (Either MetadataV2 MetadataV3) (Either MetadataV2 MetadataV3)
forall context input1 output1 input2 output2.
Codec context input1 output1
-> Codec context input2 output2
-> Codec context (Either input1 input2) (Either output1 output2)
disjointEitherCodec
(forall value. HasCodec value => JSONCodec value
codec @MetadataV2)
(forall value. HasCodec value => JSONCodec value
codec @MetadataV3)
)
Codec
Value
(Either MetadataV1 (Either MetadataV2 MetadataV3))
(Either MetadataV1 (Either MetadataV2 MetadataV3))
-> Text
-> Codec
Value
(Either MetadataV1 (Either MetadataV2 MetadataV3))
(Either MetadataV1 (Either MetadataV2 MetadataV3))
forall input output.
ValueCodec input output -> Text -> ValueCodec input output
<?> Text
"configuration format for the Hasura GraphQL Engine"
where
decode :: Either MetadataV1 (Either MetadataV2 MetadataV3) -> MetadataDTO
decode = (MetadataV1 -> MetadataDTO)
-> (Either MetadataV2 MetadataV3 -> MetadataDTO)
-> Either MetadataV1 (Either MetadataV2 MetadataV3)
-> MetadataDTO
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either MetadataV1 -> MetadataDTO
V1 ((Either MetadataV2 MetadataV3 -> MetadataDTO)
-> Either MetadataV1 (Either MetadataV2 MetadataV3) -> MetadataDTO)
-> (Either MetadataV2 MetadataV3 -> MetadataDTO)
-> Either MetadataV1 (Either MetadataV2 MetadataV3)
-> MetadataDTO
forall a b. (a -> b) -> a -> b
$ (MetadataV2 -> MetadataDTO)
-> (MetadataV3 -> MetadataDTO)
-> Either MetadataV2 MetadataV3
-> MetadataDTO
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either MetadataV2 -> MetadataDTO
V2 MetadataV3 -> MetadataDTO
V3
encode :: MetadataDTO -> Either MetadataV1 (Either MetadataV2 MetadataV3)
encode = \case
V1 MetadataV1
v1 -> MetadataV1 -> Either MetadataV1 (Either MetadataV2 MetadataV3)
forall a b. a -> Either a b
Left MetadataV1
v1
V2 MetadataV2
v2 -> Either MetadataV2 MetadataV3
-> Either MetadataV1 (Either MetadataV2 MetadataV3)
forall a b. b -> Either a b
Right (Either MetadataV2 MetadataV3
-> Either MetadataV1 (Either MetadataV2 MetadataV3))
-> Either MetadataV2 MetadataV3
-> Either MetadataV1 (Either MetadataV2 MetadataV3)
forall a b. (a -> b) -> a -> b
$ MetadataV2 -> Either MetadataV2 MetadataV3
forall a b. a -> Either a b
Left MetadataV2
v2
V3 MetadataV3
v3 -> Either MetadataV2 MetadataV3
-> Either MetadataV1 (Either MetadataV2 MetadataV3)
forall a b. b -> Either a b
Right (Either MetadataV2 MetadataV3
-> Either MetadataV1 (Either MetadataV2 MetadataV3))
-> Either MetadataV2 MetadataV3
-> Either MetadataV1 (Either MetadataV2 MetadataV3)
forall a b. (a -> b) -> a -> b
$ MetadataV3 -> Either MetadataV2 MetadataV3
forall a b. b -> Either a b
Right MetadataV3
v3