graphql-engine-1.0.0: GraphQL API over Postgres
Safe HaskellNone
LanguageHaskell2010

Hasura.Backends.DataConnector.IR.Query

Synopsis

Documentation

data QueryRequest Source #

An abstract request to retrieve structured data from some source.

Instances

Instances details
Eq QueryRequest Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Data QueryRequest Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

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

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

toConstr :: QueryRequest -> Constr #

dataTypeOf :: QueryRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord QueryRequest Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Show QueryRequest Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Generic QueryRequest Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Associated Types

type Rep QueryRequest :: Type -> Type #

ToJSON QueryRequest Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

toJSON :: QueryRequest -> Value

toEncoding :: QueryRequest -> Encoding

toJSONList :: [QueryRequest] -> Value

toEncodingList :: [QueryRequest] -> Encoding

From QueryRequest QueryRequest Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

type Rep QueryRequest Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

type Rep QueryRequest = D1 ('MetaData "QueryRequest" "Hasura.Backends.DataConnector.IR.Query" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "QueryRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "_qrTable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Name) :*: (S1 ('MetaSel ('Just "_qrTableRelationships") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TableRelationships) :*: S1 ('MetaSel ('Just "_qrQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Query))))

data Query Source #

The details of a query against a table

Constructors

Query 

Fields

Instances

Instances details
Eq Query Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

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

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

Data Query Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

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

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

toConstr :: Query -> Constr #

dataTypeOf :: Query -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Query Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

compare :: Query -> Query -> Ordering #

(<) :: Query -> Query -> Bool #

(<=) :: Query -> Query -> Bool #

(>) :: Query -> Query -> Bool #

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

max :: Query -> Query -> Query #

min :: Query -> Query -> Query #

Show Query Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Generic Query Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Associated Types

type Rep Query :: Type -> Type #

Methods

from :: Query -> Rep Query x #

to :: Rep Query x -> Query #

ToJSON Query Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

toJSON :: Query -> Value

toEncoding :: Query -> Encoding

toJSONList :: [Query] -> Value

toEncodingList :: [Query] -> Encoding

From Query Query Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

from :: Query -> Query0

type Rep Query Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

memptyToNothing :: (Monoid m, Eq m) => m -> Maybe m Source #

data Field Source #

The specific fields that are targeted by a Query.

A field conceptually falls under one of the two following categories: 1. a "column" within the data store that the query is being issued against 2. a "relationship", which indicates that the field is the result of another query that must be executed on its own NOTE: The ToJSON instance is only intended for logging purposes.

Instances

Instances details
Eq Field Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

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

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

Data Field Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

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

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

toConstr :: Field -> Constr #

dataTypeOf :: Field -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Field Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

compare :: Field -> Field -> Ordering #

(<) :: Field -> Field -> Bool #

(<=) :: Field -> Field -> Bool #

(>) :: Field -> Field -> Bool #

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

max :: Field -> Field -> Field #

min :: Field -> Field -> Field #

Show Field Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

Generic Field Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Associated Types

type Rep Field :: Type -> Type #

Methods

from :: Field -> Rep Field x #

to :: Rep Field x -> Field #

ToJSON Field Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

toJSON :: Field -> Value

toEncoding :: Field -> Encoding

toJSONList :: [Field] -> Value

toEncodingList :: [Field] -> Encoding

From Field Field Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

from :: Field -> Field0

type Rep Field Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

type Rep Field = D1 ('MetaData "Field" "Hasura.Backends.DataConnector.IR.Query" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "ColumnField" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Name)) :+: C1 ('MetaCons "RelField" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RelationshipField)))

data RelationshipField Source #

A relationship consists of the following components: - a sub-query, from the perspective that a relationship field will occur within a broader Query - a join condition relating the data returned by the sub-query with that of the broader Query

cf. https://en.wikipedia.org/wiki/Join_(SQL) https://www.postgresql.org/docs/13/tutorial-join.html https://www.postgresql.org/docs/13/queries-table-expressions.html#QUERIES-FROM

NOTE: The ToJSON instance is only intended for logging purposes.

Instances

Instances details
Eq RelationshipField Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Data RelationshipField Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Methods

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

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

toConstr :: RelationshipField -> Constr #

dataTypeOf :: RelationshipField -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RelationshipField Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Show RelationshipField Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Generic RelationshipField Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

Associated Types

type Rep RelationshipField :: Type -> Type #

ToJSON RelationshipField Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

From RelationshipField RelationshipField Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

type Rep RelationshipField Source # 
Instance details

Defined in Hasura.Backends.DataConnector.IR.Query

type Rep RelationshipField = D1 ('MetaData "RelationshipField" "Hasura.Backends.DataConnector.IR.Query" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "RelationshipField" 'PrefixI 'True) (S1 ('MetaSel ('Just "_rfRelationship") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RelationshipName) :*: S1 ('MetaSel ('Just "_rfQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Query)))