-
Notifications
You must be signed in to change notification settings - Fork 483
/
Copy pathContexts.hs
304 lines (262 loc) · 11.9 KB
/
Contexts.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-simplifiable-class-constraints #-}
{-# OPTIONS_GHC -fno-strictness #-}
{-# OPTIONS_GHC -fno-specialise #-}
{-# OPTIONS_GHC -fno-omit-interface-pragmas #-}
module Plutus.V1.Ledger.Contexts
(
-- * Pending transactions and related types
TxInfo(..)
, ScriptContext(..)
, ScriptPurpose(..)
, TxOut(..)
, TxOutRef(..)
, TxInInfo(..)
, findOwnInput
, findDatum
, findDatumHash
, findTxInByTxOutRef
, findContinuingOutputs
, getContinuingOutputs
-- ** Hashes (see note [Hashes in validator scripts])
, scriptCurrencySymbol
, pubKeyHash
-- * Validator functions
-- ** Signatures
, txSignedBy
-- ** Transactions
, pubKeyOutput
, scriptOutputsAt
, pubKeyOutputsAt
, valueLockedBy
, valuePaidTo
, adaLockedBy
, signsTransaction
, spendsOutput
, valueSpent
, valueProduced
, ownCurrencySymbol
, ownHashes
, ownHash
, fromSymbol
) where
import GHC.Generics (Generic)
import PlutusTx
import qualified PlutusTx.Builtins as Builtins
import PlutusTx.Prelude
import Plutus.V1.Ledger.Ada (Ada)
import qualified Plutus.V1.Ledger.Ada as Ada
import Plutus.V1.Ledger.Address (Address (..), toPubKeyHash)
import Plutus.V1.Ledger.Bytes (LedgerBytes (..))
import Plutus.V1.Ledger.Credential (Credential (..), StakingCredential)
import Plutus.V1.Ledger.Crypto (PubKey (..), PubKeyHash (..), Signature (..), pubKeyHash)
import Plutus.V1.Ledger.DCert (DCert (..))
import Plutus.V1.Ledger.Scripts
import Plutus.V1.Ledger.Slot (SlotRange)
import Plutus.V1.Ledger.Tx (TxOut (..), TxOutRef (..))
import Plutus.V1.Ledger.TxId
import Plutus.V1.Ledger.Value (CurrencySymbol (..), Value)
import qualified Plutus.V1.Ledger.Value as Value
{- Note [Script types in pending transactions]
To validate a transaction, we have to evaluate the validation script of each of
the transaction's inputs. The validation script sees the data of the
transaction output it validates, and the redeemer of the transaction input of
the transaction that consumes it.
In addition, the validation script also needs information on the transaction as
a whole (not just the output-input pair it is concerned with). This information
is provided by the `TxInfo` type. A `TxInfo` contains the hashes of
redeemer and data scripts of all of its inputs and outputs.
-}
-- | An input of a pending transaction.
data TxInInfo = TxInInfo
{ txInInfoOutRef :: TxOutRef
, txInInfoResolved :: TxOut
} deriving (Generic)
-- | Purpose of the script that is currently running
data ScriptPurpose
= Minting CurrencySymbol
| Spending TxOutRef
| Rewarding StakingCredential
| Certifying DCert
-- | A pending transaction. This is the view as seen by validator scripts, so some details are stripped out.
data TxInfo = TxInfo
{ txInfoInputs :: [TxInInfo] -- ^ Transaction inputs
, txInfoInputsFees :: [TxInInfo] -- ^ Transaction inputs designated to pay fees
, txInfoOutputs :: [TxOut] -- ^ Transaction outputs
, txInfoFee :: Value -- ^ The fee paid by this transaction.
, txInfoForge :: Value -- ^ The 'Value' forged by this transaction.
, txInfoDCert :: [DCert] -- ^ Digests of certificates included in this transaction
, txInfoWdrl :: [(StakingCredential, Integer)] -- ^ Withdrawals
, txInfoValidRange :: SlotRange -- ^ The valid range for the transaction.
, txInfoSignatories :: [PubKeyHash] -- ^ Signatures provided with the transaction, attested that they all signed the tx
, txInfoData :: [(DatumHash, Datum)]
, txInfoId :: TxId
-- ^ Hash of the pending transaction (excluding witnesses)
} deriving (Generic)
data ScriptContext = ScriptContext{scriptContextTxInfo :: TxInfo, scriptContextPurpose :: ScriptPurpose }
{-# INLINABLE findOwnInput #-}
-- | Find the input currently being validated.
findOwnInput :: ScriptContext -> Maybe TxInInfo
findOwnInput ScriptContext{scriptContextTxInfo=TxInfo{txInfoInputs}, scriptContextPurpose=Spending txOutRef} =
listToMaybe $ filter (\TxInInfo{txInInfoOutRef} -> txInInfoOutRef == txOutRef) txInfoInputs
findOwnInput _ = Nothing
{-# INLINABLE findDatum #-}
-- | Find the data corresponding to a data hash, if there is one
findDatum :: DatumHash -> TxInfo -> Maybe Datum
findDatum dsh TxInfo{txInfoData} = snd <$> find f txInfoData
where
f (dsh', _) = dsh' == dsh
{-# INLINABLE findDatumHash #-}
-- | Find the hash of a datum, if it is part of the pending transaction's
-- hashes
findDatumHash :: Datum -> TxInfo -> Maybe DatumHash
findDatumHash ds TxInfo{txInfoData} = fst <$> find f txInfoData
where
f (_, ds') = ds' == ds
{-# INLINABLE findTxInByTxOutRef #-}
findTxInByTxOutRef :: TxOutRef -> TxInfo -> Maybe TxInInfo
findTxInByTxOutRef outRef TxInfo{txInfoInputs} =
listToMaybe
$ filter (\TxInInfo{txInInfoOutRef} -> txInInfoOutRef == outRef) txInfoInputs
{-# INLINABLE findContinuingOutputs #-}
-- | Finds all the outputs that pay to the same script address that we are currently spending from, if any.
findContinuingOutputs :: ScriptContext -> [Integer]
findContinuingOutputs ctx | Just (TxInInfo{txInInfoResolved=TxOut{txOutAddress}}) <- findOwnInput ctx = findIndices (f txOutAddress) (txInfoOutputs $ scriptContextTxInfo ctx)
where
f addr TxOut{txOutAddress=otherAddress} = addr == otherAddress
findContinuingOutputs _ = Builtins.error()
{-# INLINABLE getContinuingOutputs #-}
getContinuingOutputs :: ScriptContext -> [TxOut]
getContinuingOutputs ctx | Just (TxInInfo{txInInfoResolved=TxOut{txOutAddress}}) <- findOwnInput ctx = filter (f txOutAddress) (txInfoOutputs $ scriptContextTxInfo ctx)
where
f addr TxOut{txOutAddress=otherAddress} = addr == otherAddress
getContinuingOutputs _ = Builtins.error()
{- Note [Hashes in validator scripts]
We need to deal with hashes of four different things in a validator script:
1. Transactions
2. Validator scripts
3. Data scripts
4. Redeemer scripts
The mockchain code in 'Ledger.Tx' only deals with the hashes of(1)
and (2), and uses the 'Ledger.Tx.TxId' and `Digest SHA256` types for
them.
In PLC validator scripts the situation is different: First, they need to work
with hashes of (1-4). Second, the `Digest SHA256` type is not available in PLC
- we have to represent all hashes as `ByteStrings`.
To ensure that we only compare hashes of the correct type inside a validator
script, we define a newtype for each of them, as well as functions for creating
them from the correct types in Haskell, and for comparing them (in
`Language.Plutus.Runtime.TH`).
-}
{-# INLINABLE scriptCurrencySymbol #-}
-- | The 'CurrencySymbol' of a 'MonetaryPolicy'
scriptCurrencySymbol :: MonetaryPolicy -> CurrencySymbol
scriptCurrencySymbol scrpt = let (MonetaryPolicyHash hsh) = monetaryPolicyHash scrpt in Value.currencySymbol hsh
{-# INLINABLE txSignedBy #-}
-- | Check if a transaction was signed by the given public key.
txSignedBy :: TxInfo -> PubKeyHash -> Bool
txSignedBy TxInfo{txInfoSignatories} k = case find ((==) k) txInfoSignatories of
Just _ -> True
Nothing -> False
{-# INLINABLE pubKeyOutput #-}
-- | Get the public key hash that locks the transaction output, if any.
pubKeyOutput :: TxOut -> Maybe PubKeyHash
pubKeyOutput TxOut{txOutAddress} = toPubKeyHash txOutAddress
{-# INLINABLE ownHashes #-}
-- | Get the validator and datum hashes of the output that is curently being validated
ownHashes :: ScriptContext -> (ValidatorHash, DatumHash)
ownHashes (findOwnInput -> Just (TxInInfo{txInInfoResolved=TxOut{txOutAddress=Address (ScriptCredential s) _, txOutDatumHash=Just dh}})) = (s,dh)
ownHashes _ = Builtins.error ()
{-# INLINABLE ownHash #-}
-- | Get the hash of the validator script that is currently being validated.
ownHash :: ScriptContext -> ValidatorHash
ownHash p = fst (ownHashes p)
{-# INLINABLE fromSymbol #-}
-- | Convert a 'CurrencySymbol' to a 'ValidatorHash'
fromSymbol :: CurrencySymbol -> ValidatorHash
fromSymbol (CurrencySymbol s) = ValidatorHash s
{-# INLINABLE scriptOutputsAt #-}
-- | Get the list of 'TxOut' outputs of the pending transaction at
-- a given script address.
scriptOutputsAt :: ValidatorHash -> TxInfo -> [(DatumHash, Value)]
scriptOutputsAt h p =
let flt TxOut{txOutDatumHash=Just ds, txOutAddress=Address (ScriptCredential s) _, txOutValue} | s == h = Just (ds, txOutValue)
flt _ = Nothing
in mapMaybe flt (txInfoOutputs p)
{-# INLINABLE valueLockedBy #-}
-- | Get the total value locked by the given validator in this transaction.
valueLockedBy :: TxInfo -> ValidatorHash -> Value
valueLockedBy ptx h =
let outputs = map snd (scriptOutputsAt h ptx)
in mconcat outputs
{-# INLINABLE pubKeyOutputsAt #-}
-- | Get the values paid to a public key address by a pending transaction.
pubKeyOutputsAt :: PubKeyHash -> TxInfo -> [Value]
pubKeyOutputsAt pk p =
let flt TxOut{txOutAddress = Address (PubKeyCredential pk') _, txOutValue} | pk == pk' = Just txOutValue
flt _ = Nothing
in mapMaybe flt (txInfoOutputs p)
{-# INLINABLE valuePaidTo #-}
-- | Get the total value paid to a public key address by a pending transaction.
valuePaidTo :: TxInfo -> PubKeyHash -> Value
valuePaidTo ptx pkh = mconcat (pubKeyOutputsAt pkh ptx)
{-# INLINABLE adaLockedBy #-}
-- | Get the total amount of 'Ada' locked by the given validator in this transaction.
adaLockedBy :: TxInfo -> ValidatorHash -> Ada
adaLockedBy ptx h = Ada.fromValue (valueLockedBy ptx h)
{-# INLINABLE signsTransaction #-}
-- | Check if the provided signature is the result of signing the pending
-- transaction (without witnesses) with the given public key.
signsTransaction :: Signature -> PubKey -> TxInfo -> Bool
signsTransaction (Signature sig) (PubKey (LedgerBytes pk)) (TxInfo{txInfoId=TxId h}) =
verifySignature pk h sig
{-# INLINABLE valueSpent #-}
-- | Get the total value of inputs spent by this transaction.
valueSpent :: TxInfo -> Value
valueSpent = foldMap (txOutValue . txInInfoResolved) . txInfoInputs
{-# INLINABLE valueProduced #-}
-- | Get the total value of outputs produced by this transaction.
valueProduced :: TxInfo -> Value
valueProduced = foldMap txOutValue . txInfoOutputs
{-# INLINABLE ownCurrencySymbol #-}
-- | The 'CurrencySymbol' of the current validator script.
ownCurrencySymbol :: ScriptContext -> CurrencySymbol
ownCurrencySymbol ScriptContext{scriptContextPurpose=Minting cs} = cs
ownCurrencySymbol _ = Builtins.error ()
{-# INLINABLE spendsOutput #-}
-- | Check if the pending transaction spends a specific transaction output
-- (identified by the hash of a transaction and an index into that
-- transactions' outputs)
spendsOutput :: TxInfo -> TxId -> Integer -> Bool
spendsOutput p h i =
let spendsOutRef inp =
let outRef = txInInfoOutRef inp
in h == txOutRefId outRef
&& i == txOutRefIdx outRef
in any spendsOutRef (txInfoInputs p)
makeLift ''TxInInfo
makeIsDataIndexed ''TxInInfo [('TxInInfo,0)]
makeLift ''TxInfo
makeIsDataIndexed ''TxInfo [('TxInfo,0)]
makeLift ''ScriptContext
makeIsDataIndexed ''ScriptContext [('ScriptContext,0)]
makeLift ''ScriptPurpose
makeIsDataIndexed ''ScriptPurpose
[ ('Minting,0)
, ('Spending,1)
, ('Rewarding,2)
, ('Certifying,3)
]