Skip to content

Commit

Permalink
Feat 30: Pagination checked by querying UTxOs at multiple addresses
Browse files Browse the repository at this point in the history
  • Loading branch information
sourabhxyz committed Jul 5, 2023
1 parent 9972c3d commit 8a668d6
Show file tree
Hide file tree
Showing 12 changed files with 150 additions and 22 deletions.
9 changes: 9 additions & 0 deletions maestro-exe/Maestro/Run/AddressV1.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
module Maestro.Run.AddressV1 where

import Maestro.Client.V1

runV1AddressAPI :: MaestroEnv -> IO ()
runV1AddressAPI mEnv = do
utxos <- allPages $ (flip $ utxosAtMultiAddresses mEnv Nothing Nothing) ["insert","your", "big", "address", "list", "here"]
putStrLn $ "Received: ⮯\n" ++ show utxos
-- writeFile "allUtxos.txt" $ show utxos
7 changes: 6 additions & 1 deletion maestro-exe/Main.hs
Original file line number Diff line number Diff line change
@@ -1,27 +1,32 @@
module Main (main) where

import qualified Data.Text as T
import Maestro.Client.V0
import Maestro.Client.Env
import Maestro.Run.Datum
import Maestro.Run.Epochs
import Maestro.Run.General
import Maestro.Run.Pools
import Maestro.Run.Scripts
import Maestro.Run.Tx
import Maestro.Run.AddressV1
import System.Environment (getEnv)


main :: IO ()

main = do
apiKey <- maestroKey
apiKeyMain <- maestroMainKey
env <- mkMaestroEnv (T.pack apiKey) Preprod V0
runPoolsAPI env
runTxApi env
runEpochsAPI env
runDatumAPI env
runScriptsAPI env
runGeneralAPI env
env' <- mkMaestroEnv (T.pack apiKeyMain) Mainnet V1
runV1AddressAPI env'

where
maestroKey = getEnv "MAESTRO_API_KEY"
maestroMainKey = getEnv "MAESTRO_MAIN_KEY"
15 changes: 14 additions & 1 deletion maestro-sdk.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,10 @@ library
Maestro.API.V0.Transaction
Maestro.API.V0.TxManager

Maestro.API.V1
Maestro.API.V1.Address
Maestro.API.V1.General

Maestro.Client.Env
Maestro.Client.Error
Maestro.Client.V0
Expand All @@ -66,12 +70,16 @@ library
Maestro.Client.V0.Address
Maestro.Client.V0.Assets
Maestro.Client.V0.General
Maestro.Client.V0.Pagination
Maestro.Client.V0.Pools
Maestro.Client.V0.Scripts
Maestro.Client.V0.Transaction
Maestro.Client.V0.TxManager

Maestro.Client.V1
Maestro.Client.V1.Core
Maestro.Client.V1.Core.Pagination
Maestro.Client.V1.Address

Maestro.Types.Common
Maestro.Types.V0
Maestro.Types.V0.Accounts
Expand All @@ -83,6 +91,10 @@ library
Maestro.Types.V0.General
Maestro.Types.V0.Pool

Maestro.Types.V1
Maestro.Types.V1.Common
Maestro.Types.V1.General

-- other-modules:
-- other-extensions:
build-depends:
Expand Down Expand Up @@ -142,6 +154,7 @@ executable maestro-exe
Maestro.Run.Scripts
Maestro.Run.Tx
Maestro.Run.Epochs
Maestro.Run.AddressV1
-- other-extensions:
hs-source-dirs: maestro-exe
main-is: Main.hs
Expand Down
6 changes: 4 additions & 2 deletions src/Maestro/API/V1.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,14 @@
module Maestro.API.V1 where

import Data.Text (Text)
import Maestro.API.V0.General
import Maestro.API.V1.Address
import Maestro.API.V1.General
import Servant.API
import Servant.API.Generic

