Skip to content

Commit 16d0aff

Browse files
committed
remove deprecated utxosMapParser
1 parent 198ed0b commit 16d0aff

File tree

5 files changed

+3
-308
lines changed

5 files changed

+3
-308
lines changed

bot-plutus-interface.cabal

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -189,7 +189,6 @@ test-suite bot-plutus-interface-test
189189
Spec.BotPlutusInterface.ContractStats
190190
Spec.BotPlutusInterface.Server
191191
Spec.BotPlutusInterface.TxStatusChange
192-
Spec.BotPlutusInterface.UtxoParser
193192
Spec.MockContract
194193
Spec.RandomLedger
195194

src/BotPlutusInterface/CardanoCLI.hs

Lines changed: 1 addition & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,6 @@ module BotPlutusInterface.CardanoCLI (
99
validatorScriptFilePath,
1010
unsafeSerialiseAddress,
1111
policyScriptFilePath,
12-
utxosAt,
1312
queryTip,
1413
) where
1514

@@ -44,7 +43,6 @@ import Data.Attoparsec.Text (parseOnly)
4443
import Data.Bifunctor (first)
4544
import Data.Bool (bool)
4645
import Data.ByteString.Lazy.Char8 qualified as Char8
47-
import Data.Either (fromRight)
4846
import Data.Either.Combinators (mapLeft)
4947
import Data.Hex (hex)
5048
import Data.Kind (Type)
@@ -69,7 +67,7 @@ import Ledger.Interval (
6967
)
7068
import Ledger.Scripts (Datum, DatumHash (..))
7169
import Ledger.Scripts qualified as Scripts
72-
import Ledger.Tx (ChainIndexTxOut, RedeemerPtr (..), Redeemers, ScriptTag (..), Tx (..), TxId (..), TxIn (..), TxInType (..), TxOut (..), TxOutRef (..), txId)
70+
import Ledger.Tx (RedeemerPtr (..), Redeemers, ScriptTag (..), Tx (..), TxId (..), TxIn (..), TxInType (..), TxOut (..), TxOutRef (..), txId)
7371
import Ledger.Tx.CardanoAPI (toCardanoAddressInEra)
7472
import Ledger.Value (Value)
7573
import Ledger.Value qualified as Value
@@ -98,30 +96,6 @@ queryTip config =
9896
, cmdOutParser = fromMaybe (error "Couldn't parse chain tip") . JSON.decode . Char8.pack
9997
}
10098

101-
-- | Getting all available UTXOs at an address (all utxos are assumed to be PublicKeyChainIndexTxOut)
102-
utxosAt ::
103-
forall (w :: Type) (effs :: [Type -> Type]).
104-
Member (PABEffect w) effs =>
105-
PABConfig ->
106-
Address ->
107-
Eff effs (Either Text (Map TxOutRef ChainIndexTxOut))
108-
utxosAt pabConf address =
109-
callCommand @w
110-
ShellArgs
111-
{ cmdName = "cardano-cli"
112-
, cmdArgs =
113-
mconcat
114-
[ ["query", "utxo"]
115-
, ["--address", unsafeSerialiseAddress pabConf.pcNetwork address]
116-
, networkOpt pabConf
117-
]
118-
, cmdOutParser =
119-
Map.fromList
120-
. fromRight []
121-
. parseOnly (UtxoParser.utxoMapParser address)
122-
. Text.pack
123-
}
124-
12599
-- | Calculating fee for an unbalanced transaction
126100
calculateMinFee ::
127101
forall (w :: Type) (effs :: [Type -> Type]).

src/BotPlutusInterface/UtxoParser.hs

