{-# LANGUAGE TemplateHaskell #-}
module Hasura.RQL.Types.Relationships.ToSource
( ToSourceRelationshipDef (..),
tsrdFieldMapping,
tsrdRelationshipType,
tsrdSource,
tsrdTable,
RemoteSourceFieldInfo (..),
)
where
import Control.Lens (makeLenses)
import Data.Aeson
import Data.HashMap.Strict qualified as HM
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.Instances ()
import Hasura.RQL.Types.SourceCustomization
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
showList :: [ToSourceRelationshipDef] -> ShowS
$cshowList :: [ToSourceRelationshipDef] -> ShowS
show :: ToSourceRelationshipDef -> String
$cshow :: ToSourceRelationshipDef -> String
showsPrec :: Int -> ToSourceRelationshipDef -> ShowS
$cshowsPrec :: Int -> ToSourceRelationshipDef -> ShowS
Show, ToSourceRelationshipDef -> ToSourceRelationshipDef -> Bool
(ToSourceRelationshipDef -> ToSourceRelationshipDef -> Bool)
-> (ToSourceRelationshipDef -> ToSourceRelationshipDef -> Bool)
-> Eq ToSourceRelationshipDef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ToSourceRelationshipDef -> ToSourceRelationshipDef -> Bool
$c/= :: ToSourceRelationshipDef -> ToSourceRelationshipDef -> Bool
== :: ToSourceRelationshipDef -> ToSourceRelationshipDef -> Bool
$c== :: 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
$cto :: forall x. Rep ToSourceRelationshipDef x -> ToSourceRelationshipDef
$cfrom :: forall x. ToSourceRelationshipDef -> Rep ToSourceRelationshipDef x
Generic)
instance NFData ToSourceRelationshipDef
instance Cacheable ToSourceRelationshipDef
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
{ RemoteSourceFieldInfo tgt -> RelName
_rsfiName :: RelName,
RemoteSourceFieldInfo tgt -> RelType
_rsfiType :: RelType,
RemoteSourceFieldInfo tgt -> SourceName
_rsfiSource :: SourceName,
RemoteSourceFieldInfo tgt -> SourceConfig tgt
_rsfiSourceConfig :: SourceConfig tgt,
RemoteSourceFieldInfo tgt -> SourceTypeCustomization
_rsfiSourceCustomization :: SourceTypeCustomization,
RemoteSourceFieldInfo tgt -> TableName tgt
_rsfiTable :: TableName tgt,
RemoteSourceFieldInfo tgt
-> HashMap FieldName (ScalarType tgt, Column tgt)
_rsfiMapping :: HM.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
$cto :: forall (tgt :: BackendType) x.
Rep (RemoteSourceFieldInfo tgt) x -> RemoteSourceFieldInfo tgt
$cfrom :: forall (tgt :: BackendType) x.
RemoteSourceFieldInfo tgt -> Rep (RemoteSourceFieldInfo tgt) x
Generic)
deriving instance (Backend tgt) => Eq (RemoteSourceFieldInfo tgt)
instance (Backend tgt) => Cacheable (RemoteSourceFieldInfo tgt)
$(makeLenses ''ToSourceRelationshipDef)