Skip to content

Commit

Permalink
Merge pull request #25 from maestro-org/17-hackage-readiness
Browse files Browse the repository at this point in the history
Feat 17: Hackage readiness
  • Loading branch information
Vardominator authored Jun 12, 2023
2 parents 4b0a9fc + 3a1db63 commit 33d2a4d
Show file tree
Hide file tree
Showing 39 changed files with 644 additions and 489 deletions.
1 change: 0 additions & 1 deletion cabal.project

This file was deleted.

3 changes: 1 addition & 2 deletions maestro-exe/Maestro/Run/Datum.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
module Maestro.Run.Datum where

import Maestro.Client.Datum
import Maestro.Client.Env
import Maestro.Client
import Text.Printf (printf)

runDatumAPI :: MaestroEnv -> IO ()
Expand Down
3 changes: 1 addition & 2 deletions maestro-exe/Maestro/Run/Epochs.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
module Maestro.Run.Epochs where

import Maestro.Client.Env
import Maestro.Client.Epochs
import Maestro.Client

runEpochsAPI :: MaestroEnv -> IO ()
runEpochsAPI mEnv = do
Expand Down
8 changes: 3 additions & 5 deletions maestro-exe/Maestro/Run/Pools.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,7 @@
module Maestro.Run.Pools where

import Maestro.Client.Env
import Maestro.Client.Pools
import Maestro.Client
import Maestro.Types
import Maestro.Util.Pagination

poolId :: Bech32StringOf PoolId
poolId = "pool1rkfs9glmfva3jd0q9vnlqvuhnrflpzj4l07u6sayfx5k7d788us"
Expand Down Expand Up @@ -42,10 +40,10 @@ runPoolsAPI mEnv = do
updates <- runPoolInfo mEnv
putStrLn $ "fetched pool Updates: \n " ++ show updates

runPoolUpdates :: MaestroEnv -> IO [PoolUpdates]
runPoolUpdates :: MaestroEnv -> IO [PoolUpdate]
runPoolUpdates mEnv = poolUpdates mEnv poolId

runListPools :: MaestroEnv -> IO [Pool]
runListPools :: MaestroEnv -> IO [PoolListInfo]
runListPools mEnv = listPools mEnv (Page 1 1)

runPoolBlocks :: MaestroEnv -> IO [PoolBlock]
Expand Down
3 changes: 1 addition & 2 deletions maestro-exe/Maestro/Run/Scripts.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
module Maestro.Run.Scripts where

import Maestro.Client.Env
import Maestro.Client.Scripts
import Maestro.Client
import Text.Printf (printf)

runScriptsAPI :: MaestroEnv -> IO ()
Expand Down
5 changes: 2 additions & 3 deletions maestro-exe/Maestro/Run/Tx.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
module Maestro.Run.Tx where

import Maestro.Client.Env
import Maestro.Client.Transaction
import Maestro.Client
import Maestro.Types

txHash :: HashStringOf Tx
Expand All @@ -21,7 +20,7 @@ runTxApi mEnv = do
utxo <- runTxUtxo mEnv
putStrLn $ "fetched Tx Utxos: \n " ++ show utxo

runTxAddress :: MaestroEnv -> IO TxAddress
runTxAddress :: MaestroEnv -> IO UtxoAddress
runTxAddress mEnv = txAddress mEnv txHash $ TxIndex 0

runTxCbor :: MaestroEnv -> IO TxCbor
Expand Down
10 changes: 5 additions & 5 deletions maestro-exe/Main.hs
Original file line number Diff line number Diff line change
@@ -1,25 +1,25 @@
module Main (main) where

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


main :: IO ()

main = do
apiId <- maestroId
env <- mkMaestroEnv (T.pack apiId) Preprod
apiKey <- maestroKey
env <- mkMaestroEnv (T.pack apiKey) Preprod
runPoolsAPI env
runTxApi env
runEpochsAPI env
runDatumAPI env
runScriptsAPI env

where
maestroId = getEnv "MAESTRO_API_KEY"
maestroKey = getEnv "MAESTRO_API_KEY"
9 changes: 6 additions & 3 deletions maestro-sdk.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -48,8 +48,11 @@ library
Maestro.API.Pool
Maestro.API.Scripts
Maestro.API.Transaction
Maestro.API.TxManager

