graphql-engine-1.0.0: GraphQL API over Postgres
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hasura.Backends.Postgres.SQL.DML

Description

Postgres SQL DML

Provide types and combinators for defining Postgres SQL queries and mutations.

Synopsis

Documentation

data Select Source #

An select statement that does not require mutation CTEs.

See SelectWithG or SelectWithG for select statements with mutations as CTEs.

Instances

Instances details
Data Select Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Select -> c Select #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Select #

toConstr :: Select -> Constr #

dataTypeOf :: Select -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Select) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Select) #

gmapT :: (forall b. Data b => b -> b) -> Select -> Select #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Select -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Select -> r #

gmapQ :: (forall d. Data d => d -> u) -> Select -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Select -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Select -> m Select #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Select -> m Select #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Select -> m Select #

Generic Select Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep Select :: Type -> Type #

Methods

from :: Select -> Rep Select x #

to :: Rep Select x -> Select #

Show Select Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData Select Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: Select -> () #

Eq Select Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

(==) :: Select -> Select -> Bool #

(/=) :: Select -> Select -> Bool #

ToSQL Select Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

toSQL :: Select -> Builder Source #

Hashable Select Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep Select Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

mkSelect :: Select Source #

An empty select statement.

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.

newtype LimitExp Source #

Constructors

LimitExp SQLExp 

Instances

Instances details
Data LimitExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData LimitExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: LimitExp -> () #

Eq LimitExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL LimitExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable LimitExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

newtype OffsetExp Source #

Constructors

OffsetExp SQLExp 

Instances

Instances details
Data OffsetExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData OffsetExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: OffsetExp -> () #

Eq OffsetExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL OffsetExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable OffsetExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

newtype OrderByExp Source #

Instances

Instances details
Data OrderByExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderByExp -> c OrderByExp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderByExp #

toConstr :: OrderByExp -> Constr #

dataTypeOf :: OrderByExp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OrderByExp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderByExp) #

gmapT :: (forall b. Data b => b -> b) -> OrderByExp -> OrderByExp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderByExp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderByExp -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderByExp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderByExp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderByExp -> m OrderByExp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderByExp -> m OrderByExp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderByExp -> m OrderByExp #

Show OrderByExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData OrderByExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: OrderByExp -> () #

Eq OrderByExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL OrderByExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable OrderByExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

data OrderByItem Source #

Instances

Instances details
Data OrderByItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OrderByItem -> c OrderByItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OrderByItem #

toConstr :: OrderByItem -> Constr #

dataTypeOf :: OrderByItem -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OrderByItem) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OrderByItem) #

gmapT :: (forall b. Data b => b -> b) -> OrderByItem -> OrderByItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OrderByItem -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OrderByItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> OrderByItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OrderByItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OrderByItem -> m OrderByItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderByItem -> m OrderByItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OrderByItem -> m OrderByItem #

Generic OrderByItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep OrderByItem :: Type -> Type #

Show OrderByItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData OrderByItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: OrderByItem -> () #

