{-# LANGUAGE DuplicateRecordFields #-}
module Hasura.Backends.MSSQL.Types.Internal
( Aggregate (..),
Aliased (..),
BooleanOperators (..),
Column,
ColumnName (..),
columnNameToFieldName,
ColumnType,
Comment (..),
ConstraintName (..),
Countable (..),
DataLength (..),
Delete (..),
DeleteOutput,
EntityAlias (..),
fromAlias,
Expression (..),
FieldName (..),
For (..),
ForJson (..),
From (..),
FunctionApplicationExpression (..),
FunctionName (..),
MergeUsing (..),
MergeOn (..),
MergeWhenMatched (..),
MergeWhenNotMatched (..),
Merge (..),
Insert (..),
InsertOutput,
Join (..),
JoinAlias (..),
JoinSource (..),
JsonCardinality (..),
JsonFieldSpec (..),
JsonPath (..),
MethodApplicationExpression (..),
NullsOrder (..),
Op (..),
OpenJson (..),
Order (..),
OrderBy (..),
OutputColumn (..),
Inserted (..),
Deleted (..),
Output (..),
Projection (..),
Reselect (..),
Root (..),
ScalarType (..),
SchemaName (..),
Select (..),
SetIdentityInsert (..),
TempTableName (..),
SomeTableName (..),
TempTable (..),
SetValue (..),
SelectIntoTempTable (..),
SITTConstraints (..),
InsertValuesIntoTempTable (..),
SpatialOp (..),
TableName (..),
Top (..),
UnifiedArrayRelationship (..),
UnifiedColumn (..),
UnifiedObjectRelationship (..),
UnifiedOn (..),
UnifiedTableName (..),
UnifiedUsing (..),
Value,
Values (..),
Where (..),
With (..),
emptySelect,
geoTypes,
getGQLTableName,
getTableIdentifier,
isComparableType,
isNumType,
mkMSSQLScalarTypeName,
parseScalarValue,
scalarTypeDBName,
snakeCaseTableName,
stringTypes,
namingConventionSupport,
)
where
import Data.Aeson qualified as J
import Data.Text.Casing (GQLNameIdentifier)
import Data.Text.Casing qualified as C
import Database.ODBC.SQLServer qualified as ODBC
import Hasura.Base.Error
import Hasura.GraphQL.Parser.Name qualified as GName
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
import Hasura.RQL.Types.Backend (SupportedNamingCase (..))
import Hasura.SQL.Backend
import Hasura.SQL.GeoJSON qualified as Geo
import Hasura.SQL.WKT qualified as WKT
import Language.GraphQL.Draft.Syntax qualified as G
import Language.Haskell.TH.Syntax (Lift)
type Column (b :: BackendType) = ColumnName
type ColumnType (b :: BackendType) = ScalarType
type Value = ODBC.Value
data UnifiedColumn = UnifiedColumn
{ UnifiedColumn -> ColumnName
name :: ColumnName,
UnifiedColumn -> ScalarType
type' :: ScalarType
}
data UnifiedTableName = UnifiedTableName
{ UnifiedTableName -> Text
schema :: Text,
UnifiedTableName -> Text
name :: Text
}
data UnifiedObjectRelationship = UnifiedObjectRelationship
{ UnifiedObjectRelationship -> UnifiedUsing
using :: UnifiedUsing,
UnifiedObjectRelationship -> Text
name :: Text
}
data UnifiedArrayRelationship = UnifiedArrayRelationship
{ UnifiedArrayRelationship -> UnifiedUsing
using :: UnifiedUsing,
UnifiedArrayRelationship -> Text
name :: Text
}
newtype UnifiedUsing = UnifiedUsing
{ UnifiedUsing -> UnifiedOn
foreign_key_constraint_on :: UnifiedOn
}
data UnifiedOn = UnifiedOn
{ UnifiedOn -> UnifiedTableName
table :: UnifiedTableName,
UnifiedOn -> Text
column :: Text
}
data BooleanOperators a
= ASTContains a
| ASTCrosses a
| ASTEquals a
| ASTIntersects a
| ASTOverlaps a
| ASTTouches a
| ASTWithin a
data Select = Select
{ Select -> Maybe With
selectWith :: (Maybe With),
Select -> Top
selectTop :: Top,
Select -> [Projection]
selectProjections :: [Projection],
Select -> Maybe From
selectFrom :: (Maybe From),
Select -> [Join]
selectJoins :: [Join],
Select -> Where
selectWhere :: Where,
Select -> For
selectFor :: For,
Select -> Maybe (NonEmpty OrderBy)
selectOrderBy :: (Maybe (NonEmpty OrderBy)),
Select -> Maybe Expression
selectOffset :: (Maybe Expression)
}
emptySelect :: Select
emptySelect :: Select
emptySelect =
Select :: Maybe With
-> Top
-> [Projection]
-> Maybe From
-> [Join]
-> Where
-> For
-> Maybe (NonEmpty OrderBy)
-> Maybe Expression
-> Select
Select
{ $sel:selectWith:Select :: Maybe With
selectWith = Maybe With
forall a. Maybe a
Nothing,
$sel:selectFrom:Select :: Maybe From
selectFrom = Maybe From
forall a. Maybe a
Nothing,
$sel:selectTop:Select :: Top
selectTop = Top
NoTop,
$sel:selectProjections:Select :: [Projection]
selectProjections = [],
$sel:selectJoins:Select :: [Join]
selectJoins = [],
$sel:selectWhere:Select :: Where
selectWhere = [Expression] -> Where
Where [],
$sel:selectOrderBy:Select :: Maybe (NonEmpty OrderBy)
selectOrderBy = Maybe (NonEmpty OrderBy)
forall a. Maybe a
Nothing,
$sel:selectFor:Select :: For
selectFor = For
NoFor,
$sel:selectOffset:Select :: Maybe Expression
selectOffset = Maybe Expression
forall a. Maybe a
Nothing
}
newtype OutputColumn = OutputColumn {OutputColumn -> ColumnName
unOutputColumn :: ColumnName}
data Inserted = Inserted
data Deleted = Deleted
data Output t = Output
{ Output t -> t
outputType :: t,
Output t -> [OutputColumn]
outputColumns :: [OutputColumn]
}
type InsertOutput = Output Inserted
newtype Values = Values [Expression]
data Insert = Insert
{ Insert -> TableName
insertTable :: TableName,
Insert -> [ColumnName]
insertColumns :: [ColumnName],
Insert -> InsertOutput
insertOutput :: InsertOutput,
Insert -> TempTable
insertTempTable :: TempTable,
Insert -> [Values]
insertValues :: [Values]
}
data SetValue
= SetON
| SetOFF
data SetIdentityInsert = SetIdentityInsert
{ SetIdentityInsert -> SomeTableName
setTable :: SomeTableName,
SetIdentityInsert -> SetValue
setValue :: SetValue
}
type DeleteOutput = Output Deleted
data Delete = Delete
{ Delete -> Aliased TableName
deleteTable :: (Aliased TableName),
Delete -> DeleteOutput
deleteOutput :: DeleteOutput,
Delete -> TempTable
deleteTempTable :: TempTable,
Delete -> Where
deleteWhere :: Where
}
data Merge = Merge
{ Merge -> TableName
mergeTargetTable :: TableName,
Merge -> MergeUsing
mergeUsing :: MergeUsing,
Merge -> MergeOn
mergeOn :: MergeOn,
Merge -> MergeWhenMatched
mergeWhenMatched :: MergeWhenMatched,
Merge -> MergeWhenNotMatched
mergeWhenNotMatched :: MergeWhenNotMatched,
Merge -> InsertOutput
mergeInsertOutput :: InsertOutput,
Merge -> TempTable
mergeOutputTempTable :: TempTable
}
data MergeUsing = MergeUsing
{ MergeUsing -> TempTableName
mergeUsingTempTable :: TempTableName,
MergeUsing -> [ColumnName]
mergeUsingColumns :: [ColumnName]
}
data MergeOn = MergeOn
{ MergeOn -> [ColumnName]
mergeOnColumns :: [ColumnName]
}
data MergeWhenMatched = MergeWhenMatched
{ MergeWhenMatched -> [ColumnName]
mwmUpdateColumns :: [ColumnName],
MergeWhenMatched -> Expression
mwmCondition :: Expression,
MergeWhenMatched -> HashMap ColumnName Expression
mwmUpdatePreset :: HashMap ColumnName Expression
}
newtype MergeWhenNotMatched = MergeWhenNotMatched
{ MergeWhenNotMatched -> [ColumnName]
mergeWhenNotMatchedInsertColumns :: [ColumnName]
}
data SelectIntoTempTable = SelectIntoTempTable
{ SelectIntoTempTable -> TempTableName
sittTempTableName :: TempTableName,
SelectIntoTempTable -> [UnifiedColumn]
sittColumns :: [UnifiedColumn],
SelectIntoTempTable -> TableName
sittFromTableName :: TableName,
SelectIntoTempTable -> SITTConstraints
sittConstraints :: SITTConstraints
}
data SITTConstraints
= KeepConstraints
| RemoveConstraints
data InsertValuesIntoTempTable = InsertValuesIntoTempTable
{ InsertValuesIntoTempTable -> TempTableName
ivittTempTableName :: TempTableName,
InsertValuesIntoTempTable -> [ColumnName]
ivittColumns :: [ColumnName],
InsertValuesIntoTempTable -> [Values]
ivittValues :: [Values]
}
newtype TempTableName = TempTableName Text
data SomeTableName
= RegularTableName TableName
| TemporaryTableName TempTableName
data TempTable = TempTable
{ TempTable -> TempTableName
ttName :: TempTableName,
TempTable -> [ColumnName]
ttColumns :: [ColumnName]
}
data Reselect = Reselect
{ Reselect -> [Projection]
reselectProjections :: [Projection],
Reselect -> For
reselectFor :: For,
Reselect -> Where
reselectWhere :: Where
}
data OrderBy = OrderBy
{ OrderBy -> FieldName
orderByFieldName :: FieldName,
OrderBy -> Order
orderByOrder :: Order,
OrderBy -> NullsOrder
orderByNullsOrder :: NullsOrder,
OrderBy -> Maybe ScalarType
orderByType :: Maybe ScalarType
}
data Order
= AscOrder
| DescOrder
data NullsOrder
= NullsFirst
| NullsLast
| NullsAnyOrder
data For
= JsonFor ForJson
| NoFor
data ForJson = ForJson
{ ForJson -> JsonCardinality
jsonCardinality :: JsonCardinality,
ForJson -> Root
jsonRoot :: Root
}
data Root
= NoRoot
| Root Text
data JsonCardinality
= JsonArray
| JsonSingleton
data Projection
= ExpressionProjection (Aliased Expression)
| FieldNameProjection (Aliased FieldName)
| AggregateProjection (Aliased Aggregate)
| StarProjection
data Join = Join
{ Join -> JoinSource
joinSource :: JoinSource,
Join -> JoinAlias
joinJoinAlias :: JoinAlias
}
data JoinSource
= JoinSelect Select
| JoinReselect Reselect
data JoinAlias = JoinAlias
{ JoinAlias -> Text
joinAliasEntity :: Text,
JoinAlias -> Maybe Text
joinAliasField :: Maybe Text
}
newtype Where
= Where [Expression]
newtype With
= With (NonEmpty (Aliased Select))
data Top
= NoTop
| Top Int
data Expression
= ValueExpression ODBC.Value
| AndExpression [Expression]
| OrExpression [Expression]
| NotExpression Expression
| ExistsExpression Select
| SelectExpression Select
| IsNullExpression Expression
| IsNotNullExpression Expression
| ColumnExpression FieldName
|
JsonQueryExpression Expression
| ToStringExpression Expression
| MethodApplicationExpression Expression MethodApplicationExpression
| FunctionApplicationExpression FunctionApplicationExpression
|
JsonValueExpression Expression JsonPath
| OpExpression Op Expression Expression
| ListExpression [Expression]
| STOpExpression SpatialOp Expression Expression
| CastExpression Expression ScalarType DataLength
|
ConditionalExpression Expression Expression Expression
|
DefaultExpression
data DataLength = DataLengthUnspecified | DataLengthInt Int | DataLengthMax
data FunctionApplicationExpression
= FunExpISNULL Expression Expression
data MethodApplicationExpression
= MethExpSTAsText
data JsonPath
= RootPath
| FieldPath JsonPath Text
| IndexPath JsonPath Integer
data Aggregate
= CountAggregate (Countable FieldName)
| OpAggregate Text [Expression]
| TextAggregate Text
data Countable name
= StarCountable
| NonNullFieldCountable name
| DistinctCountable name
deriving instance Functor Countable
data From
= FromQualifiedTable (Aliased TableName)
| FromOpenJson (Aliased OpenJson)
| FromSelect (Aliased Select)
| FromIdentifier Text
| FromTempTable (Aliased TempTableName)
fromAlias :: From -> EntityAlias
fromAlias :: From -> EntityAlias
fromAlias (FromQualifiedTable Aliased {Text
$sel:aliasedAlias:Aliased :: forall a. Aliased a -> Text
aliasedAlias :: Text
aliasedAlias}) = Text -> EntityAlias
EntityAlias Text
aliasedAlias
fromAlias (FromOpenJson Aliased {Text
aliasedAlias :: Text
$sel:aliasedAlias:Aliased :: forall a. Aliased a -> Text
aliasedAlias}) = Text -> EntityAlias
EntityAlias Text
aliasedAlias
fromAlias (FromSelect Aliased {Text
aliasedAlias :: Text
$sel:aliasedAlias:Aliased :: forall a. Aliased a -> Text
aliasedAlias}) = Text -> EntityAlias
EntityAlias Text
aliasedAlias
fromAlias (FromIdentifier Text
identifier) = Text -> EntityAlias
EntityAlias Text
identifier
fromAlias (FromTempTable Aliased {Text
aliasedAlias :: Text
$sel:aliasedAlias:Aliased :: forall a. Aliased a -> Text
aliasedAlias}) = Text -> EntityAlias
EntityAlias Text
aliasedAlias
data OpenJson = OpenJson
{ OpenJson -> Expression
openJsonExpression :: Expression,
OpenJson -> Maybe (NonEmpty JsonFieldSpec)
openJsonWith :: Maybe (NonEmpty JsonFieldSpec)
}
data JsonFieldSpec
= ScalarField ScalarType DataLength Text (Maybe JsonPath)
| JsonField Text (Maybe JsonPath)
| StringField Text (Maybe JsonPath)
data Aliased a = Aliased
{ Aliased a -> a
aliasedThing :: a,
Aliased a -> Text
aliasedAlias :: Text
}
newtype SchemaName = SchemaName {SchemaName -> Text
_unSchemaName :: Text}
deriving (Int -> SchemaName -> ShowS
[SchemaName] -> ShowS
SchemaName -> String
(Int -> SchemaName -> ShowS)
-> (SchemaName -> String)
-> ([SchemaName] -> ShowS)
-> Show SchemaName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SchemaName] -> ShowS
$cshowList :: [SchemaName] -> ShowS
show :: SchemaName -> String
$cshow :: SchemaName -> String
showsPrec :: Int -> SchemaName -> ShowS
$cshowsPrec :: Int -> SchemaName -> ShowS
Show, SchemaName -> SchemaName -> Bool
(SchemaName -> SchemaName -> Bool)
-> (SchemaName -> SchemaName -> Bool) -> Eq SchemaName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SchemaName -> SchemaName -> Bool
$c/= :: SchemaName -> SchemaName -> Bool
== :: SchemaName -> SchemaName -> Bool
$c== :: SchemaName -> SchemaName -> Bool
Eq, Eq SchemaName
Eq SchemaName
-> (SchemaName -> SchemaName -> Ordering)
-> (SchemaName -> SchemaName -> Bool)
-> (SchemaName -> SchemaName -> Bool)
-> (SchemaName -> SchemaName -> Bool)
-> (SchemaName -> SchemaName -> Bool)
-> (SchemaName -> SchemaName -> SchemaName)
-> (SchemaName -> SchemaName -> SchemaName)
-> Ord SchemaName
SchemaName -> SchemaName -> Bool
SchemaName -> SchemaName -> Ordering
SchemaName -> SchemaName -> SchemaName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SchemaName -> SchemaName -> SchemaName
$cmin :: SchemaName -> SchemaName -> SchemaName
max :: SchemaName -> SchemaName -> SchemaName
$cmax :: SchemaName -> SchemaName -> SchemaName
>= :: SchemaName -> SchemaName -> Bool
$c>= :: SchemaName -> SchemaName -> Bool
> :: SchemaName -> SchemaName -> Bool
$c> :: SchemaName -> SchemaName -> Bool
<= :: SchemaName -> SchemaName -> Bool
$c<= :: SchemaName -> SchemaName -> Bool
< :: SchemaName -> SchemaName -> Bool
$c< :: SchemaName -> SchemaName -> Bool
compare :: SchemaName -> SchemaName -> Ordering
$ccompare :: SchemaName -> SchemaName -> Ordering
$cp1Ord :: Eq SchemaName
Ord, Typeable SchemaName
DataType
Constr
Typeable SchemaName
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SchemaName -> c SchemaName)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SchemaName)
-> (SchemaName -> Constr)
-> (SchemaName -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SchemaName))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SchemaName))
-> ((forall b. Data b => b -> b) -> SchemaName -> SchemaName)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r)
-> (forall u. (forall d. Data d => d -> u) -> SchemaName -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> SchemaName -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName)
-> Data SchemaName
SchemaName -> DataType
SchemaName -> Constr
(forall b. Data b => b -> b) -> SchemaName -> SchemaName
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SchemaName -> c SchemaName
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SchemaName
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> SchemaName -> u
forall u. (forall d. Data d => d -> u) -> SchemaName -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SchemaName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SchemaName -> c SchemaName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SchemaName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SchemaName)
$cSchemaName :: Constr
$tSchemaName :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
gmapMp :: (forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
gmapM :: (forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SchemaName -> m SchemaName
gmapQi :: Int -> (forall d. Data d => d -> u) -> SchemaName -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SchemaName -> u
gmapQ :: (forall d. Data d => d -> u) -> SchemaName -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SchemaName -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SchemaName -> r
gmapT :: (forall b. Data b => b -> b) -> SchemaName -> SchemaName
$cgmapT :: (forall b. Data b => b -> b) -> SchemaName -> SchemaName
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SchemaName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SchemaName)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SchemaName)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SchemaName)
dataTypeOf :: SchemaName -> DataType
$cdataTypeOf :: SchemaName -> DataType
toConstr :: SchemaName -> Constr
$ctoConstr :: SchemaName -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SchemaName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SchemaName
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SchemaName -> c SchemaName
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SchemaName -> c SchemaName
$cp1Data :: Typeable SchemaName
Data, [SchemaName] -> Value
[SchemaName] -> Encoding
SchemaName -> Value
SchemaName -> Encoding
(SchemaName -> Value)
-> (SchemaName -> Encoding)
-> ([SchemaName] -> Value)
-> ([SchemaName] -> Encoding)
-> ToJSON SchemaName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SchemaName] -> Encoding
$ctoEncodingList :: [SchemaName] -> Encoding
toJSONList :: [SchemaName] -> Value
$ctoJSONList :: [SchemaName] -> Value
toEncoding :: SchemaName -> Encoding
$ctoEncoding :: SchemaName -> Encoding
toJSON :: SchemaName -> Value
$ctoJSON :: SchemaName -> Value
J.ToJSON, Value -> Parser [SchemaName]
Value -> Parser SchemaName
(Value -> Parser SchemaName)
-> (Value -> Parser [SchemaName]) -> FromJSON SchemaName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SchemaName]
$cparseJSONList :: Value -> Parser [SchemaName]
parseJSON :: Value -> Parser SchemaName
$cparseJSON :: Value -> Parser SchemaName
J.FromJSON, SchemaName -> ()
(SchemaName -> ()) -> NFData SchemaName
forall a. (a -> ()) -> NFData a
rnf :: SchemaName -> ()
$crnf :: SchemaName -> ()
NFData, (forall x. SchemaName -> Rep SchemaName x)
-> (forall x. Rep SchemaName x -> SchemaName) -> Generic SchemaName
forall x. Rep SchemaName x -> SchemaName
forall x. SchemaName -> Rep SchemaName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SchemaName x -> SchemaName
$cfrom :: forall x. SchemaName -> Rep SchemaName x
Generic, Eq SchemaName
Eq SchemaName
-> (Accesses -> SchemaName -> SchemaName -> Bool)
-> Cacheable SchemaName
Accesses -> SchemaName -> SchemaName -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> SchemaName -> SchemaName -> Bool
$cunchanged :: Accesses -> SchemaName -> SchemaName -> Bool
$cp1Cacheable :: Eq SchemaName
Cacheable, String -> SchemaName
(String -> SchemaName) -> IsString SchemaName
forall a. (String -> a) -> IsString a
fromString :: String -> SchemaName
$cfromString :: String -> SchemaName
IsString, Int -> SchemaName -> Int
SchemaName -> Int
(Int -> SchemaName -> Int)
-> (SchemaName -> Int) -> Hashable SchemaName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: SchemaName -> Int
$chash :: SchemaName -> Int
hashWithSalt :: Int -> SchemaName -> Int
$chashWithSalt :: Int -> SchemaName -> Int
Hashable, SchemaName -> Q Exp
SchemaName -> Q (TExp SchemaName)
(SchemaName -> Q Exp)
-> (SchemaName -> Q (TExp SchemaName)) -> Lift SchemaName
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: SchemaName -> Q (TExp SchemaName)
$cliftTyped :: SchemaName -> Q (TExp SchemaName)
lift :: SchemaName -> Q Exp
$clift :: SchemaName -> Q Exp
Lift)
data TableName = TableName
{ TableName -> Text
tableName :: Text,
TableName -> SchemaName
tableSchema :: SchemaName
}
data FieldName = FieldName
{ FieldName -> Text
fieldName :: Text,
FieldName -> Text
fieldNameEntity :: Text
}
data = DueToPermission | RequestedSingleObject
newtype EntityAlias = EntityAlias
{ EntityAlias -> Text
entityAliasText :: Text
}
columnNameToFieldName :: ColumnName -> EntityAlias -> FieldName
columnNameToFieldName :: ColumnName -> EntityAlias -> FieldName
columnNameToFieldName (ColumnName Text
fieldName) EntityAlias {$sel:entityAliasText:EntityAlias :: EntityAlias -> Text
entityAliasText = Text
fieldNameEntity} =
FieldName :: Text -> Text -> FieldName
FieldName {Text
fieldName :: Text
$sel:fieldName:FieldName :: Text
fieldName, Text
fieldNameEntity :: Text
$sel:fieldNameEntity:FieldName :: Text
fieldNameEntity}
data Op
= LT
| LTE
| GT
| GTE
| IN
| LIKE
| NLIKE
| NIN
| EQ'
| NEQ'
data SpatialOp
= STEquals
| STContains
| STCrosses
| STIntersects
| STOverlaps
| STWithin
| STTouches
newtype ColumnName = ColumnName {ColumnName -> Text
columnNameText :: Text}
newtype ConstraintName = ConstraintName {ConstraintName -> Text
constraintNameText :: Text}
newtype FunctionName = FunctionName {FunctionName -> Text
functionNameText :: Text}
data ScalarType
= CharType
| NumericType
| DecimalType
| IntegerType
| SmallintType
| FloatType
| RealType
| DateType
| Ss_time2Type
| VarcharType
| WcharType
| WvarcharType
| WtextType
| TimestampType
| TextType
| BinaryType
| VarbinaryType
| BigintType
| TinyintType
| BitType
| GuidType
| GeographyType
| GeometryType
| UnknownType Text
scalarTypeDBName :: DataLength -> ScalarType -> Text
scalarTypeDBName :: DataLength -> ScalarType -> Text
scalarTypeDBName DataLength
dataLength = \case
ScalarType
CharType -> Text
"char"
ScalarType
NumericType -> Text
"numeric"
ScalarType
DecimalType -> Text
"decimal"
ScalarType
IntegerType -> Text
"int"
ScalarType
SmallintType -> Text
"smallint"
ScalarType
FloatType -> Text
"float"
ScalarType
RealType -> Text
"real"
ScalarType
DateType -> Text
"date"
ScalarType
Ss_time2Type -> Text
"time"
ScalarType
VarcharType -> Text
"varchar" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> DataLength -> Text
fromDataLength DataLength
dataLength
ScalarType
WcharType -> Text
"nchar"
ScalarType
WvarcharType -> Text
"nvarchar" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> DataLength -> Text
fromDataLength DataLength
dataLength
ScalarType
WtextType -> Text
"ntext"
ScalarType
TextType -> Text
"text"
ScalarType
TimestampType -> Text
"timestamp"
ScalarType
BinaryType -> Text
"binary"
ScalarType
VarbinaryType -> Text
"varbinary" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> DataLength -> Text
fromDataLength DataLength
dataLength
ScalarType
BigintType -> Text
"bigint"
ScalarType
TinyintType -> Text
"tinyint"
ScalarType
BitType -> Text
"bit"
ScalarType
GuidType -> Text
"uniqueidentifier"
ScalarType
GeographyType -> Text
"geography"
ScalarType
GeometryType -> Text
"geometry"
UnknownType Text
t -> Text
t
fromDataLength :: DataLength -> Text
fromDataLength :: DataLength -> Text
fromDataLength = \case
DataLength
DataLengthUnspecified -> Text
""
DataLengthInt Int
len -> Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow Int
len Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
DataLength
DataLengthMax -> Text
"(max)"
mkMSSQLScalarTypeName :: MonadError QErr m => ScalarType -> m G.Name
mkMSSQLScalarTypeName :: ScalarType -> m Name
mkMSSQLScalarTypeName = \case
ScalarType
CharType -> Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure Name
GName._String
ScalarType
WcharType -> Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure Name
GName._String
ScalarType
WvarcharType -> Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure Name
GName._String
ScalarType
VarcharType -> Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure Name
GName._String
ScalarType
WtextType -> Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure Name
GName._String
ScalarType
TextType -> Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure Name
GName._String
ScalarType
FloatType -> Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure Name
GName._Float
ScalarType
IntegerType -> Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure Name
GName._Int
ScalarType
BitType -> Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure Name
GName._Boolean
ScalarType
scalarType ->
Text -> Maybe Name
G.mkName (DataLength -> ScalarType -> Text
scalarTypeDBName DataLength
DataLengthUnspecified ScalarType
scalarType)
Maybe Name -> m Name -> m Name
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` Code -> Text -> m Name
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400
Code
ValidationFailed
( Text
"cannot use SQL type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> DataLength -> ScalarType -> Text
scalarTypeDBName DataLength
DataLengthUnspecified ScalarType
scalarType Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" in the GraphQL schema because its name is not a "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"valid GraphQL identifier"
)
parseScalarValue :: ScalarType -> J.Value -> Either QErr Value
parseScalarValue :: ScalarType -> Value -> Either QErr Value
parseScalarValue ScalarType
scalarType Value
jValue = case ScalarType
scalarType of
ScalarType
CharType -> Text -> Value
ODBC.TextValue (Text -> Value) -> Either QErr Text -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Text
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
VarcharType -> Text -> Value
ODBC.TextValue (Text -> Value) -> Either QErr Text -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Text
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
TextType -> Text -> Value
ODBC.TextValue (Text -> Value) -> Either QErr Text -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Text
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
WcharType -> Text -> Value
ODBC.TextValue (Text -> Value) -> Either QErr Text -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Text
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
WvarcharType -> Text -> Value
ODBC.TextValue (Text -> Value) -> Either QErr Text -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Text
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
WtextType -> Text -> Value
ODBC.TextValue (Text -> Value) -> Either QErr Text -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Text
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
IntegerType -> Int -> Value
ODBC.IntValue (Int -> Value) -> Either QErr Int -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Int
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
SmallintType -> Int -> Value
ODBC.IntValue (Int -> Value) -> Either QErr Int -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Int
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
BigintType -> Int -> Value
ODBC.IntValue (Int -> Value) -> Either QErr Int -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Int
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
TinyintType -> Int -> Value
ODBC.IntValue (Int -> Value) -> Either QErr Int -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Int
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
NumericType -> Float -> Value
ODBC.FloatValue (Float -> Value) -> Either QErr Float -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Float
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
DecimalType -> Float -> Value
ODBC.FloatValue (Float -> Value) -> Either QErr Float -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Float
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
FloatType -> Float -> Value
ODBC.FloatValue (Float -> Value) -> Either QErr Float -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Float
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
RealType -> Float -> Value
ODBC.FloatValue (Float -> Value) -> Either QErr Float -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Float
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
BitType -> Word8 -> Value
ODBC.ByteValue (Word8 -> Value) -> Either QErr Word8 -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Word8
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
GeographyType -> Text -> Value
ODBC.TextValue (Text -> Value) -> Either QErr Text -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Text
parseGeoTypes Value
jValue
ScalarType
GeometryType -> Text -> Value
ODBC.TextValue (Text -> Value) -> Either QErr Text -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Text
parseGeoTypes Value
jValue
ScalarType
BinaryType -> Binary -> Value
ODBC.BinaryValue (Binary -> Value) -> (Text -> Binary) -> Text -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Binary
ODBC.Binary (ByteString -> Binary) -> (Text -> ByteString) -> Text -> Binary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
txtToBs (Text -> Value) -> Either QErr Text -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Text
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
VarbinaryType -> Binary -> Value
ODBC.BinaryValue (Binary -> Value) -> (Text -> Binary) -> Text -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Binary
ODBC.Binary (ByteString -> Binary) -> (Text -> ByteString) -> Text -> Binary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
txtToBs (Text -> Value) -> Either QErr Text -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Text
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
Ss_time2Type -> TimeOfDay -> Value
ODBC.TimeOfDayValue (TimeOfDay -> Value) -> Either QErr TimeOfDay -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr TimeOfDay
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
TimestampType -> LocalTime -> Value
ODBC.LocalTimeValue (LocalTime -> Value) -> Either QErr LocalTime -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr LocalTime
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
DateType -> Day -> Value
ODBC.DayValue (Day -> Value) -> Either QErr Day -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Day
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
ScalarType
GuidType -> Text -> Value
ODBC.TextValue (Text -> Value) -> Either QErr Text -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Text
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
UnknownType Text
_ -> Text -> Value
ODBC.TextValue (Text -> Value) -> Either QErr Text -> Either QErr Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Either QErr Text
forall a. FromJSON a => Value -> Either QErr a
parseJValue Value
jValue
where
parseJValue :: (J.FromJSON a) => J.Value -> Either QErr a
parseJValue :: Value -> Either QErr a
parseJValue = (Value -> Parser a) -> Value -> Either QErr a
forall (m :: * -> *) v a. QErrM m => (v -> Parser a) -> v -> m a
runAesonParser Value -> Parser a
forall a. FromJSON a => Value -> Parser a
J.parseJSON
parseGeoTypes :: J.Value -> Either QErr Text
parseGeoTypes :: Value -> Either QErr Text
parseGeoTypes Value
jv =
(Value -> Parser Text) -> Value -> Either QErr Text
forall (m :: * -> *) v a. QErrM m => (v -> Parser a) -> v -> m a
runAesonParser (FromJSON Text => Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
J.parseJSON @Text) Value
jv Either QErr Text -> Either QErr Text -> Either QErr Text
forall a. Semigroup a => a -> a -> a
<> Value -> Either QErr Text
parseGeoJSONAsWKT Value
jValue
parseGeoJSONAsWKT :: J.Value -> Either QErr Text
parseGeoJSONAsWKT :: Value -> Either QErr Text
parseGeoJSONAsWKT Value
jv =
(Value -> Parser GeometryWithCRS)
-> Value -> Either QErr GeometryWithCRS
forall (m :: * -> *) v a. QErrM m => (v -> Parser a) -> v -> m a
runAesonParser (FromJSON GeometryWithCRS => Value -> Parser GeometryWithCRS
forall a. FromJSON a => Value -> Parser a
J.parseJSON @Geo.GeometryWithCRS) Value
jv
Either QErr GeometryWithCRS
-> (GeometryWithCRS -> Either QErr Text) -> Either QErr Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (WKT -> Text) -> Either QErr WKT -> Either QErr Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap WKT -> Text
WKT.getWKT (Either QErr WKT -> Either QErr Text)
-> (GeometryWithCRS -> Either QErr WKT)
-> GeometryWithCRS
-> Either QErr Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GeometryWithCRS -> Either QErr WKT
forall a. ToWKT a => a -> Either QErr WKT
WKT.toWKT
isComparableType, isNumType :: ScalarType -> Bool
isComparableType :: ScalarType -> Bool
isComparableType = \case
ScalarType
BinaryType -> Bool
False
ScalarType
VarbinaryType -> Bool
False
ScalarType
BitType -> Bool
False
ScalarType
GuidType -> Bool
False
ScalarType
_ -> Bool
True
isNumType :: ScalarType -> Bool
isNumType = \case
ScalarType
NumericType -> Bool
True
ScalarType
DecimalType -> Bool
True
ScalarType
IntegerType -> Bool
True
ScalarType
SmallintType -> Bool
True
ScalarType
FloatType -> Bool
True
ScalarType
RealType -> Bool
True
ScalarType
BigintType -> Bool
True
ScalarType
TinyintType -> Bool
True
ScalarType
_ -> Bool
False
getGQLTableName :: TableName -> Either QErr G.Name
getGQLTableName :: TableName -> Either QErr Name
getGQLTableName TableName
tn = do
let textName :: Text
textName = TableName -> Text
snakeCaseTableName TableName
tn
Maybe Name -> Either QErr Name -> Either QErr Name
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
onNothing (Text -> Maybe Name
G.mkName (Text -> Maybe Name) -> Text -> Maybe Name
forall a b. (a -> b) -> a -> b
$ TableName -> Text
snakeCaseTableName TableName
tn) (Either QErr Name -> Either QErr Name)
-> Either QErr Name -> Either QErr Name
forall a b. (a -> b) -> a -> b
$
Code -> Text -> Either QErr Name
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
ValidationFailed (Text -> Either QErr Name) -> Text -> Either QErr Name
forall a b. (a -> b) -> a -> b
$
Text
"cannot include " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
textName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" in the GraphQL schema because it is not a valid GraphQL identifier"
snakeCaseTableName :: TableName -> Text
snakeCaseTableName :: TableName -> Text
snakeCaseTableName (TableName Text
tableName (SchemaName Text
tableSchema)) =
if Text
tableSchema Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"dbo"
then Text
tableName
else Text
tableSchema Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tableName
getTableIdentifier :: TableName -> Either QErr GQLNameIdentifier
getTableIdentifier :: TableName -> Either QErr GQLNameIdentifier
getTableIdentifier TableName
tName = do
Name
gqlTableName <- TableName -> Either QErr Name
getGQLTableName TableName
tName
GQLNameIdentifier -> Either QErr GQLNameIdentifier
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GQLNameIdentifier -> Either QErr GQLNameIdentifier)
-> GQLNameIdentifier -> Either QErr GQLNameIdentifier
forall a b. (a -> b) -> a -> b
$ Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
gqlTableName
namingConventionSupport :: SupportedNamingCase
namingConventionSupport :: SupportedNamingCase
namingConventionSupport = SupportedNamingCase
OnlyHasuraCase
stringTypes :: [ScalarType]
stringTypes :: [ScalarType]
stringTypes =
[ ScalarType
CharType,
ScalarType
VarcharType,
ScalarType
TextType,
ScalarType
WcharType,
ScalarType
WvarcharType,
ScalarType
WtextType
]
geoTypes :: [ScalarType]
geoTypes :: [ScalarType]
geoTypes = [ScalarType
GeometryType, ScalarType
GeographyType]