66{-# LANGUAGE FlexibleContexts #-}
77{-# LANGUAGE FlexibleInstances #-}
88{-# LANGUAGE GeneralizedNewtypeDeriving #-}
9- {-# LANGUAGE LambdaCase #-}
109{-# LANGUAGE NamedFieldPuns #-}
1110{-# LANGUAGE OverloadedStrings #-}
1211{-# LANGUAGE Rank2Types #-}
@@ -24,7 +23,6 @@ module Ouroboros.Consensus.Shelley.Ledger.Mempool (
2423 , SL. ApplyTxError (.. )
2524 , TxId (.. )
2625 , Validated (.. )
27- , WithTop (.. )
2826 , fixedBlockBodyOverhead
2927 , mkShelleyTx
3028 , mkShelleyValidatedTx
@@ -55,8 +53,7 @@ import Control.Monad.Except (Except)
5553import Control.Monad.Identity (Identity (.. ))
5654import Data.DerivingVia (InstantiatedAt (.. ))
5755import Data.Foldable (toList )
58- import Data.Measure (BoundedMeasure , Measure )
59- import qualified Data.Measure as Measure
56+ import Data.Measure (Measure )
6057import Data.Typeable (Typeable )
6158import GHC.Generics (Generic )
6259import GHC.Natural (Natural )
@@ -322,17 +319,17 @@ instance ( ShelleyCompatible p (AlonzoEra c)
322319
323320data AlonzoMeasure = AlonzoMeasure {
324321 byteSize :: ! ByteSize
325- , exUnits :: ! (ExUnits' ( WithTop Natural ) )
322+ , exUnits :: ! (ExUnits' Natural )
326323 } deriving stock (Eq , Generic , Show )
327324 deriving anyclass (NoThunks )
328- deriving (BoundedMeasure , Measure )
325+ deriving (Measure )
329326 via (InstantiatedAt Generic AlonzoMeasure )
330327
331328instance HasByteSize AlonzoMeasure where
332329 txMeasureByteSize = byteSize
333330
334- fromExUnits :: ExUnits -> ExUnits' ( WithTop Natural )
335- fromExUnits = fmap NotTop . unWrapExUnits
331+ fromExUnits :: ExUnits -> ExUnits' Natural
332+ fromExUnits = unWrapExUnits
336333
337334txMeasureAlonzo ::
338335 forall proto era .
@@ -369,7 +366,7 @@ data ConwayMeasure = ConwayMeasure {
369366 , refScriptsSize :: ! ByteSize
370367 } deriving stock (Eq , Generic , Show )
371368 deriving anyclass (NoThunks )
372- deriving (BoundedMeasure , Measure )
369+ deriving (Measure )
373370 via (InstantiatedAt Generic ConwayMeasure )
374371
375372instance HasByteSize ConwayMeasure where
@@ -396,39 +393,3 @@ instance ( ShelleyCompatible p (ConwayEra c)
396393 -- For post-Conway eras, this will become a protocol parameter.
397394 SL. maxRefScriptSizePerBlock
398395 }
399-
400- {- ------------------------------------------------------------------------------
401- WithTop
402- -------------------------------------------------------------------------------}
403-
404- -- | Add a unique top element to a lattice.
405- --
406- -- TODO This should be relocated to `cardano-base:Data.Measure'.
407- data WithTop a = NotTop ! a | Top
408- deriving (Eq , Generic , Show )
409- deriving anyclass (NoThunks )
410-
411- instance Ord a => Ord (WithTop a ) where
412- compare = curry $ \ case
413- (Top , Top ) -> EQ
414- (Top , _ ) -> GT
415- (_ , Top ) -> LT
416- (NotTop l, NotTop r) -> compare l r
417-
418- instance Measure a => Measure (WithTop a ) where
419- zero = NotTop Measure. zero
420- plus = curry $ \ case
421- (Top , _ ) -> Top
422- (_ , Top ) -> Top
423- (NotTop l, NotTop r) -> NotTop $ Measure. plus l r
424- min = curry $ \ case
425- (Top , r ) -> r
426- (l , Top ) -> l
427- (NotTop l, NotTop r) -> NotTop $ Measure. min l r
428- max = curry $ \ case
429- (Top , _ ) -> Top
430- (_ , Top ) -> Top
431- (NotTop l, NotTop r) -> NotTop $ Measure. max l r
432-
433- instance Measure a => BoundedMeasure (WithTop a ) where
434- maxBound = Top
0 commit comments