Eq OrderByItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL OrderByItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable OrderByItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep OrderByItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep OrderByItem = D1 ('MetaData "OrderByItem" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "OrderByItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "oExpression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp) :*: (S1 ('MetaSel ('Just "oOrdering") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe OrderType)) :*: S1 ('MetaSel ('Just "oNullsOrder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe NullsOrder)))))

data OrderType Source #

Order by ascending or descending

Constructors

OTAsc 
OTDesc 

Instances

Instances details
FromJSON OrderType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToJSON OrderType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Data OrderType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep OrderType :: Type -> Type #

Show OrderType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData OrderType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: OrderType -> () #

Eq OrderType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL OrderType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable OrderType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep OrderType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep OrderType = D1 ('MetaData "OrderType" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "OTAsc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OTDesc" 'PrefixI 'False) (U1 :: Type -> Type))

data NullsOrder Source #

Constructors

NullsFirst 
NullsLast 

Instances

Instances details
FromJSON NullsOrder Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToJSON NullsOrder Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Data NullsOrder Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NullsOrder -> c NullsOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NullsOrder #

toConstr :: NullsOrder -> Constr #

dataTypeOf :: NullsOrder -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NullsOrder) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NullsOrder) #

gmapT :: (forall b. Data b => b -> b) -> NullsOrder -> NullsOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NullsOrder -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NullsOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> NullsOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NullsOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NullsOrder -> m NullsOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NullsOrder -> m NullsOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NullsOrder -> m NullsOrder #

Generic NullsOrder Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep NullsOrder :: Type -> Type #

Show NullsOrder Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData NullsOrder Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: NullsOrder -> () #

Eq NullsOrder Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL NullsOrder Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable NullsOrder Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep NullsOrder Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep NullsOrder = D1 ('MetaData "NullsOrder" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "NullsFirst" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NullsLast" 'PrefixI 'False) (U1 :: Type -> Type))

newtype GroupByExp Source #

Constructors

GroupByExp [SQLExp] 

Instances

Instances details
Data GroupByExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GroupByExp -> c GroupByExp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GroupByExp #

toConstr :: GroupByExp -> Constr #

dataTypeOf :: GroupByExp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GroupByExp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GroupByExp) #

gmapT :: (forall b. Data b => b -> b) -> GroupByExp -> GroupByExp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GroupByExp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GroupByExp -> r #

gmapQ :: (forall d. Data d => d -> u) -> GroupByExp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GroupByExp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GroupByExp -> m GroupByExp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GroupByExp -> m GroupByExp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GroupByExp -> m GroupByExp #

Show GroupByExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData GroupByExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: GroupByExp -> () #

Eq GroupByExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL GroupByExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable GroupByExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

newtype FromExp Source #

Constructors

FromExp [FromItem] 

Instances

Instances details
Data FromExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData FromExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: FromExp -> () #

Eq FromExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

(==) :: FromExp -> FromExp -> Bool #

(/=) :: FromExp -> FromExp -> Bool #

ToSQL FromExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable FromExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

newtype HavingExp Source #

Constructors

HavingExp BoolExp 

Instances

Instances details
Data HavingExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData HavingExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: HavingExp -> () #

Eq HavingExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL HavingExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable HavingExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

newtype WhereFrag Source #

Constructors

WhereFrag BoolExp 

Instances

Instances details
Data WhereFrag Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData WhereFrag Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: WhereFrag -> () #

Eq WhereFrag Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL WhereFrag Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable WhereFrag Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

data Qual Source #

Instances

Instances details
Data Qual Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 #

toConstr :: Qual -> Constr #

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep Qual :: Type -> Type #

Methods

from :: Qual -> Rep Qual x #

to :: Rep Qual x -> Qual #

Show Qual Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

showsPrec :: Int -> Qual -> ShowS #

show :: Qual -> String #

showList :: [Qual] -> ShowS #

NFData Qual Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: Qual -> () #

Eq Qual Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

(==) :: Qual -> Qual -> Bool #

(/=) :: Qual -> Qual -> Bool #

ToSQL Qual Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

toSQL :: Qual -> Builder Source #

Hashable Qual Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep Qual Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

data QIdentifier Source #

Instances

Instances details
Data QIdentifier Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QIdentifier -> c QIdentifier #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QIdentifier #

toConstr :: QIdentifier -> Constr #

dataTypeOf :: QIdentifier -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c QIdentifier) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QIdentifier) #

gmapT :: (forall b. Data b => b -> b) -> QIdentifier -> QIdentifier #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QIdentifier -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QIdentifier -> r #

gmapQ :: (forall d. Data d => d -> u) -> QIdentifier -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> QIdentifier -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QIdentifier -> m QIdentifier #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QIdentifier -> m QIdentifier #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QIdentifier -> m QIdentifier #

Generic QIdentifier Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep QIdentifier :: Type -> Type #

Show QIdentifier Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData QIdentifier Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: QIdentifier -> () #

