Skip to content

Commit 70f7b79

Browse files
author
euonymos
committed
chore: comments in the code, reformat
1 parent 64b662d commit 70f7b79

File tree

6 files changed

+34
-32
lines changed

6 files changed

+34
-32
lines changed

docs/getting_started.md

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -175,8 +175,7 @@ data ResolvedTx = MkResolvedTx
175175
, toMint :: TxMintValue BuildTx Era
176176
, interval :: Interval POSIXTime
177177
, additionalSigners :: [PubKeyHash]
178-
, -- FIXME
179-
signer :: ~(SigningKey PaymentKey)
178+
, signer :: ~(SigningKey PaymentKey)
180179
}
181180
deriving stock (Show, Eq)
182181

@@ -302,7 +301,7 @@ data TxConstraint (resolved :: Bool) script
302301
-- | Value being matched by its Spine
303302
(DSLPattern resolved script sop)
304303
-- | Case switch
305-
-- FIXME: might use function instead, will bring `_` syntax,
304+
-- TODO: might use function instead, will bring `_` syntax,
306305
-- reusing matched var and probably implicitly type-checking spine
307306
-- by saving it to such var DSL value
308307
(Map.Map (Spine sop) (TxConstraint resolved script))

example/CEM/Example/Auction.hs

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -16,8 +16,8 @@ data SimpleAuction
1616

1717
-- | A bid
1818
data Bid = MkBet
19-
{ bidder :: PubKeyHash -- FIXME: rename to bidder
20-
, bidAmount :: Integer -- FIXME: rename to bidder
19+
{ bidder :: PubKeyHash
20+
, bidAmount :: Integer
2121
}
2222
deriving stock (Prelude.Eq, Prelude.Show)
2323

@@ -128,14 +128,14 @@ instance CEMScript SimpleAuction where
128128
, byFlagError (lift False) "Another err"
129129
, -- Example: In constraints redundant for on-chain
130130
offchainOnly
131-
(if'
132-
(ctxParams.seller `eq'` buyoutBid.bidder)
133-
(signedBy ctxParams.seller)
134-
(spentBy
135-
buyoutBid.bidder
136-
(cMinLovelace @<> cMkAdaOnlyValue buyoutBid.bidAmount)
137-
cEmptyValue
138-
)
131+
( if'
132+
(ctxParams.seller `eq'` buyoutBid.bidder)
133+
(signedBy ctxParams.seller)
134+
( spentBy
135+
buyoutBid.bidder
136+
(cMinLovelace @<> cMkAdaOnlyValue buyoutBid.bidAmount)
137+
cEmptyValue
138+
)
139139
)
140140
, output
141141
(userUtxo buyoutBid.bidder) -- NOTE: initial zero bidder is seller
@@ -144,8 +144,8 @@ instance CEMScript SimpleAuction where
144144
(ctxParams.seller `eq'` buyoutBid.bidder)
145145
noop
146146
( output
147-
(userUtxo ctxParams.seller)
148-
(cMinLovelace @<> cMkAdaOnlyValue buyoutBid.bidAmount)
147+
(userUtxo ctxParams.seller)
148+
(cMinLovelace @<> cMkAdaOnlyValue buyoutBid.bidAmount)
149149
)
150150
]
151151
)

