{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE UndecidableInstances #-}
module Hasura.RQL.Types.Relationships.Remote
( RemoteRelationship,
RemoteRelationshipDefinition (..),
RemoteSourceRelationshipBuilder (..),
parseRemoteRelationshipDefinition,
RRFormat (..),
RRParseMode (..),
_RelationshipToSource,
_RelationshipToSchema,
rrName,
rrDefinition,
RemoteSchemaFieldInfo (..),
RemoteSourceFieldInfo (..),
RemoteFieldInfoRHS (..),
RemoteFieldInfo (..),
DBJoinField (..),
ScalarComputedField (..),
graphQLValueToJSON,
LHSIdentifier (..),
tableNameToLHSIdentifier,
)
where
import Autodocodec (HasCodec (codec), JSONCodec, dimapCodec, disjointEitherCodec, requiredField', requiredFieldWith')
import Autodocodec qualified as AC
import Autodocodec.Extended (hashSetCodec)
import Control.Lens (makePrisms)
import Data.Aeson
import Data.Aeson.Types (Parser)
import Data.HashMap.Strict qualified as HashMap
import Data.Text.Extended (ToTxt (toTxt))
import GHC.TypeLits (ErrorMessage (..), TypeError)
import Hasura.Prelude
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.BackendType
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.ComputedField
import Hasura.RQL.Types.Instances ()
import Hasura.RQL.Types.Relationships.ToSource
import Hasura.RemoteSchema.Metadata
import Hasura.RemoteSchema.SchemaCache.Types
import Hasura.SQL.AnyBackend (AnyBackend)
type RemoteRelationship = RemoteRelationshipG RemoteRelationshipDefinition
instance HasCodec RemoteRelationship where
codec :: JSONCodec RemoteRelationship
codec = JSONCodec RemoteRelationshipDefinition
-> JSONCodec RemoteRelationship
forall definition.
Typeable definition =>
JSONCodec definition -> JSONCodec (RemoteRelationshipG definition)
remoteRelationshipCodec (JSONCodec RemoteRelationshipDefinition
-> JSONCodec RemoteRelationship)
-> JSONCodec RemoteRelationshipDefinition
-> JSONCodec RemoteRelationship
forall a b. (a -> b) -> a -> b
$ RRParseMode -> JSONCodec RemoteRelationshipDefinition
remoteRelationshipDefinitionCodec RRParseMode
RRPLenient
instance FromJSON RemoteRelationship where
parseJSON :: Value -> Parser RemoteRelationship
parseJSON = String
-> (Object -> Parser RemoteRelationship)
-> Value
-> Parser RemoteRelationship
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RemoteRelationship" ((Object -> Parser RemoteRelationship)
-> Value -> Parser RemoteRelationship)
-> (Object -> Parser RemoteRelationship)
-> Value
-> Parser RemoteRelationship
forall a b. (a -> b) -> a -> b
$ \Object
obj ->
RelName -> RemoteRelationshipDefinition -> RemoteRelationship
forall definition.
RelName -> definition -> RemoteRelationshipG definition
RemoteRelationship
(RelName -> RemoteRelationshipDefinition -> RemoteRelationship)
-> Parser RelName
-> Parser (RemoteRelationshipDefinition -> RemoteRelationship)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj
Object -> Key -> Parser RelName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Parser (RemoteRelationshipDefinition -> RemoteRelationship)
-> Parser RemoteRelationshipDefinition -> Parser RemoteRelationship
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (RRParseMode -> Value -> Parser RemoteRelationshipDefinition
parseRemoteRelationshipDefinition RRParseMode
RRPLenient (Value -> Parser RemoteRelationshipDefinition)
-> Parser Value -> Parser RemoteRelationshipDefinition
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
obj Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"definition")
data RRFormat
=
RRFOldDBToRemoteSchema
|
RRFUnifiedFormat
deriving (Int -> RRFormat -> ShowS
[RRFormat] -> ShowS
RRFormat -> String
(Int -> RRFormat -> ShowS)
-> (RRFormat -> String) -> ([RRFormat] -> ShowS) -> Show RRFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RRFormat -> ShowS
showsPrec :: Int -> RRFormat -> ShowS
$cshow :: RRFormat -> String
show :: RRFormat -> String
$cshowList :: [RRFormat] -> ShowS
showList :: [RRFormat] -> ShowS
Show, RRFormat -> RRFormat -> Bool
(RRFormat -> RRFormat -> Bool)
-> (RRFormat -> RRFormat -> Bool) -> Eq RRFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RRFormat -> RRFormat -> Bool
== :: RRFormat -> RRFormat -> Bool
$c/= :: RRFormat -> RRFormat -> Bool
/= :: RRFormat -> RRFormat -> Bool
Eq, (forall x. RRFormat -> Rep RRFormat x)
-> (forall x. Rep RRFormat x -> RRFormat) -> Generic RRFormat
forall x. Rep RRFormat x -> RRFormat
forall x. RRFormat -> Rep RRFormat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RRFormat -> Rep RRFormat x
from :: forall x. RRFormat -> Rep RRFormat x
$cto :: forall x. Rep RRFormat x -> RRFormat
to :: forall x. Rep RRFormat x -> RRFormat
Generic)
data RemoteSourceRelationshipBuilder = IncludeRemoteSourceRelationship | ExcludeRemoteSourceRelationship
data RemoteRelationshipDefinition
=
RelationshipToSource ToSourceRelationshipDef
|
RelationshipToSchema RRFormat ToSchemaRelationshipDef
deriving (Int -> RemoteRelationshipDefinition -> ShowS
[RemoteRelationshipDefinition] -> ShowS
RemoteRelationshipDefinition -> String
(Int -> RemoteRelationshipDefinition -> ShowS)
-> (RemoteRelationshipDefinition -> String)
-> ([RemoteRelationshipDefinition] -> ShowS)
-> Show RemoteRelationshipDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RemoteRelationshipDefinition -> ShowS
showsPrec :: Int -> RemoteRelationshipDefinition -> ShowS
$cshow :: RemoteRelationshipDefinition -> String
show :: RemoteRelationshipDefinition -> String
$cshowList :: [RemoteRelationshipDefinition] -> ShowS
showList :: [RemoteRelationshipDefinition] -> ShowS
Show, RemoteRelationshipDefinition
-> RemoteRelationshipDefinition -> Bool
(RemoteRelationshipDefinition
-> RemoteRelationshipDefinition -> Bool)
-> (RemoteRelationshipDefinition
-> RemoteRelationshipDefinition -> Bool)
-> Eq RemoteRelationshipDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RemoteRelationshipDefinition
-> RemoteRelationshipDefinition -> Bool
== :: RemoteRelationshipDefinition
-> RemoteRelationshipDefinition -> Bool
$c/= :: RemoteRelationshipDefinition
-> RemoteRelationshipDefinition -> Bool
/= :: RemoteRelationshipDefinition
-> RemoteRelationshipDefinition -> Bool
Eq, (forall x.
RemoteRelationshipDefinition -> Rep RemoteRelationshipDefinition x)
-> (forall x.
Rep RemoteRelationshipDefinition x -> RemoteRelationshipDefinition)
-> Generic RemoteRelationshipDefinition
forall x.
Rep RemoteRelationshipDefinition x -> RemoteRelationshipDefinition
forall x.
RemoteRelationshipDefinition -> Rep RemoteRelationshipDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
RemoteRelationshipDefinition -> Rep RemoteRelationshipDefinition x
from :: forall x.
RemoteRelationshipDefinition -> Rep RemoteRelationshipDefinition x
$cto :: forall x.
Rep RemoteRelationshipDefinition x -> RemoteRelationshipDefinition
to :: forall x.
Rep RemoteRelationshipDefinition x -> RemoteRelationshipDefinition
Generic)
instance
( TypeError
( 'ShowType RemoteRelationshipDefinition
':<>: 'Text " has different JSON representations depending on context;"
':$$: 'Text "call ‘parseRemoteRelationshipDefinition’ directly instead of relying on ‘FromJSON’"
)
) =>
FromJSON RemoteRelationshipDefinition
where
parseJSON :: Value -> Parser RemoteRelationshipDefinition
parseJSON = String -> Value -> Parser RemoteRelationshipDefinition
forall a. HasCallStack => String -> a
error String
"impossible"
data RRParseMode
=
RRPLegacy
|
RRPLenient
|
RRPStrict
deriving (Int -> RRParseMode -> ShowS
[RRParseMode] -> ShowS
RRParseMode -> String
(Int -> RRParseMode -> ShowS)
-> (RRParseMode -> String)
-> ([RRParseMode] -> ShowS)
-> Show RRParseMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RRParseMode -> ShowS
showsPrec :: Int -> RRParseMode -> ShowS
$cshow :: RRParseMode -> String
show :: RRParseMode -> String
$cshowList :: [RRParseMode] -> ShowS
showList :: [RRParseMode] -> ShowS
Show, RRParseMode -> RRParseMode -> Bool
(RRParseMode -> RRParseMode -> Bool)
-> (RRParseMode -> RRParseMode -> Bool) -> Eq RRParseMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RRParseMode -> RRParseMode -> Bool
== :: RRParseMode -> RRParseMode -> Bool
$c/= :: RRParseMode -> RRParseMode -> Bool
/= :: RRParseMode -> RRParseMode -> Bool
Eq, (forall x. RRParseMode -> Rep RRParseMode x)
-> (forall x. Rep RRParseMode x -> RRParseMode)
-> Generic RRParseMode
forall x. Rep RRParseMode x -> RRParseMode
forall x. RRParseMode -> Rep RRParseMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RRParseMode -> Rep RRParseMode x
from :: forall x. RRParseMode -> Rep RRParseMode x
$cto :: forall x. Rep RRParseMode x -> RRParseMode
to :: forall x. Rep RRParseMode x -> RRParseMode
Generic)
remoteRelationshipDefinitionCodec :: RRParseMode -> JSONCodec RemoteRelationshipDefinition
remoteRelationshipDefinitionCodec :: RRParseMode -> JSONCodec RemoteRelationshipDefinition
remoteRelationshipDefinitionCodec RRParseMode
mode =
(Either ToSourceRelationshipDef (RRFormat, ToSchemaRelationshipDef)
-> RemoteRelationshipDefinition)
-> (RemoteRelationshipDefinition
-> Either
ToSourceRelationshipDef (RRFormat, ToSchemaRelationshipDef))
-> Codec
Value
(Either
ToSourceRelationshipDef (RRFormat, ToSchemaRelationshipDef))
(Either
ToSourceRelationshipDef (RRFormat, ToSchemaRelationshipDef))
-> JSONCodec RemoteRelationshipDefinition
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec
((ToSourceRelationshipDef -> RemoteRelationshipDefinition)
-> ((RRFormat, ToSchemaRelationshipDef)
-> RemoteRelationshipDefinition)
-> Either
ToSourceRelationshipDef (RRFormat, ToSchemaRelationshipDef)
-> RemoteRelationshipDefinition
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ToSourceRelationshipDef -> RemoteRelationshipDefinition
RelationshipToSource ((RRFormat
-> ToSchemaRelationshipDef -> RemoteRelationshipDefinition)
-> (RRFormat, ToSchemaRelationshipDef)
-> RemoteRelationshipDefinition
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry RRFormat -> ToSchemaRelationshipDef -> RemoteRelationshipDefinition
RelationshipToSchema))
( \case
RelationshipToSource ToSourceRelationshipDef
source -> ToSourceRelationshipDef
-> Either
ToSourceRelationshipDef (RRFormat, ToSchemaRelationshipDef)
forall a b. a -> Either a b
Left ToSourceRelationshipDef
source
RelationshipToSchema RRFormat
format ToSchemaRelationshipDef
schema -> (RRFormat, ToSchemaRelationshipDef)
-> Either
ToSourceRelationshipDef (RRFormat, ToSchemaRelationshipDef)
forall a b. b -> Either a b
Right (RRFormat
format, ToSchemaRelationshipDef
schema)
)
(Codec
Value
(Either
ToSourceRelationshipDef (RRFormat, ToSchemaRelationshipDef))
(Either
ToSourceRelationshipDef (RRFormat, ToSchemaRelationshipDef))
-> JSONCodec RemoteRelationshipDefinition)
-> Codec
Value
(Either
ToSourceRelationshipDef (RRFormat, ToSchemaRelationshipDef))
(Either
ToSourceRelationshipDef (RRFormat, ToSchemaRelationshipDef))
-> JSONCodec RemoteRelationshipDefinition
forall a b. (a -> b) -> a -> b
$ Codec Value ToSourceRelationshipDef ToSourceRelationshipDef
-> Codec
Value
(RRFormat, ToSchemaRelationshipDef)
(RRFormat, ToSchemaRelationshipDef)
-> Codec
Value
(Either
ToSourceRelationshipDef (RRFormat, ToSchemaRelationshipDef))
(Either
ToSourceRelationshipDef (RRFormat, ToSchemaRelationshipDef))
forall context input1 output1 input2 output2.
Codec context input1 output1
-> Codec context input2 output2
-> Codec context (Either input1 input2) (Either output1 output2)
disjointEitherCodec Codec Value ToSourceRelationshipDef ToSourceRelationshipDef
toSource Codec
Value
(RRFormat, ToSchemaRelationshipDef)
(RRFormat, ToSchemaRelationshipDef)
toSchema
where
toSource :: Codec Value ToSourceRelationshipDef ToSourceRelationshipDef
toSource = Text
-> ObjectCodec ToSourceRelationshipDef ToSourceRelationshipDef
-> Codec Value ToSourceRelationshipDef ToSourceRelationshipDef
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object Text
"RelationshipToSource" (ObjectCodec ToSourceRelationshipDef ToSourceRelationshipDef
-> Codec Value ToSourceRelationshipDef ToSourceRelationshipDef)
-> ObjectCodec ToSourceRelationshipDef ToSourceRelationshipDef
-> Codec Value ToSourceRelationshipDef ToSourceRelationshipDef
forall a b. (a -> b) -> a -> b
$ Text -> ObjectCodec ToSourceRelationshipDef ToSourceRelationshipDef
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"to_source"
toSchema :: JSONCodec (RRFormat, ToSchemaRelationshipDef)
toSchema :: Codec
Value
(RRFormat, ToSchemaRelationshipDef)
(RRFormat, ToSchemaRelationshipDef)
toSchema = case RRParseMode
mode of
RRParseMode
RRPLegacy -> (ToSchemaRelationshipDef -> (RRFormat, ToSchemaRelationshipDef))
-> ((RRFormat, ToSchemaRelationshipDef) -> ToSchemaRelationshipDef)
-> Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef
-> Codec
Value
(RRFormat, ToSchemaRelationshipDef)
(RRFormat, ToSchemaRelationshipDef)
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec (RRFormat
RRFOldDBToRemoteSchema,) (RRFormat, ToSchemaRelationshipDef) -> ToSchemaRelationshipDef
forall a b. (a, b) -> b
snd Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef
toSchemaOldDBFormat
RRParseMode
RRPStrict -> (ToSchemaRelationshipDef -> (RRFormat, ToSchemaRelationshipDef))
-> ((RRFormat, ToSchemaRelationshipDef) -> ToSchemaRelationshipDef)
-> Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef
-> Codec
Value
(RRFormat, ToSchemaRelationshipDef)
(RRFormat, ToSchemaRelationshipDef)
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec (RRFormat
RRFUnifiedFormat,) (RRFormat, ToSchemaRelationshipDef) -> ToSchemaRelationshipDef
forall a b. (a, b) -> b
snd Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef
toSchemaUnified
RRParseMode
RRPLenient ->
(Either ToSchemaRelationshipDef ToSchemaRelationshipDef
-> (RRFormat, ToSchemaRelationshipDef))
-> ((RRFormat, ToSchemaRelationshipDef)
-> Either ToSchemaRelationshipDef ToSchemaRelationshipDef)
-> Codec
Value
(Either ToSchemaRelationshipDef ToSchemaRelationshipDef)
(Either ToSchemaRelationshipDef ToSchemaRelationshipDef)
-> Codec
Value
(RRFormat, ToSchemaRelationshipDef)
(RRFormat, ToSchemaRelationshipDef)
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec
((ToSchemaRelationshipDef -> (RRFormat, ToSchemaRelationshipDef))
-> (ToSchemaRelationshipDef -> (RRFormat, ToSchemaRelationshipDef))
-> Either ToSchemaRelationshipDef ToSchemaRelationshipDef
-> (RRFormat, ToSchemaRelationshipDef)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (RRFormat
RRFUnifiedFormat,) (RRFormat
RRFOldDBToRemoteSchema,))
( \case
(RRFormat
RRFUnifiedFormat, ToSchemaRelationshipDef
l) -> ToSchemaRelationshipDef
-> Either ToSchemaRelationshipDef ToSchemaRelationshipDef
forall a b. a -> Either a b
Left ToSchemaRelationshipDef
l
(RRFormat
RRFOldDBToRemoteSchema, ToSchemaRelationshipDef
r) -> ToSchemaRelationshipDef
-> Either ToSchemaRelationshipDef ToSchemaRelationshipDef
forall a b. b -> Either a b
Right ToSchemaRelationshipDef
r
)
(Codec
Value
(Either ToSchemaRelationshipDef ToSchemaRelationshipDef)
(Either ToSchemaRelationshipDef ToSchemaRelationshipDef)
-> Codec
Value
(RRFormat, ToSchemaRelationshipDef)
(RRFormat, ToSchemaRelationshipDef))
-> Codec
Value
(Either ToSchemaRelationshipDef ToSchemaRelationshipDef)
(Either ToSchemaRelationshipDef ToSchemaRelationshipDef)
-> Codec
Value
(RRFormat, ToSchemaRelationshipDef)
(RRFormat, ToSchemaRelationshipDef)
forall a b. (a -> b) -> a -> b
$ Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef
-> Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef
-> Codec
Value
(Either ToSchemaRelationshipDef ToSchemaRelationshipDef)
(Either ToSchemaRelationshipDef ToSchemaRelationshipDef)
forall context input1 output1 input2 output2.
Codec context input1 output1
-> Codec context input2 output2
-> Codec context (Either input1 input2) (Either output1 output2)
disjointEitherCodec Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef
toSchemaUnified Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef
toSchemaOldDBFormat
toSchemaUnified :: JSONCodec ToSchemaRelationshipDef
toSchemaUnified :: Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef
toSchemaUnified = Text
-> ObjectCodec ToSchemaRelationshipDef ToSchemaRelationshipDef
-> Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object Text
"RelationshipToSchema" (ObjectCodec ToSchemaRelationshipDef ToSchemaRelationshipDef
-> Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef)
-> ObjectCodec ToSchemaRelationshipDef ToSchemaRelationshipDef
-> Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef
forall a b. (a -> b) -> a -> b
$ Text -> ObjectCodec ToSchemaRelationshipDef ToSchemaRelationshipDef
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"to_remote_schema"
toSchemaOldDBFormat :: JSONCodec ToSchemaRelationshipDef
toSchemaOldDBFormat :: Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef
toSchemaOldDBFormat =
Text
-> ObjectCodec ToSchemaRelationshipDef ToSchemaRelationshipDef
-> Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object Text
"ToSchemaRelationshipDefLegacyFormat"
(ObjectCodec ToSchemaRelationshipDef ToSchemaRelationshipDef
-> Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef)
-> ObjectCodec ToSchemaRelationshipDef ToSchemaRelationshipDef
-> Codec Value ToSchemaRelationshipDef ToSchemaRelationshipDef
forall a b. (a -> b) -> a -> b
$ RemoteSchemaName
-> HashSet FieldName -> RemoteFields -> ToSchemaRelationshipDef
ToSchemaRelationshipDef
(RemoteSchemaName
-> HashSet FieldName -> RemoteFields -> ToSchemaRelationshipDef)
-> Codec Object ToSchemaRelationshipDef RemoteSchemaName
-> Codec
Object
ToSchemaRelationshipDef
(HashSet FieldName -> RemoteFields -> ToSchemaRelationshipDef)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec RemoteSchemaName RemoteSchemaName
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"remote_schema"
ObjectCodec RemoteSchemaName RemoteSchemaName
-> (ToSchemaRelationshipDef -> RemoteSchemaName)
-> Codec Object ToSchemaRelationshipDef RemoteSchemaName
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= ToSchemaRelationshipDef -> RemoteSchemaName
_trrdRemoteSchema
Codec
Object
ToSchemaRelationshipDef
(HashSet FieldName -> RemoteFields -> ToSchemaRelationshipDef)
-> Codec Object ToSchemaRelationshipDef (HashSet FieldName)
-> Codec
Object
ToSchemaRelationshipDef
(RemoteFields -> ToSchemaRelationshipDef)
forall a b.
Codec Object ToSchemaRelationshipDef (a -> b)
-> Codec Object ToSchemaRelationshipDef a
-> Codec Object ToSchemaRelationshipDef b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ValueCodec (HashSet FieldName) (HashSet FieldName)
-> ObjectCodec (HashSet FieldName) (HashSet FieldName)
forall input output.
Text -> ValueCodec input output -> ObjectCodec input output
requiredFieldWith' Text
"hasura_fields" ValueCodec (HashSet FieldName) (HashSet FieldName)
forall a. (Hashable a, HasCodec a) => JSONCodec (HashSet a)
hashSetCodec
ObjectCodec (HashSet FieldName) (HashSet FieldName)
-> (ToSchemaRelationshipDef -> HashSet FieldName)
-> Codec Object ToSchemaRelationshipDef (HashSet FieldName)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= ToSchemaRelationshipDef -> HashSet FieldName
_trrdLhsFields
Codec
Object
ToSchemaRelationshipDef
(RemoteFields -> ToSchemaRelationshipDef)
-> Codec Object ToSchemaRelationshipDef RemoteFields
-> ObjectCodec ToSchemaRelationshipDef ToSchemaRelationshipDef
forall a b.
Codec Object ToSchemaRelationshipDef (a -> b)
-> Codec Object ToSchemaRelationshipDef a
-> Codec Object ToSchemaRelationshipDef b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec RemoteFields RemoteFields
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"remote_field"
ObjectCodec RemoteFields RemoteFields
-> (ToSchemaRelationshipDef -> RemoteFields)
-> Codec Object ToSchemaRelationshipDef RemoteFields
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= ToSchemaRelationshipDef -> RemoteFields
_trrdRemoteField
parseRemoteRelationshipDefinition :: RRParseMode -> Value -> Parser RemoteRelationshipDefinition
parseRemoteRelationshipDefinition :: RRParseMode -> Value -> Parser RemoteRelationshipDefinition
parseRemoteRelationshipDefinition RRParseMode
mode = String
-> (Object -> Parser RemoteRelationshipDefinition)
-> Value
-> Parser RemoteRelationshipDefinition
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject (String
"RemoteRelationshipDefinition " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
suffix) \Object
obj -> do
Maybe RemoteSchemaName
remoteSchema <- Object
obj Object -> Key -> Parser (Maybe RemoteSchemaName)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"remote_schema"
case (Maybe RemoteSchemaName
remoteSchema, RRParseMode
mode) of
(Just {}, RRParseMode
RRPStrict) -> Parser RemoteRelationshipDefinition
invalid
(Just RemoteSchemaName
schema, RRParseMode
_) -> do
HashSet FieldName
hasuraFields <- Object
obj Object -> Key -> Parser (HashSet FieldName)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"hasura_fields"
RemoteFields
remoteField <- Object
obj Object -> Key -> Parser RemoteFields
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"remote_field"
RemoteRelationshipDefinition -> Parser RemoteRelationshipDefinition
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RemoteRelationshipDefinition
-> Parser RemoteRelationshipDefinition)
-> RemoteRelationshipDefinition
-> Parser RemoteRelationshipDefinition
forall a b. (a -> b) -> a -> b
$ RRFormat -> ToSchemaRelationshipDef -> RemoteRelationshipDefinition
RelationshipToSchema RRFormat
RRFOldDBToRemoteSchema (ToSchemaRelationshipDef -> RemoteRelationshipDefinition)
-> ToSchemaRelationshipDef -> RemoteRelationshipDefinition
forall a b. (a -> b) -> a -> b
$ RemoteSchemaName
-> HashSet FieldName -> RemoteFields -> ToSchemaRelationshipDef
ToSchemaRelationshipDef RemoteSchemaName
schema HashSet FieldName
hasuraFields RemoteFields
remoteField
(Maybe RemoteSchemaName
Nothing, RRParseMode
RRPLegacy) -> Parser RemoteRelationshipDefinition
invalid
(Maybe RemoteSchemaName
Nothing, RRParseMode
_) -> do
Maybe Value
toSource <- Object
obj Object -> Key -> Parser (Maybe Value)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"to_source"
Maybe Value
toSchema <- Object
obj Object -> Key -> Parser (Maybe Value)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"to_remote_schema"
case (Maybe Value
toSchema, Maybe Value
toSource) of
(Just Value
schema, Maybe Value
Nothing) -> RRFormat -> ToSchemaRelationshipDef -> RemoteRelationshipDefinition
RelationshipToSchema RRFormat
RRFUnifiedFormat (ToSchemaRelationshipDef -> RemoteRelationshipDefinition)
-> Parser ToSchemaRelationshipDef
-> Parser RemoteRelationshipDefinition
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser ToSchemaRelationshipDef
forall a. FromJSON a => Value -> Parser a
parseJSON Value
schema
(Maybe Value
Nothing, Just Value
source) -> ToSourceRelationshipDef -> RemoteRelationshipDefinition
RelationshipToSource (ToSourceRelationshipDef -> RemoteRelationshipDefinition)
-> Parser ToSourceRelationshipDef
-> Parser RemoteRelationshipDefinition
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser ToSourceRelationshipDef
forall a. FromJSON a => Value -> Parser a
parseJSON Value
source
(Maybe Value, Maybe Value)
_ -> Parser RemoteRelationshipDefinition
invalid
where
(String
suffix, String
expected) = case RRParseMode
mode of
RRParseMode
RRPLegacy -> (String
"(legacy format)", String
"remote_schema")
RRParseMode
RRPLenient -> (String
"(lenient format)", String
"remote_schema, to_source, to_remote_schema")
RRParseMode
RRPStrict -> (String
"(strict format)", String
"to_source, to_remote_schema")
invalid :: Parser RemoteRelationshipDefinition
invalid =
String -> Parser RemoteRelationshipDefinition
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
(String -> Parser RemoteRelationshipDefinition)
-> String -> Parser RemoteRelationshipDefinition
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"remote relationship definition ",
String
suffix,
String
" expects exactly one of: ",
String
expected
]
instance ToJSON RemoteRelationshipDefinition where
toJSON :: RemoteRelationshipDefinition -> Value
toJSON = \case
RelationshipToSource ToSourceRelationshipDef
source -> [Pair] -> Value
object [Key
"to_source" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ToSourceRelationshipDef -> Value
forall a. ToJSON a => a -> Value
toJSON ToSourceRelationshipDef
source]
RelationshipToSchema RRFormat
format schema :: ToSchemaRelationshipDef
schema@ToSchemaRelationshipDef {HashSet FieldName
RemoteSchemaName
RemoteFields
_trrdRemoteSchema :: ToSchemaRelationshipDef -> RemoteSchemaName
_trrdLhsFields :: ToSchemaRelationshipDef -> HashSet FieldName
_trrdRemoteField :: ToSchemaRelationshipDef -> RemoteFields
_trrdRemoteSchema :: RemoteSchemaName
_trrdLhsFields :: HashSet FieldName
_trrdRemoteField :: RemoteFields
..} -> case RRFormat
format of
RRFormat
RRFUnifiedFormat -> [Pair] -> Value
object [Key
"to_remote_schema" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ToSchemaRelationshipDef -> Value
forall a. ToJSON a => a -> Value
toJSON ToSchemaRelationshipDef
schema]
RRFormat
RRFOldDBToRemoteSchema ->
[Pair] -> Value
object
[ Key
"remote_schema" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= RemoteSchemaName -> Value
forall a. ToJSON a => a -> Value
toJSON RemoteSchemaName
_trrdRemoteSchema,
Key
"hasura_fields" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= HashSet FieldName -> Value
forall a. ToJSON a => a -> Value
toJSON HashSet FieldName
_trrdLhsFields,
Key
"remote_field" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= RemoteFields -> Value
forall a. ToJSON a => a -> Value
toJSON RemoteFields
_trrdRemoteField
]
data RemoteFieldInfo lhsJoinField = RemoteFieldInfo
{ forall lhsJoinField.
RemoteFieldInfo lhsJoinField -> HashMap FieldName lhsJoinField
_rfiLHS :: HashMap.HashMap FieldName lhsJoinField,
forall lhsJoinField.
RemoteFieldInfo lhsJoinField -> RemoteFieldInfoRHS
_rfiRHS :: RemoteFieldInfoRHS
}
deriving ((forall x.
RemoteFieldInfo lhsJoinField
-> Rep (RemoteFieldInfo lhsJoinField) x)
-> (forall x.
Rep (RemoteFieldInfo lhsJoinField) x
-> RemoteFieldInfo lhsJoinField)
-> Generic (RemoteFieldInfo lhsJoinField)
forall x.
Rep (RemoteFieldInfo lhsJoinField) x
-> RemoteFieldInfo lhsJoinField
forall x.
RemoteFieldInfo lhsJoinField
-> Rep (RemoteFieldInfo lhsJoinField) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall lhsJoinField x.
Rep (RemoteFieldInfo lhsJoinField) x
-> RemoteFieldInfo lhsJoinField
forall lhsJoinField x.
RemoteFieldInfo lhsJoinField
-> Rep (RemoteFieldInfo lhsJoinField) x
$cfrom :: forall lhsJoinField x.
RemoteFieldInfo lhsJoinField
-> Rep (RemoteFieldInfo lhsJoinField) x
from :: forall x.
RemoteFieldInfo lhsJoinField
-> Rep (RemoteFieldInfo lhsJoinField) x
$cto :: forall lhsJoinField x.
Rep (RemoteFieldInfo lhsJoinField) x
-> RemoteFieldInfo lhsJoinField
to :: forall x.
Rep (RemoteFieldInfo lhsJoinField) x
-> RemoteFieldInfo lhsJoinField
Generic, RemoteFieldInfo lhsJoinField
-> RemoteFieldInfo lhsJoinField -> Bool
(RemoteFieldInfo lhsJoinField
-> RemoteFieldInfo lhsJoinField -> Bool)
-> (RemoteFieldInfo lhsJoinField
-> RemoteFieldInfo lhsJoinField -> Bool)
-> Eq (RemoteFieldInfo lhsJoinField)
forall lhsJoinField.
Eq lhsJoinField =>
RemoteFieldInfo lhsJoinField
-> RemoteFieldInfo lhsJoinField -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall lhsJoinField.
Eq lhsJoinField =>
RemoteFieldInfo lhsJoinField
-> RemoteFieldInfo lhsJoinField -> Bool
== :: RemoteFieldInfo lhsJoinField
-> RemoteFieldInfo lhsJoinField -> Bool
$c/= :: forall lhsJoinField.
Eq lhsJoinField =>
RemoteFieldInfo lhsJoinField
-> RemoteFieldInfo lhsJoinField -> Bool
/= :: RemoteFieldInfo lhsJoinField
-> RemoteFieldInfo lhsJoinField -> Bool
Eq)
instance (ToJSON lhsJoinField) => ToJSON (RemoteFieldInfo lhsJoinField)
data RemoteFieldInfoRHS
= RFISchema RemoteSchemaFieldInfo
| RFISource (AnyBackend RemoteSourceFieldInfo)
deriving ((forall x. RemoteFieldInfoRHS -> Rep RemoteFieldInfoRHS x)
-> (forall x. Rep RemoteFieldInfoRHS x -> RemoteFieldInfoRHS)
-> Generic RemoteFieldInfoRHS
forall x. Rep RemoteFieldInfoRHS x -> RemoteFieldInfoRHS
forall x. RemoteFieldInfoRHS -> Rep RemoteFieldInfoRHS x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RemoteFieldInfoRHS -> Rep RemoteFieldInfoRHS x
from :: forall x. RemoteFieldInfoRHS -> Rep RemoteFieldInfoRHS x
$cto :: forall x. Rep RemoteFieldInfoRHS x -> RemoteFieldInfoRHS
to :: forall x. Rep RemoteFieldInfoRHS x -> RemoteFieldInfoRHS
Generic, RemoteFieldInfoRHS -> RemoteFieldInfoRHS -> Bool
(RemoteFieldInfoRHS -> RemoteFieldInfoRHS -> Bool)
-> (RemoteFieldInfoRHS -> RemoteFieldInfoRHS -> Bool)
-> Eq RemoteFieldInfoRHS
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RemoteFieldInfoRHS -> RemoteFieldInfoRHS -> Bool
== :: RemoteFieldInfoRHS -> RemoteFieldInfoRHS -> Bool
$c/= :: RemoteFieldInfoRHS -> RemoteFieldInfoRHS -> Bool
/= :: RemoteFieldInfoRHS -> RemoteFieldInfoRHS -> Bool
Eq)
instance ToJSON RemoteFieldInfoRHS where
toJSON :: RemoteFieldInfoRHS -> Value
toJSON =
\case
RFISchema RemoteSchemaFieldInfo
schema -> RemoteSchemaFieldInfo -> Value
forall a. ToJSON a => a -> Value
toJSON RemoteSchemaFieldInfo
schema
RFISource AnyBackend RemoteSourceFieldInfo
_ -> () -> Value
forall a. ToJSON a => a -> Value
toJSON ()
data DBJoinField (b :: BackendType)
= JoinColumn (Column b) (ColumnType b)
| JoinComputedField (ScalarComputedField b)
deriving ((forall x. DBJoinField b -> Rep (DBJoinField b) x)
-> (forall x. Rep (DBJoinField b) x -> DBJoinField b)
-> Generic (DBJoinField b)
forall x. Rep (DBJoinField b) x -> DBJoinField b
forall x. DBJoinField b -> Rep (DBJoinField b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x. Rep (DBJoinField b) x -> DBJoinField b
forall (b :: BackendType) x. DBJoinField b -> Rep (DBJoinField b) x
$cfrom :: forall (b :: BackendType) x. DBJoinField b -> Rep (DBJoinField b) x
from :: forall x. DBJoinField b -> Rep (DBJoinField b) x
$cto :: forall (b :: BackendType) x. Rep (DBJoinField b) x -> DBJoinField b
to :: forall x. Rep (DBJoinField b) x -> DBJoinField b
Generic)
deriving instance (Backend b) => Eq (DBJoinField b)
deriving instance (Backend b) => Show (DBJoinField b)
instance (Backend b) => Hashable (DBJoinField b)
instance (Backend b) => ToJSON (DBJoinField b) where
toJSON :: DBJoinField b -> Value
toJSON = \case
JoinColumn Column b
column ColumnType b
columnType -> (Column b, ColumnType b) -> Value
forall a. ToJSON a => a -> Value
toJSON (Column b
column, ColumnType b
columnType)
JoinComputedField ScalarComputedField b
computedField -> ScalarComputedField b -> Value
forall a. ToJSON a => a -> Value
toJSON ScalarComputedField b
computedField
data ScalarComputedField (b :: BackendType) = ScalarComputedField
{ forall (b :: BackendType).
ScalarComputedField b -> XComputedField b
_scfXField :: XComputedField b,
forall (b :: BackendType).
ScalarComputedField b -> ComputedFieldName
_scfName :: ComputedFieldName,
forall (b :: BackendType). ScalarComputedField b -> FunctionName b
_scfFunction :: FunctionName b,
forall (b :: BackendType).
ScalarComputedField b -> ComputedFieldImplicitArguments b
_scfComputedFieldImplicitArgs :: ComputedFieldImplicitArguments b,
forall (b :: BackendType). ScalarComputedField b -> ScalarType b
_scfType :: ScalarType b
}
deriving ((forall x. ScalarComputedField b -> Rep (ScalarComputedField b) x)
-> (forall x.
Rep (ScalarComputedField b) x -> ScalarComputedField b)
-> Generic (ScalarComputedField b)
forall x. Rep (ScalarComputedField b) x -> ScalarComputedField b
forall x. ScalarComputedField b -> Rep (ScalarComputedField b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x.
Rep (ScalarComputedField b) x -> ScalarComputedField b
forall (b :: BackendType) x.
ScalarComputedField b -> Rep (ScalarComputedField b) x
$cfrom :: forall (b :: BackendType) x.
ScalarComputedField b -> Rep (ScalarComputedField b) x
from :: forall x. ScalarComputedField b -> Rep (ScalarComputedField b) x
$cto :: forall (b :: BackendType) x.
Rep (ScalarComputedField b) x -> ScalarComputedField b
to :: forall x. Rep (ScalarComputedField b) x -> ScalarComputedField b
Generic)
deriving instance (Backend b) => Eq (ScalarComputedField b)
deriving instance (Backend b) => Show (ScalarComputedField b)
instance (Backend b) => Hashable (ScalarComputedField b)
instance (Backend b) => ToJSON (ScalarComputedField b) where
toJSON :: ScalarComputedField b -> Value
toJSON ScalarComputedField {ComputedFieldName
FunctionName b
ScalarType b
ComputedFieldImplicitArguments b
XComputedField b
_scfXField :: forall (b :: BackendType).
ScalarComputedField b -> XComputedField b
_scfName :: forall (b :: BackendType).
ScalarComputedField b -> ComputedFieldName
_scfFunction :: forall (b :: BackendType). ScalarComputedField b -> FunctionName b
_scfComputedFieldImplicitArgs :: forall (b :: BackendType).
ScalarComputedField b -> ComputedFieldImplicitArguments b
_scfType :: forall (b :: BackendType). ScalarComputedField b -> ScalarType b
_scfXField :: XComputedField b
_scfName :: ComputedFieldName
_scfFunction :: FunctionName b
_scfComputedFieldImplicitArgs :: ComputedFieldImplicitArguments b
_scfType :: ScalarType b
..} =
[Pair] -> Value
object
[ Key
"name" Key -> ComputedFieldName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ComputedFieldName
_scfName,
Key
"function" Key -> FunctionName b -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= FunctionName b
_scfFunction,
Key
"function_implicit_arguments" Key -> ComputedFieldImplicitArguments b -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ComputedFieldImplicitArguments b
_scfComputedFieldImplicitArgs,
Key
"type" Key -> ScalarType b -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ScalarType b
_scfType
]
tableNameToLHSIdentifier :: (Backend b) => TableName b -> LHSIdentifier
tableNameToLHSIdentifier :: forall (b :: BackendType).
Backend b =>
TableName b -> LHSIdentifier
tableNameToLHSIdentifier = Text -> LHSIdentifier
LHSIdentifier (Text -> LHSIdentifier)
-> (TableName b -> Text) -> TableName b -> LHSIdentifier
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableName b -> Text
forall a. ToTxt a => a -> Text
toTxt
$(makePrisms ''RemoteRelationshipDefinition)