Eq QIdentifier Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL QIdentifier Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable QIdentifier Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL (CountType QIdentifier) Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep QIdentifier Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep QIdentifier = D1 ('MetaData "QIdentifier" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "QIdentifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Qual) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Identifier)))

data ColumnOp Source #

Constructors

ColumnOp 

Fields

Instances

Instances details
Data ColumnOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep ColumnOp :: Type -> Type #

Methods

from :: ColumnOp -> Rep ColumnOp x #

to :: Rep ColumnOp x -> ColumnOp #

Show ColumnOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData ColumnOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: ColumnOp -> () #

Eq ColumnOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable ColumnOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep ColumnOp Source # 
Instance details

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)))

newtype SQLOp Source #

Constructors

SQLOp Text 

Instances

Instances details
Data SQLOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 #

toConstr :: SQLOp -> Constr #

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

showsPrec :: Int -> SQLOp -> ShowS #

show :: SQLOp -> String #

showList :: [SQLOp] -> ShowS #

NFData SQLOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: SQLOp -> () #

Eq SQLOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

(==) :: SQLOp -> SQLOp -> Bool #

(/=) :: SQLOp -> SQLOp -> Bool #

Hashable SQLOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

newtype TypeAnn Source #

Constructors

TypeAnn Text 

Instances

Instances details
Data TypeAnn Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData TypeAnn Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: TypeAnn -> () #

Eq TypeAnn Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

(==) :: TypeAnn -> TypeAnn -> Bool #

(/=) :: TypeAnn -> TypeAnn -> Bool #

ToSQL TypeAnn Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable TypeAnn Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

data CountType columnType Source #

Constructors

CTStar 
CTSimple [columnType] 
CTDistinct [columnType] 

Instances

Instances details
Foldable CountType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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] #

null :: CountType a -> Bool #

length :: CountType a -> Int #

elem :: Eq a => a -> CountType a -> Bool #

maximum :: Ord a => CountType a -> a #

minimum :: Ord a => CountType a -> a #

sum :: Num a => CountType a -> a #

product :: Num a => CountType a -> a #

Traversable CountType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

traverse :: Applicative f => (a -> f b) -> CountType a -> f (CountType b) #

sequenceA :: Applicative f => CountType (f a) -> f (CountType a) #

mapM :: Monad m => (a -> m b) -> CountType a -> m (CountType b) #

sequence :: Monad m => CountType (m a) -> m (CountType a) #

Functor CountType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

fmap :: (a -> b) -> CountType a -> CountType b #

(<$) :: a -> CountType b -> CountType a #

Data columnType => Data (CountType columnType) Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep (CountType columnType) :: Type -> Type #

Methods

from :: CountType columnType -> Rep (CountType columnType) x #

to :: Rep (CountType columnType) x -> CountType columnType #

Show columnType => Show (CountType columnType) Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

showsPrec :: Int -> CountType columnType -> ShowS #

show :: CountType columnType -> String #

showList :: [CountType columnType] -> ShowS #

NFData columnType => NFData (CountType columnType) Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: CountType columnType -> () #

Eq columnType => Eq (CountType columnType) Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

(==) :: CountType columnType -> CountType columnType -> Bool #

(/=) :: CountType columnType -> CountType columnType -> Bool #

ToSQL (CountType QIdentifier) Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable columnType => Hashable (CountType columnType) Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

hashWithSalt :: Int -> CountType columnType -> Int Source #

hash :: CountType columnType -> Int Source #

type Rep (CountType columnType) Source # 
Instance details

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]))))

newtype TupleExp Source #

Constructors

TupleExp [SQLExp] 

Instances

Instances details
Data TupleExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData TupleExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: TupleExp -> () #

Eq TupleExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL TupleExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable TupleExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

data SQLExp Source #

Constructors

SEPrep Int 
SENull 
SELit Text 
SEUnsafe Text 
SESelect Select 
SEStar (Maybe Qual)

all fields (*) or all fields from relation (iden.*)

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 Text is the function name

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

Instances details
ToJSON SQLExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Data SQLExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SQLExp -> c SQLExp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SQLExp #

toConstr :: SQLExp -> Constr #

dataTypeOf :: SQLExp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SQLExp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SQLExp) #

gmapT :: (forall b. Data b => b -> b) -> SQLExp -> SQLExp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SQLExp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SQLExp -> r #

