2022-04-22 16:38:35 +03:00
|
|
|
-- | Stuff gutted from Translate.Select.
|
2022-04-22 20:18:20 +03:00
|
|
|
module Hasura.Backends.Postgres.Translate.Select.Internal.Helpers
|
|
|
|
( mkFirstElementExp,
|
|
|
|
mkLastElementExp,
|
|
|
|
cursorIdentifier,
|
|
|
|
startCursorIdentifier,
|
|
|
|
endCursorIdentifier,
|
|
|
|
hasNextPageIdentifier,
|
|
|
|
hasPreviousPageIdentifier,
|
2022-10-05 13:03:36 +03:00
|
|
|
pageInfoSelectAlias,
|
2022-04-22 20:18:20 +03:00
|
|
|
pageInfoSelectAliasIdentifier,
|
2022-10-05 13:03:36 +03:00
|
|
|
cursorsSelectAlias,
|
2022-04-22 20:18:20 +03:00
|
|
|
cursorsSelectAliasIdentifier,
|
|
|
|
encodeBase64,
|
|
|
|
fromTableRowArgs,
|
|
|
|
selectFromToFromItem,
|
|
|
|
functionToIdentifier,
|
|
|
|
withJsonBuildObj,
|
|
|
|
withForceAggregation,
|
2023-01-27 17:36:35 +03:00
|
|
|
selectToSelectWith,
|
|
|
|
customSQLToTopLevelCTEs,
|
2023-02-28 14:17:08 +03:00
|
|
|
customSQLToInnerCTEs,
|
2023-04-13 19:10:38 +03:00
|
|
|
nativeQueryNameToAlias,
|
2023-01-27 17:36:35 +03:00
|
|
|
toQuery,
|
2022-04-22 20:18:20 +03:00
|
|
|
)
|
|
|
|
where
|
2022-04-22 16:38:35 +03:00
|
|
|
|
2023-01-27 17:36:35 +03:00
|
|
|
import Control.Monad.Writer (Writer, runWriter)
|
|
|
|
import Data.Bifunctor (bimap)
|
2023-04-26 18:42:13 +03:00
|
|
|
import Data.HashMap.Strict qualified as HashMap
|
2023-02-08 18:46:09 +03:00
|
|
|
import Data.Text.Extended (toTxt)
|
2023-01-27 17:36:35 +03:00
|
|
|
import Database.PG.Query (Query, fromBuilder)
|
2022-04-22 16:38:35 +03:00
|
|
|
import Hasura.Backends.Postgres.SQL.DML qualified as S
|
2023-01-27 17:36:35 +03:00
|
|
|
import Hasura.Backends.Postgres.SQL.RenameIdentifiers
|
2022-10-11 13:42:15 +03:00
|
|
|
import Hasura.Backends.Postgres.SQL.Types
|
|
|
|
( Identifier (..),
|
|
|
|
QualifiedFunction,
|
|
|
|
TableIdentifier (..),
|
|
|
|
qualifiedObjectToText,
|
|
|
|
tableIdentifierToIdentifier,
|
|
|
|
)
|
2022-04-22 20:18:20 +03:00
|
|
|
import Hasura.Backends.Postgres.Translate.Select.Internal.Aliases
|
2023-01-27 17:36:35 +03:00
|
|
|
import Hasura.Backends.Postgres.Translate.Types (CustomSQLCTEs (..))
|
2022-05-25 13:24:41 +03:00
|
|
|
import Hasura.Backends.Postgres.Types.Function
|
2023-04-03 13:18:54 +03:00
|
|
|
import Hasura.Function.Cache
|
2023-04-13 19:10:38 +03:00
|
|
|
import Hasura.NativeQuery.IR (NativeQuery (..))
|
|
|
|
import Hasura.NativeQuery.Metadata (NativeQueryName (..))
|
2022-04-22 16:38:35 +03:00
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.IR
|
2023-04-24 21:35:48 +03:00
|
|
|
import Hasura.RQL.Types.BackendType
|
2022-04-22 16:38:35 +03:00
|
|
|
import Hasura.RQL.Types.Common (FieldName)
|
2023-01-27 17:36:35 +03:00
|
|
|
import Hasura.SQL.Types (ToSQL (toSQL))
|
2022-04-22 16:38:35 +03:00
|
|
|
|
|
|
|
-- | First element extractor expression from given record set
|
|
|
|
-- For example:- To get first "id" column from given row set,
|
|
|
|
-- the function generates the SQL expression AS `(array_agg("id"))[1]`
|
|
|
|
mkFirstElementExp :: S.SQLExp -> S.SQLExp
|
|
|
|
mkFirstElementExp expIdentifier =
|
|
|
|
-- For Example
|
|
|
|
S.SEArrayIndex (S.SEFnApp "array_agg" [expIdentifier] Nothing) (S.intToSQLExp 1)
|
|
|
|
|
|
|
|
-- | Last element extractor expression from given record set.
|
|
|
|
-- For example:- To get first "id" column from given row set,
|
|
|
|
-- the function generates the SQL expression AS `(array_agg("id"))[array_length(array_agg("id"), 1)]`
|
|
|
|
mkLastElementExp :: S.SQLExp -> S.SQLExp
|
|
|
|
mkLastElementExp expIdentifier =
|
|
|
|
let arrayExp = S.SEFnApp "array_agg" [expIdentifier] Nothing
|
|
|
|
in S.SEArrayIndex arrayExp $
|
|
|
|
S.SEFnApp "array_length" [arrayExp, S.intToSQLExp 1] Nothing
|
|
|
|
|
|
|
|
cursorIdentifier :: Identifier
|
|
|
|
cursorIdentifier = Identifier "__cursor"
|
|
|
|
|
|
|
|
startCursorIdentifier :: Identifier
|
|
|
|
startCursorIdentifier = Identifier "__start_cursor"
|
|
|
|
|
|
|
|
endCursorIdentifier :: Identifier
|
|
|
|
endCursorIdentifier = Identifier "__end_cursor"
|
|
|
|
|
|
|
|
hasPreviousPageIdentifier :: Identifier
|
|
|
|
hasPreviousPageIdentifier = Identifier "__has_previous_page"
|
|
|
|
|
|
|
|
hasNextPageIdentifier :: Identifier
|
|
|
|
hasNextPageIdentifier = Identifier "__has_next_page"
|
|
|
|
|
2022-10-05 13:03:36 +03:00
|
|
|
pageInfoSelectAlias :: S.TableAlias
|
|
|
|
pageInfoSelectAlias = S.mkTableAlias "__page_info"
|
2022-04-22 16:38:35 +03:00
|
|
|
|
2022-10-05 13:03:36 +03:00
|
|
|
pageInfoSelectAliasIdentifier :: TableIdentifier
|
|
|
|
pageInfoSelectAliasIdentifier = S.tableAliasToIdentifier pageInfoSelectAlias
|
|
|
|
|
|
|
|
cursorsSelectAlias :: S.TableAlias
|
|
|
|
cursorsSelectAlias = S.mkTableAlias "__cursors_select"
|
|
|
|
|
|
|
|
cursorsSelectAliasIdentifier :: TableIdentifier
|
|
|
|
cursorsSelectAliasIdentifier = S.tableAliasToIdentifier cursorsSelectAlias
|
2022-04-22 16:38:35 +03:00
|
|
|
|
|
|
|
encodeBase64 :: S.SQLExp -> S.SQLExp
|
|
|
|
encodeBase64 =
|
|
|
|
removeNewline . bytesToBase64Text . convertToBytes
|
|
|
|
where
|
|
|
|
convertToBytes e =
|
|
|
|
S.SEFnApp "convert_to" [e, S.SELit "UTF8"] Nothing
|
|
|
|
bytesToBase64Text e =
|
|
|
|
S.SEFnApp "encode" [e, S.SELit "base64"] Nothing
|
|
|
|
removeNewline e =
|
|
|
|
S.SEFnApp "regexp_replace" [e, S.SELit "\\n", S.SELit "", S.SELit "g"] Nothing
|
|
|
|
|
|
|
|
fromTableRowArgs ::
|
2022-10-11 13:42:15 +03:00
|
|
|
TableIdentifier -> FunctionArgsExpG (ArgumentExp S.SQLExp) -> S.FunctionArgs
|
2022-04-22 16:38:35 +03:00
|
|
|
fromTableRowArgs prefix = toFunctionArgs . fmap toSQLExp
|
|
|
|
where
|
|
|
|
toFunctionArgs (FunctionArgsExp positional named) =
|
|
|
|
S.FunctionArgs positional named
|
|
|
|
toSQLExp =
|
|
|
|
onArgumentExp
|
2022-10-11 13:42:15 +03:00
|
|
|
(S.SERowIdentifier (tableIdentifierToIdentifier baseTableIdentifier))
|
|
|
|
(S.mkQIdenExp baseTableIdentifier . Identifier)
|
|
|
|
baseTableIdentifier = mkBaseTableIdentifier prefix
|
2022-04-22 16:38:35 +03:00
|
|
|
|
2022-10-11 13:42:15 +03:00
|
|
|
selectFromToFromItem :: TableIdentifier -> SelectFrom ('Postgres pgKind) -> S.FromItem
|
2022-10-05 13:03:36 +03:00
|
|
|
selectFromToFromItem prefix = \case
|
2022-04-22 16:38:35 +03:00
|
|
|
FromTable tn -> S.FISimple tn Nothing
|
2022-10-05 13:03:36 +03:00
|
|
|
FromIdentifier i -> S.FIIdentifier $ TableIdentifier $ unFIIdentifier i
|
2022-04-22 16:38:35 +03:00
|
|
|
FromFunction qf args defListM ->
|
|
|
|
S.FIFunc $
|
2022-10-05 13:03:36 +03:00
|
|
|
S.FunctionExp qf (fromTableRowArgs prefix args) $
|
2022-07-22 18:27:42 +03:00
|
|
|
Just $
|
|
|
|
S.mkFunctionAlias
|
2022-10-05 13:03:36 +03:00
|
|
|
qf
|
2022-07-22 18:27:42 +03:00
|
|
|
(fmap (fmap (first S.toColumnAlias)) defListM)
|
2023-04-27 17:02:55 +03:00
|
|
|
FromStoredProcedure {} -> error "selectFromToFromItem: FromStoredProcedure"
|
2023-04-13 19:10:38 +03:00
|
|
|
FromNativeQuery lm ->
|
|
|
|
S.FIIdentifier (S.tableAliasToIdentifier $ nativeQueryNameToAlias (nqRootFieldName lm))
|
2023-01-27 17:36:35 +03:00
|
|
|
|
2023-04-13 19:10:38 +03:00
|
|
|
-- | Given a @NativeQueryName@, what should we call the CTE generated for it?
|
|
|
|
nativeQueryNameToAlias :: NativeQueryName -> S.TableAlias
|
|
|
|
nativeQueryNameToAlias nqName = S.mkTableAlias ("cte_" <> toTxt (getNativeQueryName nqName))
|
2022-04-22 16:38:35 +03:00
|
|
|
|
|
|
|
-- | Converts a function name to an 'Identifier'.
|
|
|
|
--
|
|
|
|
-- If the schema name is public, it will just use its name, otherwise it will
|
|
|
|
-- prefix it by the schema name.
|
|
|
|
functionToIdentifier :: QualifiedFunction -> Identifier
|
|
|
|
functionToIdentifier = Identifier . qualifiedObjectToText
|
|
|
|
|
|
|
|
-- uses json_build_object to build a json object
|
|
|
|
withJsonBuildObj ::
|
2022-07-18 12:44:17 +03:00
|
|
|
FieldName -> [S.SQLExp] -> (S.ColumnAlias, S.SQLExp)
|
2022-04-22 16:38:35 +03:00
|
|
|
withJsonBuildObj parAls exps =
|
2022-07-18 12:44:17 +03:00
|
|
|
(S.toColumnAlias parAls, jsonRow)
|
2022-04-22 16:38:35 +03:00
|
|
|
where
|
|
|
|
jsonRow = S.applyJsonBuildObj exps
|
|
|
|
|
|
|
|
-- | Forces aggregation
|
|
|
|
withForceAggregation :: S.TypeAnn -> S.SQLExp -> S.SQLExp
|
|
|
|
withForceAggregation tyAnn e =
|
|
|
|
-- bool_or to force aggregation
|
|
|
|
S.SEFnApp "coalesce" [e, S.SETyAnn (S.SEUnsafe "bool_or('true')") tyAnn] Nothing
|
2023-01-27 17:36:35 +03:00
|
|
|
|
|
|
|
-- | unwrap any emitted TopLevelCTEs for custom sql from the Writer and combine
|
|
|
|
-- them with a @Select@ to create a @SelectWith@
|
|
|
|
selectToSelectWith :: Writer CustomSQLCTEs S.Select -> S.SelectWith
|
|
|
|
selectToSelectWith action =
|
|
|
|
let (selectSQL, customSQLCTEs) = runWriter action
|
|
|
|
in S.SelectWith (customSQLToTopLevelCTEs customSQLCTEs) selectSQL
|
|
|
|
|
|
|
|
-- | convert map of CustomSQL CTEs into named TopLevelCTEs
|
|
|
|
customSQLToTopLevelCTEs :: CustomSQLCTEs -> [(S.TableAlias, S.TopLevelCTE)]
|
|
|
|
customSQLToTopLevelCTEs =
|
2023-04-26 18:42:13 +03:00
|
|
|
fmap (bimap S.toTableAlias S.CTEUnsafeRawSQL) . HashMap.toList . getCustomSQLCTEs
|
2023-01-27 17:36:35 +03:00
|
|
|
|
2023-02-28 14:17:08 +03:00
|
|
|
-- | convert map of CustomSQL CTEs into named InnerCTEs
|
|
|
|
customSQLToInnerCTEs :: CustomSQLCTEs -> [(S.TableAlias, S.InnerCTE)]
|
|
|
|
customSQLToInnerCTEs =
|
2023-04-26 18:42:13 +03:00
|
|
|
fmap (bimap S.toTableAlias S.ICTEUnsafeRawSQL) . HashMap.toList . getCustomSQLCTEs
|
2023-02-28 14:17:08 +03:00
|
|
|
|
2023-01-27 17:36:35 +03:00
|
|
|
toQuery :: S.SelectWithG S.TopLevelCTE -> Query
|
|
|
|
toQuery = fromBuilder . toSQL . renameIdentifiersSelectWithTopLevelCTE
|