Skip to content

Commit

Permalink
Feat 30: V1 Endpoints support - v1 to v0 UTxO conversion function to …
Browse files Browse the repository at this point in the history
…assert equality
  • Loading branch information
sourabhxyz committed Jul 6, 2023
1 parent c598820 commit 4f6095e
Show file tree
Hide file tree
Showing 5 changed files with 59 additions and 17 deletions.
17 changes: 13 additions & 4 deletions maestro-exe/Maestro/Run/Address.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,17 @@
module Maestro.Run.Address where

import Control.Monad (when)
import Data.List (sort)
import Maestro.Client.Env
import qualified Maestro.Client.V0 as V0
import qualified Maestro.Client.V1 as V1
import qualified Maestro.Client.V0 as V0
import qualified Maestro.Client.V1 as V1
import Maestro.Types.V1.Common (v1UtxoToV0)

runAddressAPI :: MaestroEnv 'V0 -> IO ()
runAddressAPI mEnv = undefined
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
let utxos'Sorted = sort utxos'
when (utxosSorted == utxos'Sorted) $ putStrLn "Yes"
6 changes: 3 additions & 3 deletions maestro-exe/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,9 +24,9 @@ main = do
runDatumAPI env
runScriptsAPI env
runGeneralAPI env
-- env' <- mkMaestroEnv @'V1 (T.pack apiKeyMain) Mainnet
env' <- mkMaestroEnv @'V0 (T.pack apiKeyMain) Mainnet
runAddressAPI env'
envV1 <- mkMaestroEnv @'V1 (T.pack apiKeyMain) Mainnet
envV0 <- mkMaestroEnv @'V0 (T.pack apiKeyMain) Mainnet
runAddressAPI envV0 envV1

where
maestroKey = getEnv "MAESTRO_API_KEY"
Expand Down
12 changes: 8 additions & 4 deletions src/Maestro/Types/Common.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
module Maestro.Types.Common
( Tx,
TxOutCbor,
TxIndex (..),
PolicyId (..),
AssetId (..),
Expand Down Expand Up @@ -41,6 +42,9 @@ import Servant.API
-- | Phantom datatype to be used with constructors like `HashStringOf`.
data Tx

-- | Phantom datatype to be used with `HexStringOf` to represent hex encoded CBOR bytes of transaction output.
data TxOutCbor

-- | Index of UTxO in a transaction outputs.
newtype TxIndex = TxIndex Natural
deriving stock (Eq, Ord, Show, Generic)
Expand Down Expand Up @@ -106,7 +110,7 @@ newtype HashStringOf a = HashStringOf Text
deriving newtype (FromHttpApiData, ToHttpApiData, FromJSON, ToJSON, IsString)

data DatumOptionType = Inline | Hash
deriving stock (Show, Eq, Generic)
deriving stock (Show, Eq, Ord, Generic)
deriving (FromJSON, ToJSON) via CustomJSON '[ConstructorTagModifier '[LowerFirst]] DatumOptionType

data DatumOption = DatumOption
Expand All @@ -115,13 +119,13 @@ data DatumOption = DatumOption
_datumOptionJson :: !(Maybe Aeson.Value),
_datumOptionType :: !DatumOptionType
}
deriving stock (Show, Eq, Generic)
deriving stock (Show, Eq, Ord, Generic)
deriving
(FromJSON, ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_datumOption", LowerFirst]] DatumOption

data ScriptType = Native | PlutusV1 | PlutusV2
deriving stock (Show, Eq, Generic)
deriving stock (Show, Eq, Ord, Generic)
deriving
(FromJSON, ToJSON)
via CustomJSON '[ConstructorTagModifier '[LowerAll]] ScriptType
Expand All @@ -132,7 +136,7 @@ data Script = Script
_scriptJson :: !(Maybe Aeson.Value),
_scriptType :: !ScriptType
}
deriving stock (Show, Eq, Generic)
deriving stock (Show, Eq, Ord, Generic)
deriving
(FromJSON, ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_script", LowerFirst]] Script
Expand Down
7 changes: 4 additions & 3 deletions src/Maestro/Types/V0/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ data Asset = Asset
{ _assetQuantity :: !Integer
, _assetUnit :: !Text
}
deriving stock (Show, Eq, Generic)
deriving stock (Show, Eq, Ord, Generic)
deriving
(FromJSON, ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_asset", CamelToSnake]] Asset
Expand All @@ -27,9 +27,10 @@ data Utxo = Utxo
_utxoDatum :: !(Maybe DatumOption),
_utxoIndex :: !Natural,
_utxoReferenceScript :: !(Maybe Script),
_utxoTxHash :: !Text
_utxoTxHash :: !Text,
_utxoTxoutCbor :: !(Maybe (HexStringOf TxOutCbor))
}
deriving stock (Show, Eq, Generic)
deriving stock (Show, Eq, Ord, Generic)
deriving
(FromJSON, ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_utxo", CamelToSnake]] Utxo
34 changes: 31 additions & 3 deletions src/Maestro/Types/V1/Common.hs
Original file line number Diff line number Diff line change
@@ -1,17 +1,21 @@
module Maestro.Types.V1.Common
( LastUpdated (..),
Asset (..),
v1AssetToV0,
UtxoData (..),
v1UtxoToV0,
Utxos (..),
module Maestro.Types.Common
)
where

import Data.Text (Text)
import qualified Data.Text as T (splitAt)
import Deriving.Aeson
import GHC.Natural (Natural)
import Maestro.Client.V1.Core.Pagination (HasCursor (..))
import Maestro.Types.Common
import qualified Maestro.Types.V0 as V0 (Asset (..), Utxo (..))

-- | 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.
data LastUpdated = LastUpdated
Expand All @@ -28,11 +32,22 @@ data Asset = Asset
{ _assetAmount :: !Integer
, _assetUnit :: !Text
}
deriving stock (Show, Eq, Generic)
deriving stock (Show, Eq, Ord, Generic)
deriving
(FromJSON, ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_asset", CamelToSnake]] Asset

-- | Convert @V1@ API version `Asset` type into corresponding @V0@ type.
v1AssetToV0 :: Asset -> V0.Asset
v1AssetToV0 Asset {..} = V0.Asset {
V0._assetQuantity = _assetAmount
, V0._assetUnit =
if _assetUnit == "lovelace" then _assetUnit
else
let (policyId, tokenName) = T.splitAt 56 _assetUnit
in policyId <> "#" <> tokenName
}

-- | Transaction output.
data UtxoData = UtxoData
{ _utxoDataAddress :: !Text,
Expand All @@ -42,13 +57,26 @@ data UtxoData = UtxoData
_utxoDataReferenceScript :: !(Maybe Script),
_utxoDataTxHash :: !Text,
_utxoDataSlot :: !SlotNo,
_utxoDataTxoutCbor :: !(Maybe TxCbor)
_utxoDataTxoutCbor :: !(Maybe (HexStringOf TxOutCbor))

}
deriving stock (Show, Eq, Generic)
deriving stock (Show, Eq, Ord, Generic)
deriving
(FromJSON, ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_utxoData", CamelToSnake]] UtxoData

-- | Convert @V1@ API version `UtxoData` type into corresponding @V0@ type.
v1UtxoToV0 :: UtxoData -> V0.Utxo
v1UtxoToV0 UtxoData {..} = V0.Utxo {
V0._utxoAddress = _utxoDataAddress
, V0._utxoAssets = map v1AssetToV0 _utxoDataAssets
, V0._utxoDatum = _utxoDataDatum
, V0._utxoIndex = _utxoDataIndex
, V0._utxoReferenceScript = _utxoDataReferenceScript
, V0._utxoTxHash = _utxoDataTxHash
, V0._utxoTxoutCbor = _utxoDataTxoutCbor
}

-- | Transaction Outputs
data Utxos = Utxos
{ _utxosData :: ![UtxoData],
Expand Down

0 comments on commit 4f6095e

Please sign in to comment.