gmapQ :: (forall d. Data d => d -> u) -> SQLExp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SQLExp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SQLExp -> m SQLExp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SQLExp -> m SQLExp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SQLExp -> m SQLExp #

Generic SQLExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep SQLExp :: Type -> Type #

Methods

from :: SQLExp -> Rep SQLExp x #

to :: Rep SQLExp x -> SQLExp #

Show SQLExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData SQLExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: SQLExp -> () #

Eq SQLExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

(==) :: SQLExp -> SQLExp -> Bool #

(/=) :: SQLExp -> SQLExp -> Bool #

ToSQL SQLExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

toSQL :: SQLExp -> Builder Source #

Hashable SQLExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep SQLExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep SQLExp = D1 ('MetaData "SQLExp" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) ((((C1 ('MetaCons "SEPrep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "SENull" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SELit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "SEUnsafe" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "SESelect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Select))))) :+: ((C1 ('MetaCons "SEStar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Qual))) :+: C1 ('MetaCons "SEIdentifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Identifier))) :+: (C1 ('MetaCons "SERowIdentifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Identifier)) :+: (C1 ('MetaCons "SEQIdentifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 QIdentifier)) :+: C1 ('MetaCons "SEFnApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [SQLExp]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe OrderByExp)))))))) :+: (((C1 ('MetaCons "SEOpApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [SQLExp])) :+: C1 ('MetaCons "SETyAnn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TypeAnn))) :+: (C1 ('MetaCons "SECond" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BoolExp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp))) :+: (C1 ('MetaCons "SEBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BoolExp)) :+: C1 ('MetaCons "SEExcluded" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Identifier))))) :+: ((C1 ('MetaCons "SEArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [SQLExp])) :+: (C1 ('MetaCons "SEArrayIndex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp)) :+: C1 ('MetaCons "SETuple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TupleExp)))) :+: (C1 ('MetaCons "SECount" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (CountType QIdentifier))) :+: (C1 ('MetaCons "SENamedArg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp)) :+: C1 ('MetaCons "SEFunction" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FunctionExp)))))))

newtype ColumnAlias Source #

Represents an alias assignment for a column

Constructors

ColumnAlias 

Instances

Instances details
Data ColumnAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColumnAlias -> c ColumnAlias #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColumnAlias #

toConstr :: ColumnAlias -> Constr #

dataTypeOf :: ColumnAlias -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColumnAlias) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColumnAlias) #

gmapT :: (forall b. Data b => b -> b) -> ColumnAlias -> ColumnAlias #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColumnAlias -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColumnAlias -> r #

gmapQ :: (forall d. Data d => d -> u) -> ColumnAlias -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ColumnAlias -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ColumnAlias -> m ColumnAlias #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ColumnAlias -> m ColumnAlias #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ColumnAlias -> m ColumnAlias #

IsString ColumnAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Semigroup ColumnAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Show ColumnAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData ColumnAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: ColumnAlias -> () #

Eq ColumnAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

IsIdentifier ColumnAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable ColumnAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

newtype TableAlias Source #

Represents an alias assignment for a table, relation or row

Constructors

TableAlias 

Instances

Instances details
Data TableAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableAlias -> c TableAlias #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableAlias #

toConstr :: TableAlias -> Constr #

dataTypeOf :: TableAlias -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableAlias) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableAlias) #

gmapT :: (forall b. Data b => b -> b) -> TableAlias -> TableAlias #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableAlias -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableAlias -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableAlias -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableAlias -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableAlias -> m TableAlias #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableAlias -> m TableAlias #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableAlias -> m TableAlias #

IsString TableAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Semigroup TableAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Generic TableAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep TableAlias :: Type -> Type #

Show TableAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData TableAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: TableAlias -> () #

Eq TableAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