Maestro.Client
Maestro.Client.Core
Maestro.Client.Core.Pagination
Maestro.Client.Datum
Maestro.Client.Env
Maestro.Client.Epochs
Expand All @@ -60,6 +63,7 @@ library
Maestro.Client.Pools
Maestro.Client.Scripts
Maestro.Client.Transaction
Maestro.Client.TxManager

Maestro.Types
Maestro.Types.Accounts
Expand All @@ -71,8 +75,6 @@ library
Maestro.Types.General
Maestro.Types.Pool

Maestro.Util.Pagination

-- other-modules:
-- other-extensions:
build-depends:
Expand All @@ -85,9 +87,10 @@ library
, servant-client
, servant-client-core
, text
, time ^>= 1.12.1
, time
, http-client
, http-client-tls
, http-types
, http-api-data
, data-default-class

Expand Down
29 changes: 16 additions & 13 deletions src/Maestro/API.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Maestro.API where

import Data.Proxy (Proxy (..))
import Data.Text (Text)
import Maestro.API.Accounts
import Maestro.API.Address
import Maestro.API.Assets
Expand All @@ -10,20 +10,23 @@ import Maestro.API.General
import Maestro.API.Pool
import Maestro.API.Scripts
import Maestro.API.Transaction
import Maestro.API.TxManager
import Servant.API
import Servant.API.Generic

