module Hasura.Backends.Postgres.DDL.BoolExp
( parseBoolExpOperations,
buildComputedFieldBooleanExp,
)
where
import Data.Aeson
import Data.Aeson.Key qualified as K
import Data.Aeson.KeyMap qualified as KM
import Data.HashMap.Strict qualified as HashMap
import Data.Text qualified as T
import Data.Text.Extended
import Hasura.Backends.Postgres.SQL.Types hiding (TableName)
import Hasura.Backends.Postgres.Types.BoolExp
import Hasura.Backends.Postgres.Types.ComputedField as PG
import Hasura.Base.Error
import Hasura.Function.Cache
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.BackendType
import Hasura.RQL.Types.BoolExp
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.ComputedField
import Hasura.RQL.Types.SchemaCache
import Hasura.SQL.Types
import Hasura.Table.Cache
parseBoolExpOperations ::
forall pgKind m v.
( Backend ('Postgres pgKind),
MonadError QErr m
) =>
ValueParser ('Postgres pgKind) m v ->
FieldInfoMap (FieldInfo ('Postgres pgKind)) ->
FieldInfoMap (FieldInfo ('Postgres pgKind)) ->
ColumnReference ('Postgres pgKind) ->
Value ->
m [OpExpG ('Postgres pgKind) v]
parseBoolExpOperations :: forall (pgKind :: PostgresKind) (m :: * -> *) v.
(Backend ('Postgres pgKind), MonadError QErr m) =>
ValueParser ('Postgres pgKind) m v
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
-> ColumnReference ('Postgres pgKind)
-> Value
-> m [OpExpG ('Postgres pgKind) v]
parseBoolExpOperations ValueParser ('Postgres pgKind) m v
rhsParser FieldInfoMap (FieldInfo ('Postgres pgKind))
rootFieldInfoMap FieldInfoMap (FieldInfo ('Postgres pgKind))
fim ColumnReference ('Postgres pgKind)
columnRef Value
value = do
m ()
restrictJSONColumn
Text
-> m [OpExpG ('Postgres pgKind) v]
-> m [OpExpG ('Postgres pgKind) v]
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK (ColumnReference ('Postgres pgKind) -> Text
forall a. ToTxt a => a -> Text
toTxt ColumnReference ('Postgres pgKind)
columnRef) (m [OpExpG ('Postgres pgKind) v]
-> m [OpExpG ('Postgres pgKind) v])
-> m [OpExpG ('Postgres pgKind) v]
-> m [OpExpG ('Postgres pgKind) v]
forall a b. (a -> b) -> a -> b
$ ColumnReference ('Postgres pgKind)
-> Value -> m [OpExpG ('Postgres pgKind) v]
parseOperations ColumnReference ('Postgres pgKind)
columnRef Value
value
where
restrictJSONColumn :: m ()
restrictJSONColumn :: m ()
restrictJSONColumn = case ColumnReference ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (backend :: BackendType).
ColumnReference backend -> ColumnType backend
columnReferenceType ColumnReference ('Postgres pgKind)
columnRef of
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGJSON ->
QErr -> m ()
forall a. QErr -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Code -> Text -> QErr
err400 Code
UnexpectedPayload Text
"JSON column can not be part of boolean expression")
ColumnType ('Postgres pgKind)
_ -> () -> m ()
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
parseOperations :: ColumnReference ('Postgres pgKind) -> Value -> m [OpExpG ('Postgres pgKind) v]
parseOperations :: ColumnReference ('Postgres pgKind)
-> Value -> m [OpExpG ('Postgres pgKind) v]
parseOperations ColumnReference ('Postgres pgKind)
column = \case
Object Object
o -> ((Key, Value) -> m (OpExpG ('Postgres pgKind) v))
-> [(Key, Value)] -> m [OpExpG ('Postgres pgKind) v]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (ColumnReference ('Postgres pgKind)
-> (Text, Value) -> m (OpExpG ('Postgres pgKind) v)
parseOperation ColumnReference ('Postgres pgKind)
column ((Text, Value) -> m (OpExpG ('Postgres pgKind) v))
-> ((Key, Value) -> (Text, Value))
-> (Key, Value)
-> m (OpExpG ('Postgres pgKind) v)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> Text) -> (Key, Value) -> (Text, Value)
forall b c d. (b -> c) -> (b, d) -> (c, d)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first Key -> Text
K.toText) (Object -> [(Key, Value)]
forall v. KeyMap v -> [(Key, v)]
KM.toList Object
o)
Value
val -> OpExpG ('Postgres pgKind) v -> [OpExpG ('Postgres pgKind) v]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (OpExpG ('Postgres pgKind) v -> [OpExpG ('Postgres pgKind) v])
-> (v -> OpExpG ('Postgres pgKind) v)
-> v
-> [OpExpG ('Postgres pgKind) v]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ComparisonNullability -> v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
ComparisonNullability -> field -> OpExpG backend field
AEQ ComparisonNullability
NullableComparison (v -> [OpExpG ('Postgres pgKind) v])
-> m v -> m [OpExpG ('Postgres pgKind) v]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ValueParser ('Postgres pgKind) m v
rhsParser CollectableType (ColumnType ('Postgres pgKind))
columnType Value
val
where
columnType :: CollectableType (ColumnType ('Postgres pgKind))
columnType = ColumnType ('Postgres pgKind)
-> CollectableType (ColumnType ('Postgres pgKind))
forall a. a -> CollectableType a
CollectableTypeScalar (ColumnType ('Postgres pgKind)
-> CollectableType (ColumnType ('Postgres pgKind)))
-> ColumnType ('Postgres pgKind)
-> CollectableType (ColumnType ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ ColumnReference ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (backend :: BackendType).
ColumnReference backend -> ColumnType backend
columnReferenceType ColumnReference ('Postgres pgKind)
column
parseOperation :: ColumnReference ('Postgres pgKind) -> (Text, Value) -> m (OpExpG ('Postgres pgKind) v)
parseOperation :: ColumnReference ('Postgres pgKind)
-> (Text, Value) -> m (OpExpG ('Postgres pgKind) v)
parseOperation ColumnReference ('Postgres pgKind)
column (Text
opStr, Value
val) = Text
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
opStr
(m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v))
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. (a -> b) -> a -> b
$ case Text
opStr of
Text
"$cast" -> m (OpExpG ('Postgres pgKind) v)
parseCast
Text
"_cast" -> m (OpExpG ('Postgres pgKind) v)
parseCast
Text
"$eq" -> m (OpExpG ('Postgres pgKind) v)
parseEq
Text
"_eq" -> m (OpExpG ('Postgres pgKind) v)
parseEq
Text
"$ne" -> m (OpExpG ('Postgres pgKind) v)
parseNe
Text
"_ne" -> m (OpExpG ('Postgres pgKind) v)
parseNe
Text
"$neq" -> m (OpExpG ('Postgres pgKind) v)
parseNe
Text
"_neq" -> m (OpExpG ('Postgres pgKind) v)
parseNe
Text
"$in" -> m (OpExpG ('Postgres pgKind) v)
parseIn
Text
"_in" -> m (OpExpG ('Postgres pgKind) v)
parseIn
Text
"$nin" -> m (OpExpG ('Postgres pgKind) v)
parseNin
Text
"_nin" -> m (OpExpG ('Postgres pgKind) v)
parseNin
Text
"$gt" -> m (OpExpG ('Postgres pgKind) v)
parseGt
Text
"_gt" -> m (OpExpG ('Postgres pgKind) v)
parseGt
Text
"$lt" -> m (OpExpG ('Postgres pgKind) v)
parseLt
Text
"_lt" -> m (OpExpG ('Postgres pgKind) v)
parseLt
Text
"$gte" -> m (OpExpG ('Postgres pgKind) v)
parseGte
Text
"_gte" -> m (OpExpG ('Postgres pgKind) v)
parseGte
Text
"$lte" -> m (OpExpG ('Postgres pgKind) v)
parseLte
Text
"_lte" -> m (OpExpG ('Postgres pgKind) v)
parseLte
Text
"$like" -> m (OpExpG ('Postgres pgKind) v)
parseLike
Text
"_like" -> m (OpExpG ('Postgres pgKind) v)
parseLike
Text
"$nlike" -> m (OpExpG ('Postgres pgKind) v)
parseNlike
Text
"_nlike" -> m (OpExpG ('Postgres pgKind) v)
parseNlike
Text
"$ilike" -> m (OpExpG ('Postgres pgKind) v)
parseIlike
Text
"_ilike" -> m (OpExpG ('Postgres pgKind) v)
parseIlike
Text
"$nilike" -> m (OpExpG ('Postgres pgKind) v)
parseNilike
Text
"_nilike" -> m (OpExpG ('Postgres pgKind) v)
parseNilike
Text
"$similar" -> m (OpExpG ('Postgres pgKind) v)
parseSimilar
Text
"_similar" -> m (OpExpG ('Postgres pgKind) v)
parseSimilar
Text
"$nsimilar" -> m (OpExpG ('Postgres pgKind) v)
parseNsimilar
Text
"_nsimilar" -> m (OpExpG ('Postgres pgKind) v)
parseNsimilar
Text
"$regex" -> m (OpExpG ('Postgres pgKind) v)
parseRegex
Text
"_regex" -> m (OpExpG ('Postgres pgKind) v)
parseRegex
Text
"$iregex" -> m (OpExpG ('Postgres pgKind) v)
parseIRegex
Text
"_iregex" -> m (OpExpG ('Postgres pgKind) v)
parseIRegex
Text
"$nregex" -> m (OpExpG ('Postgres pgKind) v)
parseNRegex
Text
"_nregex" -> m (OpExpG ('Postgres pgKind) v)
parseNRegex
Text
"$niregex" -> m (OpExpG ('Postgres pgKind) v)
parseNIRegex
Text
"_niregex" -> m (OpExpG ('Postgres pgKind) v)
parseNIRegex
Text
"$is_null" -> m (OpExpG ('Postgres pgKind) v)
parseIsNull
Text
"_is_null" -> m (OpExpG ('Postgres pgKind) v)
parseIsNull
Text
"_contains" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGJSONB] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AContains (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
Text
"$contains" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGJSONB] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AContains (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
Text
"_contained_in" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGJSONB] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AContainedIn (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
Text
"$contained_in" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGJSONB] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AContainedIn (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
Text
"_has_key" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGJSONB] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AHasKey (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseWithTy (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGText)
Text
"$has_key" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGJSONB] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AHasKey (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseWithTy (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGText)
Text
"_has_keys_any" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGJSONB] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AHasKeysAny (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseManyWithType (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGText)
Text
"$has_keys_any" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGJSONB] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AHasKeysAny (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseManyWithType (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGText)
Text
"_has_keys_all" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGJSONB] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AHasKeysAll (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseManyWithType (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGText)
Text
"$has_keys_all" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGJSONB] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AHasKeysAll (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseManyWithType (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGText)
Text
"_st_contains" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASTContains
Text
"$st_contains" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASTContains
Text
"_st_crosses" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASTCrosses
Text
"$st_crosses" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASTCrosses
Text
"_st_equals" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASTEquals
Text
"$st_equals" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASTEquals
Text
"_st_overlaps" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASTOverlaps
Text
"$st_overlaps" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASTOverlaps
Text
"_st_touches" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASTTouches
Text
"$st_touches" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASTTouches
Text
"_st_within" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASTWithin
Text
"$st_within" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASTWithin
Text
"_st_intersects" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOrGeographyOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASTIntersects
Text
"$st_intersects" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOrGeographyOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASTIntersects
Text
"_st_3d_intersects" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
AST3DIntersects
Text
"$st_3d_intersects" -> (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
forall a. a -> BooleanOperators a
AST3DIntersects
Text
"_st_d_within" -> m (OpExpG ('Postgres pgKind) v)
parseSTDWithinObj
Text
"$st_d_within" -> m (OpExpG ('Postgres pgKind) v)
parseSTDWithinObj
Text
"_st_3d_d_within" -> m (OpExpG ('Postgres pgKind) v)
parseST3DDWithinObj
Text
"$st_3d_d_within" -> m (OpExpG ('Postgres pgKind) v)
parseST3DDWithinObj
Text
"$ceq" -> m (OpExpG ('Postgres pgKind) v)
parseCeq
Text
"_ceq" -> m (OpExpG ('Postgres pgKind) v)
parseCeq
Text
"$cne" -> m (OpExpG ('Postgres pgKind) v)
parseCne
Text
"_cne" -> m (OpExpG ('Postgres pgKind) v)
parseCne
Text
"$cneq" -> m (OpExpG ('Postgres pgKind) v)
parseCne
Text
"_cneq" -> m (OpExpG ('Postgres pgKind) v)
parseCne
Text
"$cgt" -> m (OpExpG ('Postgres pgKind) v)
parseCgt
Text
"_cgt" -> m (OpExpG ('Postgres pgKind) v)
parseCgt
Text
"$clt" -> m (OpExpG ('Postgres pgKind) v)
parseClt
Text
"_clt" -> m (OpExpG ('Postgres pgKind) v)
parseClt
Text
"$cgte" -> m (OpExpG ('Postgres pgKind) v)
parseCgte
Text
"_cgte" -> m (OpExpG ('Postgres pgKind) v)
parseCgte
Text
"$clte" -> m (OpExpG ('Postgres pgKind) v)
parseClte
Text
"_clte" -> m (OpExpG ('Postgres pgKind) v)
parseClte
Text
"_ancestor" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGLtree] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AAncestor (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
Text
"$ancestor" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGLtree] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AAncestor (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
Text
"_ancestor_any" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGLtree] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AAncestorAny (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseManyWithType (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGLtree)
Text
"$ancestor_any" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGLtree] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AAncestorAny (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseManyWithType (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGLtree)
Text
"_descendant" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGLtree] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
ADescendant (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
Text
"$descendant" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGLtree] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
ADescendant (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
Text
"_descendant_any" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGLtree] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
ADescendantAny (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseManyWithType (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGLtree)
Text
"$descendant_any" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGLtree] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
ADescendantAny (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseManyWithType (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGLtree)
Text
"_matches" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGLtree] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AMatches (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseWithTy (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGLquery)
Text
"$matches" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGLtree] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AMatches (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseWithTy (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGLquery)
Text
"_matches_any" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGLtree] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AMatchesAny (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseManyWithType (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGLquery)
Text
"$matches_any" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGLtree] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AMatchesAny (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseManyWithType (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGLquery)
Text
"_matches_fulltext" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGLtree] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AMatchesFulltext (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseWithTy (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGLtxtquery)
Text
"$matches_fulltext" -> [PGScalarType] -> m ()
guardType [PGScalarType
PGLtree] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AMatchesFulltext (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseWithTy (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGLtxtquery)
Text
x -> Code -> Text -> m (OpExpG ('Postgres pgKind) v)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
UnexpectedPayload (Text -> m (OpExpG ('Postgres pgKind) v))
-> Text -> m (OpExpG ('Postgres pgKind) v)
forall a b. (a -> b) -> a -> b
$ Text
"Unknown operator: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
x
where
colTy :: ColumnType ('Postgres pgKind)
colTy = ColumnReference ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (backend :: BackendType).
ColumnReference backend -> ColumnType backend
columnReferenceType ColumnReference ('Postgres pgKind)
column
colNonNullable :: ComparisonNullability
colNonNullable = case Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
True (Maybe Bool -> Bool) -> Maybe Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ColumnReference ('Postgres pgKind) -> Maybe Bool
forall (b :: BackendType). ColumnReference b -> Maybe Bool
columnReferenceNullable ColumnReference ('Postgres pgKind)
column of
Bool
True -> ComparisonNullability
NullableComparison
Bool
False -> ComparisonNullability
NonNullableComparison
parseIsNull :: m (OpExpG ('Postgres pgKind) v)
parseIsNull = OpExpG ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
-> Bool
-> OpExpG ('Postgres pgKind) v
forall a. a -> a -> Bool -> a
bool OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field. OpExpG backend field
ANISNOTNULL OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field. OpExpG backend field
ANISNULL (Bool -> OpExpG ('Postgres pgKind) v)
-> m Bool -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m Bool
forall a. FromJSON a => m a
parseVal
parseEq :: m (OpExpG ('Postgres pgKind) v)
parseEq = ComparisonNullability -> v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
ComparisonNullability -> field -> OpExpG backend field
AEQ ComparisonNullability
colNonNullable (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseNe :: m (OpExpG ('Postgres pgKind) v)
parseNe = ComparisonNullability -> v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
ComparisonNullability -> field -> OpExpG backend field
ANE ComparisonNullability
colNonNullable (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseIn :: m (OpExpG ('Postgres pgKind) v)
parseIn = v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
field -> OpExpG backend field
AIN (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseManyWithType ColumnType ('Postgres pgKind)
colTy
parseNin :: m (OpExpG ('Postgres pgKind) v)
parseNin = v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
field -> OpExpG backend field
ANIN (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> m v
parseManyWithType ColumnType ('Postgres pgKind)
colTy
parseGt :: m (OpExpG ('Postgres pgKind) v)
parseGt = v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
field -> OpExpG backend field
AGT (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseLt :: m (OpExpG ('Postgres pgKind) v)
parseLt = v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
field -> OpExpG backend field
ALT (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseGte :: m (OpExpG ('Postgres pgKind) v)
parseGte = v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
field -> OpExpG backend field
AGTE (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseLte :: m (OpExpG ('Postgres pgKind) v)
parseLte = v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
field -> OpExpG backend field
ALTE (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseCeq :: m (OpExpG ('Postgres pgKind) v)
parseCeq = RootOrCurrentColumn ('Postgres pgKind)
-> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
RootOrCurrentColumn backend -> OpExpG backend field
CEQ (RootOrCurrentColumn ('Postgres pgKind)
-> OpExpG ('Postgres pgKind) v)
-> m (RootOrCurrentColumn ('Postgres pgKind))
-> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> m (RootOrCurrentColumn ('Postgres pgKind))
decodeAndValidateRhsCol Value
val
parseCne :: m (OpExpG ('Postgres pgKind) v)
parseCne = RootOrCurrentColumn ('Postgres pgKind)
-> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
RootOrCurrentColumn backend -> OpExpG backend field
CNE (RootOrCurrentColumn ('Postgres pgKind)
-> OpExpG ('Postgres pgKind) v)
-> m (RootOrCurrentColumn ('Postgres pgKind))
-> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> m (RootOrCurrentColumn ('Postgres pgKind))
decodeAndValidateRhsCol Value
val
parseCgt :: m (OpExpG ('Postgres pgKind) v)
parseCgt = RootOrCurrentColumn ('Postgres pgKind)
-> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
RootOrCurrentColumn backend -> OpExpG backend field
CGT (RootOrCurrentColumn ('Postgres pgKind)
-> OpExpG ('Postgres pgKind) v)
-> m (RootOrCurrentColumn ('Postgres pgKind))
-> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> m (RootOrCurrentColumn ('Postgres pgKind))
decodeAndValidateRhsCol Value
val
parseClt :: m (OpExpG ('Postgres pgKind) v)
parseClt = RootOrCurrentColumn ('Postgres pgKind)
-> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
RootOrCurrentColumn backend -> OpExpG backend field
CLT (RootOrCurrentColumn ('Postgres pgKind)
-> OpExpG ('Postgres pgKind) v)
-> m (RootOrCurrentColumn ('Postgres pgKind))
-> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> m (RootOrCurrentColumn ('Postgres pgKind))
decodeAndValidateRhsCol Value
val
parseCgte :: m (OpExpG ('Postgres pgKind) v)
parseCgte = RootOrCurrentColumn ('Postgres pgKind)
-> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
RootOrCurrentColumn backend -> OpExpG backend field
CGTE (RootOrCurrentColumn ('Postgres pgKind)
-> OpExpG ('Postgres pgKind) v)
-> m (RootOrCurrentColumn ('Postgres pgKind))
-> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> m (RootOrCurrentColumn ('Postgres pgKind))
decodeAndValidateRhsCol Value
val
parseClte :: m (OpExpG ('Postgres pgKind) v)
parseClte = RootOrCurrentColumn ('Postgres pgKind)
-> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
RootOrCurrentColumn backend -> OpExpG backend field
CLTE (RootOrCurrentColumn ('Postgres pgKind)
-> OpExpG ('Postgres pgKind) v)
-> m (RootOrCurrentColumn ('Postgres pgKind))
-> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> m (RootOrCurrentColumn ('Postgres pgKind))
decodeAndValidateRhsCol Value
val
parseLike :: m (OpExpG ('Postgres pgKind) v)
parseLike = [PGScalarType] -> m ()
guardType [PGScalarType]
stringTypes m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
field -> OpExpG backend field
ALIKE (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseNlike :: m (OpExpG ('Postgres pgKind) v)
parseNlike = [PGScalarType] -> m ()
guardType [PGScalarType]
stringTypes m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
field -> OpExpG backend field
ANLIKE (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseIlike :: m (OpExpG ('Postgres pgKind) v)
parseIlike = [PGScalarType] -> m ()
guardType [PGScalarType]
stringTypes m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AILIKE (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseNilike :: m (OpExpG ('Postgres pgKind) v)
parseNilike = [PGScalarType] -> m ()
guardType [PGScalarType]
stringTypes m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
ANILIKE (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseRegex :: m (OpExpG ('Postgres pgKind) v)
parseRegex = [PGScalarType] -> m ()
guardType [PGScalarType]
stringTypes m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AREGEX (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseIRegex :: m (OpExpG ('Postgres pgKind) v)
parseIRegex = [PGScalarType] -> m ()
guardType [PGScalarType]
stringTypes m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
AIREGEX (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseNRegex :: m (OpExpG ('Postgres pgKind) v)
parseNRegex = [PGScalarType] -> m ()
guardType [PGScalarType]
stringTypes m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
ANREGEX (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseNIRegex :: m (OpExpG ('Postgres pgKind) v)
parseNIRegex = [PGScalarType] -> m ()
guardType [PGScalarType]
stringTypes m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
ANIREGEX (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseSimilar :: m (OpExpG ('Postgres pgKind) v)
parseSimilar = [PGScalarType] -> m ()
guardType [PGScalarType]
stringTypes m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
ASIMILAR (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseNsimilar :: m (OpExpG ('Postgres pgKind) v)
parseNsimilar = [PGScalarType] -> m ()
guardType [PGScalarType]
stringTypes m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
forall a. a -> BooleanOperators a
ANSIMILAR (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m v
parseOne
parseCast :: m (OpExpG ('Postgres pgKind) v)
parseCast = do
HashMap Text Value
castOperations <- m (HashMap Text Value)
forall a. FromJSON a => m a
parseVal
[(PGScalarType, [OpExpG ('Postgres pgKind) v])]
parsedCastOperations <-
[(Text, Value)]
-> ((Text, Value)
-> m (PGScalarType, [OpExpG ('Postgres pgKind) v]))
-> m [(PGScalarType, [OpExpG ('Postgres pgKind) v])]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (HashMap Text Value -> [(Text, Value)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList HashMap Text Value
castOperations) (((Text, Value) -> m (PGScalarType, [OpExpG ('Postgres pgKind) v]))
-> m [(PGScalarType, [OpExpG ('Postgres pgKind) v])])
-> ((Text, Value)
-> m (PGScalarType, [OpExpG ('Postgres pgKind) v]))
-> m [(PGScalarType, [OpExpG ('Postgres pgKind) v])]
forall a b. (a -> b) -> a -> b
$ \(Text
targetTypeName, Value
castedComparisons) -> do
let targetType :: PGScalarType
targetType = Text -> PGScalarType
textToPGScalarType Text
targetTypeName
castedColumn :: ColumnReference ('Postgres pgKind)
castedColumn = ColumnReference ('Postgres pgKind)
-> ColumnType ('Postgres pgKind)
-> ColumnReference ('Postgres pgKind)
forall (b :: BackendType).
ColumnReference b -> ColumnType b -> ColumnReference b
ColumnReferenceCast ColumnReference ('Postgres pgKind)
column (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
targetType)
PGScalarType -> m ()
checkValidCast PGScalarType
targetType
[OpExpG ('Postgres pgKind) v]
parsedCastedComparisons <-
Text
-> m [OpExpG ('Postgres pgKind) v]
-> m [OpExpG ('Postgres pgKind) v]
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
targetTypeName
(m [OpExpG ('Postgres pgKind) v]
-> m [OpExpG ('Postgres pgKind) v])
-> m [OpExpG ('Postgres pgKind) v]
-> m [OpExpG ('Postgres pgKind) v]
forall a b. (a -> b) -> a -> b
$ ColumnReference ('Postgres pgKind)
-> Value -> m [OpExpG ('Postgres pgKind) v]
parseOperations ColumnReference ('Postgres pgKind)
castedColumn Value
castedComparisons
(PGScalarType, [OpExpG ('Postgres pgKind) v])
-> m (PGScalarType, [OpExpG ('Postgres pgKind) v])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (PGScalarType
targetType, [OpExpG ('Postgres pgKind) v]
parsedCastedComparisons)
OpExpG ('Postgres pgKind) v -> m (OpExpG ('Postgres pgKind) v)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (OpExpG ('Postgres pgKind) v -> m (OpExpG ('Postgres pgKind) v))
-> (HashMap PGScalarType [OpExpG ('Postgres pgKind) v]
-> OpExpG ('Postgres pgKind) v)
-> HashMap PGScalarType [OpExpG ('Postgres pgKind) v]
-> m (OpExpG ('Postgres pgKind) v)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CastExp ('Postgres pgKind) v -> OpExpG ('Postgres pgKind) v
HashMap PGScalarType [OpExpG ('Postgres pgKind) v]
-> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
CastExp backend field -> OpExpG backend field
ACast (HashMap PGScalarType [OpExpG ('Postgres pgKind) v]
-> m (OpExpG ('Postgres pgKind) v))
-> HashMap PGScalarType [OpExpG ('Postgres pgKind) v]
-> m (OpExpG ('Postgres pgKind) v)
forall a b. (a -> b) -> a -> b
$ [(PGScalarType, [OpExpG ('Postgres pgKind) v])]
-> HashMap PGScalarType [OpExpG ('Postgres pgKind) v]
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList [(PGScalarType, [OpExpG ('Postgres pgKind) v])]
parsedCastOperations
checkValidCast :: PGScalarType -> m ()
checkValidCast PGScalarType
targetType = case (ColumnType ('Postgres pgKind)
colTy, PGScalarType
targetType) of
(ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGGeometry, PGScalarType
PGGeography) -> () -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
(ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGGeography, PGScalarType
PGGeometry) -> () -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
(ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGJSONB, PGScalarType
PGText) -> () -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
(ColumnType ('Postgres pgKind), PGScalarType)
_ ->
Code -> Text -> m ()
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
UnexpectedPayload
(Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ Text
"cannot cast column of type "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ColumnType ('Postgres pgKind)
colTy
ColumnType ('Postgres pgKind) -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" to type "
Text -> PGScalarType -> Text
forall t. ToTxt t => Text -> t -> Text
<>> PGScalarType
targetType
parseGeometryOp :: (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOp v -> BooleanOperators v
f =
[PGScalarType] -> m ()
guardType [PGScalarType
PGGeometry] m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
f (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> Value -> m v
parseOneNoSess ColumnType ('Postgres pgKind)
colTy Value
val
parseGeometryOrGeographyOp :: (v -> BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
parseGeometryOrGeographyOp v -> BooleanOperators v
f =
[PGScalarType] -> m ()
guardType [PGScalarType]
geoTypes m ()
-> m (OpExpG ('Postgres pgKind) v)
-> m (OpExpG ('Postgres pgKind) v)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> (v -> BooleanOperators v) -> v -> OpExpG ('Postgres pgKind) v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> BooleanOperators v
f (v -> OpExpG ('Postgres pgKind) v)
-> m v -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind) -> Value -> m v
parseOneNoSess ColumnType ('Postgres pgKind)
colTy Value
val
parseSTDWithinObj :: m (OpExpG ('Postgres pgKind) v)
parseSTDWithinObj =
BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> m (BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case ColumnType ('Postgres pgKind)
colTy of
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGGeometry -> do
DWithinGeomOp Value
distVal Value
fromVal <- m (DWithinGeomOp Value)
forall a. FromJSON a => m a
parseVal
v
dist <- Text -> m v -> m v
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"distance" (m v -> m v) -> m v -> m v
forall a b. (a -> b) -> a -> b
$ ColumnType ('Postgres pgKind) -> Value -> m v
parseOneNoSess (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGFloat) Value
distVal
v
from <- Text -> m v -> m v
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"from" (m v -> m v) -> m v -> m v
forall a b. (a -> b) -> a -> b
$ ColumnType ('Postgres pgKind) -> Value -> m v
parseOneNoSess ColumnType ('Postgres pgKind)
colTy Value
fromVal
BooleanOperators v -> m (BooleanOperators v)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (BooleanOperators v -> m (BooleanOperators v))
-> BooleanOperators v -> m (BooleanOperators v)
forall a b. (a -> b) -> a -> b
$ DWithinGeomOp v -> BooleanOperators v
forall a. DWithinGeomOp a -> BooleanOperators a
ASTDWithinGeom (DWithinGeomOp v -> BooleanOperators v)
-> DWithinGeomOp v -> BooleanOperators v
forall a b. (a -> b) -> a -> b
$ v -> v -> DWithinGeomOp v
forall field. field -> field -> DWithinGeomOp field
DWithinGeomOp v
dist v
from
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGGeography -> do
DWithinGeogOp Value
distVal Value
fromVal Value
sphVal <- m (DWithinGeogOp Value)
forall a. FromJSON a => m a
parseVal
v
dist <- Text -> m v -> m v
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"distance" (m v -> m v) -> m v -> m v
forall a b. (a -> b) -> a -> b
$ ColumnType ('Postgres pgKind) -> Value -> m v
parseOneNoSess (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGFloat) Value
distVal
v
from <- Text -> m v -> m v
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"from" (m v -> m v) -> m v -> m v
forall a b. (a -> b) -> a -> b
$ ColumnType ('Postgres pgKind) -> Value -> m v
parseOneNoSess ColumnType ('Postgres pgKind)
colTy Value
fromVal
v
useSpheroid <- Text -> m v -> m v
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"use_spheroid" (m v -> m v) -> m v -> m v
forall a b. (a -> b) -> a -> b
$ ColumnType ('Postgres pgKind) -> Value -> m v
parseOneNoSess (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGBoolean) Value
sphVal
BooleanOperators v -> m (BooleanOperators v)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (BooleanOperators v -> m (BooleanOperators v))
-> BooleanOperators v -> m (BooleanOperators v)
forall a b. (a -> b) -> a -> b
$ DWithinGeogOp v -> BooleanOperators v
forall a. DWithinGeogOp a -> BooleanOperators a
ASTDWithinGeog (DWithinGeogOp v -> BooleanOperators v)
-> DWithinGeogOp v -> BooleanOperators v
forall a b. (a -> b) -> a -> b
$ v -> v -> v -> DWithinGeogOp v
forall field. field -> field -> field -> DWithinGeogOp field
DWithinGeogOp v
dist v
from v
useSpheroid
ColumnType ('Postgres pgKind)
_ -> QErr -> m (BooleanOperators v)
forall a. QErr -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (QErr -> m (BooleanOperators v)) -> QErr -> m (BooleanOperators v)
forall a b. (a -> b) -> a -> b
$ ColumnType ('Postgres pgKind) -> [PGScalarType] -> QErr
forall {t} {a}. (ToTxt t, ToTxt a) => t -> [a] -> QErr
buildMsg ColumnType ('Postgres pgKind)
colTy [PGScalarType
PGGeometry, PGScalarType
PGGeography]
decodeAndValidateRhsCol :: Value -> m (RootOrCurrentColumn ('Postgres pgKind))
decodeAndValidateRhsCol :: Value -> m (RootOrCurrentColumn ('Postgres pgKind))
decodeAndValidateRhsCol Value
v = case Value
v of
String Text
_ -> RootOrCurrent
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
-> Value
-> m (RootOrCurrentColumn ('Postgres pgKind))
go RootOrCurrent
IsCurrent FieldInfoMap (FieldInfo ('Postgres pgKind))
fim Value
v
Array Array
path -> case Array -> [Value]
forall a. Vector a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Array
path of
[] -> Code -> Text -> m (RootOrCurrentColumn ('Postgres pgKind))
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
Unexpected Text
"path cannot be empty"
[Value
col] -> RootOrCurrent
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
-> Value
-> m (RootOrCurrentColumn ('Postgres pgKind))
go RootOrCurrent
IsCurrent FieldInfoMap (FieldInfo ('Postgres pgKind))
fim Value
col
[String Text
"$", Value
col] -> do
RootOrCurrent
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
-> Value
-> m (RootOrCurrentColumn ('Postgres pgKind))
go RootOrCurrent
IsRoot FieldInfoMap (FieldInfo ('Postgres pgKind))
rootFieldInfoMap Value
col
[Value]
_ -> Code -> Text -> m (RootOrCurrentColumn ('Postgres pgKind))
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotSupported Text
"Relationship references are not supported in column comparison RHS"
Value
_ -> Code -> Text -> m (RootOrCurrentColumn ('Postgres pgKind))
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
Unexpected Text
"a boolean expression JSON must be either a string or an array"
where
go :: RootOrCurrent
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
-> Value
-> m (RootOrCurrentColumn ('Postgres pgKind))
go RootOrCurrent
rootInfo FieldInfoMap (FieldInfo ('Postgres pgKind))
fieldsInfoMap Value
columnValue = do
PGCol
colName <- Value -> m PGCol
forall a (m :: * -> *). (FromJSON a, QErrM m) => Value -> m a
decodeValue Value
columnValue
PGCol
colInfo <- FieldInfoMap (FieldInfo ('Postgres pgKind)) -> PGCol -> m PGCol
validateRhsCol FieldInfoMap (FieldInfo ('Postgres pgKind))
fieldsInfoMap PGCol
colName
RootOrCurrentColumn ('Postgres pgKind)
-> m (RootOrCurrentColumn ('Postgres pgKind))
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RootOrCurrentColumn ('Postgres pgKind)
-> m (RootOrCurrentColumn ('Postgres pgKind)))
-> RootOrCurrentColumn ('Postgres pgKind)
-> m (RootOrCurrentColumn ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ RootOrCurrent
-> Column ('Postgres pgKind)
-> RootOrCurrentColumn ('Postgres pgKind)
forall (b :: BackendType).
RootOrCurrent -> Column b -> RootOrCurrentColumn b
RootOrCurrentColumn RootOrCurrent
rootInfo Column ('Postgres pgKind)
PGCol
colInfo
parseST3DDWithinObj :: m (OpExpG ('Postgres pgKind) v)
parseST3DDWithinObj =
BooleanOperators ('Postgres pgKind) v
-> OpExpG ('Postgres pgKind) v
BooleanOperators v -> OpExpG ('Postgres pgKind) v
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators v -> OpExpG ('Postgres pgKind) v)
-> m (BooleanOperators v) -> m (OpExpG ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
[PGScalarType] -> m ()
guardType [PGScalarType
PGGeometry]
DWithinGeomOp Value
distVal Value
fromVal <- m (DWithinGeomOp Value)
forall a. FromJSON a => m a
parseVal
v
dist <- Text -> m v -> m v
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"distance" (m v -> m v) -> m v -> m v
forall a b. (a -> b) -> a -> b
$ ColumnType ('Postgres pgKind) -> Value -> m v
parseOneNoSess (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGFloat) Value
distVal
v
from <- Text -> m v -> m v
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"from" (m v -> m v) -> m v -> m v
forall a b. (a -> b) -> a -> b
$ ColumnType ('Postgres pgKind) -> Value -> m v
parseOneNoSess ColumnType ('Postgres pgKind)
colTy Value
fromVal
BooleanOperators v -> m (BooleanOperators v)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (BooleanOperators v -> m (BooleanOperators v))
-> BooleanOperators v -> m (BooleanOperators v)
forall a b. (a -> b) -> a -> b
$ DWithinGeomOp v -> BooleanOperators v
forall a. DWithinGeomOp a -> BooleanOperators a
AST3DDWithinGeom (DWithinGeomOp v -> BooleanOperators v)
-> DWithinGeomOp v -> BooleanOperators v
forall a b. (a -> b) -> a -> b
$ v -> v -> DWithinGeomOp v
forall field. field -> field -> DWithinGeomOp field
DWithinGeomOp v
dist v
from
validateRhsCol :: FieldInfoMap (FieldInfo ('Postgres pgKind)) -> PGCol -> m PGCol
validateRhsCol FieldInfoMap (FieldInfo ('Postgres pgKind))
fieldInfoMap PGCol
rhsCol = do
ColumnType ('Postgres pgKind)
rhsType <- FieldInfoMap (FieldInfo ('Postgres pgKind))
-> Column ('Postgres pgKind)
-> Text
-> m (ColumnType ('Postgres pgKind))
forall (m :: * -> *) (backend :: BackendType).
(MonadError QErr m, Backend backend) =>
FieldInfoMap (FieldInfo backend)
-> Column backend -> Text -> m (ColumnType backend)
askColumnType FieldInfoMap (FieldInfo ('Postgres pgKind))
fieldInfoMap Column ('Postgres pgKind)
PGCol
rhsCol Text
"column operators can only compare postgres columns"
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ColumnType ('Postgres pgKind)
colTy ColumnType ('Postgres pgKind)
-> ColumnType ('Postgres pgKind) -> Bool
forall a. Eq a => a -> a -> Bool
/= ColumnType ('Postgres pgKind)
rhsType)
(m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ Code -> Text -> m ()
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
UnexpectedPayload
(Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ Text
"incompatible column types: "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ColumnReference ('Postgres pgKind)
column
ColumnReference ('Postgres pgKind) -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" has type "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ColumnType ('Postgres pgKind)
colTy
ColumnType ('Postgres pgKind) -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
", but "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> PGCol
rhsCol
PGCol -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" has type "
Text -> ColumnType ('Postgres pgKind) -> Text
forall t. ToTxt t => Text -> t -> Text
<>> ColumnType ('Postgres pgKind)
rhsType
PGCol -> m PGCol
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure PGCol
rhsCol
parseWithTy :: ColumnType ('Postgres pgKind) -> m v
parseWithTy ColumnType ('Postgres pgKind)
ty = ValueParser ('Postgres pgKind) m v
rhsParser (ColumnType ('Postgres pgKind)
-> CollectableType (ColumnType ('Postgres pgKind))
forall a. a -> CollectableType a
CollectableTypeScalar ColumnType ('Postgres pgKind)
ty) Value
val
parseOne :: m v
parseOne = ColumnType ('Postgres pgKind) -> m v
parseWithTy ColumnType ('Postgres pgKind)
colTy
parseOneNoSess :: ColumnType ('Postgres pgKind) -> Value -> m v
parseOneNoSess ColumnType ('Postgres pgKind)
ty = ValueParser ('Postgres pgKind) m v
rhsParser (ColumnType ('Postgres pgKind)
-> CollectableType (ColumnType ('Postgres pgKind))
forall a. a -> CollectableType a
CollectableTypeScalar ColumnType ('Postgres pgKind)
ty)
parseManyWithType :: ColumnType ('Postgres pgKind) -> m v
parseManyWithType ColumnType ('Postgres pgKind)
ty = ValueParser ('Postgres pgKind) m v
rhsParser (ColumnType ('Postgres pgKind)
-> CollectableType (ColumnType ('Postgres pgKind))
forall a. a -> CollectableType a
CollectableTypeArray ColumnType ('Postgres pgKind)
ty) Value
val
guardType :: [PGScalarType] -> m ()
guardType [PGScalarType]
validTys =
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((ScalarType ('Postgres pgKind) -> Bool)
-> ColumnType ('Postgres pgKind) -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (ScalarType ('Postgres pgKind)
-> [ScalarType ('Postgres pgKind)] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ScalarType ('Postgres pgKind)]
[PGScalarType]
validTys) ColumnType ('Postgres pgKind)
colTy)
(m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ QErr -> m ()
forall a. QErr -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError
(QErr -> m ()) -> QErr -> m ()
forall a b. (a -> b) -> a -> b
$ ColumnType ('Postgres pgKind) -> [PGScalarType] -> QErr
forall {t} {a}. (ToTxt t, ToTxt a) => t -> [a] -> QErr
buildMsg ColumnType ('Postgres pgKind)
colTy [PGScalarType]
validTys
buildMsg :: t -> [a] -> QErr
buildMsg t
ty [a]
expTys =
Code -> Text -> QErr
err400 Code
UnexpectedPayload
(Text -> QErr) -> Text -> QErr
forall a b. (a -> b) -> a -> b
$ Text
" is of type "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> t
ty
t -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
"; this operator works only on columns of type "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
"/" ((a -> Text) -> [a] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map a -> Text
forall a. ToTxt a => a -> Text
dquote [a]
expTys)
parseVal :: (FromJSON a) => m a
parseVal :: forall a. FromJSON a => m a
parseVal = Value -> m a
forall a (m :: * -> *). (FromJSON a, QErrM m) => Value -> m a
decodeValue Value
val
buildComputedFieldBooleanExp ::
forall pgKind m v.
( MonadError QErr m,
Backend ('Postgres pgKind),
TableCoreInfoRM ('Postgres pgKind) m
) =>
BoolExpResolver ('Postgres pgKind) m v ->
BoolExpRHSParser ('Postgres pgKind) m v ->
FieldInfoMap (FieldInfo ('Postgres pgKind)) ->
FieldInfoMap (FieldInfo ('Postgres pgKind)) ->
ComputedFieldInfo ('Postgres pgKind) ->
Value ->
m (AnnComputedFieldBoolExp ('Postgres pgKind) v)
buildComputedFieldBooleanExp :: forall (pgKind :: PostgresKind) (m :: * -> *) v.
(MonadError QErr m, Backend ('Postgres pgKind),
TableCoreInfoRM ('Postgres pgKind) m) =>
BoolExpResolver ('Postgres pgKind) m v
-> BoolExpRHSParser ('Postgres pgKind) m v
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
-> ComputedFieldInfo ('Postgres pgKind)
-> Value
-> m (AnnComputedFieldBoolExp ('Postgres pgKind) v)
buildComputedFieldBooleanExp BoolExpResolver ('Postgres pgKind) m v
boolExpResolver BoolExpRHSParser ('Postgres pgKind) m v
rhsParser FieldInfoMap (FieldInfo ('Postgres pgKind))
rootFieldInfoMap FieldInfoMap (FieldInfo ('Postgres pgKind))
colInfoMap ComputedFieldInfo {Maybe Text
ComputedFieldName
ComputedFieldReturn ('Postgres pgKind)
XComputedField ('Postgres pgKind)
ComputedFieldFunction ('Postgres pgKind)
_cfiXComputedFieldInfo :: XComputedField ('Postgres pgKind)
_cfiName :: ComputedFieldName
_cfiFunction :: ComputedFieldFunction ('Postgres pgKind)
_cfiReturnType :: ComputedFieldReturn ('Postgres pgKind)
_cfiDescription :: Maybe Text
_cfiXComputedFieldInfo :: forall (b :: BackendType). ComputedFieldInfo b -> XComputedField b
_cfiName :: forall (b :: BackendType). ComputedFieldInfo b -> ComputedFieldName
_cfiFunction :: forall (b :: BackendType).
ComputedFieldInfo b -> ComputedFieldFunction b
_cfiReturnType :: forall (b :: BackendType).
ComputedFieldInfo b -> ComputedFieldReturn b
_cfiDescription :: forall (b :: BackendType). ComputedFieldInfo b -> Maybe Text
..} Value
colVal = do
let ComputedFieldFunction {Maybe PGDescription
Seq (FunctionArgument ('Postgres pgKind))
FunctionName ('Postgres pgKind)
ComputedFieldImplicitArguments ('Postgres pgKind)
_cffName :: FunctionName ('Postgres pgKind)
_cffInputArgs :: Seq (FunctionArgument ('Postgres pgKind))
_cffComputedFieldImplicitArgs :: ComputedFieldImplicitArguments ('Postgres pgKind)
_cffDescription :: Maybe PGDescription
_cffName :: forall (b :: BackendType).
ComputedFieldFunction b -> FunctionName b
_cffInputArgs :: forall (b :: BackendType).
ComputedFieldFunction b -> Seq (FunctionArgument b)
_cffComputedFieldImplicitArgs :: forall (b :: BackendType).
ComputedFieldFunction b -> ComputedFieldImplicitArguments b
_cffDescription :: forall (b :: BackendType).
ComputedFieldFunction b -> Maybe PGDescription
..} = ComputedFieldFunction ('Postgres pgKind)
_cfiFunction
case Seq FunctionArg -> [FunctionArg]
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Seq (FunctionArgument ('Postgres pgKind))
Seq FunctionArg
_cffInputArgs of
[] -> do
let hasuraSession :: v
hasuraSession = BoolExpRHSParser ('Postgres pgKind) m v -> v
forall (b :: BackendType) (m :: * -> *) v.
BoolExpRHSParser b m v -> v
_berpSessionValue BoolExpRHSParser ('Postgres pgKind) m v
rhsParser
computedFieldFunctionArgs :: FunctionArgsExpG (ArgumentExp v)
computedFieldFunctionArgs = ([ArgumentExp v]
-> HashMap Text (ArgumentExp v)
-> FunctionArgsExpG (ArgumentExp v))
-> HashMap Text (ArgumentExp v)
-> [ArgumentExp v]
-> FunctionArgsExpG (ArgumentExp v)
forall a b c. (a -> b -> c) -> b -> a -> c
flip [ArgumentExp v]
-> HashMap Text (ArgumentExp v) -> FunctionArgsExpG (ArgumentExp v)
forall a. [a] -> HashMap Text a -> FunctionArgsExpG a
FunctionArgsExp HashMap Text (ArgumentExp v)
forall a. Monoid a => a
mempty ([ArgumentExp v] -> FunctionArgsExpG (ArgumentExp v))
-> [ArgumentExp v] -> FunctionArgsExpG (ArgumentExp v)
forall a b. (a -> b) -> a -> b
$ v -> ComputedFieldImplicitArguments -> [ArgumentExp v]
forall v. v -> ComputedFieldImplicitArguments -> [ArgumentExp v]
PG.fromComputedFieldImplicitArguments v
hasuraSession ComputedFieldImplicitArguments ('Postgres pgKind)
ComputedFieldImplicitArguments
_cffComputedFieldImplicitArgs
XComputedField ('Postgres pgKind)
-> ComputedFieldName
-> FunctionName ('Postgres pgKind)
-> FunctionArgsExp ('Postgres pgKind) v
-> ComputedFieldBoolExp ('Postgres pgKind) v
-> AnnComputedFieldBoolExp ('Postgres pgKind) v
forall (backend :: BackendType) scalar.
XComputedField backend
-> ComputedFieldName
-> FunctionName backend
-> FunctionArgsExp backend scalar
-> ComputedFieldBoolExp backend scalar
-> AnnComputedFieldBoolExp backend scalar
AnnComputedFieldBoolExp XComputedField ('Postgres pgKind)
_cfiXComputedFieldInfo ComputedFieldName
_cfiName FunctionName ('Postgres pgKind)
_cffName FunctionArgsExp ('Postgres pgKind) v
FunctionArgsExpG (ArgumentExp v)
computedFieldFunctionArgs
(ComputedFieldBoolExp ('Postgres pgKind) v
-> AnnComputedFieldBoolExp ('Postgres pgKind) v)
-> m (ComputedFieldBoolExp ('Postgres pgKind) v)
-> m (AnnComputedFieldBoolExp ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case ComputedFieldReturn ('Postgres pgKind)
_cfiReturnType of
CFRScalar PGScalarType
scalarType ->
[OpExpG ('Postgres pgKind) v]
-> ComputedFieldBoolExp ('Postgres pgKind) v
forall (backend :: BackendType) scalar.
[OpExpG backend scalar] -> ComputedFieldBoolExp backend scalar
CFBEScalar
([OpExpG ('Postgres pgKind) v]
-> ComputedFieldBoolExp ('Postgres pgKind) v)
-> m [OpExpG ('Postgres pgKind) v]
-> m (ComputedFieldBoolExp ('Postgres pgKind) v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ValueParser ('Postgres pgKind) m v
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
-> ColumnReference ('Postgres pgKind)
-> Value
-> m [OpExpG ('Postgres pgKind) v]
forall (pgKind :: PostgresKind) (m :: * -> *) v.
(Backend ('Postgres pgKind), MonadError QErr m) =>
ValueParser ('Postgres pgKind) m v
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
-> ColumnReference ('Postgres pgKind)
-> Value
-> m [OpExpG ('Postgres pgKind) v]
parseBoolExpOperations (BoolExpRHSParser ('Postgres pgKind) m v
-> ValueParser ('Postgres pgKind) m v
forall (b :: BackendType) (m :: * -> *) v.
BoolExpRHSParser b m v -> ValueParser b m v
_berpValueParser BoolExpRHSParser ('Postgres pgKind) m v
rhsParser) FieldInfoMap (FieldInfo ('Postgres pgKind))
rootFieldInfoMap FieldInfoMap (FieldInfo ('Postgres pgKind))
colInfoMap (ComputedFieldName
-> ScalarType ('Postgres pgKind)
-> ColumnReference ('Postgres pgKind)
forall (b :: BackendType).
ComputedFieldName -> ScalarType b -> ColumnReference b
ColumnReferenceComputedField ComputedFieldName
_cfiName ScalarType ('Postgres pgKind)
PGScalarType
scalarType) Value
colVal
CFRSetofTable QualifiedTable
table -> do
BoolExp ('Postgres pgKind)
tableBoolExp <- Value -> m (BoolExp ('Postgres pgKind))
forall a (m :: * -> *). (FromJSON a, QErrM m) => Value -> m a
decodeValue Value
colVal
FieldInfoMap (FieldInfo ('Postgres pgKind))
tableFieldInfoMap <- TableName ('Postgres pgKind)
-> m (FieldInfoMap (FieldInfo ('Postgres pgKind)))
forall (m :: * -> *) (b :: BackendType).
(QErrM m, Backend b, TableCoreInfoRM b m) =>
TableName b -> m (FieldInfoMap (FieldInfo b))
askFieldInfoMapSource TableName ('Postgres pgKind)
QualifiedTable
table
AnnBoolExp ('Postgres pgKind) v
annTableBoolExp <- (BoolExpResolver ('Postgres pgKind) m v
-> BoolExpRHSParser ('Postgres pgKind) m v
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
-> GBoolExp ('Postgres pgKind) ColExp
-> m (AnnBoolExp ('Postgres pgKind) v)
forall (b :: BackendType) (m :: * -> *) v.
BoolExpResolver b m v
-> BoolExpRHSParser b m v
-> FieldInfoMap (FieldInfo b)
-> FieldInfoMap (FieldInfo b)
-> GBoolExp b ColExp
-> m (AnnBoolExp b v)
getBoolExpResolver BoolExpResolver ('Postgres pgKind) m v
boolExpResolver) BoolExpRHSParser ('Postgres pgKind) m v
rhsParser FieldInfoMap (FieldInfo ('Postgres pgKind))
tableFieldInfoMap FieldInfoMap (FieldInfo ('Postgres pgKind))
tableFieldInfoMap (GBoolExp ('Postgres pgKind) ColExp
-> m (AnnBoolExp ('Postgres pgKind) v))
-> GBoolExp ('Postgres pgKind) ColExp
-> m (AnnBoolExp ('Postgres pgKind) v)
forall a b. (a -> b) -> a -> b
$ BoolExp ('Postgres pgKind) -> GBoolExp ('Postgres pgKind) ColExp
forall (b :: BackendType). BoolExp b -> GBoolExp b ColExp
unBoolExp BoolExp ('Postgres pgKind)
tableBoolExp
ComputedFieldBoolExp ('Postgres pgKind) v
-> m (ComputedFieldBoolExp ('Postgres pgKind) v)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ComputedFieldBoolExp ('Postgres pgKind) v
-> m (ComputedFieldBoolExp ('Postgres pgKind) v))
-> ComputedFieldBoolExp ('Postgres pgKind) v
-> m (ComputedFieldBoolExp ('Postgres pgKind) v)
forall a b. (a -> b) -> a -> b
$ TableName ('Postgres pgKind)
-> AnnBoolExp ('Postgres pgKind) v
-> ComputedFieldBoolExp ('Postgres pgKind) v
forall (backend :: BackendType) scalar.
TableName backend
-> AnnBoolExp backend scalar -> ComputedFieldBoolExp backend scalar
CFBETable TableName ('Postgres pgKind)
QualifiedTable
table AnnBoolExp ('Postgres pgKind) v
annTableBoolExp
[FunctionArg]
_ ->
Code -> Text -> m (AnnComputedFieldBoolExp ('Postgres pgKind) v)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400
Code
UnexpectedPayload
Text
"Computed columns with input arguments can not be part of the where clause"