module Hasura.Backends.Postgres.Translate.Select.Connection
( connectionSelectQuerySQL,
mkConnectionSelect,
)
where
import Control.Monad.Writer (runWriter)
import Database.PG.Query (Query)
import Hasura.Backends.Postgres.SQL.DML qualified as S
import Hasura.Backends.Postgres.SQL.Types
import Hasura.Backends.Postgres.Translate.Select.AnnotatedFieldJSON
import Hasura.Backends.Postgres.Translate.Select.Internal.GenerateSelect (connectionToSelectWith)
import Hasura.Backends.Postgres.Translate.Select.Internal.Helpers (customSQLToTopLevelCTEs, toQuery)
import Hasura.Backends.Postgres.Translate.Select.Internal.Process (processConnectionSelect)
import Hasura.Backends.Postgres.Translate.Types
import Hasura.Prelude
import Hasura.RQL.IR.Select
( AnnSelectG (_asnStrfyNum),
ConnectionSelect (_csSelect),
)
import Hasura.RQL.Types.Backend (Backend)
import Hasura.RQL.Types.BackendType (BackendType (Postgres))
import Hasura.RQL.Types.Common (FieldName (FieldName))
connectionSelectQuerySQL ::
forall pgKind.
( Backend ('Postgres pgKind),
PostgresAnnotatedFieldJSON pgKind
) =>
ConnectionSelect ('Postgres pgKind) Void S.SQLExp ->
Query
connectionSelectQuerySQL :: forall (pgKind :: PostgresKind).
(Backend ('Postgres pgKind), PostgresAnnotatedFieldJSON pgKind) =>
ConnectionSelect ('Postgres pgKind) Void SQLExp -> Query
connectionSelectQuerySQL =
SelectWithG TopLevelCTE -> Query
toQuery
(SelectWithG TopLevelCTE -> Query)
-> (ConnectionSelect ('Postgres pgKind) Void SQLExp
-> SelectWithG TopLevelCTE)
-> ConnectionSelect ('Postgres pgKind) Void SQLExp
-> Query
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ( \(SelectWithG Select
selectWith, CustomSQLCTEs
customCTEs) ->
SelectWithG Select
selectWith
{ swCTEs :: [(TableAlias, TopLevelCTE)]
S.swCTEs =
((TableAlias, Select) -> (TableAlias, TopLevelCTE))
-> [(TableAlias, Select)] -> [(TableAlias, TopLevelCTE)]
forall a b. (a -> b) -> [a] -> [b]
map ((Select -> TopLevelCTE)
-> (TableAlias, Select) -> (TableAlias, TopLevelCTE)
forall a b. (a -> b) -> (TableAlias, a) -> (TableAlias, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Select -> TopLevelCTE
S.CTESelect) (SelectWithG Select -> [(TableAlias, Select)]
forall statement.
SelectWithG statement -> [(TableAlias, statement)]
S.swCTEs SelectWithG Select
selectWith)
[(TableAlias, TopLevelCTE)]
-> [(TableAlias, TopLevelCTE)] -> [(TableAlias, TopLevelCTE)]
forall a. Semigroup a => a -> a -> a
<> CustomSQLCTEs -> [(TableAlias, TopLevelCTE)]
customSQLToTopLevelCTEs CustomSQLCTEs
customCTEs
}
)
((SelectWithG Select, CustomSQLCTEs) -> SelectWithG TopLevelCTE)
-> (ConnectionSelect ('Postgres pgKind) Void SQLExp
-> (SelectWithG Select, CustomSQLCTEs))
-> ConnectionSelect ('Postgres pgKind) Void SQLExp
-> SelectWithG TopLevelCTE
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Writer CustomSQLCTEs (SelectWithG Select)
-> (SelectWithG Select, CustomSQLCTEs)
forall w a. Writer w a -> (a, w)
runWriter
(Writer CustomSQLCTEs (SelectWithG Select)
-> (SelectWithG Select, CustomSQLCTEs))
-> (ConnectionSelect ('Postgres pgKind) Void SQLExp
-> Writer CustomSQLCTEs (SelectWithG Select))
-> ConnectionSelect ('Postgres pgKind) Void SQLExp
-> (SelectWithG Select, CustomSQLCTEs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConnectionSelect ('Postgres pgKind) Void SQLExp
-> Writer CustomSQLCTEs (SelectWithG Select)
forall (pgKind :: PostgresKind) (m :: * -> *).
(Backend ('Postgres pgKind), PostgresAnnotatedFieldJSON pgKind,
MonadWriter CustomSQLCTEs m) =>
ConnectionSelect ('Postgres pgKind) Void SQLExp
-> m (SelectWithG Select)
mkConnectionSelect
mkConnectionSelect ::
forall pgKind m.
( Backend ('Postgres pgKind),
PostgresAnnotatedFieldJSON pgKind,
MonadWriter CustomSQLCTEs m
) =>
ConnectionSelect ('Postgres pgKind) Void S.SQLExp ->
m (S.SelectWithG S.Select)
mkConnectionSelect :: forall (pgKind :: PostgresKind) (m :: * -> *).
(Backend ('Postgres pgKind), PostgresAnnotatedFieldJSON pgKind,
MonadWriter CustomSQLCTEs m) =>
ConnectionSelect ('Postgres pgKind) Void SQLExp
-> m (SelectWithG Select)
mkConnectionSelect ConnectionSelect ('Postgres pgKind) Void SQLExp
connectionSelect = do
let ( (ArrayConnectionSource
connectionSource, Extractor
topExtractor, InsOrdHashMap ColumnAlias SQLExp
nodeExtractors),
SelectWriter {_swJoinTree :: SelectWriter -> JoinTree
_swJoinTree = JoinTree
joinTree, _swCustomSQLCTEs :: SelectWriter -> CustomSQLCTEs
_swCustomSQLCTEs = CustomSQLCTEs
customSQLCTEs}
) =
Writer
SelectWriter
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
-> ((ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp),
SelectWriter)
forall w a. Writer w a -> (a, w)
runWriter
(Writer
SelectWriter
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
-> ((ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp),
SelectWriter))
-> Writer
SelectWriter
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
-> ((ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp),
SelectWriter)
forall a b. (a -> b) -> a -> b
$ (StateT
NativeQueryFreshIdStore
(WriterT SelectWriter Identity)
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
-> NativeQueryFreshIdStore
-> Writer
SelectWriter
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp))
-> NativeQueryFreshIdStore
-> StateT
NativeQueryFreshIdStore
(WriterT SelectWriter Identity)
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
-> Writer
SelectWriter
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
forall a b c. (a -> b -> c) -> b -> a -> c
flip StateT
NativeQueryFreshIdStore
(WriterT SelectWriter Identity)
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
-> NativeQueryFreshIdStore
-> Writer
SelectWriter
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT NativeQueryFreshIdStore
initialNativeQueryFreshIdStore
(StateT
NativeQueryFreshIdStore
(WriterT SelectWriter Identity)
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
-> Writer
SelectWriter
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp))
-> StateT
NativeQueryFreshIdStore
(WriterT SelectWriter Identity)
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
-> Writer
SelectWriter
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
forall a b. (a -> b) -> a -> b
$ (ReaderT
StringifyNumbers
(StateT NativeQueryFreshIdStore (WriterT SelectWriter Identity))
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
-> StringifyNumbers
-> StateT
NativeQueryFreshIdStore
(WriterT SelectWriter Identity)
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp))
-> StringifyNumbers
-> ReaderT
StringifyNumbers
(StateT NativeQueryFreshIdStore (WriterT SelectWriter Identity))
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
-> StateT
NativeQueryFreshIdStore
(WriterT SelectWriter Identity)
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT
StringifyNumbers
(StateT NativeQueryFreshIdStore (WriterT SelectWriter Identity))
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
-> StringifyNumbers
-> StateT
NativeQueryFreshIdStore
(WriterT SelectWriter Identity)
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT StringifyNumbers
strfyNum
(ReaderT
StringifyNumbers
(StateT NativeQueryFreshIdStore (WriterT SelectWriter Identity))
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
-> StateT
NativeQueryFreshIdStore
(WriterT SelectWriter Identity)
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp))
-> ReaderT
StringifyNumbers
(StateT NativeQueryFreshIdStore (WriterT SelectWriter Identity))
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
-> StateT
NativeQueryFreshIdStore
(WriterT SelectWriter Identity)
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
forall a b. (a -> b) -> a -> b
$ SourcePrefixes
-> FieldName
-> TableAlias
-> HashMap PGCol PGCol
-> ConnectionSelect ('Postgres pgKind) Void SQLExp
-> ReaderT
StringifyNumbers
(StateT NativeQueryFreshIdStore (WriterT SelectWriter Identity))
(ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
forall (pgKind :: PostgresKind) (m :: * -> *).
(MonadReader StringifyNumbers m, MonadWriter SelectWriter m,
MonadState NativeQueryFreshIdStore m, Backend ('Postgres pgKind),
PostgresAnnotatedFieldJSON pgKind) =>
SourcePrefixes
-> FieldName
-> TableAlias
-> HashMap PGCol PGCol
-> ConnectionSelect ('Postgres pgKind) Void SQLExp
-> m (ArrayConnectionSource, Extractor,
InsOrdHashMap ColumnAlias SQLExp)
processConnectionSelect
SourcePrefixes
sourcePrefixes
FieldName
rootFieldName
(Identifier -> TableAlias
forall a. IsIdentifier a => a -> TableAlias
S.toTableAlias Identifier
rootIdentifier)
HashMap PGCol PGCol
forall a. Monoid a => a
mempty
ConnectionSelect ('Postgres pgKind) Void SQLExp
connectionSelect
selectNode :: MultiRowSelectNode
selectNode =
[Extractor] -> SelectNode -> MultiRowSelectNode
MultiRowSelectNode [Extractor
topExtractor]
(SelectNode -> MultiRowSelectNode)
-> SelectNode -> MultiRowSelectNode
forall a b. (a -> b) -> a -> b
$ InsOrdHashMap ColumnAlias SQLExp -> JoinTree -> SelectNode
SelectNode InsOrdHashMap ColumnAlias SQLExp
nodeExtractors JoinTree
joinTree
selectWith :: SelectWithG Select
selectWith =
TableAlias
-> ArrayConnectionSource
-> MultiRowSelectNode
-> SelectWithG Select
connectionToSelectWith (Identifier -> TableAlias
forall a. IsIdentifier a => a -> TableAlias
S.toTableAlias Identifier
rootIdentifier) ArrayConnectionSource
connectionSource MultiRowSelectNode
selectNode
CustomSQLCTEs -> m ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell CustomSQLCTEs
customSQLCTEs
SelectWithG Select -> m (SelectWithG Select)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SelectWithG Select
selectWith
where
strfyNum :: StringifyNumbers
strfyNum = AnnSelectG
('Postgres pgKind) (ConnectionField ('Postgres pgKind) Void) SQLExp
-> StringifyNumbers
forall (b :: BackendType) (f :: * -> *) v.
AnnSelectG b f v -> StringifyNumbers
_asnStrfyNum (AnnSelectG
('Postgres pgKind) (ConnectionField ('Postgres pgKind) Void) SQLExp
-> StringifyNumbers)
-> AnnSelectG
('Postgres pgKind) (ConnectionField ('Postgres pgKind) Void) SQLExp
-> StringifyNumbers
forall a b. (a -> b) -> a -> b
$ ConnectionSelect ('Postgres pgKind) Void SQLExp
-> AnnSelectG
('Postgres pgKind) (ConnectionField ('Postgres pgKind) Void) SQLExp
forall (b :: BackendType) r v.
ConnectionSelect b r v -> AnnSelectG b (ConnectionField b r) v
_csSelect ConnectionSelect ('Postgres pgKind) Void SQLExp
connectionSelect
rootFieldName :: FieldName
rootFieldName = Text -> FieldName
FieldName Text
"root"
rootIdentifier :: Identifier
rootIdentifier = FieldName -> Identifier
forall a. IsIdentifier a => a -> Identifier
toIdentifier FieldName
rootFieldName
sourcePrefixes :: SourcePrefixes
sourcePrefixes = Identifier -> Identifier -> SourcePrefixes
SourcePrefixes Identifier
rootIdentifier Identifier
rootIdentifier