diff --git a/ChangeLog.md b/ChangeLog.md index 81e3167..0bfee8c 100644 --- a/ChangeLog.md +++ b/ChangeLog.md @@ -2,6 +2,10 @@ ## Unreleased changes +## 0.21 + +Add support for CIS2TokenMetadata and CIS2TokenBalance queries. + ## 0.20 Add support for protocol version 5. diff --git a/README.md b/README.md index 1345519..83d37bd 100644 --- a/README.md +++ b/README.md @@ -15,9 +15,9 @@ The wallet proxy provides the following endpoints: of a transfer or credential deployment * `PUT /v0/submitCredential`: deploy a credential/create an account * `PUT /v0/submitTransfer`: perform a simple transfer -* `GET /v0/accTransactions/{accountNumber}`: get the transactions affecting an account -* `GET /v1/accTransactions/{accountNumber}`: get the transactions affecting an account, including memos -* `PUT /v0/testnetGTUDrop/{accountNumber}`: request a CCD drop to the specified account +* `GET /v0/accTransactions/{account address}`: get the transactions affecting an account +* `GET /v1/accTransactions/{account address}`: get the transactions affecting an account, including memos +* `PUT /v0/testnetGTUDrop/{account address}`: request a CCD drop to the specified account * `GET /v0/health`: get a response specifying if the wallet proxy is up to date * `GET /v0/global`: get the cryptographic parameters obtained from the node it is connected to * `GET /v0/ip_info`: get the identity providers information, including links for @@ -29,7 +29,10 @@ The wallet proxy provides the following endpoints: * `GET /v0/appSettings`: get the up-to-date status of the old mobile wallet app. * `GET /v1/appSettings`: get the up-to-date status of the new mobile wallet app. * `GET /v0/epochLength`: get the epoch length in milliseconds. -* `GET /v0/CIS2Tokens`: get the list of tokens on a given contract address. +* `GET /v0/CIS2Tokens/{index}/{subindex}`: get the list of tokens on a given contract address. +* `GET /v0/CIS2TokenMetadata/{index}/{subindex}`: get the metadata of tokens in on given contract address. +* `GET /v0/CIS2TokenMetadata/{index}/{subindex}/{account address}`: get the balance of tokens on given contract address for a given account address. + ### Errors @@ -729,6 +732,94 @@ The return value is an object with fields - `totalSupply` ... a non-negative integer (encoded in a string) that records the total supply of the token as computed by using `Mint` and `Burn` events. +## Get metadata URL for a list of tokens + +The endpoint `v0/CIS2TokenMetadata/index/subindex` retrieves a list of token +metadata URLs. + +The following parameters are supported and required +- `tokenId`: a comma separated list of token IDs. Token IDs are hex encoded, in + the same format as that returned by `CIS2Tokens` endpoint. An empty string is interpreted + as a single token with an empty ID. + +The return value is a JSON list of objects with fields +- `metadataURL` (required) ... a string value that contains a URL returned by + the contract. The client should do validation that this is a usable URL, since + it is purely up to the smart contract to return this value. +- `tokenId` (required) ... the token ID as in the query +- `metadataChecksum` (optional) ... if `null` then no checksum is included in + the contract. Otherwise it is a hex string that contains the SHA256 hash of the **data at the URL**. + +An example query is +``` +v0/CIS2TokenMetadata/996/0?tokenId=0b5000b73a53f0916c93c68f4b9b6ba8af5a10978634ae4f2237e1f3fbe324fa,1209fe3bc3497e47376dfbd9df0600a17c63384c85f859671956d8289e5a0be8,1209fe3bc3497e47376dfbd9df0600a17c63384c85f859671956d8289e5a0be8 +``` + +and an example response is +```json +[ + { + "metadataChecksum": "aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa", + "metadataURL": "https://some.example/token/0B5000B73A53F0916C93C68F4B9B6BA8AF5A10978634AE4F2237E1F3FBE324FA", + "tokenId": "0b5000b73a53f0916c93c68f4b9b6ba8af5a10978634ae4f2237e1f3fbe324fa" + }, + { + "metadataChecksum": null, + "metadataURL": "https://some.example/token/1209FE3BC3497E47376DFBD9DF0600A17C63384C85F859671956D8289E5A0BE8", + "tokenId": "1209fe3bc3497e47376dfbd9df0600a17c63384c85f859671956d8289e5a0be8" + }, + { + "metadataChecksum": null, + "metadataURL": "https://some.example/token/1209FE3BC3497E47376DFBD9DF0600A17C63384C85F859671956D8289E5A0BE8", + "tokenId": "1209fe3bc3497e47376dfbd9df0600a17c63384c85f859671956d8289e5a0be8" + } +] +``` + +## Get token balance for an account address + +The endpoint `v0/CIS2TokenBalance/index/subindex/accountAddress` retrieves the +balance of tokens for the given account address. + +The following parameters are supported and required +- `tokenId`: a comma separated list of token IDs. Token IDs are hex encoded, in + the same format as that returned by `CIS2Tokens` endpoint. An empty string is interpreted + as a single token with an empty ID. + +The return value is a JSON list of objects with fields + +- `balance` (required) ... a string that contains the balance as a decimal + number. The balance is always non-negative, but can be very large, and will + not fit into a 64-bit integer in general. The value should always fit into a + 256-bit unsigned integer though. Generally unbounded integral type should be + used for parsing. The metadata contains information on how to display this + amount, i.e., with how many decimals. +- `tokenId` (required) ... the token ID as in the query + +An example query is +``` +v0/CIS2TokenBalance/996/0/4tSmWDREJwsSzfgNkUeT7xrNdAPHEs8gQBBdiRsmcvnjFeogf6?tokenId=0b5000b73a53f0916c93c68f4b9b6ba8af5a10978634ae4f2237e1f3fbe324fa,1209fe3bc3497e47376dfbd9df0600a17c63384c85f859671956d8289e5a0be8,1209fe3bc3497e47376dfbd9df0600a17c63384c85f859671956d8289e5a0be8 +``` + +and an example response is +```json +[ + { + "balance": "188848148218418242823213123123123", + "tokenId": "0b5000b73a53f0916c93c68f4b9b6ba8af5a10978634ae4f2237e1f3fbe324fa" + }, + { + "balance": "0", + "tokenId": "1209fe3bc3497e47376dfbd9df0600a17c63384c85f859671956d8289e5a0be8" + }, + { + "balance": "1", + "tokenId": "1209fe3bc3497e47376dfbd9df0600a17c63384c85f859671956d8289e5a0be8" + } +] +``` + + ## Notes on account balances. Suppose that at time tâ‚€ you query the account balance and get a structure diff --git a/package.yaml b/package.yaml index d4224c7..ed4bc69 100644 --- a/package.yaml +++ b/package.yaml @@ -1,5 +1,5 @@ name: wallet-proxy -version: 0.20.0 +version: 0.21.0 github: "Concordium/concordium-wallet-proxy" author: "Concordium" maintainer: "developers@concordium.com" diff --git a/src/Internationalization/Base.hs b/src/Internationalization/Base.hs index f1c4fa8..8d12739 100644 --- a/src/Internationalization/Base.hs +++ b/src/Internationalization/Base.hs @@ -32,6 +32,10 @@ data ErrorMessage | EMMissingParameter -- |Action not supported due to the node protocol version not allowing it. | EMActionNotCurrentlySupported + -- |Invoke of a smart contract failed with the given reason. + | EMInvokeFailed + -- |Expected a V1 contract, but a V0 contract was given. + | EMV0Contract data I18n = I18n { i18nRejectReason :: RejectReason -> Text, diff --git a/src/Internationalization/En.hs b/src/Internationalization/En.hs index c54d183..929b01a 100644 --- a/src/Internationalization/En.hs +++ b/src/Internationalization/En.hs @@ -244,3 +244,5 @@ translation = I18n {..} i18nErrorMessage EMAccountDoesNotExist = "Account does not exist" i18nErrorMessage EMMissingParameter = "Missing parameter" i18nErrorMessage EMActionNotCurrentlySupported = "The required action is not supported. The node's protocol version is incompatible with it." + i18nErrorMessage EMInvokeFailed = "Invoking a contract failed." + i18nErrorMessage EMV0Contract = "Invoking a V0 contract is not supported." diff --git a/src/Proxy.hs b/src/Proxy.hs index 2db186d..560a507 100644 --- a/src/Proxy.hs +++ b/src/Proxy.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE BangPatterns #-} {-# LANGUAGE DerivingVia #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -9,6 +10,7 @@ {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE UndecidableInstances, StandaloneDeriving #-} +{-# LANGUAGE NumericUnderscores #-} module Proxy where import Database.Persist.Postgresql @@ -16,6 +18,7 @@ import Database.Persist.Postgresql.JSON() import Database.Persist.TH import Data.Ratio +import Data.Bits import qualified Data.ByteString.Base16 as BS16 import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as BSL @@ -71,6 +74,7 @@ import Concordium.Types.Accounts import Concordium.Types.Block import Concordium.Types.HashableTo import Concordium.Types.Transactions +import Concordium.Utils.Serialization (getMaybe) import Concordium.Types.Execution import qualified Concordium.Types.InvokeContract as InvokeContract import qualified Concordium.Wasm as Wasm @@ -91,6 +95,7 @@ import Concordium.Client.Types.Transaction(transferWithScheduleEnergyCost, ) import Concordium.ID.Types (addressFromText, addressToBytes, KeyIndex, CredentialIndex) import Concordium.Crypto.SignatureScheme (KeyPair) +import Concordium.Crypto.SHA256 (Hash) import Concordium.Crypto.ByteStringHelpers (ByteStringHex(..)) import Concordium.Common.Version import qualified Logging @@ -120,6 +125,11 @@ instance PersistField TokenId where instance PersistFieldSql TokenId where sqlType _ = sqlType (Proxy.Proxy :: Proxy.Proxy BS.ByteString) +instance S.Serialize TokenId where + put (TokenId tid) = S.putWord8 (fromIntegral (BSS.length tid)) <> S.putShortByteString tid + get = do + len <- S.getWord8 + TokenId <$> S.getShortByteString (fromIntegral len) -- |Create the database schema and types. This creates a type called @Summary@ -- with fields @summaryBlock@, @summaryTimestamp@, etc., with stated types. @@ -234,6 +244,8 @@ mkYesod "Proxy" [parseRoutes| /v1/appSettings AppSettingsV1 GET /v0/epochLength EpochLengthR GET /v0/CIS2Tokens/#Word64/#Word64 CIS2Tokens GET +/v0/CIS2TokenMetadata/#Word64/#Word64 CIS2TokenMetadata GET +/v0/CIS2TokenBalance/#Word64/#Word64/#Text CIS2TokenBalance GET |] instance Yesod Proxy where @@ -295,16 +307,16 @@ parseSetCookie' c = flags = map (first (BS8.map CH.toLower)) $ tail pairs parsePair = breakDiscard 61 -- equals sign dropSpace = BS.dropWhile (== 32) -- space --- ^ we need this for addHeader since expiry fails to parse in +-- ^ we need this for addHeader since expiry fails to parse in -- parseSetCookie in Web.Cookie. -- |Parse a setcookie expires field. parseSetCookieExpires' :: BS.ByteString -> Maybe UTCTime parseSetCookieExpires' s = parseTimeM True defaultTimeLocale "%a, %d %b %Y %X GMT" $ BS8.unpack s --- |Run a GRPC request. +-- |Run a GRPC request. runGRPC :: ClientMonad IO (GRPCResult a) - -> (a -> Handler TypedContent) + -> (a -> Handler TypedContent) -> Handler TypedContent runGRPC c k = do cfg <- grpcEnvData <$> getYesod @@ -428,7 +440,7 @@ getAccountBalanceR addrText = case aiStakingInfo of AccountStakingNone -> Left . Just $ object balanceInfo AccountStakingBaker{..} -> do - let infoWithoutPending = + let infoWithoutPending = [ "stakedAmount" .= asiStakedAmount, "restakeEarnings" .= asiStakeEarnings, @@ -552,7 +564,7 @@ getTransactionCostR = withExchangeRate $ \(rate, pv) -> do costResponse $ simpleTransferEnergyCost (simpleTransferPayloadSize + memoPayloadSize) numSignatures "encryptedTransfer" -> costResponse $ encryptedTransferEnergyCost (encryptedTransferPayloadSize + memoPayloadSize) numSignatures - "transferToSecret" -> + "transferToSecret" -> costResponse $ accountEncryptEnergyCost accountEncryptPayloadSize numSignatures "transferToPublic" -> costResponse $ accountDecryptEnergyCost accountDecryptPayloadSize numSignatures @@ -1014,6 +1026,184 @@ getCIS2Tokens index subindex = do "tokens" .= makeJsonEntries entries ] <> maybeToList (("from" .=) <$> mfrom) + +-- |Lookup token ids from the tokenId query parameter, and attempt to parse +-- them as a comma-separated list. Responds with an invalid request error +-- in case parsing is unsuccessful. +parseCIS2TokenIds :: Handler [TokenId] +parseCIS2TokenIds = do + param <- lookupGetParam "tokenId" >>= \case + Nothing -> respond400Error EMMissingParameter RequestInvalid + Just p -> return p + case mapM (AE.fromJSON . AE.String) . Text.split (== ',') $ param of + AE.Error err -> respond400Error (EMParseError err) RequestInvalid + AE.Success tids + | length tids > fromIntegral (maxBound :: Word16) -> + respond400Error (EMParseError "Too many token ids.") RequestInvalid + | otherwise -> do + $(logOther "Trace") (Text.pack ("Query with token ids: " ++ show tids)) + return tids + +getCIS2TokenMetadata :: Word64 -> Word64 -> Handler TypedContent +getCIS2TokenMetadata index subindex = do + let nrg = Energy 500_000 -- ~500ms worth of + let contractAddr = ContractAddress (ContractIndex index) (ContractSubindex subindex) + tids <- parseCIS2TokenIds + let serializedParam = Wasm.Parameter . BSS.toShort . S.runPut $ do + S.putWord16le (fromIntegral (length tids)) + mapM_ S.put tids + cis2InvokeHelper contractAddr (Wasm.EntrypointName "tokenMetadata") serializedParam nrg $ \rv -> do + let getURLs = do + len <- S.getWord16le + replicateM (fromIntegral len) getMetadataUrl + case S.runGet getURLs rv of + Left err -> do + $logDebug $ "Failed to parse the response from tokenMetadata: " <> Text.pack err + respond400Error EMInvokeFailed RequestInvalid + Right urls -> + sendResponse $ + AE.toJSON + ( zipWith + ( \tid md -> + object + [ "tokenId" .= tid + , "metadataURL" .= muURL md + , "metadataChecksum" .= muChecksum md + ] + ) + tids + urls + ) + +getCIS2TokenBalance :: Word64 -> Word64 -> Text -> Handler TypedContent +getCIS2TokenBalance index subindex addrText = do + let nrg = Energy 500_000 -- ~500ms worth of + case addressFromText addrText of + Left err -> respond400Error (EMParseError err) RequestInvalid + Right addr -> do + tids <- parseCIS2TokenIds + let serializedParam = Wasm.Parameter . BSS.toShort . S.runPut $ do + S.putWord16le (fromIntegral (length tids)) + mapM_ S.put (zip tids (repeat (AddressAccount addr))) + let contractAddr = ContractAddress (ContractIndex index) (ContractSubindex subindex) + cis2InvokeHelper contractAddr (Wasm.EntrypointName "balanceOf") serializedParam nrg $ \rv -> do + let getBalances = do + len <- S.getWord16le + replicateM (fromIntegral len) getTokenBalance + case S.runGet getBalances rv of + Left err -> do + $logDebug $ "Failed to parse response from the balanceOf: " <> Text.pack err + respond400Error EMInvokeFailed RequestInvalid + Right urls -> + sendResponse $ + AE.toJSON + ( zipWith + ( \tid bal -> + object + [ "tokenId" .= tid + , "balance" .= bal + ] + ) + tids + urls + ) + +-- |Helper to handle the boilerplate common to both the metadata and balance of +-- queries. It handles getting the address of a contract, handling errors in +-- invocations, and calling the respective handlers for the specific query via +-- the continuation. +cis2InvokeHelper :: + -- |Address of the contract to invoke. + ContractAddress -> + -- |Its entrypoint. + Wasm.EntrypointName -> + -- |The parameter to invoke + Wasm.Parameter -> + -- |Energy to allow for the invoke. + Energy -> + -- |Continuation applied to a return value produced by a successful result. + (BS8.ByteString -> Handler TypedContent) -> + HandlerFor Proxy TypedContent +cis2InvokeHelper contractAddr entrypoint serializedParam nrg k = do + let invokeContext contractName = + InvokeContract.ContractContext + { ccInvoker = Nothing + , ccContract = contractAddr + , ccAmount = 0 + , ccMethod = Wasm.uncheckedMakeReceiveName contractName entrypoint + , ccParameter = serializedParam + , ccEnergy = nrg + } + -- Query the name of a contract at the given block hash. + let queryContractName block = do + ci <- getInstanceInfo (Text.decodeUtf8 . BSL.toStrict . AE.encode $ contractAddr) block + case ci of + Left err -> return (Left err) + Right v -> return (parseEither (AE.withObject "ContractInfo" (.: "name")) (grpcResponseVal v)) + let query = do + withLastFinalBlockHash Nothing $ \bh -> do + name <- queryContractName bh + case name of + Left err -> return (Left err) + Right n -> do + let ctx = invokeContext n + let invokeContextArg = Text.decodeUtf8 . BSL.toStrict . AE.encode $ ctx + res <- invokeContract invokeContextArg bh + case res of + Left err -> return (Left err) + Right v -> case AE.fromJSON (grpcResponseVal v) of + AE.Error jsonErr -> return (Left jsonErr) + AE.Success ir -> return (Right (ir <$ v)) + runGRPC query $ \case + InvokeContract.Failure{..} -> do + $logDebug $ "Invoke failed: " <> Text.pack (show rcrReason) + respond400Error EMInvokeFailed RequestInvalid + InvokeContract.Success{..} -> do + case rcrReturnValue of + Nothing -> respond400Error EMV0Contract RequestInvalid + Just rv -> k rv + +-- |Balance of a CIS2 token. +newtype TokenBalance = TokenBalance Integer + deriving(Show) + +instance AE.ToJSON TokenBalance where + toJSON (TokenBalance i) = toJSON (show i) + +-- |A custom parser for a CIS2 token that uses LEB128 to parse the token +-- balance. +getTokenBalance :: S.Get TokenBalance +getTokenBalance = TokenBalance <$> go 0 0 + where + go !acc !s + | s >= 37 = fail "Invalid token amount encoding." + | otherwise = do + n <- S.getWord8 + if testBit n 7 + then go (acc + (toInteger (clearBit n 7) `shiftL` (s * 7))) (s + 1) + else return $! (acc + toInteger (n `shiftL` (s * 7))) + +newtype Checksum = Checksum Hash + deriving (Show, AE.ToJSON, AE.FromJSON, S.Serialize) + +-- |CIS2 token metadata URL. +data MetadataURL = MetadataURL { + -- |Metadata URL. + muURL :: !Text, + -- |Optional checksum (sha256) of the contents of the metadata URL. + muChecksum :: Maybe Hash + } + +getMetadataUrl :: S.Get MetadataURL +getMetadataUrl = do + urlLen <- S.getWord16le + muURL' <- Text.decodeUtf8' <$> S.getByteString (fromIntegral urlLen) + case muURL' of + Left err -> fail (show err) + Right muURL -> do + muChecksum <- getMaybe S.get + return MetadataURL{..} + -- |List transactions for the account. getAccountTransactionsWorker :: IncludeMemos -> Text -> Handler TypedContent getAccountTransactionsWorker includeMemos addrText = do @@ -1730,7 +1920,7 @@ getBakerPoolR bid = doGetNextPayday :: Text -> ClientMonad IO (GRPCResult UTCTime) doGetNextPayday lastFinal = do rewardStatus <- getRewardStatus lastFinal - return $ do + return $ do response <- rewardStatus utc <- parseEither ( withObject "Best finalized block" $ \v -> do