IsIdentifier TableAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable TableAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep TableAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep TableAlias = D1 ('MetaData "TableAlias" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'True) (C1 ('MetaCons "TableAlias" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTableAlias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Identifier)))

mkTableAlias :: Text -> TableAlias Source #

Create a table alias.

tableAliasToIdentifier :: TableAlias -> TableIdentifier Source #

Create a table identifier from a table alias.

data Extractor Source #

Extractor can be used to apply Postgres alias to a column

Instances

Instances details
Data Extractor Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep Extractor :: Type -> Type #

Show Extractor Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData Extractor Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: Extractor -> () #

Eq Extractor Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL Extractor Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable Extractor Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep Extractor Source # 
Instance details

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))))

data DistinctExpr Source #

Instances

Instances details
Data DistinctExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DistinctExpr -> c DistinctExpr #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DistinctExpr #

toConstr :: DistinctExpr -> Constr #

dataTypeOf :: DistinctExpr -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DistinctExpr) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DistinctExpr) #

gmapT :: (forall b. Data b => b -> b) -> DistinctExpr -> DistinctExpr #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DistinctExpr -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DistinctExpr -> r #

gmapQ :: (forall d. Data d => d -> u) -> DistinctExpr -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DistinctExpr -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DistinctExpr -> m DistinctExpr #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DistinctExpr -> m DistinctExpr #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DistinctExpr -> m DistinctExpr #

Generic DistinctExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep DistinctExpr :: Type -> Type #

Show DistinctExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData DistinctExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: DistinctExpr -> () #

Eq DistinctExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL DistinctExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable DistinctExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep DistinctExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep DistinctExpr = D1 ('MetaData "DistinctExpr" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "DistinctSimple" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DistinctOn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [SQLExp])))

data FunctionArgs Source #

Instances

Instances details
Data FunctionArgs Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunctionArgs -> c FunctionArgs #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunctionArgs #

toConstr :: FunctionArgs -> Constr #

dataTypeOf :: FunctionArgs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunctionArgs) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunctionArgs) #

gmapT :: (forall b. Data b => b -> b) -> FunctionArgs -> FunctionArgs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunctionArgs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunctionArgs -> r #

gmapQ :: (forall d. Data d => d -> u) -> FunctionArgs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FunctionArgs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunctionArgs -> m FunctionArgs #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionArgs -> m FunctionArgs #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionArgs -> m FunctionArgs #

Generic FunctionArgs Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep FunctionArgs :: Type -> Type #

Show FunctionArgs Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData FunctionArgs Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: FunctionArgs -> () #