data MaestroApi route = Routes
{ _accounts :: route :- "accounts" :> ToServantApi AccountsAPI
, _address :: route :- "addresses" :> ToServantApi AddressAPI
, _assets :: route :- "assets" :> ToServantApi AssetsAPI
, _general :: route :- ToServantApi GeneralAPI
, _pools :: route :- "pools" :> ToServantApi PoolAPI
, _tx :: route :- ToServantApi TxAPI
, _epochs :: route :- "epochs" :> ToServantApi EpochsAPI
, _datum :: route :- "datum" :> ToServantApi DatumAPI
, _scripts :: route :- "scripts" :> ToServantApi ScriptsAPI
data MaestroApiV0 route = MaestroApiV0
{ _accounts :: route :- "accounts" :> ToServantApi AccountsAPI
, _address :: route :- "addresses" :> ToServantApi AddressAPI
, _assets :: route :- "assets" :> ToServantApi AssetsAPI
, _general :: route :- ToServantApi GeneralAPI
, _pools :: route :- "pools" :> ToServantApi PoolAPI
, _tx :: route :- ToServantApi TxAPI
, _epochs :: route :- "epochs" :> ToServantApi EpochsAPI
, _datum :: route :- "datum" :> ToServantApi DatumAPI
, _scripts :: route :- "scripts" :> ToServantApi ScriptsAPI
, _txManager :: route :- "txmanager" :> ToServantApi TxManagerAPI
} deriving Generic

api :: Proxy (ToServantApi MaestroApi)
api = genericApi (Proxy :: Proxy MaestroApi)
newtype MaestroApiV0Auth route = MaestroApiV0Auth
{ _apiV0 :: route :- Header' '[Required] "api-key" Text :> ToServantApi MaestroApiV0 }
deriving Generic
27 changes: 14 additions & 13 deletions src/Maestro/API/Accounts.hs
Original file line number Diff line number Diff line change
@@ -1,52 +1,53 @@
module Maestro.API.Accounts where

import Data.Text (Text)
import Maestro.Client.Core.Pagination
import Maestro.Types.Accounts
import Maestro.Types.Common
import Maestro.Util.Pagination
import Servant.API
import Servant.API.Generic

data AccountsAPI route = AccountsAPI
{
_account
:: route
:- Capture "stake_addr" String
:> Get '[JSON] AccountsInfo
:- Capture "stake_addr" Text
:> Get '[JSON] AccountInfo

, _accountAddresses
:: route
:- Capture "stake_addr" String
:- Capture "stake_addr" Text
:> "addresses"
:> Pagination
:> Get '[JSON] [String]
:> Get '[JSON] [Text]

, _accountAssets
:: route
:- Capture "stake_addr" String
:- Capture "stake_addr" Text
:> "assets"
:> Pagination
:> Get '[JSON] [AccountsAssets]
:> Get '[JSON] [Asset]

, _accountsHistory
:: route
:- Capture "stake_addr" String
:- Capture "stake_addr" Text
:> "history"
:> QueryParam "epoch_no" EpochNo
:> Pagination
:> Get '[JSON] [AccountsHistory]
:> Get '[JSON] [AccountHistory]

, _accountsReward
:: route
:- Capture "stake_addr" String
:- Capture "stake_addr" Text
:> "rewards"
:> Pagination
:> Get '[JSON] [AccountsRewards]
:> Get '[JSON] [AccountReward]

, _accountsUpdates
:: route
:- Capture "stake_addr" String
:- Capture "stake_addr" Text
:> "updates"
:> Pagination
:> Get '[JSON] [AccountsUpdates]
:> Get '[JSON] [AccountUpdate]

} deriving (Generic)
13 changes: 7 additions & 6 deletions src/Maestro/API/Address.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,21 +2,22 @@ module Maestro.API.Address where

import Data.Text (Text)
import Maestro.Types.Address
import Maestro.Util.Pagination
import Maestro.Types.Common (Utxo)
import Maestro.Client.Core.Pagination
import Servant.API
import Servant.API.Generic

data AddressAPI route = AddressAPI
{

_addressesUtxos
_addressesUtxos
:: route
:- "utxos"
:> QueryParam "resolve_datums" Bool
:> QueryParam "with_cbor" Bool
:> Pagination
:> ReqBody '[JSON][Text]
:> Post '[JSON] [AddressUtxo]
:> ReqBody '[JSON] [Text]
:> Post '[JSON] [Utxo]

, _addressUtxo
:: route
Expand All @@ -25,14 +26,14 @@ data AddressAPI route = AddressAPI
:> QueryParam "resolve_datums" Bool
:> QueryParam "with_cbor" Bool
:> Pagination
:> Get '[JSON] [AddressUtxo]
:> Get '[JSON] [Utxo]

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

, _addressTransactionCount
:: route
Expand Down
29 changes: 15 additions & 14 deletions src/Maestro/API/Assets.hs
Original file line number Diff line number Diff line change
@@ -1,69 +1,70 @@
module Maestro.API.Assets where

import Maestro.Types.Assets
import Maestro.Types.Common
import Maestro.Util.Pagination
import Servant.API
import Servant.API.Generic
import Data.Text (Text)
import Maestro.Client.Core.Pagination
import Maestro.Types.Assets
import Maestro.Types.Common
import Servant.API
import Servant.API.Generic

data AssetsAPI route = AssetsAPI
{ _assetPolicyInfo ::
route
:- "policy"
:> Capture "policy" PolicyId
:> Pagination
:> Get '[JSON] [MaestroAssetInfo],
:> Get '[JSON] [AssetInfo],
_assetPolicyAddress ::
route
:- "policy"
:> Capture "policy" PolicyId
:> "addresses"
:> Pagination
:> Get '[JSON] [String],
:> Get '[JSON] [Text],
_assetPolicyTxs ::
route
:- "policy"
:> Capture "policy" PolicyId
:> "txs"
:> Pagination
:> Get '[JSON] [MaestroAssetTx],
:> Get '[JSON] [AssetTx],
_assetPolicyUtxos ::
route
:- "policy"
:> Capture "policy" PolicyId
:> "utxos"
:> Pagination
:> Get '[JSON] [MaestroAssetUtxo],
:> Get '[JSON] [PolicyUtxo],
_assetDetail ::
route
:- Capture "asset" AssetId
:> Get '[JSON] MaestroAssetInfo,
:> Get '[JSON] AssetInfo,
_assetAddresses ::
route
:- Capture "asset" AssetId
:> "addresses"
:> Pagination
:> Get '[JSON] [String],
:> Get '[JSON] [Text],
_assetTxs ::
route
:- Capture "asset" AssetId
:> "txs"
:> QueryParam "from_height" Integer
:> Pagination
:> QueryParam "order" Order
:> Get '[JSON] [MaestroAssetTx],
:> Get '[JSON] [AssetTx],
_assetUpdates ::
route
:- Capture "asset" AssetId
:> "updates"
:> Pagination
:> QueryParam "order" Order
:> Get '[JSON] [MaestroAssetUpdates],
:> Get '[JSON] [MintingTx],
_assetUtxos ::
route
:- Capture "asset" AssetId
:> "utxos"
:> Pagination
:> Get '[JSON] [MaestroAssetUtxo]
:> Get '[JSON] [AssetUtxo]
}
deriving (Generic)
Loading

0 comments on commit 33d2a4d

Please sign in to comment.