Skip to content

Commit

Permalink
chore: extract faucet yaml-file writing functionality. (#4208)
Browse files Browse the repository at this point in the history
I have extracted a group of functions related by their purpose (faucet
writing) into a separate module

### Issue Number

ADP-3137
  • Loading branch information
Unisay authored Nov 7, 2023
2 parents 2f92c63 + a690298 commit 996d90e
Show file tree
Hide file tree
Showing 3 changed files with 119 additions and 80 deletions.
84 changes: 4 additions & 80 deletions lib/local-cluster/lib/Cardano/Wallet/Faucet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,11 +33,10 @@ module Cardano.Wallet.Faucet
, hwLedgerTestFunds
, seaHorseTestAssets

, byronAddresses
, icarusAddresses

-- * Internals
, genByronFaucets
, genIcarusFaucets
, genShelleyFaucets
, genMAFaucets
, genMnemonics
, deriveShelleyAddresses
, deriveShelleyRewardAccount
Expand All @@ -49,8 +48,6 @@ import Prelude hiding

import Cardano.Address
( Address
, base58
, unAddress
)
import Cardano.Address.Derivation
( AccountIndexDerivationType
Expand Down Expand Up @@ -86,7 +83,6 @@ import Cardano.Mnemonic
, ValidMnemonicSentence
, entropyToMnemonic
, genEntropy
, mnemonicToText
)
import Cardano.Wallet.Primitive.Types.Coin
( Coin (..)
Expand All @@ -107,26 +103,17 @@ import Cardano.Wallet.Unsafe
, unsafeMkMnemonic
)
import Control.Monad
( forM
, forM_
, replicateM
( replicateM
)
import Data.Bifunctor
( first
)
import Data.ByteArray.Encoding
( Base (..)
, convertToBase
)
import Data.ByteString
( ByteString
)
import Data.List
( unfoldr
)
import Data.Text
( Text
)
import Data.Tuple.Extra
( dupe
)
Expand All @@ -149,8 +136,6 @@ import qualified Cardano.Wallet.Primitive.Types.TokenBundle as TokenBundle
import qualified Data.ByteString.Char8 as B8
import qualified Data.List.NonEmpty as NE
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as TIO

-- | An opaque 'Faucet' type from which one can get a wallet with funds
data Faucet = Faucet
Expand Down Expand Up @@ -209,12 +194,6 @@ instance NextWallet "ma" where
nextTxBuilder :: Faucet -> IO ((Address, Coin) -> IO ByteString)
nextTxBuilder (Faucet _ _ _ _ _ mvar) = takeNext "txBuilder" mvar

-- | Generate faucets addresses and mnemonics to a file.
--
-- >>> genMnemonics 100 >>= genByronFaucets "byron-faucets.yaml"
genByronFaucets :: CA.NetworkTag -> FilePath -> [Mnemonic 12] -> IO [[Text]]
genByronFaucets = genFaucet base58 . byronAddresses

byronAddresses :: KnownNat mw => CA.NetworkTag -> Mnemonic mw -> [Address]
byronAddresses networkTag mw = mkPaymentAddrForIx <$> paymentKeyIxs
where
Expand All @@ -237,12 +216,6 @@ byronAddresses networkTag mw = mkPaymentAddrForIx <$> paymentKeyIxs
accountIx :: Index (AddressIndexDerivationType Byron) AccountK =
coerceWholeDomainIndex (minBound :: Index Hardened AccountK)

-- | Generate faucets addresses and mnemonics to a file.
--
-- >>> genMnemonics 100 >>= genIcarusFaucets (CA.NetworkTag 42) "icarus-faucets.yaml"
genIcarusFaucets :: CA.NetworkTag -> FilePath -> [Mnemonic 15] -> IO [[Text]]
genIcarusFaucets = genFaucet base58 . icarusAddresses

icarusAddresses :: CA.NetworkTag -> Mnemonic 15 -> [Address]
icarusAddresses networkTag mw = mkPaymentAddrForIx <$> paymentKeyIxs
where
Expand All @@ -263,22 +236,6 @@ icarusAddresses networkTag mw = mkPaymentAddrForIx <$> paymentKeyIxs
minBound
masterKey = genMasterKeyFromMnemonic (SomeMnemonic mw) mempty

-- | Generate faucet addresses and mnemonics to a file.
--
-- >>> genMnemonics 100 >>= genShelleyFaucets "shelley-faucets.yaml"
genShelleyFaucets :: FilePath -> [Mnemonic 15] -> IO [[Text]]
genShelleyFaucets =
genFaucet encodeAddressHex (deriveShelleyAddresses . SomeMnemonic)

-- | Generate faucet addresses and mnemonics to a file.
--
-- >>> genMnemonics 100 >>= genMAFaucets "ma-faucets.yaml"
genMAFaucets :: FilePath -> [Mnemonic 24] -> IO [[Text]]
genMAFaucets = genFaucet encodeAddressHex (deriveShelleyAddresses . SomeMnemonic)

encodeAddressHex :: Address -> Text
encodeAddressHex = T.decodeUtf8 . convertToBase Base16 . unAddress

deriveShelleyAddresses :: SomeMnemonic -> [Address]
deriveShelleyAddresses mnemonic = mkPaymentAddrForIx <$> paymentKeyIxs
where
Expand Down Expand Up @@ -308,39 +265,6 @@ deriveShelleyAccountKey mnemonic = deriveAccountPrivateKey masterKey accountIx
accountIx :: Index 'Hardened 'AccountK = minBound
masterKey = genMasterKeyFromMnemonic mnemonic mempty

-- | Abstract function for generating a faucet as a YAML file.
--
-- Returns the generated mnemonics as Text.
genFaucet
:: forall a mw
. (a -> Text)
-> (Mnemonic mw -> [a])
-> FilePath
-> [Mnemonic mw]
-> IO [[Text]]
genFaucet encodeAddress genAddresses file mnemonics = do
TIO.writeFile file ""
forM [(mnemonicToText m, take 10 (genAddresses m)) | m <- mnemonics]
$ \(mnem, addrs) -> do
let comment = ("# " <>)
$ T.intercalate ", "
$ map (surroundedBy '"') mnem
appendFile file comment
forM_ addrs (appendFile file . encodeFaucet)
pure mnem
where
surroundedBy :: Char -> Text -> Text
surroundedBy c txt = T.singleton c <> txt <> T.singleton c

encodeFaucet :: a -> Text
encodeFaucet addr =
" " <> encodeAddress addr <> ": " <> T.pack (show faucetAmount)
where
faucetAmount :: Int = ada 100_000 where ada = (* 1000_000)

appendFile :: FilePath -> Text -> IO ()
appendFile f txt = TIO.appendFile f (txt <> "\n")

genMnemonics
:: forall mw ent csz
. ( ValidMnemonicSentence mw
Expand Down
114 changes: 114 additions & 0 deletions lib/local-cluster/lib/Cardano/Wallet/Faucet/Writer.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,114 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}

{- | This module contains functionality to generate faucet addresses.
It is not used at the moment by the local cluster, but it might be useful
for troubleshooting to introspect addresses derived from mnemonics.
-}
module Cardano.Wallet.Faucet.Writer
( genByronFaucets
, genIcarusFaucets
, genShelleyFaucets
, genMaryAllegraFaucets
) where

import Prelude

import Cardano.Address
( Address
, base58
, unAddress
)
import Cardano.Mnemonic
( Mnemonic
, SomeMnemonic (..)
, mnemonicToText
)
import Cardano.Wallet.Faucet
( byronAddresses
, deriveShelleyAddresses
, icarusAddresses
)
import Control.Monad
( forM
, forM_
)
import Data.ByteArray.Encoding
( Base (Base16)
, convertToBase
)
import Data.Text
( Text
)

import qualified Cardano.Address as CA
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as TIO

-- | Generate faucets addresses and mnemonics to a file.
--
-- >>> genMnemonics 100 >>= genByronFaucets "byron-faucets.yaml"
genByronFaucets :: CA.NetworkTag -> FilePath -> [Mnemonic 12] -> IO [[Text]]
genByronFaucets = genFaucet base58 . byronAddresses

-- | Generate faucets addresses and mnemonics to a file.
--
-- >>> genMnemonics 100 >>= genIcarusFaucets (CA.NetworkTag 42) "icarus-faucets.yaml"
genIcarusFaucets :: CA.NetworkTag -> FilePath -> [Mnemonic 15] -> IO [[Text]]
genIcarusFaucets = genFaucet base58 . icarusAddresses

-- | Generate faucet addresses and mnemonics to a file.
--
-- >>> genMnemonics 100 >>= genShelleyFaucets "shelley-faucets.yaml"
genShelleyFaucets :: FilePath -> [Mnemonic 15] -> IO [[Text]]
genShelleyFaucets =
genFaucet encodeAddressHex (deriveShelleyAddresses . SomeMnemonic)

-- | Generate faucet addresses and mnemonics to a file.
--
-- >>> genMnemonics 100 >>= genMaryAllegraFaucets "ma-faucets.yaml"
genMaryAllegraFaucets :: FilePath -> [Mnemonic 24] -> IO [[Text]]
genMaryAllegraFaucets =
genFaucet encodeAddressHex (deriveShelleyAddresses . SomeMnemonic)

-- | Abstract function for generating a faucet as a YAML file.
--
-- Returns the generated mnemonics as Text.
genFaucet
:: forall a mw
. (a -> Text)
-> (Mnemonic mw -> [a])
-> FilePath
-> [Mnemonic mw]
-> IO [[Text]]
genFaucet encodeAddress genAddresses file mnemonics = do
TIO.writeFile file ""
forM [(mnemonicToText m, take 10 (genAddresses m)) | m <- mnemonics]
$ \(mnem, addrs) -> do
let comment = ("# " <>)
$ T.intercalate ", "
$ map (surroundedBy '"') mnem
appendToFile file comment
forM_ addrs (appendToFile file . encodeFaucet)
pure mnem
where
surroundedBy :: Char -> Text -> Text
surroundedBy c txt = T.singleton c <> txt <> T.singleton c

encodeFaucet :: a -> Text
encodeFaucet addr =
" " <> encodeAddress addr <> ": " <> T.pack (show faucetAmount)
where
faucetAmount :: Int = ada 100_000 where ada = (* 1000_000)

appendToFile :: FilePath -> Text -> IO ()
appendToFile f txt = TIO.appendFile f (txt <> "\n")

--------------------------------------------------------------------------------
-- Utility functions -----------------------------------------------------------

encodeAddressHex :: Address -> Text
encodeAddressHex = T.decodeUtf8 . convertToBase Base16 . unAddress
1 change: 1 addition & 0 deletions lib/local-cluster/local-cluster.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,7 @@ library
Cardano.Node.Cli.Launcher
Cardano.Wallet.Cli.Launcher
Cardano.Wallet.Faucet
Cardano.Wallet.Faucet.Writer
Cardano.Wallet.Faucet.Mnemonics
Cardano.Wallet.Faucet.Shelley
Cardano.Wallet.Launch.Cluster
Expand Down

0 comments on commit 996d90e

Please sign in to comment.