Skip to content

Commit

Permalink
further clean ups for preBalanceTxM type signature
Browse files Browse the repository at this point in the history
  • Loading branch information
vvtran committed Jan 18, 2022
1 parent 539b3e2 commit e31ffde
Showing 1 changed file with 13 additions and 21 deletions.
34 changes: 13 additions & 21 deletions src/PreBalanceTx.purs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@ module PreBalanceTx
where

import Prelude
import Control.Monad.Reader.Trans (runReaderT)
import Data.Array ((\\))
import Data.Array as Array
import Data.BigInt (BigInt, fromInt, quot)
Expand All @@ -20,10 +19,9 @@ import Data.Set as Set
import Data.String.CodeUnits (length)
import Data.Tuple (fst)
import Data.Tuple.Nested ((/\), type (/\))
import Effect.Aff (Aff)
import Undefined (undefined)

import Ogmios (QueryConfig, QueryM)
import Ogmios (QueryM)
import ProtocolParametersAlonzo (coinSize, lovelacePerUTxOWord, pidSize, protocolParamUTxOCostPerWord, utxoEntrySizeWithoutVal)
import Types.Ada (adaSymbol, fromValue, getLovelace, lovelaceValueOf)
import Types.Transaction (Address, Credential(..), RequiredSigner, Transaction(..), TransactionInput, TransactionOutput(..), TxBody(..), Utxo, UtxoM)
Expand All @@ -37,20 +35,17 @@ utxosAt :: Address -> QueryM UtxoM
utxosAt = undefined

preBalanceTxM
:: QueryConfig
-> Address
:: Address
-> Map.Map Address RequiredSigner -- FIX ME: take from unbalanced tx?
-> Array Address -- FIX ME: take from unbalanced tx?
-> Transaction -- unbalanced transaction, FIX ME: do we need a newtype wrapper?
-> Aff (Either String Transaction)
preBalanceTxM qConfig ownAddr addReqSigners requiredAddrs unbalancedTx =
runReaderT
do
utxos <- unwrap <$> utxosAt ownAddr -- Do we want :: Either String UtxoM here?
let utxoIndex = utxos -- FIX ME: include newtype wrapper? UNWRAP
_unwrapUnbalancedTx = unwrap unbalancedTx
loop utxoIndex ownAddr addReqSigners requiredAddrs [] unbalancedTx
qConfig
-> QueryM (Either String Transaction)
preBalanceTxM ownAddr addReqSigners requiredAddrs unbalancedTx = do
utxos :: Utxo <- unwrap <$> utxosAt ownAddr -- Do we want :: Either String UtxoM here?
let utxoIndex :: Utxo
utxoIndex = utxos -- FIX ME: include newtype wrapper? UNWRAP
_unwrapUnbalancedTx = unwrap unbalancedTx
loop utxoIndex ownAddr addReqSigners requiredAddrs [] unbalancedTx
where
loop ::
Utxo ->
Expand All @@ -66,9 +61,9 @@ preBalanceTxM qConfig ownAddr addReqSigners requiredAddrs unbalancedTx =
addReqSigners'
requiredAddrs'
prevMinUtxos'
(Transaction unwrapTx') = do
(Transaction tx') = do
let txBody' :: TxBody
txBody' = unwrapTx'.body
txBody' = tx'.body

unwrapTxBody' = unwrap txBody'

Expand All @@ -93,15 +88,15 @@ preBalanceTxM qConfig ownAddr addReqSigners requiredAddrs unbalancedTx =
Left err -> pure $ Left err
Right balancedTxBody'' ->
if txBody' == balancedTxBody''
then pure $ Right $ wrap unwrapTx' { body = balancedTxBody'' }
then pure $ Right $ wrap tx' { body = balancedTxBody'' }
else
loop
utxoIndex'
ownAddr'
addReqSigners'
requiredAddrs'
prevMinUtxos'
$ wrap unwrapTx' { body = balancedTxBody'' }
$ wrap tx' { body = balancedTxBody'' }

chainedBalancer
:: Array (TransactionOutput /\ BigInt)
Expand Down Expand Up @@ -134,8 +129,6 @@ preBalanceTxM qConfig ownAddr addReqSigners requiredAddrs unbalancedTx =
requiredAddrs'
txBody'

-- pure $ Right tx

-- let minUtxos = prevMinUtxos ++ nextMinUtxos

-- lift $ printLog @w Debug $ "Min utxos: " ++ show minUtxos
Expand Down Expand Up @@ -237,7 +230,6 @@ size v = fromInt 6 + roundupBytesToWords b
lenAdd :: BigInt -> TokenName -> BigInt
lenAdd = \c a -> c + fromInt (length $ unwrap a)


preBalanceTxBody
:: Array (TransactionOutput /\ BigInt)
-> BigInt
Expand Down

0 comments on commit e31ffde

Please sign in to comment.