Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Postgres SQL DML
Provide types and combinators for defining Postgres SQL queries and mutations.
Synopsis
- data Select = Select [(TableAlias, InnerCTE)] (Maybe DistinctExpr) [Extractor] (Maybe FromExp) (Maybe WhereFrag) (Maybe GroupByExp) (Maybe HavingExp) (Maybe OrderByExp) (Maybe LimitExp) (Maybe OffsetExp)
- mkSelect :: Select
- dummySelectList :: [Extractor]
- newtype LimitExp = LimitExp SQLExp
- newtype OffsetExp = OffsetExp SQLExp
- newtype OrderByExp = OrderByExp (NonEmpty OrderByItem)
- data OrderByItem = OrderByItem SQLExp (Maybe OrderType) (Maybe NullsOrder)
- data OrderType
- data NullsOrder
- newtype GroupByExp = GroupByExp [SQLExp]
- newtype FromExp = FromExp [FromItem]
- mkIdenFromExp :: TableIdentifier -> FromExp
- mkSimpleFromExp :: QualifiedTable -> FromExp
- mkSelFromExp :: Bool -> Select -> TableName -> FromItem
- mkRowExp :: [Extractor] -> SQLExp
- newtype HavingExp = HavingExp BoolExp
- newtype WhereFrag = WhereFrag BoolExp
- mkSIdenExp :: IsIdentifier a => a -> SQLExp
- mkQIdenExp :: IsIdentifier b => TableIdentifier -> b -> SQLExp
- data Qual
- mkQual :: QualifiedTable -> Qual
- mkQIdentifier :: IsIdentifier b => TableIdentifier -> b -> QIdentifier
- mkQIdentifierTable :: IsIdentifier a => QualifiedTable -> a -> QIdentifier
- mkIdentifierSQLExp :: forall a. IsIdentifier a => Qual -> a -> SQLExp
- data QIdentifier = QIdentifier Qual Identifier
- data ColumnOp = ColumnOp {}
- newtype SQLOp = SQLOp Text
- incOp :: SQLOp
- mulOp :: SQLOp
- jsonbPathOp :: SQLOp
- jsonbConcatOp :: SQLOp
- jsonbDeleteOp :: SQLOp
- jsonbDeleteAtPathOp :: SQLOp
- newtype TypeAnn = TypeAnn Text
- mkTypeAnn :: CollectableType PGScalarType -> TypeAnn
- intTypeAnn :: TypeAnn
- numericTypeAnn :: TypeAnn
- textTypeAnn :: TypeAnn
- textArrTypeAnn :: TypeAnn
- jsonTypeAnn :: TypeAnn
- jsonbTypeAnn :: TypeAnn
- boolTypeAnn :: TypeAnn
- data CountType columnType
- = CTStar
- | CTSimple [columnType]
- | CTDistinct [columnType]
- newtype TupleExp = TupleExp [SQLExp]
- data SQLExp
- = SEPrep Int
- | SENull
- | SELit Text
- | SEUnsafe Text
- | SESelect Select
- | SEStar (Maybe Qual)
- | SEIdentifier Identifier
- | SERowIdentifier Identifier
- | SEQIdentifier QIdentifier
- | SEFnApp Text [SQLExp] (Maybe OrderByExp)
- | SEOpApp SQLOp [SQLExp]
- | SETyAnn SQLExp TypeAnn
- | SECond BoolExp SQLExp SQLExp
- | SEBool BoolExp
- | SEExcluded Identifier
- | SEArray [SQLExp]
- | SEArrayIndex SQLExp SQLExp
- | SETuple TupleExp
- | SECount (CountType QIdentifier)
- | SENamedArg Identifier SQLExp
- | SEFunction FunctionExp
- newtype ColumnAlias = ColumnAlias {}
- mkColumnAlias :: Text -> ColumnAlias
- tableIdentifierToColumnAlias :: TableIdentifier -> ColumnAlias
- toColumnAlias :: IsIdentifier a => a -> ColumnAlias
- newtype TableAlias = TableAlias {}
- mkTableAlias :: Text -> TableAlias
- tableAliasToIdentifier :: TableAlias -> TableIdentifier
- toTableAlias :: IsIdentifier a => a -> TableAlias
- countStar :: SQLExp
- intToSQLExp :: Int -> SQLExp
- int64ToSQLExp :: Int64 -> SQLExp
- data Extractor = Extractor SQLExp (Maybe ColumnAlias)
- mkSQLOpExp :: SQLOp -> SQLExp -> SQLExp -> SQLExp
- columnDefaultValue :: SQLExp
- handleIfNull :: SQLExp -> SQLExp -> SQLExp
- applyJsonBuildObj :: [SQLExp] -> SQLExp
- applyJsonBuildArray :: [SQLExp] -> SQLExp
- applyRowToJson :: [Extractor] -> SQLExp
- applyUppercase :: SQLExp -> SQLExp
- mkExtr :: IsIdentifier a => a -> Extractor
- data DistinctExpr
- data FunctionArgs = FunctionArgs [SQLExp] (HashMap Text SQLExp)
- data FunctionDefinitionListItem = FunctionDefinitionListItem {}
- data FunctionAlias = FunctionAlias TableAlias (Maybe [FunctionDefinitionListItem])
- mkFunctionAlias :: QualifiedObject FunctionName -> Maybe [(ColumnAlias, PGScalarType)] -> FunctionAlias
- data FunctionExp = FunctionExp QualifiedFunction FunctionArgs (Maybe FunctionAlias)
- data FromItem
- mkSelFromItem :: Select -> TableAlias -> FromItem
- mkSelectWithFromItem :: SelectWithG Select -> TableAlias -> FromItem
- mkLateralFromItem :: Select -> TableAlias -> FromItem
- newtype Lateral = Lateral Bool
- data JoinExpr = JoinExpr FromItem JoinType FromItem JoinCond
- data JoinType
- data JoinCond
- = JoinOn BoolExp
- | JoinUsing [Identifier]
- data BoolExp
- simplifyBoolExp :: BoolExp -> BoolExp
- mkExists :: FromItem -> BoolExp -> BoolExp
- data BinOp
- data CompareOp
- data SQLDelete = SQLDelete QualifiedTable (Maybe UsingExp) (Maybe WhereFrag) (Maybe RetExp)
- data SQLUpdate = SQLUpdate {}
- newtype SetExp = SetExp [SetExpItem]
- newtype SetExpItem = SetExpItem (PGCol, SQLExp)
- buildUpsertSetExp :: [PGCol] -> HashMap PGCol SQLExp -> SetExp
- newtype RetExp = RetExp [Extractor]
- selectStar :: Extractor
- selectStar' :: Qual -> Extractor
- returningStar :: RetExp
- data SQLConflictTarget
- data SQLConflict
- newtype ValuesExp = ValuesExp [TupleExp]
- data SQLInsert = SQLInsert {
- siTable :: QualifiedTable
- siCols :: [PGCol]
- siValues :: ValuesExp
- siConflict :: Maybe SQLConflict
- siRet :: Maybe RetExp
- data TopLevelCTE
- data InnerCTE
- data SelectWithG statement = SelectWith {
- swCTEs :: [(TableAlias, statement)]
- swSelect :: Select
- type SelectWith = SelectWithG TopLevelCTE
Documentation
An select statement that does not require mutation CTEs.
See SelectWithG
or SelectWithG
for select statements with mutations as CTEs.
Select [(TableAlias, InnerCTE)] (Maybe DistinctExpr) [Extractor] (Maybe FromExp) (Maybe WhereFrag) (Maybe GroupByExp) (Maybe HavingExp) (Maybe OrderByExp) (Maybe LimitExp) (Maybe OffsetExp) |
Instances
dummySelectList :: [Extractor] Source #
A dummy select list to avoid an empty select list, which doesn't work for cockroach db.
This is just the value 1
without an alias.
Instances
Data LimitExp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LimitExp -> c LimitExp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LimitExp # toConstr :: LimitExp -> Constr # dataTypeOf :: LimitExp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LimitExp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LimitExp) # gmapT :: (forall b. Data b => b -> b) -> LimitExp -> LimitExp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LimitExp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LimitExp -> r # gmapQ :: (forall d. Data d => d -> u) -> LimitExp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LimitExp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LimitExp -> m LimitExp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitExp -> m LimitExp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LimitExp -> m LimitExp # | |
Show LimitExp Source # | |
NFData LimitExp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq LimitExp Source # | |
ToSQL LimitExp Source # | |
Hashable LimitExp Source # | |
Instances
Data OffsetExp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OffsetExp -> c OffsetExp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OffsetExp # toConstr :: OffsetExp -> Constr # dataTypeOf :: OffsetExp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OffsetExp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OffsetExp) # gmapT :: (forall b. Data b => b -> b) -> OffsetExp -> OffsetExp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OffsetExp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OffsetExp -> r # gmapQ :: (forall d. Data d => d -> u) -> OffsetExp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OffsetExp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OffsetExp -> m OffsetExp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OffsetExp -> m OffsetExp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OffsetExp -> m OffsetExp # | |
Show OffsetExp Source # | |
NFData OffsetExp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq OffsetExp Source # | |
ToSQL OffsetExp Source # | |
Hashable OffsetExp Source # | |
newtype OrderByExp Source #
Instances
data OrderByItem Source #
Instances
Order by ascending or descending
Instances
FromJSON OrderType Source # | |
ToJSON OrderType Source # | |
Data OrderType Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderType -> c OrderType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderType # toConstr :: OrderType -> Constr # dataTypeOf :: OrderType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OrderType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderType) # gmapT :: (forall b. Data b => b -> b) -> OrderType -> OrderType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderType -> r # gmapQ :: (forall d. Data d => d -> u) -> OrderType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderType -> m OrderType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderType -> m OrderType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderType -> m OrderType # | |
Generic OrderType Source # | |
Show OrderType Source # | |
NFData OrderType Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq OrderType Source # | |
ToSQL OrderType Source # | |
Hashable OrderType Source # | |
type Rep OrderType Source # | |
data NullsOrder Source #
Instances
newtype GroupByExp Source #
Instances
Instances
Data FromExp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FromExp -> c FromExp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FromExp # toConstr :: FromExp -> Constr # dataTypeOf :: FromExp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FromExp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FromExp) # gmapT :: (forall b. Data b => b -> b) -> FromExp -> FromExp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromExp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromExp -> r # gmapQ :: (forall d. Data d => d -> u) -> FromExp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FromExp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromExp -> m FromExp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromExp -> m FromExp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromExp -> m FromExp # | |
Show FromExp Source # | |
NFData FromExp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq FromExp Source # | |
ToSQL FromExp Source # | |
Hashable FromExp Source # | |
Instances
Data HavingExp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HavingExp -> c HavingExp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HavingExp # toConstr :: HavingExp -> Constr # dataTypeOf :: HavingExp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HavingExp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HavingExp) # gmapT :: (forall b. Data b => b -> b) -> HavingExp -> HavingExp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HavingExp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HavingExp -> r # gmapQ :: (forall d. Data d => d -> u) -> HavingExp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HavingExp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HavingExp -> m HavingExp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HavingExp -> m HavingExp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HavingExp -> m HavingExp # | |
Show HavingExp Source # | |
NFData HavingExp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq HavingExp Source # | |
ToSQL HavingExp Source # | |
Hashable HavingExp Source # | |
Instances
Data WhereFrag Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WhereFrag -> c WhereFrag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WhereFrag # toConstr :: WhereFrag -> Constr # dataTypeOf :: WhereFrag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WhereFrag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WhereFrag) # gmapT :: (forall b. Data b => b -> b) -> WhereFrag -> WhereFrag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WhereFrag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WhereFrag -> r # gmapQ :: (forall d. Data d => d -> u) -> WhereFrag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WhereFrag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WhereFrag -> m WhereFrag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WhereFrag -> m WhereFrag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WhereFrag -> m WhereFrag # | |
Show WhereFrag Source # | |
NFData WhereFrag Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq WhereFrag Source # | |
ToSQL WhereFrag Source # | |
Hashable WhereFrag Source # | |
mkSIdenExp :: IsIdentifier a => a -> SQLExp Source #
mkQIdenExp :: IsIdentifier b => TableIdentifier -> b -> SQLExp Source #
Instances
Data Qual Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Qual -> c Qual # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Qual # dataTypeOf :: Qual -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Qual) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Qual) # gmapT :: (forall b. Data b => b -> b) -> Qual -> Qual # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Qual -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Qual -> r # gmapQ :: (forall d. Data d => d -> u) -> Qual -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Qual -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Qual -> m Qual # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Qual -> m Qual # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Qual -> m Qual # | |
Generic Qual Source # | |
Show Qual Source # | |
NFData Qual Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq Qual Source # | |
ToSQL Qual Source # | |
Hashable Qual Source # | |
type Rep Qual Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML type Rep Qual = D1 ('MetaData "Qual" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "QualifiedIdentifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TableIdentifier) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe TypeAnn))) :+: (C1 ('MetaCons "QualTable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 QualifiedTable)) :+: C1 ('MetaCons "QualVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))) |
mkQual :: QualifiedTable -> Qual Source #
mkQIdentifier :: IsIdentifier b => TableIdentifier -> b -> QIdentifier Source #
mkQIdentifierTable :: IsIdentifier a => QualifiedTable -> a -> QIdentifier Source #
mkIdentifierSQLExp :: forall a. IsIdentifier a => Qual -> a -> SQLExp Source #
data QIdentifier Source #
Instances
Instances
Data ColumnOp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColumnOp -> c ColumnOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColumnOp # toConstr :: ColumnOp -> Constr # dataTypeOf :: ColumnOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColumnOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColumnOp) # gmapT :: (forall b. Data b => b -> b) -> ColumnOp -> ColumnOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColumnOp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColumnOp -> r # gmapQ :: (forall d. Data d => d -> u) -> ColumnOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ColumnOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ColumnOp -> m ColumnOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ColumnOp -> m ColumnOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ColumnOp -> m ColumnOp # | |
Generic ColumnOp Source # | |
Show ColumnOp Source # | |
NFData ColumnOp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq ColumnOp Source # | |
Hashable ColumnOp Source # | |
type Rep ColumnOp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML type Rep ColumnOp = D1 ('MetaData "ColumnOp" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "ColumnOp" 'PrefixI 'True) (S1 ('MetaSel ('Just "_colOp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLOp) :*: S1 ('MetaSel ('Just "_colExp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp))) |
Instances
Data SQLOp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SQLOp -> c SQLOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SQLOp # dataTypeOf :: SQLOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SQLOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SQLOp) # gmapT :: (forall b. Data b => b -> b) -> SQLOp -> SQLOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SQLOp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SQLOp -> r # gmapQ :: (forall d. Data d => d -> u) -> SQLOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SQLOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SQLOp -> m SQLOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SQLOp -> m SQLOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SQLOp -> m SQLOp # | |
Show SQLOp Source # | |
NFData SQLOp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq SQLOp Source # | |
Hashable SQLOp Source # | |
jsonbPathOp :: SQLOp Source #
Instances
Data TypeAnn Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeAnn -> c TypeAnn # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeAnn # toConstr :: TypeAnn -> Constr # dataTypeOf :: TypeAnn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeAnn) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeAnn) # gmapT :: (forall b. Data b => b -> b) -> TypeAnn -> TypeAnn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeAnn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeAnn -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeAnn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeAnn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeAnn -> m TypeAnn # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeAnn -> m TypeAnn # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeAnn -> m TypeAnn # | |
Show TypeAnn Source # | |
NFData TypeAnn Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq TypeAnn Source # | |
ToSQL TypeAnn Source # | |
Hashable TypeAnn Source # | |
intTypeAnn :: TypeAnn Source #
data CountType columnType Source #
CTStar | |
CTSimple [columnType] | |
CTDistinct [columnType] |
Instances
Foldable CountType Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML fold :: Monoid m => CountType m -> m # foldMap :: Monoid m => (a -> m) -> CountType a -> m # foldMap' :: Monoid m => (a -> m) -> CountType a -> m # foldr :: (a -> b -> b) -> b -> CountType a -> b # foldr' :: (a -> b -> b) -> b -> CountType a -> b # foldl :: (b -> a -> b) -> b -> CountType a -> b # foldl' :: (b -> a -> b) -> b -> CountType a -> b # foldr1 :: (a -> a -> a) -> CountType a -> a # foldl1 :: (a -> a -> a) -> CountType a -> a # toList :: CountType a -> [a] # length :: CountType a -> Int # elem :: Eq a => a -> CountType a -> Bool # maximum :: Ord a => CountType a -> a # minimum :: Ord a => CountType a -> a # | |
Traversable CountType Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Functor CountType Source # | |
Data columnType => Data (CountType columnType) Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CountType columnType -> c (CountType columnType) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CountType columnType) # toConstr :: CountType columnType -> Constr # dataTypeOf :: CountType columnType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (CountType columnType)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CountType columnType)) # gmapT :: (forall b. Data b => b -> b) -> CountType columnType -> CountType columnType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CountType columnType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CountType columnType -> r # gmapQ :: (forall d. Data d => d -> u) -> CountType columnType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CountType columnType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CountType columnType -> m (CountType columnType) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CountType columnType -> m (CountType columnType) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CountType columnType -> m (CountType columnType) # | |
Generic (CountType columnType) Source # | |
Show columnType => Show (CountType columnType) Source # | |
NFData columnType => NFData (CountType columnType) Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq columnType => Eq (CountType columnType) Source # | |
ToSQL (CountType QIdentifier) Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Hashable columnType => Hashable (CountType columnType) Source # | |
type Rep (CountType columnType) Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML type Rep (CountType columnType) = D1 ('MetaData "CountType" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "CTStar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CTSimple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [columnType])) :+: C1 ('MetaCons "CTDistinct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [columnType])))) |
Instances
Data TupleExp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TupleExp -> c TupleExp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TupleExp # toConstr :: TupleExp -> Constr # dataTypeOf :: TupleExp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TupleExp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TupleExp) # gmapT :: (forall b. Data b => b -> b) -> TupleExp -> TupleExp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TupleExp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TupleExp -> r # gmapQ :: (forall d. Data d => d -> u) -> TupleExp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TupleExp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TupleExp -> m TupleExp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TupleExp -> m TupleExp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TupleExp -> m TupleExp # | |
Show TupleExp Source # | |
NFData TupleExp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq TupleExp Source # | |
ToSQL TupleExp Source # | |
Hashable TupleExp Source # | |
SEPrep Int | |
SENull | |
SELit Text | |
SEUnsafe Text | |
SESelect Select | |
SEStar (Maybe Qual) | all fields ( |
SEIdentifier Identifier | A column name |
SERowIdentifier Identifier | SEIdentifier and SERowIdentifier are distinguished for easier rewrite rules |
SEQIdentifier QIdentifier | A qualified column name |
SEFnApp Text [SQLExp] (Maybe OrderByExp) | this is used to apply a sql function to an expression. The |
SEOpApp SQLOp [SQLExp] | |
SETyAnn SQLExp TypeAnn | |
SECond BoolExp SQLExp SQLExp | |
SEBool BoolExp | |
SEExcluded Identifier | |
SEArray [SQLExp] | |
SEArrayIndex SQLExp SQLExp | |
SETuple TupleExp | |
SECount (CountType QIdentifier) | |
SENamedArg Identifier SQLExp | |
SEFunction FunctionExp |
Instances
newtype ColumnAlias Source #
Represents an alias assignment for a column
Instances
mkColumnAlias :: Text -> ColumnAlias Source #
toColumnAlias :: IsIdentifier a => a -> ColumnAlias Source #
newtype TableAlias Source #
Represents an alias assignment for a table, relation or row
Instances
mkTableAlias :: Text -> TableAlias Source #
Create a table alias.
tableAliasToIdentifier :: TableAlias -> TableIdentifier Source #
Create a table identifier from a table alias.
toTableAlias :: IsIdentifier a => a -> TableAlias Source #
intToSQLExp :: Int -> SQLExp Source #
int64ToSQLExp :: Int64 -> SQLExp Source #
Extractor can be used to apply Postgres alias to a column
Instances
Data Extractor Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Extractor -> c Extractor # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Extractor # toConstr :: Extractor -> Constr # dataTypeOf :: Extractor -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Extractor) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Extractor) # gmapT :: (forall b. Data b => b -> b) -> Extractor -> Extractor # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Extractor -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Extractor -> r # gmapQ :: (forall d. Data d => d -> u) -> Extractor -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Extractor -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Extractor -> m Extractor # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Extractor -> m Extractor # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Extractor -> m Extractor # | |
Generic Extractor Source # | |
Show Extractor Source # | |
NFData Extractor Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq Extractor Source # | |
ToSQL Extractor Source # | |
Hashable Extractor Source # | |
type Rep Extractor Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML type Rep Extractor = D1 ('MetaData "Extractor" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "Extractor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ColumnAlias)))) |
applyJsonBuildObj :: [SQLExp] -> SQLExp Source #
applyJsonBuildArray :: [SQLExp] -> SQLExp Source #
applyRowToJson :: [Extractor] -> SQLExp Source #
applyUppercase :: SQLExp -> SQLExp Source #
mkExtr :: IsIdentifier a => a -> Extractor Source #
data DistinctExpr Source #
Instances
data FunctionArgs Source #
Instances
data FunctionDefinitionListItem Source #
Instances
data FunctionAlias Source #
We can alias the result of a function call that returns a SETOF RECORD
by naming the result relation, and the columns and their types. For example:
SELECT * FROM function_returns_record(arg1, arg2 ...) AS relation_name(column_1 column_1_type, column_2 column_2_type, ...)
Note: a function that returns a table (instead of a record) cannot name the types as seen in the above example.
Instances
mkFunctionAlias :: QualifiedObject FunctionName -> Maybe [(ColumnAlias, PGScalarType)] -> FunctionAlias Source #
Construct a function alias which represents the "relation signature" for the function invocation, Using the function name as the relation name, and the columns as the relation schema.
data FunctionExp Source #
A function call
Instances
See from_item
in https://www.postgresql.org/docs/current/sql-select.html
FISimple QualifiedTable (Maybe TableAlias) | A simple table |
FIIdentifier TableIdentifier | An identifier (from CTEs) |
FIFunc FunctionExp | A function call (that should return a relation ( |
FIUnnest [SQLExp] TableAlias [ColumnAlias] |
We have: * The unnest function arguments * The relation alias * A list of column aliases See |
FISelect Lateral Select TableAlias | |
FISelectWith Lateral (SelectWithG Select) TableAlias | |
FIValues ValuesExp TableAlias (Maybe [ColumnAlias]) | |
FIJoin JoinExpr |
Instances
mkSelFromItem :: Select -> TableAlias -> FromItem Source #
mkLateralFromItem :: Select -> TableAlias -> FromItem Source #
Instances
Data Lateral Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Lateral -> c Lateral # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Lateral # toConstr :: Lateral -> Constr # dataTypeOf :: Lateral -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Lateral) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lateral) # gmapT :: (forall b. Data b => b -> b) -> Lateral -> Lateral # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Lateral -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Lateral -> r # gmapQ :: (forall d. Data d => d -> u) -> Lateral -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Lateral -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Lateral -> m Lateral # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Lateral -> m Lateral # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Lateral -> m Lateral # | |
Show Lateral Source # | |
NFData Lateral Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq Lateral Source # | |
ToSQL Lateral Source # | |
Hashable Lateral Source # | |
Instances
Instances
Data JoinType Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JoinType -> c JoinType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JoinType # toConstr :: JoinType -> Constr # dataTypeOf :: JoinType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JoinType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JoinType) # gmapT :: (forall b. Data b => b -> b) -> JoinType -> JoinType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JoinType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JoinType -> r # gmapQ :: (forall d. Data d => d -> u) -> JoinType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> JoinType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> JoinType -> m JoinType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinType -> m JoinType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinType -> m JoinType # | |
Generic JoinType Source # | |
Show JoinType Source # | |
NFData JoinType Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq JoinType Source # | |
ToSQL JoinType Source # | |
Hashable JoinType Source # | |
type Rep JoinType Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML type Rep JoinType = D1 ('MetaData "JoinType" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) ((C1 ('MetaCons "Inner" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LeftOuter" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RightOuter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FullOuter" 'PrefixI 'False) (U1 :: Type -> Type))) |
Instances
Data JoinCond Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JoinCond -> c JoinCond # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JoinCond # toConstr :: JoinCond -> Constr # dataTypeOf :: JoinCond -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JoinCond) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JoinCond) # gmapT :: (forall b. Data b => b -> b) -> JoinCond -> JoinCond # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JoinCond -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JoinCond -> r # gmapQ :: (forall d. Data d => d -> u) -> JoinCond -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> JoinCond -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> JoinCond -> m JoinCond # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinCond -> m JoinCond # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinCond -> m JoinCond # | |
Generic JoinCond Source # | |
Show JoinCond Source # | |
NFData JoinCond Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq JoinCond Source # | |
ToSQL JoinCond Source # | |
Hashable JoinCond Source # | |
type Rep JoinCond Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML type Rep JoinCond = D1 ('MetaData "JoinCond" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "JoinOn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BoolExp)) :+: C1 ('MetaCons "JoinUsing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Identifier]))) |
Instances
simplifyBoolExp :: BoolExp -> BoolExp Source #
Instances
Data BinOp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BinOp -> c BinOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BinOp # dataTypeOf :: BinOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BinOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BinOp) # gmapT :: (forall b. Data b => b -> b) -> BinOp -> BinOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BinOp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BinOp -> r # gmapQ :: (forall d. Data d => d -> u) -> BinOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BinOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp # | |
Generic BinOp Source # | |
Show BinOp Source # | |
NFData BinOp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq BinOp Source # | |
ToSQL BinOp Source # | |
Hashable BinOp Source # | |
type Rep BinOp Source # | |
SEQ | |
SGT | |
SLT | |
SNE | |
SGTE | |
SLTE | |
SLIKE | |
SNLIKE | |
SILIKE | |
SNILIKE | |
SSIMILAR | |
SNSIMILAR | |
SREGEX | |
SIREGEX | |
SNREGEX | |
SNIREGEX | |
SContains | |
SContainedIn | |
SHasKey | |
SHasKeysAny | |
SHasKeysAll | |
SMatchesFulltext |
Instances
Data CompareOp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompareOp -> c CompareOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CompareOp # toConstr :: CompareOp -> Constr # dataTypeOf :: CompareOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CompareOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CompareOp) # gmapT :: (forall b. Data b => b -> b) -> CompareOp -> CompareOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompareOp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompareOp -> r # gmapQ :: (forall d. Data d => d -> u) -> CompareOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CompareOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompareOp -> m CompareOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompareOp -> m CompareOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompareOp -> m CompareOp # | |
Generic CompareOp Source # | |
Show CompareOp Source # | |
NFData CompareOp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq CompareOp Source # | |
ToSQL CompareOp Source # | |
Hashable CompareOp Source # | |
type Rep CompareOp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML type Rep CompareOp = D1 ('MetaData "CompareOp" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) ((((C1 ('MetaCons "SEQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SGT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SLT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SIN" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SNE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SGTE" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "SLTE" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SNIN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SLIKE" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SNLIKE" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SILIKE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SNILIKE" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "SSIMILAR" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SNSIMILAR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SREGEX" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SIREGEX" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SNREGEX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SNIREGEX" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "SContains" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SContainedIn" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SHasKey" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SHasKeysAny" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SHasKeysAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SMatchesFulltext" 'PrefixI 'False) (U1 :: Type -> Type)))))) |
newtype SetExpItem Source #
Instances
Show SetExpItem Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML showsPrec :: Int -> SetExpItem -> ShowS # show :: SetExpItem -> String # showList :: [SetExpItem] -> ShowS # | |
Eq SetExpItem Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML (==) :: SetExpItem -> SetExpItem -> Bool # (/=) :: SetExpItem -> SetExpItem -> Bool # | |
ToSQL SetExpItem Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML toSQL :: SetExpItem -> Builder Source # |
selectStar' :: Qual -> Extractor Source #
data SQLConflictTarget Source #
Instances
Show SQLConflictTarget Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML showsPrec :: Int -> SQLConflictTarget -> ShowS # show :: SQLConflictTarget -> String # showList :: [SQLConflictTarget] -> ShowS # | |
Eq SQLConflictTarget Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML (==) :: SQLConflictTarget -> SQLConflictTarget -> Bool # (/=) :: SQLConflictTarget -> SQLConflictTarget -> Bool # | |
ToSQL SQLConflictTarget Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML toSQL :: SQLConflictTarget -> Builder Source # |
data SQLConflict Source #
Instances
Show SQLConflict Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML showsPrec :: Int -> SQLConflict -> ShowS # show :: SQLConflict -> String # showList :: [SQLConflict] -> ShowS # | |
Eq SQLConflict Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML (==) :: SQLConflict -> SQLConflict -> Bool # (/=) :: SQLConflict -> SQLConflict -> Bool # | |
ToSQL SQLConflict Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML toSQL :: SQLConflict -> Builder Source # |
Instances
Data ValuesExp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ValuesExp -> c ValuesExp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ValuesExp # toConstr :: ValuesExp -> Constr # dataTypeOf :: ValuesExp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ValuesExp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ValuesExp) # gmapT :: (forall b. Data b => b -> b) -> ValuesExp -> ValuesExp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ValuesExp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ValuesExp -> r # gmapQ :: (forall d. Data d => d -> u) -> ValuesExp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ValuesExp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ValuesExp -> m ValuesExp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ValuesExp -> m ValuesExp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ValuesExp -> m ValuesExp # | |
Show ValuesExp Source # | |
NFData ValuesExp Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq ValuesExp Source # | |
ToSQL ValuesExp Source # | |
Hashable ValuesExp Source # | |
SQLInsert | |
|
data TopLevelCTE Source #
Top-level Common Table Expression statement.
A top level CTE can be a query or a mutation statement.
Postgres supports mutations only in top-level CTEs. See https://www.postgresql.org/docs/current/queries-with.html#QUERIES-WITH-MODIFYING
CTESelect Select | |
CTEInsert SQLInsert | |
CTEUpdate SQLUpdate | |
CTEDelete SQLDelete | |
CTEUnsafeRawSQL (InterpolatedQuery SQLExp) |
Instances
Show TopLevelCTE Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML showsPrec :: Int -> TopLevelCTE -> ShowS # show :: TopLevelCTE -> String # showList :: [TopLevelCTE] -> ShowS # | |
Eq TopLevelCTE Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML (==) :: TopLevelCTE -> TopLevelCTE -> Bool # (/=) :: TopLevelCTE -> TopLevelCTE -> Bool # | |
ToSQL TopLevelCTE Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML toSQL :: TopLevelCTE -> Builder Source # |
Represents a common table expresion that can be used in nested selects.
Instances
Data InnerCTE Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InnerCTE -> c InnerCTE # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InnerCTE # toConstr :: InnerCTE -> Constr # dataTypeOf :: InnerCTE -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InnerCTE) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InnerCTE) # gmapT :: (forall b. Data b => b -> b) -> InnerCTE -> InnerCTE # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InnerCTE -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InnerCTE -> r # gmapQ :: (forall d. Data d => d -> u) -> InnerCTE -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InnerCTE -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InnerCTE -> m InnerCTE # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InnerCTE -> m InnerCTE # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InnerCTE -> m InnerCTE # | |
Generic InnerCTE Source # | |
Show InnerCTE Source # | |
NFData InnerCTE Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML | |
Eq InnerCTE Source # | |
Hashable InnerCTE Source # | |
type Rep InnerCTE Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML type Rep InnerCTE = D1 ('MetaData "InnerCTE" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "ICTESelect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Select)) :+: C1 ('MetaCons "ICTEUnsafeRawSQL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (InterpolatedQuery SQLExp)))) |
data SelectWithG statement Source #
A SELECT
statement with Common Table Expressions.
https://www.postgresql.org/docs/current/queries-with.html
These CTEs are determined by the statement
parameter.
Currently they are either TopLevelCTE
, which allow for a query or mutation statement,
or Select
, which only allow for querying results.
The distinction is required because Postgres only supports mutations in CTEs at the top level. See https://www.postgresql.org/docs/current/queries-with.html#QUERIES-WITH-MODIFYING
SelectWith | |
|
Instances
Data statement => Data (SelectWithG statement) Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectWithG statement -> c (SelectWithG statement) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SelectWithG statement) # toConstr :: SelectWithG statement -> Constr # dataTypeOf :: SelectWithG statement -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SelectWithG statement)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SelectWithG statement)) # gmapT :: (forall b. Data b => b -> b) -> SelectWithG statement -> SelectWithG statement # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectWithG statement -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectWithG statement -> r # gmapQ :: (forall d. Data d => d -> u) -> SelectWithG statement -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectWithG statement -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectWithG statement -> m (SelectWithG statement) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectWithG statement -> m (SelectWithG statement) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectWithG statement -> m (SelectWithG statement) # | |
Generic (SelectWithG statement) Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML type Rep (SelectWithG statement) :: Type -> Type # from :: SelectWithG statement -> Rep (SelectWithG statement) x # to :: Rep (SelectWithG statement) x -> SelectWithG statement # | |
Show statement => Show (SelectWithG statement) Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML showsPrec :: Int -> SelectWithG statement -> ShowS # show :: SelectWithG statement -> String # showList :: [SelectWithG statement] -> ShowS # | |
NFData v => NFData (SelectWithG v) Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML rnf :: SelectWithG v -> () # | |
Eq statement => Eq (SelectWithG statement) Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML (==) :: SelectWithG statement -> SelectWithG statement -> Bool # (/=) :: SelectWithG statement -> SelectWithG statement -> Bool # | |
ToSQL v => ToSQL (SelectWithG v) Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML toSQL :: SelectWithG v -> Builder Source # | |
Hashable v => Hashable (SelectWithG v) Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML hashWithSalt :: Int -> SelectWithG v -> Int Source # hash :: SelectWithG v -> Int Source # | |
type Rep (SelectWithG statement) Source # | |
Defined in Hasura.Backends.Postgres.SQL.DML type Rep (SelectWithG statement) = D1 ('MetaData "SelectWithG" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "SelectWith" 'PrefixI 'True) (S1 ('MetaSel ('Just "swCTEs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(TableAlias, statement)]) :*: S1 ('MetaSel ('Just "swSelect") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Select))) |
type SelectWith = SelectWithG TopLevelCTE Source #
A top-level select with CTEs.