{-# LANGUAGE TemplateHaskell #-}
module Hasura.RQL.Types.Relationships.ToSource
( ToSourceRelationshipDef (..),
tsrdFieldMapping,
tsrdRelationshipType,
tsrdSource,
tsrdTable,
RemoteSourceFieldInfo (..),
)
where
import Autodocodec (HasCodec, requiredField')
import Autodocodec qualified as AC
import Control.Lens (makeLenses)
import Data.Aeson
import Data.HashMap.Strict qualified as HashMap
import Hasura.Prelude
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Common
data ToSourceRelationshipDef = ToSourceRelationshipDef
{ ToSourceRelationshipDef -> RelType
_tsrdRelationshipType :: RelType,
ToSourceRelationshipDef -> HashMap FieldName FieldName
_tsrdFieldMapping :: HashMap FieldName FieldName,
ToSourceRelationshipDef -> SourceName
_tsrdSource :: SourceName,
ToSourceRelationshipDef -> Value
_tsrdTable :: Value
}
deriving stock (Int -> ToSourceRelationshipDef -> ShowS
[ToSourceRelationshipDef] -> ShowS
ToSourceRelationshipDef -> String
(Int -> ToSourceRelationshipDef -> ShowS)
-> (ToSourceRelationshipDef -> String)
-> ([ToSourceRelationshipDef] -> ShowS)
-> Show ToSourceRelationshipDef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ToSourceRelationshipDef -> ShowS
showsPrec :: Int -> ToSourceRelationshipDef -> ShowS
$cshow :: ToSourceRelationshipDef -> String
show :: ToSourceRelationshipDef -> String
$cshowList :: [ToSourceRelationshipDef] -> ShowS
showList :: [ToSourceRelationshipDef] -> ShowS
Show, ToSourceRelationshipDef -> ToSourceRelationshipDef -> Bool
(ToSourceRelationshipDef -> ToSourceRelationshipDef -> Bool)
-> (ToSourceRelationshipDef -> ToSourceRelationshipDef -> Bool)
-> Eq ToSourceRelationshipDef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ToSourceRelationshipDef -> ToSourceRelationshipDef -> Bool
== :: ToSourceRelationshipDef -> ToSourceRelationshipDef -> Bool
$c/= :: ToSourceRelationshipDef -> ToSourceRelationshipDef -> Bool
/= :: ToSourceRelationshipDef -> ToSourceRelationshipDef -> Bool
Eq, (forall x.
ToSourceRelationshipDef -> Rep ToSourceRelationshipDef x)
-> (forall x.
Rep ToSourceRelationshipDef x -> ToSourceRelationshipDef)
-> Generic ToSourceRelationshipDef
forall x. Rep ToSourceRelationshipDef x -> ToSourceRelationshipDef
forall x. ToSourceRelationshipDef -> Rep ToSourceRelationshipDef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ToSourceRelationshipDef -> Rep ToSourceRelationshipDef x
from :: forall x. ToSourceRelationshipDef -> Rep ToSourceRelationshipDef x
$cto :: forall x. Rep ToSourceRelationshipDef x -> ToSourceRelationshipDef
to :: forall x. Rep ToSourceRelationshipDef x -> ToSourceRelationshipDef
Generic)
instance NFData ToSourceRelationshipDef
instance HasCodec ToSourceRelationshipDef where
codec :: JSONCodec ToSourceRelationshipDef
codec =
Text
-> ObjectCodec ToSourceRelationshipDef ToSourceRelationshipDef
-> JSONCodec ToSourceRelationshipDef
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object Text
"ToSourceRelationshipDef"
(ObjectCodec ToSourceRelationshipDef ToSourceRelationshipDef
-> JSONCodec ToSourceRelationshipDef)
-> ObjectCodec ToSourceRelationshipDef ToSourceRelationshipDef
-> JSONCodec ToSourceRelationshipDef
forall a b. (a -> b) -> a -> b
$ RelType
-> HashMap FieldName FieldName
-> SourceName
-> Value
-> ToSourceRelationshipDef
ToSourceRelationshipDef
(RelType
-> HashMap FieldName FieldName
-> SourceName
-> Value
-> ToSourceRelationshipDef)
-> Codec Object ToSourceRelationshipDef RelType
-> Codec
Object
ToSourceRelationshipDef
(HashMap FieldName FieldName
-> SourceName -> Value -> ToSourceRelationshipDef)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec RelType RelType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"relationship_type"
ObjectCodec RelType RelType
-> (ToSourceRelationshipDef -> RelType)
-> Codec Object ToSourceRelationshipDef RelType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= ToSourceRelationshipDef -> RelType
_tsrdRelationshipType
Codec
Object
ToSourceRelationshipDef
(HashMap FieldName FieldName
-> SourceName -> Value -> ToSourceRelationshipDef)
-> Codec
Object ToSourceRelationshipDef (HashMap FieldName FieldName)
-> Codec
Object
ToSourceRelationshipDef
(SourceName -> Value -> ToSourceRelationshipDef)
forall a b.
Codec Object ToSourceRelationshipDef (a -> b)
-> Codec Object ToSourceRelationshipDef a
-> Codec Object ToSourceRelationshipDef b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(HashMap FieldName FieldName) (HashMap FieldName FieldName)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"field_mapping"
ObjectCodec
(HashMap FieldName FieldName) (HashMap FieldName FieldName)
-> (ToSourceRelationshipDef -> HashMap FieldName FieldName)
-> Codec
Object ToSourceRelationshipDef (HashMap FieldName FieldName)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= ToSourceRelationshipDef -> HashMap FieldName FieldName
_tsrdFieldMapping
Codec
Object
ToSourceRelationshipDef
(SourceName -> Value -> ToSourceRelationshipDef)
-> Codec Object ToSourceRelationshipDef SourceName
-> Codec
Object ToSourceRelationshipDef (Value -> ToSourceRelationshipDef)
forall a b.
Codec Object ToSourceRelationshipDef (a -> b)
-> Codec Object ToSourceRelationshipDef a
-> Codec Object ToSourceRelationshipDef b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec SourceName SourceName
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"source"
ObjectCodec SourceName SourceName
-> (ToSourceRelationshipDef -> SourceName)
-> Codec Object ToSourceRelationshipDef SourceName
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= ToSourceRelationshipDef -> SourceName
_tsrdSource
Codec
Object ToSourceRelationshipDef (Value -> ToSourceRelationshipDef)
-> Codec Object ToSourceRelationshipDef Value
-> ObjectCodec ToSourceRelationshipDef ToSourceRelationshipDef
forall a b.
Codec Object ToSourceRelationshipDef (a -> b)
-> Codec Object ToSourceRelationshipDef a
-> Codec Object ToSourceRelationshipDef b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Value Value
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"table"
ObjectCodec Value Value
-> (ToSourceRelationshipDef -> Value)
-> Codec Object ToSourceRelationshipDef Value
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= ToSourceRelationshipDef -> Value
_tsrdTable
instance ToJSON ToSourceRelationshipDef where
toJSON :: ToSourceRelationshipDef -> Value
toJSON = Options -> ToSourceRelationshipDef -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON
instance FromJSON ToSourceRelationshipDef where
parseJSON :: Value -> Parser ToSourceRelationshipDef
parseJSON = Options -> Value -> Parser ToSourceRelationshipDef
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON
data RemoteSourceFieldInfo tgt = RemoteSourceFieldInfo
{ forall (tgt :: BackendType). RemoteSourceFieldInfo tgt -> RelName
_rsfiName :: RelName,
forall (tgt :: BackendType). RemoteSourceFieldInfo tgt -> RelType
_rsfiType :: RelType,
forall (tgt :: BackendType).
RemoteSourceFieldInfo tgt -> SourceName
_rsfiSource :: SourceName,
forall (tgt :: BackendType).
RemoteSourceFieldInfo tgt -> SourceConfig tgt
_rsfiSourceConfig :: SourceConfig tgt,
forall (tgt :: BackendType).
RemoteSourceFieldInfo tgt -> TableName tgt
_rsfiTable :: TableName tgt,
forall (tgt :: BackendType).
RemoteSourceFieldInfo tgt
-> HashMap FieldName (ScalarType tgt, Column tgt)
_rsfiMapping :: HashMap.HashMap FieldName (ScalarType tgt, Column tgt)
}
deriving stock ((forall x.
RemoteSourceFieldInfo tgt -> Rep (RemoteSourceFieldInfo tgt) x)
-> (forall x.
Rep (RemoteSourceFieldInfo tgt) x -> RemoteSourceFieldInfo tgt)
-> Generic (RemoteSourceFieldInfo tgt)
forall x.
Rep (RemoteSourceFieldInfo tgt) x -> RemoteSourceFieldInfo tgt
forall x.
RemoteSourceFieldInfo tgt -> Rep (RemoteSourceFieldInfo tgt) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (tgt :: BackendType) x.
Rep (RemoteSourceFieldInfo tgt) x -> RemoteSourceFieldInfo tgt
forall (tgt :: BackendType) x.
RemoteSourceFieldInfo tgt -> Rep (RemoteSourceFieldInfo tgt) x
$cfrom :: forall (tgt :: BackendType) x.
RemoteSourceFieldInfo tgt -> Rep (RemoteSourceFieldInfo tgt) x
from :: forall x.
RemoteSourceFieldInfo tgt -> Rep (RemoteSourceFieldInfo tgt) x
$cto :: forall (tgt :: BackendType) x.
Rep (RemoteSourceFieldInfo tgt) x -> RemoteSourceFieldInfo tgt
to :: forall x.
Rep (RemoteSourceFieldInfo tgt) x -> RemoteSourceFieldInfo tgt
Generic)
deriving instance (Backend tgt) => Eq (RemoteSourceFieldInfo tgt)
$(makeLenses ''ToSourceRelationshipDef)