{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
module Hasura.RQL.Types.SourceCustomization
( SourceTypeCustomization,
RootFieldsCustomization (..),
mkCustomizedTypename,
emptySourceCustomization,
emptySourceTypeCustomization,
getSourceTypeCustomization,
SourceCustomization (..),
ResolvedSourceCustomization (..),
mkResolvedSourceCustomization,
MkRootFieldName (..),
applyEnumValueCase,
applyFieldNameCaseCust,
applyTypeNameCaseCust,
applyFieldNameCaseIdentifier,
applyTypeNameCaseIdentifier,
getNamingCase,
getTextFieldName,
getTextTypeName,
setFieldNameCase,
mkSelectField,
mkSelectAggregateField,
mkSelectByPkField,
mkSelectStreamField,
mkInsertField,
mkInsertOneField,
mkUpdateField,
mkUpdateByPkField,
mkUpdateManyField,
mkDeleteField,
mkDeleteByPkField,
mkRelayConnectionField,
mkRelationFunctionArgumentsFieldName,
mkMultiRowUpdateTypeName,
mkOnConflictTypeName,
mkTableConstraintTypeName,
mkTableAggregateTypeName,
mkFunctionArgsTypeName,
mkTableBoolExpTypeName,
mkTableTypeName,
mkTableInsertInputTypeName,
mkTableObjRelInsertInputTypeName,
mkTableArrRelInsertInputTypeName,
mkTableMutationResponseTypeName,
mkTableOrderByTypeName,
mkTableAggregateOrderByTypeName,
mkTableAggregateOrderByOpTypeName,
mkTableAggregateFieldTypeName,
mkTableAggOperatorTypeName,
mkTableSelectColumnTypeName,
mkTableUpdateColumnTypeName,
mkTableOperatorInputTypeName,
mkTablePkColumnsInputTypeName,
mkEnumTableTypeName,
mkStreamCursorInputTypeName,
mkStreamCursorValueInputTypeName,
mkSelectColumnPredTypeName,
mkTableAggregateBoolExpTypeName,
mkGroupByTypeName,
mkGroupByKeyTypeName,
mkGroupByKeyFieldsTypeName,
mkRelationFunctionIdentifier,
updateColumnsFieldName,
affectedRowsFieldName,
pkColumnsFieldName,
)
where
import Autodocodec (HasCodec (codec), optionalField', optionalFieldWith')
import Autodocodec qualified as AC
import Autodocodec.Extended (graphQLFieldNameCodec)
import Control.Lens
import Data.Aeson.Extended
import Data.Has
import Data.List.NonEmpty qualified as NE
import Data.Monoid
import Data.Text qualified as T
import Data.Text.Casing (GQLNameIdentifier (..))
import Data.Text.Casing qualified as C
import Hasura.Base.Error (Code (NotSupported), QErr, throw400)
import Hasura.GraphQL.Schema.Typename
import Hasura.Name qualified as Name
import Hasura.Prelude
import Hasura.RQL.Types.Backend (SupportedNamingCase (..))
import Hasura.RQL.Types.NamingCase (NamingCase (..))
import Hasura.Table.Cache (CustomRootField (..), TableConfig (..), TableCoreInfoG (..), TableInfo (..))
import Language.GraphQL.Draft.Syntax qualified as G
data RootFieldsCustomization = RootFieldsCustomization
{ RootFieldsCustomization -> Maybe Name
_rootfcNamespace :: Maybe G.Name,
RootFieldsCustomization -> Maybe Name
_rootfcPrefix :: Maybe G.Name,
RootFieldsCustomization -> Maybe Name
_rootfcSuffix :: Maybe G.Name
}
deriving (RootFieldsCustomization -> RootFieldsCustomization -> Bool
(RootFieldsCustomization -> RootFieldsCustomization -> Bool)
-> (RootFieldsCustomization -> RootFieldsCustomization -> Bool)
-> Eq RootFieldsCustomization
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RootFieldsCustomization -> RootFieldsCustomization -> Bool
== :: RootFieldsCustomization -> RootFieldsCustomization -> Bool
$c/= :: RootFieldsCustomization -> RootFieldsCustomization -> Bool
/= :: RootFieldsCustomization -> RootFieldsCustomization -> Bool
Eq, Int -> RootFieldsCustomization -> ShowS
[RootFieldsCustomization] -> ShowS
RootFieldsCustomization -> String
(Int -> RootFieldsCustomization -> ShowS)
-> (RootFieldsCustomization -> String)
-> ([RootFieldsCustomization] -> ShowS)
-> Show RootFieldsCustomization
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RootFieldsCustomization -> ShowS
showsPrec :: Int -> RootFieldsCustomization -> ShowS
$cshow :: RootFieldsCustomization -> String
show :: RootFieldsCustomization -> String
$cshowList :: [RootFieldsCustomization] -> ShowS
showList :: [RootFieldsCustomization] -> ShowS
Show, (forall x.
RootFieldsCustomization -> Rep RootFieldsCustomization x)
-> (forall x.
Rep RootFieldsCustomization x -> RootFieldsCustomization)
-> Generic RootFieldsCustomization
forall x. Rep RootFieldsCustomization x -> RootFieldsCustomization
forall x. RootFieldsCustomization -> Rep RootFieldsCustomization x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RootFieldsCustomization -> Rep RootFieldsCustomization x
from :: forall x. RootFieldsCustomization -> Rep RootFieldsCustomization x
$cto :: forall x. Rep RootFieldsCustomization x -> RootFieldsCustomization
to :: forall x. Rep RootFieldsCustomization x -> RootFieldsCustomization
Generic)
instance HasCodec RootFieldsCustomization where
codec :: JSONCodec RootFieldsCustomization
codec =
Text
-> ObjectCodec RootFieldsCustomization RootFieldsCustomization
-> JSONCodec RootFieldsCustomization
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object Text
"RootFieldsCustomization"
(ObjectCodec RootFieldsCustomization RootFieldsCustomization
-> JSONCodec RootFieldsCustomization)
-> ObjectCodec RootFieldsCustomization RootFieldsCustomization
-> JSONCodec RootFieldsCustomization
forall a b. (a -> b) -> a -> b
$ Maybe Name -> Maybe Name -> Maybe Name -> RootFieldsCustomization
RootFieldsCustomization
(Maybe Name -> Maybe Name -> Maybe Name -> RootFieldsCustomization)
-> Codec Object RootFieldsCustomization (Maybe Name)
-> Codec
Object
RootFieldsCustomization
(Maybe Name -> Maybe Name -> RootFieldsCustomization)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ValueCodec Name Name -> ObjectCodec (Maybe Name) (Maybe Name)
forall input output.
Text
-> ValueCodec input output
-> ObjectCodec (Maybe input) (Maybe output)
optionalFieldWith' Text
"namespace" ValueCodec Name Name
graphQLFieldNameCodec
ObjectCodec (Maybe Name) (Maybe Name)
-> (RootFieldsCustomization -> Maybe Name)
-> Codec Object RootFieldsCustomization (Maybe Name)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= RootFieldsCustomization -> Maybe Name
_rootfcNamespace
Codec
Object
RootFieldsCustomization
(Maybe Name -> Maybe Name -> RootFieldsCustomization)
-> Codec Object RootFieldsCustomization (Maybe Name)
-> Codec
Object
RootFieldsCustomization
(Maybe Name -> RootFieldsCustomization)
forall a b.
Codec Object RootFieldsCustomization (a -> b)
-> Codec Object RootFieldsCustomization a
-> Codec Object RootFieldsCustomization b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ValueCodec Name Name -> ObjectCodec (Maybe Name) (Maybe Name)
forall input output.
Text
-> ValueCodec input output
-> ObjectCodec (Maybe input) (Maybe output)
optionalFieldWith' Text
"prefix" ValueCodec Name Name
graphQLFieldNameCodec
ObjectCodec (Maybe Name) (Maybe Name)
-> (RootFieldsCustomization -> Maybe Name)
-> Codec Object RootFieldsCustomization (Maybe Name)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= RootFieldsCustomization -> Maybe Name
_rootfcPrefix
Codec
Object
RootFieldsCustomization
(Maybe Name -> RootFieldsCustomization)
-> Codec Object RootFieldsCustomization (Maybe Name)
-> ObjectCodec RootFieldsCustomization RootFieldsCustomization
forall a b.
Codec Object RootFieldsCustomization (a -> b)
-> Codec Object RootFieldsCustomization a
-> Codec Object RootFieldsCustomization b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ValueCodec Name Name -> ObjectCodec (Maybe Name) (Maybe Name)
forall input output.
Text
-> ValueCodec input output
-> ObjectCodec (Maybe input) (Maybe output)
optionalFieldWith' Text
"suffix" ValueCodec Name Name
graphQLFieldNameCodec
ObjectCodec (Maybe Name) (Maybe Name)
-> (RootFieldsCustomization -> Maybe Name)
-> Codec Object RootFieldsCustomization (Maybe Name)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= RootFieldsCustomization -> Maybe Name
_rootfcSuffix
instance ToJSON RootFieldsCustomization where
toJSON :: RootFieldsCustomization -> Value
toJSON = Options -> RootFieldsCustomization -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance FromJSON RootFieldsCustomization where
parseJSON :: Value -> Parser RootFieldsCustomization
parseJSON = Options -> Value -> Parser RootFieldsCustomization
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON
emptyRootFieldsCustomization :: RootFieldsCustomization
emptyRootFieldsCustomization :: RootFieldsCustomization
emptyRootFieldsCustomization = Maybe Name -> Maybe Name -> Maybe Name -> RootFieldsCustomization
RootFieldsCustomization Maybe Name
forall a. Maybe a
Nothing Maybe Name
forall a. Maybe a
Nothing Maybe Name
forall a. Maybe a
Nothing
data SourceTypeCustomization = SourceTypeCustomization
{ SourceTypeCustomization -> Maybe Name
_stcPrefix :: Maybe G.Name,
SourceTypeCustomization -> Maybe Name
_stcSuffix :: Maybe G.Name
}
deriving (SourceTypeCustomization -> SourceTypeCustomization -> Bool
(SourceTypeCustomization -> SourceTypeCustomization -> Bool)
-> (SourceTypeCustomization -> SourceTypeCustomization -> Bool)
-> Eq SourceTypeCustomization
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SourceTypeCustomization -> SourceTypeCustomization -> Bool
== :: SourceTypeCustomization -> SourceTypeCustomization -> Bool
$c/= :: SourceTypeCustomization -> SourceTypeCustomization -> Bool
/= :: SourceTypeCustomization -> SourceTypeCustomization -> Bool
Eq, Int -> SourceTypeCustomization -> ShowS
[SourceTypeCustomization] -> ShowS
SourceTypeCustomization -> String
(Int -> SourceTypeCustomization -> ShowS)
-> (SourceTypeCustomization -> String)
-> ([SourceTypeCustomization] -> ShowS)
-> Show SourceTypeCustomization
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SourceTypeCustomization -> ShowS
showsPrec :: Int -> SourceTypeCustomization -> ShowS
$cshow :: SourceTypeCustomization -> String
show :: SourceTypeCustomization -> String
$cshowList :: [SourceTypeCustomization] -> ShowS
showList :: [SourceTypeCustomization] -> ShowS
Show, (forall x.
SourceTypeCustomization -> Rep SourceTypeCustomization x)
-> (forall x.
Rep SourceTypeCustomization x -> SourceTypeCustomization)
-> Generic SourceTypeCustomization
forall x. Rep SourceTypeCustomization x -> SourceTypeCustomization
forall x. SourceTypeCustomization -> Rep SourceTypeCustomization x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SourceTypeCustomization -> Rep SourceTypeCustomization x
from :: forall x. SourceTypeCustomization -> Rep SourceTypeCustomization x
$cto :: forall x. Rep SourceTypeCustomization x -> SourceTypeCustomization
to :: forall x. Rep SourceTypeCustomization x -> SourceTypeCustomization
Generic)
instance HasCodec SourceTypeCustomization where
codec :: JSONCodec SourceTypeCustomization
codec =
Text
-> ObjectCodec SourceTypeCustomization SourceTypeCustomization
-> JSONCodec SourceTypeCustomization
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object Text
"SourceTypeCustomization"
(ObjectCodec SourceTypeCustomization SourceTypeCustomization
-> JSONCodec SourceTypeCustomization)
-> ObjectCodec SourceTypeCustomization SourceTypeCustomization
-> JSONCodec SourceTypeCustomization
forall a b. (a -> b) -> a -> b
$ Maybe Name -> Maybe Name -> SourceTypeCustomization
SourceTypeCustomization
(Maybe Name -> Maybe Name -> SourceTypeCustomization)
-> Codec Object SourceTypeCustomization (Maybe Name)
-> Codec
Object
SourceTypeCustomization
(Maybe Name -> SourceTypeCustomization)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ValueCodec Name Name -> ObjectCodec (Maybe Name) (Maybe Name)
forall input output.
Text
-> ValueCodec input output
-> ObjectCodec (Maybe input) (Maybe output)
optionalFieldWith' Text
"prefix" ValueCodec Name Name
graphQLFieldNameCodec
ObjectCodec (Maybe Name) (Maybe Name)
-> (SourceTypeCustomization -> Maybe Name)
-> Codec Object SourceTypeCustomization (Maybe Name)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= SourceTypeCustomization -> Maybe Name
_stcPrefix
Codec
Object
SourceTypeCustomization
(Maybe Name -> SourceTypeCustomization)
-> Codec Object SourceTypeCustomization (Maybe Name)
-> ObjectCodec SourceTypeCustomization SourceTypeCustomization
forall a b.
Codec Object SourceTypeCustomization (a -> b)
-> Codec Object SourceTypeCustomization a
-> Codec Object SourceTypeCustomization b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ValueCodec Name Name -> ObjectCodec (Maybe Name) (Maybe Name)
forall input output.
Text
-> ValueCodec input output
-> ObjectCodec (Maybe input) (Maybe output)
optionalFieldWith' Text
"suffix" ValueCodec Name Name
graphQLFieldNameCodec
ObjectCodec (Maybe Name) (Maybe Name)
-> (SourceTypeCustomization -> Maybe Name)
-> Codec Object SourceTypeCustomization (Maybe Name)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= SourceTypeCustomization -> Maybe Name
_stcSuffix
instance ToJSON SourceTypeCustomization where
toJSON :: SourceTypeCustomization -> Value
toJSON = Options -> SourceTypeCustomization -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance FromJSON SourceTypeCustomization where
parseJSON :: Value -> Parser SourceTypeCustomization
parseJSON = Options -> Value -> Parser SourceTypeCustomization
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON
emptySourceTypeCustomization :: SourceTypeCustomization
emptySourceTypeCustomization :: SourceTypeCustomization
emptySourceTypeCustomization = Maybe Name -> Maybe Name -> SourceTypeCustomization
SourceTypeCustomization Maybe Name
forall a. Maybe a
Nothing Maybe Name
forall a. Maybe a
Nothing
mkCustomizedTypename :: Maybe SourceTypeCustomization -> NamingCase -> MkTypename
mkCustomizedTypename :: Maybe SourceTypeCustomization -> NamingCase -> MkTypename
mkCustomizedTypename Maybe SourceTypeCustomization
stc NamingCase
tCase = (Name -> Name) -> MkTypename
MkTypename (Maybe SourceTypeCustomization -> NamingCase -> Name -> Name
applyTypeCust Maybe SourceTypeCustomization
stc NamingCase
tCase)
mkCustomizedFieldName :: Maybe RootFieldsCustomization -> NamingCase -> MkRootFieldName
mkCustomizedFieldName :: Maybe RootFieldsCustomization -> NamingCase -> MkRootFieldName
mkCustomizedFieldName Maybe RootFieldsCustomization
rtc NamingCase
tCase = (Name -> Name) -> MkRootFieldName
MkRootFieldName (Maybe RootFieldsCustomization -> NamingCase -> Name -> Name
applyFieldCust Maybe RootFieldsCustomization
rtc NamingCase
tCase)
applyTypeCust :: Maybe SourceTypeCustomization -> NamingCase -> (G.Name -> G.Name)
applyTypeCust :: Maybe SourceTypeCustomization -> NamingCase -> Name -> Name
applyTypeCust Maybe SourceTypeCustomization
Nothing NamingCase
_ = Name -> Name
forall a. a -> a
id
applyTypeCust (Just SourceTypeCustomization {Maybe Name
_stcPrefix :: SourceTypeCustomization -> Maybe Name
_stcSuffix :: SourceTypeCustomization -> Maybe Name
_stcPrefix :: Maybe Name
_stcSuffix :: Maybe Name
..}) NamingCase
tCase = Maybe Name -> Maybe Name -> NamingCase -> Bool -> Name -> Name
applyPrefixSuffix Maybe Name
_stcPrefix Maybe Name
_stcSuffix NamingCase
tCase Bool
True
applyFieldCust :: Maybe RootFieldsCustomization -> NamingCase -> (G.Name -> G.Name)
applyFieldCust :: Maybe RootFieldsCustomization -> NamingCase -> Name -> Name
applyFieldCust Maybe RootFieldsCustomization
Nothing NamingCase
_ = Name -> Name
forall a. a -> a
id
applyFieldCust (Just RootFieldsCustomization {Maybe Name
_rootfcNamespace :: RootFieldsCustomization -> Maybe Name
_rootfcPrefix :: RootFieldsCustomization -> Maybe Name
_rootfcSuffix :: RootFieldsCustomization -> Maybe Name
_rootfcNamespace :: Maybe Name
_rootfcPrefix :: Maybe Name
_rootfcSuffix :: Maybe Name
..}) NamingCase
tCase = Maybe Name -> Maybe Name -> NamingCase -> Bool -> Name -> Name
applyPrefixSuffix Maybe Name
_rootfcPrefix Maybe Name
_rootfcSuffix NamingCase
tCase Bool
False
applyTypeNameCaseCust :: NamingCase -> G.Name -> G.Name
applyTypeNameCaseCust :: NamingCase -> Name -> Name
applyTypeNameCaseCust NamingCase
tCase Name
name = case NamingCase
tCase of
NamingCase
HasuraCase -> Name
name
NamingCase
GraphqlCase -> (Text -> Text) -> Name -> Name
C.transformNameWith (Text -> Text
C.snakeToPascal) Name
name
applyFieldNameCaseCust :: NamingCase -> G.Name -> G.Name
applyFieldNameCaseCust :: NamingCase -> Name -> Name
applyFieldNameCaseCust NamingCase
tCase Name
name = case NamingCase
tCase of
NamingCase
HasuraCase -> Name
name
NamingCase
GraphqlCase -> (Text -> Text) -> Name -> Name
C.transformNameWith (Text -> Text
C.snakeToCamel) Name
name
getTextFieldName :: NamingCase -> GQLNameIdentifier -> Text
getTextFieldName :: NamingCase -> GQLNameIdentifier -> Text
getTextFieldName NamingCase
tCase GQLNameIdentifier
name = Name -> Text
G.unName (Name -> Text) -> Name -> Text
forall a b. (a -> b) -> a -> b
$ NamingCase -> GQLNameIdentifier -> Name
applyFieldNameCaseIdentifier NamingCase
tCase GQLNameIdentifier
name
applyTypeNameCaseIdentifier :: NamingCase -> GQLNameIdentifier -> G.Name
applyTypeNameCaseIdentifier :: NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
tCase GQLNameIdentifier
nameLst = case NamingCase
tCase of
NamingCase
HasuraCase -> GQLNameIdentifier -> Name
C.toSnakeG GQLNameIdentifier
nameLst
NamingCase
GraphqlCase -> GQLNameIdentifier -> Name
C.toPascalG GQLNameIdentifier
nameLst
getTextTypeName :: NamingCase -> GQLNameIdentifier -> Text
getTextTypeName :: NamingCase -> GQLNameIdentifier -> Text
getTextTypeName NamingCase
tCase GQLNameIdentifier
name = Name -> Text
G.unName (Name -> Text) -> Name -> Text
forall a b. (a -> b) -> a -> b
$ NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
tCase GQLNameIdentifier
name
applyFieldNameCaseIdentifier :: NamingCase -> GQLNameIdentifier -> G.Name
applyFieldNameCaseIdentifier :: NamingCase -> GQLNameIdentifier -> Name
applyFieldNameCaseIdentifier NamingCase
tCase GQLNameIdentifier
nameLst = case NamingCase
tCase of
NamingCase
HasuraCase -> GQLNameIdentifier -> Name
C.toSnakeG GQLNameIdentifier
nameLst
NamingCase
GraphqlCase -> GQLNameIdentifier -> Name
C.toCamelG GQLNameIdentifier
nameLst
applyEnumValueCase :: NamingCase -> G.Name -> G.Name
applyEnumValueCase :: NamingCase -> Name -> Name
applyEnumValueCase NamingCase
tCase Name
v = case NamingCase
tCase of
NamingCase
HasuraCase -> Name
v
NamingCase
GraphqlCase -> (Text -> Text) -> Name -> Name
C.transformNameWith (Text -> Text
T.toUpper) Name
v
setFieldNameCase ::
NamingCase ->
TableInfo b ->
CustomRootField ->
(C.GQLNameIdentifier -> C.GQLNameIdentifier) ->
C.GQLNameIdentifier ->
G.Name
setFieldNameCase :: forall (b :: BackendType).
NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
setFieldNameCase NamingCase
tCase TableInfo b
tInfo CustomRootField
crf GQLNameIdentifier -> GQLNameIdentifier
getFieldName GQLNameIdentifier
tableName =
(NamingCase -> GQLNameIdentifier -> Name
applyFieldNameCaseIdentifier NamingCase
tCase GQLNameIdentifier
fieldIdentifier)
where
tccName :: Maybe GQLNameIdentifier
tccName = (Name -> GQLNameIdentifier)
-> Maybe Name -> Maybe GQLNameIdentifier
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Name -> GQLNameIdentifier
C.fromCustomName (Maybe Name -> Maybe GQLNameIdentifier)
-> (TableInfo b -> Maybe Name)
-> TableInfo b
-> Maybe GQLNameIdentifier
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableConfig b -> Maybe Name
forall (b :: BackendType). TableConfig b -> Maybe Name
_tcCustomName (TableConfig b -> Maybe Name)
-> (TableInfo b -> TableConfig b) -> TableInfo b -> Maybe Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> TableConfig b
_tciCustomConfig (TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b)
-> (TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b))
-> TableInfo b
-> TableConfig b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo (TableInfo b -> Maybe GQLNameIdentifier)
-> TableInfo b -> Maybe GQLNameIdentifier
forall a b. (a -> b) -> a -> b
$ TableInfo b
tInfo
crfName :: Maybe GQLNameIdentifier
crfName = (Name -> GQLNameIdentifier)
-> Maybe Name -> Maybe GQLNameIdentifier
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Name -> GQLNameIdentifier
C.fromCustomName (CustomRootField -> Maybe Name
_crfName CustomRootField
crf)
fieldIdentifier :: GQLNameIdentifier
fieldIdentifier = GQLNameIdentifier -> Maybe GQLNameIdentifier -> GQLNameIdentifier
forall a. a -> Maybe a -> a
fromMaybe (GQLNameIdentifier -> GQLNameIdentifier
getFieldName (GQLNameIdentifier -> Maybe GQLNameIdentifier -> GQLNameIdentifier
forall a. a -> Maybe a -> a
fromMaybe GQLNameIdentifier
tableName Maybe GQLNameIdentifier
tccName)) Maybe GQLNameIdentifier
crfName
applyPrefixSuffix :: Maybe G.Name -> Maybe G.Name -> NamingCase -> Bool -> G.Name -> G.Name
applyPrefixSuffix :: Maybe Name -> Maybe Name -> NamingCase -> Bool -> Name -> Name
applyPrefixSuffix Maybe Name
Nothing Maybe Name
Nothing NamingCase
tCase Bool
isTypeName Name
name = NamingCase -> Bool -> NonEmpty (Name, NameOrigin) -> Name
concatPrefixSuffix NamingCase
tCase Bool
isTypeName (NonEmpty (Name, NameOrigin) -> Name)
-> NonEmpty (Name, NameOrigin) -> Name
forall a b. (a -> b) -> a -> b
$ [(Name, NameOrigin)] -> NonEmpty (Name, NameOrigin)
forall a. HasCallStack => [a] -> NonEmpty a
NE.fromList [(Name
name, NameOrigin
C.CustomName)]
applyPrefixSuffix (Just Name
prefix) Maybe Name
Nothing NamingCase
tCase Bool
isTypeName Name
name = NamingCase -> Bool -> NonEmpty (Name, NameOrigin) -> Name
concatPrefixSuffix NamingCase
tCase Bool
isTypeName (NonEmpty (Name, NameOrigin) -> Name)
-> NonEmpty (Name, NameOrigin) -> Name
forall a b. (a -> b) -> a -> b
$ [(Name, NameOrigin)] -> NonEmpty (Name, NameOrigin)
forall a. HasCallStack => [a] -> NonEmpty a
NE.fromList [(Name
prefix, NameOrigin
C.CustomName), (Name
name, NameOrigin
C.AutogeneratedName)]
applyPrefixSuffix Maybe Name
Nothing (Just Name
suffix) NamingCase
tCase Bool
isTypeName Name
name = NamingCase -> Bool -> NonEmpty (Name, NameOrigin) -> Name
concatPrefixSuffix NamingCase
tCase Bool
isTypeName (NonEmpty (Name, NameOrigin) -> Name)
-> NonEmpty (Name, NameOrigin) -> Name
forall a b. (a -> b) -> a -> b
$ [(Name, NameOrigin)] -> NonEmpty (Name, NameOrigin)
forall a. HasCallStack => [a] -> NonEmpty a
NE.fromList [(Name
name, NameOrigin
C.CustomName), (Name
suffix, NameOrigin
C.CustomName)]
applyPrefixSuffix (Just Name
prefix) (Just Name
suffix) NamingCase
tCase Bool
isTypeName Name
name = NamingCase -> Bool -> NonEmpty (Name, NameOrigin) -> Name
concatPrefixSuffix NamingCase
tCase Bool
isTypeName (NonEmpty (Name, NameOrigin) -> Name)
-> NonEmpty (Name, NameOrigin) -> Name
forall a b. (a -> b) -> a -> b
$ [(Name, NameOrigin)] -> NonEmpty (Name, NameOrigin)
forall a. HasCallStack => [a] -> NonEmpty a
NE.fromList [(Name
prefix, NameOrigin
C.CustomName), (Name
name, NameOrigin
C.AutogeneratedName), (Name
suffix, NameOrigin
C.CustomName)]
concatPrefixSuffix :: NamingCase -> Bool -> NonEmpty (G.Name, C.NameOrigin) -> G.Name
concatPrefixSuffix :: NamingCase -> Bool -> NonEmpty (Name, NameOrigin) -> Name
concatPrefixSuffix (NamingCase
HasuraCase) Bool
_ NonEmpty (Name, NameOrigin)
neList = NonEmpty Name -> Name
forall a. Semigroup a => NonEmpty a -> a
sconcat ((Name, NameOrigin) -> Name
forall a b. (a, b) -> a
fst ((Name, NameOrigin) -> Name)
-> NonEmpty (Name, NameOrigin) -> NonEmpty Name
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty (Name, NameOrigin)
neList)
concatPrefixSuffix (NamingCase
GraphqlCase) Bool
isTypeName NonEmpty (Name, NameOrigin)
neList =
if Bool
isTypeName
then GQLNameIdentifier -> Name
C.toPascalG GQLNameIdentifier
prefixSuffixGQLIdent
else GQLNameIdentifier -> (Text -> Text) -> (Text -> Text) -> Name
C.transformPrefixAndSuffixAndConcat GQLNameIdentifier
prefixSuffixGQLIdent Text -> Text
forall a. a -> a
id Text -> Text
C.upperFirstChar
where
prefixSuffixGQLIdent :: GQLNameIdentifier
prefixSuffixGQLIdent = NonEmpty (Name, NameOrigin) -> GQLNameIdentifier
C.fromNonEmptyList NonEmpty (Name, NameOrigin)
neList
data SourceCustomization = SourceCustomization
{ SourceCustomization -> Maybe RootFieldsCustomization
_scRootFields :: Maybe RootFieldsCustomization,
SourceCustomization -> Maybe SourceTypeCustomization
_scTypeNames :: Maybe SourceTypeCustomization,
SourceCustomization -> Maybe NamingCase
_scNamingConvention :: Maybe NamingCase
}
deriving (SourceCustomization -> SourceCustomization -> Bool
(SourceCustomization -> SourceCustomization -> Bool)
-> (SourceCustomization -> SourceCustomization -> Bool)
-> Eq SourceCustomization
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SourceCustomization -> SourceCustomization -> Bool
== :: SourceCustomization -> SourceCustomization -> Bool
$c/= :: SourceCustomization -> SourceCustomization -> Bool
/= :: SourceCustomization -> SourceCustomization -> Bool
Eq, Int -> SourceCustomization -> ShowS
[SourceCustomization] -> ShowS
SourceCustomization -> String
(Int -> SourceCustomization -> ShowS)
-> (SourceCustomization -> String)
-> ([SourceCustomization] -> ShowS)
-> Show SourceCustomization
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SourceCustomization -> ShowS
showsPrec :: Int -> SourceCustomization -> ShowS
$cshow :: SourceCustomization -> String
show :: SourceCustomization -> String
$cshowList :: [SourceCustomization] -> ShowS
showList :: [SourceCustomization] -> ShowS
Show, (forall x. SourceCustomization -> Rep SourceCustomization x)
-> (forall x. Rep SourceCustomization x -> SourceCustomization)
-> Generic SourceCustomization
forall x. Rep SourceCustomization x -> SourceCustomization
forall x. SourceCustomization -> Rep SourceCustomization x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SourceCustomization -> Rep SourceCustomization x
from :: forall x. SourceCustomization -> Rep SourceCustomization x
$cto :: forall x. Rep SourceCustomization x -> SourceCustomization
to :: forall x. Rep SourceCustomization x -> SourceCustomization
Generic)
instance HasCodec SourceCustomization where
codec :: JSONCodec SourceCustomization
codec =
Text
-> ObjectCodec SourceCustomization SourceCustomization
-> JSONCodec SourceCustomization
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object Text
"SourceCustomization"
(ObjectCodec SourceCustomization SourceCustomization
-> JSONCodec SourceCustomization)
-> ObjectCodec SourceCustomization SourceCustomization
-> JSONCodec SourceCustomization
forall a b. (a -> b) -> a -> b
$ Maybe RootFieldsCustomization
-> Maybe SourceTypeCustomization
-> Maybe NamingCase
-> SourceCustomization
SourceCustomization
(Maybe RootFieldsCustomization
-> Maybe SourceTypeCustomization
-> Maybe NamingCase
-> SourceCustomization)
-> Codec Object SourceCustomization (Maybe RootFieldsCustomization)
-> Codec
Object
SourceCustomization
(Maybe SourceTypeCustomization
-> Maybe NamingCase -> SourceCustomization)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ObjectCodec
(Maybe RootFieldsCustomization) (Maybe RootFieldsCustomization)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"root_fields"
ObjectCodec
(Maybe RootFieldsCustomization) (Maybe RootFieldsCustomization)
-> (SourceCustomization -> Maybe RootFieldsCustomization)
-> Codec Object SourceCustomization (Maybe RootFieldsCustomization)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= SourceCustomization -> Maybe RootFieldsCustomization
_scRootFields
Codec
Object
SourceCustomization
(Maybe SourceTypeCustomization
-> Maybe NamingCase -> SourceCustomization)
-> Codec Object SourceCustomization (Maybe SourceTypeCustomization)
-> Codec
Object
SourceCustomization
(Maybe NamingCase -> SourceCustomization)
forall a b.
Codec Object SourceCustomization (a -> b)
-> Codec Object SourceCustomization a
-> Codec Object SourceCustomization b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe SourceTypeCustomization) (Maybe SourceTypeCustomization)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"type_names"
ObjectCodec
(Maybe SourceTypeCustomization) (Maybe SourceTypeCustomization)
-> (SourceCustomization -> Maybe SourceTypeCustomization)
-> Codec Object SourceCustomization (Maybe SourceTypeCustomization)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= SourceCustomization -> Maybe SourceTypeCustomization
_scTypeNames
Codec
Object
SourceCustomization
(Maybe NamingCase -> SourceCustomization)
-> Codec Object SourceCustomization (Maybe NamingCase)
-> ObjectCodec SourceCustomization SourceCustomization
forall a b.
Codec Object SourceCustomization (a -> b)
-> Codec Object SourceCustomization a
-> Codec Object SourceCustomization b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe NamingCase) (Maybe NamingCase)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"naming_convention"
ObjectCodec (Maybe NamingCase) (Maybe NamingCase)
-> (SourceCustomization -> Maybe NamingCase)
-> Codec Object SourceCustomization (Maybe NamingCase)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= SourceCustomization -> Maybe NamingCase
_scNamingConvention
instance ToJSON SourceCustomization where
toJSON :: SourceCustomization -> Value
toJSON = Options -> SourceCustomization -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance FromJSON SourceCustomization where
parseJSON :: Value -> Parser SourceCustomization
parseJSON = Options -> Value -> Parser SourceCustomization
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON
emptySourceCustomization :: SourceCustomization
emptySourceCustomization :: SourceCustomization
emptySourceCustomization = Maybe RootFieldsCustomization
-> Maybe SourceTypeCustomization
-> Maybe NamingCase
-> SourceCustomization
SourceCustomization Maybe RootFieldsCustomization
forall a. Maybe a
Nothing Maybe SourceTypeCustomization
forall a. Maybe a
Nothing Maybe NamingCase
forall a. Maybe a
Nothing
getSourceTypeCustomization :: SourceCustomization -> SourceTypeCustomization
getSourceTypeCustomization :: SourceCustomization -> SourceTypeCustomization
getSourceTypeCustomization = SourceTypeCustomization
-> Maybe SourceTypeCustomization -> SourceTypeCustomization
forall a. a -> Maybe a -> a
fromMaybe SourceTypeCustomization
emptySourceTypeCustomization (Maybe SourceTypeCustomization -> SourceTypeCustomization)
-> (SourceCustomization -> Maybe SourceTypeCustomization)
-> SourceCustomization
-> SourceTypeCustomization
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceCustomization -> Maybe SourceTypeCustomization
_scTypeNames
data ResolvedSourceCustomization = ResolvedSourceCustomization
{ ResolvedSourceCustomization -> MkRootFieldName
_rscRootFields :: MkRootFieldName,
ResolvedSourceCustomization -> MkTypename
_rscTypeNames :: MkTypename,
ResolvedSourceCustomization -> NamingCase
_rscNamingConvention :: NamingCase,
ResolvedSourceCustomization -> Maybe Name
_rscRootNamespace :: Maybe G.Name
}
mkResolvedSourceCustomization :: SourceCustomization -> NamingCase -> ResolvedSourceCustomization
mkResolvedSourceCustomization :: SourceCustomization -> NamingCase -> ResolvedSourceCustomization
mkResolvedSourceCustomization SourceCustomization
sourceCustomization NamingCase
namingConv =
ResolvedSourceCustomization
{ _rscRootFields :: MkRootFieldName
_rscRootFields = Maybe RootFieldsCustomization -> NamingCase -> MkRootFieldName
mkCustomizedFieldName (SourceCustomization -> Maybe RootFieldsCustomization
_scRootFields SourceCustomization
sourceCustomization) NamingCase
namingConv,
_rscTypeNames :: MkTypename
_rscTypeNames = Maybe SourceTypeCustomization -> NamingCase -> MkTypename
mkCustomizedTypename (SourceCustomization -> Maybe SourceTypeCustomization
_scTypeNames SourceCustomization
sourceCustomization) NamingCase
namingConv,
_rscNamingConvention :: NamingCase
_rscNamingConvention = NamingCase
namingConv,
_rscRootNamespace :: Maybe Name
_rscRootNamespace = RootFieldsCustomization -> Maybe Name
_rootfcNamespace (RootFieldsCustomization -> Maybe Name)
-> Maybe RootFieldsCustomization -> Maybe Name
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SourceCustomization -> Maybe RootFieldsCustomization
_scRootFields SourceCustomization
sourceCustomization
}
newtype MkRootFieldName = MkRootFieldName {MkRootFieldName -> Name -> Name
runMkRootFieldName :: G.Name -> G.Name}
deriving (NonEmpty MkRootFieldName -> MkRootFieldName
MkRootFieldName -> MkRootFieldName -> MkRootFieldName
(MkRootFieldName -> MkRootFieldName -> MkRootFieldName)
-> (NonEmpty MkRootFieldName -> MkRootFieldName)
-> (forall b.
Integral b =>
b -> MkRootFieldName -> MkRootFieldName)
-> Semigroup MkRootFieldName
forall b. Integral b => b -> MkRootFieldName -> MkRootFieldName
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: MkRootFieldName -> MkRootFieldName -> MkRootFieldName
<> :: MkRootFieldName -> MkRootFieldName -> MkRootFieldName
$csconcat :: NonEmpty MkRootFieldName -> MkRootFieldName
sconcat :: NonEmpty MkRootFieldName -> MkRootFieldName
$cstimes :: forall b. Integral b => b -> MkRootFieldName -> MkRootFieldName
stimes :: forall b. Integral b => b -> MkRootFieldName -> MkRootFieldName
Semigroup, Semigroup MkRootFieldName
MkRootFieldName
Semigroup MkRootFieldName
-> MkRootFieldName
-> (MkRootFieldName -> MkRootFieldName -> MkRootFieldName)
-> ([MkRootFieldName] -> MkRootFieldName)
-> Monoid MkRootFieldName
[MkRootFieldName] -> MkRootFieldName
MkRootFieldName -> MkRootFieldName -> MkRootFieldName
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: MkRootFieldName
mempty :: MkRootFieldName
$cmappend :: MkRootFieldName -> MkRootFieldName -> MkRootFieldName
mappend :: MkRootFieldName -> MkRootFieldName -> MkRootFieldName
$cmconcat :: [MkRootFieldName] -> MkRootFieldName
mconcat :: [MkRootFieldName] -> MkRootFieldName
Monoid) via (Endo G.Name)
getNamingCase ::
forall m.
(MonadError QErr m) =>
SourceCustomization ->
SupportedNamingCase ->
NamingCase ->
m NamingCase
getNamingCase :: forall (m :: * -> *).
MonadError QErr m =>
SourceCustomization
-> SupportedNamingCase -> NamingCase -> m NamingCase
getNamingCase SourceCustomization
sc SupportedNamingCase
namingConventionSupport NamingCase
defaultNC = do
let namingConv :: NamingCase
namingConv = NamingCase -> Maybe NamingCase -> NamingCase
forall a. a -> Maybe a -> a
fromMaybe NamingCase
defaultNC (SourceCustomization -> Maybe NamingCase
_scNamingConvention SourceCustomization
sc)
case SupportedNamingCase
namingConventionSupport of
SupportedNamingCase
AllConventions -> NamingCase -> m NamingCase
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure NamingCase
namingConv
SupportedNamingCase
OnlyHasuraCase -> case (SourceCustomization -> Maybe NamingCase
_scNamingConvention SourceCustomization
sc) of
Just NamingCase
GraphqlCase -> Code -> Text -> m NamingCase
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotSupported (Text -> m NamingCase) -> Text -> m NamingCase
forall a b. (a -> b) -> a -> b
$ Text
"sources other than postgres do not support graphql-default as naming convention yet"
Maybe NamingCase
_ -> NamingCase -> m NamingCase
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure NamingCase
HasuraCase
withNamingCaseCustomization :: forall m r a. (MonadReader r m, Has NamingCase r) => NamingCase -> m a -> m a
withNamingCaseCustomization :: forall (m :: * -> *) r a.
(MonadReader r m, Has NamingCase r) =>
NamingCase -> m a -> m a
withNamingCaseCustomization = (r -> r) -> m a -> m a
forall a. (r -> r) -> m a -> m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local ((r -> r) -> m a -> m a)
-> (NamingCase -> r -> r) -> NamingCase -> m a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter r r NamingCase NamingCase -> NamingCase -> r -> r
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter r r NamingCase NamingCase
forall a t. Has a t => Lens t a
Lens r NamingCase
hasLens
mkSelectField :: GQLNameIdentifier -> GQLNameIdentifier
mkSelectField :: GQLNameIdentifier -> GQLNameIdentifier
mkSelectField = GQLNameIdentifier -> GQLNameIdentifier
forall a. a -> a
id
mkSelectAggregateField :: GQLNameIdentifier -> GQLNameIdentifier
mkSelectAggregateField :: GQLNameIdentifier -> GQLNameIdentifier
mkSelectAggregateField GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name._aggregate
mkSelectByPkField :: GQLNameIdentifier -> GQLNameIdentifier
mkSelectByPkField :: GQLNameIdentifier -> GQLNameIdentifier
mkSelectByPkField GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["by", "pk"])
mkInsertField :: GQLNameIdentifier -> GQLNameIdentifier
mkInsertField :: GQLNameIdentifier -> GQLNameIdentifier
mkInsertField GQLNameIdentifier
name = Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name._insert GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> GQLNameIdentifier
name
mkInsertOneField :: GQLNameIdentifier -> GQLNameIdentifier
mkInsertOneField :: GQLNameIdentifier -> GQLNameIdentifier
mkInsertOneField GQLNameIdentifier
name = Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name._insert GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name._one
mkUpdateField :: GQLNameIdentifier -> GQLNameIdentifier
mkUpdateField :: GQLNameIdentifier -> GQLNameIdentifier
mkUpdateField GQLNameIdentifier
name = Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name._update GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> GQLNameIdentifier
name
mkUpdateByPkField :: GQLNameIdentifier -> GQLNameIdentifier
mkUpdateByPkField :: GQLNameIdentifier -> GQLNameIdentifier
mkUpdateByPkField GQLNameIdentifier
name = Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name._update GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["by", "pk"])
mkUpdateManyField :: GQLNameIdentifier -> GQLNameIdentifier
mkUpdateManyField :: GQLNameIdentifier -> GQLNameIdentifier
mkUpdateManyField GQLNameIdentifier
name = Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name._update GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name._many
mkDeleteField :: GQLNameIdentifier -> GQLNameIdentifier
mkDeleteField :: GQLNameIdentifier -> GQLNameIdentifier
mkDeleteField GQLNameIdentifier
name = Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name._delete GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> GQLNameIdentifier
name
mkDeleteByPkField :: GQLNameIdentifier -> GQLNameIdentifier
mkDeleteByPkField :: GQLNameIdentifier -> GQLNameIdentifier
mkDeleteByPkField GQLNameIdentifier
name = Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name._delete GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["by", "pk"])
mkRelayConnectionField :: GQLNameIdentifier -> GQLNameIdentifier
mkRelayConnectionField :: GQLNameIdentifier -> GQLNameIdentifier
mkRelayConnectionField GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name._connection
mkSelectStreamField :: GQLNameIdentifier -> GQLNameIdentifier
mkSelectStreamField :: GQLNameIdentifier -> GQLNameIdentifier
mkSelectStreamField GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name._stream
mkMultiRowUpdateTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkMultiRowUpdateTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkMultiRowUpdateTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromAutogeneratedName $$(G.litName "updates")
mkOnConflictTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkOnConflictTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkOnConflictTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["on", "conflict"])
mkTableConstraintTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableConstraintTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableConstraintTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromAutogeneratedName $$(G.litName "constraint")
mkTableAggregateTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableAggregateTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableAggregateTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromAutogeneratedName $$(G.litName "aggregate")
mkTableAggregateFieldTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableAggregateFieldTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableAggregateFieldTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["aggregate", "fields"])
mkFunctionArgsTypeName :: G.Name -> GQLNameIdentifier -> GQLNameIdentifier
mkFunctionArgsTypeName :: Name -> GQLNameIdentifier -> GQLNameIdentifier
mkFunctionArgsTypeName Name
computedFieldName GQLNameIdentifier
tableName = Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
computedFieldName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> GQLNameIdentifier
tableName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromAutogeneratedName $$(G.litName "args")
mkTableBoolExpTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableBoolExpTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableBoolExpTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["bool", "exp"])
mkTableTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableTypeName = GQLNameIdentifier -> GQLNameIdentifier
forall a. a -> a
id
mkTableInsertInputTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableInsertInputTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableInsertInputTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["insert", "input"])
mkTableObjRelInsertInputTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableObjRelInsertInputTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableObjRelInsertInputTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["obj", "rel", "insert", "input"])
mkTableArrRelInsertInputTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableArrRelInsertInputTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableArrRelInsertInputTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["arr", "rel", "insert", "input"])
mkTableMutationResponseTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableMutationResponseTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableMutationResponseTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["mutation", "response"])
mkTableOrderByTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableOrderByTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableOrderByTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["order", "by"])
mkTableAggregateOrderByTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableAggregateOrderByTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableAggregateOrderByTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["aggregate", "order", "by"])
mkTableAggregateOrderByOpTypeName :: GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
mkTableAggregateOrderByOpTypeName :: GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
mkTableAggregateOrderByOpTypeName GQLNameIdentifier
tableName GQLNameIdentifier
operator = GQLNameIdentifier
tableName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> GQLNameIdentifier
operator GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["order", "by"])
mkTableAggOperatorTypeName :: GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
mkTableAggOperatorTypeName :: GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
mkTableAggOperatorTypeName GQLNameIdentifier
tableName GQLNameIdentifier
operator = GQLNameIdentifier
tableName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> GQLNameIdentifier
operator GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromAutogeneratedName $$(G.litName "fields")
mkTableSelectColumnTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableSelectColumnTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableSelectColumnTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["select", "column"])
mkTableUpdateColumnTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableUpdateColumnTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableUpdateColumnTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["update", "column"])
mkTableOperatorInputTypeName :: GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
mkTableOperatorInputTypeName :: GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
mkTableOperatorInputTypeName GQLNameIdentifier
tableName GQLNameIdentifier
operator = GQLNameIdentifier
tableName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> GQLNameIdentifier
operator GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromAutogeneratedName $$(G.litName "input")
mkTablePkColumnsInputTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTablePkColumnsInputTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTablePkColumnsInputTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["pk", "columns", "input"])
mkEnumTableTypeName :: GQLNameIdentifier -> Maybe G.Name -> GQLNameIdentifier
mkEnumTableTypeName :: GQLNameIdentifier -> Maybe Name -> GQLNameIdentifier
mkEnumTableTypeName GQLNameIdentifier
name (Just Name
customName) = Name -> GQLNameIdentifier
C.fromCustomName Name
customName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromAutogeneratedName $$(G.litName "enum")
mkEnumTableTypeName GQLNameIdentifier
name Maybe Name
Nothing = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromAutogeneratedName $$(G.litName "enum")
mkStreamCursorInputTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkStreamCursorInputTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkStreamCursorInputTypeName GQLNameIdentifier
tableName = GQLNameIdentifier
tableName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["stream", "cursor", "input"])
mkStreamCursorValueInputTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkStreamCursorValueInputTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkStreamCursorValueInputTypeName GQLNameIdentifier
tableName = GQLNameIdentifier
tableName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["stream", "cursor", "value", "input"])
mkSelectColumnPredTypeName :: GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
mkSelectColumnPredTypeName :: GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
mkSelectColumnPredTypeName GQLNameIdentifier
tableName GQLNameIdentifier
predName = GQLNameIdentifier
tableName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["select", "column"]) GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> GQLNameIdentifier
predName
mkTableAggregateBoolExpTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableAggregateBoolExpTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkTableAggregateBoolExpTypeName GQLNameIdentifier
name = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["aggregate", "bool", "exp"])
mkGroupByTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkGroupByTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkGroupByTypeName GQLNameIdentifier
tableName = GQLNameIdentifier
tableName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["group", "by"])
mkGroupByKeyTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkGroupByKeyTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkGroupByKeyTypeName GQLNameIdentifier
tableName = GQLNameIdentifier
tableName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["group", "by", "key"])
mkGroupByKeyFieldsTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkGroupByKeyFieldsTypeName :: GQLNameIdentifier -> GQLNameIdentifier
mkGroupByKeyFieldsTypeName GQLNameIdentifier
tableName = GQLNameIdentifier
tableName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["group", "by", "key", "fields"])
mkRelationFunctionIdentifier :: GQLNameIdentifier -> G.Name -> GQLNameIdentifier
mkRelationFunctionIdentifier :: GQLNameIdentifier -> Name -> GQLNameIdentifier
mkRelationFunctionIdentifier GQLNameIdentifier
name Name
functionName = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromCustomName Name
functionName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["arguments", "columns"])
mkRelationFunctionArgumentsFieldName :: GQLNameIdentifier -> G.Name -> GQLNameIdentifier
mkRelationFunctionArgumentsFieldName :: GQLNameIdentifier -> Name -> GQLNameIdentifier
mkRelationFunctionArgumentsFieldName GQLNameIdentifier
name Name
functionName = GQLNameIdentifier
name GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromCustomName Name
functionName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> Name -> GQLNameIdentifier
C.fromAutogeneratedName $$(G.litName "arguments")
updateColumnsFieldName :: GQLNameIdentifier
updateColumnsFieldName :: GQLNameIdentifier
updateColumnsFieldName = (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["update", "columns"])
affectedRowsFieldName :: GQLNameIdentifier
affectedRowsFieldName :: GQLNameIdentifier
affectedRowsFieldName = (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["affected", "rows"])
pkColumnsFieldName :: GQLNameIdentifier
pkColumnsFieldName :: GQLNameIdentifier
pkColumnsFieldName = (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["pk", "columns"])