mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-18 04:51:35 +03:00
104 lines
3.8 KiB
Haskell
104 lines
3.8 KiB
Haskell
|
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||
|
|
||
|
-- | Stuff gutted from Translate.Select.
|
||
|
module Hasura.Backends.Postgres.Translate.Select.Aux1 where
|
||
|
|
||
|
import Hasura.Backends.Postgres.SQL.DML qualified as S
|
||
|
import Hasura.Backends.Postgres.SQL.Types (Identifier (..), QualifiedFunction, qualifiedObjectToText, toIdentifier)
|
||
|
import Hasura.Backends.Postgres.Translate.Select.Aliases
|
||
|
import Hasura.Prelude
|
||
|
import Hasura.RQL.IR
|
||
|
import Hasura.RQL.Types (BackendType (Postgres))
|
||
|
import Hasura.RQL.Types.Common (FieldName)
|
||
|
|
||
|
-- | 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"
|
||
|
|
||
|
pageInfoSelectAliasIdentifier :: Identifier
|
||
|
pageInfoSelectAliasIdentifier = Identifier "__page_info"
|
||
|
|
||
|
cursorsSelectAliasIdentifier :: Identifier
|
||
|
cursorsSelectAliasIdentifier = Identifier "__cursors_select"
|
||
|
|
||
|
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 ::
|
||
|
Identifier -> FunctionArgsExpTableRow S.SQLExp -> S.FunctionArgs
|
||
|
fromTableRowArgs prefix = toFunctionArgs . fmap toSQLExp
|
||
|
where
|
||
|
toFunctionArgs (FunctionArgsExp positional named) =
|
||
|
S.FunctionArgs positional named
|
||
|
toSQLExp =
|
||
|
onArgumentExp
|
||
|
(S.SERowIdentifier alias)
|
||
|
(S.mkQIdenExp alias . Identifier)
|
||
|
alias = mkBaseTableAlias prefix
|
||
|
|
||
|
selectFromToFromItem :: Identifier -> SelectFrom ('Postgres pgKind) -> S.FromItem
|
||
|
selectFromToFromItem pfx = \case
|
||
|
FromTable tn -> S.FISimple tn Nothing
|
||
|
FromIdentifier i -> S.FIIdentifier $ toIdentifier i
|
||
|
FromFunction qf args defListM ->
|
||
|
S.FIFunc $
|
||
|
S.FunctionExp qf (fromTableRowArgs pfx args) $
|
||
|
Just $ S.mkFunctionAlias (functionToIdentifier qf) defListM
|
||
|
|
||
|
-- | 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 ::
|
||
|
FieldName -> [S.SQLExp] -> (S.Alias, S.SQLExp)
|
||
|
withJsonBuildObj parAls exps =
|
||
|
(S.toAlias parAls, jsonRow)
|
||
|
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
|