Skip to content

Commit

Permalink
add a check to see if contraint exists
Browse files Browse the repository at this point in the history
  • Loading branch information
Cmdv committed Aug 29, 2023
1 parent dcb2a00 commit ee110ae
Show file tree
Hide file tree
Showing 4 changed files with 61 additions and 27 deletions.
17 changes: 9 additions & 8 deletions cardano-db-sync/src/Cardano/DbSync/Default.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,10 +3,10 @@
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# LANGUAGE RankNTypes #-}

module Cardano.DbSync.Default (
insertListBlocks,
Expand Down Expand Up @@ -79,8 +79,9 @@ applyAndInsertBlockMaybe syncEnv cblk = do
-- equal, insert the block and restore consistency between ledger and db.
case eiBlockInDbAlreadyId of
Left _ -> do
liftIO . logInfo tracer $
mconcat
liftIO
. logInfo tracer
$ mconcat
[ "Received block which is not in the db with "
, textShow (getHeaderFields cblk)
, ". Time to restore consistency."
Expand All @@ -93,7 +94,6 @@ applyAndInsertBlockMaybe syncEnv cblk = do
-- we can put the constraints on rewards table
lift addRewardTableConstraint
lift addEpochStakeTableConstraint

Right blockId | Just (adaPots, slotNo, epochNo) <- getAdaPots applyRes -> do
replaced <- lift $ DB.replaceAdaPots blockId $ mkAdaPots blockId slotNo epochNo adaPots
if replaced
Expand Down Expand Up @@ -125,7 +125,7 @@ applyAndInsertBlockMaybe syncEnv cblk = do
Generic.neEpoch <$> maybeFromStrict (apNewEpoch appRes)

addRewardTableConstraint ::
forall m. ( MonadBaseControl IO m , MonadIO m) => ReaderT SqlBackend m ()
forall m. (MonadBaseControl IO m, MonadIO m) => ReaderT SqlBackend m ()
addRewardTableConstraint = do
let entityD = entityDef $ Proxy @DB.Reward
DB.alterTable
Expand All @@ -140,7 +140,7 @@ addRewardTableConstraint = do
)

addEpochStakeTableConstraint ::
forall m. ( MonadBaseControl IO m , MonadIO m) => ReaderT SqlBackend m ()
forall m. (MonadBaseControl IO m, MonadIO m) => ReaderT SqlBackend m ()
addEpochStakeTableConstraint = do
let entityD = entityDef $ Proxy @DB.EpochStake
DB.alterTable
Expand Down Expand Up @@ -215,8 +215,9 @@ insertBlock syncEnv cblk applyRes firstAfterRollback tookSnapshot = do
-- update the epoch
updateEpoch details isNewEpochEvent
whenPruneTxOut syncEnv $
when (unBlockNo blkNo `mod` getPruneInterval syncEnv == 0) $ do
lift $ DB.deleteConsumedTxOut tracer (getSafeBlockNoDiff syncEnv)
when (unBlockNo blkNo `mod` getPruneInterval syncEnv == 0) $
do
lift $ DB.deleteConsumedTxOut tracer (getSafeBlockNoDiff syncEnv)
lift $ commitOrIndexes withinTwoMin withinHalfHour
where
tracer = getTrace syncEnv
Expand Down
2 changes: 1 addition & 1 deletion cardano-db/src/Cardano/Db.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,10 +13,10 @@ module Cardano.Db (
queryTxOutConsumedCount,
) where

import Cardano.Db.AlterTable as X
import Cardano.Db.Delete as X
import Cardano.Db.Error as X
import Cardano.Db.Insert as X
import Cardano.Db.AlterTable as X
import Cardano.Db.Migration as X
import Cardano.Db.Migration.Extra.CosnumedTxOut.Queries (isMigrated, migrateTxOut, queryTxOutConsumedCount, queryTxOutConsumedNullCount)
import Cardano.Db.Migration.Version as X
Expand Down
66 changes: 49 additions & 17 deletions cardano-db/src/Cardano/Db/AlterTable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,8 @@
{-# OPTIONS_GHC -Wno-unused-local-binds #-}

module Cardano.Db.AlterTable (
AlterTable(..),
DbAlterTableException(..),
AlterTable (..),
DbAlterTableException (..),
alterTable,
) where

Expand All @@ -16,9 +16,9 @@ import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Trans.Control (MonadBaseControl)
import Control.Monad.Trans.Reader (ReaderT)
import qualified Data.Text as T

Check warning on line 18 in cardano-db/src/Cardano/Db/AlterTable.hs

View workflow job for this annotation

GitHub Actions / build

Warning in module Cardano.Db.AlterTable: Avoid restricted qualification ▫︎ Found: "import qualified Data.Text as T" ▫︎ Perhaps: "import qualified Data.Text as Text" ▫︎ Note: may break the code
import Database.Persist.Postgresql (ConstraintNameDB (..), EntityNameDB (..), FieldNameDB (..), SqlBackend, rawExecute, EntityDef, getEntityFields, fieldDB)
import Database.PostgreSQL.Simple (SqlError (..), ExecStatus (..))
import Database.Persist.EntityDef.Internal (entityDB)
import Database.Persist.Postgresql (ConstraintNameDB (..), EntityDef, EntityNameDB (..), FieldNameDB (..), Single (..), SqlBackend, fieldDB, getEntityFields, rawExecute, rawSql)
import Database.PostgreSQL.Simple (ExecStatus (..), SqlError (..))

-- The ability to `ALTER TABLE` currently dealing with `CONSTRAINT` but can be extended
data AlterTable
Expand All @@ -36,29 +36,48 @@ alterTable ::
forall m.
( MonadBaseControl IO m
, MonadIO m
, MonadFail m
) =>
EntityDef ->
AlterTable ->
ReaderT SqlBackend m ()
alterTable entity (AddUniqueConstraint cname cols) = do
-- Check that input fields are indeed present
-- Check that entity fields are in the schema
if checkAllFieldsValid entity cols
then handle alterTableExceptHandler (rawExecute query [])
else liftIO $ throwIO (DbAlterTableException "Constraint field does not exist" sqlError)
then do
-- check if the constraint name already exists
constraintRes <- queryConstraint cname
if constraintRes == "1"
then throwErr "Constraint field already exist"
else -- if it doesn't exist then add a new constraint
handle alterTableExceptHandler (rawExecute queryAddConstraint [])
else error "Some of the unique values which you are being added to the constraint don't correlate"
where
query :: T.Text
query =
queryAddConstraint :: T.Text
queryAddConstraint =
T.concat
[ "ALTER TABLE "
, unEntityNameDB (entityDB entity)
, " ADD CONSTRAINT IF NOT EXISTS "
, " ADD CONSTRAINT "
, unConstraintNameDB cname
, " UNIQUE("
, T.intercalate "," $ map escapeDBName' cols
, ")"
]

escapeDBName' :: FieldNameDB -> T.Text
escapeDBName' name = unFieldNameDB name

throwErr :: forall m'. (MonadIO m') => [Char] -> ReaderT SqlBackend m' ()
throwErr e = liftIO $ throwIO (DbAlterTableException e sqlError)

queryCheckConstraint :: T.Text
queryCheckConstraint =
T.concat
[ "SELECT COUNT(*) FROM pg_constraint WHERE conname ='"
, unConstraintNameDB cname
, "'"
]
alterTable entity (DropUniqueConstraint cname) =
handle alterTableExceptHandler (rawExecute query [])
where
Expand All @@ -71,6 +90,18 @@ alterTable entity (DropUniqueConstraint cname) =
, unConstraintNameDB cname
]

