Skip to content

Commit

Permalink
Output line number when failing to parse persistence data
Browse files Browse the repository at this point in the history
  • Loading branch information
noonio authored and v0d1ch committed Aug 8, 2024
1 parent f42d9ec commit 1bab0c8
Showing 1 changed file with 6 additions and 3 deletions.
9 changes: 6 additions & 3 deletions hydra-node/src/Hydra/Persistence.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ module Hydra.Persistence where
import Hydra.Prelude

import Control.Concurrent.Class.MonadSTM (newTVarIO, throwSTM, writeTVar)
import Control.Lens.Combinators (iforM)
import Control.Monad.Class.MonadFork (myThreadId)
import Data.Aeson qualified as Aeson
import Data.ByteString qualified as BS
Expand Down Expand Up @@ -90,7 +91,9 @@ createPersistenceIncremental fp = do
-- NOTE: We require the whole file to be loadable. It might
-- happen that the data written by 'append' is only there
-- partially and then this will fail (which we accept now).
case forM (C8.lines bs) Aeson.eitherDecodeStrict' of
Left e -> throwIO $ PersistenceException e
Right decoded -> pure decoded
let loadOrFail i o =
case Aeson.eitherDecodeStrict' o of
Left e -> throwIO $ PersistenceException ("Error at line: " <> show (i + 1) <> " in file " <> fp <> " - " <> e)
Right decoded -> pure decoded
in iforM (C8.lines bs) loadOrFail
}

0 comments on commit 1bab0c8

Please sign in to comment.