Skip to content

Commit 30f98d8

Browse files
CmdvCmdv
authored andcommitted
fix the DbWord64 error
1 parent ee922bc commit 30f98d8

File tree

13 files changed

+56
-33
lines changed

13 files changed

+56
-33
lines changed

cardano-db-sync/src/Cardano/DbSync/Default.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -122,8 +122,7 @@ applyAndInsertBlockMaybe syncEnv tracer cblk = do
122122
Right _
123123
| Just epochNo <- getNewEpoch applyRes -> do
124124
liftIO $ logInfo tracer $ "Reached " <> textShow epochNo
125-
_otherwise -> do
126-
pure ()
125+
_ -> pure ()
127126
where
128127
mkApplyResult :: Bool -> IO (ApplyResult, Bool)
129128
mkApplyResult isCons = do
@@ -240,7 +239,7 @@ insertBlock syncEnv cblk applyRes firstAfterRollback tookSnapshot = do
240239
ranIndexes <- liftIO $ getRanIndexes syncEnv
241240
addConstraintsIfNotExist syncEnv tracer
242241
unless ranIndexes $ do
243-
-- Only commit if we haven't already committed above to avoid double-commit
242+
-- Only commit if we haven't already committed above to avoid double commits
244243
unless commited $ lift $ DB.transactionSaveWithIsolation DB.RepeatableRead
245244
liftIO $ runNearTipMigrations syncEnv
246245

