{-# LANGUAGE TemplateHaskell #-}
module Hasura.GraphQL.Explain
( explainGQLQuery,
GQLExplain,
)
where
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.Aeson qualified as J
import Data.Aeson.TH qualified as J
import Data.HashMap.Strict qualified as Map
import Data.HashMap.Strict.InsOrd qualified as OMap
import Hasura.Base.Error
import Hasura.EncJSON
import Hasura.GraphQL.Context qualified as C
import Hasura.GraphQL.Execute qualified as E
import Hasura.GraphQL.Execute.Action qualified as E
import Hasura.GraphQL.Execute.Backend
import Hasura.GraphQL.Execute.Instances ()
import Hasura.GraphQL.Execute.Query qualified as E
import Hasura.GraphQL.Execute.RemoteJoin.Collect qualified as RJ
import Hasura.GraphQL.Execute.Resolve qualified as ER
import Hasura.GraphQL.Namespace (RootFieldAlias)
import Hasura.GraphQL.ParameterizedQueryHash
import Hasura.GraphQL.Transport.Backend
import Hasura.GraphQL.Transport.HTTP.Protocol qualified as GH
import Hasura.GraphQL.Transport.Instances ()
import Hasura.Metadata.Class
import Hasura.Prelude
import Hasura.RQL.IR
import Hasura.RQL.Types.SchemaCache
import Hasura.SQL.AnyBackend qualified as AB
import Hasura.Session
import Language.GraphQL.Draft.Syntax qualified as G
data GQLExplain = GQLExplain
{ GQLExplain -> GQLReqParsed
_gqeQuery :: !GH.GQLReqParsed,
GQLExplain -> Maybe (HashMap Text Text)
_gqeUser :: !(Maybe (Map.HashMap Text Text)),
GQLExplain -> Maybe Bool
_gqeIsRelay :: !(Maybe Bool)
}
deriving (Int -> GQLExplain -> ShowS
[GQLExplain] -> ShowS
GQLExplain -> String
(Int -> GQLExplain -> ShowS)
-> (GQLExplain -> String)
-> ([GQLExplain] -> ShowS)
-> Show GQLExplain
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GQLExplain] -> ShowS
$cshowList :: [GQLExplain] -> ShowS
show :: GQLExplain -> String
$cshow :: GQLExplain -> String
showsPrec :: Int -> GQLExplain -> ShowS
$cshowsPrec :: Int -> GQLExplain -> ShowS
Show, GQLExplain -> GQLExplain -> Bool
(GQLExplain -> GQLExplain -> Bool)
-> (GQLExplain -> GQLExplain -> Bool) -> Eq GQLExplain
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GQLExplain -> GQLExplain -> Bool
$c/= :: GQLExplain -> GQLExplain -> Bool
== :: GQLExplain -> GQLExplain -> Bool
$c== :: GQLExplain -> GQLExplain -> Bool
Eq)
$( J.deriveJSON
hasuraJSON {J.omitNothingFields = True}
''GQLExplain
)
explainQueryField ::
( MonadError QErr m,
MonadIO m
) =>
UserInfo ->
RootFieldAlias ->
QueryRootField UnpreparedValue ->
m EncJSON
explainQueryField :: UserInfo
-> RootFieldAlias -> QueryRootField UnpreparedValue -> m EncJSON
explainQueryField UserInfo
userInfo RootFieldAlias
fieldName QueryRootField UnpreparedValue
rootField = do
case QueryRootField UnpreparedValue
rootField of
RFRemote RemoteSchemaRootField
(RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable
_ -> Code -> Text -> m EncJSON
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
InvalidParams Text
"only hasura queries can be explained"
RFAction QueryActionRoot UnpreparedValue
_ -> Code -> Text -> m EncJSON
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
InvalidParams Text
"query actions cannot be explained"
RFRaw Value
_ -> EncJSON -> m EncJSON
forall (f :: * -> *) a. Applicative f => a -> f a
pure (EncJSON -> m EncJSON) -> EncJSON -> m EncJSON
forall a b. (a -> b) -> a -> b
$ ExplainPlan -> EncJSON
forall a. ToJSON a => a -> EncJSON
encJFromJValue (ExplainPlan -> EncJSON) -> ExplainPlan -> EncJSON
forall a b. (a -> b) -> a -> b
$ RootFieldAlias -> Maybe Text -> Maybe [Text] -> ExplainPlan
ExplainPlan RootFieldAlias
fieldName Maybe Text
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing
RFMulti [QueryRootField UnpreparedValue]
_ -> EncJSON -> m EncJSON
forall (f :: * -> *) a. Applicative f => a -> f a
pure (EncJSON -> m EncJSON) -> EncJSON -> m EncJSON
forall a b. (a -> b) -> a -> b
$ ExplainPlan -> EncJSON
forall a. ToJSON a => a -> EncJSON
encJFromJValue (ExplainPlan -> EncJSON) -> ExplainPlan -> EncJSON
forall a b. (a -> b) -> a -> b
$ RootFieldAlias -> Maybe Text -> Maybe [Text] -> ExplainPlan
ExplainPlan RootFieldAlias
fieldName Maybe Text
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing
RFDB SourceName
sourceName AnyBackend
(SourceConfigWith
(QueryDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue))
exists -> do
AnyBackend DBStepInfo
step <- AnyBackend
(SourceConfigWith
(QueryDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue))
-> (forall (b :: BackendType).
BackendExecute b =>
SourceConfigWith
(QueryDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue)
b
-> m (AnyBackend DBStepInfo))
-> m (AnyBackend DBStepInfo)
forall (c :: BackendType -> Constraint) (i :: BackendType -> *) r.
AllBackendsSatisfy c =>
AnyBackend i -> (forall (b :: BackendType). c b => i b -> r) -> r
AB.dispatchAnyBackend @BackendExecute
AnyBackend
(SourceConfigWith
(QueryDBRoot
(RemoteRelationshipField UnpreparedValue) UnpreparedValue))
exists
\(SourceConfigWith SourceConfig b
sourceConfig Maybe QueryTagsConfig
_ (QDBR QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
db)) -> do
let (QueryDB b Void (UnpreparedValue b)
newDB, Maybe RemoteJoins
remoteJoins) = QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> (QueryDB b Void (UnpreparedValue b), Maybe RemoteJoins)
forall (b :: BackendType).
Backend b =>
QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> (QueryDB b Void (UnpreparedValue b), Maybe RemoteJoins)
RJ.getRemoteJoinsQueryDB QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
db
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Maybe RemoteJoins -> Bool
forall a. Maybe a -> Bool
isNothing Maybe RemoteJoins
remoteJoins) (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
InvalidParams Text
"queries with remote relationships cannot be explained"
RootFieldAlias
-> UserInfo
-> SourceName
-> SourceConfig b
-> QueryDB b Void (UnpreparedValue b)
-> m (AnyBackend DBStepInfo)
forall (b :: BackendType) (m :: * -> *).
(BackendExecute b, MonadError QErr m) =>
RootFieldAlias
-> UserInfo
-> SourceName
-> SourceConfig b
-> QueryDB b Void (UnpreparedValue b)
-> m (AnyBackend DBStepInfo)
mkDBQueryExplain RootFieldAlias
fieldName UserInfo
userInfo SourceName
sourceName SourceConfig b
sourceConfig QueryDB b Void (UnpreparedValue b)
newDB
AnyBackend DBStepInfo
-> (forall (b :: BackendType).
BackendTransport b =>
DBStepInfo b -> m EncJSON)
-> m EncJSON
forall (c :: BackendType -> Constraint) (i :: BackendType -> *) r.
AllBackendsSatisfy c =>
AnyBackend i -> (forall (b :: BackendType). c b => i b -> r) -> r
AB.dispatchAnyBackend @BackendTransport AnyBackend DBStepInfo
step forall (b :: BackendType).
BackendTransport b =>
DBStepInfo b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(BackendTransport b, MonadIO m, MonadError QErr m) =>
DBStepInfo b -> m EncJSON
runDBQueryExplain
explainGQLQuery ::
forall m.
( MonadError QErr m,
MonadIO m,
MonadBaseControl IO m,
MonadMetadataStorage (MetadataStorageT m),
MonadQueryTags m
) =>
SchemaCache ->
GQLExplain ->
m EncJSON
explainGQLQuery :: SchemaCache -> GQLExplain -> m EncJSON
explainGQLQuery SchemaCache
sc (GQLExplain GQLReqParsed
query Maybe (HashMap Text Text)
userVarsRaw Maybe Bool
maybeIsRelay) = do
UserInfo
userInfo <-
UserRoleBuild -> UserAdminSecret -> SessionVariables -> m UserInfo
forall (m :: * -> *).
MonadError QErr m =>
UserRoleBuild -> UserAdminSecret -> SessionVariables -> m UserInfo
mkUserInfo
(RoleName -> UserRoleBuild
URBFromSessionVariablesFallback RoleName
adminRoleName)
UserAdminSecret
UAdminSecretSent
SessionVariables
sessionVariables
let graphQLContext :: GQLContext
graphQLContext = UserInfo -> SchemaCache -> GraphQLQueryType -> GQLContext
E.makeGQLContext UserInfo
userInfo SchemaCache
sc GraphQLQueryType
queryType
SingleOperation
queryParts <- GQLReqParsed -> m SingleOperation
forall (m :: * -> *).
MonadError QErr m =>
GQLReqParsed -> m SingleOperation
GH.getSingleOperation GQLReqParsed
query
case SingleOperation
queryParts of
G.TypedOperationDefinition OperationType
G.OperationTypeQuery Maybe Name
_ [VariableDefinition]
varDefs [Directive Name]
directives SelectionSet NoFragments Name
inlinedSelSet -> do
(RootFieldMap (QueryRootField UnpreparedValue)
unpreparedQueries, [Directive Variable]
_, SelectionSet NoFragments Variable
_) <-
GQLContext
-> [VariableDefinition]
-> Maybe (HashMap Name Value)
-> [Directive Name]
-> SelectionSet NoFragments Name
-> m (RootFieldMap (QueryRootField UnpreparedValue),
[Directive Variable], SelectionSet NoFragments Variable)
forall (m :: * -> *).
MonadError QErr m =>
GQLContext
-> [VariableDefinition]
-> Maybe (HashMap Name Value)
-> [Directive Name]
-> SelectionSet NoFragments Name
-> m (RootFieldMap (QueryRootField UnpreparedValue),
[Directive Variable], SelectionSet NoFragments Variable)
E.parseGraphQLQuery GQLContext
graphQLContext [VariableDefinition]
varDefs (GQLReqParsed -> Maybe (HashMap Name Value)
forall a. GQLReq a -> Maybe (HashMap Name Value)
GH._grVariables GQLReqParsed
query) [Directive Name]
directives SelectionSet NoFragments Name
inlinedSelSet
[EncJSON] -> EncJSON
encJFromList
([EncJSON] -> EncJSON) -> m [EncJSON] -> m EncJSON
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(RootFieldAlias, QueryRootField UnpreparedValue)]
-> ((RootFieldAlias, QueryRootField UnpreparedValue) -> m EncJSON)
-> m [EncJSON]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (RootFieldMap (QueryRootField UnpreparedValue)
-> [(RootFieldAlias, QueryRootField UnpreparedValue)]
forall k v. InsOrdHashMap k v -> [(k, v)]
OMap.toList RootFieldMap (QueryRootField UnpreparedValue)
unpreparedQueries) ((RootFieldAlias -> QueryRootField UnpreparedValue -> m EncJSON)
-> (RootFieldAlias, QueryRootField UnpreparedValue) -> m EncJSON
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (UserInfo
-> RootFieldAlias -> QueryRootField UnpreparedValue -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, MonadIO m) =>
UserInfo
-> RootFieldAlias -> QueryRootField UnpreparedValue -> m EncJSON
explainQueryField UserInfo
userInfo))
G.TypedOperationDefinition OperationType
G.OperationTypeMutation Maybe Name
_ [VariableDefinition]
_ [Directive Name]
_ SelectionSet NoFragments Name
_ ->
Code -> Text -> m EncJSON
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
InvalidParams Text
"only queries can be explained"
G.TypedOperationDefinition OperationType
G.OperationTypeSubscription Maybe Name
_ [VariableDefinition]
varDefs [Directive Name]
directives SelectionSet NoFragments Name
inlinedSelSet -> do
([Directive Variable]
_normalizedDirectives, SelectionSet NoFragments Variable
normalizedSelectionSet) <-
[VariableDefinition]
-> HashMap Name Value
-> [Directive Name]
-> SelectionSet NoFragments Name
-> m ([Directive Variable], SelectionSet NoFragments Variable)
forall (m :: * -> *) (fragments :: * -> *).
(MonadError QErr m, Traversable fragments) =>
[VariableDefinition]
-> HashMap Name Value
-> [Directive Name]
-> SelectionSet fragments Name
-> m ([Directive Variable], SelectionSet fragments Variable)
ER.resolveVariables
[VariableDefinition]
varDefs
(HashMap Name Value
-> Maybe (HashMap Name Value) -> HashMap Name Value
forall a. a -> Maybe a -> a
fromMaybe HashMap Name Value
forall a. Monoid a => a
mempty (GQLReqParsed -> Maybe (HashMap Name Value)
forall a. GQLReq a -> Maybe (HashMap Name Value)
GH._grVariables GQLReqParsed
query))
[Directive Name]
directives
SelectionSet NoFragments Name
inlinedSelSet
ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
subscriptionParser <- GQLContext
-> Maybe (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
C.gqlSubscriptionParser GQLContext
graphQLContext Maybe (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
-> m (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` Code
-> Text
-> m (ParserFn (RootFieldMap (QueryRootField UnpreparedValue)))
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotFound Text
"no subscriptions found"
RootFieldMap (QueryRootField UnpreparedValue)
unpreparedQueries <- Either QErr (RootFieldMap (QueryRootField UnpreparedValue))
-> m (RootFieldMap (QueryRootField UnpreparedValue))
forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither (Either QErr (RootFieldMap (QueryRootField UnpreparedValue))
-> m (RootFieldMap (QueryRootField UnpreparedValue)))
-> Either QErr (RootFieldMap (QueryRootField UnpreparedValue))
-> m (RootFieldMap (QueryRootField UnpreparedValue))
forall a b. (a -> b) -> a -> b
$ ParserFn (RootFieldMap (QueryRootField UnpreparedValue))
subscriptionParser SelectionSet NoFragments Variable
normalizedSelectionSet
let parameterizedQueryHash :: ParameterizedQueryHash
parameterizedQueryHash = SelectionSet NoFragments Variable -> ParameterizedQueryHash
calculateParameterizedQueryHash SelectionSet NoFragments Variable
normalizedSelectionSet
SubscriptionExecution
validSubscription <- UserInfo
-> RootFieldMap (QueryRootField UnpreparedValue)
-> ParameterizedQueryHash
-> m SubscriptionExecution
forall (m :: * -> *).
(MonadError QErr m, MonadQueryTags m, MonadIO m,
MonadBaseControl IO m) =>
UserInfo
-> RootFieldMap (QueryRootField UnpreparedValue)
-> ParameterizedQueryHash
-> m SubscriptionExecution
E.buildSubscriptionPlan UserInfo
userInfo RootFieldMap (QueryRootField UnpreparedValue)
unpreparedQueries ParameterizedQueryHash
parameterizedQueryHash
case SubscriptionExecution
validSubscription of
E.SEAsyncActionsWithNoRelationships RootFieldMap (ActionId, ActionLogResponse -> Either QErr EncJSON)
_ -> Code -> Text -> m EncJSON
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotSupported Text
"async action query fields without relationships to table cannot be explained"
E.SEOnSourceDB (E.SSLivequery HashSet ActionId
actionIds ActionLogResponseMap
-> ExceptT QErr IO (SourceName, SubscriptionQueryPlan)
liveQueryBuilder) -> do
ActionLogResponseMap
actionLogResponseMap <- (ActionLogResponseMap, Bool) -> ActionLogResponseMap
forall a b. (a, b) -> a
fst ((ActionLogResponseMap, Bool) -> ActionLogResponseMap)
-> m (ActionLogResponseMap, Bool) -> m ActionLogResponseMap
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HashSet ActionId -> m (ActionLogResponseMap, Bool)
forall (m :: * -> *) (t :: * -> *).
(MonadError QErr m, MonadMetadataStorage (MetadataStorageT m),
Foldable t) =>
t ActionId -> m (ActionLogResponseMap, Bool)
E.fetchActionLogResponses HashSet ActionId
actionIds
(SourceName
_, E.SubscriptionQueryPlan AnyBackend MultiplexedSubscriptionQueryPlan
exists) <- m (Either QErr (SourceName, SubscriptionQueryPlan))
-> m (SourceName, SubscriptionQueryPlan)
forall e (m :: * -> *) a. MonadError e m => m (Either e a) -> m a
liftEitherM (m (Either QErr (SourceName, SubscriptionQueryPlan))
-> m (SourceName, SubscriptionQueryPlan))
-> m (Either QErr (SourceName, SubscriptionQueryPlan))
-> m (SourceName, SubscriptionQueryPlan)
forall a b. (a -> b) -> a -> b
$ IO (Either QErr (SourceName, SubscriptionQueryPlan))
-> m (Either QErr (SourceName, SubscriptionQueryPlan))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either QErr (SourceName, SubscriptionQueryPlan))
-> m (Either QErr (SourceName, SubscriptionQueryPlan)))
-> IO (Either QErr (SourceName, SubscriptionQueryPlan))
-> m (Either QErr (SourceName, SubscriptionQueryPlan))
forall a b. (a -> b) -> a -> b
$ ExceptT QErr IO (SourceName, SubscriptionQueryPlan)
-> IO (Either QErr (SourceName, SubscriptionQueryPlan))
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT QErr IO (SourceName, SubscriptionQueryPlan)
-> IO (Either QErr (SourceName, SubscriptionQueryPlan)))
-> ExceptT QErr IO (SourceName, SubscriptionQueryPlan)
-> IO (Either QErr (SourceName, SubscriptionQueryPlan))
forall a b. (a -> b) -> a -> b
$ ActionLogResponseMap
-> ExceptT QErr IO (SourceName, SubscriptionQueryPlan)
liveQueryBuilder ActionLogResponseMap
actionLogResponseMap
AnyBackend MultiplexedSubscriptionQueryPlan
-> (forall (b :: BackendType).
BackendExecute b =>
MultiplexedSubscriptionQueryPlan b -> m EncJSON)
-> m EncJSON
forall (c :: BackendType -> Constraint) (i :: BackendType -> *) r.
AllBackendsSatisfy c =>
AnyBackend i -> (forall (b :: BackendType). c b => i b -> r) -> r
AB.dispatchAnyBackend @BackendExecute AnyBackend MultiplexedSubscriptionQueryPlan
exists \(E.MultiplexedSubscriptionQueryPlan SubscriptionQueryPlan b (MultiplexedQuery b)
execPlan) ->
SubscriptionQueryPlanExplanation -> EncJSON
forall a. ToJSON a => a -> EncJSON
encJFromJValue (SubscriptionQueryPlanExplanation -> EncJSON)
-> m SubscriptionQueryPlanExplanation -> m EncJSON
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SubscriptionQueryPlan b (MultiplexedQuery b)
-> m SubscriptionQueryPlanExplanation
forall (b :: BackendType) (m :: * -> *).
(BackendExecute b, MonadError QErr m, MonadIO m,
MonadBaseControl IO m) =>
SubscriptionQueryPlan b (MultiplexedQuery b)
-> m SubscriptionQueryPlanExplanation
mkSubscriptionExplain SubscriptionQueryPlan b (MultiplexedQuery b)
execPlan
E.SEOnSourceDB (E.SSStreaming RootFieldAlias
_ (SourceName
_, E.SubscriptionQueryPlan AnyBackend MultiplexedSubscriptionQueryPlan
exists)) -> do
AnyBackend MultiplexedSubscriptionQueryPlan
-> (forall (b :: BackendType).
BackendExecute b =>
MultiplexedSubscriptionQueryPlan b -> m EncJSON)
-> m EncJSON
forall (c :: BackendType -> Constraint) (i :: BackendType -> *) r.
AllBackendsSatisfy c =>
AnyBackend i -> (forall (b :: BackendType). c b => i b -> r) -> r
AB.dispatchAnyBackend @BackendExecute AnyBackend MultiplexedSubscriptionQueryPlan
exists \(E.MultiplexedSubscriptionQueryPlan SubscriptionQueryPlan b (MultiplexedQuery b)
execPlan) ->
SubscriptionQueryPlanExplanation -> EncJSON
forall a. ToJSON a => a -> EncJSON
encJFromJValue (SubscriptionQueryPlanExplanation -> EncJSON)
-> m SubscriptionQueryPlanExplanation -> m EncJSON
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SubscriptionQueryPlan b (MultiplexedQuery b)
-> m SubscriptionQueryPlanExplanation
forall (b :: BackendType) (m :: * -> *).
(BackendExecute b, MonadError QErr m, MonadIO m,
MonadBaseControl IO m) =>
SubscriptionQueryPlan b (MultiplexedQuery b)
-> m SubscriptionQueryPlanExplanation
mkSubscriptionExplain SubscriptionQueryPlan b (MultiplexedQuery b)
execPlan
where
queryType :: GraphQLQueryType
queryType = GraphQLQueryType -> GraphQLQueryType -> Bool -> GraphQLQueryType
forall a. a -> a -> Bool -> a
bool GraphQLQueryType
E.QueryHasura GraphQLQueryType
E.QueryRelay (Bool -> GraphQLQueryType) -> Bool -> GraphQLQueryType
forall a b. (a -> b) -> a -> b
$ Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe Bool
maybeIsRelay
sessionVariables :: SessionVariables
sessionVariables = HashMap Text Text -> SessionVariables
mkSessionVariablesText (HashMap Text Text -> SessionVariables)
-> HashMap Text Text -> SessionVariables
forall a b. (a -> b) -> a -> b
$ HashMap Text Text -> Maybe (HashMap Text Text) -> HashMap Text Text
forall a. a -> Maybe a -> a
fromMaybe HashMap Text Text
forall a. Monoid a => a
mempty Maybe (HashMap Text Text)
userVarsRaw