Skip to content

Commit

Permalink
Feat 30: V1 Endpoints support - support for endpoints needed for Atlas
Browse files Browse the repository at this point in the history
  • Loading branch information
sourabhxyz committed Jul 9, 2023
1 parent 4f6095e commit 1efdc78
Show file tree
Hide file tree
Showing 31 changed files with 797 additions and 170 deletions.
4 changes: 2 additions & 2 deletions maestro-exe/Maestro/Run/Address.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,13 +5,13 @@ import Data.List (sort)
import Maestro.Client.Env
import qualified Maestro.Client.V0 as V0
import qualified Maestro.Client.V1 as V1
import Maestro.Types.V1.Common (v1UtxoToV0)
import Maestro.Types.V1.Common (v1UtxoWithSlotToV0)

runAddressAPI :: MaestroEnv 'V0 -> MaestroEnv 'V1 -> IO ()
runAddressAPI mEnvV0 mEnvV1 = do
let addrs = undefined -- Mention list of addresses.
utxos <- V0.allPages $ flip (V0.utxosAtMultiAddresses mEnvV0 Nothing Nothing) addrs
let utxosSorted = sort utxos
utxos' <- fmap (fmap v1UtxoToV0) $ V1.allPages $ flip (V1.utxosAtMultiAddresses mEnvV1 Nothing Nothing) addrs
utxos' <- fmap (fmap v1UtxoWithSlotToV0) $ V1.allPages $ flip (V1.utxosAtMultiAddresses mEnvV1 Nothing Nothing) addrs
let utxos'Sorted = sort utxos'
when (utxosSorted == utxos'Sorted) $ putStrLn "Yes"
19 changes: 17 additions & 2 deletions maestro-sdk.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -57,8 +57,12 @@ library
Maestro.API.V0.TxManager

Maestro.API.V1
Maestro.API.V1.Address
Maestro.API.V1.Addresses
Maestro.API.V1.Datum
Maestro.API.V1.General
Maestro.API.V1.Pools
Maestro.API.V1.Transactions
Maestro.API.V1.TxManager

Maestro.Client.Env
Maestro.Client.Error
Expand All @@ -79,7 +83,12 @@ library
Maestro.Client.V1
Maestro.Client.V1.Core
Maestro.Client.V1.Core.Pagination
Maestro.Client.V1.Address
Maestro.Client.V1.Addresses
Maestro.Client.V1.Datum
Maestro.Client.V1.General
Maestro.Client.V1.Pools
Maestro.Client.V1.Transactions
Maestro.Client.V1.TxManager

Maestro.Types.Common
Maestro.Types.V0
Expand All @@ -91,10 +100,16 @@ library
Maestro.Types.V0.Epochs
Maestro.Types.V0.General
Maestro.Types.V0.Pool
Maestro.Types.V0.Transactions

Maestro.Types.V1
Maestro.Types.V1.Addresses
Maestro.Types.V1.Datum
Maestro.Types.V1.Common
Maestro.Types.V1.Common.Pagination
Maestro.Types.V1.General
Maestro.Types.V1.Pools
Maestro.Types.V1.Transactions

-- other-modules:
-- other-extensions:
Expand Down
10 changes: 5 additions & 5 deletions src/Maestro/API/V0/Address.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Maestro.API.V0.Address where

import Data.Text (Text)
import Data.Text (Text)
import Maestro.Client.V0.Core.Pagination
import Maestro.Types.V0
import Servant.API
Expand All @@ -12,8 +12,8 @@ data AddressAPI route = AddressAPI
_addressesUtxos
:: route
:- "utxos"
:> QueryParam "resolve_datums" Bool
:> QueryParam "with_cbor" Bool
:> QueryParam "resolve_datums" Bool
:> QueryParam "with_cbor" Bool
:> Pagination
:> ReqBody '[JSON] [Text]
:> Post '[JSON] [Utxo]
Expand All @@ -22,8 +22,8 @@ data AddressAPI route = AddressAPI
:: route
:- Capture "address" Text
:> "utxos"
:> QueryParam "resolve_datums" Bool
:> QueryParam "with_cbor" Bool
:> QueryParam "resolve_datums" Bool
:> QueryParam "with_cbor" Bool
:> Pagination
:> Get '[JSON] [Utxo]

Expand Down
16 changes: 12 additions & 4 deletions src/Maestro/API/V1.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,22 @@
module Maestro.API.V1 where

import Data.Text (Text)
import Maestro.API.V1.Address
import Data.Text (Text)
import Maestro.API.V1.Addresses
import Maestro.API.V1.Datum
import Maestro.API.V1.General
import Maestro.API.V1.Pools
import Maestro.API.V1.Transactions
import Maestro.API.V1.TxManager
import Servant.API
import Servant.API.Generic

data MaestroApiV1 route = MaestroApiV1
{ _general :: route :- ToServantApi GeneralAPI
, _address :: route :- "addresses" :> ToServantApi AddressAPI
{ _general :: route :- ToServantApi GeneralAPI
, _addresses :: route :- "addresses" :> ToServantApi AddressesAPI
, _datum :: route :- "datum" :> ToServantApi DatumAPI
, _pools :: route :- "pools" :> ToServantApi PoolsAPI
, _txManager :: route :- "txmanager" :> ToServantApi TxManagerAPI
, _transactions :: route :- ToServantApi TransactionsAPI
} deriving Generic

newtype MaestroApiV1Auth route = MaestroApiV1Auth
Expand Down
20 changes: 0 additions & 20 deletions src/Maestro/API/V1/Address.hs

This file was deleted.

32 changes: 32 additions & 0 deletions src/Maestro/API/V1/Addresses.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
module Maestro.API.V1.Addresses where

import Maestro.Client.V1.Core.Pagination
import Maestro.Types.V1
import Servant.API
import Servant.API.Generic

data AddressesAPI route = AddressesAPI
{
_decodeAddress
:: route
:- Capture "address" (TaggedText AddressToDecode)
:> "decode"
:> Get '[JSON] AddressInfo

, _addressesUtxos
:: route
:- "utxos"
:> QueryParam "resolve_datums" Bool
:> QueryParam "with_cbor" Bool
:> Pagination
:> ReqBody '[JSON] [Bech32StringOf Address]
:> Post '[JSON] PaginatedUtxoWithSlot

-- , _addressUtxoRefs
-- :: route
-- :- Capture "address" Text
-- :> "utxo_refs"
-- :> Pagination
-- :> Get '[JSON] [UtxoRef]

} deriving (Generic)
14 changes: 14 additions & 0 deletions src/Maestro/API/V1/Datum.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
module Maestro.API.V1.Datum where

import Maestro.Types.V1
import Servant.API
import Servant.API.Generic

newtype DatumAPI route =
DatumAPI
{
_datumByHash
:: route
:- Capture "datum_hash" (HexStringOf DatumHash)
:> Get '[JSON] Datum
} deriving Generic
14 changes: 14 additions & 0 deletions src/Maestro/API/V1/Pools.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
module Maestro.API.V1.Pools where

import Maestro.Client.V1.Core.Pagination
import Maestro.Types.V1
import Servant.API
import Servant.API.Generic

data PoolsAPI route = PoolsAPI
{ _listPools ::
route
:- Pagination
:> Get '[JSON] PaginatedPoolListInfo
}
deriving (Generic)
19 changes: 19 additions & 0 deletions src/Maestro/API/V1/Transactions.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
module Maestro.API.V1.Transactions where

import Maestro.Client.V1.Core.Pagination
import Maestro.Types.V1
import Servant.API
import Servant.API.Generic

newtype TransactionsAPI route = TransactionsAPI
{ _txOutputs ::
route
:- "transactions"
:> "outputs"
:> QueryParam "resolve_datums" Bool
:> QueryParam "with_cbor" Bool
:> Pagination
:> ReqBody '[JSON] [OutputReference]
:> Post '[JSON] PaginatedUtxo
}
deriving (Generic)
15 changes: 15 additions & 0 deletions src/Maestro/API/V1/TxManager.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
module Maestro.API.V1.TxManager where

import qualified Data.ByteString as BS
import qualified Data.Text as T
import Maestro.Types.V1
import Servant.API
import Servant.API.Generic

newtype TxManagerAPI route = TxManagerAPI
{ _monitoredTxSubmit ::
route
:- ReqBody' '[Required] '[CBORStream] BS.ByteString
:> PostAccepted '[JSON] T.Text
}
deriving (Generic)
4 changes: 2 additions & 2 deletions src/Maestro/Client/V1.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,11 +2,11 @@ module Maestro.Client.V1
( module Maestro.Client.Env
, module Maestro.Client.Error
, module Maestro.Client.V1.Core
, module Maestro.Client.V1.Address
, module Maestro.Client.V1.Addresses
) where


import Maestro.Client.Env
import Maestro.Client.Error
import Maestro.Client.V1.Address
import Maestro.Client.V1.Addresses
import Maestro.Client.V1.Core
28 changes: 0 additions & 28 deletions src/Maestro/Client/V1/Address.hs

This file was deleted.

32 changes: 32 additions & 0 deletions src/Maestro/Client/V1/Addresses.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
-- | Module to query for /"addresses"/ category of endpoints defined at [docs.gomaestro.org](https://docs.gomaestro.org/docs/category/addresses).

module Maestro.Client.V1.Addresses (
utxosAtMultiAddresses,
) where

import Maestro.API.V1
import Maestro.API.V1.Addresses
import Maestro.Client.Env
import Maestro.Client.V1.Core
import Maestro.Types.Common (Address, Bech32StringOf)
import Maestro.Types.V1 (PaginatedUtxoWithSlot)
import Servant.API.Generic
import Servant.Client

addressClient :: MaestroEnv 'V1 -> AddressesAPI (AsClientT IO)
addressClient = fromServant . _addresses . apiV1Client

-- | Returns list of utxos for multiple addresses.
utxosAtMultiAddresses ::
-- | The Maestro Environment.
MaestroEnv 'V1 ->
-- | 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.
[Bech32StringOf Address] ->
IO PaginatedUtxoWithSlot
utxosAtMultiAddresses = _addressesUtxos . addressClient
26 changes: 10 additions & 16 deletions src/Maestro/Client/V1/Core/Pagination.hs
Original file line number Diff line number Diff line change
@@ -1,18 +1,18 @@
module Maestro.Client.V1.Core.Pagination where

import Data.Default.Class
import Data.Kind (Type)
import Data.Maybe (isNothing)
import Data.Proxy (Proxy (..))
import Data.Text (Text)
import Servant.API (QueryParam, (:>))
import Servant.Client.Core (Client, HasClient, clientWithRoute,
hoistClientMonad)
import Data.Maybe (isNothing)
import Data.Proxy (Proxy (..))
import Maestro.Types.V1.Common.Pagination
import Servant.API (QueryParam, (:>))
import Servant.Client.Core (Client, HasClient,
clientWithRoute,
hoistClientMonad)

-- | Pagination parameters.
data Cursor = Cursor
{ resultPerPage :: !Int -- ^ Total result to have per page.
, cursor :: !(Maybe Text) -- ^ Cursor.
{ resultPerPage :: !Int -- ^ Total result to have per page.
, cursor :: !(Maybe NextCursor) -- ^ Cursor.
}

-- | Maximum number of result per page.
Expand All @@ -22,12 +22,6 @@ maxResultsPerPage = 100
instance Default Cursor where
def = Cursor maxResultsPerPage Nothing

-- | Is the endpoint paged?
class (Monoid (CursorData a)) => HasCursor a where
type CursorData a :: Type
getNextCursor :: a -> Maybe Text
getCursorData :: a -> CursorData a

-- Utility for querying all results from a paged endpoint.
allPages :: (Monad m, HasCursor a) => (Cursor -> m a) -> m (CursorData a)
allPages act = fetch Nothing
Expand All @@ -46,7 +40,7 @@ data Pagination

type PaginationApi api =
QueryParam "count" Int
:> QueryParam "cursor" Text
:> QueryParam "cursor" NextCursor
:> api

instance HasClient m api => HasClient m (Pagination :> api) where
Expand Down
20 changes: 20 additions & 0 deletions src/Maestro/Client/V1/Datum.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
-- | Module to query for /"datum"/ category of endpoints defined at [docs.gomaestro.org](https://docs.gomaestro.org/docs/category/datum).

module Maestro.Client.V1.Datum
( getDatumByHash
) where

import Maestro.API.V1 (_datum)
import Maestro.API.V1.Datum
import Maestro.Client.Env
import Maestro.Client.V1.Core
import Maestro.Types.V1
import Servant.API.Generic
import Servant.Client

datumClient :: MaestroEnv 'V1 -> DatumAPI (AsClientT IO)
datumClient = fromServant . _datum . apiV1Client

-- | Get information about the datum from it's hash.
getDatumByHash :: MaestroEnv 'V1 -> HexStringOf DatumHash -> IO Datum
getDatumByHash = _datumByHash . datumClient
Loading

0 comments on commit 1efdc78

Please sign in to comment.