Skip to content

Commit

Permalink
Use record patterns
Browse files Browse the repository at this point in the history
  • Loading branch information
ana-pantilie committed Feb 18, 2025
1 parent 848d1d9 commit a8294f0
Show file tree
Hide file tree
Showing 6 changed files with 21 additions and 30 deletions.
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}

Expand Down Expand Up @@ -54,8 +55,8 @@ mkValue i = assetClassValue (assetClass adaSymbol adaToken) i
checkScriptContext1 :: PlutusTx.BuiltinData -> ()
checkScriptContext1 d =
case PlutusTx.unsafeFromBuiltinData d of
ScriptContext (TxInfo _ txOuts _ _ _ _ _ _ _ _) _ ->
if Data.List.length txOuts `PlutusTx.modInteger` 2 PlutusTx.== 0
ScriptContext { scriptContextTxInfo = TxInfo { txInfoOutputs } } ->
if Data.List.length txInfoOutputs `PlutusTx.modInteger` 2 PlutusTx.== 0
then ()
else PlutusTx.traceError "Odd number of outputs"
{-# INLINABLE checkScriptContext1 #-}
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}

Expand Down Expand Up @@ -58,8 +59,8 @@ mkValue i = assetClassValue (assetClass adaSymbol adaToken) i
checkScriptContext1 :: PlutusTx.BuiltinData -> ()
checkScriptContext1 d =
case PlutusTx.unsafeFromBuiltinData d of
ScriptContext (TxInfo _ _ txOuts _ _ _ _ _ _ _ _ _) _ ->
if Data.List.length txOuts `PlutusTx.modInteger` 2 PlutusTx.== 0
ScriptContext { scriptContextTxInfo = TxInfo { txInfoOutputs } } ->
if Data.List.length txInfoOutputs `PlutusTx.modInteger` 2 PlutusTx.== 0
then ()
else PlutusTx.traceError "Odd number of outputs"
{-# INLINABLE checkScriptContext1 #-}
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TemplateHaskell #-}
Expand All @@ -11,12 +12,12 @@ import PlutusLedgerApi.Data.V1 qualified as PlutusTx
import PlutusLedgerApi.Data.V3 (PubKeyHash (..), Redeemer (..), ScriptContext, TxId (..), TxInfo,
TxOut, always, pattern NoOutputDatum, pattern ScriptContext,
pattern SpendingScript, pattern TxInfo, pattern TxOut,
pattern TxOutRef, txInfoCurrentTreasuryAmount, txInfoData,
txInfoFee, txInfoId, txInfoInputs, txInfoMint, txInfoOutputs,
txInfoProposalProcedures, txInfoRedeemers, txInfoReferenceInputs,
txInfoSignatories, txInfoTreasuryDonation, txInfoTxCerts,
txInfoValidRange, txInfoVotes, txInfoWdrl, txOutAddress, txOutDatum,
txOutReferenceScript, txOutValue)
pattern TxOutRef, scriptContextTxInfo, txInfoCurrentTreasuryAmount,
txInfoData, txInfoFee, txInfoId, txInfoInputs, txInfoMint,
txInfoOutputs, txInfoProposalProcedures, txInfoRedeemers,
txInfoReferenceInputs, txInfoSignatories, txInfoTreasuryDonation,
txInfoTxCerts, txInfoValidRange, txInfoVotes, txInfoWdrl,
txOutAddress, txOutDatum, txOutReferenceScript, txOutValue)
import PlutusLedgerApi.V1.Data.Address
import PlutusLedgerApi.V1.Data.Value
import PlutusTx qualified
Expand Down Expand Up @@ -76,8 +77,8 @@ mkValue i = assetClassValue (assetClass adaSymbol adaToken) i
checkScriptContext1 :: PlutusTx.BuiltinData -> ()
checkScriptContext1 d =
case PlutusTx.unsafeFromBuiltinData d of
ScriptContext (TxInfo _ _ txOuts _ _ _ _ _ _ _ _ _ _ _ _ _) _ _ ->
if Data.List.length txOuts `PlutusTx.modInteger` 2 PlutusTx.== 0
ScriptContext { scriptContextTxInfo = TxInfo { txInfoOutputs } } ->
if Data.List.length txInfoOutputs `PlutusTx.modInteger` 2 PlutusTx.== 0
then ()
else PlutusTx.traceError "Odd number of outputs"
{-# INLINEABLE checkScriptContext1 #-}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@
~rest : list data = tailList {data} rest
~rest : list data = tailList {data} rest
!ds : (\a -> list data) data = unListData (headList {data} constrArgs)
!txOuts : (\a -> list data) data = unListData (headList {data} rest)
!ds : (\a -> list data) data = unListData (headList {data} rest)
!ds :
(\k a -> list (pair data data))
bytestring
Expand Down Expand Up @@ -75,11 +75,7 @@
{all dead. dead}
in
Bool_match
(ifThenElse
{Bool}
(equalsInteger 0 (modInteger (go txOuts 0) 2))
True
False)
(ifThenElse {Bool} (equalsInteger 0 (modInteger (go ds 0) 2)) True False)
{all dead. Unit}
(/\dead -> Unit)
(/\dead ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@
~rest : list data = tailList {data} rest
!ds : (\a -> list data) data = unListData (headList {data} constrArgs)
!ds : (\a -> list data) data = unListData (headList {data} rest)
!txOuts : (\a -> list data) data = unListData (headList {data} rest)
!ds : (\a -> list data) data = unListData (headList {data} rest)
!ds :
(\k a -> list (pair data data))
bytestring
Expand Down Expand Up @@ -79,11 +79,7 @@
{all dead. dead}
in
Bool_match
(ifThenElse
{Bool}
(equalsInteger 0 (modInteger (go txOuts 0) 2))
True
False)
(ifThenElse {Bool} (equalsInteger 0 (modInteger (go ds 0) 2)) True False)
{all dead. Unit}
(/\dead -> Unit)
(/\dead ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,7 @@
!ds : data = headList {data} (tailList {data} rest)
!ds : (\a -> list data) data = unListData (headList {data} constrArgs)
!ds : (\a -> list data) data = unListData (headList {data} rest)
!txOuts : (\a -> list data) data = unListData (headList {data} rest)
!ds : (\a -> list data) data = unListData (headList {data} rest)
!ds : integer = unIData (headList {data} rest)
!ds :
(\k a -> list (pair data data))
Expand Down Expand Up @@ -110,11 +110,7 @@
(headList {data} (tailList {data} rest))
in
Bool_match
(ifThenElse
{Bool}
(equalsInteger 0 (modInteger (go txOuts 0) 2))
True
False)
(ifThenElse {Bool} (equalsInteger 0 (modInteger (go ds 0) 2)) True False)
{all dead. Unit}
(/\dead -> Unit)
(/\dead ->
Expand Down

0 comments on commit a8294f0

Please sign in to comment.