cardano-db-sync/src/Cardano/DbSync/Era/Universal/Insert/GovAction.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -82,7 +82,7 @@ insertGovActionProposal syncEnv blkId txId govExpiresAt mcgs (index, (govId, pp)
8282
case pProcGovAction pp of
8383
ParameterChange _ pparams _ ->
8484
Just <$> insertParamProposal blkId txId (convertConwayParamProposal pparams)
85-
_otherwise -> pure Nothing
85+
_ -> pure Nothing
8686
prevGovActionDBId <- case mprevGovAction of
8787
Nothing -> pure Nothing
8888
Just prevGovActionId -> Just <$> resolveGovActionProposal syncEnv prevGovActionId
@@ -109,15 +109,15 @@ insertGovActionProposal syncEnv blkId txId govExpiresAt mcgs (index, (govId, pp)
109109
TreasuryWithdrawals mp _ -> insertTreasuryWithdrawalsBulk govActionProposalId (Map.toList mp)
110110
UpdateCommittee {} -> insertNewCommittee govActionProposalId
111111
NewConstitution _ constitution -> void $ insertConstitution blkId (Just govActionProposalId) constitution
112-
_otherwise -> pure ()
112+
_ -> pure ()
113113
where
114114
mprevGovAction :: Maybe GovActionId = case pProcGovAction pp of
115115
ParameterChange prv _ _ -> unGovPurposeId <$> strictMaybeToMaybe prv
116116
HardForkInitiation prv _ -> unGovPurposeId <$> strictMaybeToMaybe prv
117117
NoConfidence prv -> unGovPurposeId <$> strictMaybeToMaybe prv
118118
UpdateCommittee prv _ _ _ -> unGovPurposeId <$> strictMaybeToMaybe prv
119119
NewConstitution prv _ -> unGovPurposeId <$> strictMaybeToMaybe prv
120-
_otherwise -> Nothing
120+
_ -> Nothing
121121

122122
-- Bulk insert treasury withdrawals
123123
insertTreasuryWithdrawalsBulk ::

cardano-db-sync/src/Cardano/DbSync/Rollback.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@ rollbackFromBlockNo ::
4242
rollbackFromBlockNo syncEnv blkNo = do
4343
nBlocks <- lift $ DB.queryBlockCountAfterBlockNo (unBlockNo blkNo) True
4444
mres <- lift $ DB.queryBlockNoAndEpoch (unBlockNo blkNo)
45-
-- Use whenJust like the original - silently skip if block not found
45+
-- Use whenJust to silently skip if block not found
4646
whenJust mres $ \(blockId, epochNo) -> do
4747
liftIO . logInfo trce $
4848
mconcat
@@ -135,13 +135,12 @@ rollbackLedger syncEnv point =
135135
Just . fmap fst <$> verifySnapshotPoint syncEnv (OnDisk <$> lsfs)
136136
NoLedger _ -> pure Nothing
137137

138-
-- For testing and debugging.
139-
-- Enhanced rollback that logs more info and handles the rollback more carefully
138+
-- For testing and debugging. A rollback that logs more information.
140139
unsafeRollback :: Trace IO Text -> DB.TxOutVariantType -> DB.PGConfig -> SlotNo -> IO (Either SyncNodeError ())
141140
unsafeRollback trce txOutVariantType config slotNo = do
142141
logWarning trce $ "Starting a forced rollback to slot: " <> textShow (unSlotNo slotNo)
143142

144-
-- Perform rollback with improved diagnostics
143+
-- Perform rollback with diagnostics
145144
Right
146145
<$> DB.runDbStandaloneDirectSilent
147146
(DB.PGPassCached config)

cardano-db/src/Cardano/Db/Migration.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -106,7 +106,6 @@ runMigrations trce pgconfig quiet migrationDir mLogfiledir mToRun txOutVariantTy
106106
putStrLn "Running:"
107107
(scripts', ranAll) <- filterMigrations scripts
108108

109-
-- Replace just this forM_ with progress bar
110109
withProgress trce (length scripts') "Migration" $ \progressRef -> do
111110
forM_ (zip [1 :: Integer ..] scripts') $ \(i, script) -> do
112111
updateProgress trce progressRef (fromIntegral i) "Migration"
@@ -120,7 +119,6 @@ runMigrations trce pgconfig quiet migrationDir mLogfiledir mToRun txOutVariantTy
120119
unless quiet $ putStrLn "Running:"
121120
(scripts', ranAll) <- filterMigrations scripts
122121

123-
-- Replace just this forM_ with progress bar
124122
withProgress trce (length scripts') "Migration" $ \progressRef -> do
125123
forM_ (zip [1 :: Integer ..] scripts') $ \(i, script) -> do
126124
updateProgress trce progressRef (fromIntegral i) "Migration"

cardano-db/src/Cardano/Db/Schema/Core/Base.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,7 @@ import Cardano.Db.Types (
3535
ScriptType,
3636
dbLovelaceDecoder,
3737
dbLovelaceEncoder,
38+
dbWord64ValueEncoder,
3839
maybeDbWord64Decoder,
3940
maybeDbWord64Encoder,
4041
scriptPurposeEncoder,
@@ -210,7 +211,7 @@ type instance Key TxMetadata = TxMetadataId
210211
instance DbInfo TxMetadata where
211212
jsonbFields _ = ["json"]
212213
unnestParamTypes _ =
213-
[ ("key", "bigint[]")
214+
[ ("key", "numeric[]")
214215
, ("json", "text[]")
215216
, ("bytes", "bytea[]")
216217
, ("tx_id", "bigint[]")
@@ -219,7 +220,7 @@ instance DbInfo TxMetadata where
219220
txMetadataBulkEncoder :: E.Params ([DbWord64], [Maybe Text], [ByteString], [TxId])
220221
txMetadataBulkEncoder =
221222
contrazip4
222-
(bulkEncoder $ E.nonNullable $ fromIntegral . unDbWord64 >$< E.int8)
223+
(bulkEncoder $ E.nonNullable dbWord64ValueEncoder)
223224
(bulkEncoder $ E.nullable E.text)
224225
(bulkEncoder $ E.nonNullable E.bytea)
225226
(bulkEncoder $ E.nonNullable $ getTxId >$< E.int8)

cardano-db/src/Cardano/Db/Schema/Core/Pool.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@ import Cardano.Db.Types (
3232
DbLovelace (..),
3333
DbWord64 (..),
3434
dbLovelaceEncoder,
35+
dbWord64ValueEncoder,
3536
)
3637

3738
-----------------------------------------------------------------------------------------------------------------------------------
@@ -89,10 +90,10 @@ poolStatBulkEncoder =
8990
contrazip6
9091
(bulkEncoder $ E.nonNullable $ Id.getPoolHashId >$< E.int8) -- poolHashId
9192
(bulkEncoder $ E.nonNullable $ fromIntegral >$< E.int4) -- epoch_no
92-
(bulkEncoder $ E.nonNullable $ fromIntegral . unDbWord64 >$< E.numeric) -- number_of_blocks
93-
(bulkEncoder $ E.nonNullable $ fromIntegral . unDbWord64 >$< E.numeric) -- number_of_delegators
94-
(bulkEncoder $ E.nonNullable $ fromIntegral . unDbWord64 >$< E.numeric) -- stake
95-
(bulkEncoder $ E.nullable $ fromIntegral . unDbWord64 >$< E.numeric) -- voting_power
93+
(bulkEncoder $ E.nonNullable dbWord64ValueEncoder) -- number_of_blocks
94+
(bulkEncoder $ E.nonNullable dbWord64ValueEncoder) -- number_of_delegators
95+
(bulkEncoder $ E.nonNullable dbWord64ValueEncoder) -- stake
96+
(bulkEncoder $ E.nullable dbWord64ValueEncoder) -- voting_power
9697

9798
-- |
9899
-- Table Name: pool_update

cardano-db/src/Cardano/Db/Schema/Variants/TxOutAddress.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ import qualified Cardano.Db.Schema.Ids as Id
1818
import Cardano.Db.Schema.Types (textDecoder)
1919
import Cardano.Db.Statement.Function.Core (bulkEncoder)
2020
import Cardano.Db.Statement.Types (DbInfo (..), Key)
21-
import Cardano.Db.Types (DbLovelace, DbWord64 (..), dbLovelaceDecoder, dbLovelaceEncoder, dbLovelaceValueEncoder)
21+
import Cardano.Db.Types (DbLovelace, DbWord64 (..), dbLovelaceDecoder, dbLovelaceEncoder, dbLovelaceValueEncoder, dbWord64ValueEncoder)
2222

2323
-- |
2424
-- Table Name: tx_out
@@ -200,11 +200,11 @@ type instance Key MaTxOutAddress = Id.MaTxOutAddressId
200200
instance DbInfo MaTxOutAddress where
201201
tableName _ = "ma_tx_out"
202202
columnNames _ = NE.fromList ["quantity", "tx_out_id", "ident"]
203-
unnestParamTypes _ = [("ident", "bigint[]"), ("quantity", "bigint[]"), ("tx_out_id", "bigint[]")]
203+
unnestParamTypes _ = [("ident", "bigint[]"), ("quantity", "numeric[]"), ("tx_out_id", "bigint[]")]
204204

205205
maTxOutAddressBulkEncoder :: E.Params ([Id.MultiAssetId], [DbWord64], [Id.TxOutAddressId])
206206
maTxOutAddressBulkEncoder =
207207
contrazip3
208208
(bulkEncoder $ E.nonNullable $ Id.getMultiAssetId >$< E.int8) -- maTxOutAddressIdent
209-
(bulkEncoder $ E.nonNullable $ fromIntegral . unDbWord64 >$< E.int8) -- maTxOutAddressQuantity
209+
(bulkEncoder $ E.nonNullable dbWord64ValueEncoder) -- maTxOutAddressQuantity
210210
(bulkEncoder $ E.nonNullable $ Id.getTxOutAddressId >$< E.int8) -- maTxOutAddressTxOutId

cardano-db/src/Cardano/Db/Schema/Variants/TxOutCore.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ module Cardano.Db.Schema.Variants.TxOutCore where
77
import qualified Cardano.Db.Schema.Ids as Id
88
import Cardano.Db.Statement.Function.Core (bulkEncoder)
99
import Cardano.Db.Statement.Types (DbInfo (..), Entity (..), Key)
10-
import Cardano.Db.Types (DbLovelace, DbWord64 (..), dbLovelaceDecoder, dbLovelaceEncoder, dbLovelaceValueEncoder)
10+
import Cardano.Db.Types (DbLovelace, DbWord64 (..), dbLovelaceDecoder, dbLovelaceEncoder, dbLovelaceValueEncoder, dbWord64Decoder, dbWord64ValueEncoder)
1111
import Contravariant.Extras (contrazip11, contrazip3)
1212
import Data.ByteString.Char8 (ByteString)
1313
import Data.Functor.Contravariant ((>$<))
@@ -193,17 +193,18 @@ instance DbInfo MaTxOutCore where
193193
, "tx_out_id"
194194
, "ident"
195195
]
196+
unnestParamTypes _ = [("quantity", "numeric[]"), ("tx_out_id", "bigint[]"), ("ident", "bigint[]")]
196197

197198
maTxOutCoreDecoder :: D.Row MaTxOutCore
198199
maTxOutCoreDecoder =
199200
MaTxOutCore
200-
<$> D.column (D.nonNullable $ DbWord64 . fromIntegral <$> D.int8) -- maTxOutCoreQuantity
201+
<$> dbWord64Decoder -- maTxOutCoreQuantity
201202
<*> Id.idDecoder Id.TxOutCoreId -- maTxOutCoreTxOutId
202203
<*> Id.idDecoder Id.MultiAssetId -- maTxOutCoreIdent
203204

204205
maTxOutCoreBulkEncoder :: E.Params ([DbWord64], [Id.TxOutCoreId], [Id.MultiAssetId])
205206
maTxOutCoreBulkEncoder =
206207
contrazip3
207-
(bulkEncoder $ E.nonNullable $ fromIntegral . unDbWord64 >$< E.int8)
208+
(bulkEncoder $ E.nonNullable dbWord64ValueEncoder)
208209
(bulkEncoder $ E.nonNullable $ Id.getTxOutCoreId >$< E.int8)
209210
(bulkEncoder $ E.nonNullable $ Id.getMultiAssetId >$< E.int8)

cardano-db/src/Cardano/Db/Statement/Types.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,7 @@ class Typeable a => DbInfo a where
5555
default columnNames :: (Generic a, GRecordFieldNames (Rep a)) => Proxy a -> NE.NonEmpty Text
5656
columnNames p =
5757
let typeName = tyConName $ typeRepTyCon $ typeRep p
58+
-- Safe use of undefined: acts as type witness, never evaluated
5859
fieldNames = gRecordFieldNames (from (undefined :: a))
5960
in case fieldNames of
6061
[] -> error "No fields found"
@@ -155,12 +156,15 @@ instance GRecordFieldNames U1 where
155156
gRecordFieldNames _ = []
156157

157158
instance (GRecordFieldNames a, GRecordFieldNames b) => GRecordFieldNames (a :*: b) where
159+
-- Safe use of undefined: type witnesses for generic recursion, never evaluated
158160
gRecordFieldNames _ = gRecordFieldNames (undefined :: a p) ++ gRecordFieldNames (undefined :: b p)
159161

160162
instance GRecordFieldNames a => GRecordFieldNames (M1 D c a) where
163+
-- Safe use of undefined: type witness for generic metadata, never evaluated
161164
gRecordFieldNames _ = gRecordFieldNames (undefined :: a p)
162165

163166
instance GRecordFieldNames a => GRecordFieldNames (M1 C c a) where
167+
-- Safe use of undefined: type witness for generic metadata, never evaluated
164168
gRecordFieldNames _ = gRecordFieldNames (undefined :: a p)
165169

166170
instance Selector c => GRecordFieldNames (M1 S c (K1 i a)) where

cardano-db/src/Cardano/Db/Types.hs

Lines changed: 24 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ import Data.Fixed (Micro, showFixed)
2828
import Data.Functor.Contravariant ((>$<))
2929
import Data.Int (Int64)
3030
import Data.Pool (Pool)
31-
import Data.Scientific (Scientific (..), scientific, toBoundedInteger)
31+
import Data.Scientific (Scientific (..), coefficient, scientific, toBoundedInteger)
3232
import Data.Text (Text)
3333
import qualified Data.Text as Text
3434
import Data.WideWord (Word128 (..))
@@ -89,7 +89,7 @@ instance ToJSON Ada where
8989
-- `Number` results in it becoming `7.3112484749601107e10` while the old explorer is returning `73112484749.601107`
9090
toEncoding (Ada ada) =
9191
unsafeToEncoding $
92-
Builder.string8 $ -- convert ByteString to Aeson's
92+
Builder.string8 $ -- convert ByteString to Aeson's -- convert ByteString to Aeson's
9393
showFixed True ada -- convert String to ByteString using Latin1 encoding
9494
-- convert Micro to String chopping off trailing zeros
9595

@@ -176,11 +176,31 @@ newtype DbWord64 = DbWord64 {unDbWord64 :: Word64}
176176
deriving (Eq, Generic, Num)
177177
deriving (Read, Show) via (Quiet DbWord64)
178178

179+
-- Helper to replicate the original Persistent fromPersistValue behavior for DbWord64
180+
-- This matches the PersistRational case: fromIntegral $ numerator r
181+
scientificToWord64 :: Scientific -> Word64
182+
scientificToWord64 s = case toBoundedInteger @Word64 s of
183+
Just w64 -> w64
184+
Nothing -> fromIntegral $ coefficient s -- Fallback to coefficient for out-of-bounds values
185+
186+
-- Value encoder for DbWord64 using numeric (matches word64type domain)
187+
dbWord64ValueEncoder :: HsqlE.Value DbWord64
188+
dbWord64ValueEncoder = (\x -> scientific (toInteger $ unDbWord64 x) 0) >$< HsqlE.numeric
189+
190+
-- Non-nullable encoder for DbWord64 parameters
191+
dbWord64Encoder :: HsqlE.Params DbWord64
192+
dbWord64Encoder = HsqlE.param $ HsqlE.nonNullable dbWord64ValueEncoder
193+
194+
-- Non-nullable decoder for DbWord64
195+
dbWord64Decoder :: HsqlD.Row DbWord64
196+
dbWord64Decoder = HsqlD.column (HsqlD.nonNullable (DbWord64 . scientificToWord64 <$> HsqlD.numeric))
197+
198+
-- Nullable encoder for DbWord64 parameters
179199
maybeDbWord64Encoder :: HsqlE.Params (Maybe DbWord64)
180-
maybeDbWord64Encoder = HsqlE.param $ HsqlE.nullable $ fromIntegral . unDbWord64 >$< HsqlE.int8
200+
maybeDbWord64Encoder = HsqlE.param $ HsqlE.nullable dbWord64ValueEncoder
181201

182202
maybeDbWord64Decoder :: HsqlD.Row (Maybe DbWord64)
183-
maybeDbWord64Decoder = HsqlD.column (HsqlD.nullable (DbWord64 . fromIntegral <$> HsqlD.int8))
203+
maybeDbWord64Decoder = HsqlD.column (HsqlD.nullable (DbWord64 . scientificToWord64 <$> HsqlD.numeric))
184204

185205
--------------------------------------------------------------------------------
186206
-- The following must be in alphabetic order.

0 commit comments

Comments
 (0)