{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs            #-}
{-# LANGUAGE TypeOperators    #-}

module Plutus.Blockfrost.Client(handleBlockfrostClient) where

import Blockfrost.Client (BlockfrostClientT, BlockfrostError (BlockfrostNotFound), projectFromFile, runBlockfrost)
import Control.Monad.Freer (Eff, LastMember, Member, type (~>))
import Control.Monad.Freer.Reader (Reader, ask)
import Control.Monad.IO.Class (MonadIO (..))
import Plutus.ChainIndex.Effects (ChainIndexQueryEffect (..))

import Plutus.Blockfrost.Queries
import Plutus.Blockfrost.Responses
import Plutus.Blockfrost.Types (BlockfrostEnv (..))
import Plutus.Blockfrost.Utils


-- | Handle 'ChainIndexQueryEffect' by making HTTP calls to the remote
--   blockfrost server.
handleBlockfrostClient ::
    forall m effs.
    ( LastMember m effs
    , Member (Reader BlockfrostEnv) effs
    , MonadIO m
    )
    => ChainIndexQueryEffect
    ~> Eff effs
handleBlockfrostClient :: ChainIndexQueryEffect ~> Eff effs
handleBlockfrostClient ChainIndexQueryEffect x
event = do
    BlockfrostEnv
bfEnv <- Eff effs BlockfrostEnv
forall r (effs :: [* -> *]). Member (Reader r) effs => Eff effs r
ask
    IO x -> Eff effs x
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO x -> Eff effs x) -> IO x -> Eff effs x
forall a b. (a -> b) -> a -> b
$ do
        Project
prj <- FilePath -> IO Project
projectFromFile (FilePath -> IO Project) -> FilePath -> IO Project
forall a b. (a -> b) -> a -> b
$ BlockfrostEnv -> FilePath
envBfTokenPath BlockfrostEnv
bfEnv
        let
            runClient :: forall a. BlockfrostClientT IO a -> IO a
            runClient :: BlockfrostClientT IO a -> IO a
runClient BlockfrostClientT IO a
a = Project -> BlockfrostClientT IO a -> IO (Either BlockfrostError a)
forall a.
Project -> BlockfrostClientT IO a -> IO (Either BlockfrostError a)
runBlockfrost Project
prj BlockfrostClientT IO a
a IO (Either BlockfrostError a)
-> (Either BlockfrostError a -> IO a) -> IO a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (BlockfrostError -> IO a)
-> (a -> IO a) -> Either BlockfrostError a -> IO a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (IOError -> IO a
forall a. IOError -> IO a
ioError (IOError -> IO a)
-> (BlockfrostError -> IOError) -> BlockfrostError -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IOError
userError (FilePath -> IOError)
-> (BlockfrostError -> FilePath) -> BlockfrostError -> IOError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockfrostError -> FilePath
forall a. Show a => a -> FilePath
show) a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return

            runClientWithDef :: forall a. BlockfrostClientT IO a -> BlockfrostClientT IO a -> IO a
            runClientWithDef :: BlockfrostClientT IO a -> BlockfrostClientT IO a -> IO a
runClientWithDef BlockfrostClientT IO a
defIO BlockfrostClientT IO a
a = do
                Either BlockfrostError a
response <- Project -> BlockfrostClientT IO a -> IO (Either BlockfrostError a)
forall a.
Project -> BlockfrostClientT IO a -> IO (Either BlockfrostError a)
runBlockfrost Project
prj BlockfrostClientT IO a
a
                case Either BlockfrostError a
response of
                    Right a
a'                -> a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a'
                    Left BlockfrostError
BlockfrostNotFound -> BlockfrostClientT IO a -> IO a
forall a. BlockfrostClientT IO a -> IO a
runClient BlockfrostClientT IO a
defIO
                    Left BlockfrostError
e                  -> IOError -> IO a
forall a. IOError -> IO a
ioError (FilePath -> IOError
userError (FilePath -> IOError) -> FilePath -> IOError
forall a b. (a -> b) -> a -> b
$ BlockfrostError -> FilePath
forall a. Show a => a -> FilePath
show BlockfrostError
e)

            runClientMaybe :: forall a. BlockfrostClientT IO a -> IO (Maybe a)
            runClientMaybe :: BlockfrostClientT IO a -> IO (Maybe a)
runClientMaybe BlockfrostClientT IO a
a = do
                Either BlockfrostError a
response <- Project -> BlockfrostClientT IO a -> IO (Either BlockfrostError a)
forall a.
Project -> BlockfrostClientT IO a -> IO (Either BlockfrostError a)
runBlockfrost Project
prj BlockfrostClientT IO a
a
                case Either BlockfrostError a
response of
                    Right a
a'                -> Maybe a -> IO (Maybe a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Maybe a
forall a. a -> Maybe a
Just a
a')
                    Left BlockfrostError
BlockfrostNotFound -> Maybe a -> IO (Maybe a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing
                    Left BlockfrostError
e                  -> IOError -> IO (Maybe a)
forall a. IOError -> IO a
ioError (FilePath -> IOError
userError (FilePath -> IOError) -> FilePath -> IOError
forall a b. (a -> b) -> a -> b
$ BlockfrostError -> FilePath
forall a. Show a => a -> FilePath
show BlockfrostError
e)

        case ChainIndexQueryEffect x
event of
            DatumFromHash DatumHash
d               -> (BlockfrostClientT IO Value -> IO (Maybe Value)
forall a. BlockfrostClientT IO a -> IO (Maybe a)
runClientMaybe (BlockfrostClientT IO Value -> IO (Maybe Value))
-> (DatumHash -> BlockfrostClientT IO Value)
-> DatumHash
-> IO (Maybe Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DatumHash -> BlockfrostClientT IO Value
forall (m :: * -> *). MonadBlockfrost m => DatumHash -> m Value
getDatumBlockfrost (DatumHash -> BlockfrostClientT IO Value)
-> (DatumHash -> DatumHash)
-> DatumHash
-> BlockfrostClientT IO Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DatumHash -> DatumHash
forall a. ToBlockfrostDatumHash a => a -> DatumHash
toBlockfrostDatumHash) DatumHash
d        IO (Maybe Value)
-> (Maybe Value -> IO (Maybe Datum)) -> IO (Maybe Datum)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe Value -> IO (Maybe Datum)
forall a. FromData a => Maybe Value -> IO (Maybe a)
processGetDatum
            RedeemerFromHash RedeemerHash
d            -> (BlockfrostClientT IO Value -> IO (Maybe Value)
forall a. BlockfrostClientT IO a -> IO (Maybe a)
runClientMaybe (BlockfrostClientT IO Value -> IO (Maybe Value))
-> (RedeemerHash -> BlockfrostClientT IO Value)
-> RedeemerHash
-> IO (Maybe Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DatumHash -> BlockfrostClientT IO Value
forall (m :: * -> *). MonadBlockfrost m => DatumHash -> m Value
getDatumBlockfrost (DatumHash -> BlockfrostClientT IO Value)
-> (RedeemerHash -> DatumHash)
-> RedeemerHash
-> BlockfrostClientT IO Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RedeemerHash -> DatumHash
forall a. ToBlockfrostDatumHash a => a -> DatumHash
toBlockfrostDatumHash) RedeemerHash
d        IO (Maybe Value)
-> (Maybe Value -> IO (Maybe Redeemer)) -> IO (Maybe Redeemer)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe Value -> IO (Maybe Redeemer)
forall a. FromData a => Maybe Value -> IO (Maybe a)
processGetDatum
            ValidatorFromHash ValidatorHash
d           -> (BlockfrostClientT IO ScriptCBOR -> IO (Maybe ScriptCBOR)
forall a. BlockfrostClientT IO a -> IO (Maybe a)
runClientMaybe (BlockfrostClientT IO ScriptCBOR -> IO (Maybe ScriptCBOR))
-> (ValidatorHash -> BlockfrostClientT IO ScriptCBOR)
-> ValidatorHash
-> IO (Maybe ScriptCBOR)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptHash -> BlockfrostClientT IO ScriptCBOR
forall (m :: * -> *).
MonadBlockfrost m =>
ScriptHash -> m ScriptCBOR
getValidatorBlockfrost (ScriptHash -> BlockfrostClientT IO ScriptCBOR)
-> (ValidatorHash -> ScriptHash)
-> ValidatorHash
-> BlockfrostClientT IO ScriptCBOR
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValidatorHash -> ScriptHash
forall a. ToBlockfrostScriptHash a => a -> ScriptHash
toBlockfrostScriptHash) ValidatorHash
d   IO (Maybe ScriptCBOR)
-> (Maybe ScriptCBOR -> IO (Maybe (Versioned Validator)))
-> IO (Maybe (Versioned Validator))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe ScriptCBOR -> IO (Maybe (Versioned Validator))
forall a.
PlutusValidator a =>
Maybe ScriptCBOR -> IO (Maybe (Versioned a))
processGetValidator
            MintingPolicyFromHash MintingPolicyHash
d       -> (BlockfrostClientT IO ScriptCBOR -> IO (Maybe ScriptCBOR)
forall a. BlockfrostClientT IO a -> IO (Maybe a)
runClientMaybe (BlockfrostClientT IO ScriptCBOR -> IO (Maybe ScriptCBOR))
-> (MintingPolicyHash -> BlockfrostClientT IO ScriptCBOR)
-> MintingPolicyHash
-> IO (Maybe ScriptCBOR)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptHash -> BlockfrostClientT IO ScriptCBOR
forall (m :: * -> *).
MonadBlockfrost m =>
ScriptHash -> m ScriptCBOR
getValidatorBlockfrost (ScriptHash -> BlockfrostClientT IO ScriptCBOR)
-> (MintingPolicyHash -> ScriptHash)
-> MintingPolicyHash
-> BlockfrostClientT IO ScriptCBOR
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MintingPolicyHash -> ScriptHash
forall a. ToBlockfrostScriptHash a => a -> ScriptHash
toBlockfrostScriptHash) MintingPolicyHash
d   IO (Maybe ScriptCBOR)
-> (Maybe ScriptCBOR -> IO (Maybe (Versioned MintingPolicy)))
-> IO (Maybe (Versioned MintingPolicy))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe ScriptCBOR -> IO (Maybe (Versioned MintingPolicy))
forall a.
PlutusValidator a =>
Maybe ScriptCBOR -> IO (Maybe (Versioned a))
processGetValidator
            StakeValidatorFromHash StakeValidatorHash
d      -> (BlockfrostClientT IO ScriptCBOR -> IO (Maybe ScriptCBOR)
forall a. BlockfrostClientT IO a -> IO (Maybe a)
runClientMaybe (BlockfrostClientT IO ScriptCBOR -> IO (Maybe ScriptCBOR))
-> (StakeValidatorHash -> BlockfrostClientT IO ScriptCBOR)
-> StakeValidatorHash
-> IO (Maybe ScriptCBOR)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptHash -> BlockfrostClientT IO ScriptCBOR
forall (m :: * -> *).
MonadBlockfrost m =>
ScriptHash -> m ScriptCBOR
getValidatorBlockfrost (ScriptHash -> BlockfrostClientT IO ScriptCBOR)
-> (StakeValidatorHash -> ScriptHash)
-> StakeValidatorHash
-> BlockfrostClientT IO ScriptCBOR
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StakeValidatorHash -> ScriptHash
forall a. ToBlockfrostScriptHash a => a -> ScriptHash
toBlockfrostScriptHash) StakeValidatorHash
d   IO (Maybe ScriptCBOR)
-> (Maybe ScriptCBOR -> IO (Maybe (Versioned StakeValidator)))
-> IO (Maybe (Versioned StakeValidator))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe ScriptCBOR -> IO (Maybe (Versioned StakeValidator))
forall a.
PlutusValidator a =>
Maybe ScriptCBOR -> IO (Maybe (Versioned a))
processGetValidator
            UnspentTxOutFromRef TxOutRef
r         -> (BlockfrostClientT IO UtxoOutput -> IO (Maybe UtxoOutput)
forall a. BlockfrostClientT IO a -> IO (Maybe a)
runClientMaybe (BlockfrostClientT IO UtxoOutput -> IO (Maybe UtxoOutput))
-> (TxOutRef -> BlockfrostClientT IO UtxoOutput)
-> TxOutRef
-> IO (Maybe UtxoOutput)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxHash, Integer) -> BlockfrostClientT IO UtxoOutput
getUnspentTxOutBlockfrost ((TxHash, Integer) -> BlockfrostClientT IO UtxoOutput)
-> (TxOutRef -> (TxHash, Integer))
-> TxOutRef
-> BlockfrostClientT IO UtxoOutput
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOutRef -> (TxHash, Integer)
toBlockfrostRef) TxOutRef
r       IO (Maybe UtxoOutput)
-> (Maybe UtxoOutput -> IO (Maybe DecoratedTxOut))
-> IO (Maybe DecoratedTxOut)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe UtxoOutput -> IO (Maybe DecoratedTxOut)
processUnspentTxOut
            TxOutFromRef TxOutRef
r                -> (BlockfrostClientT IO UtxoOutput -> IO (Maybe UtxoOutput)
forall a. BlockfrostClientT IO a -> IO (Maybe a)
runClientMaybe (BlockfrostClientT IO UtxoOutput -> IO (Maybe UtxoOutput))
-> (TxOutRef -> BlockfrostClientT IO UtxoOutput)
-> TxOutRef
-> IO (Maybe UtxoOutput)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxHash, Integer) -> BlockfrostClientT IO UtxoOutput
getTxOutBlockfrost ((TxHash, Integer) -> BlockfrostClientT IO UtxoOutput)
-> (TxOutRef -> (TxHash, Integer))
-> TxOutRef
-> BlockfrostClientT IO UtxoOutput
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOutRef -> (TxHash, Integer)
toBlockfrostRef) TxOutRef
r              IO (Maybe UtxoOutput)
-> (Maybe UtxoOutput -> IO (Maybe DecoratedTxOut))
-> IO (Maybe DecoratedTxOut)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe UtxoOutput -> IO (Maybe DecoratedTxOut)
processUnspentTxOut
            TxFromTxId TxId
i                  -> (BlockfrostClientT IO TxResponse -> IO (Maybe TxResponse)
forall a. BlockfrostClientT IO a -> IO (Maybe a)
runClientMaybe (BlockfrostClientT IO TxResponse -> IO (Maybe TxResponse))
-> (TxId -> BlockfrostClientT IO TxResponse)
-> TxId
-> IO (Maybe TxResponse)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxHash -> BlockfrostClientT IO TxResponse
forall (m :: * -> *). MonadBlockfrost m => TxHash -> m TxResponse
getTxFromTxIdBlockfrost (TxHash -> BlockfrostClientT IO TxResponse)
-> (TxId -> TxHash) -> TxId -> BlockfrostClientT IO TxResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxId -> TxHash
toBlockfrostTxHash) TxId
i      IO (Maybe TxResponse)
-> (Maybe TxResponse -> IO (Maybe ChainIndexTx))
-> IO (Maybe ChainIndexTx)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe TxResponse -> IO (Maybe ChainIndexTx)
processGetTxFromTxId
            TxsFromTxIds [TxId]
is               -> (BlockfrostClientT IO [TxResponse]
-> BlockfrostClientT IO [TxResponse] -> IO [TxResponse]
forall a. BlockfrostClientT IO a -> BlockfrostClientT IO a -> IO a
runClientWithDef BlockfrostClientT IO [TxResponse]
forall (m :: * -> *) a. MonadBlockfrost m => m [a]
defaultGetList (BlockfrostClientT IO [TxResponse] -> IO [TxResponse])
-> ([TxId] -> BlockfrostClientT IO [TxResponse])
-> [TxId]
-> IO [TxResponse]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [TxHash] -> BlockfrostClientT IO [TxResponse]
forall (m :: * -> *).
MonadBlockfrost m =>
[TxHash] -> m [TxResponse]
getTxsFromTxIdsBlockfrost ([TxHash] -> BlockfrostClientT IO [TxResponse])
-> ([TxId] -> [TxHash])
-> [TxId]
-> BlockfrostClientT IO [TxResponse]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [TxId] -> [TxHash]
toBlockfrostTxHashes) [TxId]
is IO [TxResponse]
-> ([TxResponse] -> IO [ChainIndexTx]) -> IO [ChainIndexTx]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [TxResponse] -> IO [ChainIndexTx]
processGetTxsFromTxIds
            UtxoSetMembership TxOutRef
r           -> (BlockfrostClientT IO (Block, Bool)
-> BlockfrostClientT IO (Block, Bool) -> IO (Block, Bool)
forall a. BlockfrostClientT IO a -> BlockfrostClientT IO a -> IO a
runClientWithDef BlockfrostClientT IO (Block, Bool)
forall (m :: * -> *). MonadBlockfrost m => m (Block, Bool)
defaultIsUtxo  (BlockfrostClientT IO (Block, Bool) -> IO (Block, Bool))
-> (TxOutRef -> BlockfrostClientT IO (Block, Bool))
-> TxOutRef
-> IO (Block, Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxHash, Integer) -> BlockfrostClientT IO (Block, Bool)
forall (m :: * -> *).
MonadBlockfrost m =>
(TxHash, Integer) -> m (Block, Bool)
getIsUtxoBlockfrost ((TxHash, Integer) -> BlockfrostClientT IO (Block, Bool))
-> (TxOutRef -> (TxHash, Integer))
-> TxOutRef
-> BlockfrostClientT IO (Block, Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOutRef -> (TxHash, Integer)
toBlockfrostRef) TxOutRef
r                IO (Block, Bool)
-> ((Block, Bool) -> IO IsUtxoResponse) -> IO IsUtxoResponse
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Block, Bool) -> IO IsUtxoResponse
processIsUtxo
            UtxoSetAtAddress PageQuery TxOutRef
pq Credential
a         -> (BlockfrostClientT IO (Block, [AddressUtxo])
-> BlockfrostClientT IO (Block, [AddressUtxo])
-> IO (Block, [AddressUtxo])
forall a. BlockfrostClientT IO a -> BlockfrostClientT IO a -> IO a
runClientWithDef BlockfrostClientT IO (Block, [AddressUtxo])
forall (m :: * -> *). MonadBlockfrost m => m (Block, [AddressUtxo])
defaultGetUtxo (BlockfrostClientT IO (Block, [AddressUtxo])
 -> IO (Block, [AddressUtxo]))
-> (Credential -> BlockfrostClientT IO (Block, [AddressUtxo]))
-> Credential
-> IO (Block, [AddressUtxo])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PageQuery TxOutRef
-> Address -> BlockfrostClientT IO (Block, [AddressUtxo])
forall (m :: * -> *) a.
MonadBlockfrost m =>
PageQuery a -> Address -> m (Block, [AddressUtxo])
getUtxoAtAddressBlockfrost PageQuery TxOutRef
pq (Address -> BlockfrostClientT IO (Block, [AddressUtxo]))
-> (Credential -> Address)
-> Credential
-> BlockfrostClientT IO (Block, [AddressUtxo])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NetworkId -> Credential -> Address
credentialToAddress (BlockfrostEnv -> NetworkId
envNetworkId BlockfrostEnv
bfEnv)) Credential
a  IO (Block, [AddressUtxo])
-> ((Block, [AddressUtxo]) -> IO UtxosResponse) -> IO UtxosResponse
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= PageQuery TxOutRef -> (Block, [AddressUtxo]) -> IO UtxosResponse
processGetUtxos PageQuery TxOutRef
pq
            UtxoSetWithCurrency PageQuery TxOutRef
pq AssetClass
a      -> (BlockfrostClientT IO (Block, [AddressUtxo])
-> BlockfrostClientT IO (Block, [AddressUtxo])
-> IO (Block, [AddressUtxo])
forall a. BlockfrostClientT IO a -> BlockfrostClientT IO a -> IO a
runClientWithDef BlockfrostClientT IO (Block, [AddressUtxo])
forall (m :: * -> *). MonadBlockfrost m => m (Block, [AddressUtxo])
defaultGetUtxo (BlockfrostClientT IO (Block, [AddressUtxo])
 -> IO (Block, [AddressUtxo]))
-> (AssetClass -> BlockfrostClientT IO (Block, [AddressUtxo]))
-> AssetClass
-> IO (Block, [AddressUtxo])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PageQuery TxOutRef
-> AssetId -> BlockfrostClientT IO (Block, [AddressUtxo])
forall (m :: * -> *) a.
MonadBlockfrost m =>
PageQuery a -> AssetId -> m (Block, [AddressUtxo])
getUtxoSetWithCurrency PageQuery TxOutRef
pq (AssetId -> BlockfrostClientT IO (Block, [AddressUtxo]))
-> (AssetClass -> AssetId)
-> AssetClass
-> BlockfrostClientT IO (Block, [AddressUtxo])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AssetClass -> AssetId
toBlockfrostAssetId) AssetClass
a      IO (Block, [AddressUtxo])
-> ((Block, [AddressUtxo]) -> IO UtxosResponse) -> IO UtxosResponse
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= PageQuery TxOutRef -> (Block, [AddressUtxo]) -> IO UtxosResponse
processGetUtxos PageQuery TxOutRef
pq
            TxoSetAtAddress PageQuery TxOutRef
pq Credential
a          -> (BlockfrostClientT IO [UtxoInput]
-> BlockfrostClientT IO [UtxoInput] -> IO [UtxoInput]
forall a. BlockfrostClientT IO a -> BlockfrostClientT IO a -> IO a
runClientWithDef BlockfrostClientT IO [UtxoInput]
forall (m :: * -> *) a. MonadBlockfrost m => m [a]
defaultGetList (BlockfrostClientT IO [UtxoInput] -> IO [UtxoInput])
-> (Credential -> BlockfrostClientT IO [UtxoInput])
-> Credential
-> IO [UtxoInput]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PageQuery TxOutRef -> Address -> BlockfrostClientT IO [UtxoInput]
forall (m :: * -> *) a.
MonadBlockfrost m =>
PageQuery a -> Address -> m [UtxoInput]
getTxoAtAddressBlockfrost PageQuery TxOutRef
pq (Address -> BlockfrostClientT IO [UtxoInput])
-> (Credential -> Address)
-> Credential
-> BlockfrostClientT IO [UtxoInput]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NetworkId -> Credential -> Address
credentialToAddress (BlockfrostEnv -> NetworkId
envNetworkId BlockfrostEnv
bfEnv)) Credential
a IO [UtxoInput]
-> ([UtxoInput] -> IO TxosResponse) -> IO TxosResponse
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= PageQuery TxOutRef -> [UtxoInput] -> IO TxosResponse
processGetTxos PageQuery TxOutRef
pq
            ChainIndexQueryEffect x
GetTip                        -> BlockfrostClientT IO Block -> IO Block
forall a. BlockfrostClientT IO a -> IO a
runClient BlockfrostClientT IO Block
forall (m :: * -> *). MonadBlockfrost m => m Block
getTipBlockfrost IO Block -> (Block -> IO Tip) -> IO Tip
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Block -> IO Tip
processTip
            UnspentTxOutSetAtAddress PageQuery TxOutRef
pq Credential
a -> (BlockfrostClientT IO [AddressUtxo]
-> BlockfrostClientT IO [AddressUtxo] -> IO [AddressUtxo]
forall a. BlockfrostClientT IO a -> BlockfrostClientT IO a -> IO a
runClientWithDef BlockfrostClientT IO [AddressUtxo]
forall (m :: * -> *) a. MonadBlockfrost m => m [a]
defaultGetList (BlockfrostClientT IO [AddressUtxo] -> IO [AddressUtxo])
-> (Credential -> BlockfrostClientT IO [AddressUtxo])
-> Credential
-> IO [AddressUtxo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PageQuery TxOutRef -> Address -> BlockfrostClientT IO [AddressUtxo]
forall (m :: * -> *) a.
MonadBlockfrost m =>
PageQuery a -> Address -> m [AddressUtxo]
getUnspentAtAddressBlockfrost PageQuery TxOutRef
pq (Address -> BlockfrostClientT IO [AddressUtxo])
-> (Credential -> Address)
-> Credential
-> BlockfrostClientT IO [AddressUtxo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NetworkId -> Credential -> Address
credentialToAddress (BlockfrostEnv -> NetworkId
envNetworkId BlockfrostEnv
bfEnv)) Credential
a  IO [AddressUtxo]
-> ([AddressUtxo]
    -> IO (QueryResponse [(TxOutRef, DecoratedTxOut)]))
-> IO (QueryResponse [(TxOutRef, DecoratedTxOut)])
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= PageQuery TxOutRef
-> Credential
-> [AddressUtxo]
-> IO (QueryResponse [(TxOutRef, DecoratedTxOut)])
processUnspentTxOutSetAtAddress PageQuery TxOutRef
pq Credential
a
            DatumsAtAddress PageQuery TxOutRef
pq Credential
a          -> (BlockfrostClientT IO [Value]
-> BlockfrostClientT IO [Value] -> IO [Value]
forall a. BlockfrostClientT IO a -> BlockfrostClientT IO a -> IO a
runClientWithDef BlockfrostClientT IO [Value]
forall (m :: * -> *) a. MonadBlockfrost m => m [a]
defaultGetList (BlockfrostClientT IO [Value] -> IO [Value])
-> (Credential -> BlockfrostClientT IO [Value])
-> Credential
-> IO [Value]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PageQuery TxOutRef -> Address -> BlockfrostClientT IO [Value]
forall (m :: * -> *) a.
MonadBlockfrost m =>
PageQuery a -> Address -> m [Value]
getDatumsAtAddressBlockfrost PageQuery TxOutRef
pq (Address -> BlockfrostClientT IO [Value])
-> (Credential -> Address)
-> Credential
-> BlockfrostClientT IO [Value]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NetworkId -> Credential -> Address
credentialToAddress (BlockfrostEnv -> NetworkId
envNetworkId BlockfrostEnv
bfEnv)) Credential
a  IO [Value]
-> ([Value] -> IO (QueryResponse [Datum]))
-> IO (QueryResponse [Datum])
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= PageQuery TxOutRef
-> Credential -> [Value] -> IO (QueryResponse [Datum])
forall a.
FromData a =>
PageQuery TxOutRef
-> Credential -> [Value] -> IO (QueryResponse [a])
processDatumsAtAddress PageQuery TxOutRef
pq Credential
a