Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
MSSQL Types Internal
Types for Transact-SQL aka T-SQL; the language of SQL Server.
In this module we define various MS SQL Server specific data types used for T-SQL generation.
These types are also used as underlying types in the Backend 'MSSQL
instance
which is defined in Hasura.Backends.MSSQL.Instances.Types.
We convert RQL IR ASTs to types defined here in the Hasura.Backends.MSSQL.FromIr module, and we implement pretty-printing for these types in the Hasura.Backends.MSSQL.ToQuery module.
NOTE: Various type class instances (including simple once such as Eq and Show) are implemented in the Hasura.Backends.MSSQL.Types.Instances module.
Synopsis
- type Column (b :: BackendType) = ColumnName
- type ColumnType (b :: BackendType) = ScalarType
- type Value = Value
- data UnifiedColumn = UnifiedColumn {
- name :: ColumnName
- type' :: ScalarType
- data UnifiedTableName = UnifiedTableName {}
- data UnifiedObjectRelationship = UnifiedObjectRelationship {
- using :: UnifiedUsing
- name :: Text
- data UnifiedArrayRelationship = UnifiedArrayRelationship {
- using :: UnifiedUsing
- name :: Text
- newtype UnifiedUsing = UnifiedUsing {}
- data UnifiedOn = UnifiedOn {
- table :: UnifiedTableName
- column :: Text
- data BooleanOperators a
- = ASTContains a
- | ASTCrosses a
- | ASTEquals a
- | ASTIntersects a
- | ASTOverlaps a
- | ASTTouches a
- | ASTWithin a
- data Select = Select {
- selectWith :: Maybe With
- selectTop :: Top
- selectProjections :: [Projection]
- selectFrom :: Maybe From
- selectJoins :: [Join]
- selectWhere :: Where
- selectFor :: For
- selectOrderBy :: Maybe (NonEmpty OrderBy)
- selectOffset :: Maybe Expression
- emptySelect :: Select
- newtype OutputColumn = OutputColumn {}
- data Inserted = Inserted
- data Deleted = Deleted
- data Output t = Output {
- outputType :: t
- outputColumns :: [OutputColumn]
- type InsertOutput = Output Inserted
- newtype Values = Values [Expression]
- data Insert = Insert {}
- data SetValue
- data SetIdentityInsert = SetIdentityInsert {}
- type DeleteOutput = Output Deleted
- data Delete = Delete {}
- data Merge = Merge {}
- data MergeUsing = MergeUsing {}
- data MergeOn = MergeOn {
- mergeOnColumns :: [ColumnName]
- data MergeWhenMatched = MergeWhenMatched {}
- newtype MergeWhenNotMatched = MergeWhenNotMatched {}
- data SelectIntoTempTable = SelectIntoTempTable {}
- data SITTConstraints
- data InsertValuesIntoTempTable = InsertValuesIntoTempTable {}
- newtype TempTableName = TempTableName Text
- data SomeTableName
- data TempTable = TempTable {
- ttName :: TempTableName
- ttColumns :: [ColumnName]
- data Reselect = Reselect {}
- data OrderBy = OrderBy {}
- data Order
- data NullsOrder
- data For
- data ForJson = ForJson {}
- data Root
- data JsonCardinality
- data Projection
- data Join = Join {}
- data JoinSource
- data JoinAlias = JoinAlias {}
- newtype Where = Where [Expression]
- newtype With = With (NonEmpty (Aliased CTEBody))
- data CTEBody
- data TempTableDDL
- = CreateTemp { }
- | InsertTemp { }
- | DropTemp { }
- data Declare = Declare {
- dName :: Text
- dType :: ScalarType
- dValue :: Expression
- data Top
- data Expression
- = ValueExpression 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
- data FunctionApplicationExpression = FunExpISNULL Expression Expression
- data MethodApplicationExpression = MethExpSTAsText
- data JsonPath
- data Aggregate
- data Countable name
- = StarCountable
- | NonNullFieldCountable name
- | DistinctCountable name
- data From
- fromAlias :: From -> EntityAlias
- data OpenJson = OpenJson {}
- data JsonFieldSpec
- data Aliased a = Aliased {
- aliasedThing :: a
- aliasedAlias :: Text
- newtype SchemaName = SchemaName {}
- data TableName = TableName {}
- data FieldName = FieldName {
- fieldName :: Text
- fieldNameEntity :: Text
- data Comment
- newtype EntityAlias = EntityAlias {}
- columnNameToFieldName :: ColumnName -> EntityAlias -> FieldName
- data Op
- data SpatialOp
- newtype ColumnName = ColumnName {}
- newtype ConstraintName = ConstraintName {}
- data FunctionName = FunctionName {}
- data QueryWithDDL a = QueryWithDDL {
- qwdBeforeSteps :: [TempTableDDL]
- qwdQuery :: a
- qwdAfterSteps :: [TempTableDDL]
- 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
- mkMSSQLScalarTypeName :: MonadError QErr m => ScalarType -> m Name
- parseScalarType :: Text -> ScalarType
- parseScalarValue :: ScalarType -> Value -> Either QErr Value
- isComparableType :: ScalarType -> Bool
- isNumType :: ScalarType -> Bool
- getGQLTableName :: TableName -> Either QErr Name
- getGQLFunctionName :: FunctionName -> Either QErr Name
- snakeCaseName :: Text -> SchemaName -> Text
- getTableIdentifier :: TableName -> Either QErr GQLNameIdentifier
- namingConventionSupport :: SupportedNamingCase
- stringTypes :: [ScalarType]
- geoTypes :: [ScalarType]
Documentation
type Column (b :: BackendType) = ColumnName Source #
type ColumnType (b :: BackendType) = ScalarType Source #
data UnifiedColumn Source #
Instances
data UnifiedTableName Source #
Instances
data UnifiedObjectRelationship Source #
Instances
data UnifiedArrayRelationship Source #
Instances
newtype UnifiedUsing Source #
Instances
UnifiedOn | |
|
Instances
data BooleanOperators a Source #
ASTContains a | |
ASTCrosses a | |
ASTEquals a | |
ASTIntersects a | |
ASTOverlaps a | |
ASTTouches a | |
ASTWithin a |
Instances
Select | |
|
Instances
emptySelect :: Select Source #
newtype OutputColumn Source #
Instances
Instances
Instances
Output | |
|
Instances
type InsertOutput = Output Inserted Source #
Instances
Data Values Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Values -> c Values # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Values # toConstr :: Values -> Constr # dataTypeOf :: Values -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Values) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Values) # gmapT :: (forall b. Data b => b -> b) -> Values -> Values # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Values -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Values -> r # gmapQ :: (forall d. Data d => d -> u) -> Values -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Values -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Values -> m Values # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Values -> m Values # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Values -> m Values # | |
Generic Values Source # | |
Show Values Source # | |
NFData Values Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq Values Source # | |
Hashable Values Source # | |
type Rep Values Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep Values = D1 ('MetaData "Values" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'True) (C1 ('MetaCons "Values" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Expression]))) |
Insert | |
|
Instances
Data Insert Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Insert -> c Insert # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Insert # toConstr :: Insert -> Constr # dataTypeOf :: Insert -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Insert) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Insert) # gmapT :: (forall b. Data b => b -> b) -> Insert -> Insert # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Insert -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Insert -> r # gmapQ :: (forall d. Data d => d -> u) -> Insert -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Insert -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Insert -> m Insert # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Insert -> m Insert # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Insert -> m Insert # | |
Generic Insert Source # | |
Show Insert Source # | |
NFData Insert Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq Insert Source # | |
Hashable Insert Source # | |
type Rep Insert Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep Insert = D1 ('MetaData "Insert" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "Insert" 'PrefixI 'True) ((S1 ('MetaSel ('Just "insertTable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TableName) :*: S1 ('MetaSel ('Just "insertColumns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ColumnName])) :*: (S1 ('MetaSel ('Just "insertOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 InsertOutput) :*: (S1 ('MetaSel ('Just "insertTempTable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TempTable) :*: S1 ('MetaSel ('Just "insertValues") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Values]))))) |
type DeleteOutput = Output Deleted Source #
Instances
Data Delete Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Delete -> c Delete # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Delete # toConstr :: Delete -> Constr # dataTypeOf :: Delete -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Delete) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Delete) # gmapT :: (forall b. Data b => b -> b) -> Delete -> Delete # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Delete -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Delete -> r # gmapQ :: (forall d. Data d => d -> u) -> Delete -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Delete -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Delete -> m Delete # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Delete -> m Delete # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Delete -> m Delete # | |
Generic Delete Source # | |
Show Delete Source # | |
NFData Delete Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq Delete Source # | |
Hashable Delete Source # | |
type Rep Delete Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep Delete = D1 ('MetaData "Delete" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "Delete" 'PrefixI 'True) ((S1 ('MetaSel ('Just "deleteTable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Aliased TableName)) :*: S1 ('MetaSel ('Just "deleteOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DeleteOutput)) :*: (S1 ('MetaSel ('Just "deleteTempTable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TempTable) :*: S1 ('MetaSel ('Just "deleteWhere") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Where)))) |
MERGE statement. Used for upserts and is responsible for actually inserting or updating the data in the table.
Instances
data MergeUsing Source #
The USING
section of a MERGE
statement.
Specifies the temp table schema where the input values are.
Instances
The ON
section of a MERGE
statement.
Which columns to match on?
Instances
Data MergeOn Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MergeOn -> c MergeOn # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MergeOn # toConstr :: MergeOn -> Constr # dataTypeOf :: MergeOn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MergeOn) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MergeOn) # gmapT :: (forall b. Data b => b -> b) -> MergeOn -> MergeOn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MergeOn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MergeOn -> r # gmapQ :: (forall d. Data d => d -> u) -> MergeOn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MergeOn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MergeOn -> m MergeOn # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MergeOn -> m MergeOn # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MergeOn -> m MergeOn # | |
Generic MergeOn Source # | |
Show MergeOn Source # | |
NFData MergeOn Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq MergeOn Source # | |
Hashable MergeOn Source # | |
type Rep MergeOn Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep MergeOn = D1 ('MetaData "MergeOn" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "MergeOn" 'PrefixI 'True) (S1 ('MetaSel ('Just "mergeOnColumns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ColumnName]))) |
data MergeWhenMatched Source #
The WHEN MATCHED
section of a MERGE
statement.
Which columns to update when match_columns
match (including presets),
and on which condition to actually update the values.
Instances
newtype MergeWhenNotMatched Source #
The WHEN MATCHED
section of a MERGE
statement.
Which columns to insert?
Instances
data SelectIntoTempTable Source #
SELECT INTO temporary table statement without values. Used to create a temporary table with the same schema as an existing table.
Instances
data SITTConstraints Source #
When creating a temporary table from an existing table schema,
what should we do with the constraints (such as IDENTITY
?)
Instances
data InsertValuesIntoTempTable Source #
Simple insert into a temporary table.
InsertValuesIntoTempTable | |
|
Instances
newtype TempTableName Source #
A temporary table name is prepended by a hash-sign
Instances
data SomeTableName Source #
A name of a regular table or temporary table
Instances
TempTable | |
|
Instances
Data TempTable Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TempTable -> c TempTable # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TempTable # toConstr :: TempTable -> Constr # dataTypeOf :: TempTable -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TempTable) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TempTable) # gmapT :: (forall b. Data b => b -> b) -> TempTable -> TempTable # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TempTable -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TempTable -> r # gmapQ :: (forall d. Data d => d -> u) -> TempTable -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TempTable -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TempTable -> m TempTable # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TempTable -> m TempTable # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TempTable -> m TempTable # | |
Generic TempTable Source # | |
Show TempTable Source # | |
NFData TempTable Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq TempTable Source # | |
Hashable TempTable Source # | |
type Rep TempTable Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep TempTable = D1 ('MetaData "TempTable" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "TempTable" 'PrefixI 'True) (S1 ('MetaSel ('Just "ttName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TempTableName) :*: S1 ('MetaSel ('Just "ttColumns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ColumnName]))) |
A version of Select
without a FROM
clause. This means it can only project expressions already selected in adjacent join clauses, hence the name reselect
.
Instances
Data Reselect Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Reselect -> c Reselect # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Reselect # toConstr :: Reselect -> Constr # dataTypeOf :: Reselect -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Reselect) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reselect) # gmapT :: (forall b. Data b => b -> b) -> Reselect -> Reselect # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Reselect -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Reselect -> r # gmapQ :: (forall d. Data d => d -> u) -> Reselect -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Reselect -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Reselect -> m Reselect # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Reselect -> m Reselect # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Reselect -> m Reselect # | |
Generic Reselect Source # | |
Show Reselect Source # | |
NFData Reselect Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq Reselect Source # | |
Hashable Reselect Source # | |
type Rep Reselect Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep Reselect = D1 ('MetaData "Reselect" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "Reselect" 'PrefixI 'True) (S1 ('MetaSel ('Just "reselectProjections") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Projection]) :*: (S1 ('MetaSel ('Just "reselectFor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 For) :*: S1 ('MetaSel ('Just "reselectWhere") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Where)))) |
Instances
Data OrderBy Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderBy -> c OrderBy # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderBy # toConstr :: OrderBy -> Constr # dataTypeOf :: OrderBy -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OrderBy) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderBy) # gmapT :: (forall b. Data b => b -> b) -> OrderBy -> OrderBy # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderBy -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderBy -> r # gmapQ :: (forall d. Data d => d -> u) -> OrderBy -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderBy -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderBy -> m OrderBy # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderBy -> m OrderBy # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderBy -> m OrderBy # | |
Generic OrderBy Source # | |
Show OrderBy Source # | |
NFData OrderBy Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq OrderBy Source # | |
Hashable OrderBy Source # | |
type Rep OrderBy Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep OrderBy = D1 ('MetaData "OrderBy" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "OrderBy" 'PrefixI 'True) ((S1 ('MetaSel ('Just "orderByFieldName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FieldName) :*: S1 ('MetaSel ('Just "orderByOrder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Order)) :*: (S1 ('MetaSel ('Just "orderByNullsOrder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 NullsOrder) :*: S1 ('MetaSel ('Just "orderByType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ScalarType))))) |
Instances
FromJSON Order Source # | |
ToJSON Order Source # | |
Data Order Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Order -> c Order # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Order # dataTypeOf :: Order -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Order) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Order) # gmapT :: (forall b. Data b => b -> b) -> Order -> Order # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Order -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Order -> r # gmapQ :: (forall d. Data d => d -> u) -> Order -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Order -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Order -> m Order # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Order -> m Order # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Order -> m Order # | |
Generic Order Source # | |
Show Order Source # | |
NFData Order Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq Order Source # | |
Hashable Order Source # | |
Lift Order Source # | |
type Rep Order Source # | |
data NullsOrder Source #
Instances
Instances
Data For Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> For -> c For # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c For # dataTypeOf :: For -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c For) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c For) # gmapT :: (forall b. Data b => b -> b) -> For -> For # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> For -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> For -> r # gmapQ :: (forall d. Data d => d -> u) -> For -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> For -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> For -> m For # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> For -> m For # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> For -> m For # | |
Generic For Source # | |
Show For Source # | |
NFData For Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq For Source # | |
Hashable For Source # | |
type Rep For Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep For = D1 ('MetaData "For" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "JsonFor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ForJson)) :+: C1 ('MetaCons "NoFor" 'PrefixI 'False) (U1 :: Type -> Type)) |
Instances
Data ForJson Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForJson -> c ForJson # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ForJson # toConstr :: ForJson -> Constr # dataTypeOf :: ForJson -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ForJson) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForJson) # gmapT :: (forall b. Data b => b -> b) -> ForJson -> ForJson # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForJson -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForJson -> r # gmapQ :: (forall d. Data d => d -> u) -> ForJson -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForJson -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForJson -> m ForJson # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForJson -> m ForJson # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForJson -> m ForJson # | |
Generic ForJson Source # | |
Show ForJson Source # | |
NFData ForJson Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq ForJson Source # | |
Hashable ForJson Source # | |
type Rep ForJson Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep ForJson = D1 ('MetaData "ForJson" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "ForJson" 'PrefixI 'True) (S1 ('MetaSel ('Just "jsonCardinality") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 JsonCardinality) :*: S1 ('MetaSel ('Just "jsonRoot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Root))) |
Instances
Data Root Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Root -> c Root # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Root # dataTypeOf :: Root -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Root) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Root) # gmapT :: (forall b. Data b => b -> b) -> Root -> Root # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Root -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Root -> r # gmapQ :: (forall d. Data d => d -> u) -> Root -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Root -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Root -> m Root # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Root -> m Root # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Root -> m Root # | |
Generic Root Source # | |
Show Root Source # | |
NFData Root Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq Root Source # | |
Hashable Root Source # | |
type Rep Root Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep Root = D1 ('MetaData "Root" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "NoRoot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Root" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))) |
data JsonCardinality Source #
Instances
data Projection Source #
ExpressionProjection (Aliased Expression) | |
FieldNameProjection (Aliased FieldName) | |
AggregateProjection (Aliased Aggregate) | |
StarProjection |
Instances
Join | |
|
Instances
Data Join Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Join -> c Join # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Join # dataTypeOf :: Join -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Join) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Join) # gmapT :: (forall b. Data b => b -> b) -> Join -> Join # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Join -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Join -> r # gmapQ :: (forall d. Data d => d -> u) -> Join -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Join -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Join -> m Join # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Join -> m Join # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Join -> m Join # | |
Generic Join Source # | |
Show Join Source # | |
NFData Join Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq Join Source # | |
Hashable Join Source # | |
type Rep Join Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep Join = D1 ('MetaData "Join" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "Join" 'PrefixI 'True) (S1 ('MetaSel ('Just "joinSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 JoinSource) :*: (S1 ('MetaSel ('Just "joinJoinAlias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 JoinAlias) :*: S1 ('MetaSel ('Just "joinWhere") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Where)))) |
data JoinSource Source #
Instances
Instances
Data JoinAlias Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JoinAlias -> c JoinAlias # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JoinAlias # toConstr :: JoinAlias -> Constr # dataTypeOf :: JoinAlias -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JoinAlias) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JoinAlias) # gmapT :: (forall b. Data b => b -> b) -> JoinAlias -> JoinAlias # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JoinAlias -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JoinAlias -> r # gmapQ :: (forall d. Data d => d -> u) -> JoinAlias -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> JoinAlias -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> JoinAlias -> m JoinAlias # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinAlias -> m JoinAlias # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinAlias -> m JoinAlias # | |
Generic JoinAlias Source # | |
Show JoinAlias Source # | |
NFData JoinAlias Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq JoinAlias Source # | |
Hashable JoinAlias Source # | |
type Rep JoinAlias Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep JoinAlias = D1 ('MetaData "JoinAlias" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "JoinAlias" 'PrefixI 'True) (S1 ('MetaSel ('Just "joinAliasEntity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "joinAliasField") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)))) |
Instances
Data Where Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Where -> c Where # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Where # dataTypeOf :: Where -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Where) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Where) # gmapT :: (forall b. Data b => b -> b) -> Where -> Where # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Where -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Where -> r # gmapQ :: (forall d. Data d => d -> u) -> Where -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Where -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Where -> m Where # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Where -> m Where # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Where -> m Where # | |
Monoid Where Source # | |
Semigroup Where Source # | |
Generic Where Source # | |
Show Where Source # | |
NFData Where Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq Where Source # | |
Hashable Where Source # | |
type Rep Where Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep Where = D1 ('MetaData "Where" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'True) (C1 ('MetaCons "Where" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Expression]))) |
Instances
Data With Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> With -> c With # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c With # dataTypeOf :: With -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c With) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c With) # gmapT :: (forall b. Data b => b -> b) -> With -> With # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> With -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> With -> r # gmapQ :: (forall d. Data d => d -> u) -> With -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> With -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> With -> m With # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> With -> m With # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> With -> m With # | |
Semigroup With Source # | |
Generic With Source # | |
Show With Source # | |
NFData With Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq With Source # | |
Hashable With Source # | |
type Rep With Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances |
Something that can appear in a CTE body.
Instances
Data CTEBody Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CTEBody -> c CTEBody # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CTEBody # toConstr :: CTEBody -> Constr # dataTypeOf :: CTEBody -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CTEBody) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CTEBody) # gmapT :: (forall b. Data b => b -> b) -> CTEBody -> CTEBody # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CTEBody -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CTEBody -> r # gmapQ :: (forall d. Data d => d -> u) -> CTEBody -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CTEBody -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CTEBody -> m CTEBody # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CTEBody -> m CTEBody # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CTEBody -> m CTEBody # | |
Generic CTEBody Source # | |
Show CTEBody Source # | |
NFData CTEBody Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq CTEBody Source # | |
Hashable CTEBody Source # | |
type Rep CTEBody Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep CTEBody = D1 ('MetaData "CTEBody" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "CTESelect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Select)) :+: C1 ('MetaCons "CTEUnsafeRawSQL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (InterpolatedQuery Expression)))) |
data TempTableDDL Source #
Extra query steps that can be emitted from the main query to do things like setup temp tables
CreateTemp | create a temp table |
InsertTemp | insert output of a statement into a temp table |
DropTemp | Drop a temp table |
Declare | |
|
Instances
Data Top Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Top -> c Top # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Top # dataTypeOf :: Top -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Top) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Top) # gmapT :: (forall b. Data b => b -> b) -> Top -> Top # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Top -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Top -> r # gmapQ :: (forall d. Data d => d -> u) -> Top -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Top -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Top -> m Top # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Top -> m Top # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Top -> m Top # | |
Monoid Top Source # | |
Semigroup Top Source # | |
Generic Top Source # | |
Show Top Source # | |
NFData Top Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq Top Source # | |
Hashable Top Source # | |
type Rep Top Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep Top = D1 ('MetaData "Top" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "NoTop" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Top" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int))) |
data Expression Source #
ValueExpression Value | |
AndExpression [Expression] | |
OrExpression [Expression] | |
NotExpression Expression | |
ExistsExpression Select | |
SelectExpression Select | |
IsNullExpression Expression | |
IsNotNullExpression Expression | |
ColumnExpression FieldName | |
JsonQueryExpression Expression | This one acts like a "cast to JSON" and makes SQL Server behave like it knows your field is JSON and not double-encode it. |
ToStringExpression Expression | |
MethodApplicationExpression Expression MethodApplicationExpression | |
FunctionApplicationExpression FunctionApplicationExpression | |
JsonValueExpression Expression JsonPath | This is for getting actual atomic values out of a JSON string. |
OpExpression Op Expression Expression | |
ListExpression [Expression] | |
STOpExpression SpatialOp Expression Expression | |
CastExpression Expression ScalarType DataLength | |
ConditionalExpression Expression Expression Expression | "CASE WHEN (expression) THEN (expression) ELSE (expression) END" |
DefaultExpression | The |
Instances
data DataLength Source #
Data type describing the length of a datatype. Used in CastExpression
s.
Instances
data FunctionApplicationExpression Source #
SQL functions application: some_function(e1, e2, ..)
.
Instances
data MethodApplicationExpression Source #
Object expression method application: (expression).text(e1, e2, ..)
Instances
Instances
Instances
Instances
Functor Countable Source # | |
FromJSON n => FromJSON (Countable n) Source # | |
ToJSON n => ToJSON (Countable n) Source # | |
Data n => Data (Countable n) Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Countable n -> c (Countable n) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Countable n) # toConstr :: Countable n -> Constr # dataTypeOf :: Countable n -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Countable n)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Countable n)) # gmapT :: (forall b. Data b => b -> b) -> Countable n -> Countable n # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Countable n -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Countable n -> r # gmapQ :: (forall d. Data d => d -> u) -> Countable n -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Countable n -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Countable n -> m (Countable n) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Countable n -> m (Countable n) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Countable n -> m (Countable n) # | |
Generic (Countable n) Source # | |
Show n => Show (Countable n) Source # | |
NFData n => NFData (Countable n) Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq n => Eq (Countable n) Source # | |
Hashable n => Hashable (Countable n) Source # | |
type Rep (Countable n) Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep (Countable n) = D1 ('MetaData "Countable" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "StarCountable" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NonNullFieldCountable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 n)) :+: C1 ('MetaCons "DistinctCountable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 n)))) |
FromQualifiedTable (Aliased TableName) | |
FromOpenJson (Aliased OpenJson) | |
FromSelect (Aliased Select) | |
FromIdentifier Text | |
FromTempTable (Aliased TempTableName) |
Instances
fromAlias :: From -> EntityAlias Source #
Extract the name bound in a From
clause as an EntityAlias
.
Instances
Data OpenJson Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OpenJson -> c OpenJson # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OpenJson # toConstr :: OpenJson -> Constr # dataTypeOf :: OpenJson -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OpenJson) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OpenJson) # gmapT :: (forall b. Data b => b -> b) -> OpenJson -> OpenJson # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OpenJson -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OpenJson -> r # gmapQ :: (forall d. Data d => d -> u) -> OpenJson -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OpenJson -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OpenJson -> m OpenJson # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OpenJson -> m OpenJson # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OpenJson -> m OpenJson # | |
Generic OpenJson Source # | |
Show OpenJson Source # | |
NFData OpenJson Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq OpenJson Source # | |
Hashable OpenJson Source # | |
type Rep OpenJson Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep OpenJson = D1 ('MetaData "OpenJson" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "OpenJson" 'PrefixI 'True) (S1 ('MetaSel ('Just "openJsonExpression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Expression) :*: S1 ('MetaSel ('Just "openJsonWith") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (NonEmpty JsonFieldSpec))))) |
data JsonFieldSpec Source #
ScalarField ScalarType DataLength Text (Maybe JsonPath) | |
JsonField Text (Maybe JsonPath) | |
StringField Text (Maybe JsonPath) |
Instances
Aliased | |
|
Instances
Functor Aliased Source # | |
Data a => Data (Aliased a) Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Aliased a -> c (Aliased a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Aliased a) # toConstr :: Aliased a -> Constr # dataTypeOf :: Aliased a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Aliased a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Aliased a)) # gmapT :: (forall b. Data b => b -> b) -> Aliased a -> Aliased a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Aliased a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Aliased a -> r # gmapQ :: (forall d. Data d => d -> u) -> Aliased a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Aliased a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Aliased a -> m (Aliased a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Aliased a -> m (Aliased a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Aliased a -> m (Aliased a) # | |
Generic (Aliased a) Source # | |
Show a => Show (Aliased a) Source # | |
NFData a => NFData (Aliased a) Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq a => Eq (Aliased a) Source # | |
Hashable a => Hashable (Aliased a) Source # | |
type Rep (Aliased a) Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep (Aliased a) = D1 ('MetaData "Aliased" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "Aliased" 'PrefixI 'True) (S1 ('MetaSel ('Just "aliasedThing") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "aliasedAlias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))) |
newtype SchemaName Source #
Instances
Instances
Instances
FromJSON FieldName Source # | |
ToJSON FieldName Source # | |
Data FieldName Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldName -> c FieldName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldName # toConstr :: FieldName -> Constr # dataTypeOf :: FieldName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FieldName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldName) # gmapT :: (forall b. Data b => b -> b) -> FieldName -> FieldName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldName -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldName -> m FieldName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldName -> m FieldName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldName -> m FieldName # | |
Generic FieldName Source # | |
Show FieldName Source # | |
NFData FieldName Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq FieldName Source # | |
Hashable FieldName Source # | |
type Rep FieldName Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep FieldName = D1 ('MetaData "FieldName" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "FieldName" 'PrefixI 'True) (S1 ('MetaSel ('Just "fieldName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "fieldNameEntity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))) |
newtype EntityAlias Source #
Instances
Instances
Data Op Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Op -> c Op # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Op # dataTypeOf :: Op -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Op) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Op) # gmapT :: (forall b. Data b => b -> b) -> Op -> Op # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Op -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Op -> r # gmapQ :: (forall d. Data d => d -> u) -> Op -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Op -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Op -> m Op # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Op -> m Op # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Op -> m Op # | |
Generic Op Source # | |
Show Op Source # | |
NFData Op Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq Op Source # | |
Hashable Op Source # | |
type Rep Op Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep Op = D1 ('MetaData "Op" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) (((C1 ('MetaCons "LT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LTE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GTE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IN" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "LIKE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NLIKE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NIN" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EQ'" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NEQ'" 'PrefixI 'False) (U1 :: Type -> Type))))) |
Supported operations for spatial data types
Instances
Data SpatialOp Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpatialOp -> c SpatialOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SpatialOp # toConstr :: SpatialOp -> Constr # dataTypeOf :: SpatialOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SpatialOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SpatialOp) # gmapT :: (forall b. Data b => b -> b) -> SpatialOp -> SpatialOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpatialOp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpatialOp -> r # gmapQ :: (forall d. Data d => d -> u) -> SpatialOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SpatialOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpatialOp -> m SpatialOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpatialOp -> m SpatialOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpatialOp -> m SpatialOp # | |
Generic SpatialOp Source # | |
Show SpatialOp Source # | |
NFData SpatialOp Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances | |
Eq SpatialOp Source # | |
Hashable SpatialOp Source # | |
type Rep SpatialOp Source # | |
Defined in Hasura.Backends.MSSQL.Types.Instances type Rep SpatialOp = D1 ('MetaData "SpatialOp" "Hasura.Backends.MSSQL.Types.Internal" "graphql-engine-1.0.0-inplace" 'False) ((C1 ('MetaCons "STEquals" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "STContains" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "STCrosses" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "STIntersects" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "STOverlaps" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "STWithin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "STTouches" 'PrefixI 'False) (U1 :: Type -> Type)))) |
newtype ColumnName Source #
Column name of some database table -- this differs to FieldName that is used for referring to things within a query.
Instances
newtype ConstraintName Source #
Instances
data FunctionName Source #
Instances
data QueryWithDDL a Source #
type for a query generated from IR along with any DDL actions
QueryWithDDL | |
|
data ScalarType Source #
Derived from the odbc package.
Instances
scalarTypeDBName :: DataLength -> ScalarType -> Text Source #
mkMSSQLScalarTypeName :: MonadError QErr m => ScalarType -> m Name Source #
parseScalarType :: Text -> ScalarType Source #
parseScalarValue :: ScalarType -> Value -> Either QErr Value Source #
isComparableType :: ScalarType -> Bool Source #
isNumType :: ScalarType -> Bool Source #
snakeCaseName :: Text -> SchemaName -> Text Source #
stringTypes :: [ScalarType] Source #
geoTypes :: [ScalarType] Source #