{-# LANGUAGE TemplateHaskell #-}
module Hasura.GraphQL.Execute.Action.Types
( ActionContext (..),
ActionExecution (..),
ActionExecutionPlan (..),
ActionHandlerLog (..),
ActionInternalError (..),
ActionRequestInfo (..),
ActionResponseInfo (..),
ActionWebhookErrorResponse (..),
ActionWebhookPayload (..),
ActionWebhookResponse,
AsyncActionQueryExecution (..),
AsyncActionQueryExecutionPlan (..),
AsyncActionQuerySourceExecution (..),
)
where
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.Aeson qualified as J
import Data.Aeson.Casing qualified as J
import Data.Aeson.TH qualified as J
import Data.Int (Int64)
import Hasura.Base.Error
import Hasura.EncJSON
import Hasura.GraphQL.Transport.HTTP.Protocol
import Hasura.Logging qualified as L
import Hasura.Prelude
import Hasura.RQL.DDL.Headers
import Hasura.RQL.IR.Select qualified as RS
import Hasura.RQL.IR.Value
import Hasura.RQL.Types.Action
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Common
import Hasura.SQL.Backend
import Hasura.Session
import Hasura.Tracing qualified as Tracing
import Network.HTTP.Client.Transformable qualified as HTTP
newtype ActionExecution = ActionExecution
{ ActionExecution
-> forall (m :: * -> *).
(MonadIO m, MonadBaseControl IO m, MonadError QErr m,
MonadTrace m) =>
m (EncJSON, ResponseHeaders)
unActionExecution ::
forall m.
(MonadIO m, MonadBaseControl IO m, MonadError QErr m, Tracing.MonadTrace m) =>
m (EncJSON, HTTP.ResponseHeaders)
}
data AsyncActionQuerySourceExecution v = AsyncActionQuerySourceExecution
{ AsyncActionQuerySourceExecution v -> SourceName
_aaqseSource :: !SourceName,
AsyncActionQuerySourceExecution v -> JsonAggSelect
_aaqseJsonAggSelect :: !JsonAggSelect,
AsyncActionQuerySourceExecution v
-> ActionLogResponse
-> AnnSimpleSelectG ('Postgres 'Vanilla) Void v
_aaqseSelectBuilder :: !(ActionLogResponse -> RS.AnnSimpleSelectG ('Postgres 'Vanilla) Void v)
}
data AsyncActionQueryExecution v
=
AAQENoRelationships !(ActionLogResponse -> Either QErr EncJSON)
|
AAQEOnSourceDB !(SourceConfig ('Postgres 'Vanilla)) !(AsyncActionQuerySourceExecution v)
data AsyncActionQueryExecutionPlan = AsyncActionQueryExecutionPlan
{ AsyncActionQueryExecutionPlan -> ActionId
_aaqepId :: !ActionId,
AsyncActionQueryExecutionPlan
-> AsyncActionQueryExecution (UnpreparedValue ('Postgres 'Vanilla))
_aaqepExecution :: !(AsyncActionQueryExecution (UnpreparedValue ('Postgres 'Vanilla)))
}
data ActionExecutionPlan
= AEPSync !ActionExecution
| AEPAsyncQuery !AsyncActionQueryExecutionPlan
| AEPAsyncMutation !ActionId
newtype ActionContext = ActionContext {ActionContext -> ActionName
_acName :: ActionName}
deriving (Int -> ActionContext -> ShowS
[ActionContext] -> ShowS
ActionContext -> String
(Int -> ActionContext -> ShowS)
-> (ActionContext -> String)
-> ([ActionContext] -> ShowS)
-> Show ActionContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionContext] -> ShowS
$cshowList :: [ActionContext] -> ShowS
show :: ActionContext -> String
$cshow :: ActionContext -> String
showsPrec :: Int -> ActionContext -> ShowS
$cshowsPrec :: Int -> ActionContext -> ShowS
Show, ActionContext -> ActionContext -> Bool
(ActionContext -> ActionContext -> Bool)
-> (ActionContext -> ActionContext -> Bool) -> Eq ActionContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionContext -> ActionContext -> Bool
$c/= :: ActionContext -> ActionContext -> Bool
== :: ActionContext -> ActionContext -> Bool
$c== :: ActionContext -> ActionContext -> Bool
Eq)
$(J.deriveJSON (J.aesonDrop 3 J.snakeCase) ''ActionContext)
data ActionWebhookPayload = ActionWebhookPayload
{ ActionWebhookPayload -> ActionContext
_awpAction :: !ActionContext,
ActionWebhookPayload -> SessionVariables
_awpSessionVariables :: !SessionVariables,
ActionWebhookPayload -> Value
_awpInput :: !J.Value,
ActionWebhookPayload -> Maybe GQLQueryText
_awpRequestQuery :: !(Maybe GQLQueryText)
}
deriving (Int -> ActionWebhookPayload -> ShowS
[ActionWebhookPayload] -> ShowS
ActionWebhookPayload -> String
(Int -> ActionWebhookPayload -> ShowS)
-> (ActionWebhookPayload -> String)
-> ([ActionWebhookPayload] -> ShowS)
-> Show ActionWebhookPayload
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionWebhookPayload] -> ShowS
$cshowList :: [ActionWebhookPayload] -> ShowS
show :: ActionWebhookPayload -> String
$cshow :: ActionWebhookPayload -> String
showsPrec :: Int -> ActionWebhookPayload -> ShowS
$cshowsPrec :: Int -> ActionWebhookPayload -> ShowS
Show, ActionWebhookPayload -> ActionWebhookPayload -> Bool
(ActionWebhookPayload -> ActionWebhookPayload -> Bool)
-> (ActionWebhookPayload -> ActionWebhookPayload -> Bool)
-> Eq ActionWebhookPayload
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionWebhookPayload -> ActionWebhookPayload -> Bool
$c/= :: ActionWebhookPayload -> ActionWebhookPayload -> Bool
== :: ActionWebhookPayload -> ActionWebhookPayload -> Bool
$c== :: ActionWebhookPayload -> ActionWebhookPayload -> Bool
Eq)
$(J.deriveJSON (J.aesonDrop 4 J.snakeCase) ''ActionWebhookPayload)
data ActionWebhookErrorResponse = ActionWebhookErrorResponse
{ ActionWebhookErrorResponse -> Text
_awerMessage :: !Text,
ActionWebhookErrorResponse -> Maybe Text
_awerCode :: !(Maybe Text),
ActionWebhookErrorResponse -> Maybe Value
_awerExtensions :: !(Maybe J.Value)
}
deriving (Int -> ActionWebhookErrorResponse -> ShowS
[ActionWebhookErrorResponse] -> ShowS
ActionWebhookErrorResponse -> String
(Int -> ActionWebhookErrorResponse -> ShowS)
-> (ActionWebhookErrorResponse -> String)
-> ([ActionWebhookErrorResponse] -> ShowS)
-> Show ActionWebhookErrorResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionWebhookErrorResponse] -> ShowS
$cshowList :: [ActionWebhookErrorResponse] -> ShowS
show :: ActionWebhookErrorResponse -> String
$cshow :: ActionWebhookErrorResponse -> String
showsPrec :: Int -> ActionWebhookErrorResponse -> ShowS
$cshowsPrec :: Int -> ActionWebhookErrorResponse -> ShowS
Show, ActionWebhookErrorResponse -> ActionWebhookErrorResponse -> Bool
(ActionWebhookErrorResponse -> ActionWebhookErrorResponse -> Bool)
-> (ActionWebhookErrorResponse
-> ActionWebhookErrorResponse -> Bool)
-> Eq ActionWebhookErrorResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionWebhookErrorResponse -> ActionWebhookErrorResponse -> Bool
$c/= :: ActionWebhookErrorResponse -> ActionWebhookErrorResponse -> Bool
== :: ActionWebhookErrorResponse -> ActionWebhookErrorResponse -> Bool
$c== :: ActionWebhookErrorResponse -> ActionWebhookErrorResponse -> Bool
Eq)
$(J.deriveJSON (J.aesonDrop 5 J.snakeCase) ''ActionWebhookErrorResponse)
type ActionWebhookResponse = J.Value
data ActionRequestInfo = ActionRequestInfo
{ ActionRequestInfo -> Text
_areqiUrl :: !Text,
ActionRequestInfo -> Value
_areqiBody :: !J.Value,
:: ![HeaderConf],
ActionRequestInfo -> Maybe Request
_areqiTransformedRequest :: !(Maybe HTTP.Request)
}
deriving (Int -> ActionRequestInfo -> ShowS
[ActionRequestInfo] -> ShowS
ActionRequestInfo -> String
(Int -> ActionRequestInfo -> ShowS)
-> (ActionRequestInfo -> String)
-> ([ActionRequestInfo] -> ShowS)
-> Show ActionRequestInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionRequestInfo] -> ShowS
$cshowList :: [ActionRequestInfo] -> ShowS
show :: ActionRequestInfo -> String
$cshow :: ActionRequestInfo -> String
showsPrec :: Int -> ActionRequestInfo -> ShowS
$cshowsPrec :: Int -> ActionRequestInfo -> ShowS
Show)
$(J.deriveToJSON (J.aesonDrop 6 J.snakeCase) ''ActionRequestInfo)
data ActionResponseInfo = ActionResponseInfo
{ ActionResponseInfo -> Int
_aresiStatus :: !Int,
ActionResponseInfo -> Value
_aresiBody :: !J.Value,
:: ![HeaderConf]
}
deriving (Int -> ActionResponseInfo -> ShowS
[ActionResponseInfo] -> ShowS
ActionResponseInfo -> String
(Int -> ActionResponseInfo -> ShowS)
-> (ActionResponseInfo -> String)
-> ([ActionResponseInfo] -> ShowS)
-> Show ActionResponseInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionResponseInfo] -> ShowS
$cshowList :: [ActionResponseInfo] -> ShowS
show :: ActionResponseInfo -> String
$cshow :: ActionResponseInfo -> String
showsPrec :: Int -> ActionResponseInfo -> ShowS
$cshowsPrec :: Int -> ActionResponseInfo -> ShowS
Show, ActionResponseInfo -> ActionResponseInfo -> Bool
(ActionResponseInfo -> ActionResponseInfo -> Bool)
-> (ActionResponseInfo -> ActionResponseInfo -> Bool)
-> Eq ActionResponseInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionResponseInfo -> ActionResponseInfo -> Bool
$c/= :: ActionResponseInfo -> ActionResponseInfo -> Bool
== :: ActionResponseInfo -> ActionResponseInfo -> Bool
$c== :: ActionResponseInfo -> ActionResponseInfo -> Bool
Eq)
$(J.deriveToJSON (J.aesonDrop 6 J.snakeCase) ''ActionResponseInfo)
data ActionInternalError = ActionInternalError
{ ActionInternalError -> Value
_aieError :: !J.Value,
ActionInternalError -> ActionRequestInfo
_aieRequest :: !ActionRequestInfo,
ActionInternalError -> Maybe ActionResponseInfo
_aieResponse :: !(Maybe ActionResponseInfo)
}
deriving (Int -> ActionInternalError -> ShowS
[ActionInternalError] -> ShowS
ActionInternalError -> String
(Int -> ActionInternalError -> ShowS)
-> (ActionInternalError -> String)
-> ([ActionInternalError] -> ShowS)
-> Show ActionInternalError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionInternalError] -> ShowS
$cshowList :: [ActionInternalError] -> ShowS
show :: ActionInternalError -> String
$cshow :: ActionInternalError -> String
showsPrec :: Int -> ActionInternalError -> ShowS
$cshowsPrec :: Int -> ActionInternalError -> ShowS
Show)
$(J.deriveToJSON (J.aesonDrop 4 J.snakeCase) ''ActionInternalError)
data ActionHandlerLog = ActionHandlerLog
{ ActionHandlerLog -> Request
_ahlRequest :: !HTTP.Request,
ActionHandlerLog -> Maybe Request
_ahlRequestTrans :: !(Maybe HTTP.Request),
ActionHandlerLog -> Int64
_ahlRequestSize :: !Int64,
ActionHandlerLog -> Maybe Int64
_ahlTransformedRequestSize :: !(Maybe Int64),
ActionHandlerLog -> Int64
_ahlResponseSize :: !Int64,
ActionHandlerLog -> ActionName
_ahlActionName :: !ActionName
}
deriving (Int -> ActionHandlerLog -> ShowS
[ActionHandlerLog] -> ShowS
ActionHandlerLog -> String
(Int -> ActionHandlerLog -> ShowS)
-> (ActionHandlerLog -> String)
-> ([ActionHandlerLog] -> ShowS)
-> Show ActionHandlerLog
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionHandlerLog] -> ShowS
$cshowList :: [ActionHandlerLog] -> ShowS
show :: ActionHandlerLog -> String
$cshow :: ActionHandlerLog -> String
showsPrec :: Int -> ActionHandlerLog -> ShowS
$cshowsPrec :: Int -> ActionHandlerLog -> ShowS
Show)
$(J.deriveToJSON (J.aesonDrop 4 J.snakeCase) {J.omitNothingFields = True} ''ActionHandlerLog)
instance L.ToEngineLog ActionHandlerLog L.Hasura where
toEngineLog :: ActionHandlerLog -> (LogLevel, EngineLogType Hasura, Value)
toEngineLog ActionHandlerLog
ahl = (LogLevel
L.LevelInfo, EngineLogType Hasura
L.ELTActionHandler, ActionHandlerLog -> Value
forall a. ToJSON a => a -> Value
J.toJSON ActionHandlerLog
ahl)