{-# OPTIONS_GHC -fno-warn-orphans #-}

module Hasura.Backends.DataConnector.Adapter.Backend (CustomBooleanOperator (..)) where

import Data.Aeson qualified as J (ToJSON (..), Value)
import Data.Aeson.Extended (ToJSONKeyValue (..))
import Data.Aeson.Key (fromText)
import Data.List.NonEmpty qualified as NonEmpty
import Data.Text qualified as Text
import Data.Text.Casing qualified as C
import Data.Text.Extended ((<<>))
import Hasura.Backends.DataConnector.Adapter.Types qualified as Adapter
import Hasura.Backends.DataConnector.IR.Aggregate qualified as IR.A
import Hasura.Backends.DataConnector.IR.Column qualified as IR.C
import Hasura.Backends.DataConnector.IR.Function qualified as IR.F
import Hasura.Backends.DataConnector.IR.OrderBy qualified as IR.O
import Hasura.Backends.DataConnector.IR.Scalar.Type qualified as IR.S.T
import Hasura.Backends.DataConnector.IR.Scalar.Value qualified as IR.S.V
import Hasura.Backends.DataConnector.IR.Table as IR.T
import Hasura.Base.Error (Code (ValidationFailed), QErr, runAesonParser, throw400)
import Hasura.Incremental
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp
import Hasura.RQL.Types.Backend (Backend (..), ComputedFieldReturnType, SupportedNamingCase (..), XDisable, XEnable)
import Hasura.SQL.Backend (BackendType (DataConnector))
import Language.GraphQL.Draft.Syntax qualified as G

-- | An alias for '()' indicating that a particular associated type has not yet
-- been implemented for the 'DataConnector' backend.
--
-- '()' is used (rather than a type with an empty data constructor) because it
-- comes with many of the instances that these associated types require.
--
-- This alias should /not/ be exported from this module, and it's only defined
-- for clarity.
type Unimplemented = ()

instance Backend 'DataConnector where
  type BackendConfig 'DataConnector = InsOrdHashMap Adapter.DataConnectorName Adapter.DataConnectorOptions
  type SourceConfig 'DataConnector = Adapter.SourceConfig
  type SourceConnConfiguration 'DataConnector = Adapter.ConnSourceConfig

  type TableName 'DataConnector = IR.T.Name
  type FunctionName 'DataConnector = IR.F.Name
  type RawFunctionInfo 'DataConnector = XDisable
  type FunctionArgument 'DataConnector = XDisable
  type ConstraintName 'DataConnector = IR.T.ConstraintName
  type BasicOrderType 'DataConnector = IR.O.OrderDirection
  type NullsOrderType 'DataConnector = Unimplemented
  type CountType 'DataConnector = IR.A.CountAggregate
  type Column 'DataConnector = IR.C.Name
  type ScalarValue 'DataConnector = IR.S.V.Value
  type ScalarType 'DataConnector = IR.S.T.Type

  -- This does not actually have to be the full IR Expression, in fact it is only
  -- required to represent literals, so we use a special type for that.
  -- The 'SQLExpression' type family should be removed in a future refactor
  type SQLExpression 'DataConnector = IR.S.V.Literal
  type ScalarSelectionArguments 'DataConnector = Void
  type BooleanOperators 'DataConnector = CustomBooleanOperator
  type ExtraTableMetadata 'DataConnector = Unimplemented
  type ComputedFieldDefinition 'DataConnector = Unimplemented
  type FunctionArgumentExp 'DataConnector = Const Unimplemented
  type ComputedFieldImplicitArguments 'DataConnector = Unimplemented
  type ComputedFieldReturn 'DataConnector = Unimplemented

  type XComputedField 'DataConnector = XDisable
  type XRelay 'DataConnector = XDisable
  type XNodesAgg 'DataConnector = XEnable
  type XNestedInserts 'DataConnector = XDisable
  type XStreamingSubscription 'DataConnector = XDisable

  isComparableType :: ScalarType 'DataConnector -> Bool
  isComparableType :: ScalarType 'DataConnector -> Bool
isComparableType = \case
    ScalarType 'DataConnector
IR.S.T.Number -> Bool
True
    ScalarType 'DataConnector
IR.S.T.String -> Bool
True
    ScalarType 'DataConnector
IR.S.T.Bool -> Bool
False

  isNumType :: ScalarType 'DataConnector -> Bool
  isNumType :: ScalarType 'DataConnector -> Bool
isNumType ScalarType 'DataConnector
IR.S.T.Number = Bool
True
  isNumType ScalarType 'DataConnector
_ = Bool
False

  textToScalarValue :: Maybe Text -> ScalarValue 'DataConnector
  textToScalarValue :: Maybe Text -> ScalarValue 'DataConnector
textToScalarValue = [Char] -> Maybe Text -> Value
forall a. HasCallStack => [Char] -> a
error [Char]
"textToScalarValue: not implemented for the Data Connector backend."

  parseScalarValue :: ScalarType 'DataConnector -> J.Value -> Either QErr (ScalarValue 'DataConnector)
  parseScalarValue :: ScalarType 'DataConnector
