Skip to content

Commit

Permalink
Bump libraries to target most recent cardano-node
Browse files Browse the repository at this point in the history
  • Loading branch information
Anviking committed Jun 15, 2020
1 parent 0fd7262 commit b0a7c42
Show file tree
Hide file tree
Showing 49 changed files with 340 additions and 130 deletions.
4 changes: 2 additions & 2 deletions lib/byron/src/Cardano/Wallet/Byron/Network.hs
Original file line number Diff line number Diff line change
Expand Up @@ -318,7 +318,7 @@ mkWalletClient
-> m (NetworkClient m)
mkWalletClient gp chainSyncQ = do
responsesBuffer <- atomically newTQueue
pure $ nodeToClientProtocols (const NodeToClientProtocols
pure $ nodeToClientProtocols (const $ pure $ NodeToClientProtocols
{ localChainSyncProtocol =
let
fromTip' =
Expand Down Expand Up @@ -391,7 +391,7 @@ mkTipSyncClient tr np localTxSubmissionQ onTipUpdate onProtocolParamsUpdate = do
onTipUpdate tip
queryLocalState (getTipPoint tip)

pure $ nodeToClientProtocols (const NodeToClientProtocols
pure $ nodeToClientProtocols (const $ pure $ NodeToClientProtocols
{ localChainSyncProtocol =
let
codec = cChainSyncCodec codecs
Expand Down
22 changes: 7 additions & 15 deletions lib/shelley/src/Cardano/Wallet/Shelley/Compatibility.hs
Original file line number Diff line number Diff line change
Expand Up @@ -120,14 +120,8 @@ import GHC.Stack
( HasCallStack )
import Numeric.Natural
( Natural )
import Ouroboros.Consensus.BlockchainTime.WallClock.Types
( SlotLength (..), getSystemStart )
import Ouroboros.Consensus.Protocol.Abstract
( SecurityParam (..) )
import Ouroboros.Consensus.Shelley.Ledger
( GenTx, ShelleyHash (..) )
import Ouroboros.Consensus.Shelley.Node
( initialFundsPseudoTxIn )
import Ouroboros.Consensus.Shelley.Protocol.Crypto
( TPraosStandardCrypto )
import Ouroboros.Network.Block
Expand Down Expand Up @@ -170,6 +164,7 @@ import qualified Shelley.Spec.Ledger.BaseTypes as SL
import qualified Shelley.Spec.Ledger.BlockChain as SL
import qualified Shelley.Spec.Ledger.Coin as SL
import qualified Shelley.Spec.Ledger.Credential as SL
import qualified Shelley.Spec.Ledger.Genesis as SL
import qualified Shelley.Spec.Ledger.Keys as SL
import qualified Shelley.Spec.Ledger.LedgerState as SL
import qualified Shelley.Spec.Ledger.PParams as SL
Expand Down Expand Up @@ -386,10 +381,6 @@ fromTip' gp = fromTip getGenesisBlockHash getEpochLength
, getGenesisBlockHash
} = gp

fromSlotLength :: SlotLength -> W.SlotLength
fromSlotLength = W.SlotLength
. getSlotLength

-- NOTE: Unsafe conversion from Natural -> Word16
fromMaxTxSize :: Natural -> Quantity "byte" Word16
fromMaxTxSize =
Expand Down Expand Up @@ -429,6 +420,7 @@ decentralizationLevelFromPParams
decentralizationLevelFromPParams pp =
either reportInvalidValue W.DecentralizationLevel
$ mkPercentage
$ toRational
$ SL.intervalValue
-- We must invert the value provided: (see function comment)
$ invertUnitInterval d
Expand Down Expand Up @@ -464,13 +456,13 @@ fromGenesisData g =
{ genesisParameters = W.GenesisParameters
{ getGenesisBlockHash = dummyGenesisHash
, getGenesisBlockDate =
W.StartTime . getSystemStart . sgSystemStart $ g
W.StartTime . sgSystemStart $ g
, getSlotLength =
fromSlotLength . sgSlotLength $ g
W.SlotLength $ sgSlotLength g
, getEpochLength =
W.EpochLength . fromIntegral . unEpochSize . sgEpochLength $ g
, getEpochStability =
Quantity . fromIntegral . maxRollbacks . sgSecurityParam $ g
Quantity . fromIntegral . sgSecurityParam $ g
, getActiveSlotCoefficient =
W.ActiveSlotCoefficient 1.0
}
Expand Down Expand Up @@ -515,7 +507,7 @@ fromGenesisData g =
[W.TxOut (fromShelleyAddress addr) (fromShelleyCoin c)]
where
W.TxIn pseudoHash _ = fromShelleyTxIn $
initialFundsPseudoTxIn @TPraosStandardCrypto addr
SL.initialFundsPseudoTxIn @TPraosStandardCrypto addr

fromNetworkMagic :: NetworkMagic -> W.ProtocolMagic
fromNetworkMagic (NetworkMagic magic) =
Expand Down Expand Up @@ -559,7 +551,7 @@ fromShelleyCoin (SL.Coin c) = W.Coin $ unsafeCast c

-- NOTE: For resolved inputs we have to pass in a dummy value of 0.
fromShelleyTx :: SL.Tx TPraosStandardCrypto -> (W.Tx, [W.DelegationCertificate])
fromShelleyTx (SL.Tx bod@(SL.TxBody ins outs certs _ _ _ _ _) _ _ _) =
fromShelleyTx (SL.Tx bod@(SL.TxBody ins outs certs _ _ _ _ _) _ _) =
( W.Tx
(fromShelleyTxId $ SL.txid bod)
(map ((,W.Coin 0) . fromShelleyTxIn) (toList ins))
Expand Down
4 changes: 2 additions & 2 deletions lib/shelley/src/Cardano/Wallet/Shelley/Launch.hs
Original file line number Diff line number Diff line change
Expand Up @@ -182,7 +182,7 @@ parseGenesisData = \case
TestnetConfig genesisFile -> do
(genesis :: ShelleyGenesis TPraosStandardCrypto)
<- ExceptT $ eitherDecode <$> BL.readFile genesisFile
let nm = unNetworkMagic $ sgNetworkMagic genesis
let nm = sgNetworkMagic genesis
let (discriminant, vData) =
someTestnetDiscriminant $ ProtocolMagic $ fromIntegral nm
let (np, block0) = fromGenesisData genesis
Expand Down Expand Up @@ -434,7 +434,7 @@ genConfig dir severity = do
( dir </> "node.config"
, block0
, networkParameters
, (NodeToClientVersionData nm, nodeToClientCodecCBORTerm)
, (NodeToClientVersionData $ NetworkMagic nm, nodeToClientCodecCBORTerm)
)
where
source :: FilePath
Expand Down
6 changes: 3 additions & 3 deletions lib/shelley/src/Cardano/Wallet/Shelley/Network.hs
Original file line number Diff line number Diff line change
Expand Up @@ -364,7 +364,7 @@ mkWalletClient
-> m (NetworkClient m)
mkWalletClient gp chainSyncQ = do
stash <- atomically newTQueue
pure $ nodeToClientProtocols (const NodeToClientProtocols
pure $ nodeToClientProtocols (const $ return $ NodeToClientProtocols
{ localChainSyncProtocol =
let
codec = cChainSyncCodec codecs
Expand Down Expand Up @@ -393,7 +393,7 @@ mkDelegationRewardsClient
-- ^ Communication channel with the LocalStateQuery client
-> NetworkClient m
mkDelegationRewardsClient tr queryRewardQ =
nodeToClientProtocols (const NodeToClientProtocols
nodeToClientProtocols (const $ return $ NodeToClientProtocols
{ localChainSyncProtocol =
doNothingProtocol

Expand Down Expand Up @@ -480,7 +480,7 @@ mkTipSyncClient tr np localTxSubmissionQ onTipUpdate onPParamsUpdate = do
onTipUpdate tip
queryLocalState (getTipPoint tip)

pure $ nodeToClientProtocols (const NodeToClientProtocols
pure $ nodeToClientProtocols (const $ return $ NodeToClientProtocols
{ localChainSyncProtocol =
let
codec = cChainSyncCodec $ serialisedCodecs @m
Expand Down
25 changes: 12 additions & 13 deletions lib/shelley/src/Cardano/Wallet/Shelley/Transaction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -106,6 +106,7 @@ import qualified Shelley.Spec.Ledger.BaseTypes as SL
import qualified Shelley.Spec.Ledger.Keys as SL
import qualified Shelley.Spec.Ledger.LedgerState as SL
import qualified Shelley.Spec.Ledger.Tx as SL
import qualified Shelley.Spec.Ledger.TxData as SL
import qualified Shelley.Spec.Ledger.UTxO as SL

newTransactionLayer
Expand Down Expand Up @@ -142,10 +143,10 @@ newTransactionLayer _proxy _protocolMagic epochLength = TransactionLayer
(k, pwd) <- lookupPrivateKey keyFrom addr
pure $ mkWitness unsigned (getRawKey k, pwd)

let scriptWits = mempty
let metadata = SL.SNothing
let metadata = SL.SNothing

pure $ toSealed $ SL.Tx unsigned addrWits scriptWits metadata
let wits = SL.WitnessSet addrWits mempty mempty
pure $ toSealed $ SL.Tx unsigned wits metadata

_mkDelegationJoinTx
:: WalletDelegation
Expand Down Expand Up @@ -174,11 +175,9 @@ newTransactionLayer _proxy _protocolMagic epochLength = TransactionLayer
pure $ mkWitness unsigned (getRawKey k, pwd)
let certWits =
Set.singleton (mkWitness unsigned (getRawKey accXPrv, pwd'))
let scriptWits =
mempty
let wits = Set.unions [addrWits,certWits]
let wits = SL.WitnessSet (Set.union addrWits certWits) mempty mempty

pure $ toSealed $ SL.Tx unsigned wits scriptWits metadata
pure $ toSealed $ SL.Tx unsigned wits metadata

_mkDelegationQuitTx
:: (k 'AddressK XPrv, Passphrase "encryption")
Expand All @@ -199,11 +198,9 @@ newTransactionLayer _proxy _protocolMagic epochLength = TransactionLayer
pure $ mkWitness unsigned (getRawKey k, pwd)
let certWits =
Set.singleton (mkWitness unsigned (getRawKey accXPrv, pwd'))
let scriptWits =
mempty
let wits = Set.unions [addrWits,certWits]
let wits = SL.WitnessSet (Set.union addrWits certWits) mempty mempty

pure $ toSealed $ SL.Tx unsigned wits scriptWits metadata
pure $ toSealed $ SL.Tx unsigned wits metadata


_estimateMaxNumberOfInputs
Expand All @@ -223,15 +220,15 @@ _minimumFee
-> Fee
_minimumFee policy (WithDelegation withDelegation) (CoinSelection inps outs chngs) =
computeFee $ SL.txsize $
SL.Tx unsigned addrWits scriptWits metadata
SL.Tx unsigned wits metadata
where
computeFee :: Integer -> Fee
computeFee size =
Fee $ ceiling (a + b*fromIntegral size)
where
LinearFee (Quantity a) (Quantity b) (Quantity _unused) = policy

scriptWits = mempty
wits = SL.WitnessSet addrWits mempty mempty

metadata = SL.SNothing

Expand Down Expand Up @@ -280,7 +277,9 @@ mkUnsignedTx ttl ownedIns outs certs =
ttl
(realFee (snd <$> ownedIns) outs)
certs
(Cardano.WithdrawalsShelley $ SL.Wdrl mempty) -- Withdrawals
Nothing -- Update
Nothing -- Metadata hash
in
unsigned

Expand Down
1 change: 1 addition & 0 deletions lib/shelley/test/data/cardano-node-shelley/genesis.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ protocolParams:
nOpt: 100
rho: 0
poolMinRefund: 0
minPoolCost: 0
tau: 0
a0: 0
genDelegs:
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -59,11 +59,13 @@ import Data.Function
import Data.Proxy
( Proxy (..) )
import Data.Ratio
( (%) )
( Ratio, (%) )
import Data.Text
( Text )
import Data.Text.Class
( toText )
import Data.Word
( Word64 )
import GHC.TypeLits
( natVal )
import Ouroboros.Consensus.Shelley.Protocol.Crypto
Expand Down Expand Up @@ -136,7 +138,7 @@ spec = do
let mkDecentralizationParam :: SL.UnitInterval -> SL.PParams
mkDecentralizationParam i = SL.emptyPParams { SL._d = i }

let testCases :: [(Rational, Text)]
let testCases :: [(Ratio Word64, Text)]
testCases =
[ (10 % 10, "0.00%")
, ( 9 % 10, "10.00%")
Expand Down
4 changes: 2 additions & 2 deletions nix/.stack.nix/Win32-network.nix

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 2 additions & 2 deletions nix/.stack.nix/byron-spec-chain.nix

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 2 additions & 2 deletions nix/.stack.nix/byron-spec-ledger.nix

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

5 changes: 3 additions & 2 deletions nix/.stack.nix/cardano-api.nix

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

6 changes: 4 additions & 2 deletions nix/.stack.nix/cardano-cli.nix

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 2 additions & 2 deletions nix/.stack.nix/cardano-config.nix

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 2 additions & 2 deletions nix/.stack.nix/cardano-crypto-test.nix

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 2 additions & 2 deletions nix/.stack.nix/cardano-crypto-wrapper.nix

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 2 additions & 2 deletions nix/.stack.nix/cardano-ledger-test.nix

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 2 additions & 2 deletions nix/.stack.nix/cardano-ledger.nix

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

Loading

0 comments on commit b0a7c42

Please sign in to comment.