Skip to content

Commit

Permalink
Re-instantiate eraParams as they are used in showing the exception
Browse files Browse the repository at this point in the history
  • Loading branch information
ch1bo committed Sep 23, 2022
1 parent e844fd2 commit d86e37c
Show file tree
Hide file tree
Showing 3 changed files with 24 additions and 16 deletions.
29 changes: 20 additions & 9 deletions hydra-node/src/Hydra/Ledger/Cardano/Evaluate.hs
Expand Up @@ -23,7 +23,7 @@ import Cardano.Ledger.BaseTypes (ProtVer (..), boundRational)
import Cardano.Ledger.Coin (Coin (Coin))
import Cardano.Ledger.Val (Val ((<+>)), (<×>))
import Cardano.Slotting.EpochInfo (EpochInfo, fixedEpochInfo)
import Cardano.Slotting.Slot (EpochSize (EpochSize), SlotNo (SlotNo), EpochNo (EpochNo))
import Cardano.Slotting.Slot (EpochNo (EpochNo), EpochSize (EpochSize), SlotNo (SlotNo))
import Cardano.Slotting.Time (RelativeTime (RelativeTime), SlotLength (getSlotLength), SystemStart (SystemStart), mkSlotLength, toRelativeTime)
import qualified Data.ByteString as BS
import Data.Default (def)
Expand Down Expand Up @@ -59,14 +59,14 @@ import Hydra.Cardano.Api (
import Hydra.Data.ContestationPeriod (posixToUTCTime)
import Ouroboros.Consensus.Cardano.Block (CardanoEras)
import Ouroboros.Consensus.HardFork.History (
Bound (Bound, boundEpoch, boundSlot, boundTime),
EraEnd (EraEnd, EraUnbounded),
EraParams (..),
EraSummary (..),
SafeZone (..),
Summary (Summary),
initBound,
mkInterpreter,
mkUpperBound, Bound (Bound, boundTime, boundSlot, boundEpoch)
)
import Ouroboros.Consensus.Util.Counting (NonEmpty (NonEmptyOne))
import Test.Cardano.Ledger.Alonzo.PlutusScripts (testingCostModelV1, testingCostModelV2)
Expand Down Expand Up @@ -214,10 +214,12 @@ eraHistory =
-- at a known or earliest possible end of the current era + a safe zone.
--
-- See 'Ouroboros.Consensus.HardFork.History.EraParams' for details.
-- NOTE: This era is using not so realistic epoch sizes (1)
--
-- NOTE: This era is using not so realistic epoch sizes of 1 and sets a slot
-- length of 1
eraHistoryWithHorizonAt :: SlotNo -> EraHistory CardanoMode
eraHistoryWithHorizonAt slotNo@(SlotNo n) =
EraHistory CardanoMode (mkInterpreter summary)
EraHistory CardanoMode (mkInterpreter summary)
where
summary :: Summary (CardanoEras StandardCrypto)
summary =
Expand All @@ -227,13 +229,22 @@ eraHistoryWithHorizonAt slotNo@(SlotNo n) =
, eraEnd =
EraEnd $
Bound
{ boundTime = RelativeTime $ fromIntegral n
, boundSlot = slotNo
, boundEpoch = EpochNo n
}
, eraParams = error "This should be unused"
{ boundTime = RelativeTime $ fromIntegral n
, boundSlot = slotNo
, boundEpoch = EpochNo n
}
, eraParams
}

eraParams =
EraParams
{ eraEpochSize = EpochSize 1
, eraSlotLength = mkSlotLength 1
, -- NOTE: unused if the 'eraEnd' is already defined, but would be used to
-- extend the last era accordingly in the real cardano-node
eraSafeZone = UnsafeIndefiniteSafeZone
}

epochInfo :: Monad m => EpochInfo m
epochInfo = fixedEpochInfo epochSize slotLength

Expand Down
2 changes: 1 addition & 1 deletion hydra-node/test/Hydra/Chain/Direct/HandlersSpec.hs
Expand Up @@ -55,7 +55,7 @@ import Hydra.Chain.Direct.StateSpec (genChainState, genChainStateWithTx)
import Hydra.Chain.Direct.TimeHandle (TimeHandle, mkTimeHandle)
import Hydra.Chain.Direct.Util (Block)
import Hydra.Ledger.Cardano (genTxIn)
import Hydra.Ledger.Cardano.Evaluate (slotNoToUTCTime)
import Hydra.Ledger.Cardano.Evaluate (eraHistoryWithHorizonAt, slotNoToUTCTime)
import Ouroboros.Consensus.Block (Point, blockPoint)
import Ouroboros.Consensus.Cardano.Block (HardForkBlock (BlockBabbage))
import qualified Ouroboros.Consensus.Protocol.Praos.Header as Praos
Expand Down
9 changes: 3 additions & 6 deletions hydra-node/test/Hydra/Chain/Direct/TimeHandleSpec.hs
Expand Up @@ -19,15 +19,12 @@ spec = do
(slot, _) <- currentPointInTime
res <- slotFromUTCTime =<< slotToUTCTime slot
pure $ res === slot

it "should convert slot within latest/current era" $ do
let now = posixSecondsToUTCTime 13.4
systemStart = SystemStart $ posixSecondsToUTCTime 0
eraHistory = eraHistoryWithHorizonAt
timeHandle =
mkTimeHandle
now
systemStart
eraHistory
eraHistory = eraHistoryWithHorizonAt 15
timeHandle = mkTimeHandle now systemStart eraHistory
slotInside = SlotNo 14
converted = slotToUTCTime timeHandle slotInside
expected = Right $ posixSecondsToUTCTime 14
Expand Down

0 comments on commit d86e37c

Please sign in to comment.