src/Cardano/CEM.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@ import Cardano.CEM.Address as X (
88
cemScriptPlutusCredential,
99
)
1010
import Cardano.CEM.Compile as X
11-
import Cardano.CEM.Documentation as X (genCemGraph)
1211
import Cardano.CEM.DSL as X (
1312
CEMScript (..),
1413
CEMScriptDatum,
@@ -17,6 +16,7 @@ import Cardano.CEM.DSL as X (
1716
RecordSetter ((::=)),
1817
TxConstraint,
1918
)
19+
import Cardano.CEM.Documentation as X (genCemGraph)
2020
import Cardano.CEM.Monads as X
2121
import Cardano.CEM.Monads.CLB as X
2222
import Cardano.CEM.OffChain as X

src/Cardano/CEM/DSL.hs

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -122,7 +122,7 @@ data ConstraintDSL script value where
122122
Proxy label ->
123123
ConstraintDSL script value
124124
-- | Builds a datatype value from the spine and field setters.
125-
-- Used in Utxo Out spec.
125+
-- Used in Utxo Out spec. Only specified fields are compared.
126126
UnsafeOfSpine ::
127127
forall script datatype spine.
128128
( spine ~ Spine datatype
@@ -173,7 +173,7 @@ instance Show (ConstraintDSL x y) where
173173
(GetField valueDsl proxyLabel) ->
174174
show valueDsl <> "." <> symbolVal proxyLabel
175175
Eq x y -> show x <> " @== " <> show y
176-
-- FIXME: add user annotations
176+
-- TODO: add user annotations
177177
LiftPlutarch _ x -> "somePlutarchCode (" <> show x <> ")"
178178
LiftPlutarch2 _ x y ->
179179
"somePlutarchCode (" <> show x <> ") (" <> show y <> ")"
@@ -346,9 +346,10 @@ class
346346
-- | The crux part - a map that defines constraints for each transition via DSL.
347347
transitionSpec :: CEMScriptSpec False script
348348

349-
-- | Optional Plutus script to calculate things, which can be used in the cases
350-
-- when CEM constraints and/or inlining Plutarch functions are not expressible
351-
-- enough.
349+
-- | Optional Plutus script to calculate a value of type
350+
-- (TransitionComp script), which can be used in the cases
351+
-- when CEM constraints and/or inlining Plutarch functions
352+
-- are not expressive enough.
352353
transitionComp ::
353354
Maybe
354355
( Params script ->
@@ -385,6 +386,7 @@ class CEMScriptTypes script where
385386
-- | See 'transitionComp'
386387
type TransitionComp script
387388

389+
-- | By default it's not set.
388390
type TransitionComp script = Void
389391

390392
-- | Options used for compiling.

src/Cardano/CEM/OffChain.hs

Lines changed: 11 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -118,7 +118,6 @@ queryScriptState params = do
118118
mTxInOut <- queryScriptTxInOut params
119119
return (cemTxOutState . snd =<< mTxInOut)
120120

121-
-- FIXME: doc, naming
122121
data OffchainTxIR
123122
= TxInR (TxIn, TxInWitness)
124123
| TxInRefR (TxIn, TxInWitness)
@@ -171,15 +170,16 @@ compileActionConstraints
171170
throwError CEMScriptTxInResolutionError
172171

173172
let
174-
-- FIXME: fromJust laziness trick
173+
-- TODO: fromJust laziness trick
175174
datum = (params, fromJust mState)
176175
compiled' = map (compileConstraint datum transition) uncompiled
177176

178-
-- FIXME: raise lefts from compiled
177+
-- NB: raise lefts from compiled
179178
let f x = case x of
180179
Left message -> throwError $ PerTransitionErrors [CompilationError message]
181180
Right x' -> return x'
182-
-- FIXME: add resolution logging
181+
182+
-- TODO: add resolution logging
183183
mapM f compiled'
184184

185185
process ::
@@ -194,7 +194,7 @@ process (MkCEMAction params transition) ec = case ec of
194194
utxo <- lift $ queryUtxo $ ByAddresses [pubKeyHashAddress $ user c]
195195
let utxoPairs =
196196
map (withKeyWitness . fst) $ Map.toList $ unUTxO utxo
197-
-- FIXME: do actuall coin selection
197+
-- TODO: do actuall coin selection
198198
return $ TxInR $ head utxoPairs
199199
c@(Utxo kind fanFilter value) -> do
200200
case kind of
@@ -213,7 +213,7 @@ process (MkCEMAction params transition) ec = case ec of
213213
map (addWittness . fst) $ filter predicate utxoPairs
214214
case matchingUtxos of
215215
x : _ -> return $ case someIn of
216-
-- FIXME: log/fail on >1 options to choose for script
216+
-- TODO: log/fail on >1 options to choose for script
217217
In -> TxInR x
218218
InRef -> TxInRefR x
219219
[] ->
@@ -222,7 +222,7 @@ process (MkCEMAction params transition) ec = case ec of
222222
predicate (_, txOut) =
223223
txOutValue txOut == fromPlutusValue value
224224
&& case fanFilter of
225-
-- FIXME: refactor DRY
225+
-- TODO: refactor DRY
226226
SameScript (MkSameScriptArg state) ->
227227
cemTxOutDatum txOut
228228
== Just
@@ -240,9 +240,10 @@ process (MkCEMAction params transition) ec = case ec of
240240
, state
241241
)
242242
)
243-
-- FIXME: understand what is happening
243+
244244
convertTxOut x =
245245
TxOutValueShelleyBased shelleyBasedEra $ toMaryValue x
246+
246247
addWittness = case fanFilter of
247248
UserAddress {} -> withKeyWitness
248249
SameScript {} -> (,scriptWitness)
@@ -315,7 +316,7 @@ awaitTx txId = do
315316
go 5
316317
where
317318
go :: Integer -> m ()
318-
go 0 = liftIO $ fail "Tx was not awaited." -- FIXME:
319+
go 0 = liftIO $ fail "Tx was not awaited."
319320
go n = do
320321
exists <- checkTxIdExists
321322
liftIO $ threadDelay 1_000_000
@@ -404,7 +405,7 @@ compileDsl datum@(params, state) transition dsl = case dsl of
404405
UnsafeUpdateOfSpine valueDsl _spine setters -> do
405406
case setters of
406407
[] -> recur valueDsl
407-
_ -> error "FIXME: not implemented"
408+
_ -> error "Not implemented yet."
408409
LiftPlutarch pterm argDsl -> do
409410
arg <- recur argDsl
410411
case evalTerm NoTracing $ pterm # pconstant arg of

src/Cardano/CEM/Smart.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -68,7 +68,7 @@ cOfSpine ::
6868
Spine datatype ->
6969
[RecordSetter (ConstraintDSL script) datatype] ->
7070
ConstraintDSL script datatype
71-
-- FIXME: should it be ordered?
71+
-- TODO: should it be ordered?
7272
cOfSpine spine setters =
7373
if toInteger (length setters) == toInteger (spineFieldsNum spine)
7474
then UnsafeOfSpine spine setters

0 commit comments

Comments
 (0)