Lines changed: 2 additions & 111 deletions
Original file line numberDiff line numberDiff line change
@@ -1,120 +1,31 @@
1-
module BotPlutusInterface.UtxoParser
2-
{-# DEPRECATED "This parser doesn't parses utxo(s) with inline datum, use 'utxosAt' from BotPlutusInterface.CardanoNode.Effects.hs instead." #-}
3-
(
4-
chainIndexTxOutParser,
1+
module BotPlutusInterface.UtxoParser (
52
feeParser,
6-
utxoParser,
7-
utxoMapParser,
83
tokenNameParser,
94
) where
105

11-
import Control.Applicative (many, optional, (<|>))
6+
import Control.Applicative (optional)
127
import Control.Monad (mzero, void)
138
import Data.Aeson.Extras (tryDecode)
149
import Data.Attoparsec.ByteString.Char8 (isSpace)
1510
import Data.Attoparsec.Text (
1611
Parser,
1712
char,
1813
choice,
19-
count,
2014
decimal,
21-
inClass,
22-
isEndOfLine,
2315
option,
24-
sepBy,
2516
signed,
2617
skipSpace,
27-
skipWhile,
2818
string,
2919
takeWhile,
30-
(<?>),
3120
)
32-
import Data.Functor (($>))
3321
import Data.Text (Text)
34-
import Ledger (Address (addressCredential), Datum)
35-
import Ledger.Ada qualified as Ada
36-
import Ledger.Scripts (DatumHash (..))
37-
import Ledger.Tx (ChainIndexTxOut (PublicKeyChainIndexTxOut, ScriptChainIndexTxOut), TxId (..), TxOutRef (..))
38-
import Ledger.Value (AssetClass, Value)
39-
import Ledger.Value qualified as Value
40-
import Plutus.Script.Utils.Scripts qualified as ScriptUtils
4122
import Plutus.V1.Ledger.Api (
4223
BuiltinByteString,
43-
Credential (PubKeyCredential, ScriptCredential),
44-
CurrencySymbol (..),
4524
TokenName (..),
4625
)
47-
import Plutus.V2.Ledger.Api (OutputDatum (NoOutputDatum, OutputDatum, OutputDatumHash))
4826
import PlutusTx.Builtins (toBuiltin)
4927
import Prelude hiding (takeWhile)
5028

51-
{-# DEPRECATED utxoMapParser "use 'utxosAt' from BotPlutusInterface.CardanoNode.Effects.hs" #-}
52-
utxoMapParser :: Address -> Parser [(TxOutRef, ChainIndexTxOut)]
53-
utxoMapParser address = do
54-
skipLine 2
55-
many (utxoParser address)
56-
57-
skipLine :: Int -> Parser ()
58-
skipLine n =
59-
void $
60-
count n $ do
61-
skipWhile (not . isEndOfLine)
62-
skipWhile isEndOfLine
63-
64-
utxoParser :: Address -> Parser (TxOutRef, ChainIndexTxOut)
65-
utxoParser address =
66-
(,) <$> (txOutRefParser <?> "TxOutRef") <* skipSpace
67-
<*> (chainIndexTxOutParser address <?> "ChainIndexTxOut") <* skipWhile isEndOfLine
68-
69-
txOutRefParser :: Parser TxOutRef
70-
txOutRefParser = do
71-
txId <- TxId <$> decodeHash (takeWhile (/= ' '))
72-
73-
skipSpace
74-
txIx <- decimal
75-
pure $ TxOutRef txId txIx
76-
77-
chainIndexTxOutParser :: Address -> Parser ChainIndexTxOut
78-
chainIndexTxOutParser address = do
79-
value <- mconcat <$> (valueParser <?> "Value") `sepBy` " + "
80-
void " + "
81-
82-
case addressCredential address of
83-
ScriptCredential validatorHash -> do
84-
datumHash <- datumHashParser <?> "DatumHash"
85-
pure $
86-
ScriptChainIndexTxOut
87-
address
88-
value
89-
(datumHash, Nothing)
90-
Nothing
91-
(validatorHash, Nothing)
92-
PubKeyCredential _ -> do
93-
outputDatum <- outputDatumParser <?> "OutputDatum"
94-
pure $
95-
PublicKeyChainIndexTxOut
96-
address
97-
value
98-
(convertOutputDatum outputDatum)
99-
Nothing
100-
101-
valueParser :: Parser Value
102-
valueParser = do
103-
amt <- signed decimal
104-
skipSpace
105-
assetClass <- assetClassParser <?> "AssetClass"
106-
pure $ Value.assetClassValue assetClass amt
107-
108-
assetClassParser :: Parser AssetClass
109-
assetClassParser =
110-
choice [adaAssetClass, otherAssetClass]
111-
where
112-
adaAssetClass = Value.assetClass Ada.adaSymbol Ada.adaToken <$ "lovelace"
113-
otherAssetClass = do
114-
curSymbol <- CurrencySymbol <$> decodeHash (takeWhile (not . inClass " .")) <?> "CurrencySymbol"
115-
tokenname <- tokenNameParser <?> "TokenName"
116-
pure $ Value.assetClass curSymbol tokenname
117-
11829
tokenNameParser :: Parser TokenName
11930
tokenNameParser = do
12031
option "" tokenName
@@ -124,26 +35,6 @@ tokenNameParser = do
12435
void $ optional $ string "0x"
12536
TokenName <$> decodeHash (takeWhile (not . isSpace))
12637

127-
convertOutputDatum :: OutputDatum -> Maybe (DatumHash, Maybe Datum)
128-
convertOutputDatum = \case
129-
NoOutputDatum -> Nothing
130-
OutputDatumHash dh -> Just (dh, Nothing)
131-
OutputDatum d -> Just (ScriptUtils.datumHash d, Just d)
132-
133-
{-# DEPRECATED outputDatumParser "This will fail on inline datum, since we don't parse that utxo(s)." #-}
134-
outputDatumParser :: Parser OutputDatum
135-
outputDatumParser =
136-
OutputDatumHash <$> datumHashParser
137-
<|> "TxOutDatumNone" $> NoOutputDatum
138-
139-
datumHashParser :: Parser DatumHash
140-
datumHashParser = do
141-
void "TxOutDatumHash"
142-
skipSpace
143-
void $ "ScriptDataInAlonzoEra" <|> "ScriptDataInBabbageEra"
144-
skipSpace
145-
char '\"' *> (DatumHash <$> decodeHash (takeWhile (/= '\"'))) <* char '\"'
146-
14738
decodeHash :: Parser Text -> Parser BuiltinByteString
14839
decodeHash rawParser =
14940
rawParser >>= \parsed -> either (const mzero) (pure . toBuiltin) (tryDecode parsed)

test/Spec.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,6 @@ import Spec.BotPlutusInterface.Contract qualified
77
import Spec.BotPlutusInterface.ContractStats qualified
88
import Spec.BotPlutusInterface.Server qualified
99
import Spec.BotPlutusInterface.TxStatusChange qualified
10-
import Spec.BotPlutusInterface.UtxoParser qualified
1110
import System.IO
1211
import Test.Tasty (TestTree, defaultMain, testGroup)
1312

@@ -27,7 +26,6 @@ tests =
2726
testGroup
2827
"BotPlutusInterface"
2928
[ Spec.BotPlutusInterface.Contract.tests
30-
, Spec.BotPlutusInterface.UtxoParser.tests
3129
, Spec.BotPlutusInterface.Balance.tests
3230
, Spec.BotPlutusInterface.CoinSelection.tests
3331
, Spec.BotPlutusInterface.Server.tests

test/Spec/BotPlutusInterface/UtxoParser.hs

Lines changed: 0 additions & 167 deletions
This file was deleted.

0 commit comments

Comments
 (0)