Skip to content

Commit

Permalink
Fixed OMap.assocList
Browse files Browse the repository at this point in the history
  • Loading branch information
Soupstraw committed Apr 30, 2024
1 parent 42d5b6d commit aef62f0
Show file tree
Hide file tree
Showing 4 changed files with 48 additions and 6 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}

Expand Down Expand Up @@ -33,6 +34,8 @@ import Cardano.Ledger.Val (zero, (<->))
import Data.Default.Class (Default (..))
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.Map.Strict as Map
import Data.Maybe (fromJust)
import qualified Data.OMap.Strict as OMap
import qualified Data.Sequence.Strict as SSeq
import qualified Data.Set as Set
import Data.Tree
Expand Down Expand Up @@ -264,7 +267,9 @@ pparamUpdateSpec =

proposalsWithVotingSpec ::
forall era.
ConwayEraImp era =>
( ConwayEraImp era
, GovState era ~ ConwayGovState era
) =>
SpecWith (ImpTestState era)
proposalsWithVotingSpec =
describe "Proposals" $ do
Expand Down Expand Up @@ -497,6 +502,38 @@ proposalsWithVotingSpec =
passNEpochs 3
fmap (!! 3) getProposalsForest
`shouldReturn` Node (SJust p116) []
it "Proposals are stored in the expected order" $ do
modifyPParams $
ppMaxValSizeL .~ 1_000_000_000
returnAddr <- registerRewardAccount
deposit <- getsNES $ nesEsL . curPParamsEpochStateL . ppGovActionDepositL
ens <- getEnactState
withdrawals <- arbitrary
let
mkProp name action = do
ProposalProcedure
{ pProcReturnAddr = returnAddr
, pProcGovAction = action
, pProcDeposit = deposit
, pProcAnchor = Anchor (fromJust $ textToUrl 16 name) def
}
prop0 = mkProp "prop0" InfoAction
prop1 = mkProp "prop1" $ NoConfidence (ens ^. ensPrevCommitteeL)
prop2 = mkProp "prop2" InfoAction
prop3 = mkProp "prop3" $ TreasuryWithdrawals withdrawals SNothing
submitProposal_ prop0
submitProposal_ prop1
let
checkProps l = do
props <-
getsNES $
nesEsL . epochStateGovStateL @era . cgsProposalsL . pPropsL
fmap (pProcAnchor . gasProposalProcedure . snd) (OMap.assocList props)
`shouldBe` fmap pProcAnchor l
checkProps [prop0, prop1]
submitProposal_ prop2
submitProposal_ prop3
checkProps [prop0, prop1, prop2, prop3]
where
submitConstitutionForest = submitGovActionForest submitConstitutionGovAction

Expand Down
2 changes: 1 addition & 1 deletion libs/cardano-data/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@

## 1.2.2.0

* Add `assocList`
* Add `assocList`, `elems`
* Add module Data.MonoTuple

## 1.2.1.0
Expand Down
12 changes: 8 additions & 4 deletions libs/cardano-data/src/Data/OMap/Strict.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ module Data.OMap.Strict (
fromFoldableDuplicates,
toMap,
assocList,
elems,
toStrictSeq,
toStrictSeqOKeys,
toStrictSeqOfPairs,
Expand Down Expand Up @@ -63,7 +64,7 @@ import Data.Maybe (isJust)
import Data.Sequence.Strict qualified as SSeq
import Data.Set qualified as Set
import Data.Typeable (Typeable)
import GHC.Exts (IsList (..))
import GHC.Exts qualified as Exts
import GHC.Generics (Generic)
import Lens.Micro
import NoThunks.Class (NoThunks (..))
Expand Down Expand Up @@ -371,13 +372,16 @@ omapl ><| omapr = case omapl of

infixr 5 ><|

instance HasOKey k v => IsList (OMap k v) where
instance HasOKey k v => Exts.IsList (OMap k v) where
type Item (OMap k v) = v
fromList = fromFoldable
toList = F.toList

assocList :: OMap k v -> [(k, v)]
assocList = Map.toList . toMap
assocList :: Ord k => OMap k v -> [(k, v)]
assocList = F.toList . toStrictSeqOfPairs

elems :: Ord k => OMap k v -> [v]
elems = F.toList . toStrictSeq

instance (HasOKey k v, ToJSON v) => ToJSON (OMap k v) where
toJSON = toJSON . toStrictSeq
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -808,6 +808,7 @@ instance SpecTranslate ctx a => SpecTranslate ctx (OSet a) where
instance
( SpecTranslate ctx k
, SpecTranslate ctx v
, Ord k
) =>
SpecTranslate ctx (OMap k v)
where
Expand Down

0 comments on commit aef62f0

Please sign in to comment.