{-# LANGUAGE TemplateHaskell #-}
module Hasura.RQL.Types.ComputedField
( ComputedFieldFunction (..),
ComputedFieldInfo (..),
ComputedFieldName (..),
CustomFunctionNames (..),
FunctionTrackedAs (..),
cfiDescription,
cfiFunction,
cfiName,
cfiReturnType,
cfiXComputedFieldInfo,
computedFieldNameToText,
fromComputedField,
onlyNumComputedFields,
isNumComputedField,
onlyComparableComputedFields,
isComparableComputedField,
removeComputedFieldsReturningExistingTable,
)
where
import Control.Lens hiding ((.=))
import Data.Aeson
import Data.Sequence qualified as Seq
import Hasura.Backends.Postgres.SQL.Types hiding (FunctionName, TableName, isComparableType, isNumType)
import Hasura.Prelude
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.BackendType
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.ComputedField.Name (ComputedFieldName (..), computedFieldNameToText, fromComputedField)
import Language.GraphQL.Draft.Syntax (Name)
data FunctionTrackedAs (b :: BackendType)
= FTAComputedField ComputedFieldName SourceName (TableName b)
| FTACustomFunction CustomFunctionNames
deriving ((forall x. FunctionTrackedAs b -> Rep (FunctionTrackedAs b) x)
-> (forall x. Rep (FunctionTrackedAs b) x -> FunctionTrackedAs b)
-> Generic (FunctionTrackedAs b)
forall x. Rep (FunctionTrackedAs b) x -> FunctionTrackedAs b
forall x. FunctionTrackedAs b -> Rep (FunctionTrackedAs b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x.
Rep (FunctionTrackedAs b) x -> FunctionTrackedAs b
forall (b :: BackendType) x.
FunctionTrackedAs b -> Rep (FunctionTrackedAs b) x
$cfrom :: forall (b :: BackendType) x.
FunctionTrackedAs b -> Rep (FunctionTrackedAs b) x
from :: forall x. FunctionTrackedAs b -> Rep (FunctionTrackedAs b) x
$cto :: forall (b :: BackendType) x.
Rep (FunctionTrackedAs b) x -> FunctionTrackedAs b
to :: forall x. Rep (FunctionTrackedAs b) x -> FunctionTrackedAs b
Generic)
data CustomFunctionNames = CustomFunctionNames
{ CustomFunctionNames -> Name
cfnFunctionName :: Name,
CustomFunctionNames -> Name
cfnArgsName :: Name
}
deriving (Int -> CustomFunctionNames -> ShowS
[CustomFunctionNames] -> ShowS
CustomFunctionNames -> String
(Int -> CustomFunctionNames -> ShowS)
-> (CustomFunctionNames -> String)
-> ([CustomFunctionNames] -> ShowS)
-> Show CustomFunctionNames
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CustomFunctionNames -> ShowS
showsPrec :: Int -> CustomFunctionNames -> ShowS
$cshow :: CustomFunctionNames -> String
show :: CustomFunctionNames -> String
$cshowList :: [CustomFunctionNames] -> ShowS
showList :: [CustomFunctionNames] -> ShowS
Show, CustomFunctionNames -> CustomFunctionNames -> Bool
(CustomFunctionNames -> CustomFunctionNames -> Bool)
-> (CustomFunctionNames -> CustomFunctionNames -> Bool)
-> Eq CustomFunctionNames
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CustomFunctionNames -> CustomFunctionNames -> Bool
== :: CustomFunctionNames -> CustomFunctionNames -> Bool
$c/= :: CustomFunctionNames -> CustomFunctionNames -> Bool
/= :: CustomFunctionNames -> CustomFunctionNames -> Bool
Eq, (forall x. CustomFunctionNames -> Rep CustomFunctionNames x)
-> (forall x. Rep CustomFunctionNames x -> CustomFunctionNames)
-> Generic CustomFunctionNames
forall x. Rep CustomFunctionNames x -> CustomFunctionNames
forall x. CustomFunctionNames -> Rep CustomFunctionNames x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CustomFunctionNames -> Rep CustomFunctionNames x
from :: forall x. CustomFunctionNames -> Rep CustomFunctionNames x
$cto :: forall x. Rep CustomFunctionNames x -> CustomFunctionNames
to :: forall x. Rep CustomFunctionNames x -> CustomFunctionNames
Generic)
deriving instance (Backend b) => Show (FunctionTrackedAs b)
deriving instance (Backend b) => Eq (FunctionTrackedAs b)
data ComputedFieldFunction (b :: BackendType) = ComputedFieldFunction
{ forall (b :: BackendType).
ComputedFieldFunction b -> FunctionName b
_cffName :: FunctionName b,
forall (b :: BackendType).
ComputedFieldFunction b -> Seq (FunctionArgument b)
_cffInputArgs :: Seq.Seq (FunctionArgument b),
forall (b :: BackendType).
ComputedFieldFunction b -> ComputedFieldImplicitArguments b
_cffComputedFieldImplicitArgs :: ComputedFieldImplicitArguments b,
forall (b :: BackendType).
ComputedFieldFunction b -> Maybe PGDescription
_cffDescription :: Maybe PGDescription
}
deriving ((forall x.
ComputedFieldFunction b -> Rep (ComputedFieldFunction b) x)
-> (forall x.
Rep (ComputedFieldFunction b) x -> ComputedFieldFunction b)
-> Generic (ComputedFieldFunction b)
forall x.
Rep (ComputedFieldFunction b) x -> ComputedFieldFunction b
forall x.
ComputedFieldFunction b -> Rep (ComputedFieldFunction b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x.
Rep (ComputedFieldFunction b) x -> ComputedFieldFunction b
forall (b :: BackendType) x.
ComputedFieldFunction b -> Rep (ComputedFieldFunction b) x
$cfrom :: forall (b :: BackendType) x.
ComputedFieldFunction b -> Rep (ComputedFieldFunction b) x
from :: forall x.
ComputedFieldFunction b -> Rep (ComputedFieldFunction b) x
$cto :: forall (b :: BackendType) x.
Rep (ComputedFieldFunction b) x -> ComputedFieldFunction b
to :: forall x.
Rep (ComputedFieldFunction b) x -> ComputedFieldFunction b
Generic)
deriving instance (Backend b) => Show (ComputedFieldFunction b)
deriving instance (Backend b) => Eq (ComputedFieldFunction b)
deriving instance (Backend b) => Ord (ComputedFieldFunction b)
instance (Backend b) => NFData (ComputedFieldFunction b)
instance (Backend b) => Hashable (ComputedFieldFunction b)
instance (Backend b) => ToJSON (ComputedFieldFunction b) where
toJSON :: ComputedFieldFunction b -> Value
toJSON = Options -> ComputedFieldFunction b -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON
data ComputedFieldInfo (b :: BackendType) = ComputedFieldInfo
{ forall (b :: BackendType). ComputedFieldInfo b -> XComputedField b
_cfiXComputedFieldInfo :: XComputedField b,
forall (b :: BackendType). ComputedFieldInfo b -> ComputedFieldName
_cfiName :: ComputedFieldName,
forall (b :: BackendType).
ComputedFieldInfo b -> ComputedFieldFunction b
_cfiFunction :: ComputedFieldFunction b,
forall (b :: BackendType).
ComputedFieldInfo b -> ComputedFieldReturn b
_cfiReturnType :: ComputedFieldReturn b,
forall (b :: BackendType). ComputedFieldInfo b -> Maybe Text
_cfiDescription :: Maybe Text
}
deriving ((forall x. ComputedFieldInfo b -> Rep (ComputedFieldInfo b) x)
-> (forall x. Rep (ComputedFieldInfo b) x -> ComputedFieldInfo b)
-> Generic (ComputedFieldInfo b)
forall x. Rep (ComputedFieldInfo b) x -> ComputedFieldInfo b
forall x. ComputedFieldInfo b -> Rep (ComputedFieldInfo b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x.
Rep (ComputedFieldInfo b) x -> ComputedFieldInfo b
forall (b :: BackendType) x.
ComputedFieldInfo b -> Rep (ComputedFieldInfo b) x
$cfrom :: forall (b :: BackendType) x.
ComputedFieldInfo b -> Rep (ComputedFieldInfo b) x
from :: forall x. ComputedFieldInfo b -> Rep (ComputedFieldInfo b) x
$cto :: forall (b :: BackendType) x.
Rep (ComputedFieldInfo b) x -> ComputedFieldInfo b
to :: forall x. Rep (ComputedFieldInfo b) x -> ComputedFieldInfo b
Generic)
deriving instance (Backend b) => Eq (ComputedFieldInfo b)
deriving instance (Backend b) => Ord (ComputedFieldInfo b)
deriving instance (Backend b) => Show (ComputedFieldInfo b)
instance (Backend b) => NFData (ComputedFieldInfo b)
instance (Backend b) => Hashable (ComputedFieldInfo b)
instance (Backend b) => ToJSON (ComputedFieldInfo b) where
toJSON :: ComputedFieldInfo b -> Value
toJSON (ComputedFieldInfo XComputedField b
_ ComputedFieldName
name ComputedFieldFunction b
func ComputedFieldReturn b
tp Maybe Text
description) =
[Pair] -> Value
object [Key
"name" Key -> ComputedFieldName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ComputedFieldName
name, Key
"function" Key -> ComputedFieldFunction b -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ComputedFieldFunction b
func, Key
"return_type" Key -> ComputedFieldReturn b -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ComputedFieldReturn b
tp, Key
"description" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Maybe Text
description]
onlyNumComputedFields :: forall b. (Backend b) => [ComputedFieldInfo b] -> [ComputedFieldInfo b]
onlyNumComputedFields :: forall (b :: BackendType).
Backend b =>
[ComputedFieldInfo b] -> [ComputedFieldInfo b]
onlyNumComputedFields = (ComputedFieldInfo b -> Bool)
-> [ComputedFieldInfo b] -> [ComputedFieldInfo b]
forall a. (a -> Bool) -> [a] -> [a]
filter ComputedFieldInfo b -> Bool
forall (b :: BackendType). Backend b => ComputedFieldInfo b -> Bool
isNumComputedField
isNumComputedField :: forall b. (Backend b) => ComputedFieldInfo b -> Bool
isNumComputedField :: forall (b :: BackendType). Backend b => ComputedFieldInfo b -> Bool
isNumComputedField ComputedFieldInfo b
cfi = case forall (b :: BackendType).
Backend b =>
ComputedFieldReturn b -> ComputedFieldReturnType b
computedFieldReturnType @b (ComputedFieldInfo b -> ComputedFieldReturn b
forall (b :: BackendType).
ComputedFieldInfo b -> ComputedFieldReturn b
_cfiReturnType ComputedFieldInfo b
cfi) of
ReturnsScalar ScalarType b
t -> forall (b :: BackendType). Backend b => ScalarType b -> Bool
isNumType @b ScalarType b
t
ComputedFieldReturnType b
_ -> Bool
False
onlyComparableComputedFields :: forall b. (Backend b) => [ComputedFieldInfo b] -> [ComputedFieldInfo b]
onlyComparableComputedFields :: forall (b :: BackendType).
Backend b =>
[ComputedFieldInfo b] -> [ComputedFieldInfo b]
onlyComparableComputedFields = (ComputedFieldInfo b -> Bool)
-> [ComputedFieldInfo b] -> [ComputedFieldInfo b]
forall a. (a -> Bool) -> [a] -> [a]
filter ComputedFieldInfo b -> Bool
forall (b :: BackendType). Backend b => ComputedFieldInfo b -> Bool
isComparableComputedField
isComparableComputedField :: forall b. (Backend b) => ComputedFieldInfo b -> Bool
isComparableComputedField :: forall (b :: BackendType). Backend b => ComputedFieldInfo b -> Bool
isComparableComputedField ComputedFieldInfo b
cfi = case forall (b :: BackendType).
Backend b =>
ComputedFieldReturn b -> ComputedFieldReturnType b
computedFieldReturnType @b (ComputedFieldInfo b -> ComputedFieldReturn b
forall (b :: BackendType).
ComputedFieldInfo b -> ComputedFieldReturn b
_cfiReturnType ComputedFieldInfo b
cfi) of
ReturnsScalar ScalarType b
t -> forall (b :: BackendType). Backend b => ScalarType b -> Bool
isComparableType @b ScalarType b
t
ComputedFieldReturnType b
_ -> Bool
False
$(makeLenses ''ComputedFieldInfo)
removeComputedFieldsReturningExistingTable ::
forall backend.
(Backend backend) =>
[ComputedFieldInfo backend] ->
[ComputedFieldInfo backend]
removeComputedFieldsReturningExistingTable :: forall (b :: BackendType).
Backend b =>
[ComputedFieldInfo b] -> [ComputedFieldInfo b]
removeComputedFieldsReturningExistingTable =
(ComputedFieldInfo backend -> Bool)
-> [ComputedFieldInfo backend] -> [ComputedFieldInfo backend]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> (ComputedFieldInfo backend -> Bool)
-> ComputedFieldInfo backend
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Any (ComputedFieldReturnType backend) (TableName backend)
-> ComputedFieldReturnType backend -> Bool
forall s a. Getting Any s a -> s -> Bool
has Getting Any (ComputedFieldReturnType backend) (TableName backend)
forall (b :: BackendType) (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p (TableName b) (f (TableName b))
-> p (ComputedFieldReturnType b) (f (ComputedFieldReturnType b))
_ReturnsTable (ComputedFieldReturnType backend -> Bool)
-> (ComputedFieldInfo backend -> ComputedFieldReturnType backend)
-> ComputedFieldInfo backend
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
Backend b =>
ComputedFieldReturn b -> ComputedFieldReturnType b
computedFieldReturnType @backend (ComputedFieldReturn backend -> ComputedFieldReturnType backend)
-> (ComputedFieldInfo backend -> ComputedFieldReturn backend)
-> ComputedFieldInfo backend
-> ComputedFieldReturnType backend
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ComputedFieldInfo backend -> ComputedFieldReturn backend
forall (b :: BackendType).
ComputedFieldInfo b -> ComputedFieldReturn b
_cfiReturnType)