mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-19 05:21:47 +03:00
1dbdb0236c
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4579 GitOrigin-RevId: 84da015123a53124488b88ce66bde26113625754
47 lines
1.5 KiB
Haskell
47 lines
1.5 KiB
Haskell
{-# LANGUAGE DeriveAnyClass #-}
|
|
|
|
module Hasura.Backends.DataConnector.IR.Export
|
|
( QueryError (..),
|
|
queryToAPI,
|
|
)
|
|
where
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
import Data.Aeson (ToJSON)
|
|
import Data.HashMap.Strict qualified as M
|
|
import Hasura.Backends.DataConnector.API qualified as API
|
|
import Hasura.Backends.DataConnector.IR.Query qualified as IR.Q
|
|
import Hasura.Prelude
|
|
import Witch qualified
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
data QueryError = ExposedLiteral Text
|
|
deriving stock (Generic)
|
|
deriving anyclass (ToJSON)
|
|
|
|
queryToAPI :: IR.Q.Query -> Either QueryError API.Query
|
|
queryToAPI IR.Q.Query {..} = do
|
|
fields' <- traverse fromField fields
|
|
pure $
|
|
API.Query
|
|
{ fields = fields',
|
|
from = Witch.from from,
|
|
limit = limit,
|
|
offset = offset,
|
|
where_ = fmap Witch.from where_,
|
|
orderBy = nonEmpty $ fmap Witch.from orderBy
|
|
}
|
|
|
|
fromField :: IR.Q.Field -> Either QueryError API.Field
|
|
fromField = \case
|
|
IR.Q.Column contents -> Right $ Witch.from contents
|
|
IR.Q.Relationship contents -> rcToAPI contents
|
|
IR.Q.Literal lit -> Left $ ExposedLiteral lit
|
|
|
|
rcToAPI :: IR.Q.RelationshipContents -> Either QueryError API.Field
|
|
rcToAPI (IR.Q.RelationshipContents joinCondition query) =
|
|
let joinCondition' = M.mapKeys Witch.from $ fmap Witch.from joinCondition
|
|
in fmap (API.RelationshipField . API.RelField joinCondition') $ queryToAPI query
|