Plutus.V1.Ledger.Examples
1. 📜 Overview
2. đź”§ LANGUAGE PRAGMAS AND IMPORTS
3. ⚙️ Example Scripts
3.1 âś… alwaysSucceedingNAryFunction
3.2 ❌ alwaysFailingNAryFunction
3.3 âž• summingFunction
3.4 đź§‚ saltFunction
4. 📚 Glossary
1 📜 Overview
This Plutus.V1.Ledger.Examples
module provides hand-crafted Plutus Core scripts for testing:
N‑ary scripts that always succeed or always fail, parameterized by the number of lambda arguments.
A simple addition script.
A salting wrapper to change a script’s hash without altering its behavior.
These functions produce SerializedScript
values suitable for exercise or regression tests and should never be used in production code.
2 đź”§ LANGUAGE PRAGMAS AND IMPORTS
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE StrictData #-} -- ensures no unexpected laziness
module Plutus.V1.Ledger.Examples (
alwaysSucceedingNAryFunction,
alwaysFailingNAryFunction,
summingFunction,
saltFunction
) where
import Codec.Serialise (serialise, deserialise)
import Data.ByteString.Lazy (toStrict, fromStrict)
import Data.ByteString.Short (toShort, fromShort)
import Numeric.Natural (Natural)
import Plutus.V1.Ledger.Api (SerializedScript)
import Plutus.V1.Ledger.Scripts qualified as Scripts
import PlutusCore qualified as PLC
import PlutusCore.MkPlc qualified as PLC
import UntypedPlutusCore qualified as UPLC
import Universe (Some(Some))
TypeApplications: for literal constants in
summingFunction
.StrictData: to avoid lazy fields in any data (though minimal here).
Imports for CBOR serialization, byte conversion, natural numbers, and Plutus Core.
3 ⚙️ Example Scripts
3.1 âś… alwaysSucceedingNAryFunction
alwaysSucceedingNAryFunction :: Natural -> SerializedScript
alwaysSucceedingNAryFunction n =
toShort . toStrict . serialise . Scripts.Script $
UPLC.Program () (PLC.defaultVersion ()) (body n)
where
body 0 = UPLC.LamAbs () (UPLC.DeBruijn 0) (UPLC.Var () (UPLC.DeBruijn 1))
body i = UPLC.LamAbs () (UPLC.DeBruijn 0) (body (i-1))
Inputs: arity
n :: Natural
.Processing: constructs an
n
‑argument lambda chain whose final body returns its first parameter, guaranteeing success.Output: serialized script that always succeeds when applied to
n
arguments.
Example:
let script1 = alwaysSucceedingNAryFunction 3
-- script1 expects 3 arguments; always returns the first one.
3.2 ❌ alwaysFailingNAryFunction
alwaysFailingNAryFunction :: Natural -> SerializedScript
alwaysFailingNAryFunction n =
toShort . toStrict . serialise . Scripts.Script $
UPLC.Program () (PLC.defaultVersion ()) (body n)
where
body 0 = UPLC.Error ()
body i = UPLC.LamAbs () (UPLC.DeBruijn 0) (body (i-1))
Inputs: arity
n :: Natural
.Processing: builds an
n
‑argument lambda chain ending inError
, so it always fails.Output: serialized script that throws an error regardless of arguments.
Example:
let scriptFail = alwaysFailingNAryFunction 1
-- scriptFail x == Error
3.3 âž• summingFunction
summingFunction :: SerializedScript
summingFunction = toShort . toStrict . serialise . Scripts.Script $
UPLC.Program () (PLC.defaultVersion ()) $
UPLC.Apply ()
(UPLC.Apply () (UPLC.Builtin () PLC.AddInteger)
(PLC.mkConstant @Integer () 1))
(PLC.mkConstant @Integer () 2)
Inputs: none.
Processing: applies the
AddInteger
builtin to the constants 1 and 2.Output: serialized script computing
1 + 2
.
Example:
-- When run, this script returns the integer 3.
3.4 đź§‚ saltFunction
saltFunction :: Integer -> SerializedScript -> SerializedScript
saltFunction salt b0 = toShort . toStrict . serialise . Scripts.Script $
UPLC.Program () version body
where
Scripts.Script (UPLC.Program () version b1) =
deserialise $ fromStrict $ fromShort b0
body = UPLC.Apply ()
(UPLC.LamAbs () (UPLC.DeBruijn 0) b1)
(UPLC.Constant () $ Some $ PLC.ValueOf PLC.DefaultUniInteger salt)
Inputs:
salt :: Integer
and existing scriptb0
.Processing: deserializes
b0
, wraps it with a new lambda accepting the salt, then applies it to the salt constant—preserving behavior but changing the hash.Output: new serialized script with different on-chain hash but identical core logic.
Example:
let salted = saltFunction 42 summingFunction
-- `salted` behaves like `summingFunction`, but with a different script hash.
4 📚 Glossary
SerializedScript: a
ShortByteString
representing a Plutus Core program.DeBruijn index: nameless variable representation by integer depth.
LamAbs: lambda abstraction in UPLC.
Error: runtime failure construct in UPLC.
Builtin: Plutus Core built‑in functions (e.g.,
AddInteger
).Script hash: ledger‑computed hash of serialized script; used for on‑chain references.
Salt: additional argument to change script hash without modifying logic.
Last updated