Eq FunctionArgs Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL FunctionArgs Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable FunctionArgs Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep FunctionArgs Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep FunctionArgs = D1 ('MetaData "FunctionArgs" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "FunctionArgs" 'PrefixI 'True) (S1 ('MetaSel ('Just "fasPostional") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [SQLExp]) :*: S1 ('MetaSel ('Just "fasNamed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (HashMap Text SQLExp))))

data FunctionDefinitionListItem Source #

Instances

Instances details
Data FunctionDefinitionListItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunctionDefinitionListItem -> c FunctionDefinitionListItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunctionDefinitionListItem #

toConstr :: FunctionDefinitionListItem -> Constr #

dataTypeOf :: FunctionDefinitionListItem -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunctionDefinitionListItem) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunctionDefinitionListItem) #

gmapT :: (forall b. Data b => b -> b) -> FunctionDefinitionListItem -> FunctionDefinitionListItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunctionDefinitionListItem -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunctionDefinitionListItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> FunctionDefinitionListItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FunctionDefinitionListItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunctionDefinitionListItem -> m FunctionDefinitionListItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionDefinitionListItem -> m FunctionDefinitionListItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionDefinitionListItem -> m FunctionDefinitionListItem #

Generic FunctionDefinitionListItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep FunctionDefinitionListItem :: Type -> Type #

Show FunctionDefinitionListItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData FunctionDefinitionListItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Eq FunctionDefinitionListItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL FunctionDefinitionListItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable FunctionDefinitionListItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep FunctionDefinitionListItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep FunctionDefinitionListItem = D1 ('MetaData "FunctionDefinitionListItem" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "FunctionDefinitionListItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "_dliColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ColumnAlias) :*: S1 ('MetaSel ('Just "_dliType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PGScalarType)))

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

Instances details
Data FunctionAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunctionAlias -> c FunctionAlias #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunctionAlias #

toConstr :: FunctionAlias -> Constr #

dataTypeOf :: FunctionAlias -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunctionAlias) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunctionAlias) #

gmapT :: (forall b. Data b => b -> b) -> FunctionAlias -> FunctionAlias #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunctionAlias -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunctionAlias -> r #

gmapQ :: (forall d. Data d => d -> u) -> FunctionAlias -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FunctionAlias -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunctionAlias -> m FunctionAlias #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionAlias -> m FunctionAlias #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionAlias -> m FunctionAlias #

Generic FunctionAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep FunctionAlias :: Type -> Type #

Show FunctionAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData FunctionAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: FunctionAlias -> () #

Eq FunctionAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL FunctionAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable FunctionAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep FunctionAlias Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep FunctionAlias = D1 ('MetaData "FunctionAlias" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "FunctionAlias" 'PrefixI 'True) (S1 ('MetaSel ('Just "_faIdentifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TableAlias) :*: S1 ('MetaSel ('Just "_faDefinitionList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [FunctionDefinitionListItem]))))

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

Instances details
Data FunctionExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunctionExp -> c FunctionExp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunctionExp #

toConstr :: FunctionExp -> Constr #

dataTypeOf :: FunctionExp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunctionExp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunctionExp) #

gmapT :: (forall b. Data b => b -> b) -> FunctionExp -> FunctionExp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunctionExp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunctionExp -> r #

gmapQ :: (forall d. Data d => d -> u) -> FunctionExp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FunctionExp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunctionExp -> m FunctionExp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionExp -> m FunctionExp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionExp -> m FunctionExp #

Generic FunctionExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep FunctionExp :: Type -> Type #

Show FunctionExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData FunctionExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: FunctionExp -> () #

Eq FunctionExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL FunctionExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable FunctionExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep FunctionExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep FunctionExp = D1 ('MetaData "FunctionExp" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "FunctionExp" 'PrefixI 'True) (S1 ('MetaSel ('Just "feName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 QualifiedFunction) :*: (S1 ('MetaSel ('Just "feArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FunctionArgs) :*: S1 ('MetaSel ('Just "feAlias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe FunctionAlias)))))

data FromItem Source #

Constructors

FISimple QualifiedTable (Maybe TableAlias)

A simple table

FIIdentifier TableIdentifier

An identifier (from CTEs)

FIFunc FunctionExp

A function call (that should return a relation (SETOF) and not a scalar)

FIUnnest [SQLExp] TableAlias [ColumnAlias]

unnest converts (an) array(s) to a relation.

We have: * The unnest function arguments * The relation alias * A list of column aliases

See unnest in https://www.postgresql.org/docs/current/functions-array.html.

FISelect Lateral Select TableAlias 
FISelectWith Lateral (SelectWithG Select) TableAlias 
FIValues ValuesExp TableAlias (Maybe [ColumnAlias]) 
FIJoin JoinExpr 

Instances

Instances details
Data FromItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FromItem -> c FromItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FromItem #

toConstr :: FromItem -> Constr #

dataTypeOf :: FromItem -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FromItem) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FromItem) #

gmapT :: (forall b. Data b => b -> b) -> FromItem -> FromItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromItem -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> FromItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromItem -> m FromItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromItem -> m FromItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromItem -> m FromItem #

Generic FromItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep FromItem :: Type -> Type #

Methods

from :: FromItem -> Rep FromItem x #

to :: Rep FromItem x -> FromItem #

Show FromItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData FromItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: FromItem -> () #

Eq FromItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL FromItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable FromItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep FromItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep FromItem = D1 ('MetaData "FromItem" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (((C1 ('MetaCons "FISimple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 QualifiedTable) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe TableAlias))) :+: C1 ('MetaCons "FIIdentifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TableIdentifier))) :+: (C1 ('MetaCons "FIFunc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FunctionExp)) :+: C1 ('MetaCons "FIUnnest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [SQLExp]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TableAlias) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ColumnAlias]))))) :+: ((C1 ('MetaCons "FISelect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Lateral) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Select) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TableAlias))) :+: C1 ('MetaCons "FISelectWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Lateral) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (SelectWithG Select)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TableAlias)))) :+: (C1 ('MetaCons "FIValues" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ValuesExp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TableAlias) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe [ColumnAlias])))) :+: C1 ('MetaCons "FIJoin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 JoinExpr)))))

newtype Lateral Source #

Constructors

Lateral Bool 

Instances

Instances details
Data Lateral Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData Lateral Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: Lateral -> () #

Eq Lateral Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

(==) :: Lateral -> Lateral -> Bool #

(/=) :: Lateral -> Lateral -> Bool #

ToSQL Lateral Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable Lateral Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

data JoinExpr Source #

Instances

Instances details
Data JoinExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JoinExpr -> c JoinExpr #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JoinExpr #

toConstr :: JoinExpr -> Constr #

dataTypeOf :: JoinExpr -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JoinExpr) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JoinExpr) #