data MaestroApiV1 route = MaestroApiV1
{ _general :: route :- ToServantApi GeneralAPI
{ _general :: route :- ToServantApi GeneralAPI
, _address :: route :- "addresses" :> ToServantApi AddressAPI
} deriving Generic

newtype MaestroApiV1Auth route = MaestroApiV1Auth
Expand Down
20 changes: 20 additions & 0 deletions src/Maestro/API/V1/Address.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
module Maestro.API.V1.Address where

import Data.Text (Text)
import Maestro.Client.V1.Core.Pagination
import Maestro.Types.V1
import Servant.API
import Servant.API.Generic

data AddressAPI route = AddressAPI
{
_addressesUtxos
:: route
:- "utxos"
:> QueryParam "resolve_datums" Bool
:> QueryParam "with_cbor" Bool
:> Pagination
:> ReqBody '[JSON] [Text]
:> Post '[JSON] Utxos

} deriving (Generic)
8 changes: 5 additions & 3 deletions src/Maestro/Client/V1.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,12 @@
module Maestro.Client.V0
module Maestro.Client.V1
( module Maestro.Client.Env
, module Maestro.Client.Error
, module Maestro.Client.V0.Core
, module Maestro.Client.V1.Core
, module Maestro.Client.V1.Address
) where


import Maestro.Client.Env
import Maestro.Client.Error
import Maestro.Client.V0.Core
import Maestro.Client.V1.Address
import Maestro.Client.V1.Core
28 changes: 28 additions & 0 deletions src/Maestro/Client/V1/Address.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,28 @@
module Maestro.Client.V1.Address where

import Data.Text (Text)
import Maestro.API.V1
import Maestro.API.V1.Address
import Maestro.Client.Env
import Maestro.Client.V1.Core
import Maestro.Types.V1
import Servant.API.Generic
import Servant.Client

addressClient :: MaestroEnv -> AddressAPI (AsClientT IO)
addressClient = fromServant . _address . apiV1Client

-- | Returns list of utxos for multiple addresses
utxosAtMultiAddresses ::
-- | The Maestro Environment
MaestroEnv ->
-- | Query param to include the corresponding datums for datum hashes
Maybe Bool ->
-- | Query Param to include the CBOR encodings of the transaction outputs in the response
Maybe Bool ->
-- | The pagination attributes
Cursor ->
-- | List of Address in bech32 format to fetch utxo from
[Text] ->
IO Utxos
utxosAtMultiAddresses = _addressesUtxos . addressClient
10 changes: 0 additions & 10 deletions src/Maestro/Types/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,6 @@ module Maestro.Types.Common
DatumOption (..),
ScriptType (..),
Script (..),
Asset (..),
TxCbor (..),
UtxoAddress (..),
Order (..),
Expand Down Expand Up @@ -138,15 +137,6 @@ data Script = Script
(FromJSON, ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_script", LowerFirst]] Script

data Asset = Asset
{ _assetQuantity :: !Integer
, _assetUnit :: !Text
}
deriving stock (Show, Eq, Generic)
deriving
(FromJSON, ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_asset", CamelToSnake]] Asset

newtype TxCbor = TxCbor {_txCbor :: Text}
deriving stock (Show, Eq, Generic)
deriving
Expand Down
15 changes: 13 additions & 2 deletions src/Maestro/Types/V0/Common.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
module Maestro.Types.V0.Common
( Utxo (..),
( Asset (..),
Utxo (..),
module Maestro.Types.Common
)
where
Expand All @@ -9,7 +10,17 @@ import Deriving.Aeson
import GHC.Natural (Natural)
import Maestro.Types.Common

-- | Transaction output
-- | Representation of asset in an UTxO.
data Asset = Asset
{ _assetQuantity :: !Integer
, _assetUnit :: !Text
}
deriving stock (Show, Eq, Generic)
deriving
(FromJSON, ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_asset", CamelToSnake]] Asset

-- | Transaction output.
data Utxo = Utxo
{ _utxoAddress :: !Text,
_utxoAssets :: ![Asset],
Expand Down
4 changes: 1 addition & 3 deletions src/Maestro/Types/V1.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,9 @@
-- | Maestro types

module Maestro.Types.V1
( module Maestro.Types.V0.Common
, module Maestro.Types.V1.Common
( module Maestro.Types.V1.Common
, module Maestro.Types.V1.General
) where

import Maestro.Types.V0.Common
import Maestro.Types.V1.Common
import Maestro.Types.V1.General
48 changes: 48 additions & 0 deletions src/Maestro/Types/V1/Common.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,16 @@
module Maestro.Types.V1.Common
( LastUpdated (..),
Asset (..),
UtxoData (..),
Utxos (..),
module Maestro.Types.Common
)
where

import Data.Text (Text)
import Deriving.Aeson
import GHC.Natural (Natural)
import Maestro.Client.V1.Core.Pagination (HasCursor (..))
import Maestro.Types.Common

-- | Details of the most recent block processed by the indexer (aka chain tip); that is, the data returned is correct as of this block in time.
Expand All @@ -16,3 +22,45 @@ data LastUpdated = LastUpdated
}
deriving stock (Eq, Ord, Show, Generic)
deriving (FromJSON, ToJSON) via CustomJSON '[FieldLabelModifier '[StripPrefix "_lastUpdated", CamelToSnake]] LastUpdated

-- | Representation of asset in an UTxO.
data Asset = Asset
{ _assetAmount :: !Integer
, _assetUnit :: !Text
}
deriving stock (Show, Eq, Generic)
deriving
(FromJSON, ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_asset", CamelToSnake]] Asset

-- | Transaction output.
data UtxoData = UtxoData
{ _utxoDataAddress :: !Text,
_utxoDataAssets :: ![Asset],
_utxoDataDatum :: !(Maybe DatumOption),
_utxoDataIndex :: !Natural,
_utxoDataReferenceScript :: !(Maybe Script),
_utxoDataTxHash :: !Text,
_utxoDataSlot :: !SlotNo,
_utxoDataTxoutCbor :: !(Maybe TxCbor)
}
deriving stock (Show, Eq, Generic)
deriving
(FromJSON, ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_utxoData", CamelToSnake]] UtxoData

-- | Transaction Outputs
data Utxos = Utxos
{ _utxosData :: ![UtxoData],
_utxosLastUpdated :: !LastUpdated,
_utxosNextCursor :: !(Maybe Text)
}
deriving stock (Show, Eq, Generic)
deriving
(FromJSON, ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_utxos", CamelToSnake]] Utxos

instance HasCursor Utxos where
type CursorData Utxos = [UtxoData]
getNextCursor utxos = _utxosNextCursor utxos
getCursorData utxos = _utxosData utxos
2 changes: 2 additions & 0 deletions src/Maestro/Types/V1/General.hs
Original file line number Diff line number Diff line change
Expand Up @@ -181,6 +181,8 @@ data ProtocolParameters = ProtocolParameters
{ _protocolParametersData :: !ProtocolParametersData
, _protocolParametersLastUpdated :: !LastUpdated
}
deriving stock (Eq, Show, Generic)
deriving (FromJSON, ToJSON) via CustomJSON '[FieldLabelModifier '[StripPrefix "_protocolParameters", CamelToSnake]] ProtocolParameters

-- | Protocol parameters for the latest epoch.
data ProtocolParametersData = ProtocolParametersData
Expand Down

0 comments on commit 8a668d6

Please sign in to comment.