-> Value -> Either QErr (ScalarValue 'DataConnector)
parseScalarValue ScalarType 'DataConnector
type' Value
value = (Value -> Parser Value) -> Value -> Either QErr Value
forall (m :: * -> *) v a. QErrM m => (v -> Parser a) -> v -> m a
runAesonParser (Type -> Value -> Parser Value
IR.S.V.parseValue Type
ScalarType 'DataConnector
type') Value
value

  scalarValueToJSON :: ScalarValue 'DataConnector -> J.Value
  scalarValueToJSON :: ScalarValue 'DataConnector -> Value
scalarValueToJSON = [Char] -> Value -> Value
forall a. HasCallStack => [Char] -> a
error [Char]
"scalarValueToJSON: not implemented for the Data Connector backend."

  functionToTable :: FunctionName 'DataConnector -> TableName 'DataConnector
  functionToTable :: FunctionName 'DataConnector -> TableName 'DataConnector
functionToTable = [Char] -> Name -> Name
forall a. HasCallStack => [Char] -> a
error [Char]
"functionToTable: not implemented for the Data Connector backend."

  computedFieldFunction :: ComputedFieldDefinition 'DataConnector -> FunctionName 'DataConnector
  computedFieldFunction :: ComputedFieldDefinition 'DataConnector
-> FunctionName 'DataConnector
computedFieldFunction = [Char] -> Unimplemented -> Name
forall a. HasCallStack => [Char] -> a
error [Char]
"computedFieldFunction: not implemented for the Data Connector backend"

  computedFieldReturnType :: ComputedFieldReturn 'DataConnector -> ComputedFieldReturnType 'DataConnector
  computedFieldReturnType :: ComputedFieldReturn 'DataConnector
-> ComputedFieldReturnType 'DataConnector
computedFieldReturnType = [Char] -> Unimplemented -> ComputedFieldReturnType 'DataConnector
forall a. HasCallStack => [Char] -> a
error [Char]
"computedFieldReturnType: not implemented for the Data Connector backend"

  fromComputedFieldImplicitArguments :: v -> ComputedFieldImplicitArguments 'DataConnector -> [FunctionArgumentExp 'DataConnector v]
  fromComputedFieldImplicitArguments :: v
-> ComputedFieldImplicitArguments 'DataConnector
-> [FunctionArgumentExp 'DataConnector v]
fromComputedFieldImplicitArguments = [Char] -> v -> Unimplemented -> [Const Unimplemented v]
forall a. HasCallStack => [Char] -> a
error [Char]
"fromComputedFieldImplicitArguments: not implemented for the Data Connector backend"

  -- phil said this was cursed
  tableToFunction :: TableName 'DataConnector -> FunctionName 'DataConnector
  tableToFunction :: TableName 'DataConnector -> FunctionName 'DataConnector
tableToFunction = TableName 'DataConnector -> FunctionName 'DataConnector
coerce

  tableGraphQLName :: TableName 'DataConnector -> Either QErr G.Name
  tableGraphQLName :: TableName 'DataConnector -> Either QErr Name
tableGraphQLName TableName 'DataConnector
name = do
    let snakedName :: Text
snakedName = TableName 'DataConnector -> Text
forall (b :: BackendType). Backend b => TableName b -> Text
snakeCaseTableName @'DataConnector TableName 'DataConnector
name
    Text -> Maybe Name
G.mkName Text
snakedName
      Maybe Name -> Either QErr Name -> Either QErr Name
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` Code -> Text -> Either QErr Name
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
ValidationFailed (Text
"TableName " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
snakedName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a valid GraphQL identifier")

  functionGraphQLName :: FunctionName 'DataConnector -> Either QErr G.Name
  functionGraphQLName :: FunctionName 'DataConnector -> Either QErr Name
functionGraphQLName = [Char] -> Name -> Either QErr Name
forall a. HasCallStack => [Char] -> a
error [Char]
"functionGraphQLName: not implemented for the Data Connector backend."

  snakeCaseTableName :: TableName 'DataConnector -> Text
  snakeCaseTableName :: TableName 'DataConnector -> Text
snakeCaseTableName = Text -> [Text] -> Text
Text.intercalate Text
"_" ([Text] -> Text) -> (Name -> [Text]) -> Name -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty Text -> [Text]
forall a. NonEmpty a -> [a]
NonEmpty.toList (NonEmpty Text -> [Text])
-> (Name -> NonEmpty Text) -> Name -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> NonEmpty Text
IR.T.unName

  getTableIdentifier :: TableName 'DataConnector -> Either QErr C.GQLNameIdentifier
  getTableIdentifier :: TableName 'DataConnector -> Either QErr GQLNameIdentifier
getTableIdentifier name :: TableName 'DataConnector
name@(IR.T.Name (prefix :| suffixes)) =
    let identifier :: Maybe GQLNameIdentifier
identifier = do
          Name
namePrefix <- Text -> Maybe Name
G.mkName Text
prefix
          [NameSuffix]
nameSuffixes <- (Text -> Maybe NameSuffix) -> [Text] -> Maybe [NameSuffix]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Text -> Maybe NameSuffix
G.mkNameSuffix [Text]
suffixes
          GQLNameIdentifier -> Maybe GQLNameIdentifier
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GQLNameIdentifier -> Maybe GQLNameIdentifier)
-> GQLNameIdentifier -> Maybe GQLNameIdentifier
forall a b. (a -> b) -> a -> b
$ (Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple (Name
namePrefix, [NameSuffix]
nameSuffixes)
     in Maybe GQLNameIdentifier
identifier
          Maybe GQLNameIdentifier
-> Either QErr GQLNameIdentifier -> Either QErr GQLNameIdentifier
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` Code -> Text -> Either QErr GQLNameIdentifier
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
ValidationFailed (Text
"TableName " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Name
TableName 'DataConnector
name Name -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" is not a valid GraphQL identifier")

  namingConventionSupport :: SupportedNamingCase
  namingConventionSupport :: SupportedNamingCase
namingConventionSupport = SupportedNamingCase
OnlyHasuraCase

data CustomBooleanOperator a = CustomBooleanOperator
  { CustomBooleanOperator a -> Text
_cboName :: Text,
    CustomBooleanOperator a
-> Maybe (Either (RootOrCurrentColumn 'DataConnector) a)
_cboRHS :: Maybe (Either (RootOrCurrentColumn 'DataConnector) a) -- TODO turn Either into a specific type
  }
  deriving stock (CustomBooleanOperator a -> CustomBooleanOperator a -> Bool
(CustomBooleanOperator a -> CustomBooleanOperator a -> Bool)
-> (CustomBooleanOperator a -> CustomBooleanOperator a -> Bool)
-> Eq (CustomBooleanOperator a)
forall a.
Eq a =>
CustomBooleanOperator a -> CustomBooleanOperator a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomBooleanOperator a -> CustomBooleanOperator a -> Bool
$c/= :: forall a.
Eq a =>
CustomBooleanOperator a -> CustomBooleanOperator a -> Bool
== :: CustomBooleanOperator a -> CustomBooleanOperator a -> Bool
$c== :: forall a.
Eq a =>
CustomBooleanOperator a -> CustomBooleanOperator a -> Bool
Eq, (forall x.
 CustomBooleanOperator a -> Rep (CustomBooleanOperator a) x)
-> (forall x.
    Rep (CustomBooleanOperator a) x -> CustomBooleanOperator a)
-> Generic (CustomBooleanOperator a)
forall x.
Rep (CustomBooleanOperator a) x -> CustomBooleanOperator a
forall x.
CustomBooleanOperator a -> Rep (CustomBooleanOperator a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x.
Rep (CustomBooleanOperator a) x -> CustomBooleanOperator a
forall a x.
CustomBooleanOperator a -> Rep (CustomBooleanOperator a) x
$cto :: forall a x.
Rep (CustomBooleanOperator a) x -> CustomBooleanOperator a
$cfrom :: forall a x.
CustomBooleanOperator a -> Rep (CustomBooleanOperator a) x
Generic, CustomBooleanOperator a -> Bool
(a -> m) -> CustomBooleanOperator a -> m
(a -> b -> b) -> b -> CustomBooleanOperator a -> b
(forall m. Monoid m => CustomBooleanOperator m -> m)
-> (forall m a.
    Monoid m =>
    (a -> m) -> CustomBooleanOperator a -> m)
-> (forall m a.
    Monoid m =>
    (a -> m) -> CustomBooleanOperator a -> m)
-> (forall a b. (a -> b -> b) -> b -> CustomBooleanOperator a -> b)
-> (forall a b. (a -> b -> b) -> b -> CustomBooleanOperator a -> b)
-> (forall b a. (b -> a -> b) -> b -> CustomBooleanOperator a -> b)
-> (forall b a. (b -> a -> b) -> b -> CustomBooleanOperator a -> b)
-> (forall a. (a -> a -> a) -> CustomBooleanOperator a -> a)
-> (forall a. (a -> a -> a) -> CustomBooleanOperator a -> a)
-> (forall a. CustomBooleanOperator a -> [a])
-> (forall a. CustomBooleanOperator a -> Bool)
-> (forall a. CustomBooleanOperator a -> Int)
-> (forall a. Eq a => a -> CustomBooleanOperator a -> Bool)
-> (forall a. Ord a => CustomBooleanOperator a -> a)
-> (forall a. Ord a => CustomBooleanOperator a -> a)
-> (forall a. Num a => CustomBooleanOperator a -> a)
-> (forall a. Num a => CustomBooleanOperator a -> a)
-> Foldable CustomBooleanOperator
forall a. Eq a => a -> CustomBooleanOperator a -> Bool
forall a. Num a => CustomBooleanOperator a -> a
forall a. Ord a => CustomBooleanOperator a -> a
forall m. Monoid m => CustomBooleanOperator m -> m
forall a. CustomBooleanOperator a -> Bool
forall a. CustomBooleanOperator a -> Int
forall a. CustomBooleanOperator a -> [a]
forall a. (a -> a -> a) -> CustomBooleanOperator a -> a
forall m a. Monoid m => (a -> m) -> CustomBooleanOperator a -> m
forall b a. (b -> a -> b) -> b -> CustomBooleanOperator a -> b
forall a b. (a -> b -> b) -> b -> CustomBooleanOperator 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 :: CustomBooleanOperator a -> a
$cproduct :: forall a. Num a => CustomBooleanOperator a -> a
sum :: CustomBooleanOperator a -> a
$csum :: forall a. Num a => CustomBooleanOperator a -> a
minimum :: CustomBooleanOperator a -> a
$cminimum :: forall a. Ord a => CustomBooleanOperator a -> a
maximum :: CustomBooleanOperator a -> a
$cmaximum :: forall a. Ord a => CustomBooleanOperator a -> a
elem :: a -> CustomBooleanOperator a -> Bool
$celem :: forall a. Eq a => a -> CustomBooleanOperator a -> Bool
length :: CustomBooleanOperator a -> Int
$clength :: forall a. CustomBooleanOperator a -> Int
null :: CustomBooleanOperator a -> Bool
$cnull :: forall a. CustomBooleanOperator a -> Bool
toList :: CustomBooleanOperator a -> [a]
$ctoList :: forall a. CustomBooleanOperator a -> [a]
foldl1 :: (a -> a -> a) -> CustomBooleanOperator a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> CustomBooleanOperator a -> a
foldr1 :: (a -> a -> a) -> CustomBooleanOperator a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> CustomBooleanOperator a -> a
foldl' :: (b -> a -> b) -> b -> CustomBooleanOperator a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> CustomBooleanOperator a -> b
foldl :: (b -> a -> b) -> b -> CustomBooleanOperator a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> CustomBooleanOperator a -> b
foldr' :: (a -> b -> b) -> b -> CustomBooleanOperator a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> CustomBooleanOperator a -> b
foldr :: (a -> b -> b) -> b -> CustomBooleanOperator a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> CustomBooleanOperator a -> b
foldMap' :: (a -> m) -> CustomBooleanOperator a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> CustomBooleanOperator a -> m
foldMap :: (a -> m) -> CustomBooleanOperator a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> CustomBooleanOperator a -> m
fold :: CustomBooleanOperator m -> m
$cfold :: forall m. Monoid m => CustomBooleanOperator m -> m
Foldable, a -> CustomBooleanOperator b -> CustomBooleanOperator a
(a -> b) -> CustomBooleanOperator a -> CustomBooleanOperator b
(forall a b.
 (a -> b) -> CustomBooleanOperator a -> CustomBooleanOperator b)
-> (forall a b.
    a -> CustomBooleanOperator b -> CustomBooleanOperator a)
-> Functor CustomBooleanOperator
forall a b. a -> CustomBooleanOperator b -> CustomBooleanOperator a
forall a b.
(a -> b) -> CustomBooleanOperator a -> CustomBooleanOperator b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> CustomBooleanOperator b -> CustomBooleanOperator a
$c<$ :: forall a b. a -> CustomBooleanOperator b -> CustomBooleanOperator a
fmap :: (a -> b) -> CustomBooleanOperator a -> CustomBooleanOperator b
$cfmap :: forall a b.
(a -> b) -> CustomBooleanOperator a -> CustomBooleanOperator b
Functor, Functor CustomBooleanOperator
Foldable CustomBooleanOperator
Functor CustomBooleanOperator
-> Foldable CustomBooleanOperator
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b)
    -> CustomBooleanOperator a -> f (CustomBooleanOperator b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    CustomBooleanOperator (f a) -> f (CustomBooleanOperator a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b)
    -> CustomBooleanOperator a -> m (CustomBooleanOperator b))
-> (forall (m :: * -> *) a.
    Monad m =>
    CustomBooleanOperator (m a) -> m (CustomBooleanOperator a))
-> Traversable CustomBooleanOperator
(a -> f b)
-> CustomBooleanOperator a -> f (CustomBooleanOperator 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 =>
CustomBooleanOperator (m a) -> m (CustomBooleanOperator a)
forall (f :: * -> *) a.
Applicative f =>
CustomBooleanOperator (f a) -> f (CustomBooleanOperator a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> CustomBooleanOperator a -> m (CustomBooleanOperator b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> CustomBooleanOperator a -> f (CustomBooleanOperator b)
sequence :: CustomBooleanOperator (m a) -> m (CustomBooleanOperator a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
CustomBooleanOperator (m a) -> m (CustomBooleanOperator a)
mapM :: (a -> m b)
-> CustomBooleanOperator a -> m (CustomBooleanOperator b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> CustomBooleanOperator a -> m (CustomBooleanOperator b)
sequenceA :: CustomBooleanOperator (f a) -> f (CustomBooleanOperator a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
CustomBooleanOperator (f a) -> f (CustomBooleanOperator a)
traverse :: (a -> f b)
-> CustomBooleanOperator a -> f (CustomBooleanOperator b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> CustomBooleanOperator a -> f (CustomBooleanOperator b)
$cp2Traversable :: Foldable CustomBooleanOperator
$cp1Traversable :: Functor CustomBooleanOperator
Traversable, Int -> CustomBooleanOperator a -> ShowS
[CustomBooleanOperator a] -> ShowS
CustomBooleanOperator a -> [Char]
(Int -> CustomBooleanOperator a -> ShowS)
-> (CustomBooleanOperator a -> [Char])
-> ([CustomBooleanOperator a] -> ShowS)
-> Show (CustomBooleanOperator a)
forall a. Show a => Int -> CustomBooleanOperator a -> ShowS
forall a. Show a => [CustomBooleanOperator a] -> ShowS
forall a. Show a => CustomBooleanOperator a -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [CustomBooleanOperator a] -> ShowS
$cshowList :: forall a. Show a => [CustomBooleanOperator a] -> ShowS
show :: CustomBooleanOperator a -> [Char]
$cshow :: forall a. Show a => CustomBooleanOperator a -> [Char]
showsPrec :: Int -> CustomBooleanOperator a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CustomBooleanOperator a -> ShowS
Show)

instance NFData a => NFData (CustomBooleanOperator a)

instance Hashable a => Hashable (CustomBooleanOperator a)

instance Cacheable a => Cacheable (CustomBooleanOperator a)

instance J.ToJSON a => ToJSONKeyValue (CustomBooleanOperator a) where
  toJSONKeyValue :: CustomBooleanOperator a -> (Key, Value)
toJSONKeyValue CustomBooleanOperator {Maybe (Either (RootOrCurrentColumn 'DataConnector) a)
Text
_cboRHS :: Maybe (Either (RootOrCurrentColumn 'DataConnector) a)
_cboName :: Text
_cboRHS :: forall a.
CustomBooleanOperator a
-> Maybe (Either (RootOrCurrentColumn 'DataConnector) a)
_cboName :: forall a. CustomBooleanOperator a -> Text
..} = (Text -> Key
fromText Text
_cboName, Maybe (Either (RootOrCurrentColumn 'DataConnector) a) -> Value
forall a. ToJSON a => a -> Value
J.toJSON Maybe (Either (RootOrCurrentColumn 'DataConnector) a)
_cboRHS)