gmapT :: (forall b. Data b => b -> b) -> JoinExpr -> JoinExpr #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JoinExpr -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JoinExpr -> r #

gmapQ :: (forall d. Data d => d -> u) -> JoinExpr -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JoinExpr -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JoinExpr -> m JoinExpr #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinExpr -> m JoinExpr #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinExpr -> m JoinExpr #

Generic JoinExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep JoinExpr :: Type -> Type #

Methods

from :: JoinExpr -> Rep JoinExpr x #

to :: Rep JoinExpr x -> JoinExpr #

Show JoinExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData JoinExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: JoinExpr -> () #

Eq JoinExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL JoinExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable JoinExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep JoinExpr Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

data JoinType Source #

Constructors

Inner 
LeftOuter 

Instances

Instances details
Data JoinType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep JoinType :: Type -> Type #

Methods

from :: JoinType -> Rep JoinType x #

to :: Rep JoinType x -> JoinType #

Show JoinType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData JoinType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: JoinType -> () #

Eq JoinType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL JoinType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable JoinType Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep JoinType Source # 
Instance details

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)))

data JoinCond Source #

Instances

Instances details
Data JoinCond Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep JoinCond :: Type -> Type #

Methods

from :: JoinCond -> Rep JoinCond x #

to :: Rep JoinCond x -> JoinCond #

Show JoinCond Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData JoinCond Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: JoinCond -> () #

Eq JoinCond Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL JoinCond Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable JoinCond Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep JoinCond Source # 
Instance details

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])))

data BoolExp Source #

Instances

Instances details
Data BoolExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BoolExp -> c BoolExp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BoolExp #

toConstr :: BoolExp -> Constr #

dataTypeOf :: BoolExp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BoolExp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BoolExp) #

gmapT :: (forall b. Data b => b -> b) -> BoolExp -> BoolExp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BoolExp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BoolExp -> r #

gmapQ :: (forall d. Data d => d -> u) -> BoolExp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BoolExp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BoolExp -> m BoolExp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BoolExp -> m BoolExp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BoolExp -> m BoolExp #

Generic BoolExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep BoolExp :: Type -> Type #

Methods

from :: BoolExp -> Rep BoolExp x #

to :: Rep BoolExp x -> BoolExp #

Show BoolExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData BoolExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: BoolExp -> () #

Eq BoolExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

(==) :: BoolExp -> BoolExp -> Bool #

(/=) :: BoolExp -> BoolExp -> Bool #

