Skip to content

Commit

Permalink
Use qualified style for TokenName functions. (#4301)
Browse files Browse the repository at this point in the history
## Issue

None. (Noticed while reviewing.)

## Description

This PR adjusts the names of functions exported by the `TokenName`
module so that the names of functions do not repeat the name
`TokenName`.

As a result, it's more natural to import from `TokenName` in a qualified
style.
  • Loading branch information
jonathanknowles authored Dec 5, 2023
2 parents c9b3326 + de84d27 commit 417e859
Show file tree
Hide file tree
Showing 9 changed files with 47 additions and 43 deletions.
4 changes: 2 additions & 2 deletions lib/local-cluster/lib/Cardano/Wallet/Faucet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -59,7 +59,6 @@ import Cardano.Wallet.Primitive.Types.TokenBundle
)
import Cardano.Wallet.Primitive.Types.TokenName
( TokenName (..)
, nullTokenName
)
import Cardano.Wallet.Primitive.Types.TokenPolicyId
( TokenPolicyId
Expand Down Expand Up @@ -104,6 +103,7 @@ import qualified Cardano.Address.Style.Icarus as Icarus
import qualified Cardano.Wallet.Faucet.Addresses as Addresses
import qualified Cardano.Wallet.Faucet.Mnemonics as Mnemonics
import qualified Cardano.Wallet.Primitive.Types.TokenBundle as TokenBundle
import qualified Cardano.Wallet.Primitive.Types.TokenName as TokenName
import qualified Data.ByteString.Char8 as B8
import qualified Data.List.NonEmpty as NE
import qualified Data.Text as T
Expand Down Expand Up @@ -311,7 +311,7 @@ maryIntegrationTestFunds tips =

bundle p assets = TokenBundle.fromNestedList tips [(p, NE.fromList assets)]

simple p = bundle p [(nullTokenName, TokenQuantity 1_000_000_000)]
simple p = bundle p [(TokenName.empty, TokenQuantity 1_000_000_000)]
fruit p =
bundle
p
Expand Down
26 changes: 13 additions & 13 deletions lib/primitive/lib/Cardano/Wallet/Primitive/Types/TokenName.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,9 +6,9 @@

module Cardano.Wallet.Primitive.Types.TokenName
( TokenName (..)
, mkTokenName
, nullTokenName
, tokenNameMaxLength
, empty
, fromByteString
, maxLength
) where

import Prelude
Expand Down Expand Up @@ -64,27 +64,27 @@ newtype TokenName =
deriving anyclass Hashable

-- | Construct a 'TokenName', validating that the length does not exceed
-- 'tokenNameMaxLength'.
-- 'maxLength'.
--
mkTokenName :: ByteString -> Either String TokenName
mkTokenName bs
| BS.length bs <= tokenNameMaxLength = Right $ UnsafeTokenName bs
fromByteString :: ByteString -> Either String TokenName
fromByteString bs
| BS.length bs <= maxLength = Right $ UnsafeTokenName bs
| otherwise = Left $ "TokenName length " ++ show (BS.length bs)
++ " exceeds maximum of " ++ show tokenNameMaxLength
++ " exceeds maximum of " ++ show maxLength

-- | The empty asset name.
--
-- Asset names may be empty, where a monetary policy script only mints a single
-- asset, or where one asset should be considered as the "default" token for the
-- policy.
--
nullTokenName :: TokenName
nullTokenName = UnsafeTokenName ""
empty :: TokenName
empty = UnsafeTokenName ""

-- | The maximum length of a valid token name.
--
tokenNameMaxLength :: Int
tokenNameMaxLength = 32
maxLength :: Int
maxLength = 32

instance NFData TokenName

Expand All @@ -102,6 +102,6 @@ instance ToText TokenName where

instance FromText TokenName where
fromText = first TextDecodingError
. either (Left . ("TokenName is not hex-encoded: " ++)) mkTokenName
. either (Left . ("TokenName is not hex-encoded: " ++)) fromByteString
. convertFromBase Base16
. T.encodeUtf8
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,6 @@ import Cardano.Wallet.Primitive.Types.TokenMap.Gen
)
import Cardano.Wallet.Primitive.Types.TokenName
( TokenName
, mkTokenName
)
import Cardano.Wallet.Primitive.Types.TokenName.Gen
( genTokenName
Expand Down Expand Up @@ -193,6 +192,7 @@ import Test.Utils.Paths
)

