-
Notifications
You must be signed in to change notification settings - Fork 86
/
Initial.hs
198 lines (174 loc) · 6.39 KB
/
Initial.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
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -fno-specialize #-}
-- Avoid trace calls to be optimized away when inlining functions.
{-# OPTIONS_GHC -fplugin-opt PlutusTx.Plugin:no-simplifier-inline #-}
-- Plutus core version to compile to. In babbage era, that is Cardano protocol
-- version 7 and 8, only plutus-core version 1.0.0 is available.
{-# OPTIONS_GHC -fplugin-opt PlutusTx.Plugin:target-version=1.0.0 #-}
-- | The initial validator which allows participants to commit or abort.
module Hydra.Contract.Initial where
import PlutusTx.Prelude
import Hydra.Cardano.Api (PlutusScriptVersion (PlutusScriptV2))
import Hydra.Contract.Commit (Commit (..))
import qualified Hydra.Contract.Commit as Commit
import Hydra.Contract.Error (errorCode)
import Hydra.Contract.InitialError (InitialError (..))
import Hydra.Contract.Util (mustBurnST)
import Hydra.Plutus.Extras (ValidatorType, scriptValidatorHash, wrapValidator)
import Hydra.ScriptContext (
ScriptContext (..),
TxInfo (txInfoMint, txInfoSignatories),
findDatum,
findOwnInput,
findTxInByTxOutRef,
scriptOutputsAt,
valueLockedBy,
)
import PlutusCore.Core (plcVersion100)
import PlutusLedgerApi.Common (SerialisedScript, serialiseCompiledCode)
import PlutusLedgerApi.V1.Value (isZero)
import PlutusLedgerApi.V2 (
CurrencySymbol,
Datum (..),
FromData (fromBuiltinData),
OutputDatum (..),
PubKeyHash (getPubKeyHash),
Redeemer (Redeemer),
ScriptHash,
ToData (toBuiltinData),
TokenName (unTokenName),
TxInInfo (..),
TxOut (txOutValue),
TxOutRef,
Value (getValue),
)
import PlutusTx (CompiledCode)
import qualified PlutusTx
import qualified PlutusTx.AssocMap as AssocMap
import qualified PlutusTx.Builtins as Builtins
data InitialRedeemer
= ViaAbort
| ViaCommit
{ committedRefs :: [TxOutRef]
-- ^ Points to the committed Utxo.
}
PlutusTx.unstableMakeIsData ''InitialRedeemer
type DatumType = CurrencySymbol
type RedeemerType = InitialRedeemer
-- | The v_initial validator verifies that:
--
-- * spent in a transaction also consuming a v_head output
--
-- * ensures the committed value is recorded correctly in the output datum
--
-- * ensures that the transaction was signed by the key corresponding to the
-- PubKeyHash encoded in the participation token name
--
-- NOTE: It does not need to ensure that the participation token is of some
-- specific Head currency.
validator ::
-- | Hash of the commit validator
ScriptHash ->
DatumType ->
RedeemerType ->
ScriptContext ->
Bool
validator commitValidator headId red context =
case red of
ViaAbort ->
traceIfFalse
$(errorCode STNotBurned)
(mustBurnST (txInfoMint $ scriptContextTxInfo context) headId)
ViaCommit{committedRefs} ->
checkCommit commitValidator headId committedRefs context
checkCommit ::
-- | Hash of the commit validator
ScriptHash ->
-- | Head id
CurrencySymbol ->
[TxOutRef] ->
ScriptContext ->
Bool
checkCommit commitValidator headId committedRefs context =
checkCommittedValue
&& checkLockedCommit
&& checkHeadId
&& mustBeSignedByParticipant
&& mustNotMintOrBurn
where
checkCommittedValue =
traceIfFalse $(errorCode LockedValueDoesNotMatch) $
lockedValue == initialValue + committedValue
checkLockedCommit =
traceIfFalse $(errorCode MismatchCommittedTxOutInDatum) $
go (committedUTxO, lockedCommits)
where
go = \case
([], []) ->
True
([], (_ : _)) ->
traceError $(errorCode MissingCommittedTxOutInOutputDatum)
((_ : _), []) ->
traceError $(errorCode CommittedTxOutMissingInOutputDatum)
(TxInInfo{txInInfoOutRef, txInInfoResolved} : restCommitted, Commit{input, preSerializedOutput} : restCommits) ->
Builtins.serialiseData (toBuiltinData txInInfoResolved) == preSerializedOutput
&& txInInfoOutRef == input
&& go (restCommitted, restCommits)
checkHeadId =
traceIfFalse $(errorCode WrongHeadIdInCommitDatum) $
headId' == headId
mustBeSignedByParticipant =
traceIfFalse $(errorCode MissingOrInvalidCommitAuthor) $
unTokenName ourParticipationTokenName `elem` (getPubKeyHash <$> txInfoSignatories txInfo)
mustNotMintOrBurn =
traceIfFalse $(errorCode MintingOrBurningIsForbidden) $
isZero $
txInfoMint txInfo
ourParticipationTokenName =
case AssocMap.lookup headId (getValue initialValue) of
Nothing -> traceError $(errorCode CouldNotFindTheCorrectCurrencySymbolInTokens)
Just tokenMap ->
case AssocMap.toList tokenMap of
[(tk, q)] | q == 1 -> tk
_moreThanOneToken -> traceError $(errorCode MultipleHeadTokensOrMoreThan1PTsFound)
initialValue =
maybe mempty (txOutValue . txInInfoResolved) $ findOwnInput context
committedValue =
foldMap (txOutValue . txInInfoResolved) committedUTxO
committedUTxO = do
flip fmap committedRefs $ \ref ->
case findTxInByTxOutRef ref txInfo of
Nothing -> traceError $(errorCode OutRefNotFound)
Just txInInfo -> txInInfo
lockedValue = valueLockedBy txInfo commitValidator
(lockedCommits, headId') =
case scriptOutputsAt commitValidator txInfo of
[(dat, _)] ->
case dat of
NoOutputDatum -> traceError $(errorCode MissingDatum)
OutputDatum _ -> traceError $(errorCode UnexpectedInlineDatum)
OutputDatumHash dh ->
case findDatum dh txInfo of
Nothing -> traceError $(errorCode CouldNotFindDatum)
Just da ->
case fromBuiltinData @Commit.DatumType $ getDatum da of
Nothing -> traceError $(errorCode ExpectedCommitDatumTypeGotSomethingElse)
Just (_party, commits, hid) ->
(commits, hid)
_ -> traceError $(errorCode ExpectedSingleCommitOutput)
ScriptContext{scriptContextTxInfo = txInfo} = context
compiledValidator :: CompiledCode ValidatorType
compiledValidator =
$$(PlutusTx.compile [||wrap . validator||])
`PlutusTx.unsafeApplyCode` PlutusTx.liftCode plcVersion100 Commit.validatorHash
where
wrap = wrapValidator @DatumType @RedeemerType
validatorScript :: SerialisedScript
validatorScript = serialiseCompiledCode compiledValidator
validatorHash :: ScriptHash
validatorHash = scriptValidatorHash PlutusScriptV2 validatorScript
datum :: DatumType -> Datum
datum a = Datum (toBuiltinData a)
redeemer :: RedeemerType -> Redeemer
redeemer a = Redeemer (toBuiltinData a)