ToSQL BoolExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable BoolExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep BoolExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep BoolExp = D1 ('MetaData "BoolExp" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (((C1 ('MetaCons "BELit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "BEBin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BinOp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BoolExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BoolExp)))) :+: (C1 ('MetaCons "BENot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BoolExp)) :+: (C1 ('MetaCons "BECompare" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CompareOp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp))) :+: C1 ('MetaCons "BECompareAny" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CompareOp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp)))))) :+: ((C1 ('MetaCons "BENull" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp)) :+: C1 ('MetaCons "BENotNull" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp))) :+: (C1 ('MetaCons "BEExists" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Select)) :+: (C1 ('MetaCons "BEIN" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [SQLExp])) :+: C1 ('MetaCons "BEExp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SQLExp))))))

data BinOp Source #

Constructors

AndOp 
OrOp 

Instances

Instances details
Data BinOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 #

toConstr :: BinOp -> Constr #

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep BinOp :: Type -> Type #

Methods

from :: BinOp -> Rep BinOp x #

to :: Rep BinOp x -> BinOp #

Show BinOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

NFData BinOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: BinOp -> () #

Eq BinOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

(==) :: BinOp -> BinOp -> Bool #

(/=) :: BinOp -> BinOp -> Bool #

ToSQL BinOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

toSQL :: BinOp -> Builder Source #

Hashable BinOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep BinOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep BinOp = D1 ('MetaData "BinOp" "Hasura.Backends.Postgres.SQL.DML" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "AndOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OrOp" 'PrefixI 'False) (U1 :: Type -> Type))

data CompareOp Source #

Instances

Instances details
Data CompareOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep CompareOp :: Type -> Type #

Show CompareOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData CompareOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: CompareOp -> () #

Eq CompareOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL CompareOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable CompareOp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep CompareOp Source # 
Instance details

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))))))

data SQLDelete Source #

Instances

Instances details
Show SQLDelete Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Eq SQLDelete Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL SQLDelete Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

newtype SetExp Source #

Constructors

SetExp [SetExpItem] 

Instances

Instances details
Show SetExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Eq SetExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

(==) :: SetExp -> SetExp -> Bool #

(/=) :: SetExp -> SetExp -> Bool #

ToSQL SetExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

toSQL :: SetExp -> Builder Source #

newtype SetExpItem Source #

Constructors

SetExpItem (PGCol, SQLExp) 

Instances

Instances details
Show SetExpItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Eq SetExpItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL SetExpItem Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

newtype RetExp Source #

Constructors

RetExp [Extractor] 

Instances

Instances details
Show RetExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Eq RetExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

(==) :: RetExp -> RetExp -> Bool #

(/=) :: RetExp -> RetExp -> Bool #

ToSQL RetExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

toSQL :: RetExp -> Builder Source #

newtype ValuesExp Source #

Constructors

ValuesExp [TupleExp] 

Instances

Instances details
Data ValuesExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData ValuesExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: ValuesExp -> () #

Eq ValuesExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

ToSQL ValuesExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable ValuesExp Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

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

data InnerCTE Source #

Represents a common table expresion that can be used in nested selects.

Instances

Instances details
Data InnerCTE Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep InnerCTE :: Type -> Type #

Methods

from :: InnerCTE -> Rep InnerCTE x #

to :: Rep InnerCTE x -> InnerCTE #

Show InnerCTE Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

NFData InnerCTE Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: InnerCTE -> () #

Eq InnerCTE Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable InnerCTE Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep InnerCTE Source # 
Instance details

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

Constructors

SelectWith 

Fields

Instances

Instances details
Data statement => Data (SelectWithG statement) Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

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 # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Associated Types

type Rep (SelectWithG statement) :: Type -> Type #

Methods

from :: SelectWithG statement -> Rep (SelectWithG statement) x #

to :: Rep (SelectWithG statement) x -> SelectWithG statement #

Show statement => Show (SelectWithG statement) Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

showsPrec :: Int -> SelectWithG statement -> ShowS #

show :: SelectWithG statement -> String #

showList :: [SelectWithG statement] -> ShowS #

NFData v => NFData (SelectWithG v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

rnf :: SelectWithG v -> () #

Eq statement => Eq (SelectWithG statement) Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Methods

(==) :: SelectWithG statement -> SelectWithG statement -> Bool #

(/=) :: SelectWithG statement -> SelectWithG statement -> Bool #

ToSQL v => ToSQL (SelectWithG v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

Hashable v => Hashable (SelectWithG v) Source # 
Instance details

Defined in Hasura.Backends.Postgres.SQL.DML

type Rep (SelectWithG statement) Source # 
Instance details

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.