import qualified Cardano.Wallet.Primitive.Types.TokenMap as TokenMap
import qualified Cardano.Wallet.Primitive.Types.TokenName as TokenName
import qualified Cardano.Wallet.Primitive.Types.TokenQuantity as TokenQuantity
import qualified Data.Aeson.Types as Aeson
import qualified Data.Foldable as F
Expand Down Expand Up @@ -848,7 +848,7 @@ testMapPrettyNested = [s|
--------------------------------------------------------------------------------

dummyTokenName :: ByteString -> TokenName
dummyTokenName t = fromRight reportError $ mkTokenName t
dummyTokenName t = fromRight reportError $ TokenName.fromByteString t
where
reportError = error $
"Unable to construct dummy token name from bytes: " <> show t
Expand Down
13 changes: 6 additions & 7 deletions lib/wallet/api/http/Cardano/Wallet/Api/Http/Shelley/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -604,8 +604,6 @@ import Cardano.Wallet.Primitive.Types.TokenMap
)
import Cardano.Wallet.Primitive.Types.TokenName
( TokenName (..)
, nullTokenName
, tokenNameMaxLength
)
import Cardano.Wallet.Primitive.Types.TokenPolicyId
( TokenPolicyId (..)
Expand Down Expand Up @@ -894,6 +892,7 @@ import qualified Cardano.Wallet.Primitive.Ledger.Convert as Convert
import qualified Cardano.Wallet.Primitive.Types as W
import qualified Cardano.Wallet.Primitive.Types.Coin as Coin
import qualified Cardano.Wallet.Primitive.Types.TokenBundle as TokenBundle
import qualified Cardano.Wallet.Primitive.Types.TokenName as TokenName
import qualified Cardano.Wallet.Primitive.Types.Tx.SealedTx as W
( SealedTx
, sealedTxFromCardano
Expand Down Expand Up @@ -2257,7 +2256,7 @@ getAssetDefault
-> ApiT WalletId
-> ApiT TokenPolicyId
-> Handler ApiAsset
getAssetDefault ctx wid pid = getAsset ctx wid pid (ApiT nullTokenName)
getAssetDefault ctx wid pid = getAsset ctx wid pid (ApiT TokenName.empty)

{-------------------------------------------------------------------------------
Addresses
Expand Down Expand Up @@ -2944,11 +2943,11 @@ constructTransaction api argGenChange knownPools poolStatus apiWalletId body = d
where
updateFromScript :: ApiMintBurnDataFromScript n -> ApiMintBurnDataFromScript n
updateFromScript mbd = case mbd ^. #assetName of
Nothing -> mbd {assetName = Just (ApiT nullTokenName)}
Nothing -> mbd {assetName = Just (ApiT TokenName.empty)}
Just _ -> mbd
updateFromInp :: ApiMintBurnDataFromInput n -> ApiMintBurnDataFromInput n
updateFromInp mbd = case mbd ^. #assetName of
Nothing -> mbd {assetName = Just (ApiT nullTokenName)}
Nothing -> mbd {assetName = Just (ApiT TokenName.empty)}
Just _ -> mbd

guardWrongMintingTemplate
Expand All @@ -2974,9 +2973,9 @@ constructTransaction api argGenChange knownPools poolStatus apiWalletId body = d
where
assetNameTooLong mb = case mb ^. #mintBurnData of
Left (ApiMintBurnDataFromScript _ (Just (ApiT (UnsafeTokenName bs))) _) ->
BS.length bs > tokenNameMaxLength
BS.length bs > TokenName.maxLength
Right (ApiMintBurnDataFromInput _ _ (Just (ApiT (UnsafeTokenName bs))) _) ->
BS.length bs > tokenNameMaxLength
BS.length bs > TokenName.maxLength
_ -> error "at this moment there should be asset name attributed"

guardAssetQuantityOutOfBounds
Expand Down
6 changes: 3 additions & 3 deletions lib/wallet/api/http/Cardano/Wallet/Api/Link.hs
Original file line number Diff line number Diff line change
Expand Up @@ -168,7 +168,6 @@ import Cardano.Wallet.Primitive.Types.Hash
)
import Cardano.Wallet.Primitive.Types.TokenName
( TokenName
, nullTokenName
)
import Cardano.Wallet.Primitive.Types.TokenPolicyId
( TokenPolicyId
Expand Down Expand Up @@ -222,6 +221,7 @@ import Web.HttpApiData
)

import qualified Cardano.Wallet.Api as Api
import qualified Cardano.Wallet.Primitive.Types.TokenName as TokenName

--
-- Wallets
Expand Down Expand Up @@ -585,7 +585,7 @@ getAsset
-> TokenName
-> (Method, Text)
getAsset w pid n
| n == nullTokenName = endpoint @Api.GetAssetDefault mkURLDefault
| n == TokenName.empty = endpoint @Api.GetAssetDefault mkURLDefault
| otherwise = endpoint @Api.GetAsset mkURL
where
wid = w ^. typed @(ApiT WalletId)
Expand All @@ -612,7 +612,7 @@ getByronAsset
-> TokenName
-> (Method, Text)
getByronAsset w pid n
| n == nullTokenName = endpoint @Api.GetByronAssetDefault mkURLDefault
| n == TokenName.empty = endpoint @Api.GetByronAssetDefault mkURLDefault
| otherwise = endpoint @Api.GetByronAsset mkURL
where
wid = w ^. typed @(ApiT WalletId)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -316,7 +316,7 @@ spec = describe "BYRON_TRANSACTIONS" $ do

wal <- srcFixture ctx
let polId = TokenPolicy.UnsafeTokenPolicyId $ Hash $ BS.replicate 28 0
let ep = Link.getByronAsset wal polId TokenName.nullTokenName
let ep = Link.getByronAsset wal polId TokenName.empty
r <- request @(ApiAsset) ctx ep Default Empty
expectResponseCode HTTP.status404 r
expectErrorMessage errMsg404NoAsset r
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -1074,7 +1074,7 @@ spec = describe "SHELLEY_TRANSACTIONS" $ do

wal <- fixtureMultiAssetWallet ctx
let polId = TokenPolicy.UnsafeTokenPolicyId $ Hash $ BS.replicate 28 0
let ep = Link.getAsset wal polId TokenName.nullTokenName
let ep = Link.getAsset wal polId TokenName.empty
r <- request @(ApiAsset) ctx ep Default Empty
expectResponseCode HTTP.status404 r
expectErrorMessage errMsg404NoAsset r
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -142,7 +142,6 @@ import Cardano.Wallet.Primitive.Types.TokenFingerprint
)
import Cardano.Wallet.Primitive.Types.TokenName
( TokenName (..)
, mkTokenName
)
import Cardano.Wallet.Primitive.Types.TokenPolicyId
( TokenPolicyId (..)
Expand Down Expand Up @@ -326,6 +325,7 @@ import qualified Cardano.Ledger.Keys as Ledger
import qualified Cardano.Wallet.Address.Derivation.Shelley as Shelley
import qualified Cardano.Wallet.Api.Link as Link
import qualified Cardano.Wallet.Primitive.Types.TokenMap as TokenMap
import qualified Cardano.Wallet.Primitive.Types.TokenName as TokenName
import qualified Data.Aeson as Aeson
import qualified Data.List.NonEmpty as NE
import qualified Data.Map.Strict as Map
Expand Down Expand Up @@ -1328,7 +1328,7 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do

addrsMint <- listAddresses @n ctx wa
let addrMint = (addrsMint !! 1) ^. #id
let Right tokenName' = mkTokenName "ab12"
let Right tokenName' = TokenName.fromByteString "ab12"
let payloadMint = Json [json|{
"mint_burn": [{
"policy_id": #{toText policyId'},
Expand Down Expand Up @@ -3800,7 +3800,7 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do
addrs <- listAddresses @n ctx wa
let destination = (addrs !! 1) ^. #id

let (Right tokenName') = mkTokenName "ab12"
let (Right tokenName') = TokenName.fromByteString "ab12"

let payload = Json [json|{
"mint_burn": [{
Expand Down Expand Up @@ -3840,7 +3840,7 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do
addrs <- listAddresses @n ctx wa
let destination = (addrs !! 1) ^. #id

let (Right tokenName') = mkTokenName "ab12"
let (Right tokenName') = TokenName.fromByteString "ab12"

rSlot <- request @ApiNetworkInformation ctx
Link.getNetworkInfo Default Empty
Expand Down Expand Up @@ -3894,7 +3894,7 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do
addrs <- listAddresses @n ctx wa
let destination = (addrs !! 1) ^. #id

let (Right tokenName') = mkTokenName "ab12"
let (Right tokenName') = TokenName.fromByteString "ab12"

rSlot <- request @ApiNetworkInformation ctx
Link.getNetworkInfo Default Empty
Expand Down Expand Up @@ -3943,7 +3943,7 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do
addrs <- listAddresses @n ctx wa
let destination = (addrs !! 1) ^. #id

let (Right tokenName') = mkTokenName "ab12"
let (Right tokenName') = TokenName.fromByteString "ab12"
let payloadMint = Json [json|{
"mint_burn": [{
"policy_script_template":
Expand Down Expand Up @@ -3992,7 +3992,7 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do
addrs <- listAddresses @n ctx wa
let destination = (addrs !! 1) ^. #id

let (Right tokenName') = mkTokenName ""
let (Right tokenName') = TokenName.fromByteString ""
let payloadMint = Json [json|{
"mint_burn": [
{ "policy_script_template":
Expand Down Expand Up @@ -4041,7 +4041,7 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do
addrs <- listAddresses @n ctx wForeign
let destination = (addrs !! 1) ^. #id

let (Right tokenName') = mkTokenName "ab12"
let (Right tokenName') = TokenName.fromByteString "ab12"

let payload = Json [json|{
"mint_burn": [
Expand Down
17 changes: 11 additions & 6 deletions lib/wallet/test/unit/Cardano/Wallet/TokenMetadataSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,9 +21,6 @@ import Cardano.Wallet.Primitive.Types.TokenMetadata
, AssetMetadata (..)
, AssetURL (..)
)
import Cardano.Wallet.Primitive.Types.TokenName
( nullTokenName
)
import Cardano.Wallet.Primitive.Types.TokenPolicyId
( TokenPolicyId (..)
)
Expand Down Expand Up @@ -79,6 +76,8 @@ import Test.Utils.Trace
( traceSpec
)

import qualified Cardano.Wallet.Primitive.Types.TokenName as TokenName

spec :: Spec
spec = do
describe "JSON decoding" $ do
Expand Down Expand Up @@ -140,14 +139,18 @@ spec = do
withMetadataServer (queryServerStatic golden1File) $ \srv -> do
client <- newMetadataClient tr (Just srv)
let subj = "7f71940915ea5fe85e840f843c929eba467e6f050475bad1f10b9c27"
let aid = AssetId (UnsafeTokenPolicyId (unsafeFromText subj)) nullTokenName
let aid = AssetId
(UnsafeTokenPolicyId (unsafeFromText subj))
TokenName.empty
getTokenMetadata client [assetIdFromSubject (Subject subj)]
`shouldReturn` Right [(aid, golden1Metadata0)]

it "ill-formatted entry doesn't make the entire response fail to parse" $ \tr -> do
withMetadataServer (queryServerStatic golden2File) $ \srv -> do
client <- newMetadataClient tr (Just srv)
let aid subj = AssetId (UnsafeTokenPolicyId (unsafeFromText subj)) nullTokenName
let aid subj = AssetId
(UnsafeTokenPolicyId (unsafeFromText subj))
TokenName.empty
let aid1 = aid "7f71940915ea5fe85e840f843c929eba467e6f050475bad1f10b9c27"
let aid2 = aid "bad00000000000000000000000000000000000000000000000000000"
getTokenMetadata client [aid1, aid2]
Expand All @@ -156,7 +159,9 @@ spec = do
it "missing subject" $ \tr ->
withMetadataServer (queryServerStatic golden1File) $ \srv -> do
client <- newMetadataClient tr (Just srv)
let aid = AssetId (UnsafeTokenPolicyId (Hash "a")) nullTokenName
let aid = AssetId
(UnsafeTokenPolicyId (Hash "a"))
TokenName.empty
res <- getTokenMetadata client [aid]
res `shouldBe` Right []

Expand Down

0 comments on commit 417e859

Please sign in to comment.