-- check if a constraint is already present
queryConstraint ::
( MonadIO m
, MonadFail m
) =>
ConstraintNameDB ->
ReaderT SqlBackend m T.Text
queryConstraint cname = do
let query = T.concat ["SELECT 1 FROM pg_constraint WHERE conname ='", unConstraintNameDB cname, "'"]
[Single constraintNum] <- rawSql query []
pure constraintNum

-- check to see that the field inputs exist
checkAllFieldsValid :: Foldable t => EntityDef -> t FieldNameDB -> Bool
checkAllFieldsValid entity cols = do
Expand All @@ -86,10 +117,11 @@ alterTableExceptHandler ::
alterTableExceptHandler e = liftIO $ throwIO (DbAlterTableException "" e)

sqlError :: SqlError
sqlError = SqlError
{ sqlState = ""
, sqlExecStatus = FatalError
, sqlErrorMsg = ""
, sqlErrorDetail = ""
, sqlErrorHint = ""
}
sqlError =
SqlError
{ sqlState = ""
, sqlExecStatus = FatalError
, sqlErrorMsg = ""
, sqlErrorDetail = ""
, sqlErrorHint = ""
}
3 changes: 2 additions & 1 deletion cardano-db/src/Cardano/Db/Insert.hs
Original file line number Diff line number Diff line change
Expand Up @@ -111,14 +111,15 @@ import Database.Persist.Sql (
SqlBackend,
UniqueDef,
entityDef,
getEntityForeignDefs,
insertMany,
rawExecute,
rawSql,
replace,
toPersistFields,
toPersistValue,
uniqueDBName,
uniqueFields, getEntityForeignDefs,
uniqueFields,
)
import qualified Database.Persist.Sql.Util as Util
import Database.Persist.Types (
Expand Down

0 comments on commit ee110ae

Please sign in to comment.