Skip to content

Commit

Permalink
fix test
Browse files Browse the repository at this point in the history
  • Loading branch information
rvl committed Jul 19, 2020
1 parent 7cc6a6e commit 4a06270
Show file tree
Hide file tree
Showing 4 changed files with 18 additions and 19 deletions.
12 changes: 6 additions & 6 deletions lib/shelley/src/Cardano/Wallet/Shelley/Compatibility.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ module Cardano.Wallet.Shelley.Compatibility
, genesisTip

-- * Conversions
, toShelleyHash
, toCardanoHash
, toEpochSize
, toShelleyGenTx
, toPoint
Expand Down Expand Up @@ -171,7 +171,7 @@ import GHC.Stack
import Numeric.Natural
( Natural )
import Ouroboros.Consensus.Cardano.Block
( CardanoBlock, CardanoGenTx, GenTx (..), HardForkBlock (..) )
( CardanoBlock, CardanoEras, CardanoGenTx, GenTx (..), HardForkBlock (..) )
import Ouroboros.Consensus.HardFork.Combinator.AcrossEras
( OneEraHash (..) )
import Ouroboros.Consensus.Shelley.Ledger
Expand Down Expand Up @@ -319,9 +319,9 @@ hashOfNoParent :: W.Hash "BlockHeader"
hashOfNoParent =
W.Hash . BS.pack $ replicate 32 0

toShelleyHash :: W.Hash "BlockHeader" -> ShelleyHash c
toShelleyHash (W.Hash bytes) =
ShelleyHash $ SL.HashHeader $ UnsafeHash $ toShort bytes
toCardanoHash :: W.Hash "BlockHeader" -> OneEraHash (CardanoEras sc)
toCardanoHash (W.Hash bytes) =
OneEraHash $ toShort bytes

toEpochSize :: W.EpochLength -> EpochSize
toEpochSize =
Expand Down Expand Up @@ -382,7 +382,7 @@ fromCardanoBlock gp = \case
BlockShelley blk ->
fromShelleyBlock blk
where
fromShelleyBlock blk@(ShelleyBlock (SL.Block _ (SL.TxSeq txs')) headerHash) =
fromShelleyBlock blk@(ShelleyBlock (SL.Block _ (SL.TxSeq txs')) _) =
let
(txs, certs, _) = unzip3 $ map fromShelleyTx $ toList txs'

Expand Down
6 changes: 2 additions & 4 deletions lib/shelley/src/Cardano/Wallet/Shelley/Network.hs
Original file line number Diff line number Diff line change
Expand Up @@ -155,15 +155,13 @@ import Ouroboros.Consensus.HardFork.Combinator
import Ouroboros.Consensus.HardFork.Combinator.AcrossEras
( MismatchEraInfo )
import Ouroboros.Consensus.HardFork.History.Qry
( Interpreter (..) )
( Interpreter )
import Ouroboros.Consensus.Network.NodeToClient
( ClientCodecs, Codecs' (..), DefaultCodecs, clientCodecs, defaultCodecs )
import Ouroboros.Consensus.Node.NetworkProtocolVersion
( HasNetworkProtocolVersion (..), SupportedNetworkProtocolVersion (..) )
import Ouroboros.Consensus.Shelley.Ledger
( Crypto (..) )
import Ouroboros.Consensus.Shelley.Ledger
( GenTx )
( Crypto, GenTx )
import Ouroboros.Consensus.Shelley.Ledger.Config
( CodecConfig (..) )
import Ouroboros.Consensus.Shelley.Protocol
Expand Down
6 changes: 3 additions & 3 deletions lib/shelley/src/Cardano/Wallet/Shelley/Pools.hs
Original file line number Diff line number Diff line change
Expand Up @@ -114,7 +114,7 @@ import Fmt
import GHC.Generics
( Generic )
import Ouroboros.Consensus.Cardano.Block
( CardanoBlock (..), HardForkBlock (..) )
( CardanoBlock, HardForkBlock (..) )
import Ouroboros.Consensus.Shelley.Protocol
( TPraosCrypto )

Expand All @@ -140,8 +140,8 @@ data StakePoolLayer = StakePoolLayer
}

newStakePoolLayer
:: forall sc. (TPraosCrypto sc)
=> GenesisParameters
:: forall sc.
GenesisParameters
-> NetworkLayer IO (IO Shelley) (CardanoBlock sc)
-> DBLayer IO
-> StakePoolLayer
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -50,13 +50,13 @@ import Cardano.Wallet.Primitive.Types
, SlotId (..)
)
import Cardano.Wallet.Shelley.Compatibility
( ShelleyBlock
( CardanoBlock
, TPraosStandardCrypto
, decentralizationLevelFromPParams
, fromTip
, invertUnitInterval
, toCardanoHash
, toPoint
, toShelleyHash
)
import Cardano.Wallet.Unsafe
( unsafeMkEntropy )
Expand Down Expand Up @@ -87,7 +87,7 @@ import GHC.TypeLits
import Ouroboros.Consensus.Shelley.Protocol.Crypto
( Crypto (..) )
import Ouroboros.Network.Block
( BlockNo (..), SlotNo (..), Tip (..), getTipPoint )
( BlockNo (..), Point, SlotNo (..), Tip (..), getTipPoint )
import Test.Hspec
( Spec, describe, it, shouldBe )
import Test.Hspec.QuickCheck
Expand All @@ -110,6 +110,7 @@ import Test.QuickCheck

import qualified Cardano.Wallet.Primitive.AddressDerivation.Byron as Byron
import qualified Cardano.Wallet.Primitive.AddressDerivation.Shelley as Shelley
import qualified Cardano.Wallet.Primitive.Types as W
import qualified Codec.Binary.Bech32 as Bech32
import qualified Data.ByteString as BS
import qualified Data.Text.Encoding as T
Expand All @@ -122,7 +123,7 @@ spec = do
describe "Conversions" $
it "toPoint' . fromTip' == getTipPoint" $ property $ \gh tip -> do
let fromTip' = fromTip gh
let toPoint' = toPoint gh
let toPoint' = toPoint gh :: W.BlockHeader -> Point (CardanoBlock TPraosStandardCrypto)
toPoint' (fromTip' tip) === (getTipPoint tip)

describe "Shelley StakeAddress" $ do
Expand Down Expand Up @@ -231,15 +232,15 @@ instance Arbitrary (Hash "BlockHeader") where
instance Arbitrary ChimericAccount where
arbitrary = ChimericAccount . BS.pack <$> vector 28

instance Arbitrary (Tip ShelleyBlock) where
instance Arbitrary (Tip (CardanoBlock TPraosStandardCrypto)) where
arbitrary = frequency
[ (10, return TipGenesis)
, (90, arbitraryTip)
]
where
arbitraryTip = do
n <- choose (0, 100)
hash <- toShelleyHash
hash <- toCardanoHash
. Hash
. digest (Proxy @(HASH TPraosStandardCrypto))
. BS.pack <$> vector 5
Expand Down

0 comments on commit 4a06270

Please sign in to comment.