{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
module Hasura.RQL.IR.BoolExp
( BoolExp (..),
ColExp (..),
GBoolExp (..),
gBoolExpTrue,
GExists (..),
geWhere,
geTable,
_BoolExists,
DWithinGeomOp (..),
DWithinGeogOp (..),
CastExp,
OpExpG (..),
opExpDepCol,
STIntersectsNbandGeommin (..),
STIntersectsGeomminNband (..),
ComputedFieldBoolExp (..),
AnnComputedFieldBoolExp (..),
AnnBoolExpFld (..),
AnnBoolExp,
AnnColumnCaseBoolExpPartialSQL,
AnnColumnCaseBoolExp,
AnnColumnCaseBoolExpField (..),
annBoolExpTrue,
andAnnBoolExps,
AnnBoolExpFldSQL,
AnnBoolExpSQL,
PartialSQLExp (..),
isStaticValue,
hasStaticExp,
AnnBoolExpPartialSQL,
PreSetColsG,
PreSetColsPartial,
RootOrCurrentColumn (..),
RootOrCurrent (..),
)
where
import Control.Lens.Plated
import Control.Lens.TH
import Data.Aeson.Extended
import Data.Aeson.Internal
import Data.Aeson.Key qualified as K
import Data.Aeson.KeyMap qualified as KM
import Data.Aeson.TH
import Data.HashMap.Strict qualified as M
import Data.Monoid
import Data.Text.Extended
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.ComputedField
import Hasura.RQL.Types.Function
import Hasura.RQL.Types.Relationships.Local
import Hasura.SQL.Backend
import Hasura.Session
data GBoolExp (backend :: BackendType) field
= BoolAnd [GBoolExp backend field]
| BoolOr [GBoolExp backend field]
| BoolNot (GBoolExp backend field)
|
BoolExists (GExists backend field)
|
BoolField field
deriving (Int -> GBoolExp backend field -> ShowS
[GBoolExp backend field] -> ShowS
GBoolExp backend field -> String
(Int -> GBoolExp backend field -> ShowS)
-> (GBoolExp backend field -> String)
-> ([GBoolExp backend field] -> ShowS)
-> Show (GBoolExp backend field)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (backend :: BackendType) field.
(Backend backend, Show field) =>
Int -> GBoolExp backend field -> ShowS
forall (backend :: BackendType) field.
(Backend backend, Show field) =>
[GBoolExp backend field] -> ShowS
forall (backend :: BackendType) field.
(Backend backend, Show field) =>
GBoolExp backend field -> String
showList :: [GBoolExp backend field] -> ShowS
$cshowList :: forall (backend :: BackendType) field.
(Backend backend, Show field) =>
[GBoolExp backend field] -> ShowS
show :: GBoolExp backend field -> String
$cshow :: forall (backend :: BackendType) field.
(Backend backend, Show field) =>
GBoolExp backend field -> String
showsPrec :: Int -> GBoolExp backend field -> ShowS
$cshowsPrec :: forall (backend :: BackendType) field.
(Backend backend, Show field) =>
Int -> GBoolExp backend field -> ShowS
Show, GBoolExp backend field -> GBoolExp backend field -> Bool
(GBoolExp backend field -> GBoolExp backend field -> Bool)
-> (GBoolExp backend field -> GBoolExp backend field -> Bool)
-> Eq (GBoolExp backend field)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (backend :: BackendType) field.
(Backend backend, Eq field) =>
GBoolExp backend field -> GBoolExp backend field -> Bool
/= :: GBoolExp backend field -> GBoolExp backend field -> Bool
$c/= :: forall (backend :: BackendType) field.
(Backend backend, Eq field) =>
GBoolExp backend field -> GBoolExp backend field -> Bool
== :: GBoolExp backend field -> GBoolExp backend field -> Bool
$c== :: forall (backend :: BackendType) field.
(Backend backend, Eq field) =>
GBoolExp backend field -> GBoolExp backend field -> Bool
Eq, a -> GBoolExp backend b -> GBoolExp backend a
(a -> b) -> GBoolExp backend a -> GBoolExp backend b
(forall a b. (a -> b) -> GBoolExp backend a -> GBoolExp backend b)
-> (forall a b. a -> GBoolExp backend b -> GBoolExp backend a)
-> Functor (GBoolExp backend)
forall a b. a -> GBoolExp backend b -> GBoolExp backend a
forall a b. (a -> b) -> GBoolExp backend a -> GBoolExp backend b
forall (backend :: BackendType) a b.
a -> GBoolExp backend b -> GBoolExp backend a
forall (backend :: BackendType) a b.
(a -> b) -> GBoolExp backend a -> GBoolExp backend b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> GBoolExp backend b -> GBoolExp backend a
$c<$ :: forall (backend :: BackendType) a b.
a -> GBoolExp backend b -> GBoolExp backend a
fmap :: (a -> b) -> GBoolExp backend a -> GBoolExp backend b
$cfmap :: forall (backend :: BackendType) a b.
(a -> b) -> GBoolExp backend a -> GBoolExp backend b
Functor, GBoolExp backend a -> Bool
(a -> m) -> GBoolExp backend a -> m
(a -> b -> b) -> b -> GBoolExp backend a -> b
(forall m. Monoid m => GBoolExp backend m -> m)
-> (forall m a. Monoid m => (a -> m) -> GBoolExp backend a -> m)
-> (forall m a. Monoid m => (a -> m) -> GBoolExp backend a -> m)
-> (forall a b. (a -> b -> b) -> b -> GBoolExp backend a -> b)
-> (forall a b. (a -> b -> b) -> b -> GBoolExp backend a -> b)
-> (forall b a. (b -> a -> b) -> b -> GBoolExp backend a -> b)
-> (forall b a. (b -> a -> b) -> b -> GBoolExp backend a -> b)
-> (forall a. (a -> a -> a) -> GBoolExp backend a -> a)
-> (forall a. (a -> a -> a) -> GBoolExp backend a -> a)
-> (forall a. GBoolExp backend a -> [a])
-> (forall a. GBoolExp backend a -> Bool)
-> (forall a. GBoolExp backend a -> Int)
-> (forall a. Eq a => a -> GBoolExp backend a -> Bool)
-> (forall a. Ord a => GBoolExp backend a -> a)
-> (forall a. Ord a => GBoolExp backend a -> a)
-> (forall a. Num a => GBoolExp backend a -> a)
-> (forall a. Num a => GBoolExp backend a -> a)
-> Foldable (GBoolExp backend)
forall a. Eq a => a -> GBoolExp backend a -> Bool
forall a. Num a => GBoolExp backend a -> a
forall a. Ord a => GBoolExp backend a -> a
forall m. Monoid m => GBoolExp backend m -> m
forall a. GBoolExp backend a -> Bool
forall a. GBoolExp backend a -> Int
forall a. GBoolExp backend a -> [a]
forall a. (a -> a -> a) -> GBoolExp backend a -> a
forall m a. Monoid m => (a -> m) -> GBoolExp backend a -> m
forall b a. (b -> a -> b) -> b -> GBoolExp backend a -> b
forall a b. (a -> b -> b) -> b -> GBoolExp backend a -> b
forall (backend :: BackendType) a.
Eq a =>
a -> GBoolExp backend a -> Bool
forall (backend :: BackendType) a. Num a => GBoolExp backend a -> a
forall (backend :: BackendType) a. Ord a => GBoolExp backend a -> a
forall (backend :: BackendType) m.
Monoid m =>
GBoolExp backend m -> m
forall (backend :: BackendType) a. GBoolExp backend a -> Bool
forall (backend :: BackendType) a. GBoolExp backend a -> Int
forall (backend :: BackendType) a. GBoolExp backend a -> [a]
forall (backend :: BackendType) a.
(a -> a -> a) -> GBoolExp backend a -> a
forall (backend :: BackendType) m a.
Monoid m =>
(a -> m) -> GBoolExp backend a -> m
forall (backend :: BackendType) b a.
(b -> a -> b) -> b -> GBoolExp backend a -> b
forall (backend :: BackendType) a b.
(a -> b -> b) -> b -> GBoolExp backend a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: GBoolExp backend a -> a
$cproduct :: forall (backend :: BackendType) a. Num a => GBoolExp backend a -> a
sum :: GBoolExp backend a -> a
$csum :: forall (backend :: BackendType) a. Num a => GBoolExp backend a -> a
minimum :: GBoolExp backend a -> a
$cminimum :: forall (backend :: BackendType) a. Ord a => GBoolExp backend a -> a
maximum :: GBoolExp backend a -> a
$cmaximum :: forall (backend :: BackendType) a. Ord a => GBoolExp backend a -> a
elem :: a -> GBoolExp backend a -> Bool
$celem :: forall (backend :: BackendType) a.
Eq a =>
a -> GBoolExp backend a -> Bool
length :: GBoolExp backend a -> Int
$clength :: forall (backend :: BackendType) a. GBoolExp backend a -> Int
null :: GBoolExp backend a -> Bool
$cnull :: forall (backend :: BackendType) a. GBoolExp backend a -> Bool
toList :: GBoolExp backend a -> [a]
$ctoList :: forall (backend :: BackendType) a. GBoolExp backend a -> [a]
foldl1 :: (a -> a -> a) -> GBoolExp backend a -> a
$cfoldl1 :: forall (backend :: BackendType) a.
(a -> a -> a) -> GBoolExp backend a -> a
foldr1 :: (a -> a -> a) -> GBoolExp backend a -> a
$cfoldr1 :: forall (backend :: BackendType) a.
(a -> a -> a) -> GBoolExp backend a -> a
foldl' :: (b -> a -> b) -> b -> GBoolExp backend a -> b
$cfoldl' :: forall (backend :: BackendType) b a.
(b -> a -> b) -> b -> GBoolExp backend a -> b
foldl :: (b -> a -> b) -> b -> GBoolExp backend a -> b
$cfoldl :: forall (backend :: BackendType) b a.
(b -> a -> b) -> b -> GBoolExp backend a -> b
foldr' :: (a -> b -> b) -> b -> GBoolExp backend a -> b
$cfoldr' :: forall (backend :: BackendType) a b.
(a -> b -> b) -> b -> GBoolExp backend a -> b
foldr :: (a -> b -> b) -> b -> GBoolExp backend a -> b
$cfoldr :: forall (backend :: BackendType) a b.
(a -> b -> b) -> b -> GBoolExp backend a -> b
foldMap' :: (a -> m) -> GBoolExp backend a -> m
$cfoldMap' :: forall (backend :: BackendType) m a.
Monoid m =>
(a -> m) -> GBoolExp backend a -> m
foldMap :: (a -> m) -> GBoolExp backend a -> m
$cfoldMap :: forall (backend :: BackendType) m a.
Monoid m =>
(a -> m) -> GBoolExp backend a -> m
fold :: GBoolExp backend m -> m
$cfold :: forall (backend :: BackendType) m.
Monoid m =>
GBoolExp backend m -> m
Foldable, Functor (GBoolExp backend)
Foldable (GBoolExp backend)
Functor (GBoolExp backend)
-> Foldable (GBoolExp backend)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GBoolExp backend a -> f (GBoolExp backend b))
-> (forall (f :: * -> *) a.
Applicative f =>
GBoolExp backend (f a) -> f (GBoolExp backend a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GBoolExp backend a -> m (GBoolExp backend b))
-> (forall (m :: * -> *) a.
Monad m =>
GBoolExp backend (m a) -> m (GBoolExp backend a))
-> Traversable (GBoolExp backend)
(a -> f b) -> GBoolExp backend a -> f (GBoolExp backend b)
forall (backend :: BackendType). Functor (GBoolExp backend)
forall (backend :: BackendType). Foldable (GBoolExp backend)
forall (backend :: BackendType) (m :: * -> *) a.
Monad m =>
GBoolExp backend (m a) -> m (GBoolExp backend a)
forall (backend :: BackendType) (f :: * -> *) a.
Applicative f =>
GBoolExp backend (f a) -> f (GBoolExp backend a)
forall (backend :: BackendType) (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GBoolExp backend a -> m (GBoolExp backend b)
forall (backend :: BackendType) (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GBoolExp backend a -> f (GBoolExp backend b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
GBoolExp backend (m a) -> m (GBoolExp backend a)
forall (f :: * -> *) a.
Applicative f =>
GBoolExp backend (f a) -> f (GBoolExp backend a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GBoolExp backend a -> m (GBoolExp backend b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GBoolExp backend a -> f (GBoolExp backend b)
sequence :: GBoolExp backend (m a) -> m (GBoolExp backend a)
$csequence :: forall (backend :: BackendType) (m :: * -> *) a.
Monad m =>
GBoolExp backend (m a) -> m (GBoolExp backend a)
mapM :: (a -> m b) -> GBoolExp backend a -> m (GBoolExp backend b)
$cmapM :: forall (backend :: BackendType) (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GBoolExp backend a -> m (GBoolExp backend b)
sequenceA :: GBoolExp backend (f a) -> f (GBoolExp backend a)
$csequenceA :: forall (backend :: BackendType) (f :: * -> *) a.
Applicative f =>
GBoolExp backend (f a) -> f (GBoolExp backend a)
traverse :: (a -> f b) -> GBoolExp backend a -> f (GBoolExp backend b)
$ctraverse :: forall (backend :: BackendType) (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GBoolExp backend a -> f (GBoolExp backend b)
$cp2Traversable :: forall (backend :: BackendType). Foldable (GBoolExp backend)
$cp1Traversable :: forall (backend :: BackendType). Functor (GBoolExp backend)
Traversable, Typeable (GBoolExp backend field)
DataType
Constr
Typeable (GBoolExp backend field)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> GBoolExp backend field
-> c (GBoolExp backend field))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GBoolExp backend field))
-> (GBoolExp backend field -> Constr)
-> (GBoolExp backend field -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (GBoolExp backend field)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GBoolExp backend field)))
-> ((forall b. Data b => b -> b)
-> GBoolExp backend field -> GBoolExp backend field)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> GBoolExp backend field
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> GBoolExp backend field
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> GBoolExp backend field -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> GBoolExp backend field -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> GBoolExp backend field -> m (GBoolExp backend field))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GBoolExp backend field -> m (GBoolExp backend field))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GBoolExp backend field -> m (GBoolExp backend field))
-> Data (GBoolExp backend field)
GBoolExp backend field -> DataType
GBoolExp backend field -> Constr
(forall b. Data b => b -> b)
-> GBoolExp backend field -> GBoolExp backend field
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> GBoolExp backend field
-> c (GBoolExp backend field)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GBoolExp backend field)
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> GBoolExp backend field -> u
forall u.
(forall d. Data d => d -> u) -> GBoolExp backend field -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> GBoolExp backend field
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> GBoolExp backend field
-> r
forall (backend :: BackendType) field.
(Backend backend, Data field) =>
Typeable (GBoolExp backend field)
forall (backend :: BackendType) field.
(Backend backend, Data field) =>
GBoolExp backend field -> DataType
forall (backend :: BackendType) field.
(Backend backend, Data field) =>
GBoolExp backend field -> Constr
forall (backend :: BackendType) field.
(Backend backend, Data field) =>
(forall b. Data b => b -> b)
-> GBoolExp backend field -> GBoolExp backend field
forall (backend :: BackendType) field u.
(Backend backend, Data field) =>
Int -> (forall d. Data d => d -> u) -> GBoolExp backend field -> u
forall (backend :: BackendType) field u.
(Backend backend, Data field) =>
(forall d. Data d => d -> u) -> GBoolExp backend field -> [u]
forall (backend :: BackendType) field r r'.
(Backend backend, Data field) =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> GBoolExp backend field
-> r
forall (backend :: BackendType) field r r'.
(Backend backend, Data field) =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> GBoolExp backend field
-> r
forall (backend :: BackendType) field (m :: * -> *).
(Backend backend, Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> GBoolExp backend field -> m (GBoolExp backend field)
forall (backend :: BackendType) field (m :: * -> *).
(Backend backend, Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> GBoolExp backend field -> m (GBoolExp backend field)
forall (backend :: BackendType) field (c :: * -> *).
(Backend backend, Data field) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GBoolExp backend field)
forall (backend :: BackendType) field (c :: * -> *).
(Backend backend, Data field) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> GBoolExp backend field
-> c (GBoolExp backend field)
forall (backend :: BackendType) field (t :: * -> *) (c :: * -> *).
(Backend backend, Data field, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (GBoolExp backend field))
forall (backend :: BackendType) field (t :: * -> * -> *)
(c :: * -> *).
(Backend backend, Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GBoolExp backend field))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> GBoolExp backend field -> m (GBoolExp backend field)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GBoolExp backend field -> m (GBoolExp backend field)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GBoolExp backend field)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> GBoolExp backend field
-> c (GBoolExp backend field)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (GBoolExp backend field))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GBoolExp backend field))
$cBoolField :: Constr
$cBoolExists :: Constr
$cBoolNot :: Constr
$cBoolOr :: Constr
$cBoolAnd :: Constr
$tGBoolExp :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> GBoolExp backend field -> m (GBoolExp backend field)
$cgmapMo :: forall (backend :: BackendType) field (m :: * -> *).
(Backend backend, Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> GBoolExp backend field -> m (GBoolExp backend field)
gmapMp :: (forall d. Data d => d -> m d)
-> GBoolExp backend field -> m (GBoolExp backend field)
$cgmapMp :: forall (backend :: BackendType) field (m :: * -> *).
(Backend backend, Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> GBoolExp backend field -> m (GBoolExp backend field)
gmapM :: (forall d. Data d => d -> m d)
-> GBoolExp backend field -> m (GBoolExp backend field)
$cgmapM :: forall (backend :: BackendType) field (m :: * -> *).
(Backend backend, Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> GBoolExp backend field -> m (GBoolExp backend field)
gmapQi :: Int -> (forall d. Data d => d -> u) -> GBoolExp backend field -> u
$cgmapQi :: forall (backend :: BackendType) field u.
(Backend backend, Data field) =>
Int -> (forall d. Data d => d -> u) -> GBoolExp backend field -> u
gmapQ :: (forall d. Data d => d -> u) -> GBoolExp backend field -> [u]
$cgmapQ :: forall (backend :: BackendType) field u.
(Backend backend, Data field) =>
(forall d. Data d => d -> u) -> GBoolExp backend field -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> GBoolExp backend field
-> r
$cgmapQr :: forall (backend :: BackendType) field r r'.
(Backend backend, Data field) =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> GBoolExp backend field
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> GBoolExp backend field
-> r
$cgmapQl :: forall (backend :: BackendType) field r r'.
(Backend backend, Data field) =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> GBoolExp backend field
-> r
gmapT :: (forall b. Data b => b -> b)
-> GBoolExp backend field -> GBoolExp backend field
$cgmapT :: forall (backend :: BackendType) field.
(Backend backend, Data field) =>
(forall b. Data b => b -> b)
-> GBoolExp backend field -> GBoolExp backend field
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GBoolExp backend field))
$cdataCast2 :: forall (backend :: BackendType) field (t :: * -> * -> *)
(c :: * -> *).
(Backend backend, Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (GBoolExp backend field))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (GBoolExp backend field))
$cdataCast1 :: forall (backend :: BackendType) field (t :: * -> *) (c :: * -> *).
(Backend backend, Data field, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (GBoolExp backend field))
dataTypeOf :: GBoolExp backend field -> DataType
$cdataTypeOf :: forall (backend :: BackendType) field.
(Backend backend, Data field) =>
GBoolExp backend field -> DataType
toConstr :: GBoolExp backend field -> Constr
$ctoConstr :: forall (backend :: BackendType) field.
(Backend backend, Data field) =>
GBoolExp backend field -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GBoolExp backend field)
$cgunfold :: forall (backend :: BackendType) field (c :: * -> *).
(Backend backend, Data field) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GBoolExp backend field)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> GBoolExp backend field
-> c (GBoolExp backend field)
$cgfoldl :: forall (backend :: BackendType) field (c :: * -> *).
(Backend backend, Data field) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> GBoolExp backend field
-> c (GBoolExp backend field)
$cp1Data :: forall (backend :: BackendType) field.
(Backend backend, Data field) =>
Typeable (GBoolExp backend field)
Data, (forall x.
GBoolExp backend field -> Rep (GBoolExp backend field) x)
-> (forall x.
Rep (GBoolExp backend field) x -> GBoolExp backend field)
-> Generic (GBoolExp backend field)
forall x. Rep (GBoolExp backend field) x -> GBoolExp backend field
forall x. GBoolExp backend field -> Rep (GBoolExp backend field) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (backend :: BackendType) field x.
Rep (GBoolExp backend field) x -> GBoolExp backend field
forall (backend :: BackendType) field x.
GBoolExp backend field -> Rep (GBoolExp backend field) x
$cto :: forall (backend :: BackendType) field x.
Rep (GBoolExp backend field) x -> GBoolExp backend field
$cfrom :: forall (backend :: BackendType) field x.
GBoolExp backend field -> Rep (GBoolExp backend field) x
Generic)
instance (Backend b, NFData a) => NFData (GBoolExp b a)
instance (Backend b, Data a) => Plated (GBoolExp b a)
instance (Backend b, Cacheable a) => Cacheable (GBoolExp b a)
instance (Backend b, Hashable a) => Hashable (GBoolExp b a)
instance (Backend b, FromJSONKeyValue a) => FromJSON (GBoolExp b a) where
parseJSON :: Value -> Parser (GBoolExp b a)
parseJSON = String
-> (Object -> Parser (GBoolExp b a))
-> Value
-> Parser (GBoolExp b a)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"boolean expression" \Object
o ->
[GBoolExp b a] -> GBoolExp b a
forall (backend :: BackendType) field.
[GBoolExp backend field] -> GBoolExp backend field
BoolAnd ([GBoolExp b a] -> GBoolExp b a)
-> Parser [GBoolExp b a] -> Parser (GBoolExp b a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Key, Value)]
-> ((Key, Value) -> Parser (GBoolExp b a)) -> Parser [GBoolExp b a]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (Object -> [(Key, Value)]
forall v. KeyMap v -> [(Key, v)]
KM.toList Object
o) \(Key
k, Value
v) ->
if
| Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
"$or" -> [GBoolExp b a] -> GBoolExp b a
forall (backend :: BackendType) field.
[GBoolExp backend field] -> GBoolExp backend field
BoolOr ([GBoolExp b a] -> GBoolExp b a)
-> Parser [GBoolExp b a] -> Parser (GBoolExp b a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [GBoolExp b a]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [GBoolExp b a] -> JSONPathElement -> Parser [GBoolExp b a]
forall a. Parser a -> JSONPathElement -> Parser a
<?> Key -> JSONPathElement
Key Key
k
| Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
"_or" -> [GBoolExp b a] -> GBoolExp b a
forall (backend :: BackendType) field.
[GBoolExp backend field] -> GBoolExp backend field
BoolOr ([GBoolExp b a] -> GBoolExp b a)
-> Parser [GBoolExp b a] -> Parser (GBoolExp b a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [GBoolExp b a]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [GBoolExp b a] -> JSONPathElement -> Parser [GBoolExp b a]
forall a. Parser a -> JSONPathElement -> Parser a
<?> Key -> JSONPathElement
Key Key
k
| Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
"$and" -> [GBoolExp b a] -> GBoolExp b a
forall (backend :: BackendType) field.
[GBoolExp backend field] -> GBoolExp backend field
BoolAnd ([GBoolExp b a] -> GBoolExp b a)
-> Parser [GBoolExp b a] -> Parser (GBoolExp b a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [GBoolExp b a]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [GBoolExp b a] -> JSONPathElement -> Parser [GBoolExp b a]
forall a. Parser a -> JSONPathElement -> Parser a
<?> Key -> JSONPathElement
Key Key
k
| Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
"_and" -> [GBoolExp b a] -> GBoolExp b a
forall (backend :: BackendType) field.
[GBoolExp backend field] -> GBoolExp backend field
BoolAnd ([GBoolExp b a] -> GBoolExp b a)
-> Parser [GBoolExp b a] -> Parser (GBoolExp b a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [GBoolExp b a]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [GBoolExp b a] -> JSONPathElement -> Parser [GBoolExp b a]
forall a. Parser a -> JSONPathElement -> Parser a
<?> Key -> JSONPathElement
Key Key
k
| Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
"$not" -> GBoolExp b a -> GBoolExp b a
forall (backend :: BackendType) field.
GBoolExp backend field -> GBoolExp backend field
BoolNot (GBoolExp b a -> GBoolExp b a)
-> Parser (GBoolExp b a) -> Parser (GBoolExp b a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (GBoolExp b a)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (GBoolExp b a) -> JSONPathElement -> Parser (GBoolExp b a)
forall a. Parser a -> JSONPathElement -> Parser a
<?> Key -> JSONPathElement
Key Key
k
| Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
"_not" -> GBoolExp b a -> GBoolExp b a
forall (backend :: BackendType) field.
GBoolExp backend field -> GBoolExp backend field
BoolNot (GBoolExp b a -> GBoolExp b a)
-> Parser (GBoolExp b a) -> Parser (GBoolExp b a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (GBoolExp b a)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (GBoolExp b a) -> JSONPathElement -> Parser (GBoolExp b a)
forall a. Parser a -> JSONPathElement -> Parser a
<?> Key -> JSONPathElement
Key Key
k
| Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
"$exists" -> GExists b a -> GBoolExp b a
forall (backend :: BackendType) field.
GExists backend field -> GBoolExp backend field
BoolExists (GExists b a -> GBoolExp b a)
-> Parser (GExists b a) -> Parser (GBoolExp b a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (GExists b a)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (GExists b a) -> JSONPathElement -> Parser (GExists b a)
forall a. Parser a -> JSONPathElement -> Parser a
<?> Key -> JSONPathElement
Key Key
k
| Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
"_exists" -> GExists b a -> GBoolExp b a
forall (backend :: BackendType) field.
GExists backend field -> GBoolExp backend field
BoolExists (GExists b a -> GBoolExp b a)
-> Parser (GExists b a) -> Parser (GBoolExp b a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (GExists b a)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (GExists b a) -> JSONPathElement -> Parser (GExists b a)
forall a. Parser a -> JSONPathElement -> Parser a
<?> Key -> JSONPathElement
Key Key
k
| Bool
otherwise -> a -> GBoolExp b a
forall (backend :: BackendType) field.
field -> GBoolExp backend field
BoolField (a -> GBoolExp b a) -> Parser a -> Parser (GBoolExp b a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key, Value) -> Parser a
forall a. FromJSONKeyValue a => (Key, Value) -> Parser a
parseJSONKeyValue (Key
k, Value
v)
instance (Backend backend, ToJSONKeyValue field) => ToJSON (GBoolExp backend field) where
toJSON :: GBoolExp backend field -> Value
toJSON GBoolExp backend field
be = case GBoolExp backend field
be of
BoolAnd [GBoolExp backend field]
bExps ->
let m :: HashMap Key Value
m = [(Key, Value)] -> HashMap Key Value
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
M.fromList ([(Key, Value)] -> HashMap Key Value)
-> [(Key, Value)] -> HashMap Key Value
forall a b. (a -> b) -> a -> b
$ (GBoolExp backend field -> (Key, Value))
-> [GBoolExp backend field] -> [(Key, Value)]
forall a b. (a -> b) -> [a] -> [b]
map GBoolExp backend field -> (Key, Value)
getKV [GBoolExp backend field]
bExps
in
if HashMap Key Value -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length HashMap Key Value
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [GBoolExp backend field] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [GBoolExp backend field]
bExps
then HashMap Key Value -> Value
forall a. ToJSON a => a -> Value
toJSON HashMap Key Value
m
else [(Key, Value)] -> Value
object ([(Key, Value)] -> Value) -> [(Key, Value)] -> Value
forall a b. (a -> b) -> a -> b
$ (Key, Value) -> [(Key, Value)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Key, Value)
kv
GBoolExp backend field
_ -> [(Key, Value)] -> Value
object ([(Key, Value)] -> Value) -> [(Key, Value)] -> Value
forall a b. (a -> b) -> a -> b
$ (Key, Value) -> [(Key, Value)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Key, Value)
kv
where
kv :: (Key, Value)
kv :: (Key, Value)
kv = GBoolExp backend field -> (Key, Value)
getKV GBoolExp backend field
be
getKV :: GBoolExp backend field -> (Key, Value)
getKV :: GBoolExp backend field -> (Key, Value)
getKV = \case
BoolAnd [GBoolExp backend field]
bExps -> Key
"_and" Key -> [Value] -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (GBoolExp backend field -> Value)
-> [GBoolExp backend field] -> [Value]
forall a b. (a -> b) -> [a] -> [b]
map GBoolExp backend field -> Value
forall a. ToJSON a => a -> Value
toJSON [GBoolExp backend field]
bExps
BoolOr [GBoolExp backend field]
bExps -> Key
"_or" Key -> [Value] -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (GBoolExp backend field -> Value)
-> [GBoolExp backend field] -> [Value]
forall a b. (a -> b) -> [a] -> [b]
map GBoolExp backend field -> Value
forall a. ToJSON a => a -> Value
toJSON [GBoolExp backend field]
bExps
BoolNot GBoolExp backend field
bExp -> Key
"_not" Key -> Value -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= GBoolExp backend field -> Value
forall a. ToJSON a => a -> Value
toJSON GBoolExp backend field
bExp
BoolExists GExists backend field
bExists -> Key
"_exists" Key -> Value -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= GExists backend field -> Value
forall a. ToJSON a => a -> Value
toJSON GExists backend field
bExists
BoolField field
a -> field -> (Key, Value)
forall a. ToJSONKeyValue a => a -> (Key, Value)
toJSONKeyValue field
a
gBoolExpTrue :: GBoolExp backend field
gBoolExpTrue :: GBoolExp backend field
gBoolExpTrue = [GBoolExp backend field] -> GBoolExp backend field
forall (backend :: BackendType) field.
[GBoolExp backend field] -> GBoolExp backend field
BoolAnd []
data GExists (backend :: BackendType) field = GExists
{ GExists backend field -> TableName backend
_geTable :: TableName backend,
GExists backend field -> GBoolExp backend field
_geWhere :: GBoolExp backend field
}
deriving (a -> GExists backend b -> GExists backend a
(a -> b) -> GExists backend a -> GExists backend b
(forall a b. (a -> b) -> GExists backend a -> GExists backend b)
-> (forall a b. a -> GExists backend b -> GExists backend a)
-> Functor (GExists backend)
forall a b. a -> GExists backend b -> GExists backend a
forall a b. (a -> b) -> GExists backend a -> GExists backend b
forall (backend :: BackendType) a b.
a -> GExists backend b -> GExists backend a
forall (backend :: BackendType) a b.
(a -> b) -> GExists backend a -> GExists backend b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> GExists backend b -> GExists backend a
$c<$ :: forall (backend :: BackendType) a b.
a -> GExists backend b -> GExists backend a
fmap :: (a -> b) -> GExists backend a -> GExists backend b
$cfmap :: forall (backend :: BackendType) a b.
(a -> b) -> GExists backend a -> GExists backend b
Functor, GExists backend a -> Bool
(a -> m) -> GExists backend a -> m
(a -> b -> b) -> b -> GExists backend a -> b
(forall m. Monoid m => GExists backend m -> m)
-> (forall m a. Monoid m => (a -> m) -> GExists backend a -> m)
-> (forall m a. Monoid m => (a -> m) -> GExists backend a -> m)
-> (forall a b. (a -> b -> b) -> b -> GExists backend a -> b)
-> (forall a b. (a -> b -> b) -> b -> GExists backend a -> b)
-> (forall b a. (b -> a -> b) -> b -> GExists backend a -> b)
-> (forall b a. (b -> a -> b) -> b -> GExists backend a -> b)
-> (forall a. (a -> a -> a) -> GExists backend a -> a)
-> (forall a. (a -> a -> a) -> GExists backend a -> a)
-> (forall a. GExists backend a -> [a])
-> (forall a. GExists backend a -> Bool)
-> (forall a. GExists backend a -> Int)
-> (forall a. Eq a => a -> GExists backend a -> Bool)
-> (forall a. Ord a => GExists backend a -> a)
-> (forall a. Ord a => GExists backend a -> a)
-> (forall a. Num a => GExists backend a -> a)
-> (forall a. Num a => GExists backend a -> a)
-> Foldable (GExists backend)
forall a. Eq a => a -> GExists backend a -> Bool
forall a. Num a => GExists backend a -> a
forall a. Ord a => GExists backend a -> a
forall m. Monoid m => GExists backend m -> m
forall a. GExists backend a -> Bool
forall a. GExists backend a -> Int
forall a. GExists backend a -> [a]
forall a. (a -> a -> a) -> GExists backend a -> a
forall m a. Monoid m => (a -> m) -> GExists backend a -> m
forall b a. (b -> a -> b) -> b -> GExists backend a -> b
forall a b. (a -> b -> b) -> b -> GExists backend a -> b
forall (backend :: BackendType) a.
Eq a =>
a -> GExists backend a -> Bool
forall (backend :: BackendType) a. Num a => GExists backend a -> a
forall (backend :: BackendType) a. Ord a => GExists backend a -> a
forall (backend :: BackendType) m.
Monoid m =>
GExists backend m -> m
forall (backend :: BackendType) a. GExists backend a -> Bool
forall (backend :: BackendType) a. GExists backend a -> Int
forall (backend :: BackendType) a. GExists backend a -> [a]
forall (backend :: BackendType) a.
(a -> a -> a) -> GExists backend a -> a
forall (backend :: BackendType) m a.
Monoid m =>
(a -> m) -> GExists backend a -> m
forall (backend :: BackendType) b a.
(b -> a -> b) -> b -> GExists backend a -> b
forall (backend :: BackendType) a b.
(a -> b -> b) -> b -> GExists backend a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: GExists backend a -> a
$cproduct :: forall (backend :: BackendType) a. Num a => GExists backend a -> a
sum :: GExists backend a -> a
$csum :: forall (backend :: BackendType) a. Num a => GExists backend a -> a
minimum :: GExists backend a -> a
$cminimum :: forall (backend :: BackendType) a. Ord a => GExists backend a -> a
maximum :: GExists backend a -> a
$cmaximum :: forall (backend :: BackendType) a. Ord a => GExists backend a -> a
elem :: a -> GExists backend a -> Bool
$celem :: forall (backend :: BackendType) a.
Eq a =>
a -> GExists backend a -> Bool
length :: GExists backend a -> Int
$clength :: forall (backend :: BackendType) a. GExists backend a -> Int
null :: GExists backend a -> Bool
$cnull :: forall (backend :: BackendType) a. GExists backend a -> Bool
toList :: GExists backend a -> [a]
$ctoList :: forall (backend :: BackendType) a. GExists backend a -> [a]
foldl1 :: (a -> a -> a) -> GExists backend a -> a
$cfoldl1 :: forall (backend :: BackendType) a.
(a -> a -> a) -> GExists backend a -> a
foldr1 :: (a -> a -> a) -> GExists backend a -> a
$cfoldr1 :: forall (backend :: BackendType) a.
(a -> a -> a) -> GExists backend a -> a
foldl' :: (b -> a -> b) -> b -> GExists backend a -> b
$cfoldl' :: forall (backend :: BackendType) b a.
(b -> a -> b) -> b -> GExists backend a -> b
foldl :: (b -> a -> b) -> b -> GExists backend a -> b
$cfoldl :: forall (backend :: BackendType) b a.
(b -> a -> b) -> b -> GExists backend a -> b
foldr' :: (a -> b -> b) -> b -> GExists backend a -> b
$cfoldr' :: forall (backend :: BackendType) a b.
(a -> b -> b) -> b -> GExists backend a -> b
foldr :: (a -> b -> b) -> b -> GExists backend a -> b
$cfoldr :: forall (backend :: BackendType) a b.
(a -> b -> b) -> b -> GExists backend a -> b
foldMap' :: (a -> m) -> GExists backend a -> m
$cfoldMap' :: forall (backend :: BackendType) m a.
Monoid m =>
(a -> m) -> GExists backend a -> m
foldMap :: (a -> m) -> GExists backend a -> m
$cfoldMap :: forall (backend :: BackendType) m a.
Monoid m =>
(a -> m) -> GExists backend a -> m
fold :: GExists backend m -> m
$cfold :: forall (backend :: BackendType) m.
Monoid m =>
GExists backend m -> m
Foldable, Functor (GExists backend)
Foldable (GExists backend)
Functor (GExists backend)
-> Foldable (GExists backend)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GExists backend a -> f (GExists backend b))
-> (forall (f :: * -> *) a.
Applicative f =>
GExists backend (f a) -> f (GExists backend a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GExists backend a -> m (GExists backend b))
-> (forall (m :: * -> *) a.
Monad m =>
GExists backend (m a) -> m (GExists backend a))
-> Traversable (GExists backend)
(a -> f b) -> GExists backend a -> f (GExists backend b)
forall (backend :: BackendType). Functor (GExists backend)
forall (backend :: BackendType). Foldable (GExists backend)
forall (backend :: BackendType) (m :: * -> *) a.
Monad m =>
GExists backend (m a) -> m (GExists backend a)
forall (backend :: BackendType) (f :: * -> *) a.
Applicative f =>
GExists backend (f a) -> f (GExists backend a)
forall (backend :: BackendType) (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GExists backend a -> m (GExists backend b)
forall (backend :: BackendType) (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GExists backend a -> f (GExists backend b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
GExists backend (m a) -> m (GExists backend a)
forall (f :: * -> *) a.
Applicative f =>
GExists backend (f a) -> f (GExists backend a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GExists backend a -> m (GExists backend b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GExists backend a -> f (GExists backend b)
sequence :: GExists backend (m a) -> m (GExists backend a)
$csequence :: forall (backend :: BackendType) (m :: * -> *) a.
Monad m =>
GExists backend (m a) -> m (GExists backend a)
mapM :: (a -> m b) -> GExists backend a -> m (GExists backend b)
$cmapM :: forall (backend :: BackendType) (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GExists backend a -> m (GExists backend b)
sequenceA :: GExists backend (f a) -> f (GExists backend a)
$csequenceA :: forall (backend :: BackendType) (f :: * -> *) a.
Applicative f =>
GExists backend (f a) -> f (GExists backend a)
traverse :: (a -> f b) -> GExists backend a -> f (GExists backend b)
$ctraverse :: forall (backend :: BackendType) (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GExists backend a -> f (GExists backend b)
$cp2Traversable :: forall (backend :: BackendType). Foldable (GExists backend)
$cp1Traversable :: forall (backend :: BackendType). Functor (GExists backend)
Traversable, (forall x. GExists backend field -> Rep (GExists backend field) x)
-> (forall x.
Rep (GExists backend field) x -> GExists backend field)
-> Generic (GExists backend field)
forall x. Rep (GExists backend field) x -> GExists backend field
forall x. GExists backend field -> Rep (GExists backend field) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (backend :: BackendType) field x.
Rep (GExists backend field) x -> GExists backend field
forall (backend :: BackendType) field x.
GExists backend field -> Rep (GExists backend field) x
$cto :: forall (backend :: BackendType) field x.
Rep (GExists backend field) x -> GExists backend field
$cfrom :: forall (backend :: BackendType) field x.
GExists backend field -> Rep (GExists backend field) x
Generic)
deriving instance (Backend b, Show a) => Show (GExists b a)
deriving instance (Backend b, Eq a) => Eq (GExists b a)
deriving instance (Backend b, Data a) => Data (GExists b a)
instance (Backend b, NFData a) => NFData (GExists b a)
instance (Backend b, Data a) => Plated (GExists b a)
instance (Backend b, Cacheable a) => Cacheable (GExists b a)
instance (Backend b, Hashable a) => Hashable (GExists b a)
instance (Backend b, FromJSONKeyValue a) => FromJSON (GExists b a) where
parseJSON :: Value -> Parser (GExists b a)
parseJSON = String
-> (Object -> Parser (GExists b a))
-> Value
-> Parser (GExists b a)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"_exists" \Object
o -> do
TableName b
qt <- Object
o Object -> Key -> Parser (TableName b)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"_table"
GBoolExp b a
wh <- Object
o Object -> Key -> Parser (GBoolExp b a)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"_where"
GExists b a -> Parser (GExists b a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GExists b a -> Parser (GExists b a))
-> GExists b a -> Parser (GExists b a)
forall a b. (a -> b) -> a -> b
$ TableName b -> GBoolExp b a -> GExists b a
forall (backend :: BackendType) field.
TableName backend
-> GBoolExp backend field -> GExists backend field
GExists TableName b
qt GBoolExp b a
wh
instance (Backend b, ToJSONKeyValue a) => ToJSON (GExists b a) where
toJSON :: GExists b a -> Value
toJSON (GExists TableName b
gTable GBoolExp b a
gWhere) =
[(Key, Value)] -> Value
object
[ Key
"_table" Key -> TableName b -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TableName b
gTable,
Key
"_where" Key -> GBoolExp b a -> (Key, Value)
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= GBoolExp b a
gWhere
]
makeLenses ''GExists
data ColExp = ColExp
{ ColExp -> FieldName
ceCol :: FieldName,
ColExp -> Value
ceVal :: Value
}
deriving (Int -> ColExp -> ShowS
[ColExp] -> ShowS
ColExp -> String
(Int -> ColExp -> ShowS)
-> (ColExp -> String) -> ([ColExp] -> ShowS) -> Show ColExp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColExp] -> ShowS
$cshowList :: [ColExp] -> ShowS
show :: ColExp -> String
$cshow :: ColExp -> String
showsPrec :: Int -> ColExp -> ShowS
$cshowsPrec :: Int -> ColExp -> ShowS
Show, ColExp -> ColExp -> Bool
(ColExp -> ColExp -> Bool)
-> (ColExp -> ColExp -> Bool) -> Eq ColExp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColExp -> ColExp -> Bool
$c/= :: ColExp -> ColExp -> Bool
== :: ColExp -> ColExp -> Bool
$c== :: ColExp -> ColExp -> Bool
Eq, Typeable ColExp
DataType
Constr
Typeable ColExp
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColExp -> c ColExp)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColExp)
-> (ColExp -> Constr)
-> (ColExp -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColExp))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColExp))
-> ((forall b. Data b => b -> b) -> ColExp -> ColExp)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColExp -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColExp -> r)
-> (forall u. (forall d. Data d => d -> u) -> ColExp -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> ColExp -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColExp -> m ColExp)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColExp -> m ColExp)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColExp -> m ColExp)
-> Data ColExp
ColExp -> DataType
ColExp -> Constr
(forall b. Data b => b -> b) -> ColExp -> ColExp
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColExp -> c ColExp
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColExp
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ColExp -> u
forall u. (forall d. Data d => d -> u) -> ColExp -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColExp -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColExp -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColExp -> m ColExp
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColExp -> m ColExp
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColExp
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColExp -> c ColExp
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColExp)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColExp)
$cColExp :: Constr
$tColExp :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ColExp -> m ColExp
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColExp -> m ColExp
gmapMp :: (forall d. Data d => d -> m d) -> ColExp -> m ColExp
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColExp -> m ColExp
gmapM :: (forall d. Data d => d -> m d) -> ColExp -> m ColExp
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColExp -> m ColExp
gmapQi :: Int -> (forall d. Data d => d -> u) -> ColExp -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ColExp -> u
gmapQ :: (forall d. Data d => d -> u) -> ColExp -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ColExp -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColExp -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColExp -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColExp -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColExp -> r
gmapT :: (forall b. Data b => b -> b) -> ColExp -> ColExp
$cgmapT :: (forall b. Data b => b -> b) -> ColExp -> ColExp
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColExp)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColExp)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ColExp)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColExp)
dataTypeOf :: ColExp -> DataType
$cdataTypeOf :: ColExp -> DataType
toConstr :: ColExp -> Constr
$ctoConstr :: ColExp -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColExp
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColExp
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColExp -> c ColExp
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColExp -> c ColExp
$cp1Data :: Typeable ColExp
Data, (forall x. ColExp -> Rep ColExp x)
-> (forall x. Rep ColExp x -> ColExp) -> Generic ColExp
forall x. Rep ColExp x -> ColExp
forall x. ColExp -> Rep ColExp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ColExp x -> ColExp
$cfrom :: forall x. ColExp -> Rep ColExp x
Generic)
instance NFData ColExp
instance Cacheable ColExp
instance FromJSONKeyValue ColExp where
parseJSONKeyValue :: (Key, Value) -> Parser ColExp
parseJSONKeyValue (Key
k, Value
v) = FieldName -> Value -> ColExp
ColExp (Text -> FieldName
FieldName (Key -> Text
K.toText Key
k)) (Value -> ColExp) -> Parser Value -> Parser ColExp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Value
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
instance ToJSONKeyValue ColExp where
toJSONKeyValue :: ColExp -> (Key, Value)
toJSONKeyValue (ColExp FieldName
k Value
v) = (Text -> Key
K.fromText (FieldName -> Text
getFieldNameTxt FieldName
k), Value
v)
newtype BoolExp (b :: BackendType) = BoolExp {BoolExp b -> GBoolExp b ColExp
unBoolExp :: GBoolExp b ColExp}
deriving newtype (Int -> BoolExp b -> ShowS
[BoolExp b] -> ShowS
BoolExp b -> String
(Int -> BoolExp b -> ShowS)
-> (BoolExp b -> String)
-> ([BoolExp b] -> ShowS)
-> Show (BoolExp b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (b :: BackendType). Backend b => Int -> BoolExp b -> ShowS
forall (b :: BackendType). Backend b => [BoolExp b] -> ShowS
forall (b :: BackendType). Backend b => BoolExp b -> String
showList :: [BoolExp b] -> ShowS
$cshowList :: forall (b :: BackendType). Backend b => [BoolExp b] -> ShowS
show :: BoolExp b -> String
$cshow :: forall (b :: BackendType). Backend b => BoolExp b -> String
showsPrec :: Int -> BoolExp b -> ShowS
$cshowsPrec :: forall (b :: BackendType). Backend b => Int -> BoolExp b -> ShowS
Show, BoolExp b -> BoolExp b -> Bool
(BoolExp b -> BoolExp b -> Bool)
-> (BoolExp b -> BoolExp b -> Bool) -> Eq (BoolExp b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (b :: BackendType).
Backend b =>
BoolExp b -> BoolExp b -> Bool
/= :: BoolExp b -> BoolExp b -> Bool
$c/= :: forall (b :: BackendType).
Backend b =>
BoolExp b -> BoolExp b -> Bool
== :: BoolExp b -> BoolExp b -> Bool
$c== :: forall (b :: BackendType).
Backend b =>
BoolExp b -> BoolExp b -> Bool
Eq, Rep (BoolExp b) x -> BoolExp b
BoolExp b -> Rep (BoolExp b) x
(forall x. BoolExp b -> Rep (BoolExp b) x)
-> (forall x. Rep (BoolExp b) x -> BoolExp b)
-> Generic (BoolExp b)
forall x. Rep (BoolExp b) x -> BoolExp b
forall x. BoolExp b -> Rep (BoolExp b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x. Rep (BoolExp b) x -> BoolExp b
forall (b :: BackendType) x. BoolExp b -> Rep (BoolExp b) x
to :: Rep (BoolExp b) x -> BoolExp b
$cto :: forall (b :: BackendType) x. Rep (BoolExp b) x -> BoolExp b
from :: BoolExp b -> Rep (BoolExp b) x
$cfrom :: forall (b :: BackendType) x. BoolExp b -> Rep (BoolExp b) x
Generic, BoolExp b -> ()
(BoolExp b -> ()) -> NFData (BoolExp b)
forall a. (a -> ()) -> NFData a
forall (b :: BackendType). Backend b => BoolExp b -> ()
rnf :: BoolExp b -> ()
$crnf :: forall (b :: BackendType). Backend b => BoolExp b -> ()
NFData, Eq (BoolExp b)
Eq (BoolExp b)
-> (Accesses -> BoolExp b -> BoolExp b -> Bool)
-> Cacheable (BoolExp b)
Accesses -> BoolExp b -> BoolExp b -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
forall (b :: BackendType). Backend b => Eq (BoolExp b)
forall (b :: BackendType).
Backend b =>
Accesses -> BoolExp b -> BoolExp b -> Bool
unchanged :: Accesses -> BoolExp b -> BoolExp b -> Bool
$cunchanged :: forall (b :: BackendType).
Backend b =>
Accesses -> BoolExp b -> BoolExp b -> Bool
$cp1Cacheable :: forall (b :: BackendType). Backend b => Eq (BoolExp b)
Cacheable, [BoolExp b] -> Value
[BoolExp b] -> Encoding
BoolExp b -> Value
BoolExp b -> Encoding
(BoolExp b -> Value)
-> (BoolExp b -> Encoding)
-> ([BoolExp b] -> Value)
-> ([BoolExp b] -> Encoding)
-> ToJSON (BoolExp b)
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
forall (b :: BackendType). Backend b => [BoolExp b] -> Value
forall (b :: BackendType). Backend b => [BoolExp b] -> Encoding
forall (b :: BackendType). Backend b => BoolExp b -> Value
forall (b :: BackendType). Backend b => BoolExp b -> Encoding
toEncodingList :: [BoolExp b] -> Encoding
$ctoEncodingList :: forall (b :: BackendType). Backend b => [BoolExp b] -> Encoding
toJSONList :: [BoolExp b] -> Value
$ctoJSONList :: forall (b :: BackendType). Backend b => [BoolExp b] -> Value
toEncoding :: BoolExp b -> Encoding
$ctoEncoding :: forall (b :: BackendType). Backend b => BoolExp b -> Encoding
toJSON :: BoolExp b -> Value
$ctoJSON :: forall (b :: BackendType). Backend b => BoolExp b -> Value
ToJSON, Value -> Parser [BoolExp b]
Value -> Parser (BoolExp b)
(Value -> Parser (BoolExp b))
-> (Value -> Parser [BoolExp b]) -> FromJSON (BoolExp b)
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
forall (b :: BackendType). Backend b => Value -> Parser [BoolExp b]
forall (b :: BackendType). Backend b => Value -> Parser (BoolExp b)
parseJSONList :: Value -> Parser [BoolExp b]
$cparseJSONList :: forall (b :: BackendType). Backend b => Value -> Parser [BoolExp b]
parseJSON :: Value -> Parser (BoolExp b)
$cparseJSON :: forall (b :: BackendType). Backend b => Value -> Parser (BoolExp b)
FromJSON)
$(makeWrapped ''BoolExp)
makePrisms ''GBoolExp
data PartialSQLExp (backend :: BackendType)
= PSESessVar (SessionVarType backend) SessionVariable
| PSESession
| PSESQLExp (SQLExpression backend)
deriving ((forall x. PartialSQLExp backend -> Rep (PartialSQLExp backend) x)
-> (forall x.
Rep (PartialSQLExp backend) x -> PartialSQLExp backend)
-> Generic (PartialSQLExp backend)
forall x. Rep (PartialSQLExp backend) x -> PartialSQLExp backend
forall x. PartialSQLExp backend -> Rep (PartialSQLExp backend) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (backend :: BackendType) x.
Rep (PartialSQLExp backend) x -> PartialSQLExp backend
forall (backend :: BackendType) x.
PartialSQLExp backend -> Rep (PartialSQLExp backend) x
$cto :: forall (backend :: BackendType) x.
Rep (PartialSQLExp backend) x -> PartialSQLExp backend
$cfrom :: forall (backend :: BackendType) x.
PartialSQLExp backend -> Rep (PartialSQLExp backend) x
Generic)
deriving instance (Backend b) => Eq (PartialSQLExp b)
deriving instance (Backend b) => Show (PartialSQLExp b)
instance
( Backend b,
NFData (SQLExpression b)
) =>
NFData (PartialSQLExp b)
instance
( Backend b,
Hashable (SQLExpression b)
) =>
Hashable (PartialSQLExp b)
instance
( Backend b,
Cacheable (SQLExpression b)
) =>
Cacheable (PartialSQLExp b)
instance Backend b => ToJSON (PartialSQLExp b) where
toJSON :: PartialSQLExp b -> Value
toJSON = \case
PSESessVar SessionVarType b
colTy SessionVariable
sessVar -> (SessionVarType b, SessionVariable) -> Value
forall a. ToJSON a => a -> Value
toJSON (SessionVarType b
colTy, SessionVariable
sessVar)
PartialSQLExp b
PSESession -> Text -> Value
String Text
"hasura_session"
PSESQLExp SQLExpression b
e -> SQLExpression b -> Value
forall a. ToJSON a => a -> Value
toJSON SQLExpression b
e
isStaticValue :: PartialSQLExp backend -> Bool
isStaticValue :: PartialSQLExp backend -> Bool
isStaticValue = \case
PSESessVar SessionVarType backend
_ SessionVariable
_ -> Bool
False
PartialSQLExp backend
PSESession -> Bool
False
PSESQLExp SQLExpression backend
_ -> Bool
True
hasStaticExp :: Backend b => OpExpG b (PartialSQLExp b) -> Bool
hasStaticExp :: OpExpG b (PartialSQLExp b) -> Bool
hasStaticExp = Any -> Bool
getAny (Any -> Bool)
-> (OpExpG b (PartialSQLExp b) -> Any)
-> OpExpG b (PartialSQLExp b)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PartialSQLExp b -> Any) -> OpExpG b (PartialSQLExp b) -> Any
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Bool -> Any
Any (Bool -> Any)
-> (PartialSQLExp b -> Bool) -> PartialSQLExp b -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PartialSQLExp b -> Bool
forall (backend :: BackendType). PartialSQLExp backend -> Bool
isStaticValue)
type CastExp backend field = M.HashMap (ScalarType backend) [OpExpG backend field]
data OpExpG (backend :: BackendType) field
= 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)
deriving ((forall x. OpExpG backend field -> Rep (OpExpG backend field) x)
-> (forall x. Rep (OpExpG backend field) x -> OpExpG backend field)
-> Generic (OpExpG backend field)
forall x. Rep (OpExpG backend field) x -> OpExpG backend field
forall x. OpExpG backend field -> Rep (OpExpG backend field) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (backend :: BackendType) field x.
Rep (OpExpG backend field) x -> OpExpG backend field
forall (backend :: BackendType) field x.
OpExpG backend field -> Rep (OpExpG backend field) x
$cto :: forall (backend :: BackendType) field x.
Rep (OpExpG backend field) x -> OpExpG backend field
$cfrom :: forall (backend :: BackendType) field x.
OpExpG backend field -> Rep (OpExpG backend field) x
Generic)
data RootOrCurrentColumn b = RootOrCurrentColumn RootOrCurrent (Column b)
deriving ((forall x. RootOrCurrentColumn b -> Rep (RootOrCurrentColumn b) x)
-> (forall x.
Rep (RootOrCurrentColumn b) x -> RootOrCurrentColumn b)
-> Generic (RootOrCurrentColumn b)
forall x. Rep (RootOrCurrentColumn b) x -> RootOrCurrentColumn b
forall x. RootOrCurrentColumn b -> Rep (RootOrCurrentColumn b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x.
Rep (RootOrCurrentColumn b) x -> RootOrCurrentColumn b
forall (b :: BackendType) x.
RootOrCurrentColumn b -> Rep (RootOrCurrentColumn b) x
$cto :: forall (b :: BackendType) x.
Rep (RootOrCurrentColumn b) x -> RootOrCurrentColumn b
$cfrom :: forall (b :: BackendType) x.
RootOrCurrentColumn b -> Rep (RootOrCurrentColumn b) x
Generic)
deriving instance Backend b => Show (RootOrCurrentColumn b)
deriving instance Backend b => Eq (RootOrCurrentColumn b)
instance Backend b => NFData (RootOrCurrentColumn b)
instance Backend b => Cacheable (RootOrCurrentColumn b)
instance Backend b => Hashable (RootOrCurrentColumn b)
instance Backend b => ToJSON (RootOrCurrentColumn b)
data RootOrCurrent = IsRoot | IsCurrent
deriving (RootOrCurrent -> RootOrCurrent -> Bool
(RootOrCurrent -> RootOrCurrent -> Bool)
-> (RootOrCurrent -> RootOrCurrent -> Bool) -> Eq RootOrCurrent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RootOrCurrent -> RootOrCurrent -> Bool
$c/= :: RootOrCurrent -> RootOrCurrent -> Bool
== :: RootOrCurrent -> RootOrCurrent -> Bool
$c== :: RootOrCurrent -> RootOrCurrent -> Bool
Eq, Int -> RootOrCurrent -> ShowS
[RootOrCurrent] -> ShowS
RootOrCurrent -> String
(Int -> RootOrCurrent -> ShowS)
-> (RootOrCurrent -> String)
-> ([RootOrCurrent] -> ShowS)
-> Show RootOrCurrent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RootOrCurrent] -> ShowS
$cshowList :: [RootOrCurrent] -> ShowS
show :: RootOrCurrent -> String
$cshow :: RootOrCurrent -> String
showsPrec :: Int -> RootOrCurrent -> ShowS
$cshowsPrec :: Int -> RootOrCurrent -> ShowS
Show, (forall x. RootOrCurrent -> Rep RootOrCurrent x)
-> (forall x. Rep RootOrCurrent x -> RootOrCurrent)
-> Generic RootOrCurrent
forall x. Rep RootOrCurrent x -> RootOrCurrent
forall x. RootOrCurrent -> Rep RootOrCurrent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RootOrCurrent x -> RootOrCurrent
$cfrom :: forall x. RootOrCurrent -> Rep RootOrCurrent x
Generic)
instance NFData RootOrCurrent
instance Cacheable RootOrCurrent
instance Hashable RootOrCurrent
instance ToJSON RootOrCurrent
deriving instance (Backend b) => Functor (OpExpG b)
deriving instance (Backend b) => Foldable (OpExpG b)
deriving instance (Backend b) => Traversable (OpExpG b)
deriving instance
( Backend b,
Show (BooleanOperators b a),
Show a
) =>
Show (OpExpG b a)
deriving instance
( Backend b,
Eq (BooleanOperators b a),
Eq a
) =>
Eq (OpExpG b a)
instance
( Backend b,
NFData (BooleanOperators b a),
NFData a
) =>
NFData (OpExpG b a)
instance
( Backend b,
Cacheable (BooleanOperators b a),
Cacheable a
) =>
Cacheable (OpExpG b a)
instance
( Backend b,
Hashable (BooleanOperators b a),
Hashable a
) =>
Hashable (OpExpG b a)
instance
( Backend b,
ToJSONKeyValue (BooleanOperators b a),
ToJSON a
) =>
ToJSONKeyValue (OpExpG b a)
where
toJSONKeyValue :: OpExpG b a -> (Key, Value)
toJSONKeyValue = \case
ACast CastExp b a
a -> (Key
"_cast", HashMap (ScalarType b) Value -> Value
forall a. ToJSON a => a -> Value
toJSON (HashMap (ScalarType b) Value -> Value)
-> HashMap (ScalarType b) Value -> Value
forall a b. (a -> b) -> a -> b
$ [(Key, Value)] -> Value
object ([(Key, Value)] -> Value)
-> ([OpExpG b a] -> [(Key, Value)]) -> [OpExpG b a] -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (OpExpG b a -> (Key, Value)) -> [OpExpG b a] -> [(Key, Value)]
forall a b. (a -> b) -> [a] -> [b]
map OpExpG b a -> (Key, Value)
forall a. ToJSONKeyValue a => a -> (Key, Value)
toJSONKeyValue ([OpExpG b a] -> Value)
-> CastExp b a -> HashMap (ScalarType b) Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CastExp b a
a)
AEQ Bool
_ a
a -> (Key
"_eq", a -> Value
forall a. ToJSON a => a -> Value
toJSON a
a)
ANE Bool
_ a
a -> (Key
"_ne", a -> Value
forall a. ToJSON a => a -> Value
toJSON a
a)
AIN a
a -> (Key
"_in", a -> Value
forall a. ToJSON a => a -> Value
toJSON a
a)
ANIN a
a -> (Key
"_nin", a -> Value
forall a. ToJSON a => a -> Value
toJSON a
a)
AGT a
a -> (Key
"_gt", a -> Value
forall a. ToJSON a => a -> Value
toJSON a
a)
ALT a
a -> (Key
"_lt", a -> Value
forall a. ToJSON a => a -> Value
toJSON a
a)
AGTE a
a -> (Key
"_gte", a -> Value
forall a. ToJSON a => a -> Value
toJSON a
a)
ALTE a
a -> (Key
"_lte", a -> Value
forall a. ToJSON a => a -> Value
toJSON a
a)
ALIKE a
a -> (Key
"_like", a -> Value
forall a. ToJSON a => a -> Value
toJSON a
a)
ANLIKE a
a -> (Key
"_nlike", a -> Value
forall a. ToJSON a => a -> Value
toJSON a
a)
CEQ RootOrCurrentColumn b
a -> (Key
"_ceq", RootOrCurrentColumn b -> Value
forall a. ToJSON a => a -> Value
toJSON RootOrCurrentColumn b
a)
CNE RootOrCurrentColumn b
a -> (Key
"_cne", RootOrCurrentColumn b -> Value
forall a. ToJSON a => a -> Value
toJSON RootOrCurrentColumn b
a)
CGT RootOrCurrentColumn b
a -> (Key
"_cgt", RootOrCurrentColumn b -> Value
forall a. ToJSON a => a -> Value
toJSON RootOrCurrentColumn b
a)
CLT RootOrCurrentColumn b
a -> (Key
"_clt", RootOrCurrentColumn b -> Value
forall a. ToJSON a => a -> Value
toJSON RootOrCurrentColumn b
a)
CGTE RootOrCurrentColumn b
a -> (Key
"_cgte", RootOrCurrentColumn b -> Value
forall a. ToJSON a => a -> Value
toJSON RootOrCurrentColumn b
a)
CLTE RootOrCurrentColumn b
a -> (Key
"_clte", RootOrCurrentColumn b -> Value
forall a. ToJSON a => a -> Value
toJSON RootOrCurrentColumn b
a)
OpExpG b a
ANISNULL -> (Key
"_is_null", Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
True)
OpExpG b a
ANISNOTNULL -> (Key
"_is_null", Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
False)
ABackendSpecific BooleanOperators b a
b -> BooleanOperators b a -> (Key, Value)
forall a. ToJSONKeyValue a => a -> (Key, Value)
toJSONKeyValue BooleanOperators b a
b
opExpDepCol :: OpExpG backend field -> Maybe (RootOrCurrentColumn backend)
opExpDepCol :: OpExpG backend field -> Maybe (RootOrCurrentColumn backend)
opExpDepCol = \case
CEQ RootOrCurrentColumn backend
c -> RootOrCurrentColumn backend -> Maybe (RootOrCurrentColumn backend)
forall a. a -> Maybe a
Just RootOrCurrentColumn backend
c
CNE RootOrCurrentColumn backend
c -> RootOrCurrentColumn backend -> Maybe (RootOrCurrentColumn backend)
forall a. a -> Maybe a
Just RootOrCurrentColumn backend
c
CGT RootOrCurrentColumn backend
c -> RootOrCurrentColumn backend -> Maybe (RootOrCurrentColumn backend)
forall a. a -> Maybe a
Just RootOrCurrentColumn backend
c
CLT RootOrCurrentColumn backend
c -> RootOrCurrentColumn backend -> Maybe (RootOrCurrentColumn backend)
forall a. a -> Maybe a
Just RootOrCurrentColumn backend
c
CGTE RootOrCurrentColumn backend
c -> RootOrCurrentColumn backend -> Maybe (RootOrCurrentColumn backend)
forall a. a -> Maybe a
Just RootOrCurrentColumn backend
c
CLTE RootOrCurrentColumn backend
c -> RootOrCurrentColumn backend -> Maybe (RootOrCurrentColumn backend)
forall a. a -> Maybe a
Just RootOrCurrentColumn backend
c
OpExpG backend field
_ -> Maybe (RootOrCurrentColumn backend)
forall a. Maybe a
Nothing
data ComputedFieldBoolExp (backend :: BackendType) scalar
=
CFBEScalar [OpExpG backend scalar]
|
CFBETable (TableName backend) (AnnBoolExp backend scalar)
deriving (a
-> ComputedFieldBoolExp backend b -> ComputedFieldBoolExp backend a
(a -> b)
-> ComputedFieldBoolExp backend a -> ComputedFieldBoolExp backend b
(forall a b.
(a -> b)
-> ComputedFieldBoolExp backend a
-> ComputedFieldBoolExp backend b)
-> (forall a b.
a
-> ComputedFieldBoolExp backend b
-> ComputedFieldBoolExp backend a)
-> Functor (ComputedFieldBoolExp backend)
forall a b.
a
-> ComputedFieldBoolExp backend b -> ComputedFieldBoolExp backend a
forall a b.
(a -> b)
-> ComputedFieldBoolExp backend a -> ComputedFieldBoolExp backend b
forall (backend :: BackendType) a b.
Backend backend =>
a
-> ComputedFieldBoolExp backend b -> ComputedFieldBoolExp backend a
forall (backend :: BackendType) a b.
Backend backend =>
(a -> b)
-> ComputedFieldBoolExp backend a -> ComputedFieldBoolExp backend b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a
-> ComputedFieldBoolExp backend b -> ComputedFieldBoolExp backend a
$c<$ :: forall (backend :: BackendType) a b.
Backend backend =>
a
-> ComputedFieldBoolExp backend b -> ComputedFieldBoolExp backend a
fmap :: (a -> b)
-> ComputedFieldBoolExp backend a -> ComputedFieldBoolExp backend b
$cfmap :: forall (backend :: BackendType) a b.
Backend backend =>
(a -> b)
-> ComputedFieldBoolExp backend a -> ComputedFieldBoolExp backend b
Functor, ComputedFieldBoolExp backend a -> Bool
(a -> m) -> ComputedFieldBoolExp backend a -> m
(a -> b -> b) -> b -> ComputedFieldBoolExp backend a -> b
(forall m. Monoid m => ComputedFieldBoolExp backend m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> ComputedFieldBoolExp backend a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> ComputedFieldBoolExp backend a -> m)
-> (forall a b.
(a -> b -> b) -> b -> ComputedFieldBoolExp backend a -> b)
-> (forall a b.
(a -> b -> b) -> b -> ComputedFieldBoolExp backend a -> b)
-> (forall b a.
(b -> a -> b) -> b -> ComputedFieldBoolExp backend a -> b)
-> (forall b a.
(b -> a -> b) -> b -> ComputedFieldBoolExp backend a -> b)
-> (forall a. (a -> a -> a) -> ComputedFieldBoolExp backend a -> a)
-> (forall a. (a -> a -> a) -> ComputedFieldBoolExp backend a -> a)
-> (forall a. ComputedFieldBoolExp backend a -> [a])
-> (forall a. ComputedFieldBoolExp backend a -> Bool)
-> (forall a. ComputedFieldBoolExp backend a -> Int)
-> (forall a. Eq a => a -> ComputedFieldBoolExp backend a -> Bool)
-> (forall a. Ord a => ComputedFieldBoolExp backend a -> a)
-> (forall a. Ord a => ComputedFieldBoolExp backend a -> a)
-> (forall a. Num a => ComputedFieldBoolExp backend a -> a)
-> (forall a. Num a => ComputedFieldBoolExp backend a -> a)
-> Foldable (ComputedFieldBoolExp backend)
forall a. Eq a => a -> ComputedFieldBoolExp backend a -> Bool
forall a. Num a => ComputedFieldBoolExp backend a -> a
forall a. Ord a => ComputedFieldBoolExp backend a -> a
forall m. Monoid m => ComputedFieldBoolExp backend m -> m
forall a. ComputedFieldBoolExp backend a -> Bool
forall a. ComputedFieldBoolExp backend a -> Int
forall a. ComputedFieldBoolExp backend a -> [a]
forall a. (a -> a -> a) -> ComputedFieldBoolExp backend a -> a
forall m a.
Monoid m =>
(a -> m) -> ComputedFieldBoolExp backend a -> m
forall b a.
(b -> a -> b) -> b -> ComputedFieldBoolExp backend a -> b
forall a b.
(a -> b -> b) -> b -> ComputedFieldBoolExp backend a -> b
forall (backend :: BackendType) a.
(Backend backend, Eq a) =>
a -> ComputedFieldBoolExp backend a -> Bool
forall (backend :: BackendType) a.
(Backend backend, Num a) =>
ComputedFieldBoolExp backend a -> a
forall (backend :: BackendType) a.
(Backend backend, Ord a) =>
ComputedFieldBoolExp backend a -> a
forall (backend :: BackendType) m.
(Backend backend, Monoid m) =>
ComputedFieldBoolExp backend m -> m
forall (backend :: BackendType) a.
Backend backend =>
ComputedFieldBoolExp backend a -> Bool
forall (backend :: BackendType) a.
Backend backend =>
ComputedFieldBoolExp backend a -> Int
forall (backend :: BackendType) a.
Backend backend =>
ComputedFieldBoolExp backend a -> [a]
forall (backend :: BackendType) a.
Backend backend =>
(a -> a -> a) -> ComputedFieldBoolExp backend a -> a
forall (backend :: BackendType) m a.
(Backend backend, Monoid m) =>
(a -> m) -> ComputedFieldBoolExp backend a -> m
forall (backend :: BackendType) b a.
Backend backend =>
(b -> a -> b) -> b -> ComputedFieldBoolExp backend a -> b
forall (backend :: BackendType) a b.
Backend backend =>
(a -> b -> b) -> b -> ComputedFieldBoolExp backend a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: ComputedFieldBoolExp backend a -> a
$cproduct :: forall (backend :: BackendType) a.
(Backend backend, Num a) =>
ComputedFieldBoolExp backend a -> a
sum :: ComputedFieldBoolExp backend a -> a
$csum :: forall (backend :: BackendType) a.
(Backend backend, Num a) =>
ComputedFieldBoolExp backend a -> a
minimum :: ComputedFieldBoolExp backend a -> a
$cminimum :: forall (backend :: BackendType) a.
(Backend backend, Ord a) =>
ComputedFieldBoolExp backend a -> a
maximum :: ComputedFieldBoolExp backend a -> a
$cmaximum :: forall (backend :: BackendType) a.
(Backend backend, Ord a) =>
ComputedFieldBoolExp backend a -> a
elem :: a -> ComputedFieldBoolExp backend a -> Bool
$celem :: forall (backend :: BackendType) a.
(Backend backend, Eq a) =>
a -> ComputedFieldBoolExp backend a -> Bool
length :: ComputedFieldBoolExp backend a -> Int
$clength :: forall (backend :: BackendType) a.
Backend backend =>
ComputedFieldBoolExp backend a -> Int
null :: ComputedFieldBoolExp backend a -> Bool
$cnull :: forall (backend :: BackendType) a.
Backend backend =>
ComputedFieldBoolExp backend a -> Bool
toList :: ComputedFieldBoolExp backend a -> [a]
$ctoList :: forall (backend :: BackendType) a.
Backend backend =>
ComputedFieldBoolExp backend a -> [a]
foldl1 :: (a -> a -> a) -> ComputedFieldBoolExp backend a -> a
$cfoldl1 :: forall (backend :: BackendType) a.
Backend backend =>
(a -> a -> a) -> ComputedFieldBoolExp backend a -> a
foldr1 :: (a -> a -> a) -> ComputedFieldBoolExp backend a -> a
$cfoldr1 :: forall (backend :: BackendType) a.
Backend backend =>
(a -> a -> a) -> ComputedFieldBoolExp backend a -> a
foldl' :: (b -> a -> b) -> b -> ComputedFieldBoolExp backend a -> b
$cfoldl' :: forall (backend :: BackendType) b a.
Backend backend =>
(b -> a -> b) -> b -> ComputedFieldBoolExp backend a -> b
foldl :: (b -> a -> b) -> b -> ComputedFieldBoolExp backend a -> b
$cfoldl :: forall (backend :: BackendType) b a.
Backend backend =>
(b -> a -> b) -> b -> ComputedFieldBoolExp backend a -> b
foldr' :: (a -> b -> b) -> b -> ComputedFieldBoolExp backend a -> b
$cfoldr' :: forall (backend :: BackendType) a b.
Backend backend =>
(a -> b -> b) -> b -> ComputedFieldBoolExp backend a -> b
foldr :: (a -> b -> b) -> b -> ComputedFieldBoolExp backend a -> b
$cfoldr :: forall (backend :: BackendType) a b.
Backend backend =>
(a -> b -> b) -> b -> ComputedFieldBoolExp backend a -> b
foldMap' :: (a -> m) -> ComputedFieldBoolExp backend a -> m
$cfoldMap' :: forall (backend :: BackendType) m a.
(Backend backend, Monoid m) =>
(a -> m) -> ComputedFieldBoolExp backend a -> m
foldMap :: (a -> m) -> ComputedFieldBoolExp backend a -> m
$cfoldMap :: forall (backend :: BackendType) m a.
(Backend backend, Monoid m) =>
(a -> m) -> ComputedFieldBoolExp backend a -> m
fold :: ComputedFieldBoolExp backend m -> m
$cfold :: forall (backend :: BackendType) m.
(Backend backend, Monoid m) =>
ComputedFieldBoolExp backend m -> m
Foldable, Functor (ComputedFieldBoolExp backend)
Foldable (ComputedFieldBoolExp backend)
Functor (ComputedFieldBoolExp backend)
-> Foldable (ComputedFieldBoolExp backend)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> ComputedFieldBoolExp backend a
-> f (ComputedFieldBoolExp backend b))
-> (forall (f :: * -> *) a.
Applicative f =>
ComputedFieldBoolExp backend (f a)
-> f (ComputedFieldBoolExp backend a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> ComputedFieldBoolExp backend a
-> m (ComputedFieldBoolExp backend b))
-> (forall (m :: * -> *) a.
Monad m =>
ComputedFieldBoolExp backend (m a)
-> m (ComputedFieldBoolExp backend a))
-> Traversable (ComputedFieldBoolExp backend)
(a -> f b)
-> ComputedFieldBoolExp backend a
-> f (ComputedFieldBoolExp backend b)
forall (backend :: BackendType).
Backend backend =>
Functor (ComputedFieldBoolExp backend)
forall (backend :: BackendType).
Backend backend =>
Foldable (ComputedFieldBoolExp backend)
forall (backend :: BackendType) (m :: * -> *) a.
(Backend backend, Monad m) =>
ComputedFieldBoolExp backend (m a)
-> m (ComputedFieldBoolExp backend a)
forall (backend :: BackendType) (f :: * -> *) a.
(Backend backend, Applicative f) =>
ComputedFieldBoolExp backend (f a)
-> f (ComputedFieldBoolExp backend a)
forall (backend :: BackendType) (m :: * -> *) a b.
(Backend backend, Monad m) =>
(a -> m b)
-> ComputedFieldBoolExp backend a
-> m (ComputedFieldBoolExp backend b)
forall (backend :: BackendType) (f :: * -> *) a b.
(Backend backend, Applicative f) =>
(a -> f b)
-> ComputedFieldBoolExp backend a
-> f (ComputedFieldBoolExp backend b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
ComputedFieldBoolExp backend (m a)
-> m (ComputedFieldBoolExp backend a)
forall (f :: * -> *) a.
Applicative f =>
ComputedFieldBoolExp backend (f a)
-> f (ComputedFieldBoolExp backend a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> ComputedFieldBoolExp backend a
-> m (ComputedFieldBoolExp backend b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> ComputedFieldBoolExp backend a
-> f (ComputedFieldBoolExp backend b)
sequence :: ComputedFieldBoolExp backend (m a)
-> m (ComputedFieldBoolExp backend a)
$csequence :: forall (backend :: BackendType) (m :: * -> *) a.
(Backend backend, Monad m) =>
ComputedFieldBoolExp backend (m a)
-> m (ComputedFieldBoolExp backend a)
mapM :: (a -> m b)
-> ComputedFieldBoolExp backend a
-> m (ComputedFieldBoolExp backend b)
$cmapM :: forall (backend :: BackendType) (m :: * -> *) a b.
(Backend backend, Monad m) =>
(a -> m b)
-> ComputedFieldBoolExp backend a
-> m (ComputedFieldBoolExp backend b)
sequenceA :: ComputedFieldBoolExp backend (f a)
-> f (ComputedFieldBoolExp backend a)
$csequenceA :: forall (backend :: BackendType) (f :: * -> *) a.
(Backend backend, Applicative f) =>
ComputedFieldBoolExp backend (f a)
-> f (ComputedFieldBoolExp backend a)
traverse :: (a -> f b)
-> ComputedFieldBoolExp backend a
-> f (ComputedFieldBoolExp backend b)
$ctraverse :: forall (backend :: BackendType) (f :: * -> *) a b.
(Backend backend, Applicative f) =>
(a -> f b)
-> ComputedFieldBoolExp backend a
-> f (ComputedFieldBoolExp backend b)
$cp2Traversable :: forall (backend :: BackendType).
Backend backend =>
Foldable (ComputedFieldBoolExp backend)
$cp1Traversable :: forall (backend :: BackendType).
Backend backend =>
Functor (ComputedFieldBoolExp backend)
Traversable, (forall x.
ComputedFieldBoolExp backend scalar
-> Rep (ComputedFieldBoolExp backend scalar) x)
-> (forall x.
Rep (ComputedFieldBoolExp backend scalar) x
-> ComputedFieldBoolExp backend scalar)
-> Generic (ComputedFieldBoolExp backend scalar)
forall x.
Rep (ComputedFieldBoolExp backend scalar) x
-> ComputedFieldBoolExp backend scalar
forall x.
ComputedFieldBoolExp backend scalar
-> Rep (ComputedFieldBoolExp backend scalar) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (backend :: BackendType) scalar x.
Rep (ComputedFieldBoolExp backend scalar) x
-> ComputedFieldBoolExp backend scalar
forall (backend :: BackendType) scalar x.
ComputedFieldBoolExp backend scalar
-> Rep (ComputedFieldBoolExp backend scalar) x
$cto :: forall (backend :: BackendType) scalar x.
Rep (ComputedFieldBoolExp backend scalar) x
-> ComputedFieldBoolExp backend scalar
$cfrom :: forall (backend :: BackendType) scalar x.
ComputedFieldBoolExp backend scalar
-> Rep (ComputedFieldBoolExp backend scalar) x
Generic)
deriving instance
( Backend b,
Eq (AnnBoolExp b a),
Eq (OpExpG b a)
) =>
Eq (ComputedFieldBoolExp b a)
deriving instance
( Backend b,
Show (AnnBoolExp b a),
Show (OpExpG b a)
) =>
Show (ComputedFieldBoolExp b a)
instance
( Backend b,
NFData (AnnBoolExp b a),
NFData (OpExpG b a)
) =>
NFData (ComputedFieldBoolExp b a)
instance
( Backend b,
Cacheable (AnnBoolExp b a),
Cacheable (OpExpG b a)
) =>
Cacheable (ComputedFieldBoolExp b a)
instance
( Backend b,
Hashable (AnnBoolExp b a),
Hashable (OpExpG b a)
) =>
Hashable (ComputedFieldBoolExp b a)
data AnnComputedFieldBoolExp (backend :: BackendType) scalar = AnnComputedFieldBoolExp
{ AnnComputedFieldBoolExp backend scalar -> XComputedField backend
_acfbXFieldInfo :: XComputedField backend,
AnnComputedFieldBoolExp backend scalar -> ComputedFieldName
_acfbName :: ComputedFieldName,
AnnComputedFieldBoolExp backend scalar -> FunctionName backend
_acfbFunction :: FunctionName backend,
AnnComputedFieldBoolExp backend scalar
-> FunctionArgsExp backend scalar
_acfbFunctionArgsExp :: FunctionArgsExp backend scalar,
AnnComputedFieldBoolExp backend scalar
-> ComputedFieldBoolExp backend scalar
_acfbBoolExp :: ComputedFieldBoolExp backend scalar
}
deriving ((forall x.
AnnComputedFieldBoolExp backend scalar
-> Rep (AnnComputedFieldBoolExp backend scalar) x)
-> (forall x.
Rep (AnnComputedFieldBoolExp backend scalar) x
-> AnnComputedFieldBoolExp backend scalar)
-> Generic (AnnComputedFieldBoolExp backend scalar)
forall x.
Rep (AnnComputedFieldBoolExp backend scalar) x
-> AnnComputedFieldBoolExp backend scalar
forall x.
AnnComputedFieldBoolExp backend scalar
-> Rep (AnnComputedFieldBoolExp backend scalar) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (backend :: BackendType) scalar x.
Rep (AnnComputedFieldBoolExp backend scalar) x
-> AnnComputedFieldBoolExp backend scalar
forall (backend :: BackendType) scalar x.
AnnComputedFieldBoolExp backend scalar
-> Rep (AnnComputedFieldBoolExp backend scalar) x
$cto :: forall (backend :: BackendType) scalar x.
Rep (AnnComputedFieldBoolExp backend scalar) x
-> AnnComputedFieldBoolExp backend scalar
$cfrom :: forall (backend :: BackendType) scalar x.
AnnComputedFieldBoolExp backend scalar
-> Rep (AnnComputedFieldBoolExp backend scalar) x
Generic)
deriving instance (Backend b) => Functor (AnnComputedFieldBoolExp b)
deriving instance (Backend b) => Foldable (AnnComputedFieldBoolExp b)
deriving instance (Backend b) => Traversable (AnnComputedFieldBoolExp b)
deriving instance
( Backend b,
Eq (ComputedFieldBoolExp b a),
Eq (FunctionArgsExp b a)
) =>
Eq (AnnComputedFieldBoolExp b a)
deriving instance
( Backend b,
Show (ComputedFieldBoolExp b a),
Show (FunctionArgsExp b a)
) =>
Show (AnnComputedFieldBoolExp b a)
instance
( Backend b,
NFData (ComputedFieldBoolExp b a),
NFData (FunctionArgsExp b a)
) =>
NFData (AnnComputedFieldBoolExp b a)
instance
( Backend b,
Cacheable (ComputedFieldBoolExp b a),
Cacheable (FunctionArgsExp b a)
) =>
Cacheable (AnnComputedFieldBoolExp b a)
instance
( Backend b,
Hashable (ComputedFieldBoolExp b a),
Hashable (FunctionArgsExp b a)
) =>
Hashable (AnnComputedFieldBoolExp b a)
data AnnBoolExpFld (backend :: BackendType) leaf
= AVColumn (ColumnInfo backend) [OpExpG backend leaf]
| AVRelationship (RelInfo backend) (AnnBoolExp backend leaf)
| AVComputedField (AnnComputedFieldBoolExp backend leaf)
| AVAggregationPredicates (AggregationPredicates backend leaf)
deriving (a -> AnnBoolExpFld backend b -> AnnBoolExpFld backend a
(a -> b) -> AnnBoolExpFld backend a -> AnnBoolExpFld backend b
(forall a b.
(a -> b) -> AnnBoolExpFld backend a -> AnnBoolExpFld backend b)
-> (forall a b.
a -> AnnBoolExpFld backend b -> AnnBoolExpFld backend a)
-> Functor (AnnBoolExpFld backend)
forall a b. a -> AnnBoolExpFld backend b -> AnnBoolExpFld backend a
forall a b.
(a -> b) -> AnnBoolExpFld backend a -> AnnBoolExpFld backend b
forall (backend :: BackendType) a b.
Backend backend =>
a -> AnnBoolExpFld backend b -> AnnBoolExpFld backend a
forall (backend :: BackendType) a b.
Backend backend =>
(a -> b) -> AnnBoolExpFld backend a -> AnnBoolExpFld backend b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> AnnBoolExpFld backend b -> AnnBoolExpFld backend a
$c<$ :: forall (backend :: BackendType) a b.
Backend backend =>
a -> AnnBoolExpFld backend b -> AnnBoolExpFld backend a
fmap :: (a -> b) -> AnnBoolExpFld backend a -> AnnBoolExpFld backend b
$cfmap :: forall (backend :: BackendType) a b.
Backend backend =>
(a -> b) -> AnnBoolExpFld backend a -> AnnBoolExpFld backend b
Functor, AnnBoolExpFld backend a -> Bool
(a -> m) -> AnnBoolExpFld backend a -> m
(a -> b -> b) -> b -> AnnBoolExpFld backend a -> b
(forall m. Monoid m => AnnBoolExpFld backend m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> AnnBoolExpFld backend a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> AnnBoolExpFld backend a -> m)
-> (forall a b. (a -> b -> b) -> b -> AnnBoolExpFld backend a -> b)
-> (forall a b. (a -> b -> b) -> b -> AnnBoolExpFld backend a -> b)
-> (forall b a. (b -> a -> b) -> b -> AnnBoolExpFld backend a -> b)
-> (forall b a. (b -> a -> b) -> b -> AnnBoolExpFld backend a -> b)
-> (forall a. (a -> a -> a) -> AnnBoolExpFld backend a -> a)
-> (forall a. (a -> a -> a) -> AnnBoolExpFld backend a -> a)
-> (forall a. AnnBoolExpFld backend a -> [a])
-> (forall a. AnnBoolExpFld backend a -> Bool)
-> (forall a. AnnBoolExpFld backend a -> Int)
-> (forall a. Eq a => a -> AnnBoolExpFld backend a -> Bool)
-> (forall a. Ord a => AnnBoolExpFld backend a -> a)
-> (forall a. Ord a => AnnBoolExpFld backend a -> a)
-> (forall a. Num a => AnnBoolExpFld backend a -> a)
-> (forall a. Num a => AnnBoolExpFld backend a -> a)
-> Foldable (AnnBoolExpFld backend)
forall a. Eq a => a -> AnnBoolExpFld backend a -> Bool
forall a. Num a => AnnBoolExpFld backend a -> a
forall a. Ord a => AnnBoolExpFld backend a -> a
forall m. Monoid m => AnnBoolExpFld backend m -> m
forall a. AnnBoolExpFld backend a -> Bool
forall a. AnnBoolExpFld backend a -> Int
forall a. AnnBoolExpFld backend a -> [a]
forall a. (a -> a -> a) -> AnnBoolExpFld backend a -> a
forall m a. Monoid m => (a -> m) -> AnnBoolExpFld backend a -> m
forall b a. (b -> a -> b) -> b -> AnnBoolExpFld backend a -> b
forall a b. (a -> b -> b) -> b -> AnnBoolExpFld backend a -> b
forall (backend :: BackendType) a.
(Backend backend, Eq a) =>
a -> AnnBoolExpFld backend a -> Bool
forall (backend :: BackendType) a.
(Backend backend, Num a) =>
AnnBoolExpFld backend a -> a
forall (backend :: BackendType) a.
(Backend backend, Ord a) =>
AnnBoolExpFld backend a -> a
forall (backend :: BackendType) m.
(Backend backend, Monoid m) =>
AnnBoolExpFld backend m -> m
forall (backend :: BackendType) a.
Backend backend =>
AnnBoolExpFld backend a -> Bool
forall (backend :: BackendType) a.
Backend backend =>
AnnBoolExpFld backend a -> Int
forall (backend :: BackendType) a.
Backend backend =>
AnnBoolExpFld backend a -> [a]
forall (backend :: BackendType) a.
Backend backend =>
(a -> a -> a) -> AnnBoolExpFld backend a -> a
forall (backend :: BackendType) m a.
(Backend backend, Monoid m) =>
(a -> m) -> AnnBoolExpFld backend a -> m
forall (backend :: BackendType) b a.
Backend backend =>
(b -> a -> b) -> b -> AnnBoolExpFld backend a -> b
forall (backend :: BackendType) a b.
Backend backend =>
(a -> b -> b) -> b -> AnnBoolExpFld backend a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: AnnBoolExpFld backend a -> a
$cproduct :: forall (backend :: BackendType) a.
(Backend backend, Num a) =>
AnnBoolExpFld backend a -> a
sum :: AnnBoolExpFld backend a -> a
$csum :: forall (backend :: BackendType) a.
(Backend backend, Num a) =>
AnnBoolExpFld backend a -> a
minimum :: AnnBoolExpFld backend a -> a
$cminimum :: forall (backend :: BackendType) a.
(Backend backend, Ord a) =>
AnnBoolExpFld backend a -> a
maximum :: AnnBoolExpFld backend a -> a
$cmaximum :: forall (backend :: BackendType) a.
(Backend backend, Ord a) =>
AnnBoolExpFld backend a -> a
elem :: a -> AnnBoolExpFld backend a -> Bool
$celem :: forall (backend :: BackendType) a.
(Backend backend, Eq a) =>
a -> AnnBoolExpFld backend a -> Bool
length :: AnnBoolExpFld backend a -> Int
$clength :: forall (backend :: BackendType) a.
Backend backend =>
AnnBoolExpFld backend a -> Int
null :: AnnBoolExpFld backend a -> Bool
$cnull :: forall (backend :: BackendType) a.
Backend backend =>
AnnBoolExpFld backend a -> Bool
toList :: AnnBoolExpFld backend a -> [a]
$ctoList :: forall (backend :: BackendType) a.
Backend backend =>
AnnBoolExpFld backend a -> [a]
foldl1 :: (a -> a -> a) -> AnnBoolExpFld backend a -> a
$cfoldl1 :: forall (backend :: BackendType) a.
Backend backend =>
(a -> a -> a) -> AnnBoolExpFld backend a -> a
foldr1 :: (a -> a -> a) -> AnnBoolExpFld backend a -> a
$cfoldr1 :: forall (backend :: BackendType) a.
Backend backend =>
(a -> a -> a) -> AnnBoolExpFld backend a -> a
foldl' :: (b -> a -> b) -> b -> AnnBoolExpFld backend a -> b
$cfoldl' :: forall (backend :: BackendType) b a.
Backend backend =>
(b -> a -> b) -> b -> AnnBoolExpFld backend a -> b
foldl :: (b -> a -> b) -> b -> AnnBoolExpFld backend a -> b
$cfoldl :: forall (backend :: BackendType) b a.
Backend backend =>
(b -> a -> b) -> b -> AnnBoolExpFld backend a -> b
foldr' :: (a -> b -> b) -> b -> AnnBoolExpFld backend a -> b
$cfoldr' :: forall (backend :: BackendType) a b.
Backend backend =>
(a -> b -> b) -> b -> AnnBoolExpFld backend a -> b
foldr :: (a -> b -> b) -> b -> AnnBoolExpFld backend a -> b
$cfoldr :: forall (backend :: BackendType) a b.
Backend backend =>
(a -> b -> b) -> b -> AnnBoolExpFld backend a -> b
foldMap' :: (a -> m) -> AnnBoolExpFld backend a -> m
$cfoldMap' :: forall (backend :: BackendType) m a.
(Backend backend, Monoid m) =>
(a -> m) -> AnnBoolExpFld backend a -> m
foldMap :: (a -> m) -> AnnBoolExpFld backend a -> m
$cfoldMap :: forall (backend :: BackendType) m a.
(Backend backend, Monoid m) =>
(a -> m) -> AnnBoolExpFld backend a -> m
fold :: AnnBoolExpFld backend m -> m
$cfold :: forall (backend :: BackendType) m.
(Backend backend, Monoid m) =>
AnnBoolExpFld backend m -> m
Foldable, Functor (AnnBoolExpFld backend)
Foldable (AnnBoolExpFld backend)
Functor (AnnBoolExpFld backend)
-> Foldable (AnnBoolExpFld backend)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> AnnBoolExpFld backend a -> f (AnnBoolExpFld backend b))
-> (forall (f :: * -> *) a.
Applicative f =>
AnnBoolExpFld backend (f a) -> f (AnnBoolExpFld backend a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> AnnBoolExpFld backend a -> m (AnnBoolExpFld backend b))
-> (forall (m :: * -> *) a.
Monad m =>
AnnBoolExpFld backend (m a) -> m (AnnBoolExpFld backend a))
-> Traversable (AnnBoolExpFld backend)
(a -> f b)
-> AnnBoolExpFld backend a -> f (AnnBoolExpFld backend b)
forall (backend :: BackendType).
Backend backend =>
Functor (AnnBoolExpFld backend)
forall (backend :: BackendType).
Backend backend =>
Foldable (AnnBoolExpFld backend)
forall (backend :: BackendType) (m :: * -> *) a.
(Backend backend, Monad m) =>
AnnBoolExpFld backend (m a) -> m (AnnBoolExpFld backend a)
forall (backend :: BackendType) (f :: * -> *) a.
(Backend backend, Applicative f) =>
AnnBoolExpFld backend (f a) -> f (AnnBoolExpFld backend a)
forall (backend :: BackendType) (m :: * -> *) a b.
(Backend backend, Monad m) =>
(a -> m b)
-> AnnBoolExpFld backend a -> m (AnnBoolExpFld backend b)
forall (backend :: BackendType) (f :: * -> *) a b.
(Backend backend, Applicative f) =>
(a -> f b)
-> AnnBoolExpFld backend a -> f (AnnBoolExpFld backend b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
AnnBoolExpFld backend (m a) -> m (AnnBoolExpFld backend a)
forall (f :: * -> *) a.
Applicative f =>
AnnBoolExpFld backend (f a) -> f (AnnBoolExpFld backend a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> AnnBoolExpFld backend a -> m (AnnBoolExpFld backend b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> AnnBoolExpFld backend a -> f (AnnBoolExpFld backend b)
sequence :: AnnBoolExpFld backend (m a) -> m (AnnBoolExpFld backend a)
$csequence :: forall (backend :: BackendType) (m :: * -> *) a.
(Backend backend, Monad m) =>
AnnBoolExpFld backend (m a) -> m (AnnBoolExpFld backend a)
mapM :: (a -> m b)
-> AnnBoolExpFld backend a -> m (AnnBoolExpFld backend b)
$cmapM :: forall (backend :: BackendType) (m :: * -> *) a b.
(Backend backend, Monad m) =>
(a -> m b)
-> AnnBoolExpFld backend a -> m (AnnBoolExpFld backend b)
sequenceA :: AnnBoolExpFld backend (f a) -> f (AnnBoolExpFld backend a)
$csequenceA :: forall (backend :: BackendType) (f :: * -> *) a.
(Backend backend, Applicative f) =>
AnnBoolExpFld backend (f a) -> f (AnnBoolExpFld backend a)
traverse :: (a -> f b)
-> AnnBoolExpFld backend a -> f (AnnBoolExpFld backend b)
$ctraverse :: forall (backend :: BackendType) (f :: * -> *) a b.
(Backend backend, Applicative f) =>
(a -> f b)
-> AnnBoolExpFld backend a -> f (AnnBoolExpFld backend b)
$cp2Traversable :: forall (backend :: BackendType).
Backend backend =>
Foldable (AnnBoolExpFld backend)
$cp1Traversable :: forall (backend :: BackendType).
Backend backend =>
Functor (AnnBoolExpFld backend)
Traversable, (forall x.
AnnBoolExpFld backend leaf -> Rep (AnnBoolExpFld backend leaf) x)
-> (forall x.
Rep (AnnBoolExpFld backend leaf) x -> AnnBoolExpFld backend leaf)
-> Generic (AnnBoolExpFld backend leaf)
forall x.
Rep (AnnBoolExpFld backend leaf) x -> AnnBoolExpFld backend leaf
forall x.
AnnBoolExpFld backend leaf -> Rep (AnnBoolExpFld backend leaf) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (backend :: BackendType) leaf x.
Rep (AnnBoolExpFld backend leaf) x -> AnnBoolExpFld backend leaf
forall (backend :: BackendType) leaf x.
AnnBoolExpFld backend leaf -> Rep (AnnBoolExpFld backend leaf) x
$cto :: forall (backend :: BackendType) leaf x.
Rep (AnnBoolExpFld backend leaf) x -> AnnBoolExpFld backend leaf
$cfrom :: forall (backend :: BackendType) leaf x.
AnnBoolExpFld backend leaf -> Rep (AnnBoolExpFld backend leaf) x
Generic)
deriving instance
( Backend b,
Eq (AggregationPredicates b a),
Eq (AnnBoolExp b a),
Eq (AnnComputedFieldBoolExp b a),
Eq (OpExpG b a)
) =>
Eq (AnnBoolExpFld b a)
deriving instance
( Backend b,
Show (AggregationPredicates b a),
Show (AnnBoolExp b a),
Show (AnnComputedFieldBoolExp b a),
Show (OpExpG b a)
) =>
Show (AnnBoolExpFld b a)
instance
( Backend b,
NFData (AggregationPredicates b a),
NFData (AnnBoolExp b a),
NFData (AnnComputedFieldBoolExp b a),
NFData (OpExpG b a)
) =>
NFData (AnnBoolExpFld b a)
instance
( Backend b,
Cacheable (AggregationPredicates b a),
Cacheable (AnnBoolExp b a),
Cacheable (AnnComputedFieldBoolExp b a),
Cacheable (OpExpG b a)
) =>
Cacheable (AnnBoolExpFld b a)
instance
( Backend b,
Hashable (AggregationPredicates b a),
Hashable (AnnBoolExp b a),
Hashable (AnnComputedFieldBoolExp b a),
Hashable (OpExpG b a)
) =>
Hashable (AnnBoolExpFld b a)
instance
( Backend b,
ToJSONKeyValue (AggregationPredicates b a),
ToJSONKeyValue (OpExpG b a),
ToJSON a
) =>
ToJSONKeyValue (AnnBoolExpFld b a)
where
toJSONKeyValue :: AnnBoolExpFld b a -> (Key, Value)
toJSONKeyValue = \case
AVColumn ColumnInfo b
pci [OpExpG b a]
opExps ->
( Text -> Key
K.fromText (Text -> Key) -> Text -> Key
forall a b. (a -> b) -> a -> b
$ Column b -> Text
forall a. ToTxt a => a -> Text
toTxt (Column b -> Text) -> Column b -> Text
forall a b. (a -> b) -> a -> b
$ ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
pci,
(ColumnInfo b, [Value]) -> Value
forall a. ToJSON a => a -> Value
toJSON (ColumnInfo b
pci, [(Key, Value)] -> Value
object ([(Key, Value)] -> Value)
-> (OpExpG b a -> [(Key, Value)]) -> OpExpG b a -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key, Value) -> [(Key, Value)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Key, Value) -> [(Key, Value)])
-> (OpExpG b a -> (Key, Value)) -> OpExpG b a -> [(Key, Value)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OpExpG b a -> (Key, Value)
forall a. ToJSONKeyValue a => a -> (Key, Value)
toJSONKeyValue (OpExpG b a -> Value) -> [OpExpG b a] -> [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [OpExpG b a]
opExps)
)
AVRelationship RelInfo b
ri AnnBoolExp b a
relBoolExp ->
( Text -> Key
K.fromText (Text -> Key) -> Text -> Key
forall a b. (a -> b) -> a -> b
$ RelName -> Text
relNameToTxt (RelName -> Text) -> RelName -> Text
forall a b. (a -> b) -> a -> b
$ RelInfo b -> RelName
forall (b :: BackendType). RelInfo b -> RelName
riName RelInfo b
ri,
(RelInfo b, Value) -> Value
forall a. ToJSON a => a -> Value
toJSON (RelInfo b
ri, AnnBoolExp b a -> Value
forall a. ToJSON a => a -> Value
toJSON AnnBoolExp b a
relBoolExp)
)
AVComputedField AnnComputedFieldBoolExp b a
cfBoolExp ->
( Text -> Key
K.fromText (Text -> Key) -> Text -> Key
forall a b. (a -> b) -> a -> b
$ ComputedFieldName -> Text
forall a. ToTxt a => a -> Text
toTxt (ComputedFieldName -> Text) -> ComputedFieldName -> Text
forall a b. (a -> b) -> a -> b
$ AnnComputedFieldBoolExp b a -> ComputedFieldName
forall (backend :: BackendType) scalar.
AnnComputedFieldBoolExp backend scalar -> ComputedFieldName
_acfbName AnnComputedFieldBoolExp b a
cfBoolExp,
let function :: FunctionName b
function = AnnComputedFieldBoolExp b a -> FunctionName b
forall (backend :: BackendType) scalar.
AnnComputedFieldBoolExp backend scalar -> FunctionName backend
_acfbFunction AnnComputedFieldBoolExp b a
cfBoolExp
in case AnnComputedFieldBoolExp b a -> ComputedFieldBoolExp b a
forall (backend :: BackendType) scalar.
AnnComputedFieldBoolExp backend scalar
-> ComputedFieldBoolExp backend scalar
_acfbBoolExp AnnComputedFieldBoolExp b a
cfBoolExp of
CFBEScalar [OpExpG b a]
opExps -> (FunctionName b, [Value]) -> Value
forall a. ToJSON a => a -> Value
toJSON (FunctionName b
function, [(Key, Value)] -> Value
object ([(Key, Value)] -> Value)
-> (OpExpG b a -> [(Key, Value)]) -> OpExpG b a -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key, Value) -> [(Key, Value)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Key, Value) -> [(Key, Value)])
-> (OpExpG b a -> (Key, Value)) -> OpExpG b a -> [(Key, Value)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OpExpG b a -> (Key, Value)
forall a. ToJSONKeyValue a => a -> (Key, Value)
toJSONKeyValue (OpExpG b a -> Value) -> [OpExpG b a] -> [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [OpExpG b a]
opExps)
CFBETable TableName b
_ AnnBoolExp b a
boolExp -> (FunctionName b, Value) -> Value
forall a. ToJSON a => a -> Value
toJSON (FunctionName b
function, AnnBoolExp b a -> Value
forall a. ToJSON a => a -> Value
toJSON AnnBoolExp b a
boolExp)
)
AVAggregationPredicates AggregationPredicates b a
avAggregationPredicates -> AggregationPredicates b a -> (Key, Value)
forall a. ToJSONKeyValue a => a -> (Key, Value)
toJSONKeyValue AggregationPredicates b a
avAggregationPredicates
type AnnBoolExp backend scalar = GBoolExp backend (AnnBoolExpFld backend scalar)
type AnnBoolExpFldSQL backend = AnnBoolExpFld backend (SQLExpression backend)
type AnnBoolExpSQL backend = AnnBoolExp backend (SQLExpression backend)
type AnnBoolExpPartialSQL backend = AnnBoolExp backend (PartialSQLExp backend)
annBoolExpTrue :: AnnBoolExp backend scalar
annBoolExpTrue :: AnnBoolExp backend scalar
annBoolExpTrue = AnnBoolExp backend scalar
forall (backend :: BackendType) field. GBoolExp backend field
gBoolExpTrue
andAnnBoolExps :: AnnBoolExp backend scalar -> AnnBoolExp backend scalar -> AnnBoolExp backend scalar
andAnnBoolExps :: AnnBoolExp backend scalar
-> AnnBoolExp backend scalar -> AnnBoolExp backend scalar
andAnnBoolExps AnnBoolExp backend scalar
l AnnBoolExp backend scalar
r = [AnnBoolExp backend scalar] -> AnnBoolExp backend scalar
forall (backend :: BackendType) field.
[GBoolExp backend field] -> GBoolExp backend field
BoolAnd [AnnBoolExp backend scalar
l, AnnBoolExp backend scalar
r]
data DWithinGeomOp field = DWithinGeomOp
{ DWithinGeomOp field -> field
dwgeomDistance :: field,
DWithinGeomOp field -> field
dwgeomFrom :: field
}
deriving (Int -> DWithinGeomOp field -> ShowS
[DWithinGeomOp field] -> ShowS
DWithinGeomOp field -> String
(Int -> DWithinGeomOp field -> ShowS)
-> (DWithinGeomOp field -> String)
-> ([DWithinGeomOp field] -> ShowS)
-> Show (DWithinGeomOp field)
forall field. Show field => Int -> DWithinGeomOp field -> ShowS
forall field. Show field => [DWithinGeomOp field] -> ShowS
forall field. Show field => DWithinGeomOp field -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DWithinGeomOp field] -> ShowS
$cshowList :: forall field. Show field => [DWithinGeomOp field] -> ShowS
show :: DWithinGeomOp field -> String
$cshow :: forall field. Show field => DWithinGeomOp field -> String
showsPrec :: Int -> DWithinGeomOp field -> ShowS
$cshowsPrec :: forall field. Show field => Int -> DWithinGeomOp field -> ShowS
Show, DWithinGeomOp field -> DWithinGeomOp field -> Bool
(DWithinGeomOp field -> DWithinGeomOp field -> Bool)
-> (DWithinGeomOp field -> DWithinGeomOp field -> Bool)
-> Eq (DWithinGeomOp field)
forall field.
Eq field =>
DWithinGeomOp field -> DWithinGeomOp field -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DWithinGeomOp field -> DWithinGeomOp field -> Bool
$c/= :: forall field.
Eq field =>
DWithinGeomOp field -> DWithinGeomOp field -> Bool
== :: DWithinGeomOp field -> DWithinGeomOp field -> Bool
$c== :: forall field.
Eq field =>
DWithinGeomOp field -> DWithinGeomOp field -> Bool
Eq, a -> DWithinGeomOp b -> DWithinGeomOp a
(a -> b) -> DWithinGeomOp a -> DWithinGeomOp b
(forall a b. (a -> b) -> DWithinGeomOp a -> DWithinGeomOp b)
-> (forall a b. a -> DWithinGeomOp b -> DWithinGeomOp a)
-> Functor DWithinGeomOp
forall a b. a -> DWithinGeomOp b -> DWithinGeomOp a
forall a b. (a -> b) -> DWithinGeomOp a -> DWithinGeomOp b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> DWithinGeomOp b -> DWithinGeomOp a
$c<$ :: forall a b. a -> DWithinGeomOp b -> DWithinGeomOp a
fmap :: (a -> b) -> DWithinGeomOp a -> DWithinGeomOp b
$cfmap :: forall a b. (a -> b) -> DWithinGeomOp a -> DWithinGeomOp b
Functor, DWithinGeomOp a -> Bool
(a -> m) -> DWithinGeomOp a -> m
(a -> b -> b) -> b -> DWithinGeomOp a -> b
(forall m. Monoid m => DWithinGeomOp m -> m)
-> (forall m a. Monoid m => (a -> m) -> DWithinGeomOp a -> m)
-> (forall m a. Monoid m => (a -> m) -> DWithinGeomOp a -> m)
-> (forall a b. (a -> b -> b) -> b -> DWithinGeomOp a -> b)
-> (forall a b. (a -> b -> b) -> b -> DWithinGeomOp a -> b)
-> (forall b a. (b -> a -> b) -> b -> DWithinGeomOp a -> b)
-> (forall b a. (b -> a -> b) -> b -> DWithinGeomOp a -> b)
-> (forall a. (a -> a -> a) -> DWithinGeomOp a -> a)
-> (forall a. (a -> a -> a) -> DWithinGeomOp a -> a)
-> (forall a. DWithinGeomOp a -> [a])
-> (forall a. DWithinGeomOp a -> Bool)
-> (forall a. DWithinGeomOp a -> Int)
-> (forall a. Eq a => a -> DWithinGeomOp a -> Bool)
-> (forall a. Ord a => DWithinGeomOp a -> a)
-> (forall a. Ord a => DWithinGeomOp a -> a)
-> (forall a. Num a => DWithinGeomOp a -> a)
-> (forall a. Num a => DWithinGeomOp a -> a)
-> Foldable DWithinGeomOp
forall a. Eq a => a -> DWithinGeomOp a -> Bool
forall a. Num a => DWithinGeomOp a -> a
forall a. Ord a => DWithinGeomOp a -> a
forall m. Monoid m => DWithinGeomOp m -> m
forall a. DWithinGeomOp a -> Bool
forall a. DWithinGeomOp a -> Int
forall a. DWithinGeomOp a -> [a]
forall a. (a -> a -> a) -> DWithinGeomOp a -> a
forall m a. Monoid m => (a -> m) -> DWithinGeomOp a -> m
forall b a. (b -> a -> b) -> b -> DWithinGeomOp a -> b
forall a b. (a -> b -> b) -> b -> DWithinGeomOp a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: DWithinGeomOp a -> a
$cproduct :: forall a. Num a => DWithinGeomOp a -> a
sum :: DWithinGeomOp a -> a
$csum :: forall a. Num a => DWithinGeomOp a -> a
minimum :: DWithinGeomOp a -> a
$cminimum :: forall a. Ord a => DWithinGeomOp a -> a
maximum :: DWithinGeomOp a -> a
$cmaximum :: forall a. Ord a => DWithinGeomOp a -> a
elem :: a -> DWithinGeomOp a -> Bool
$celem :: forall a. Eq a => a -> DWithinGeomOp a -> Bool
length :: DWithinGeomOp a -> Int
$clength :: forall a. DWithinGeomOp a -> Int
null :: DWithinGeomOp a -> Bool
$cnull :: forall a. DWithinGeomOp a -> Bool
toList :: DWithinGeomOp a -> [a]
$ctoList :: forall a. DWithinGeomOp a -> [a]
foldl1 :: (a -> a -> a) -> DWithinGeomOp a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> DWithinGeomOp a -> a
foldr1 :: (a -> a -> a) -> DWithinGeomOp a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> DWithinGeomOp a -> a
foldl' :: (b -> a -> b) -> b -> DWithinGeomOp a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> DWithinGeomOp a -> b
foldl :: (b -> a -> b) -> b -> DWithinGeomOp a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> DWithinGeomOp a -> b
foldr' :: (a -> b -> b) -> b -> DWithinGeomOp a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> DWithinGeomOp a -> b
foldr :: (a -> b -> b) -> b -> DWithinGeomOp a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> DWithinGeomOp a -> b
foldMap' :: (a -> m) -> DWithinGeomOp a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> DWithinGeomOp a -> m
foldMap :: (a -> m) -> DWithinGeomOp a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> DWithinGeomOp a -> m
fold :: DWithinGeomOp m -> m
$cfold :: forall m. Monoid m => DWithinGeomOp m -> m
Foldable, Functor DWithinGeomOp
Foldable DWithinGeomOp
Functor DWithinGeomOp
-> Foldable DWithinGeomOp
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> DWithinGeomOp a -> f (DWithinGeomOp b))
-> (forall (f :: * -> *) a.
Applicative f =>
DWithinGeomOp (f a) -> f (DWithinGeomOp a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> DWithinGeomOp a -> m (DWithinGeomOp b))
-> (forall (m :: * -> *) a.
Monad m =>
DWithinGeomOp (m a) -> m (DWithinGeomOp a))
-> Traversable DWithinGeomOp
(a -> f b) -> DWithinGeomOp a -> f (DWithinGeomOp b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
DWithinGeomOp (m a) -> m (DWithinGeomOp a)
forall (f :: * -> *) a.
Applicative f =>
DWithinGeomOp (f a) -> f (DWithinGeomOp a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> DWithinGeomOp a -> m (DWithinGeomOp b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> DWithinGeomOp a -> f (DWithinGeomOp b)
sequence :: DWithinGeomOp (m a) -> m (DWithinGeomOp a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
DWithinGeomOp (m a) -> m (DWithinGeomOp a)
mapM :: (a -> m b) -> DWithinGeomOp a -> m (DWithinGeomOp b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> DWithinGeomOp a -> m (DWithinGeomOp b)
sequenceA :: DWithinGeomOp (f a) -> f (DWithinGeomOp a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
DWithinGeomOp (f a) -> f (DWithinGeomOp a)
traverse :: (a -> f b) -> DWithinGeomOp a -> f (DWithinGeomOp b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> DWithinGeomOp a -> f (DWithinGeomOp b)
$cp2Traversable :: Foldable DWithinGeomOp
$cp1Traversable :: Functor DWithinGeomOp
Traversable, (forall x. DWithinGeomOp field -> Rep (DWithinGeomOp field) x)
-> (forall x. Rep (DWithinGeomOp field) x -> DWithinGeomOp field)
-> Generic (DWithinGeomOp field)
forall x. Rep (DWithinGeomOp field) x -> DWithinGeomOp field
forall x. DWithinGeomOp field -> Rep (DWithinGeomOp field) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall field x. Rep (DWithinGeomOp field) x -> DWithinGeomOp field
forall field x. DWithinGeomOp field -> Rep (DWithinGeomOp field) x
$cto :: forall field x. Rep (DWithinGeomOp field) x -> DWithinGeomOp field
$cfrom :: forall field x. DWithinGeomOp field -> Rep (DWithinGeomOp field) x
Generic, Typeable (DWithinGeomOp field)
DataType
Constr
Typeable (DWithinGeomOp field)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DWithinGeomOp field
-> c (DWithinGeomOp field))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (DWithinGeomOp field))
-> (DWithinGeomOp field -> Constr)
-> (DWithinGeomOp field -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (DWithinGeomOp field)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (DWithinGeomOp field)))
-> ((forall b. Data b => b -> b)
-> DWithinGeomOp field -> DWithinGeomOp field)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeomOp field -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeomOp field -> r)
-> (forall u.
(forall d. Data d => d -> u) -> DWithinGeomOp field -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> DWithinGeomOp field -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> DWithinGeomOp field -> m (DWithinGeomOp field))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DWithinGeomOp field -> m (DWithinGeomOp field))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DWithinGeomOp field -> m (DWithinGeomOp field))
-> Data (DWithinGeomOp field)
DWithinGeomOp field -> DataType
DWithinGeomOp field -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (DWithinGeomOp field))
(forall b. Data b => b -> b)
-> DWithinGeomOp field -> DWithinGeomOp field
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DWithinGeomOp field
-> c (DWithinGeomOp field)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (DWithinGeomOp field)
forall field. Data field => Typeable (DWithinGeomOp field)
forall field. Data field => DWithinGeomOp field -> DataType
forall field. Data field => DWithinGeomOp field -> Constr
forall field.
Data field =>
(forall b. Data b => b -> b)
-> DWithinGeomOp field -> DWithinGeomOp field
forall field u.
Data field =>
Int -> (forall d. Data d => d -> u) -> DWithinGeomOp field -> u
forall field u.
Data field =>
(forall d. Data d => d -> u) -> DWithinGeomOp field -> [u]
forall field r r'.
Data field =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeomOp field -> r
forall field r r'.
Data field =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeomOp field -> r
forall field (m :: * -> *).
(Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> DWithinGeomOp field -> m (DWithinGeomOp field)
forall field (m :: * -> *).
(Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> DWithinGeomOp field -> m (DWithinGeomOp field)
forall field (c :: * -> *).
Data field =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (DWithinGeomOp field)
forall field (c :: * -> *).
Data field =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DWithinGeomOp field
-> c (DWithinGeomOp field)
forall field (t :: * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (DWithinGeomOp field))
forall field (t :: * -> * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (DWithinGeomOp field))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> DWithinGeomOp field -> u
forall u.
(forall d. Data d => d -> u) -> DWithinGeomOp field -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeomOp field -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeomOp field -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> DWithinGeomOp field -> m (DWithinGeomOp field)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DWithinGeomOp field -> m (DWithinGeomOp field)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (DWithinGeomOp field)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DWithinGeomOp field
-> c (DWithinGeomOp field)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (DWithinGeomOp field))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (DWithinGeomOp field))
$cDWithinGeomOp :: Constr
$tDWithinGeomOp :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> DWithinGeomOp field -> m (DWithinGeomOp field)
$cgmapMo :: forall field (m :: * -> *).
(Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> DWithinGeomOp field -> m (DWithinGeomOp field)
gmapMp :: (forall d. Data d => d -> m d)
-> DWithinGeomOp field -> m (DWithinGeomOp field)
$cgmapMp :: forall field (m :: * -> *).
(Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> DWithinGeomOp field -> m (DWithinGeomOp field)
gmapM :: (forall d. Data d => d -> m d)
-> DWithinGeomOp field -> m (DWithinGeomOp field)
$cgmapM :: forall field (m :: * -> *).
(Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> DWithinGeomOp field -> m (DWithinGeomOp field)
gmapQi :: Int -> (forall d. Data d => d -> u) -> DWithinGeomOp field -> u
$cgmapQi :: forall field u.
Data field =>
Int -> (forall d. Data d => d -> u) -> DWithinGeomOp field -> u
gmapQ :: (forall d. Data d => d -> u) -> DWithinGeomOp field -> [u]
$cgmapQ :: forall field u.
Data field =>
(forall d. Data d => d -> u) -> DWithinGeomOp field -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeomOp field -> r
$cgmapQr :: forall field r r'.
Data field =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeomOp field -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeomOp field -> r
$cgmapQl :: forall field r r'.
Data field =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeomOp field -> r
gmapT :: (forall b. Data b => b -> b)
-> DWithinGeomOp field -> DWithinGeomOp field
$cgmapT :: forall field.
Data field =>
(forall b. Data b => b -> b)
-> DWithinGeomOp field -> DWithinGeomOp field
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (DWithinGeomOp field))
$cdataCast2 :: forall field (t :: * -> * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (DWithinGeomOp field))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (DWithinGeomOp field))
$cdataCast1 :: forall field (t :: * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (DWithinGeomOp field))
dataTypeOf :: DWithinGeomOp field -> DataType
$cdataTypeOf :: forall field. Data field => DWithinGeomOp field -> DataType
toConstr :: DWithinGeomOp field -> Constr
$ctoConstr :: forall field. Data field => DWithinGeomOp field -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (DWithinGeomOp field)
$cgunfold :: forall field (c :: * -> *).
Data field =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (DWithinGeomOp field)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DWithinGeomOp field
-> c (DWithinGeomOp field)
$cgfoldl :: forall field (c :: * -> *).
Data field =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DWithinGeomOp field
-> c (DWithinGeomOp field)
$cp1Data :: forall field. Data field => Typeable (DWithinGeomOp field)
Data)
instance (NFData a) => NFData (DWithinGeomOp a)
instance (Cacheable a) => Cacheable (DWithinGeomOp a)
instance (Hashable a) => Hashable (DWithinGeomOp a)
$(deriveJSON hasuraJSON ''DWithinGeomOp)
data DWithinGeogOp field = DWithinGeogOp
{ DWithinGeogOp field -> field
dwgeogDistance :: field,
DWithinGeogOp field -> field
dwgeogFrom :: field,
DWithinGeogOp field -> field
dwgeogUseSpheroid :: field
}
deriving (Int -> DWithinGeogOp field -> ShowS
[DWithinGeogOp field] -> ShowS
DWithinGeogOp field -> String
(Int -> DWithinGeogOp field -> ShowS)
-> (DWithinGeogOp field -> String)
-> ([DWithinGeogOp field] -> ShowS)
-> Show (DWithinGeogOp field)
forall field. Show field => Int -> DWithinGeogOp field -> ShowS
forall field. Show field => [DWithinGeogOp field] -> ShowS
forall field. Show field => DWithinGeogOp field -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DWithinGeogOp field] -> ShowS
$cshowList :: forall field. Show field => [DWithinGeogOp field] -> ShowS
show :: DWithinGeogOp field -> String
$cshow :: forall field. Show field => DWithinGeogOp field -> String
showsPrec :: Int -> DWithinGeogOp field -> ShowS
$cshowsPrec :: forall field. Show field => Int -> DWithinGeogOp field -> ShowS
Show, DWithinGeogOp field -> DWithinGeogOp field -> Bool
(DWithinGeogOp field -> DWithinGeogOp field -> Bool)
-> (DWithinGeogOp field -> DWithinGeogOp field -> Bool)
-> Eq (DWithinGeogOp field)
forall field.
Eq field =>
DWithinGeogOp field -> DWithinGeogOp field -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DWithinGeogOp field -> DWithinGeogOp field -> Bool
$c/= :: forall field.
Eq field =>
DWithinGeogOp field -> DWithinGeogOp field -> Bool
== :: DWithinGeogOp field -> DWithinGeogOp field -> Bool
$c== :: forall field.
Eq field =>
DWithinGeogOp field -> DWithinGeogOp field -> Bool
Eq, a -> DWithinGeogOp b -> DWithinGeogOp a
(a -> b) -> DWithinGeogOp a -> DWithinGeogOp b
(forall a b. (a -> b) -> DWithinGeogOp a -> DWithinGeogOp b)
-> (forall a b. a -> DWithinGeogOp b -> DWithinGeogOp a)
-> Functor DWithinGeogOp
forall a b. a -> DWithinGeogOp b -> DWithinGeogOp a
forall a b. (a -> b) -> DWithinGeogOp a -> DWithinGeogOp b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> DWithinGeogOp b -> DWithinGeogOp a
$c<$ :: forall a b. a -> DWithinGeogOp b -> DWithinGeogOp a
fmap :: (a -> b) -> DWithinGeogOp a -> DWithinGeogOp b
$cfmap :: forall a b. (a -> b) -> DWithinGeogOp a -> DWithinGeogOp b
Functor, DWithinGeogOp a -> Bool
(a -> m) -> DWithinGeogOp a -> m
(a -> b -> b) -> b -> DWithinGeogOp a -> b
(forall m. Monoid m => DWithinGeogOp m -> m)
-> (forall m a. Monoid m => (a -> m) -> DWithinGeogOp a -> m)
-> (forall m a. Monoid m => (a -> m) -> DWithinGeogOp a -> m)
-> (forall a b. (a -> b -> b) -> b -> DWithinGeogOp a -> b)
-> (forall a b. (a -> b -> b) -> b -> DWithinGeogOp a -> b)
-> (forall b a. (b -> a -> b) -> b -> DWithinGeogOp a -> b)
-> (forall b a. (b -> a -> b) -> b -> DWithinGeogOp a -> b)
-> (forall a. (a -> a -> a) -> DWithinGeogOp a -> a)
-> (forall a. (a -> a -> a) -> DWithinGeogOp a -> a)
-> (forall a. DWithinGeogOp a -> [a])
-> (forall a. DWithinGeogOp a -> Bool)
-> (forall a. DWithinGeogOp a -> Int)
-> (forall a. Eq a => a -> DWithinGeogOp a -> Bool)
-> (forall a. Ord a => DWithinGeogOp a -> a)
-> (forall a. Ord a => DWithinGeogOp a -> a)
-> (forall a. Num a => DWithinGeogOp a -> a)
-> (forall a. Num a => DWithinGeogOp a -> a)
-> Foldable DWithinGeogOp
forall a. Eq a => a -> DWithinGeogOp a -> Bool
forall a. Num a => DWithinGeogOp a -> a
forall a. Ord a => DWithinGeogOp a -> a
forall m. Monoid m => DWithinGeogOp m -> m
forall a. DWithinGeogOp a -> Bool
forall a. DWithinGeogOp a -> Int
forall a. DWithinGeogOp a -> [a]
forall a. (a -> a -> a) -> DWithinGeogOp a -> a
forall m a. Monoid m => (a -> m) -> DWithinGeogOp a -> m
forall b a. (b -> a -> b) -> b -> DWithinGeogOp a -> b
forall a b. (a -> b -> b) -> b -> DWithinGeogOp a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: DWithinGeogOp a -> a
$cproduct :: forall a. Num a => DWithinGeogOp a -> a
sum :: DWithinGeogOp a -> a
$csum :: forall a. Num a => DWithinGeogOp a -> a
minimum :: DWithinGeogOp a -> a
$cminimum :: forall a. Ord a => DWithinGeogOp a -> a
maximum :: DWithinGeogOp a -> a
$cmaximum :: forall a. Ord a => DWithinGeogOp a -> a
elem :: a -> DWithinGeogOp a -> Bool
$celem :: forall a. Eq a => a -> DWithinGeogOp a -> Bool
length :: DWithinGeogOp a -> Int
$clength :: forall a. DWithinGeogOp a -> Int
null :: DWithinGeogOp a -> Bool
$cnull :: forall a. DWithinGeogOp a -> Bool
toList :: DWithinGeogOp a -> [a]
$ctoList :: forall a. DWithinGeogOp a -> [a]
foldl1 :: (a -> a -> a) -> DWithinGeogOp a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> DWithinGeogOp a -> a
foldr1 :: (a -> a -> a) -> DWithinGeogOp a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> DWithinGeogOp a -> a
foldl' :: (b -> a -> b) -> b -> DWithinGeogOp a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> DWithinGeogOp a -> b
foldl :: (b -> a -> b) -> b -> DWithinGeogOp a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> DWithinGeogOp a -> b
foldr' :: (a -> b -> b) -> b -> DWithinGeogOp a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> DWithinGeogOp a -> b
foldr :: (a -> b -> b) -> b -> DWithinGeogOp a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> DWithinGeogOp a -> b
foldMap' :: (a -> m) -> DWithinGeogOp a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> DWithinGeogOp a -> m
foldMap :: (a -> m) -> DWithinGeogOp a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> DWithinGeogOp a -> m
fold :: DWithinGeogOp m -> m
$cfold :: forall m. Monoid m => DWithinGeogOp m -> m
Foldable, Functor DWithinGeogOp
Foldable DWithinGeogOp
Functor DWithinGeogOp
-> Foldable DWithinGeogOp
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> DWithinGeogOp a -> f (DWithinGeogOp b))
-> (forall (f :: * -> *) a.
Applicative f =>
DWithinGeogOp (f a) -> f (DWithinGeogOp a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> DWithinGeogOp a -> m (DWithinGeogOp b))
-> (forall (m :: * -> *) a.
Monad m =>
DWithinGeogOp (m a) -> m (DWithinGeogOp a))
-> Traversable DWithinGeogOp
(a -> f b) -> DWithinGeogOp a -> f (DWithinGeogOp b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
DWithinGeogOp (m a) -> m (DWithinGeogOp a)
forall (f :: * -> *) a.
Applicative f =>
DWithinGeogOp (f a) -> f (DWithinGeogOp a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> DWithinGeogOp a -> m (DWithinGeogOp b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> DWithinGeogOp a -> f (DWithinGeogOp b)
sequence :: DWithinGeogOp (m a) -> m (DWithinGeogOp a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
DWithinGeogOp (m a) -> m (DWithinGeogOp a)
mapM :: (a -> m b) -> DWithinGeogOp a -> m (DWithinGeogOp b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> DWithinGeogOp a -> m (DWithinGeogOp b)
sequenceA :: DWithinGeogOp (f a) -> f (DWithinGeogOp a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
DWithinGeogOp (f a) -> f (DWithinGeogOp a)
traverse :: (a -> f b) -> DWithinGeogOp a -> f (DWithinGeogOp b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> DWithinGeogOp a -> f (DWithinGeogOp b)
$cp2Traversable :: Foldable DWithinGeogOp
$cp1Traversable :: Functor DWithinGeogOp
Traversable, (forall x. DWithinGeogOp field -> Rep (DWithinGeogOp field) x)
-> (forall x. Rep (DWithinGeogOp field) x -> DWithinGeogOp field)
-> Generic (DWithinGeogOp field)
forall x. Rep (DWithinGeogOp field) x -> DWithinGeogOp field
forall x. DWithinGeogOp field -> Rep (DWithinGeogOp field) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall field x. Rep (DWithinGeogOp field) x -> DWithinGeogOp field
forall field x. DWithinGeogOp field -> Rep (DWithinGeogOp field) x
$cto :: forall field x. Rep (DWithinGeogOp field) x -> DWithinGeogOp field
$cfrom :: forall field x. DWithinGeogOp field -> Rep (DWithinGeogOp field) x
Generic, Typeable (DWithinGeogOp field)
DataType
Constr
Typeable (DWithinGeogOp field)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DWithinGeogOp field
-> c (DWithinGeogOp field))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (DWithinGeogOp field))
-> (DWithinGeogOp field -> Constr)
-> (DWithinGeogOp field -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (DWithinGeogOp field)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (DWithinGeogOp field)))
-> ((forall b. Data b => b -> b)
-> DWithinGeogOp field -> DWithinGeogOp field)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeogOp field -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeogOp field -> r)
-> (forall u.
(forall d. Data d => d -> u) -> DWithinGeogOp field -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> DWithinGeogOp field -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> DWithinGeogOp field -> m (DWithinGeogOp field))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DWithinGeogOp field -> m (DWithinGeogOp field))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DWithinGeogOp field -> m (DWithinGeogOp field))
-> Data (DWithinGeogOp field)
DWithinGeogOp field -> DataType
DWithinGeogOp field -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (DWithinGeogOp field))
(forall b. Data b => b -> b)
-> DWithinGeogOp field -> DWithinGeogOp field
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DWithinGeogOp field
-> c (DWithinGeogOp field)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (DWithinGeogOp field)
forall field. Data field => Typeable (DWithinGeogOp field)
forall field. Data field => DWithinGeogOp field -> DataType
forall field. Data field => DWithinGeogOp field -> Constr
forall field.
Data field =>
(forall b. Data b => b -> b)
-> DWithinGeogOp field -> DWithinGeogOp field
forall field u.
Data field =>
Int -> (forall d. Data d => d -> u) -> DWithinGeogOp field -> u
forall field u.
Data field =>
(forall d. Data d => d -> u) -> DWithinGeogOp field -> [u]
forall field r r'.
Data field =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeogOp field -> r
forall field r r'.
Data field =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeogOp field -> r
forall field (m :: * -> *).
(Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> DWithinGeogOp field -> m (DWithinGeogOp field)
forall field (m :: * -> *).
(Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> DWithinGeogOp field -> m (DWithinGeogOp field)
forall field (c :: * -> *).
Data field =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (DWithinGeogOp field)
forall field (c :: * -> *).
Data field =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DWithinGeogOp field
-> c (DWithinGeogOp field)
forall field (t :: * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (DWithinGeogOp field))
forall field (t :: * -> * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (DWithinGeogOp field))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> DWithinGeogOp field -> u
forall u.
(forall d. Data d => d -> u) -> DWithinGeogOp field -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeogOp field -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeogOp field -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> DWithinGeogOp field -> m (DWithinGeogOp field)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> DWithinGeogOp field -> m (DWithinGeogOp field)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (DWithinGeogOp field)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DWithinGeogOp field
-> c (DWithinGeogOp field)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (DWithinGeogOp field))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (DWithinGeogOp field))
$cDWithinGeogOp :: Constr
$tDWithinGeogOp :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> DWithinGeogOp field -> m (DWithinGeogOp field)
$cgmapMo :: forall field (m :: * -> *).
(Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> DWithinGeogOp field -> m (DWithinGeogOp field)
gmapMp :: (forall d. Data d => d -> m d)
-> DWithinGeogOp field -> m (DWithinGeogOp field)
$cgmapMp :: forall field (m :: * -> *).
(Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> DWithinGeogOp field -> m (DWithinGeogOp field)
gmapM :: (forall d. Data d => d -> m d)
-> DWithinGeogOp field -> m (DWithinGeogOp field)
$cgmapM :: forall field (m :: * -> *).
(Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> DWithinGeogOp field -> m (DWithinGeogOp field)
gmapQi :: Int -> (forall d. Data d => d -> u) -> DWithinGeogOp field -> u
$cgmapQi :: forall field u.
Data field =>
Int -> (forall d. Data d => d -> u) -> DWithinGeogOp field -> u
gmapQ :: (forall d. Data d => d -> u) -> DWithinGeogOp field -> [u]
$cgmapQ :: forall field u.
Data field =>
(forall d. Data d => d -> u) -> DWithinGeogOp field -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeogOp field -> r
$cgmapQr :: forall field r r'.
Data field =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeogOp field -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeogOp field -> r
$cgmapQl :: forall field r r'.
Data field =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DWithinGeogOp field -> r
gmapT :: (forall b. Data b => b -> b)
-> DWithinGeogOp field -> DWithinGeogOp field
$cgmapT :: forall field.
Data field =>
(forall b. Data b => b -> b)
-> DWithinGeogOp field -> DWithinGeogOp field
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (DWithinGeogOp field))
$cdataCast2 :: forall field (t :: * -> * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (DWithinGeogOp field))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (DWithinGeogOp field))
$cdataCast1 :: forall field (t :: * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (DWithinGeogOp field))
dataTypeOf :: DWithinGeogOp field -> DataType
$cdataTypeOf :: forall field. Data field => DWithinGeogOp field -> DataType
toConstr :: DWithinGeogOp field -> Constr
$ctoConstr :: forall field. Data field => DWithinGeogOp field -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (DWithinGeogOp field)
$cgunfold :: forall field (c :: * -> *).
Data field =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (DWithinGeogOp field)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DWithinGeogOp field
-> c (DWithinGeogOp field)
$cgfoldl :: forall field (c :: * -> *).
Data field =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> DWithinGeogOp field
-> c (DWithinGeogOp field)
$cp1Data :: forall field. Data field => Typeable (DWithinGeogOp field)
Data)
instance (NFData a) => NFData (DWithinGeogOp a)
instance (Cacheable a) => Cacheable (DWithinGeogOp a)
instance (Hashable a) => Hashable (DWithinGeogOp a)
$(deriveJSON hasuraJSON ''DWithinGeogOp)
data STIntersectsNbandGeommin field = STIntersectsNbandGeommin
{ STIntersectsNbandGeommin field -> field
singNband :: field,
STIntersectsNbandGeommin field -> field
singGeommin :: field
}
deriving (Int -> STIntersectsNbandGeommin field -> ShowS
[STIntersectsNbandGeommin field] -> ShowS
STIntersectsNbandGeommin field -> String
(Int -> STIntersectsNbandGeommin field -> ShowS)
-> (STIntersectsNbandGeommin field -> String)
-> ([STIntersectsNbandGeommin field] -> ShowS)
-> Show (STIntersectsNbandGeommin field)
forall field.
Show field =>
Int -> STIntersectsNbandGeommin field -> ShowS
forall field.
Show field =>
[STIntersectsNbandGeommin field] -> ShowS
forall field.
Show field =>
STIntersectsNbandGeommin field -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [STIntersectsNbandGeommin field] -> ShowS
$cshowList :: forall field.
Show field =>
[STIntersectsNbandGeommin field] -> ShowS
show :: STIntersectsNbandGeommin field -> String
$cshow :: forall field.
Show field =>
STIntersectsNbandGeommin field -> String
showsPrec :: Int -> STIntersectsNbandGeommin field -> ShowS
$cshowsPrec :: forall field.
Show field =>
Int -> STIntersectsNbandGeommin field -> ShowS
Show, STIntersectsNbandGeommin field
-> STIntersectsNbandGeommin field -> Bool
(STIntersectsNbandGeommin field
-> STIntersectsNbandGeommin field -> Bool)
-> (STIntersectsNbandGeommin field
-> STIntersectsNbandGeommin field -> Bool)
-> Eq (STIntersectsNbandGeommin field)
forall field.
Eq field =>
STIntersectsNbandGeommin field
-> STIntersectsNbandGeommin field -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: STIntersectsNbandGeommin field
-> STIntersectsNbandGeommin field -> Bool
$c/= :: forall field.
Eq field =>
STIntersectsNbandGeommin field
-> STIntersectsNbandGeommin field -> Bool
== :: STIntersectsNbandGeommin field
-> STIntersectsNbandGeommin field -> Bool
$c== :: forall field.
Eq field =>
STIntersectsNbandGeommin field
-> STIntersectsNbandGeommin field -> Bool
Eq, a -> STIntersectsNbandGeommin b -> STIntersectsNbandGeommin a
(a -> b)
-> STIntersectsNbandGeommin a -> STIntersectsNbandGeommin b
(forall a b.
(a -> b)
-> STIntersectsNbandGeommin a -> STIntersectsNbandGeommin b)
-> (forall a b.
a -> STIntersectsNbandGeommin b -> STIntersectsNbandGeommin a)
-> Functor STIntersectsNbandGeommin
forall a b.
a -> STIntersectsNbandGeommin b -> STIntersectsNbandGeommin a
forall a b.
(a -> b)
-> STIntersectsNbandGeommin a -> STIntersectsNbandGeommin b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> STIntersectsNbandGeommin b -> STIntersectsNbandGeommin a
$c<$ :: forall a b.
a -> STIntersectsNbandGeommin b -> STIntersectsNbandGeommin a
fmap :: (a -> b)
-> STIntersectsNbandGeommin a -> STIntersectsNbandGeommin b
$cfmap :: forall a b.
(a -> b)
-> STIntersectsNbandGeommin a -> STIntersectsNbandGeommin b
Functor, STIntersectsNbandGeommin a -> Bool
(a -> m) -> STIntersectsNbandGeommin a -> m
(a -> b -> b) -> b -> STIntersectsNbandGeommin a -> b
(forall m. Monoid m => STIntersectsNbandGeommin m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> STIntersectsNbandGeommin a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> STIntersectsNbandGeommin a -> m)
-> (forall a b.
(a -> b -> b) -> b -> STIntersectsNbandGeommin a -> b)
-> (forall a b.
(a -> b -> b) -> b -> STIntersectsNbandGeommin a -> b)
-> (forall b a.
(b -> a -> b) -> b -> STIntersectsNbandGeommin a -> b)
-> (forall b a.
(b -> a -> b) -> b -> STIntersectsNbandGeommin a -> b)
-> (forall a. (a -> a -> a) -> STIntersectsNbandGeommin a -> a)
-> (forall a. (a -> a -> a) -> STIntersectsNbandGeommin a -> a)
-> (forall a. STIntersectsNbandGeommin a -> [a])
-> (forall a. STIntersectsNbandGeommin a -> Bool)
-> (forall a. STIntersectsNbandGeommin a -> Int)
-> (forall a. Eq a => a -> STIntersectsNbandGeommin a -> Bool)
-> (forall a. Ord a => STIntersectsNbandGeommin a -> a)
-> (forall a. Ord a => STIntersectsNbandGeommin a -> a)
-> (forall a. Num a => STIntersectsNbandGeommin a -> a)
-> (forall a. Num a => STIntersectsNbandGeommin a -> a)
-> Foldable STIntersectsNbandGeommin
forall a. Eq a => a -> STIntersectsNbandGeommin a -> Bool
forall a. Num a => STIntersectsNbandGeommin a -> a
forall a. Ord a => STIntersectsNbandGeommin a -> a
forall m. Monoid m => STIntersectsNbandGeommin m -> m
forall a. STIntersectsNbandGeommin a -> Bool
forall a. STIntersectsNbandGeommin a -> Int
forall a. STIntersectsNbandGeommin a -> [a]
forall a. (a -> a -> a) -> STIntersectsNbandGeommin a -> a
forall m a. Monoid m => (a -> m) -> STIntersectsNbandGeommin a -> m
forall b a. (b -> a -> b) -> b -> STIntersectsNbandGeommin a -> b
forall a b. (a -> b -> b) -> b -> STIntersectsNbandGeommin a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: STIntersectsNbandGeommin a -> a
$cproduct :: forall a. Num a => STIntersectsNbandGeommin a -> a
sum :: STIntersectsNbandGeommin a -> a
$csum :: forall a. Num a => STIntersectsNbandGeommin a -> a
minimum :: STIntersectsNbandGeommin a -> a
$cminimum :: forall a. Ord a => STIntersectsNbandGeommin a -> a
maximum :: STIntersectsNbandGeommin a -> a
$cmaximum :: forall a. Ord a => STIntersectsNbandGeommin a -> a
elem :: a -> STIntersectsNbandGeommin a -> Bool
$celem :: forall a. Eq a => a -> STIntersectsNbandGeommin a -> Bool
length :: STIntersectsNbandGeommin a -> Int
$clength :: forall a. STIntersectsNbandGeommin a -> Int
null :: STIntersectsNbandGeommin a -> Bool
$cnull :: forall a. STIntersectsNbandGeommin a -> Bool
toList :: STIntersectsNbandGeommin a -> [a]
$ctoList :: forall a. STIntersectsNbandGeommin a -> [a]
foldl1 :: (a -> a -> a) -> STIntersectsNbandGeommin a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> STIntersectsNbandGeommin a -> a
foldr1 :: (a -> a -> a) -> STIntersectsNbandGeommin a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> STIntersectsNbandGeommin a -> a
foldl' :: (b -> a -> b) -> b -> STIntersectsNbandGeommin a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> STIntersectsNbandGeommin a -> b
foldl :: (b -> a -> b) -> b -> STIntersectsNbandGeommin a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> STIntersectsNbandGeommin a -> b
foldr' :: (a -> b -> b) -> b -> STIntersectsNbandGeommin a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> STIntersectsNbandGeommin a -> b
foldr :: (a -> b -> b) -> b -> STIntersectsNbandGeommin a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> STIntersectsNbandGeommin a -> b
foldMap' :: (a -> m) -> STIntersectsNbandGeommin a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> STIntersectsNbandGeommin a -> m
foldMap :: (a -> m) -> STIntersectsNbandGeommin a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> STIntersectsNbandGeommin a -> m
fold :: STIntersectsNbandGeommin m -> m
$cfold :: forall m. Monoid m => STIntersectsNbandGeommin m -> m
Foldable, Functor STIntersectsNbandGeommin
Foldable STIntersectsNbandGeommin
Functor STIntersectsNbandGeommin
-> Foldable STIntersectsNbandGeommin
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> STIntersectsNbandGeommin a -> f (STIntersectsNbandGeommin b))
-> (forall (f :: * -> *) a.
Applicative f =>
STIntersectsNbandGeommin (f a) -> f (STIntersectsNbandGeommin a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> STIntersectsNbandGeommin a -> m (STIntersectsNbandGeommin b))
-> (forall (m :: * -> *) a.
Monad m =>
STIntersectsNbandGeommin (m a) -> m (STIntersectsNbandGeommin a))
-> Traversable STIntersectsNbandGeommin
(a -> f b)
-> STIntersectsNbandGeommin a -> f (STIntersectsNbandGeommin b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
STIntersectsNbandGeommin (m a) -> m (STIntersectsNbandGeommin a)
forall (f :: * -> *) a.
Applicative f =>
STIntersectsNbandGeommin (f a) -> f (STIntersectsNbandGeommin a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> STIntersectsNbandGeommin a -> m (STIntersectsNbandGeommin b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> STIntersectsNbandGeommin a -> f (STIntersectsNbandGeommin b)
sequence :: STIntersectsNbandGeommin (m a) -> m (STIntersectsNbandGeommin a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
STIntersectsNbandGeommin (m a) -> m (STIntersectsNbandGeommin a)
mapM :: (a -> m b)
-> STIntersectsNbandGeommin a -> m (STIntersectsNbandGeommin b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> STIntersectsNbandGeommin a -> m (STIntersectsNbandGeommin b)
sequenceA :: STIntersectsNbandGeommin (f a) -> f (STIntersectsNbandGeommin a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
STIntersectsNbandGeommin (f a) -> f (STIntersectsNbandGeommin a)
traverse :: (a -> f b)
-> STIntersectsNbandGeommin a -> f (STIntersectsNbandGeommin b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> STIntersectsNbandGeommin a -> f (STIntersectsNbandGeommin b)
$cp2Traversable :: Foldable STIntersectsNbandGeommin
$cp1Traversable :: Functor STIntersectsNbandGeommin
Traversable, (forall x.
STIntersectsNbandGeommin field
-> Rep (STIntersectsNbandGeommin field) x)
-> (forall x.
Rep (STIntersectsNbandGeommin field) x
-> STIntersectsNbandGeommin field)
-> Generic (STIntersectsNbandGeommin field)
forall x.
Rep (STIntersectsNbandGeommin field) x
-> STIntersectsNbandGeommin field
forall x.
STIntersectsNbandGeommin field
-> Rep (STIntersectsNbandGeommin field) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall field x.
Rep (STIntersectsNbandGeommin field) x
-> STIntersectsNbandGeommin field
forall field x.
STIntersectsNbandGeommin field
-> Rep (STIntersectsNbandGeommin field) x
$cto :: forall field x.
Rep (STIntersectsNbandGeommin field) x
-> STIntersectsNbandGeommin field
$cfrom :: forall field x.
STIntersectsNbandGeommin field
-> Rep (STIntersectsNbandGeommin field) x
Generic, Typeable (STIntersectsNbandGeommin field)
DataType
Constr
Typeable (STIntersectsNbandGeommin field)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> STIntersectsNbandGeommin field
-> c (STIntersectsNbandGeommin field))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (STIntersectsNbandGeommin field))
-> (STIntersectsNbandGeommin field -> Constr)
-> (STIntersectsNbandGeommin field -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (STIntersectsNbandGeommin field)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (STIntersectsNbandGeommin field)))
-> ((forall b. Data b => b -> b)
-> STIntersectsNbandGeommin field
-> STIntersectsNbandGeommin field)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsNbandGeommin field
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsNbandGeommin field
-> r)
-> (forall u.
(forall d. Data d => d -> u)
-> STIntersectsNbandGeommin field -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u)
-> STIntersectsNbandGeommin field
-> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> STIntersectsNbandGeommin field
-> m (STIntersectsNbandGeommin field))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> STIntersectsNbandGeommin field
-> m (STIntersectsNbandGeommin field))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> STIntersectsNbandGeommin field
-> m (STIntersectsNbandGeommin field))
-> Data (STIntersectsNbandGeommin field)
STIntersectsNbandGeommin field -> DataType
STIntersectsNbandGeommin field -> Constr
(forall d. Data d => c (t d))
-> Maybe (c (STIntersectsNbandGeommin field))
(forall b. Data b => b -> b)
-> STIntersectsNbandGeommin field -> STIntersectsNbandGeommin field
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> STIntersectsNbandGeommin field
-> c (STIntersectsNbandGeommin field)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (STIntersectsNbandGeommin field)
forall field.
Data field =>
Typeable (STIntersectsNbandGeommin field)
forall field.
Data field =>
STIntersectsNbandGeommin field -> DataType
forall field.
Data field =>
STIntersectsNbandGeommin field -> Constr
forall field.
Data field =>
(forall b. Data b => b -> b)
-> STIntersectsNbandGeommin field -> STIntersectsNbandGeommin field
forall field u.
Data field =>
Int
-> (forall d. Data d => d -> u)
-> STIntersectsNbandGeommin field
-> u
forall field u.
Data field =>
(forall d. Data d => d -> u)
-> STIntersectsNbandGeommin field -> [u]
forall field r r'.
Data field =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsNbandGeommin field
-> r
forall field r r'.
Data field =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsNbandGeommin field
-> r
forall field (m :: * -> *).
(Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> STIntersectsNbandGeommin field
-> m (STIntersectsNbandGeommin field)
forall field (m :: * -> *).
(Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> STIntersectsNbandGeommin field
-> m (STIntersectsNbandGeommin field)
forall field (c :: * -> *).
Data field =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (STIntersectsNbandGeommin field)
forall field (c :: * -> *).
Data field =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> STIntersectsNbandGeommin field
-> c (STIntersectsNbandGeommin field)
forall field (t :: * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (STIntersectsNbandGeommin field))
forall field (t :: * -> * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (STIntersectsNbandGeommin field))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u)
-> STIntersectsNbandGeommin field
-> u
forall u.
(forall d. Data d => d -> u)
-> STIntersectsNbandGeommin field -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsNbandGeommin field
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsNbandGeommin field
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> STIntersectsNbandGeommin field
-> m (STIntersectsNbandGeommin field)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> STIntersectsNbandGeommin field
-> m (STIntersectsNbandGeommin field)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (STIntersectsNbandGeommin field)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> STIntersectsNbandGeommin field
-> c (STIntersectsNbandGeommin field)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (STIntersectsNbandGeommin field))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (STIntersectsNbandGeommin field))
$cSTIntersectsNbandGeommin :: Constr
$tSTIntersectsNbandGeommin :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> STIntersectsNbandGeommin field
-> m (STIntersectsNbandGeommin field)
$cgmapMo :: forall field (m :: * -> *).
(Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> STIntersectsNbandGeommin field
-> m (STIntersectsNbandGeommin field)
gmapMp :: (forall d. Data d => d -> m d)
-> STIntersectsNbandGeommin field
-> m (STIntersectsNbandGeommin field)
$cgmapMp :: forall field (m :: * -> *).
(Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> STIntersectsNbandGeommin field
-> m (STIntersectsNbandGeommin field)
gmapM :: (forall d. Data d => d -> m d)
-> STIntersectsNbandGeommin field
-> m (STIntersectsNbandGeommin field)
$cgmapM :: forall field (m :: * -> *).
(Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> STIntersectsNbandGeommin field
-> m (STIntersectsNbandGeommin field)
gmapQi :: Int
-> (forall d. Data d => d -> u)
-> STIntersectsNbandGeommin field
-> u
$cgmapQi :: forall field u.
Data field =>
Int
-> (forall d. Data d => d -> u)
-> STIntersectsNbandGeommin field
-> u
gmapQ :: (forall d. Data d => d -> u)
-> STIntersectsNbandGeommin field -> [u]
$cgmapQ :: forall field u.
Data field =>
(forall d. Data d => d -> u)
-> STIntersectsNbandGeommin field -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsNbandGeommin field
-> r
$cgmapQr :: forall field r r'.
Data field =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsNbandGeommin field
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsNbandGeommin field
-> r
$cgmapQl :: forall field r r'.
Data field =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsNbandGeommin field
-> r
gmapT :: (forall b. Data b => b -> b)
-> STIntersectsNbandGeommin field -> STIntersectsNbandGeommin field
$cgmapT :: forall field.
Data field =>
(forall b. Data b => b -> b)
-> STIntersectsNbandGeommin field -> STIntersectsNbandGeommin field
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (STIntersectsNbandGeommin field))
$cdataCast2 :: forall field (t :: * -> * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (STIntersectsNbandGeommin field))
dataCast1 :: (forall d. Data d => c (t d))
-> Maybe (c (STIntersectsNbandGeommin field))
$cdataCast1 :: forall field (t :: * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (STIntersectsNbandGeommin field))
dataTypeOf :: STIntersectsNbandGeommin field -> DataType
$cdataTypeOf :: forall field.
Data field =>
STIntersectsNbandGeommin field -> DataType
toConstr :: STIntersectsNbandGeommin field -> Constr
$ctoConstr :: forall field.
Data field =>
STIntersectsNbandGeommin field -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (STIntersectsNbandGeommin field)
$cgunfold :: forall field (c :: * -> *).
Data field =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (STIntersectsNbandGeommin field)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> STIntersectsNbandGeommin field
-> c (STIntersectsNbandGeommin field)
$cgfoldl :: forall field (c :: * -> *).
Data field =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> STIntersectsNbandGeommin field
-> c (STIntersectsNbandGeommin field)
$cp1Data :: forall field.
Data field =>
Typeable (STIntersectsNbandGeommin field)
Data)
instance (NFData a) => NFData (STIntersectsNbandGeommin a)
instance (Cacheable a) => Cacheable (STIntersectsNbandGeommin a)
instance (Hashable a) => Hashable (STIntersectsNbandGeommin a)
$(deriveJSON hasuraJSON ''STIntersectsNbandGeommin)
data STIntersectsGeomminNband field = STIntersectsGeomminNband
{ STIntersectsGeomminNband field -> field
signGeommin :: field,
STIntersectsGeomminNband field -> Maybe field
signNband :: Maybe field
}
deriving (Int -> STIntersectsGeomminNband field -> ShowS
[STIntersectsGeomminNband field] -> ShowS
STIntersectsGeomminNband field -> String
(Int -> STIntersectsGeomminNband field -> ShowS)
-> (STIntersectsGeomminNband field -> String)
-> ([STIntersectsGeomminNband field] -> ShowS)
-> Show (STIntersectsGeomminNband field)
forall field.
Show field =>
Int -> STIntersectsGeomminNband field -> ShowS
forall field.
Show field =>
[STIntersectsGeomminNband field] -> ShowS
forall field.
Show field =>
STIntersectsGeomminNband field -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [STIntersectsGeomminNband field] -> ShowS
$cshowList :: forall field.
Show field =>
[STIntersectsGeomminNband field] -> ShowS
show :: STIntersectsGeomminNband field -> String
$cshow :: forall field.
Show field =>
STIntersectsGeomminNband field -> String
showsPrec :: Int -> STIntersectsGeomminNband field -> ShowS
$cshowsPrec :: forall field.
Show field =>
Int -> STIntersectsGeomminNband field -> ShowS
Show, STIntersectsGeomminNband field
-> STIntersectsGeomminNband field -> Bool
(STIntersectsGeomminNband field
-> STIntersectsGeomminNband field -> Bool)
-> (STIntersectsGeomminNband field
-> STIntersectsGeomminNband field -> Bool)
-> Eq (STIntersectsGeomminNband field)
forall field.
Eq field =>
STIntersectsGeomminNband field
-> STIntersectsGeomminNband field -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: STIntersectsGeomminNband field
-> STIntersectsGeomminNband field -> Bool
$c/= :: forall field.
Eq field =>
STIntersectsGeomminNband field
-> STIntersectsGeomminNband field -> Bool
== :: STIntersectsGeomminNband field
-> STIntersectsGeomminNband field -> Bool
$c== :: forall field.
Eq field =>
STIntersectsGeomminNband field
-> STIntersectsGeomminNband field -> Bool
Eq, a -> STIntersectsGeomminNband b -> STIntersectsGeomminNband a
(a -> b)
-> STIntersectsGeomminNband a -> STIntersectsGeomminNband b
(forall a b.
(a -> b)
-> STIntersectsGeomminNband a -> STIntersectsGeomminNband b)
-> (forall a b.
a -> STIntersectsGeomminNband b -> STIntersectsGeomminNband a)
-> Functor STIntersectsGeomminNband
forall a b.
a -> STIntersectsGeomminNband b -> STIntersectsGeomminNband a
forall a b.
(a -> b)
-> STIntersectsGeomminNband a -> STIntersectsGeomminNband b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> STIntersectsGeomminNband b -> STIntersectsGeomminNband a
$c<$ :: forall a b.
a -> STIntersectsGeomminNband b -> STIntersectsGeomminNband a
fmap :: (a -> b)
-> STIntersectsGeomminNband a -> STIntersectsGeomminNband b
$cfmap :: forall a b.
(a -> b)
-> STIntersectsGeomminNband a -> STIntersectsGeomminNband b
Functor, STIntersectsGeomminNband a -> Bool
(a -> m) -> STIntersectsGeomminNband a -> m
(a -> b -> b) -> b -> STIntersectsGeomminNband a -> b
(forall m. Monoid m => STIntersectsGeomminNband m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> STIntersectsGeomminNband a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> STIntersectsGeomminNband a -> m)
-> (forall a b.
(a -> b -> b) -> b -> STIntersectsGeomminNband a -> b)
-> (forall a b.
(a -> b -> b) -> b -> STIntersectsGeomminNband a -> b)
-> (forall b a.
(b -> a -> b) -> b -> STIntersectsGeomminNband a -> b)
-> (forall b a.
(b -> a -> b) -> b -> STIntersectsGeomminNband a -> b)
-> (forall a. (a -> a -> a) -> STIntersectsGeomminNband a -> a)
-> (forall a. (a -> a -> a) -> STIntersectsGeomminNband a -> a)
-> (forall a. STIntersectsGeomminNband a -> [a])
-> (forall a. STIntersectsGeomminNband a -> Bool)
-> (forall a. STIntersectsGeomminNband a -> Int)
-> (forall a. Eq a => a -> STIntersectsGeomminNband a -> Bool)
-> (forall a. Ord a => STIntersectsGeomminNband a -> a)
-> (forall a. Ord a => STIntersectsGeomminNband a -> a)
-> (forall a. Num a => STIntersectsGeomminNband a -> a)
-> (forall a. Num a => STIntersectsGeomminNband a -> a)
-> Foldable STIntersectsGeomminNband
forall a. Eq a => a -> STIntersectsGeomminNband a -> Bool
forall a. Num a => STIntersectsGeomminNband a -> a
forall a. Ord a => STIntersectsGeomminNband a -> a
forall m. Monoid m => STIntersectsGeomminNband m -> m
forall a. STIntersectsGeomminNband a -> Bool
forall a. STIntersectsGeomminNband a -> Int
forall a. STIntersectsGeomminNband a -> [a]
forall a. (a -> a -> a) -> STIntersectsGeomminNband a -> a
forall m a. Monoid m => (a -> m) -> STIntersectsGeomminNband a -> m
forall b a. (b -> a -> b) -> b -> STIntersectsGeomminNband a -> b
forall a b. (a -> b -> b) -> b -> STIntersectsGeomminNband a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: STIntersectsGeomminNband a -> a
$cproduct :: forall a. Num a => STIntersectsGeomminNband a -> a
sum :: STIntersectsGeomminNband a -> a
$csum :: forall a. Num a => STIntersectsGeomminNband a -> a
minimum :: STIntersectsGeomminNband a -> a
$cminimum :: forall a. Ord a => STIntersectsGeomminNband a -> a
maximum :: STIntersectsGeomminNband a -> a
$cmaximum :: forall a. Ord a => STIntersectsGeomminNband a -> a
elem :: a -> STIntersectsGeomminNband a -> Bool
$celem :: forall a. Eq a => a -> STIntersectsGeomminNband a -> Bool
length :: STIntersectsGeomminNband a -> Int
$clength :: forall a. STIntersectsGeomminNband a -> Int
null :: STIntersectsGeomminNband a -> Bool
$cnull :: forall a. STIntersectsGeomminNband a -> Bool
toList :: STIntersectsGeomminNband a -> [a]
$ctoList :: forall a. STIntersectsGeomminNband a -> [a]
foldl1 :: (a -> a -> a) -> STIntersectsGeomminNband a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> STIntersectsGeomminNband a -> a
foldr1 :: (a -> a -> a) -> STIntersectsGeomminNband a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> STIntersectsGeomminNband a -> a
foldl' :: (b -> a -> b) -> b -> STIntersectsGeomminNband a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> STIntersectsGeomminNband a -> b
foldl :: (b -> a -> b) -> b -> STIntersectsGeomminNband a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> STIntersectsGeomminNband a -> b
foldr' :: (a -> b -> b) -> b -> STIntersectsGeomminNband a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> STIntersectsGeomminNband a -> b
foldr :: (a -> b -> b) -> b -> STIntersectsGeomminNband a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> STIntersectsGeomminNband a -> b
foldMap' :: (a -> m) -> STIntersectsGeomminNband a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> STIntersectsGeomminNband a -> m
foldMap :: (a -> m) -> STIntersectsGeomminNband a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> STIntersectsGeomminNband a -> m
fold :: STIntersectsGeomminNband m -> m
$cfold :: forall m. Monoid m => STIntersectsGeomminNband m -> m
Foldable, Functor STIntersectsGeomminNband
Foldable STIntersectsGeomminNband
Functor STIntersectsGeomminNband
-> Foldable STIntersectsGeomminNband
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> STIntersectsGeomminNband a -> f (STIntersectsGeomminNband b))
-> (forall (f :: * -> *) a.
Applicative f =>
STIntersectsGeomminNband (f a) -> f (STIntersectsGeomminNband a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> STIntersectsGeomminNband a -> m (STIntersectsGeomminNband b))
-> (forall (m :: * -> *) a.
Monad m =>
STIntersectsGeomminNband (m a) -> m (STIntersectsGeomminNband a))
-> Traversable STIntersectsGeomminNband
(a -> f b)
-> STIntersectsGeomminNband a -> f (STIntersectsGeomminNband b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
STIntersectsGeomminNband (m a) -> m (STIntersectsGeomminNband a)
forall (f :: * -> *) a.
Applicative f =>
STIntersectsGeomminNband (f a) -> f (STIntersectsGeomminNband a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> STIntersectsGeomminNband a -> m (STIntersectsGeomminNband b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> STIntersectsGeomminNband a -> f (STIntersectsGeomminNband b)
sequence :: STIntersectsGeomminNband (m a) -> m (STIntersectsGeomminNband a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
STIntersectsGeomminNband (m a) -> m (STIntersectsGeomminNband a)
mapM :: (a -> m b)
-> STIntersectsGeomminNband a -> m (STIntersectsGeomminNband b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> STIntersectsGeomminNband a -> m (STIntersectsGeomminNband b)
sequenceA :: STIntersectsGeomminNband (f a) -> f (STIntersectsGeomminNband a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
STIntersectsGeomminNband (f a) -> f (STIntersectsGeomminNband a)
traverse :: (a -> f b)
-> STIntersectsGeomminNband a -> f (STIntersectsGeomminNband b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> STIntersectsGeomminNband a -> f (STIntersectsGeomminNband b)
$cp2Traversable :: Foldable STIntersectsGeomminNband
$cp1Traversable :: Functor STIntersectsGeomminNband
Traversable, (forall x.
STIntersectsGeomminNband field
-> Rep (STIntersectsGeomminNband field) x)
-> (forall x.
Rep (STIntersectsGeomminNband field) x
-> STIntersectsGeomminNband field)
-> Generic (STIntersectsGeomminNband field)
forall x.
Rep (STIntersectsGeomminNband field) x
-> STIntersectsGeomminNband field
forall x.
STIntersectsGeomminNband field
-> Rep (STIntersectsGeomminNband field) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall field x.
Rep (STIntersectsGeomminNband field) x
-> STIntersectsGeomminNband field
forall field x.
STIntersectsGeomminNband field
-> Rep (STIntersectsGeomminNband field) x
$cto :: forall field x.
Rep (STIntersectsGeomminNband field) x
-> STIntersectsGeomminNband field
$cfrom :: forall field x.
STIntersectsGeomminNband field
-> Rep (STIntersectsGeomminNband field) x
Generic, Typeable (STIntersectsGeomminNband field)
DataType
Constr
Typeable (STIntersectsGeomminNband field)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> STIntersectsGeomminNband field
-> c (STIntersectsGeomminNband field))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (STIntersectsGeomminNband field))
-> (STIntersectsGeomminNband field -> Constr)
-> (STIntersectsGeomminNband field -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (STIntersectsGeomminNband field)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (STIntersectsGeomminNband field)))
-> ((forall b. Data b => b -> b)
-> STIntersectsGeomminNband field
-> STIntersectsGeomminNband field)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsGeomminNband field
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsGeomminNband field
-> r)
-> (forall u.
(forall d. Data d => d -> u)
-> STIntersectsGeomminNband field -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u)
-> STIntersectsGeomminNband field
-> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> STIntersectsGeomminNband field
-> m (STIntersectsGeomminNband field))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> STIntersectsGeomminNband field
-> m (STIntersectsGeomminNband field))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> STIntersectsGeomminNband field
-> m (STIntersectsGeomminNband field))
-> Data (STIntersectsGeomminNband field)
STIntersectsGeomminNband field -> DataType
STIntersectsGeomminNband field -> Constr
(forall d. Data d => c (t d))
-> Maybe (c (STIntersectsGeomminNband field))
(forall b. Data b => b -> b)
-> STIntersectsGeomminNband field -> STIntersectsGeomminNband field
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> STIntersectsGeomminNband field
-> c (STIntersectsGeomminNband field)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (STIntersectsGeomminNband field)
forall field.
Data field =>
Typeable (STIntersectsGeomminNband field)
forall field.
Data field =>
STIntersectsGeomminNband field -> DataType
forall field.
Data field =>
STIntersectsGeomminNband field -> Constr
forall field.
Data field =>
(forall b. Data b => b -> b)
-> STIntersectsGeomminNband field -> STIntersectsGeomminNband field
forall field u.
Data field =>
Int
-> (forall d. Data d => d -> u)
-> STIntersectsGeomminNband field
-> u
forall field u.
Data field =>
(forall d. Data d => d -> u)
-> STIntersectsGeomminNband field -> [u]
forall field r r'.
Data field =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsGeomminNband field
-> r
forall field r r'.
Data field =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsGeomminNband field
-> r
forall field (m :: * -> *).
(Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> STIntersectsGeomminNband field
-> m (STIntersectsGeomminNband field)
forall field (m :: * -> *).
(Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> STIntersectsGeomminNband field
-> m (STIntersectsGeomminNband field)
forall field (c :: * -> *).
Data field =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (STIntersectsGeomminNband field)
forall field (c :: * -> *).
Data field =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> STIntersectsGeomminNband field
-> c (STIntersectsGeomminNband field)
forall field (t :: * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (STIntersectsGeomminNband field))
forall field (t :: * -> * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (STIntersectsGeomminNband field))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u)
-> STIntersectsGeomminNband field
-> u
forall u.
(forall d. Data d => d -> u)
-> STIntersectsGeomminNband field -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsGeomminNband field
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsGeomminNband field
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> STIntersectsGeomminNband field
-> m (STIntersectsGeomminNband field)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> STIntersectsGeomminNband field
-> m (STIntersectsGeomminNband field)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (STIntersectsGeomminNband field)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> STIntersectsGeomminNband field
-> c (STIntersectsGeomminNband field)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (STIntersectsGeomminNband field))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (STIntersectsGeomminNband field))
$cSTIntersectsGeomminNband :: Constr
$tSTIntersectsGeomminNband :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> STIntersectsGeomminNband field
-> m (STIntersectsGeomminNband field)
$cgmapMo :: forall field (m :: * -> *).
(Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> STIntersectsGeomminNband field
-> m (STIntersectsGeomminNband field)
gmapMp :: (forall d. Data d => d -> m d)
-> STIntersectsGeomminNband field
-> m (STIntersectsGeomminNband field)
$cgmapMp :: forall field (m :: * -> *).
(Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> STIntersectsGeomminNband field
-> m (STIntersectsGeomminNband field)
gmapM :: (forall d. Data d => d -> m d)
-> STIntersectsGeomminNband field
-> m (STIntersectsGeomminNband field)
$cgmapM :: forall field (m :: * -> *).
(Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> STIntersectsGeomminNband field
-> m (STIntersectsGeomminNband field)
gmapQi :: Int
-> (forall d. Data d => d -> u)
-> STIntersectsGeomminNband field
-> u
$cgmapQi :: forall field u.
Data field =>
Int
-> (forall d. Data d => d -> u)
-> STIntersectsGeomminNband field
-> u
gmapQ :: (forall d. Data d => d -> u)
-> STIntersectsGeomminNband field -> [u]
$cgmapQ :: forall field u.
Data field =>
(forall d. Data d => d -> u)
-> STIntersectsGeomminNband field -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsGeomminNband field
-> r
$cgmapQr :: forall field r r'.
Data field =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsGeomminNband field
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsGeomminNband field
-> r
$cgmapQl :: forall field r r'.
Data field =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> STIntersectsGeomminNband field
-> r
gmapT :: (forall b. Data b => b -> b)
-> STIntersectsGeomminNband field -> STIntersectsGeomminNband field
$cgmapT :: forall field.
Data field =>
(forall b. Data b => b -> b)
-> STIntersectsGeomminNband field -> STIntersectsGeomminNband field
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (STIntersectsGeomminNband field))
$cdataCast2 :: forall field (t :: * -> * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (STIntersectsGeomminNband field))
dataCast1 :: (forall d. Data d => c (t d))
-> Maybe (c (STIntersectsGeomminNband field))
$cdataCast1 :: forall field (t :: * -> *) (c :: * -> *).
(Data field, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (STIntersectsGeomminNband field))
dataTypeOf :: STIntersectsGeomminNband field -> DataType
$cdataTypeOf :: forall field.
Data field =>
STIntersectsGeomminNband field -> DataType
toConstr :: STIntersectsGeomminNband field -> Constr
$ctoConstr :: forall field.
Data field =>
STIntersectsGeomminNband field -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (STIntersectsGeomminNband field)
$cgunfold :: forall field (c :: * -> *).
Data field =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (STIntersectsGeomminNband field)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> STIntersectsGeomminNband field
-> c (STIntersectsGeomminNband field)
$cgfoldl :: forall field (c :: * -> *).
Data field =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> STIntersectsGeomminNband field
-> c (STIntersectsGeomminNband field)
$cp1Data :: forall field.
Data field =>
Typeable (STIntersectsGeomminNband field)
Data)
instance (NFData a) => NFData (STIntersectsGeomminNband a)
instance (Cacheable a) => Cacheable (STIntersectsGeomminNband a)
instance (Hashable a) => Hashable (STIntersectsGeomminNband a)
$(deriveJSON hasuraJSON ''STIntersectsGeomminNband)
newtype AnnColumnCaseBoolExpField (backend :: BackendType) field = AnnColumnCaseBoolExpField {AnnColumnCaseBoolExpField backend field
-> AnnBoolExpFld backend field
_accColCaseBoolExpField :: AnnBoolExpFld backend field}
deriving (a
-> AnnColumnCaseBoolExpField backend b
-> AnnColumnCaseBoolExpField backend a
(a -> b)
-> AnnColumnCaseBoolExpField backend a
-> AnnColumnCaseBoolExpField backend b
(forall a b.
(a -> b)
-> AnnColumnCaseBoolExpField backend a
-> AnnColumnCaseBoolExpField backend b)
-> (forall a b.
a
-> AnnColumnCaseBoolExpField backend b
-> AnnColumnCaseBoolExpField backend a)
-> Functor (AnnColumnCaseBoolExpField backend)
forall a b.
a
-> AnnColumnCaseBoolExpField backend b
-> AnnColumnCaseBoolExpField backend a
forall a b.
(a -> b)
-> AnnColumnCaseBoolExpField backend a
-> AnnColumnCaseBoolExpField backend b
forall (backend :: BackendType) a b.
Backend backend =>
a
-> AnnColumnCaseBoolExpField backend b
-> AnnColumnCaseBoolExpField backend a
forall (backend :: BackendType) a b.
Backend backend =>
(a -> b)
-> AnnColumnCaseBoolExpField backend a
-> AnnColumnCaseBoolExpField backend b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a
-> AnnColumnCaseBoolExpField backend b
-> AnnColumnCaseBoolExpField backend a
$c<$ :: forall (backend :: BackendType) a b.
Backend backend =>
a
-> AnnColumnCaseBoolExpField backend b
-> AnnColumnCaseBoolExpField backend a
fmap :: (a -> b)
-> AnnColumnCaseBoolExpField backend a
-> AnnColumnCaseBoolExpField backend b
$cfmap :: forall (backend :: BackendType) a b.
Backend backend =>
(a -> b)
-> AnnColumnCaseBoolExpField backend a
-> AnnColumnCaseBoolExpField backend b
Functor, a -> AnnColumnCaseBoolExpField backend a -> Bool
AnnColumnCaseBoolExpField backend m -> m
AnnColumnCaseBoolExpField backend a -> [a]
AnnColumnCaseBoolExpField backend a -> Bool
AnnColumnCaseBoolExpField backend a -> Int
AnnColumnCaseBoolExpField backend a -> a
AnnColumnCaseBoolExpField backend a -> a
AnnColumnCaseBoolExpField backend a -> a
AnnColumnCaseBoolExpField backend a -> a
(a -> m) -> AnnColumnCaseBoolExpField backend a -> m
(a -> m) -> AnnColumnCaseBoolExpField backend a -> m
(a -> b -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
(a -> b -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
(b -> a -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
(b -> a -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
(a -> a -> a) -> AnnColumnCaseBoolExpField backend a -> a
(a -> a -> a) -> AnnColumnCaseBoolExpField backend a -> a
(forall m. Monoid m => AnnColumnCaseBoolExpField backend m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> AnnColumnCaseBoolExpField backend a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> AnnColumnCaseBoolExpField backend a -> m)
-> (forall a b.
(a -> b -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b)
-> (forall a b.
(a -> b -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b)
-> (forall b a.
(b -> a -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b)
-> (forall b a.
(b -> a -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b)
-> (forall a.
(a -> a -> a) -> AnnColumnCaseBoolExpField backend a -> a)
-> (forall a.
(a -> a -> a) -> AnnColumnCaseBoolExpField backend a -> a)
-> (forall a. AnnColumnCaseBoolExpField backend a -> [a])
-> (forall a. AnnColumnCaseBoolExpField backend a -> Bool)
-> (forall a. AnnColumnCaseBoolExpField backend a -> Int)
-> (forall a.
Eq a =>
a -> AnnColumnCaseBoolExpField backend a -> Bool)
-> (forall a. Ord a => AnnColumnCaseBoolExpField backend a -> a)
-> (forall a. Ord a => AnnColumnCaseBoolExpField backend a -> a)
-> (forall a. Num a => AnnColumnCaseBoolExpField backend a -> a)
-> (forall a. Num a => AnnColumnCaseBoolExpField backend a -> a)
-> Foldable (AnnColumnCaseBoolExpField backend)
forall a. Eq a => a -> AnnColumnCaseBoolExpField backend a -> Bool
forall a. Num a => AnnColumnCaseBoolExpField backend a -> a
forall a. Ord a => AnnColumnCaseBoolExpField backend a -> a
forall m. Monoid m => AnnColumnCaseBoolExpField backend m -> m
forall a. AnnColumnCaseBoolExpField backend a -> Bool
forall a. AnnColumnCaseBoolExpField backend a -> Int
forall a. AnnColumnCaseBoolExpField backend a -> [a]
forall a. (a -> a -> a) -> AnnColumnCaseBoolExpField backend a -> a
forall m a.
Monoid m =>
(a -> m) -> AnnColumnCaseBoolExpField backend a -> m
forall b a.
(b -> a -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
forall a b.
(a -> b -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
forall (backend :: BackendType) a.
(Backend backend, Eq a) =>
a -> AnnColumnCaseBoolExpField backend a -> Bool
forall (backend :: BackendType) a.
(Backend backend, Num a) =>
AnnColumnCaseBoolExpField backend a -> a
forall (backend :: BackendType) a.
(Backend backend, Ord a) =>
AnnColumnCaseBoolExpField backend a -> a
forall (backend :: BackendType) m.
(Backend backend, Monoid m) =>
AnnColumnCaseBoolExpField backend m -> m
forall (backend :: BackendType) a.
Backend backend =>
AnnColumnCaseBoolExpField backend a -> Bool
forall (backend :: BackendType) a.
Backend backend =>
AnnColumnCaseBoolExpField backend a -> Int
forall (backend :: BackendType) a.
Backend backend =>
AnnColumnCaseBoolExpField backend a -> [a]
forall (backend :: BackendType) a.
Backend backend =>
(a -> a -> a) -> AnnColumnCaseBoolExpField backend a -> a
forall (backend :: BackendType) m a.
(Backend backend, Monoid m) =>
(a -> m) -> AnnColumnCaseBoolExpField backend a -> m
forall (backend :: BackendType) b a.
Backend backend =>
(b -> a -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
forall (backend :: BackendType) a b.
Backend backend =>
(a -> b -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: AnnColumnCaseBoolExpField backend a -> a
$cproduct :: forall (backend :: BackendType) a.
(Backend backend, Num a) =>
AnnColumnCaseBoolExpField backend a -> a
sum :: AnnColumnCaseBoolExpField backend a -> a
$csum :: forall (backend :: BackendType) a.
(Backend backend, Num a) =>
AnnColumnCaseBoolExpField backend a -> a
minimum :: AnnColumnCaseBoolExpField backend a -> a
$cminimum :: forall (backend :: BackendType) a.
(Backend backend, Ord a) =>
AnnColumnCaseBoolExpField backend a -> a
maximum :: AnnColumnCaseBoolExpField backend a -> a
$cmaximum :: forall (backend :: BackendType) a.
(Backend backend, Ord a) =>
AnnColumnCaseBoolExpField backend a -> a
elem :: a -> AnnColumnCaseBoolExpField backend a -> Bool
$celem :: forall (backend :: BackendType) a.
(Backend backend, Eq a) =>
a -> AnnColumnCaseBoolExpField backend a -> Bool
length :: AnnColumnCaseBoolExpField backend a -> Int
$clength :: forall (backend :: BackendType) a.
Backend backend =>
AnnColumnCaseBoolExpField backend a -> Int
null :: AnnColumnCaseBoolExpField backend a -> Bool
$cnull :: forall (backend :: BackendType) a.
Backend backend =>
AnnColumnCaseBoolExpField backend a -> Bool
toList :: AnnColumnCaseBoolExpField backend a -> [a]
$ctoList :: forall (backend :: BackendType) a.
Backend backend =>
AnnColumnCaseBoolExpField backend a -> [a]
foldl1 :: (a -> a -> a) -> AnnColumnCaseBoolExpField backend a -> a
$cfoldl1 :: forall (backend :: BackendType) a.
Backend backend =>
(a -> a -> a) -> AnnColumnCaseBoolExpField backend a -> a
foldr1 :: (a -> a -> a) -> AnnColumnCaseBoolExpField backend a -> a
$cfoldr1 :: forall (backend :: BackendType) a.
Backend backend =>
(a -> a -> a) -> AnnColumnCaseBoolExpField backend a -> a
foldl' :: (b -> a -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
$cfoldl' :: forall (backend :: BackendType) b a.
Backend backend =>
(b -> a -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
foldl :: (b -> a -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
$cfoldl :: forall (backend :: BackendType) b a.
Backend backend =>
(b -> a -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
foldr' :: (a -> b -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
$cfoldr' :: forall (backend :: BackendType) a b.
Backend backend =>
(a -> b -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
foldr :: (a -> b -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
$cfoldr :: forall (backend :: BackendType) a b.
Backend backend =>
(a -> b -> b) -> b -> AnnColumnCaseBoolExpField backend a -> b
foldMap' :: (a -> m) -> AnnColumnCaseBoolExpField backend a -> m
$cfoldMap' :: forall (backend :: BackendType) m a.
(Backend backend, Monoid m) =>
(a -> m) -> AnnColumnCaseBoolExpField backend a -> m
foldMap :: (a -> m) -> AnnColumnCaseBoolExpField backend a -> m
$cfoldMap :: forall (backend :: BackendType) m a.
(Backend backend, Monoid m) =>
(a -> m) -> AnnColumnCaseBoolExpField backend a -> m
fold :: AnnColumnCaseBoolExpField backend m -> m
$cfold :: forall (backend :: BackendType) m.
(Backend backend, Monoid m) =>
AnnColumnCaseBoolExpField backend m -> m
Foldable, Functor (AnnColumnCaseBoolExpField backend)
Foldable (AnnColumnCaseBoolExpField backend)
Functor (AnnColumnCaseBoolExpField backend)
-> Foldable (AnnColumnCaseBoolExpField backend)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> AnnColumnCaseBoolExpField backend a
-> f (AnnColumnCaseBoolExpField backend b))
-> (forall (f :: * -> *) a.
Applicative f =>
AnnColumnCaseBoolExpField backend (f a)
-> f (AnnColumnCaseBoolExpField backend a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> AnnColumnCaseBoolExpField backend a
-> m (AnnColumnCaseBoolExpField backend b))
-> (forall (m :: * -> *) a.
Monad m =>
AnnColumnCaseBoolExpField backend (m a)
-> m (AnnColumnCaseBoolExpField backend a))
-> Traversable (AnnColumnCaseBoolExpField backend)
(a -> f b)
-> AnnColumnCaseBoolExpField backend a
-> f (AnnColumnCaseBoolExpField backend b)
forall (backend :: BackendType).
Backend backend =>
Functor (AnnColumnCaseBoolExpField backend)
forall (backend :: BackendType).
Backend backend =>
Foldable (AnnColumnCaseBoolExpField backend)
forall (backend :: BackendType) (m :: * -> *) a.
(Backend backend, Monad m) =>
AnnColumnCaseBoolExpField backend (m a)
-> m (AnnColumnCaseBoolExpField backend a)
forall (backend :: BackendType) (f :: * -> *) a.
(Backend backend, Applicative f) =>
AnnColumnCaseBoolExpField backend (f a)
-> f (AnnColumnCaseBoolExpField backend a)
forall (backend :: BackendType) (m :: * -> *) a b.
(Backend backend, Monad m) =>
(a -> m b)
-> AnnColumnCaseBoolExpField backend a
-> m (AnnColumnCaseBoolExpField backend b)
forall (backend :: BackendType) (f :: * -> *) a b.
(Backend backend, Applicative f) =>
(a -> f b)
-> AnnColumnCaseBoolExpField backend a
-> f (AnnColumnCaseBoolExpField backend b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
AnnColumnCaseBoolExpField backend (m a)
-> m (AnnColumnCaseBoolExpField backend a)
forall (f :: * -> *) a.
Applicative f =>
AnnColumnCaseBoolExpField backend (f a)
-> f (AnnColumnCaseBoolExpField backend a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> AnnColumnCaseBoolExpField backend a
-> m (AnnColumnCaseBoolExpField backend b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> AnnColumnCaseBoolExpField backend a
-> f (AnnColumnCaseBoolExpField backend b)
sequence :: AnnColumnCaseBoolExpField backend (m a)
-> m (AnnColumnCaseBoolExpField backend a)
$csequence :: forall (backend :: BackendType) (m :: * -> *) a.
(Backend backend, Monad m) =>
AnnColumnCaseBoolExpField backend (m a)
-> m (AnnColumnCaseBoolExpField backend a)
mapM :: (a -> m b)
-> AnnColumnCaseBoolExpField backend a
-> m (AnnColumnCaseBoolExpField backend b)
$cmapM :: forall (backend :: BackendType) (m :: * -> *) a b.
(Backend backend, Monad m) =>
(a -> m b)
-> AnnColumnCaseBoolExpField backend a
-> m (AnnColumnCaseBoolExpField backend b)
sequenceA :: AnnColumnCaseBoolExpField backend (f a)
-> f (AnnColumnCaseBoolExpField backend a)
$csequenceA :: forall (backend :: BackendType) (f :: * -> *) a.
(Backend backend, Applicative f) =>
AnnColumnCaseBoolExpField backend (f a)
-> f (AnnColumnCaseBoolExpField backend a)
traverse :: (a -> f b)
-> AnnColumnCaseBoolExpField backend a
-> f (AnnColumnCaseBoolExpField backend b)
$ctraverse :: forall (backend :: BackendType) (f :: * -> *) a b.
(Backend backend, Applicative f) =>
(a -> f b)
-> AnnColumnCaseBoolExpField backend a
-> f (AnnColumnCaseBoolExpField backend b)
$cp2Traversable :: forall (backend :: BackendType).
Backend backend =>
Foldable (AnnColumnCaseBoolExpField backend)
$cp1Traversable :: forall (backend :: BackendType).
Backend backend =>
Functor (AnnColumnCaseBoolExpField backend)
Traversable, (forall x.
AnnColumnCaseBoolExpField backend field
-> Rep (AnnColumnCaseBoolExpField backend field) x)
-> (forall x.
Rep (AnnColumnCaseBoolExpField backend field) x
-> AnnColumnCaseBoolExpField backend field)
-> Generic (AnnColumnCaseBoolExpField backend field)
forall x.
Rep (AnnColumnCaseBoolExpField backend field) x
-> AnnColumnCaseBoolExpField backend field
forall x.
AnnColumnCaseBoolExpField backend field
-> Rep (AnnColumnCaseBoolExpField backend field) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (backend :: BackendType) field x.
Rep (AnnColumnCaseBoolExpField backend field) x
-> AnnColumnCaseBoolExpField backend field
forall (backend :: BackendType) field x.
AnnColumnCaseBoolExpField backend field
-> Rep (AnnColumnCaseBoolExpField backend field) x
$cto :: forall (backend :: BackendType) field x.
Rep (AnnColumnCaseBoolExpField backend field) x
-> AnnColumnCaseBoolExpField backend field
$cfrom :: forall (backend :: BackendType) field x.
AnnColumnCaseBoolExpField backend field
-> Rep (AnnColumnCaseBoolExpField backend field) x
Generic)
deriving instance
( Eq (AnnBoolExpFld b a)
) =>
Eq (AnnColumnCaseBoolExpField b a)
deriving instance
( Backend b,
Show (AnnBoolExpFld b a),
Show a
) =>
Show (AnnColumnCaseBoolExpField b a)
instance
( Backend b,
NFData (AnnBoolExpFld b a),
NFData a
) =>
NFData (AnnColumnCaseBoolExpField b a)
instance
( Backend b,
Cacheable (AnnBoolExpFld b a),
Cacheable a
) =>
Cacheable (AnnColumnCaseBoolExpField b a)
instance
( Backend b,
Hashable (AnnBoolExpFld b a),
Hashable a
) =>
Hashable (AnnColumnCaseBoolExpField b a)
instance
( ToJSONKeyValue (AnnBoolExpFld b a)
) =>
ToJSONKeyValue (AnnColumnCaseBoolExpField b a)
where
toJSONKeyValue :: AnnColumnCaseBoolExpField b a -> (Key, Value)
toJSONKeyValue = AnnBoolExpFld b a -> (Key, Value)
forall a. ToJSONKeyValue a => a -> (Key, Value)
toJSONKeyValue (AnnBoolExpFld b a -> (Key, Value))
-> (AnnColumnCaseBoolExpField b a -> AnnBoolExpFld b a)
-> AnnColumnCaseBoolExpField b a
-> (Key, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnnColumnCaseBoolExpField b a -> AnnBoolExpFld b a
forall (backend :: BackendType) field.
AnnColumnCaseBoolExpField backend field
-> AnnBoolExpFld backend field
_accColCaseBoolExpField
type AnnColumnCaseBoolExp b a = GBoolExp b (AnnColumnCaseBoolExpField b a)
type AnnColumnCaseBoolExpPartialSQL b = AnnColumnCaseBoolExp b (PartialSQLExp b)
type PreSetColsG b v = M.HashMap (Column b) v
type PreSetColsPartial b = M.HashMap (Column b) (PartialSQLExp b)