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

Hasura.RQL.IR.BoolExp

Description

Boolean Expressions

This module defines the IR representation of boolean expressions used in _where clauses in GraphQL queries, permissions, and so on.

The types in this module define a generic structure with "holes" to be filled by each backend. Specifically, holes will include things like types for table names, and backend field types.

Synopsis

Documentation

data GBoolExp (backend :: BackendType) field Source #

This type represents a boolean expression tree. It is parametric over the actual implementation of the actual boolean term values. It nonetheless leaks some information: "exists" is only used in permissions, to add conditions based on another table.

  • The backend parameter is used to find the backend-specific type for table names in the BoolExists constructor.
  • The field type represent the type of database-specific field types.

Constructors

BoolAnd [GBoolExp backend field] 
BoolOr [GBoolExp backend field] 
BoolNot (GBoolExp backend field) 
BoolExists (GExists backend field)

Represents a condition on an aribtrary table. since the backend and field are the same, the table must be of the same database type.

BoolField field

A column field

Instances

Instances details
Functor (GBoolExp backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fmap :: (a -> b) -> GBoolExp backend a -> GBoolExp backend b #

(<$) :: a -> GBoolExp backend b -> GBoolExp backend a #

Foldable (GBoolExp backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fold :: Monoid m => GBoolExp backend m -> m #

foldMap :: Monoid m => (a -> m) -> GBoolExp backend a -> m #

foldMap' :: Monoid m => (a -> m) -> GBoolExp backend a -> m #

foldr :: (a -> b -> b) -> b -> GBoolExp backend a -> b #

foldr' :: (a -> b -> b) -> b -> GBoolExp backend a -> b #

foldl :: (b -> a -> b) -> b -> GBoolExp backend a -> b #

foldl' :: (b -> a -> b) -> b -> GBoolExp backend a -> b #

foldr1 :: (a -> a -> a) -> GBoolExp backend a -> a #

foldl1 :: (a -> a -> a) -> GBoolExp backend a -> a #

toList :: GBoolExp backend a -> [a] #

null :: GBoolExp backend a -> Bool #

length :: GBoolExp backend a -> Int #

elem :: Eq a => a -> GBoolExp backend a -> Bool #

maximum :: Ord a => GBoolExp backend a -> a #

minimum :: Ord a => GBoolExp backend a -> a #

sum :: Num a => GBoolExp backend a -> a #

product :: Num a => GBoolExp backend a -> a #

Traversable (GBoolExp backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

sequenceA :: Applicative f => GBoolExp backend (f a) -> f (GBoolExp backend a) #

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

sequence :: Monad m => GBoolExp backend (m a) -> m (GBoolExp backend a) #

(Backend backend, Eq field) => Eq (GBoolExp backend field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

(==) :: GBoolExp backend field -> GBoolExp backend field -> Bool #

(/=) :: GBoolExp backend field -> GBoolExp backend field -> Bool #

(Backend backend, Data field) => Data (GBoolExp backend field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GBoolExp backend field -> c (GBoolExp backend field) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GBoolExp backend field) #

toConstr :: GBoolExp backend field -> Constr #

dataTypeOf :: GBoolExp backend field -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> GBoolExp backend field -> GBoolExp backend field #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GBoolExp backend field -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GBoolExp backend field -> r #

gmapQ :: (forall d. Data d => d -> u) -> GBoolExp backend field -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GBoolExp backend field -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GBoolExp backend field -> m (GBoolExp backend field) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GBoolExp backend field -> m (GBoolExp backend field) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GBoolExp backend field -> m (GBoolExp backend field) #

(Backend backend, Show field) => Show (GBoolExp backend field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

showsPrec :: Int -> GBoolExp backend field -> ShowS #

show :: GBoolExp backend field -> String #

showList :: [GBoolExp backend field] -> ShowS #

Generic (GBoolExp backend field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep (GBoolExp backend field) :: Type -> Type #

Methods

from :: GBoolExp backend field -> Rep (GBoolExp backend field) x #

to :: Rep (GBoolExp backend field) x -> GBoolExp backend field #

(Backend b, NFData a) => NFData (GBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: GBoolExp b a -> () #

(Backend b, Hashable a) => Hashable (GBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

hashWithSalt :: Int -> GBoolExp b a -> Int

hash :: GBoolExp b a -> Int

(Backend b, FromJSONKeyValue a) => FromJSON (GBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

parseJSON :: Value -> Parser (GBoolExp b a)

parseJSONList :: Value -> Parser [GBoolExp b a]

(Backend backend, ToJSONKeyValue field) => ToJSON (GBoolExp backend field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

toJSON :: GBoolExp backend field -> Value

toEncoding :: GBoolExp backend field -> Encoding

toJSONList :: [GBoolExp backend field] -> Value

toEncodingList :: [GBoolExp backend field] -> Encoding

(Backend b, Data a) => Plated (GBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

plate :: Traversal' (GBoolExp b a) (GBoolExp b a)

(Backend b, Cacheable a) => Cacheable (GBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

unchanged :: Accesses -> GBoolExp b a -> GBoolExp b a -> Bool Source #

type Rep (GBoolExp backend field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (GBoolExp backend field) = D1 ('MetaData "GBoolExp" "Hasura.RQL.IR.BoolExp" "graphql-engine-1.0.0-inplace" 'False) ((C1 ('MetaCons "BoolAnd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [GBoolExp backend field])) :+: C1 ('MetaCons "BoolOr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [GBoolExp backend field]))) :+: (C1 ('MetaCons "BoolNot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (GBoolExp backend field))) :+: (C1 ('MetaCons "BoolExists" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (GExists backend field))) :+: C1 ('MetaCons "BoolField" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field)))))

gBoolExpTrue :: GBoolExp backend field Source #

A default representation for a true boolean value.

data GExists (backend :: BackendType) field Source #

Represents a condition on an aribtrary table. Used as part of our permissions boolean expressions. See our documentation for more information: https://hasura.io/docs/latest/graphql/core/auth/authorization/permission-rules.html#using-unrelated-tables-views

Constructors

GExists 

Fields

Instances

Instances details
Functor (GExists backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fmap :: (a -> b) -> GExists backend a -> GExists backend b #

(<$) :: a -> GExists backend b -> GExists backend a #

Foldable (GExists backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fold :: Monoid m => GExists backend m -> m #

foldMap :: Monoid m => (a -> m) -> GExists backend a -> m #

foldMap' :: Monoid m => (a -> m) -> GExists backend a -> m #

foldr :: (a -> b -> b) -> b -> GExists backend a -> b #

foldr' :: (a -> b -> b) -> b -> GExists backend a -> b #

foldl :: (b -> a -> b) -> b -> GExists backend a -> b #

foldl' :: (b -> a -> b) -> b -> GExists backend a -> b #

foldr1 :: (a -> a -> a) -> GExists backend a -> a #

foldl1 :: (a -> a -> a) -> GExists backend a -> a #

toList :: GExists backend a -> [a] #

null :: GExists backend a -> Bool #

length :: GExists backend a -> Int #

elem :: Eq a => a -> GExists backend a -> Bool #

maximum :: Ord a => GExists backend a -> a #

minimum :: Ord a => GExists backend a -> a #

sum :: Num a => GExists backend a -> a #

product :: Num a => GExists backend a -> a #

Traversable (GExists backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

sequenceA :: Applicative f => GExists backend (f a) -> f (GExists backend a) #

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

sequence :: Monad m => GExists backend (m a) -> m (GExists backend a) #

(Backend b, Eq a) => Eq (GExists b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

(==) :: GExists b a -> GExists b a -> Bool #

(/=) :: GExists b a -> GExists b a -> Bool #

(Backend b, Data a) => Data (GExists b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> GExists b a -> c (GExists b a) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GExists b a) #

toConstr :: GExists b a -> Constr #

dataTypeOf :: GExists b a -> DataType #

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

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

gmapT :: (forall b0. Data b0 => b0 -> b0) -> GExists b a -> GExists b a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GExists b a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GExists b a -> r #

gmapQ :: (forall d. Data d => d -> u) -> GExists b a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GExists b a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GExists b a -> m (GExists b a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GExists b a -> m (GExists b a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GExists b a -> m (GExists b a) #

(Backend b, Show a) => Show (GExists b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

showsPrec :: Int -> GExists b a -> ShowS #

show :: GExists b a -> String #

showList :: [GExists b a] -> ShowS #

Generic (GExists backend field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep (GExists backend field) :: Type -> Type #

Methods

from :: GExists backend field -> Rep (GExists backend field) x #

to :: Rep (GExists backend field) x -> GExists backend field #

(Backend b, NFData a) => NFData (GExists b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: GExists b a -> () #

(Backend b, Hashable a) => Hashable (GExists b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

hashWithSalt :: Int -> GExists b a -> Int

hash :: GExists b a -> Int

(Backend b, FromJSONKeyValue a) => FromJSON (GExists b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

parseJSON :: Value -> Parser (GExists b a)

parseJSONList :: Value -> Parser [GExists b a]

(Backend b, ToJSONKeyValue a) => ToJSON (GExists b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

toJSON :: GExists b a -> Value

toEncoding :: GExists b a -> Encoding

toJSONList :: [GExists b a] -> Value

toEncodingList :: [GExists b a] -> Encoding

(Backend b, Data a) => Plated (GExists b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

plate :: Traversal' (GExists b a) (GExists b a)

(Backend b, Cacheable a) => Cacheable (GExists b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

unchanged :: Accesses -> GExists b a -> GExists b a -> Bool Source #

type Rep (GExists backend field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (GExists backend field) = D1 ('MetaData "GExists" "Hasura.RQL.IR.BoolExp" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "GExists" 'PrefixI 'True) (S1 ('MetaSel ('Just "_geTable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (TableName backend)) :*: S1 ('MetaSel ('Just "_geWhere") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (GBoolExp backend field))))

geWhere :: forall backend field field. Lens (GExists backend field) (GExists backend field) (GBoolExp backend field) (GBoolExp backend field) Source #

geTable :: forall backend field. Lens' (GExists backend field) (TableName backend) Source #

data ColExp Source #

We don't allow conditions across relationships in permissions: the type we use as the terms in GBoolExp is this one, ColExp, which only contains a FieldName and a JSON Value.

Constructors

ColExp 

Fields

Instances

Instances details
Eq ColExp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

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

Data ColExp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

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

toConstr :: ColExp -> Constr #

dataTypeOf :: ColExp -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ColExp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Generic ColExp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep ColExp :: Type -> Type #

Methods

from :: ColExp -> Rep ColExp x #

to :: Rep ColExp x -> ColExp #

NFData ColExp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: ColExp -> () #

FromJSONKeyValue ColExp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

parseJSONKeyValue :: (Key, Value) -> Parser ColExp Source #

ToJSONKeyValue ColExp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

toJSONKeyValue :: ColExp -> (Key, Value) Source #

Cacheable ColExp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep ColExp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep ColExp = D1 ('MetaData "ColExp" "Hasura.RQL.IR.BoolExp" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "ColExp" 'PrefixI 'True) (S1 ('MetaSel ('Just "ceCol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FieldName) :*: S1 ('MetaSel ('Just "ceVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Value)))

newtype BoolExp (b :: BackendType) Source #

This BoolExp type is a simple alias for the boolean expressions used in permissions, that uses ColExp as the term in GBoolExp.

Constructors

BoolExp 

Instances

Instances details
Backend b => Eq (BoolExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

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

Backend b => Show (BoolExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

showsPrec :: Int -> BoolExp b -> ShowS #

show :: BoolExp b -> String #

showList :: [BoolExp b] -> ShowS #

Generic (BoolExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep (BoolExp b) :: Type -> Type #

Methods

from :: BoolExp b -> Rep (BoolExp b) x #

to :: Rep (BoolExp b) x -> BoolExp b #

Backend b => NFData (BoolExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: BoolExp b -> () #

Backend b => FromJSON (BoolExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

parseJSON :: Value -> Parser (BoolExp b)

parseJSONList :: Value -> Parser [BoolExp b]

Backend b => ToJSON (BoolExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

toJSON :: BoolExp b -> Value

toEncoding :: BoolExp b -> Encoding

toJSONList :: [BoolExp b] -> Value

toEncodingList :: [BoolExp b] -> Encoding

Wrapped (BoolExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Unwrapped (BoolExp b)

Methods

_Wrapped' :: Iso' (BoolExp b) (Unwrapped (BoolExp b))

Backend b => Cacheable (BoolExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

unchanged :: Accesses -> BoolExp b -> BoolExp b -> Bool Source #

BoolExp b1 ~ t => Rewrapped (BoolExp b2) t Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (BoolExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (BoolExp b) = Rep (GBoolExp b ColExp)
type Unwrapped (BoolExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Unwrapped (BoolExp b) = GBoolExp b ColExp

_BoolField :: forall backend field. Prism' (GBoolExp backend field) field Source #

_BoolExists :: forall backend field. Prism' (GBoolExp backend field) (GExists backend field) Source #

_BoolNot :: forall backend field. Prism' (GBoolExp backend field) (GBoolExp backend field) Source #

_BoolOr :: forall backend field. Prism' (GBoolExp backend field) [GBoolExp backend field] Source #

_BoolAnd :: forall backend field. Prism' (GBoolExp backend field) [GBoolExp backend field] Source #

data PartialSQLExp (backend :: BackendType) Source #

Permissions get translated into boolean expressions that are threaded throuhgout the parsers. For the leaf values of those permissions, we use this type, which references but doesn't inline the session variables.

Instances

Instances details
Backend b => Eq (PartialSQLExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Backend b => Show (PartialSQLExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Generic (PartialSQLExp backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep (PartialSQLExp backend) :: Type -> Type #

Methods

from :: PartialSQLExp backend -> Rep (PartialSQLExp backend) x #

to :: Rep (PartialSQLExp backend) x -> PartialSQLExp backend #

(Backend b, NFData (SQLExpression b)) => NFData (PartialSQLExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: PartialSQLExp b -> () #

(Backend b, Hashable (SQLExpression b)) => Hashable (PartialSQLExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Backend b => ToJSON (PartialSQLExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

toJSON :: PartialSQLExp b -> Value

toEncoding :: PartialSQLExp b -> Encoding

toJSONList :: [PartialSQLExp b] -> Value

toEncodingList :: [PartialSQLExp b] -> Encoding

(Backend b, Cacheable (SQLExpression b)) => Cacheable (PartialSQLExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (PartialSQLExp backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (PartialSQLExp backend) = D1 ('MetaData "PartialSQLExp" "Hasura.RQL.IR.BoolExp" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "PSESessVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (SessionVarType backend)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SessionVariable)) :+: (C1 ('MetaCons "PSESession" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PSESQLExp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (SQLExpression backend)))))

type CastExp backend field = HashMap (ScalarType backend) [OpExpG backend field] Source #

Operand for cast operator

data OpExpG (backend :: BackendType) field Source #

This type represents the boolean operators that can be applied on values of a column. This type only contains the common core, that we expect to be ultimately entirely supported in most if not all backends. Backends can extend this with the BooleanOperators type in Backend.

Constructors

ACast (CastExp backend field) 
AEQ Bool field 
ANE Bool field 
AIN field 
ANIN field 
AGT field 
ALT field 
AGTE field 
ALTE field 
ALIKE field 
ANLIKE field 
CEQ (RootOrCurrentColumn backend) 
CNE (RootOrCurrentColumn backend) 
CGT (RootOrCurrentColumn backend) 
CLT (RootOrCurrentColumn backend) 
CGTE (RootOrCurrentColumn backend) 
CLTE (RootOrCurrentColumn backend) 
ANISNULL 
ANISNOTNULL 
ABackendSpecific (BooleanOperators backend field) 

Instances

Instances details
Backend b => Functor (OpExpG b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fmap :: (a -> b0) -> OpExpG b a -> OpExpG b b0 #

(<$) :: a -> OpExpG b b0 -> OpExpG b a #

Backend b => Foldable (OpExpG b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fold :: Monoid m => OpExpG b m -> m #

foldMap :: Monoid m => (a -> m) -> OpExpG b a -> m #

foldMap' :: Monoid m => (a -> m) -> OpExpG b a -> m #

foldr :: (a -> b0 -> b0) -> b0 -> OpExpG b a -> b0 #

foldr' :: (a -> b0 -> b0) -> b0 -> OpExpG b a -> b0 #

foldl :: (b0 -> a -> b0) -> b0 -> OpExpG b a -> b0 #

foldl' :: (b0 -> a -> b0) -> b0 -> OpExpG b a -> b0 #

foldr1 :: (a -> a -> a) -> OpExpG b a -> a #

foldl1 :: (a -> a -> a) -> OpExpG b a -> a #

toList :: OpExpG b a -> [a] #

null :: OpExpG b a -> Bool #

length :: OpExpG b a -> Int #

elem :: Eq a => a -> OpExpG b a -> Bool #

maximum :: Ord a => OpExpG b a -> a #

minimum :: Ord a => OpExpG b a -> a #

sum :: Num a => OpExpG b a -> a #

product :: Num a => OpExpG b a -> a #

Backend b => Traversable (OpExpG b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

sequenceA :: Applicative f => OpExpG b (f a) -> f (OpExpG b a) #

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

sequence :: Monad m => OpExpG b (m a) -> m (OpExpG b a) #

(Backend b, Eq (BooleanOperators b a), Eq a) => Eq (OpExpG b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

(==) :: OpExpG b a -> OpExpG b a -> Bool #

(/=) :: OpExpG b a -> OpExpG b a -> Bool #

(Backend b, Show (BooleanOperators b a), Show a) => Show (OpExpG b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

showsPrec :: Int -> OpExpG b a -> ShowS #

show :: OpExpG b a -> String #

showList :: [OpExpG b a] -> ShowS #

Generic (OpExpG backend field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep (OpExpG backend field) :: Type -> Type #

Methods

from :: OpExpG backend field -> Rep (OpExpG backend field) x #

to :: Rep (OpExpG backend field) x -> OpExpG backend field #

(Backend b, NFData (BooleanOperators b a), NFData a) => NFData (OpExpG b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: OpExpG b a -> () #

(Backend b, Hashable (BooleanOperators b a), Hashable a) => Hashable (OpExpG b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

hashWithSalt :: Int -> OpExpG b a -> Int

hash :: OpExpG b a -> Int

(Backend b, ToJSONKeyValue (BooleanOperators b a), ToJSON a) => ToJSONKeyValue (OpExpG b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

toJSONKeyValue :: OpExpG b a -> (Key, Value) Source #

(Backend b, Cacheable (BooleanOperators b a), Cacheable a) => Cacheable (OpExpG b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

unchanged :: Accesses -> OpExpG b a -> OpExpG b a -> Bool Source #

type Rep (OpExpG backend field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (OpExpG backend field) = D1 ('MetaData "OpExpG" "Hasura.RQL.IR.BoolExp" "graphql-engine-1.0.0-inplace" 'False) ((((C1 ('MetaCons "ACast" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (CastExp backend field))) :+: C1 ('MetaCons "AEQ" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field))) :+: (C1 ('MetaCons "ANE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field)) :+: (C1 ('MetaCons "AIN" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field)) :+: C1 ('MetaCons "ANIN" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field))))) :+: ((C1 ('MetaCons "AGT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field)) :+: C1 ('MetaCons "ALT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field))) :+: (C1 ('MetaCons "AGTE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field)) :+: (C1 ('MetaCons "ALTE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field)) :+: C1 ('MetaCons "ALIKE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field)))))) :+: (((C1 ('MetaCons "ANLIKE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field)) :+: C1 ('MetaCons "CEQ" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (RootOrCurrentColumn backend)))) :+: (C1 ('MetaCons "CNE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (RootOrCurrentColumn backend))) :+: (C1 ('MetaCons "CGT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (RootOrCurrentColumn backend))) :+: C1 ('MetaCons "CLT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (RootOrCurrentColumn backend)))))) :+: ((C1 ('MetaCons "CGTE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (RootOrCurrentColumn backend))) :+: C1 ('MetaCons "CLTE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (RootOrCurrentColumn backend)))) :+: (C1 ('MetaCons "ANISNULL" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ANISNOTNULL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ABackendSpecific" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (BooleanOperators backend field))))))))

data RootOrCurrentColumn b Source #

Instances

Instances details
Backend b => Eq (RootOrCurrentColumn b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Backend b => Show (RootOrCurrentColumn b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Generic (RootOrCurrentColumn b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep (RootOrCurrentColumn b) :: Type -> Type #

Backend b => NFData (RootOrCurrentColumn b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: RootOrCurrentColumn b -> () #

Backend b => Hashable (RootOrCurrentColumn b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Backend b => ToJSON (RootOrCurrentColumn b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Backend b => Cacheable (RootOrCurrentColumn b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (RootOrCurrentColumn b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (RootOrCurrentColumn b) = D1 ('MetaData "RootOrCurrentColumn" "Hasura.RQL.IR.BoolExp" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "RootOrCurrentColumn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RootOrCurrent) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Column b))))

data RootOrCurrent Source #

The arguments of column-operators may refer to either the so-called 'root tabular value' or 'current tabular value'.

Constructors

IsRoot 
IsCurrent 

Instances

Instances details
Eq RootOrCurrent Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Show RootOrCurrent Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Generic RootOrCurrent Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep RootOrCurrent :: Type -> Type #

NFData RootOrCurrent Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: RootOrCurrent -> () #

Hashable RootOrCurrent Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

ToJSON RootOrCurrent Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

toJSON :: RootOrCurrent -> Value

toEncoding :: RootOrCurrent -> Encoding

toJSONList :: [RootOrCurrent] -> Value

toEncodingList :: [RootOrCurrent] -> Encoding

Cacheable RootOrCurrent Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep RootOrCurrent Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep RootOrCurrent = D1 ('MetaData "RootOrCurrent" "Hasura.RQL.IR.BoolExp" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "IsRoot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IsCurrent" 'PrefixI 'False) (U1 :: Type -> Type))

opExpDepCol :: OpExpG backend field -> Maybe (RootOrCurrentColumn backend) Source #

data ComputedFieldBoolExp (backend :: BackendType) scalar Source #

This type is used to represent the kinds of boolean expression used for compouted fields based on the return type of the SQL function.

Constructors

CFBEScalar [OpExpG backend scalar]

SQL function returning a scalar

CFBETable (TableName backend) (AnnBoolExp backend scalar)

SQL function returning SET OF table

Instances

Instances details
Backend backend => Functor (ComputedFieldBoolExp backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fmap :: (a -> b) -> ComputedFieldBoolExp backend a -> ComputedFieldBoolExp backend b #

(<$) :: a -> ComputedFieldBoolExp backend b -> ComputedFieldBoolExp backend a #

Backend backend => Foldable (ComputedFieldBoolExp backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fold :: Monoid m => ComputedFieldBoolExp backend m -> m #

foldMap :: Monoid m => (a -> m) -> ComputedFieldBoolExp backend a -> m #

foldMap' :: Monoid m => (a -> m) -> ComputedFieldBoolExp backend a -> m #

foldr :: (a -> b -> b) -> b -> ComputedFieldBoolExp backend a -> b #

foldr' :: (a -> b -> b) -> b -> ComputedFieldBoolExp backend a -> b #

foldl :: (b -> a -> b) -> b -> ComputedFieldBoolExp backend a -> b #

foldl' :: (b -> a -> b) -> b -> ComputedFieldBoolExp backend a -> b #

foldr1 :: (a -> a -> a) -> ComputedFieldBoolExp backend a -> a #

foldl1 :: (a -> a -> a) -> ComputedFieldBoolExp backend a -> a #

toList :: ComputedFieldBoolExp backend a -> [a] #

null :: ComputedFieldBoolExp backend a -> Bool #

length :: ComputedFieldBoolExp backend a -> Int #

elem :: Eq a => a -> ComputedFieldBoolExp backend a -> Bool #

maximum :: Ord a => ComputedFieldBoolExp backend a -> a #

minimum :: Ord a => ComputedFieldBoolExp backend a -> a #

sum :: Num a => ComputedFieldBoolExp backend a -> a #

product :: Num a => ComputedFieldBoolExp backend a -> a #

Backend backend => Traversable (ComputedFieldBoolExp backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

sequenceA :: Applicative f => ComputedFieldBoolExp backend (f a) -> f (ComputedFieldBoolExp backend a) #

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

sequence :: Monad m => ComputedFieldBoolExp backend (m a) -> m (ComputedFieldBoolExp backend a) #

(Backend b, Eq (AnnBoolExp b a), Eq (OpExpG b a)) => Eq (ComputedFieldBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

(Backend b, Show (AnnBoolExp b a), Show (OpExpG b a)) => Show (ComputedFieldBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Generic (ComputedFieldBoolExp backend scalar) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep (ComputedFieldBoolExp backend scalar) :: Type -> Type #

Methods

from :: ComputedFieldBoolExp backend scalar -> Rep (ComputedFieldBoolExp backend scalar) x #

to :: Rep (ComputedFieldBoolExp backend scalar) x -> ComputedFieldBoolExp backend scalar #

(Backend b, NFData (AnnBoolExp b a), NFData (OpExpG b a)) => NFData (ComputedFieldBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: ComputedFieldBoolExp b a -> () #

(Backend b, Hashable (AnnBoolExp b a), Hashable (OpExpG b a)) => Hashable (ComputedFieldBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

(Backend b, Cacheable (AnnBoolExp b a), Cacheable (OpExpG b a)) => Cacheable (ComputedFieldBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (ComputedFieldBoolExp backend scalar) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (ComputedFieldBoolExp backend scalar) = D1 ('MetaData "ComputedFieldBoolExp" "Hasura.RQL.IR.BoolExp" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "CFBEScalar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [OpExpG backend scalar])) :+: C1 ('MetaCons "CFBETable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (TableName backend)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (AnnBoolExp backend scalar))))

data AnnComputedFieldBoolExp (backend :: BackendType) scalar Source #

Using a computed field in boolean expression. Example: A computed field "full_name" ("first_name" || "last_name") is defined to the "user" table. Boolean expression to filter whose "full_name" is LIKE "%bob%" query { user(where: {full_name: {_like: "%bob%"}}){ id first_name last_name full_name } } Limitation: We only support computed fields in boolean expressions when they are functions with no input arguments, because it is complex to generate schema for where clauses for functions that have input arguments.

Instances

Instances details
Backend b => Functor (AnnComputedFieldBoolExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Backend b => Foldable (AnnComputedFieldBoolExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fold :: Monoid m => AnnComputedFieldBoolExp b m -> m #

foldMap :: Monoid m => (a -> m) -> AnnComputedFieldBoolExp b a -> m #

foldMap' :: Monoid m => (a -> m) -> AnnComputedFieldBoolExp b a -> m #

foldr :: (a -> b0 -> b0) -> b0 -> AnnComputedFieldBoolExp b a -> b0 #

foldr' :: (a -> b0 -> b0) -> b0 -> AnnComputedFieldBoolExp b a -> b0 #

foldl :: (b0 -> a -> b0) -> b0 -> AnnComputedFieldBoolExp b a -> b0 #

foldl' :: (b0 -> a -> b0) -> b0 -> AnnComputedFieldBoolExp b a -> b0 #

foldr1 :: (a -> a -> a) -> AnnComputedFieldBoolExp b a -> a #

foldl1 :: (a -> a -> a) -> AnnComputedFieldBoolExp b a -> a #

toList :: AnnComputedFieldBoolExp b a -> [a] #

null :: AnnComputedFieldBoolExp b a -> Bool #

length :: AnnComputedFieldBoolExp b a -> Int #

elem :: Eq a => a -> AnnComputedFieldBoolExp b a -> Bool #

maximum :: Ord a => AnnComputedFieldBoolExp b a -> a #

minimum :: Ord a => AnnComputedFieldBoolExp b a -> a #

sum :: Num a => AnnComputedFieldBoolExp b a -> a #

product :: Num a => AnnComputedFieldBoolExp b a -> a #

Backend b => Traversable (AnnComputedFieldBoolExp b) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

(Backend b, Eq (ComputedFieldBoolExp b a), Eq (FunctionArgsExp b a)) => Eq (AnnComputedFieldBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

(Backend b, Show (ComputedFieldBoolExp b a), Show (FunctionArgsExp b a)) => Show (AnnComputedFieldBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Generic (AnnComputedFieldBoolExp backend scalar) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep (AnnComputedFieldBoolExp backend scalar) :: Type -> Type #

Methods

from :: AnnComputedFieldBoolExp backend scalar -> Rep (AnnComputedFieldBoolExp backend scalar) x #

to :: Rep (AnnComputedFieldBoolExp backend scalar) x -> AnnComputedFieldBoolExp backend scalar #

(Backend b, NFData (ComputedFieldBoolExp b a), NFData (FunctionArgsExp b a)) => NFData (AnnComputedFieldBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: AnnComputedFieldBoolExp b a -> () #

(Backend b, Hashable (ComputedFieldBoolExp b a), Hashable (FunctionArgsExp b a)) => Hashable (AnnComputedFieldBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

(Backend b, Cacheable (ComputedFieldBoolExp b a), Cacheable (FunctionArgsExp b a)) => Cacheable (AnnComputedFieldBoolExp b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (AnnComputedFieldBoolExp backend scalar) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (AnnComputedFieldBoolExp backend scalar) = D1 ('MetaData "AnnComputedFieldBoolExp" "Hasura.RQL.IR.BoolExp" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "AnnComputedFieldBoolExp" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_acfbXFieldInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (XComputedField backend)) :*: S1 ('MetaSel ('Just "_acfbName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ComputedFieldName)) :*: (S1 ('MetaSel ('Just "_acfbFunction") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (FunctionName backend)) :*: (S1 ('MetaSel ('Just "_acfbFunctionArgsExp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (FunctionArgsExp backend scalar)) :*: S1 ('MetaSel ('Just "_acfbBoolExp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (ComputedFieldBoolExp backend scalar))))))

data AnnBoolExpFld (backend :: BackendType) leaf Source #

This type is used for boolean terms in GBoolExp in the schema; there are four kinds boolean terms: - operators on a column of the current table, using the OpExpG kind of operators - arbitrary expressions on columns of tables in relationships (in the same source) - A computed field of the current table - aggregation operations on array relationships on the current tables.

This type is parameterized over the type of leaf values, the values on which we operate.

Constructors

AVColumn (ColumnInfo backend) [OpExpG backend leaf] 
AVRelationship (RelInfo backend) (AnnBoolExp backend leaf) 
AVComputedField (AnnComputedFieldBoolExp backend leaf) 
AVAggregationPredicates (AggregationPredicates backend leaf) 

Instances

Instances details
Backend backend => Functor (AnnBoolExpFld backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fmap :: (a -> b) -> AnnBoolExpFld backend a -> AnnBoolExpFld backend b #

(<$) :: a -> AnnBoolExpFld backend b -> AnnBoolExpFld backend a #

Backend backend => Foldable (AnnBoolExpFld backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fold :: Monoid m => AnnBoolExpFld backend m -> m #

foldMap :: Monoid m => (a -> m) -> AnnBoolExpFld backend a -> m #

foldMap' :: Monoid m => (a -> m) -> AnnBoolExpFld backend a -> m #

foldr :: (a -> b -> b) -> b -> AnnBoolExpFld backend a -> b #

foldr' :: (a -> b -> b) -> b -> AnnBoolExpFld backend a -> b #

foldl :: (b -> a -> b) -> b -> AnnBoolExpFld backend a -> b #

foldl' :: (b -> a -> b) -> b -> AnnBoolExpFld backend a -> b #

foldr1 :: (a -> a -> a) -> AnnBoolExpFld backend a -> a #

foldl1 :: (a -> a -> a) -> AnnBoolExpFld backend a -> a #

toList :: AnnBoolExpFld backend a -> [a] #

null :: AnnBoolExpFld backend a -> Bool #

length :: AnnBoolExpFld backend a -> Int #

elem :: Eq a => a -> AnnBoolExpFld backend a -> Bool #

maximum :: Ord a => AnnBoolExpFld backend a -> a #

minimum :: Ord a => AnnBoolExpFld backend a -> a #

sum :: Num a => AnnBoolExpFld backend a -> a #

product :: Num a => AnnBoolExpFld backend a -> a #

Backend backend => Traversable (AnnBoolExpFld backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

sequenceA :: Applicative f => AnnBoolExpFld backend (f a) -> f (AnnBoolExpFld backend a) #

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

sequence :: Monad m => AnnBoolExpFld backend (m a) -> m (AnnBoolExpFld backend a) #

(Backend b, Eq (AggregationPredicates b a), Eq (AnnBoolExp b a), Eq (AnnComputedFieldBoolExp b a), Eq (OpExpG b a)) => Eq (AnnBoolExpFld b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

(==) :: AnnBoolExpFld b a -> AnnBoolExpFld b a -> Bool #

(/=) :: AnnBoolExpFld b a -> AnnBoolExpFld b a -> Bool #

(Backend b, Show (AggregationPredicates b a), Show (AnnBoolExp b a), Show (AnnComputedFieldBoolExp b a), Show (OpExpG b a)) => Show (AnnBoolExpFld b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Generic (AnnBoolExpFld backend leaf) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep (AnnBoolExpFld backend leaf) :: Type -> Type #

Methods

from :: AnnBoolExpFld backend leaf -> Rep (AnnBoolExpFld backend leaf) x #

to :: Rep (AnnBoolExpFld backend leaf) x -> AnnBoolExpFld backend leaf #

(Backend b, NFData (AggregationPredicates b a), NFData (AnnBoolExp b a), NFData (AnnComputedFieldBoolExp b a), NFData (OpExpG b a)) => NFData (AnnBoolExpFld b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: AnnBoolExpFld b a -> () #

(Backend b, Hashable (AggregationPredicates b a), Hashable (AnnBoolExp b a), Hashable (AnnComputedFieldBoolExp b a), Hashable (OpExpG b a)) => Hashable (AnnBoolExpFld b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

hashWithSalt :: Int -> AnnBoolExpFld b a -> Int

hash :: AnnBoolExpFld b a -> Int

(Backend b, ToJSONKeyValue (AggregationPredicates b a), ToJSONKeyValue (OpExpG b a), ToJSON a) => ToJSONKeyValue (AnnBoolExpFld b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

toJSONKeyValue :: AnnBoolExpFld b a -> (Key, Value) Source #

(Backend b, Cacheable (AggregationPredicates b a), Cacheable (AnnBoolExp b a), Cacheable (AnnComputedFieldBoolExp b a), Cacheable (OpExpG b a)) => Cacheable (AnnBoolExpFld b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (AnnBoolExpFld backend leaf) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type AnnBoolExp backend scalar = GBoolExp backend (AnnBoolExpFld backend scalar) Source #

A simple alias for the kind of boolean expressions used in the schema, that ties together GBoolExp, OpExpG, and AnnBoolExpFld.

type AnnBoolExpFldSQL backend = AnnBoolExpFld backend (SQLExpression backend) Source #

type AnnBoolExpSQL backend = AnnBoolExp backend (SQLExpression backend) Source #

type AnnBoolExpPartialSQL backend = AnnBoolExp backend (PartialSQLExp backend) Source #

annBoolExpTrue :: AnnBoolExp backend scalar Source #

andAnnBoolExps :: AnnBoolExp backend scalar -> AnnBoolExp backend scalar -> AnnBoolExp backend scalar Source #

data DWithinGeomOp field Source #

Operand for STDWithin opoerator

Constructors

DWithinGeomOp 

Fields

Instances

Instances details
Functor DWithinGeomOp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

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

Foldable DWithinGeomOp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fold :: Monoid m => DWithinGeomOp m -> m #

foldMap :: Monoid m => (a -> m) -> DWithinGeomOp a -> m #

foldMap' :: Monoid m => (a -> m) -> DWithinGeomOp a -> m #

foldr :: (a -> b -> b) -> b -> DWithinGeomOp a -> b #

foldr' :: (a -> b -> b) -> b -> DWithinGeomOp a -> b #

foldl :: (b -> a -> b) -> b -> DWithinGeomOp a -> b #

foldl' :: (b -> a -> b) -> b -> DWithinGeomOp a -> b #

foldr1 :: (a -> a -> a) -> DWithinGeomOp a -> a #

foldl1 :: (a -> a -> a) -> DWithinGeomOp a -> a #

toList :: DWithinGeomOp a -> [a] #

null :: DWithinGeomOp a -> Bool #

length :: DWithinGeomOp a -> Int #

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

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

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

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

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

Traversable DWithinGeomOp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

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

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

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

Eq field => Eq (DWithinGeomOp field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

(==) :: DWithinGeomOp field -> DWithinGeomOp field -> Bool #

(/=) :: DWithinGeomOp field -> DWithinGeomOp field -> Bool #

Data field => Data (DWithinGeomOp field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

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

toConstr :: DWithinGeomOp field -> Constr #

dataTypeOf :: DWithinGeomOp field -> DataType #

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

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

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

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

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

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

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

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

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

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

Show field => Show (DWithinGeomOp field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

showsPrec :: Int -> DWithinGeomOp field -> ShowS #

show :: DWithinGeomOp field -> String #

showList :: [DWithinGeomOp field] -> ShowS #

Generic (DWithinGeomOp field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep (DWithinGeomOp field) :: Type -> Type #

Methods

from :: DWithinGeomOp field -> Rep (DWithinGeomOp field) x #

to :: Rep (DWithinGeomOp field) x -> DWithinGeomOp field #

NFData a => NFData (DWithinGeomOp a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: DWithinGeomOp a -> () #

Hashable a => Hashable (DWithinGeomOp a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

FromJSON field => FromJSON (DWithinGeomOp field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

parseJSON :: Value -> Parser (DWithinGeomOp field)

parseJSONList :: Value -> Parser [DWithinGeomOp field]

ToJSON field => ToJSON (DWithinGeomOp field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

toJSON :: DWithinGeomOp field -> Value

toEncoding :: DWithinGeomOp field -> Encoding

toJSONList :: [DWithinGeomOp field] -> Value

toEncodingList :: [DWithinGeomOp field] -> Encoding

Cacheable a => Cacheable (DWithinGeomOp a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (DWithinGeomOp field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (DWithinGeomOp field) = D1 ('MetaData "DWithinGeomOp" "Hasura.RQL.IR.BoolExp" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "DWithinGeomOp" 'PrefixI 'True) (S1 ('MetaSel ('Just "dwgeomDistance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field) :*: S1 ('MetaSel ('Just "dwgeomFrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field)))

data DWithinGeogOp field Source #

Operand for STDWithin opoerator

Constructors

DWithinGeogOp 

Fields

Instances

Instances details
Functor DWithinGeogOp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

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

Foldable DWithinGeogOp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fold :: Monoid m => DWithinGeogOp m -> m #

foldMap :: Monoid m => (a -> m) -> DWithinGeogOp a -> m #

foldMap' :: Monoid m => (a -> m) -> DWithinGeogOp a -> m #

foldr :: (a -> b -> b) -> b -> DWithinGeogOp a -> b #

foldr' :: (a -> b -> b) -> b -> DWithinGeogOp a -> b #

foldl :: (b -> a -> b) -> b -> DWithinGeogOp a -> b #

foldl' :: (b -> a -> b) -> b -> DWithinGeogOp a -> b #

foldr1 :: (a -> a -> a) -> DWithinGeogOp a -> a #

foldl1 :: (a -> a -> a) -> DWithinGeogOp a -> a #

toList :: DWithinGeogOp a -> [a] #

null :: DWithinGeogOp a -> Bool #

length :: DWithinGeogOp a -> Int #

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

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

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

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

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

Traversable DWithinGeogOp Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

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

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

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

Eq field => Eq (DWithinGeogOp field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

(==) :: DWithinGeogOp field -> DWithinGeogOp field -> Bool #

(/=) :: DWithinGeogOp field -> DWithinGeogOp field -> Bool #

Data field => Data (DWithinGeogOp field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

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

toConstr :: DWithinGeogOp field -> Constr #

dataTypeOf :: DWithinGeogOp field -> DataType #

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

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

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

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

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

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

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

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

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

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

Show field => Show (DWithinGeogOp field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

showsPrec :: Int -> DWithinGeogOp field -> ShowS #

show :: DWithinGeogOp field -> String #

showList :: [DWithinGeogOp field] -> ShowS #

Generic (DWithinGeogOp field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep (DWithinGeogOp field) :: Type -> Type #

Methods

from :: DWithinGeogOp field -> Rep (DWithinGeogOp field) x #

to :: Rep (DWithinGeogOp field) x -> DWithinGeogOp field #

NFData a => NFData (DWithinGeogOp a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: DWithinGeogOp a -> () #

Hashable a => Hashable (DWithinGeogOp a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

FromJSON field => FromJSON (DWithinGeogOp field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

parseJSON :: Value -> Parser (DWithinGeogOp field)

parseJSONList :: Value -> Parser [DWithinGeogOp field]

ToJSON field => ToJSON (DWithinGeogOp field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

toJSON :: DWithinGeogOp field -> Value

toEncoding :: DWithinGeogOp field -> Encoding

toJSONList :: [DWithinGeogOp field] -> Value

toEncodingList :: [DWithinGeogOp field] -> Encoding

Cacheable a => Cacheable (DWithinGeogOp a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (DWithinGeogOp field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (DWithinGeogOp field) = D1 ('MetaData "DWithinGeogOp" "Hasura.RQL.IR.BoolExp" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "DWithinGeogOp" 'PrefixI 'True) (S1 ('MetaSel ('Just "dwgeogDistance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field) :*: (S1 ('MetaSel ('Just "dwgeogFrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field) :*: S1 ('MetaSel ('Just "dwgeogUseSpheroid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field))))

data STIntersectsNbandGeommin field Source #

Operand for STIntersect

Constructors

STIntersectsNbandGeommin 

Fields

Instances

Instances details
Functor STIntersectsNbandGeommin Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Foldable STIntersectsNbandGeommin Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fold :: Monoid m => STIntersectsNbandGeommin m -> m #

foldMap :: Monoid m => (a -> m) -> STIntersectsNbandGeommin a -> m #

foldMap' :: Monoid m => (a -> m) -> STIntersectsNbandGeommin a -> m #

foldr :: (a -> b -> b) -> b -> STIntersectsNbandGeommin a -> b #

foldr' :: (a -> b -> b) -> b -> STIntersectsNbandGeommin a -> b #

foldl :: (b -> a -> b) -> b -> STIntersectsNbandGeommin a -> b #

foldl' :: (b -> a -> b) -> b -> STIntersectsNbandGeommin a -> b #

foldr1 :: (a -> a -> a) -> STIntersectsNbandGeommin a -> a #

foldl1 :: (a -> a -> a) -> STIntersectsNbandGeommin a -> a #

toList :: STIntersectsNbandGeommin a -> [a] #

null :: STIntersectsNbandGeommin a -> Bool #

length :: STIntersectsNbandGeommin a -> Int #

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

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

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

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

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

Traversable STIntersectsNbandGeommin Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Eq field => Eq (STIntersectsNbandGeommin field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Data field => Data (STIntersectsNbandGeommin field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

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

toConstr :: STIntersectsNbandGeommin field -> Constr #

dataTypeOf :: STIntersectsNbandGeommin field -> DataType #

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

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

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

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

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

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

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

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

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

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

Show field => Show (STIntersectsNbandGeommin field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Generic (STIntersectsNbandGeommin field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep (STIntersectsNbandGeommin field) :: Type -> Type #

NFData a => NFData (STIntersectsNbandGeommin a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: STIntersectsNbandGeommin a -> () #

Hashable a => Hashable (STIntersectsNbandGeommin a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

FromJSON field => FromJSON (STIntersectsNbandGeommin field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

parseJSON :: Value -> Parser (STIntersectsNbandGeommin field)

parseJSONList :: Value -> Parser [STIntersectsNbandGeommin field]

ToJSON field => ToJSON (STIntersectsNbandGeommin field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

toJSON :: STIntersectsNbandGeommin field -> Value

toEncoding :: STIntersectsNbandGeommin field -> Encoding

toJSONList :: [STIntersectsNbandGeommin field] -> Value

toEncodingList :: [STIntersectsNbandGeommin field] -> Encoding

Cacheable a => Cacheable (STIntersectsNbandGeommin a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (STIntersectsNbandGeommin field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (STIntersectsNbandGeommin field) = D1 ('MetaData "STIntersectsNbandGeommin" "Hasura.RQL.IR.BoolExp" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "STIntersectsNbandGeommin" 'PrefixI 'True) (S1 ('MetaSel ('Just "singNband") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field) :*: S1 ('MetaSel ('Just "singGeommin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field)))

data STIntersectsGeomminNband field Source #

Operand for STIntersect

Constructors

STIntersectsGeomminNband 

Fields

Instances

Instances details
Functor STIntersectsGeomminNband Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Foldable STIntersectsGeomminNband Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fold :: Monoid m => STIntersectsGeomminNband m -> m #

foldMap :: Monoid m => (a -> m) -> STIntersectsGeomminNband a -> m #

foldMap' :: Monoid m => (a -> m) -> STIntersectsGeomminNband a -> m #

foldr :: (a -> b -> b) -> b -> STIntersectsGeomminNband a -> b #

foldr' :: (a -> b -> b) -> b -> STIntersectsGeomminNband a -> b #

foldl :: (b -> a -> b) -> b -> STIntersectsGeomminNband a -> b #

foldl' :: (b -> a -> b) -> b -> STIntersectsGeomminNband a -> b #

foldr1 :: (a -> a -> a) -> STIntersectsGeomminNband a -> a #

foldl1 :: (a -> a -> a) -> STIntersectsGeomminNband a -> a #

toList :: STIntersectsGeomminNband a -> [a] #

null :: STIntersectsGeomminNband a -> Bool #

length :: STIntersectsGeomminNband a -> Int #

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

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

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

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

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

Traversable STIntersectsGeomminNband Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Eq field => Eq (STIntersectsGeomminNband field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Data field => Data (STIntersectsGeomminNband field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

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

toConstr :: STIntersectsGeomminNband field -> Constr #

dataTypeOf :: STIntersectsGeomminNband field -> DataType #

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

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

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

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

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

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

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

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

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

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

Show field => Show (STIntersectsGeomminNband field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Generic (STIntersectsGeomminNband field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep (STIntersectsGeomminNband field) :: Type -> Type #

NFData a => NFData (STIntersectsGeomminNband a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: STIntersectsGeomminNband a -> () #

Hashable a => Hashable (STIntersectsGeomminNband a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

FromJSON field => FromJSON (STIntersectsGeomminNband field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

parseJSON :: Value -> Parser (STIntersectsGeomminNband field)

parseJSONList :: Value -> Parser [STIntersectsGeomminNband field]

ToJSON field => ToJSON (STIntersectsGeomminNband field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

toJSON :: STIntersectsGeomminNband field -> Value

toEncoding :: STIntersectsGeomminNband field -> Encoding

toJSONList :: [STIntersectsGeomminNband field] -> Value

toEncodingList :: [STIntersectsGeomminNband field] -> Encoding

Cacheable a => Cacheable (STIntersectsGeomminNband a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (STIntersectsGeomminNband field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (STIntersectsGeomminNband field) = D1 ('MetaData "STIntersectsGeomminNband" "Hasura.RQL.IR.BoolExp" "graphql-engine-1.0.0-inplace" 'False) (C1 ('MetaCons "STIntersectsGeomminNband" 'PrefixI 'True) (S1 ('MetaSel ('Just "signGeommin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 field) :*: S1 ('MetaSel ('Just "signNband") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe field))))

newtype AnnColumnCaseBoolExpField (backend :: BackendType) field Source #

This is a simple newtype over AnnBoolExpFld. At time of writing, I do not know why we want this, and why it exists. It might be a relic of a needed differentiation, now lost? TODO: can this be removed?

Instances

Instances details
Backend backend => Functor (AnnColumnCaseBoolExpField backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fmap :: (a -> b) -> AnnColumnCaseBoolExpField backend a -> AnnColumnCaseBoolExpField backend b #

(<$) :: a -> AnnColumnCaseBoolExpField backend b -> AnnColumnCaseBoolExpField backend a #

Backend backend => Foldable (AnnColumnCaseBoolExpField backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

fold :: Monoid m => AnnColumnCaseBoolExpField backend m -> m #

foldMap :: Monoid m => (a -> m) -> AnnColumnCaseBoolExpField backend a -> m #

foldMap' :: Monoid m => (a -> m) -> AnnColumnCaseBoolExpField backend a -> m #

foldr :: (a -> b -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b #

foldr' :: (a -> b -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b #

foldl :: (b -> a -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b #

foldl' :: (b -> a -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b #

foldr1 :: (a -> a -> a) -> AnnColumnCaseBoolExpField backend a -> a #

foldl1 :: (a -> a -> a) -> AnnColumnCaseBoolExpField backend a -> a #

toList :: AnnColumnCaseBoolExpField backend a -> [a] #

null :: AnnColumnCaseBoolExpField backend a -> Bool #

length :: AnnColumnCaseBoolExpField backend a -> Int #

elem :: Eq a => a -> AnnColumnCaseBoolExpField backend a -> Bool #

maximum :: Ord a => AnnColumnCaseBoolExpField backend a -> a #

minimum :: Ord a => AnnColumnCaseBoolExpField backend a -> a #

sum :: Num a => AnnColumnCaseBoolExpField backend a -> a #

product :: Num a => AnnColumnCaseBoolExpField backend a -> a #

Backend backend => Traversable (AnnColumnCaseBoolExpField backend) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

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

sequenceA :: Applicative f => AnnColumnCaseBoolExpField backend (f a) -> f (AnnColumnCaseBoolExpField backend a) #

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

sequence :: Monad m => AnnColumnCaseBoolExpField backend (m a) -> m (AnnColumnCaseBoolExpField backend a) #

Eq (AnnBoolExpFld b a) => Eq (AnnColumnCaseBoolExpField b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

(Backend b, Show (AnnBoolExpFld b a), Show a) => Show (AnnColumnCaseBoolExpField b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Generic (AnnColumnCaseBoolExpField backend field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Associated Types

type Rep (AnnColumnCaseBoolExpField backend field) :: Type -> Type #

Methods

from :: AnnColumnCaseBoolExpField backend field -> Rep (AnnColumnCaseBoolExpField backend field) x #

to :: Rep (AnnColumnCaseBoolExpField backend field) x -> AnnColumnCaseBoolExpField backend field #

(Backend b, NFData (AnnBoolExpFld b a), NFData a) => NFData (AnnColumnCaseBoolExpField b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

rnf :: AnnColumnCaseBoolExpField b a -> () #

(Backend b, Hashable (AnnBoolExpFld b a), Hashable a) => Hashable (AnnColumnCaseBoolExpField b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

ToJSONKeyValue (AnnBoolExpFld b a) => ToJSONKeyValue (AnnColumnCaseBoolExpField b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

Methods

toJSONKeyValue :: AnnColumnCaseBoolExpField b a -> (Key, Value) Source #

(Backend b, Cacheable (AnnBoolExpFld b a), Cacheable a) => Cacheable (AnnColumnCaseBoolExpField b a) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (AnnColumnCaseBoolExpField backend field) Source # 
Instance details

Defined in Hasura.RQL.IR.BoolExp

type Rep (AnnColumnCaseBoolExpField backend field) = D1 ('MetaData "AnnColumnCaseBoolExpField" "Hasura.RQL.IR.BoolExp" "graphql-engine-1.0.0-inplace" 'True) (C1 ('MetaCons "AnnColumnCaseBoolExpField" 'PrefixI 'True) (S1 ('MetaSel ('Just "_accColCaseBoolExpField") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AnnBoolExpFld backend field))))

type AnnColumnCaseBoolExp b a = GBoolExp b (AnnColumnCaseBoolExpField b a) Source #

Similar to AnnBoolExp, this type alias ties together GBoolExp, OpExpG, and AnnColumnCaseBoolExpFld.

type PreSetColsG b v = HashMap (Column b) v Source #

type PreSetColsPartial b = HashMap (Column b) (PartialSQLExp b) Source #