这是indexloc提供的服务,不要输入任何密码
Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
55 changes: 42 additions & 13 deletions server/src-exec/Ops.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiWayIf #-}

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
Expand All @@ -12,6 +11,7 @@ module Ops
, execQuery
) where

import Data.Time.Clock (UTCTime)
import TH

import Hasura.Prelude
Expand All @@ -20,13 +20,12 @@ import Hasura.RQL.Types
import Hasura.Server.Query
import Hasura.SQL.Types

import qualified Database.PG.Query as Q

import Data.Time.Clock (UTCTime)
import qualified Data.Aeson as A
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T

import qualified Data.Aeson as A
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T
import qualified Database.PG.Query as Q
import qualified Database.PG.Query.Connection as Q

curCatalogVer :: T.Text
curCatalogVer = "2"
Expand Down Expand Up @@ -71,10 +70,18 @@ initCatalogStrict createSchema initTime = do
-- This is where the generated views and triggers are stored
Q.unitQ "CREATE SCHEMA hdb_views" () False

flExtExists <- isExtInstalled "first_last_agg"
case flExtExists of
True -> Q.unitQ "CREATE EXTENSION first_last_agg SCHEMA hdb_catalog" () False
False -> Q.multiQ $(Q.sqlFromFile "src-rsr/first_last.sql") >>= \(Q.Discard _) -> return ()
flExtExists <- isExtAvailable "first_last_agg"
if flExtExists
then Q.unitQ "CREATE EXTENSION first_last_agg SCHEMA hdb_catalog" () False
else Q.multiQ $(Q.sqlFromFile "src-rsr/first_last.sql") >>= \(Q.Discard _) -> return ()

pgcryptoExtExists <- Q.catchE defaultTxErrorHandler $ isExtAvailable "pgcrypto"
if pgcryptoExtExists
-- only if we created the schema, create the extension
then when createSchema $ Q.unitQE needsPgCryptoExt "CREATE EXTENSION IF NOT EXISTS pgcrypto" () False
else throw500 "FATAL: Could not find extension pgcrytpo. This extension is required."

Q.catchE defaultTxErrorHandler $ do
Q.Discard () <- Q.multiQ $(Q.sqlFromFile "src-rsr/initialise.sql")
return ()

Expand All @@ -85,14 +92,24 @@ initCatalogStrict createSchema initTime = do
void $ snd <$> tx
setAllAsSystemDefined >> addVersion initTime
return "initialise: successfully initialised"

where
needsPgCryptoExt :: Q.PGTxErr -> QErr
needsPgCryptoExt e@(Q.PGTxErr _ _ _ err) =
case err of
Q.PGIUnexpected _ -> (err500 PostgresError pgcryptoReqdMsg) { qeInternal = Just $ A.toJSON e }
Q.PGIStatement pgErr ->
case Q.edStatusCode pgErr of
Just "42501" -> err500 PostgresError pgcryptoPermsMsg
_ -> (err500 PostgresError pgcryptoReqdMsg) { qeInternal = Just $ A.toJSON e }

addVersion modTime = Q.catchE defaultTxErrorHandler $
Q.unitQ [Q.sql|
INSERT INTO "hdb_catalog"."hdb_version" VALUES ($1, $2)
|] (curCatalogVer, modTime) False

isExtInstalled :: T.Text -> Q.Tx Bool
isExtInstalled sn =
isExtAvailable :: T.Text -> Q.Tx Bool
isExtAvailable sn =
(runIdentity . Q.getRow) <$> Q.withQ [Q.sql|
SELECT EXISTS (
SELECT 1
Expand Down Expand Up @@ -201,3 +218,15 @@ execQuery queryBs = do
schemaCache <- buildSchemaCache
tx <- liftEither $ buildTxAny adminUserInfo schemaCache query
fst <$> tx


-- error messages
pgcryptoReqdMsg :: T.Text
pgcryptoReqdMsg =
"pgcrypto extension is required, but could not install; encountered postgres error"

pgcryptoPermsMsg :: T.Text
pgcryptoPermsMsg =
"pgcrypto extension is required, but current user doesn't have permission to create it. "
<> "Please grant superuser permission or setup initial schema via "
<> "https://docs.hasura.io/1.0/graphql/manual/deployment/postgres-permissions.html"
2 changes: 0 additions & 2 deletions server/src-rsr/initialise.sql
Original file line number Diff line number Diff line change
Expand Up @@ -180,8 +180,6 @@ LANGUAGE plpgsql AS $$
END;
$$;

-- required for generating uuid
CREATE EXTENSION IF NOT EXISTS pgcrypto;

CREATE TABLE hdb_catalog.event_triggers
(
Expand Down