The Plutarch guide is your one-stop shop for getting up to speed on Plutarch!

Note: If you spot any mistakes/have any related questions that this guide lacks the answer to, please don't hesitate to raise an issue. The goal is to have high quality documentation for Plutarch users!

Aside: Not interested in the details? Skip straight to examples!

Overview

Haddock

Haddock documentation of plutus-core, plutus-ledger-api, plutus-tx, and few other upstream library with correctly matched version to latest Plutarch is available:

Go to Haddock

Compiling and Running

Introduction and Basic Syntax

The Introduction section serves as a introduction to Plutarch's basic concepts and core syntactic constructs. It will help build a mental model of Plutarch, but is insufficient to write production-ready code.

Practical Usage

The Usage section fills in the gaps left by the previous. It illustrates techniques that make Plutarch easier to work with.

Concepts

The Concepts section details additional concepts.

Typeclasses

The Typeclasses section discusses the primary typeclasses related to Plutarch.

Working with Types

The Types section discusses the core types of Plutarch.

Examples

Rules of thumb, Tips, and Tricks

Outside of the fundamental user guide, there are rules of thumb and general guidelines you can follow to improve your Plutarch experience. The Tricks section discusses ways of writing efficient and high quality Plutarch code, as well as rules that can help auditing Plutarch easier.

Common Issues and Troubleshooting

Due to the highly abstracted nature of Plutarch and its utilization of advanced type level concepts, you might face unfamiliar errors. Don't worry, the guide is here to help!

Useful Links

imports

module Plutarch.Docs.Introduction (hf) where
import Plutarch.Prelude

> Note: If you spot any mistakes/have any related questions that this guide lacks the answer to, please don't hesitate to raise an issue. The goal is to have high-quality documentation for Plutarch users!

Overview

Plutarch is an eDSL in Haskell for writing on-chain scripts for Cardano. With some caveats, Plutarch is a simply-typed lambda calculus (or STLC). Writing a script in Plutarch allows us to leverage the language features provided by Haskell while retaining the ability to compile to compact Untyped Plutus Core (or UPLC, which is an untyped lambda calculus).

When we talk about "Plutarch scripts," we are referring to values of type Term (s :: S) (a :: PType). Term is a newtype wrapper around a more complex type, the details of which Plutarch end-users can ignore. A Term is a typed lambda term; it can be thought of as representing a computation that, if successfully evaluated, will return a value of type a.

The two type variables of the Term s a declaration have particular kinds:

  • s :: S is like the s of ST s a. It represents the computation context in a manner that mimics mutable state while providing a familiar functional interface. Sections 1 through 4 of [1] give an accessible introduction to how this works. s is never instantiated with a concrete value; it is merely a type-level way to ensure that computational contexts remain properly encapsulated (i.e., different state threads don't interact). For more in-depth coverage of this and other eDSL design principles used in Plutarch, see [2].
  • a :: PType is short-hand for "Plutarch Type". We prefix these types with a capital P, such as PInteger, PBool, and so forth. Tagging a Term with a PType indicates the type of the Term's return value. Doing this allows us to bridge between the simple type system of Plutarch and the untyped UPLC.

Note that we should not think of a type of kind PType as carrying a value; it is a tag for a computation that may produce a value. For instance, the definition of PInteger is simply

data PInteger s

That is, there are no data constructors. If a value of type Term s PInteger successfully executes the computation within context s, the value computed will be an integer. We will never encounter values such as y :: PInteger; y = 3; they simply do not exist. While readers new to Plutarch may need some time to fit this into their mental model, it is a crucial distinction to keep in mind.

For brevity, we will say a "value of type Term s a will evaluate to (...)". This phrase will carry two implicit notions: one, that Term s a represents a computation executed in the context s; two, evaluating Term s a is not guaranteed to succeed.

In brief, when writing Plutarch scripts, we have a few tasks:

  • A.) Defining Plutarch Types (or PTypes). We prefix these types with a capital P, such as PInteger, PMaybe a, PBool, and so forth. As previously mentioned, these form the "tags" for Plutarch Term's, representing the type of the result of compiling and evaluating a Plutarch Script.
  • B.) Working with Plutarch Terms, which are values of the type Term (s :: S) (a :: PType). These are the Plutarch scripts themselves, from which we build up more complex scripts before compiling and executing them on-chain.
  • C.) Writing Haskell-level functions between Plutarch Terms (i.e., with types like Term s a -> Term s b). Doing so allows us to leverage Haskell's language features and ecosystem.
  • D.) Efficiently Converting the functions from (C.) to Plutarch-level functions, which are of the type Term s (a :--> b). We can directly convert the functions from (C.) to Plutarch-level functions at the most naive level using plam. Additional Plutarch utilities provide for optimization opportunities.
  • E.) Compiling and executing the functions from (D.), targeting UPLC for on-chain usage.

As a preview, the bridge Plutarch provides between Haskell and UPLC looks something like this:

------------------------------------------------------
|                  *Haskell World*                   |
------------------------------------------------------
| Values with types like `Bool`, `Integer`, `Maybe a`|
| and regular Haskell functions like a -> b          |
------------------------------------------------------
                           ^                     |
 (functions like `plift`)--|                     |--(functions like `pconstant` or `plam`)
                           |                     |
                           |                     v         (`pcon`)
-------------------------------------------------------    |                     -------------------------------------------------------
|                  *Plutarch Term World*              | <----------------------- |                  *Plutarch Type World*              |
-------------------------------------------------------                          -------------------------------------------------------
| STLC terms; constants like `Term s PInteger` and    | -----------------------> | Types like `PInteger`, `PMaybe a`                   |
| lambdas like `Term s (PInteger :--> PBool)`         |        |                 |                                                     |
-------------------------------------------------------        (`pmatch`)        -------------------------------------------------------
                              |
                              |
                              |--(`compile`)
                              |
                              |
                              v
-------------------------------------------------------
|                    *UPLC World*                     |
-------------------------------------------------------
| Untyped lambda calculus terms. Values of type `Data`|
|                                                     |
-------------------------------------------------------

Further, you may notice two general categories of functions in Plutarch: "Haskell-level" functions between terms, and "Plutarch-level" functions as lambda terms. By convention, we will prefix the Haskell-level functions with h and the Plutarch-level lambdas with p, for example

-- This example is listed here as a preview; the unfamiliar parts will
-- be detailed below.

-- A Plutarch-level lambda term
pf :: Term s (a :--> b :--> c)
pf = undefined

-- Recovering a Haskell level function from a Plutarch level function
hf :: Term s a -> Term s b -> Term s c
hf x y = pf # x # y

Note that pf is truly just a Plutarch Term and should not be treated specially.

The remainder of this document cover the bridge between Haskell and Plutarch at a high level. It will not cover all techniques necessary to write production-ready scripts. Nor will it cover the bridge between Plutarch and UPLC beyond the minimum. Nonetheless, it should provide sufficient background to prepare the reader for further study.

Sections:-

References

imports

module Plutarch.Docs.DelayAndForce (hif, pif') where 
import Plutarch.Prelude

Strictness and Laziness; Delayed Terms and Forcing

Plutarch, like UPLC, is strict by default; this is in contrast to Haskell, which is non-strict by default (often called "lazy"). This means that evaluating a function application in Plutarch (#) always evaluates the argument before executing the function.

This behavior may be undesirable. For example, it is usually unwanted to evaluate both the then and else branches of an if function, for efficiency reasons.

The Plutarch level function pif' is naturally strict in its arguments, so it does exactly that. For the purpose of this chapter we take pif' as a given, and create the lazy version pif based on that.

Note: The example below does not correspond to the actual implementations of pif or pif'. It is for pedagogic purposes only.

-- | Strict if-then-else.
pif' :: Term s (PBool :--> a :--> a :--> a)

To prevent evaluation of a term when it gets used as an argument in a function application, we can use pdelay to mark the argument term as delayed. On the type-level, it wraps the PType tag of a Term, as can be seen in its type signature.

pdelay :: Term s a -> Term s (PDelayed a)

The pforce function is the inverse to that, it converts a delayed term such that it gets evaluated when used in a function application (#). Forcing a term strips the PDelayed wrapper on the type-level:

pforce :: Term s (PDelayed a) -> Term s a

We now have the tools needed to create the lazy pif based on pif':

-- | Utilizing Haskell level functions with `pdelay` and `pforce` to have lazy wrapper around `pif`.
hif :: Term s PBool -> Term s a -> Term s a -> Term s a
hif cond whenTrue whenFalse = pforce $ pif' # cond # pdelay whenTrue # pdelay whenFalse

A word of caution: Calling pforce on the same delayed term in multiple different places can lead to duplicate evaluation of the term. Users familiar with Haskell's handling of laziness -- where forcing a thunk twice never duplicates computation -- should note that UPLC behaves differently.

Note that pdelay is not the only way to get lazy behavior. Haskell-level Term arguments, the branches of pmatch, and continuation functions on the Plutarch level are all naturally lazy.

imports

module Plutarch.Docs.PatternMatching (pisJust) where 
import Plutarch.Prelude

# Pattern matching constant `Term`s with `pmatch`.

We've shown how to construct Terms out of the data constructors of types with kind PType (i.e., pcon . PJust). Next, it is natural that we may want to pattern match on Term with a known PType tag (i.e., of a value with type Term s (PMaybe a)) to produce another Term (i.e., depending on whether the value matches PJust _ or Nothing.)

The function that we need is a method of the PMatch typeclass. For the time being, we will ignore the details of implementation and only look at the type:

pmatch :: 
  forall (a :: PType) (b :: PType) (s :: S).
  ( PlutusType a       -- `a` has to be a `PlutusType` instance. 
  ) => Term s a        -- Given a `Term` tagged with `a` and
  -> (a s -> Term s b) -- a continuation from `a s` to a Term s b`, 
  -> Term s b          -- produce a `Term s b`.

The annotation of the second argument deserves some focus; the second argument has its type displayed as (a s -> Term s b). First, recall that a is declared to have kind PType, and PType is a kind synonym for S -> Type. Thus, since s has kind S, we have that a s has the kind Type. That is, it is a regular Haskell type.

What this means, in practice, is that pmatch matches on the possible values of the result of evaluating a Term s a -- specifically, it matches on values of a type that has kind PType -- and branches accordingly. The second argument to pmatch is a continuation; it determines how the program continues once pmatch has done its work.

We have already introduced a type with kind PType suitable for branching: PMaybe. Here is an example:

{- | This function takes in a Haskell-level `PMaybe s` value (specifically, _not_ a `Term`)
     and returns a `Term` depending on the Haskell-level pattern match on `PMaybe`s data
     constructors.
-}
continuation :: PMaybe a s -> Term s PBool
continuation = \case
  PJust _ -> pcon PTrue
  PNothing -> pcon PFalse

{- | A Haskell-level `isJust` on Plutarch `Term`s. `pmatch` can match on
     the possibilities of `PJust _` or `PNothing` being the result of an evaluated
     `Term`.
-}
hisJust :: Term s (PMaybe a) -> Term s PBool
hisJust x = pmatch x continuation

-- | A Plutarch-level `isJust`
pisJust :: Term s (PMaybe a :--> PBool)
pisJust = plam hisJust

Readers should note that this is not the most ergonomic way to deal with pattern matching (Plutarch provides two versions of do syntax), but it is how the more ergonomic methods work under the hood.

Plutarch Terms

Plutarch Terms are terms in the sense of simply-typed lambda calculus terms. In a lambda calculus, we can construct terms as either "constants" or "lambdas," and terms can either be "open" (having free variables) or "closed" (having no free variables). We compose Plutarch Terms to build up increasingly complex computations. Once all free variables are eliminated from a Term (making it a Closed Term), we can compile it using the eponymous function from the Plutarch module:

-- | Closed term is a type synonym
type ClosedTerm (a :: PType) = forall (s :: S). Term s a

-- | Compile operates on closed terms to produce usable UPLC scripts.
compile :: ClosedTerm a -> Script

Terms are constructed from Haskell values and are tagged with PTypes.

imports

{-# LANGUAGE OverloadedStrings #-}
module Plutarch.Docs.PlutarchConstants (x, s, i, xd, hexs, justTerm, hPJustPInteger) where
import Plutarch.Prelude

# Plutarch Constant `Term`s

When evaluated, a constant Plutarch Term will always yield the same result. There are several ways of building constant Terms:

  • Statically building constant Terms from concrete Haskell values when we know the value at compile-time.
  • Dynamically building constant Terms from Haskell values, i.e. when the constant produced depends on a dynamic value.
  • Overloaded literal syntax
  • Helper functions

Static building of constant Terms with pconstant

If we know the desired value of a constant Term at compile-time, we can build the Term directly from Haskell synonyms. The function to do so is pconstant.

Constructing constants in this way utilizes the PLiftable typeclasses. These typeclasses expose the following associated type family:

type AsHaskell :: PType -> Type

pconstant takes a single argument: a regular Haskell type with a PLiftable instance, and yields a Plutarch term tagged with the corresponding Plutarch type. Note that you usually need to use type applications with pconstant as one Haskell type may have many Plutarch representations.

The relation between the Plutarch type and its Haskell synonym is established by the type family. For any Plutarch type p, AsHaskell p corresponds to the Haskell synonym.

For example:

-- | A Plutarch level boolean. Its value is "True", in this case.
x :: Term s PBool
x = pconstant True

You can also directly create a PAsData term using pconstantData:

-- | A Plutarch level boolean encoded as `Data`.
xd :: Term s (PAsData PBool)
xd = pconstantData True

Dynamic building of constant Terms with pcon

Sometimes the value that we want to treat as a constant Term is not known at compile time. To explain how to construct constants when we can only determine the value at runtime, we will examine the PMaybe Plutarch type. It can serve the same purpose as the Maybe type in Haskell: to represent the situation where computation may not produce a sensible result.

PMaybe has the following definition:

data PMaybe (a :: PType) (s :: S)
  = PJust (Term s a)
  | PNothing

and the following kind:

>>> :k PMaybe
PMaybe :: PType -> S -> Type

Let's dissect what this means.

  • PMaybe builds a PType from a PType; given a PType, we can tag a computation with the type PMaybe a to indicate that its return value should be semantically either Just a or Nothing. Such a tagging would look like a value with the type Term s (PMaybe a).
  • PJust and PNothing are data constructors. They are not tags. PJust :: Term s a -> PMaybe (a :: PType) (s :: S) is a helper to signify the concept of Just x. It contains a Plutarch term.

Now suppose that we want to carry around a constant Term in a Plutarch script that can be either PJust a or PNothing. To do so, we need a function to go from PJust a (which we can instantiate as a Haskell value, unlike PInteger) to a Term s (PMaybe a). This function is pcon:

-- pcon :: a s -> Term s a
-- For example:

x' :: Term s PInteger
x' = pconstant 3

justTerm :: Term s (PMaybe PInteger)
justTerm = pcon (PJust x')

These types deserve some explanation.

  • We are familiar by now with the type of x; it is a computation that returns a value that can be interpreted as a Haskell integer if evaluated successfully (in this case, 3).
  • The type of justTerm represents a computation tagged with the PMaybe PInteger type.

That is, if we ask justTerm what it will return when evaluated, it responds, "You should interpret the value I give you as either Nothing or Just Integer." Of course, we know that the result will always be Just 3; but this is the general mechanism to declare a function requiring a Maybe.

If you don't want to pretend to not know x during compile time, another example may be:

hPJustPInteger :: Term s PInteger -> Term s (PMaybe PInteger)
hPJustPInteger x = pcon (PJust x)

The pcon function is a method of the PCon typeclass.

Overloaded literals

pconstant and pcon are the long-form ways of building constants. Specific constant Haskell literals are overloaded to help construct Plutarch constants. We provide two examples below.

-- | A Plutarch level integer. Its value is 1, in this case.
i :: Term s PInteger
i = 1

-- | A Plutarch level string (this is actually `Text`). Its value is "foobar", in this case.
s :: Term s PString
s = "foobar"

Helper functions

Finally, Plutarch provides helper functions to build certain types of constants:

-- | A plutarch level bytestring. Its value is [65], in this case.
hexs :: Term s PByteString
hexs = phexByteStr "41"
-- ^ 'phexByteStr' interprets a hex string as a bytestring. 0x41 is 65 - of course.
imports

{-# LANGUAGE OverloadedStrings #-}
module Plutarch.Docs.PlutarchLambdas (pid, pid') where 
import Plutarch.Prelude

# Lambdas; Plutarch-level Function `Term`s.

Lambdas are the second form of Plutarch Terms. Lambda terms are represented at the type level by the infix type constructor :-->; a value of type Term s (a :--> b) evaluates to a function that takes a value of type a and produces a value of type b.

You can create Plutarch lambda Terms by applying the plam function to a Haskell-level function that works on Plutarch terms. The true type of plam itself is unimportant to end-users of Plutarch, but it should be thought of as

plam :: (Term s a -> Term s b) -> Term s (a :--> b)

To create the identity function as a Plutarch lambda, we would thus use:

-- | Haskell-level `id` function specialized to the `Term s a` type``
termId :: Term s a -> Term s a
termId x = x

-- | Plutarch-level `id` lambda
pid :: Term s (a :--> a)
pid = plam termId

-- | Equivalently:
pid' :: Term s (a :--> a)
pid' = plam $ \x -> x

Notice the type. A Plutarch lambda Term uses the :--> infix operator to encode a function type. So in the above case, pid is a Plutarch level function that takes a type a and returns the same type. As one would expect, :--> is right-associative, and things curry like a charm.

Guess what this Plutarch level function does:

f :: Term s (PInteger :--> PString :--> a :--> a)

It takes in an integer, a string, and a type a and returns the same type a. Notice that the types are all of kind PType. This means that when faced with filling out the gap:

f :: Term s (PInteger :--> PString :--> a :--> a)
f = plam $ \???

We know that the argument to plam here is a Haskell function g with type Term s PInteger -> Term s PString -> Term s a -> Term s a.

Function Application

Once we construct a Plutarch lambda Term using plam, it is rather useless unless we apply it to an argument. Plutarch provides two operators to do so

{- |
  High precedence infixl function application, to be used like
  function juxtaposition. e.g.:

  >>> f # x # y
  Conceptually: f x y
-}
(#) :: Term s (a :--> b) -> Term s a -> Term s b
infixl 8 #

{- |
  Low precedence infixr function application, to be used like
  `$`, in combination with `#`. e.g.:

  >>> f # x #$ g # y # z
  Conceptually: f x (g y z)
-}
(#$) :: Term s (a :--> b) -> Term s a -> Term s b
infixr 0 #$

The types of each operator match our intuition. Applying a lambda Term to a Term (tagged with the PType of the domain of the lambda) produces a Term (tagged with the PType of the codomain.).

Plutarch Types

When this guide uses the term "Plutarch Type" we explicitly talk about a type of kind PType. We will refer to " types of kind PType " simply as PTypes. We explicitly qualify when referring to the kind PType.

Note to beginners: Plutarch uses a language extension called DataKinds. This means that there are kinds beyond Type (aka *). We refer the read to [3] for an extended beginner-level introduction to these concepts if desired.

PType is defined as type PType = S -> Type; that is, it is a kind synonym for S -> Type (where S and Type are themselves kinds). This synonym is important to keep in mind because when querying the kind of something like PBool in, say, GHCi, we will not see PType as the kind. Instead, we get

ghci> :k PBool
PBool :: S -> Type

Thus, any time we see the kind S -> Type, we should mentally substitute its kind synonym PType. We reiterate: types of kind PType, should be considered as tags on computation. They do not represent types of values in the same way as standard Haskell types.

The kind of basic types such as Integer in Haskell has the kind: Type; the corresponding "basic" kind in Plutarch is simply PType. Higher-kinded types in Haskell, such as Maybe, will have kinds such as Type -> Type. In Plutarch, the corresponding kind is:

ghci> :k PMaybe
PMaybe :: PType -> S -> Type

Since the kind arrow -> is right-associative, we first read this as PMaybe :: PType -> (S -> Type); and since we know that that PType and S -> Type and synonyms, we read this as PMaybe :: PType -> PType, which should agree with our intuition.

The kind S -> Type is mysterious at first, but we recall that PTypes are tags on (unexecuted) computations indicating their result type. The S kind represents the computational context; thus, a PType expects to receive a computational context represented by a value s whose type has kind S that it will tag to produce a Type. Note that end-users never instantiate the value s with a concrete value; it is simply a type-level mechanism to maintain functional purity.

The above notion is essential to understanding why not all PTypes have data constructors; the data constructors are irrelevant, except insofar as they enable the implementation to keep track of Haskell-level and UPLC-level representations. PInteger is one such case; it is impossible to construct a constant y where y :: PInteger s. Other PTypes, such as PMaybe, do have data constructors (specifically PJust and PNothing), but still do not carry data from the viewpoint of UPLC. A value such as PNothing merely facilitates convenient term construction and deconstruction. When pcon sees PNothing, it knows it should build a UPLC constant that is morally equivalent to the concept of Nothing :: Maybe a.

In general, the concrete UPLC representations are connected to Plutarch types through their PlutusType implementation.

Also see: Figuring out the representation of a Plutarch type.

Untyped Plutus Core (UPLC)

Plutarch compiles to UPLC. Most Plutarch end-users will not need to concern themselves with the details of UPLC, but a brief overview will aid in building a mental model of how Plutarch works.

Unlike Haskell, UPLC is a low-level and untyped language implementing a basic lambda calculus. Consequently, it supports only a handful of built-in values and functions which may be strung together in lambda applications. The built-in types provided by UPLC include the usual primitive types -- integers, byte strings and strings, booleans, and so forth -- and a special Data value that can encode representations of arbitrary sum-of-products Haskell types.

While the semantic meaning of a Haskell type such as Maybe Integer is missing in UPLC, it still can be represented in UPLC through certain encodings. The aforementioned Data encoding can be used to represent arbitrary types in on-chain components such as Datum and Redeemers. On the other hand Scott Encoding can additionally encode function types but cannot be used in Datums or Redeemers. The key idea is that UPLC doesn't track what differentiates semantically distinct values, regardless of their encoding, and will not prevent a programmer from operating on the underlying representation in non-sensical ways.

Plutarch's solution is to tag scripts that compile to UPLC (i.e., Plutarch Terms) with types. Doing so allows the Plutarch compiler to track and type check operations on semantically distinct UPLC values. These tags are provided by "Plutarch Types", or "types of kind PType".

For the Plutarch compiler to bridge between arbitrary, semantically-rich Haskell types and the untyped values of UPLC, it is necessary to associate various bits of information with PTypes. On the one hand, each PType should have some semantic, type-level richness such as typeclass instances (otherwise, there would be little point in programming in Haskell!). On the other hand, each PType needs to have a UPLC representation, either as a built-in primitive value,Data, or as a Scott-encoded lambda, in order to compile to UPLC.

Looking to contribute to Plutarch? Looking for functionalities that are not currently provided by Plutarch from a safe interface? You've come to the right place!

Note: If you spot any mistakes/have any related questions that this guide lacks the answer to, please don't hesitate to raise an issue. The goal is to have high quality documentation for Plutarch developers!

Table of Contents

Code Style

You should generally follow the MLabs style guide, credit to @Koz Ross.

Discouraged Extensions

  • ImportQualifiedPost
  • RecordWildCards

Pre-commit checks

Remember to run ./bin/format to format your code and cabal test, alongside cabal test -f development, to make sure all the tests pass prior to making a PR!

Updating Changelog

If your PR makes a change to some user facing functionality - please summarize the change(s) and add it to CHANGELOG.md.

Targeting branch for PR

More often than not, you'll be making PRs directly to master.

However, sometimes, there is a release cycle going on and the state of the repository is in flux. There will usually be a master <- staging PR open during this time. As long as the staging PR is open, you should base most new branches on top of it and merge back into it. Bug fixes, for bugs present in master, are exempt from this requirement.

Concepts

Even if certain functionalities are absent from the public facing API - you can always implement them using functions like punsafeConstant and punsafeBuiltin - these allow you to walk the lines between Plutus core and Plutarch.

A general familiarity with Plutus core is important. You can learn all of that through the following documents:

Parts of the Pluto guide may also prove useful.

Plutus Core constants (UNSAFE)

NOTE: The following information is almost never necessary with the existence of pconstant. Refer to constant building and PLiftable section of the Plutarch user guide.

Often, you will need to build a Plutus core constant. You can do this using Some and ValueOf. Here's how pcon PTrue creates a Plutarch term that actually evaluates to a Plutus core constant representing a boolean:

import qualified PlutusCore as PLC

pcon' PTrue = punsafeConstant . PLC.Some $ PLC.ValueOf PLC.DefaultUniBool True
pcon' PFalse = punsafeConstant . PLC.Some $ PLC.ValueOf PLC.DefaultUniBool False

There's a lot to unpack here - but the general pattern is always the same. First step is to construct the Plutus core constant:

PLC.Some $ PLC.ValueOf PLC.DefaultUniBool True

The only parts that you will need to change when creating other constants, are the type and the value. Here the type is DefaultUniBool. This means the next argument must be a Bool. Ensured by the type system - don't you worry :)

You can glance at the other types in the default universe (what you will be working with). Can you guess how to make a Plutus core string from a Haskell string, and represent it as a Plutarch term?

import qualified Data.Text as Txt
import qualified PlutusCore as PLC

punsafeConstant . PLC.Some . PLC.ValueOf PLC.DefaultUniString . Txt.pack

(it's even pointfree!)

And that's essentially what the IsString implementation of Term s PString does. That is how your string literals end up as plutus core built in strings.

One more, how about something complex - DefaultUniProtoList. This is a builtin list. But what is the element type? Well, you'll have to specify that yourself! You use DefaultUniApply to "apply" a type (from the default universe) over DefaultUniProtoList:

import qualified PlutusCore as PLC

PLC.Some . PLC.ValueOf (PLC.DefaultUniProtoList `PLC.DefaultUniApply` PLC.DefaultUniInteger)

That right there converts a [Integer] into a Plutus core builtin list of builtin integers. Convenient!

Actually, there's a convenient pattern synonym for DefaultUniProtoList `DefaultUniApply` a- DefaultUniList a. Using that, you can simplify the above to:

PLC.Some . PLC.ValueOf (PLC.DefaultUniList PLC.DefaultUniInteger)

Note that you will have to provide the correct type annotations yourself, as punsafeConstant just infers to a Term s a. That's why it's unsafe! Make sure to provide the correct annotations when using this unsafe function:

foo :: Bool -> Term s PBool
foo = punsafeConstant . PLC.Some . PLC.ValueOf PLC.DefaultUniBool

Of course, we represent Plutus core booleans as Term s PBool in Plutarch - so that's its type!

Plutus core builtin functions

This is what you will be wrangling with the most. Builtin functions are going to be the foundation of everything you do. And the documentation on them is….. sparse.

You create Plutarch synonyms to Plutus core builtin functions using punsafeBuiltin. It creates a Plutarch level function from a Plutus core builtin functions.

Let's try making one, how about AddInteger?

import qualified PlutusCore as PLC

addI :: Term s (PInteger :--> PInteger :--> PInteger)
addI = punsafeBuiltin PLC.AddInteger

Just like punsafeConstant, you have to provide the right annotation yourself. We know that AddInteger takes two Plutus core builtin integers and returns another one. We represent these integers in Plutarch using PInteger terms - so there we go!

You can use and apply this Plutarch function just like any other.

Now here's where this goes off the rails, some builtin functions require forces to be used. These builtin functions have inherent polymorphic type variables. The number of times you need to force them, depends on the number of type variables they have.

Let's look at an example- HeadList. It's type can be thought of as - forall a. [a] -> a. It has one type variable, so it needs to be forced once:

pheadBuiltin :: Term s (PBuiltinList a :--> a)
pheadBuiltin = pforce $ punsafeBuiltin PLC.HeadList

We force a Plutarch term using pforce, recall that punsafeBuiltin returns a term. You need to type it all yourself of course. pforce doesn't mean you need to get rid of the type variable in your Plutarch level type. It'll still work with any a - the forcing just has to happen at call site.

You can sort of do this blindly, HeadList takes 1 force, so just pforce once. TailList also takes 1 force. ChooseList takes 2 forces (forall a b. [a] -> b -> b -> b). Here's how you would implement a Plutarch synonym for it:

pchooseList :: Term s (PBuiltinList a :--> b -> b -> b)
pchooseList = pforce $ pforce $ punsafeBuiltin PLC.ChooseList

Aside: You should also hoist the synonyms here that take one or more forces!

We have a Plutus Core builtin functions reference for everything you need to know about them. Including types, usage, and forcing.

Working with BuiltinData/Data/PData

Most of the time, you'll be working with BuiltinData/Data - this is the type of the arguments that will be passed onto your script from the outside. This is the type of the datum, the redeemer and the script context. This is also the type of arguments you will be able to pass to a Script.

Plutarch aims to hide these low level details from the user. Ideally, you will be using PDataSum/PDataList and PAsData - these are essentially just BuiltinData, but it is typed at the Plutarch level.

If you want to work with BuiltinData directly however, which you may have to do during developing Plutarch, you can find all that you need to know at Plutonomicon.

Lower Level Examples

Extracting txInfoInputs from ScriptContext manually (UNTYPED)

Here's a quick refresher on what ScriptContext looks like:

data ScriptContext = ScriptContext
  { scriptContextTxInfo :: TxInfo
  , scriptContextPurpose :: ScriptPurpose
  }

We are interested in txInfoInputs, which has type TxInInfo. It is the first field within TxInfo. If you have read Working with BuiltinData already - you know that a ScriptContext translates to a Data value similar to:

Constr 0 [PlutusTx.toData txInfo, PlutusTx.toData txPurpose]

Where txInfo and txPurpose are values of type TxInfo and ScriptPurpose respectively.

We are interested in that first field. That's easy, we do the following actions in sequence:

  • pasConstr - yields a PBuiltinPair PInteger (PBuiltinList PData). We know the constructor id is 0. It doesn't matter, there's only one constructor.
  • psndBuiltin - yields PBuiltinList PData, the second element of the pair. These are the fields within ScriptContext.
  • phead - yields PData, the first field. We know this is our TxInfo.

Combining that all up would give you:

import Plutarch.Prelude
import Plutarch.Builtin

f :: Term s (PData :--> PData)
f = plam $ \x -> phead #$ psndBuiltin #$ pasConstr # x

And if you test it with a mock context value, it does work:

{-# LANGUAGE OverloadedStrings #-}

import Plutus.V1.Ledger.Api
import Plutus.V1.Ledger.Interval
import qualified PlutusTx

mockCtx :: ScriptContext
mockCtx =
  ScriptContext
    (TxInfo
      [ TxInInfo
          (TxOutRef "" 1)
          (TxOut (Address (PubKeyCredential "0123") Nothing) mempty Nothing)
      ]
      mempty
      mempty
      mempty
      mempty
      mempty
      (interval (POSIXTime 1) (POSIXTime 2))
      mempty
      mempty
      ""
    )
    (Minting (CurrencySymbol ""))

>  f `evalWithArgsT` [PlutusTx.toData mockCtx]
Right (Program () (Version () 1 0 0) (Constant () (Some (ValueOf data (Constr 0 [List [Constr 0 [Constr 0 [Constr 0 [B ""],I 1],Constr 0 [Constr 0 [Constr 0 [B "\SOH#"],Constr 1 []],Map [],Constr 1 []]]],List [],Map [],Map [],List [],List [],Constr 0 [Constr 0 [Constr 1 [I 1],Constr 1 []],Constr 0 [Constr 1 [I 2],Constr 1 []]],List [],List [],Constr 0 [B ""]])))))

Aside: You can find the definition of evalWithArgsT above - Compiling and Running.

But we're not done yet! We want txInfoInputs. You may have noticed where exactly it is located on the above output. See that List …? Inside the outermost Constr's fields? That's our txInfoInputs!

Aside: Recall that List data values are simply wrappers around lists. Also recall that the fields in a Constr value must be all of type Data. So any of your list fields get translated to List data. Just remember not to confuse these with builtin lists (PBuiltinList)! Functions like pheadBuiltin don't work on List data values.

To obtain txInfoInputs from here, we do the following actions in sequence:

  • pasConstr - unpacks the TxInfo. There's only one constructor, TxInfo - we don't care about that. We need the fields.
  • psndBuiltin - extracts the second member of the pair, the fields of TxInfo.
  • phead - extracts the first element of the list. This is our field, txInfoInputs.
  • (optional) pasList - takes out the builtin list from the List data value.

And that's it! Putting it all together:

f :: Term s (PData :--> PBuiltinList PData)
f = plam $ \x ->
  let txInfo = phead #$ psndBuiltin #$ pasConstr # x
  in pasList #$ phead #$ psndBuiltin #$ pasConstr # txInfo

Trying it on the same mockCtx yields:

> f `evalWithArgsT` [PlutusTx.toData mockCtx]
Right (Program () (Version () 1 0 0) (Constant () (Some (ValueOf list (data) [Constr 0 [Constr 0 [Constr 0 [B ""],I 1],Constr 0 [Constr 0 [Constr 0 [B "\SOH#"],Constr 1 []],Map [],Constr 1 []]]]))))

Getting some of the boilerplate out of the way, this is what the value looks like:

Some
  (ValueOf list (data)
    [Constr 0
        [Constr 0 [Constr 0 [B ""],I 1],Constr 0 [Constr 0 [Constr 0 [B "\SOH#"],Constr 1 []],Map [],Constr 1 []]]
    ]
  )

There's just one element in txInfoInputs in this example, and there it is. Of course TxInInfo, the element type of this list, also gets translated to a Constr data with further fields. And that's what you see above.

Useful Links

How to build docs

To run the docs locally from the Git working copy (useful when editing them), from nix development shell,

# in plutarch-docs directory
mdbook serve .

When you add new file that is compilable, please run ./createSymlinks script. This will generate symbolic links to ./compilable directory which cabal will build. Don't forget to add the name of the module new file defines to plutarch-docs.cabal at other-modules section so that it will actually build.

To build the static HTML site,

mdbook build .

To run the docs directly without cloning the Git repo,

nix run github:Plutonomicon/plutarch#combined-docs
imports

module Plutarch.Docs.Run (applyArguments, evalT, evalSerialize, evalWithArgsT, evalWithArgsT') where
import Data.Bifunctor (first)
import Data.ByteString.Short (ShortByteString)
import Data.Text (Text, pack)
import Plutarch.Internal.Term (ClosedTerm, compile)
import Plutarch.Script (Script (unScript), serialiseScript)
import Plutarch.Evaluate (evalScript, applyArguments)
import PlutusLedgerApi.V1 (Data, ExBudget)
import UntypedPlutusCore (DeBruijn, DefaultFun, DefaultUni, Program)

This document describes how to compile and run Plutarch - whether for on chain deployment or off chain testing.

Note: If you spot any mistakes/have any related questions that this guide lacks the answer to, please don't hesitate to raise an issue. The goal is to have high quality documentation for Plutarch users!

Table of Contents

Common Extensions and GHC options

You generally want to adhere to the same extensions and GHC options the Plutarch repo uses.

List of GHC extensions
  • NoStarIsType
  • BangPatterns
  • BinaryLiterals
  • ConstrainedClassMethods
  • ConstraintKinds
  • DataKinds
  • DeriveAnyClass
  • DeriveDataTypeable
  • DeriveFoldable
  • DeriveFunctor
  • DeriveGeneric
  • DeriveLift
  • DeriveTraversable
  • DerivingStrategies
  • DerivingVia
  • DoAndIfThenElse
  • EmptyCase
  • EmptyDataDecls
  • EmptyDataDeriving
  • ExistentialQuantification
  • ExplicitForAll
  • FlexibleContexts
  • FlexibleInstances
  • ForeignFunctionInterface
  • GADTSyntax
  • GeneralisedNewtypeDeriving
  • HexFloatLiterals
  • ImplicitPrelude
  • InstanceSigs
  • KindSignatures
  • LambdaCase
  • MonomorphismRestriction
  • MultiParamTypeClasses
  • NamedFieldPuns
  • NamedWildCards
  • NumericUnderscores
  • OverloadedStrings
  • PartialTypeSignatures
  • PatternGuards
  • PolyKinds
  • PostfixOperators
  • RankNTypes
  • RelaxedPolyRec
  • ScopedTypeVariables
  • StandaloneDeriving
  • StandaloneKindSignatures
  • TraditionalRecordSyntax
  • TupleSections
  • TypeApplications
  • TypeFamilies
  • TypeOperators
  • TypeSynonymInstances
  • ViewPatterns

Evaluation

You can compile a Plutarch term using compile (from Plutarch module), making sure it has no free variables. compile returns a Script, which you can use as you would any other Plutus script.

For further insight into what is compiled - you can use Plutarch.Pretty.prettyTerm.

Note: You can pretty much ignore the UPLC types involved here. All it really means is that the result is a "UPLC program". When it's printed, it's pretty legible - especially for debugging purposes. Although not necessary to use Plutarch, you may find the Plutonomicon UPLC guide useful.

evalSerialize :: ClosedTerm a -> Either Text ShortByteString
evalSerialize x = serialiseScript . (\(a, _, _) -> a) <$> evalT x

evalT :: ClosedTerm a -> Either Text (Script, ExBudget, [Text])
evalT x = evalWithArgsT x []

evalWithArgsT :: ClosedTerm a -> [Data] -> Either Text (Script, ExBudget, [Text])
evalWithArgsT x args = do
  cmp <- compile mempty x
  let (escr, budg, trc) = evalScript $ applyArguments cmp args
  scr <- first (pack . show) escr
  pure (scr, budg, trc)

evalWithArgsT' :: ClosedTerm a -> [Data] -> Either Text (Program DeBruijn DefaultUni DefaultFun (), ExBudget, [Text])
evalWithArgsT' x args =
  (\(res, budg, trcs) -> (unScript res, budg, trcs))
    <$> evalWithArgsT x args

Note there might be utilities already in Plutarch that replaces above functions.

Note: If you spot any mistakes/have any related questions that this guide lacks the answer to, please don't hesitate to raise an issue. The goal is to have high quality documentation for Plutarch users!

Table of Contents

No instance for PUnsafeLiftDecl a

You should add PLift a to the context! PLift is just a synonym to PUnsafeLiftDecl.

Couldn't match representation of type: ... arising from the 'deriving' clause

If you're getting these errors when deriving typeclasses using the machinery provided by Plutarch (e.g. generic deriving of PlutusType) - it means you're missing a constructor import.

Infinite loop / Infinite AST

While may not be immediately obvious, things like the following are a no-go in Plutarch:

f :: Term s (PInteger :--> PInteger)
f = phoistAcyclic $ plam $ \n ->
  pif (n #== 0)
    0
    (n + f # (n - 1))

The issue here is that the AST is infinitely large. Plutarch will try to traverse this AST and will in the process not terminate, as there is no end to it. In these cases, consider using pfix.

Relevant issue: #19

Couldn't match type Plutarch.DataRepr.Internal.PUnLabel ... arising from a use of pfield, getField,

pletFields, hrecField (deprecated)

You might get some weird errors when using pfield/getField/pletFields like the above. Don't be scared! It just means that the type application you used is incorrect. Specifically, the type application names a non-existent field. Re-check the field name string you used in the type application for typos!

Expected a type, but "fieldName" has kind GHC.Types.Symbol

This just means the argument of a type application wasn't correctly promoted. Most likely arising from a usage of pletFields. In the case of pfield and getField, the argument of type application should have kind Symbol. A simple string literal representing the field name should work in this case. In the case of pletFields, the argument of type application should have kind [Symbol] - a type level list of types with kind Symbol. When you use a singleton list here, like ["foo"] - it's actually parsed as something of kind Type (like [a]).

All you need to do, is put a ' (quote) in front of the list, like so- @'["foo"]. This will promote the list constructor to the type level.

Lifting PAsData

Don't try to lift a PAsData term! It's intentionally blocked and partial. The PLift instance for PAsData is only there to make some important functionality work correctly. But the instance methods will simply error if used. Instead, you should either use pforgetData and plift that, or extract the Term s a out of Term s (PAsData a) using pfromData and plift that instead!

Type match errors when using pfield/getField (or OverloadedRecordDot, or hrecField(deprecated)) to access field

You might get nonsensical "Couldn't match type" errors when extracting fields. This has to do with GHC incorrectly inferring the return type. Field extraction is meant to be polymorphic in its return type in the sense that it might either return a Term s (PAsData p) term, or simply a Term s p (automatic pfromData). Unfortunately, sometimes this polymorphism makes it harder for GHC to infer the types. Also be aware that this automatic pfromData will infer PAsDatad terms more eagerly.

You can fix this by providing an explicit type annotation on the result of pfield or getField (or OverloadedRecordDot for field access). Otherwise, you can also explicitly use pfromData on the result. This will also help to make code more readable and is generally a good idea as plutarch validators and policies tend to get very long and consequently confusing without explicit type annotations on the bound terms.

Relevant issue: #275

imports

module Plutarch.Docs.BasicExample (fib) where

import Plutarch.Prelude

Basic examples demonstrating Plutarch usage.

Note: If you spot any mistakes/have any related questions that this guide lacks the answer to, please don't hesitate to raise an issue. The goal is to have high quality documentation for Plutarch users!

Aside: Be sure to check out Compiling and Running first!

Fibonacci number at given index

fib :: Term s (PInteger :--> PInteger)
fib = phoistAcyclic $
  pfix #$ plam $ \self n ->
    pif
      (n #== 0)
      0
      $ pif
        (n #== 1)
        1
        $ self # (n - 1) + self # (n - 2)

Execution:

> evalT $ fib # 2
Right (Program () (Version () 1 0 0) (Constant () (Some (ValueOf integer 2))))
imports

{-# LANGUAGE QualifiedDo #-}
{-# LANGUAGE OverloadedRecordDot #-}
module Plutarch.Docs.ValidatorExample (alwaysSucceeds, checkSignatory, res', res, alwaysFails) where

import Plutarch.Prelude
import Plutarch.LedgerApi.V3 (PDatum, PRedeemer, PScriptContext, PPubKeyHash,
  PScriptInfo(PSpendingScript))
import Plutarch.Docs.Run (evalWithArgsT)
import Plutarch.Script (Script)
import qualified PlutusTx
import PlutusCore.Evaluation.Machine.ExBudget (ExBudget)
import qualified Plutarch.Monadic as P
import Data.Text (Text)

Examples of validators and minting policies written in Plutarch.

Note: If you spot any mistakes/have any related questions that this guide lacks the answer to, please don't hesitate to raise an issue. The goal is to have high quality documentation for Plutarch users!

Aside: Be sure to check out Compiling and Running first!

Validator that always succeeds

alwaysSucceeds :: Term s (PAsData PDatum :--> PAsData PRedeemer :--> PAsData PScriptContext :--> PUnit)
alwaysSucceeds = plam $ \_datm _redm _ctx -> pconstant ()

All the arguments are ignored.

Execution:

res' :: Either Text (Script, ExBudget, [Text])
res' = alwaysSucceeds `evalWithArgsT` [PlutusTx.toData (), PlutusTx.toData (), PlutusTx.toData ()]
-- >>> res'
-- Right (Program () (Version () 1 0 0) (Constant () (Some (ValueOf unit ()))))

Validator that always fails

alwaysFails :: Term s (PAsData PDatum :--> PAsData PRedeemer :--> PAsData PScriptContext :--> PUnit)
alwaysFails = plam $ \_datm _redm _ctx -> perror

Similar to the example above.

Execution:

res :: Either Text (Script, ExBudget, [Text])
res = alwaysFails `evalWithArgsT` [PlutusTx.toData (), PlutusTx.toData (), PlutusTx.toData ()]
-- >>> res
-- Left (EvaluationError [] "(CekEvaluationFailure,Nothing)")

Validator that checks whether a value is present within signatories


checkSignatory :: Term s (PPubKeyHash :--> PAsData PDatum :--> PAsData PRedeemer :--> PAsData PScriptContext :--> PUnit)
checkSignatory = plam $ \ph _ _ ctx' -> P.do
  ctx <- pletFields @["txInfo", "scriptInfo"] ctx'
  PSpendingScript _ <- pmatch ctx.scriptInfo
  let signatories = pfield @"signatories" # ctx.txInfo
  pif
    (pelem # pdata ph # pfromData signatories)
    -- Success!
    (pconstant ())
    -- Signature not present.
    perror

Note: The above snippet uses GHC 9 features (QualifiedDo and OverloadedRecordDot). Be sure to check out Do syntax with TermCont and alternatives to OverloadedRecordDot.

We match on the script purpose to see if its actually for spending - and we get the signatories field from txInfo (the 7th field), check if the given pub key hash is present within the signatories and that's it!

It's important that we pass a PPubKeyHash prior to treating checkSignatory as a validator script.

{-# LANGUAGE OverloadedStrings #-}

import Plutus.V1.Ledger.Api
import Plutus.V1.Ledger.Interval
import qualified PlutusTx

hashStr :: PubKeyHash
hashStr = "abce0f123e"

pubKeyHash :: Term s PPubKeyHash
pubKeyHash = pconstant hashStr

mockCtx :: ScriptContext
mockCtx =
  ScriptContext
    (TxInfo
      mempty
      mempty
      mempty
      mempty
      mempty
      mempty
      (interval (POSIXTime 1) (POSIXTime 2))
      [fromString hashStr, "f013", "ab45"]
      mempty
      ""
    )
    (Spending (TxOutRef "" 1))

> evalWithArgsT (checkSignatory # pubKeyHash) [PlutusTx.toData (), PlutusTx.toData (), PlutusTx.toData mockCtx]
Right (Program () (Version () 1 0 0) (Constant () (Some (ValueOf unit ()))))

Using custom datum/redeemer in your Validator

All you have to do is implement PIsDataRepr and friends for your custom datum/redeemer and you can use it just like PScriptContext in your validators!

This section describes various concepts applicable in Plutarch.

Note: If you spot any mistakes/have any related questions that this guide lacks the answer to, please don't hesitate to raise an issue. The goal is to have high quality documentation for Plutarch users!

imports

{-# LANGUAGE RankNTypes #-}
module Plutarch.Docs.DataAndScottEncoding (nothing, just, foo) where

import Prelude (Integer, (+))

Data encoding and Scott encoding

In Plutus Core, there are really two (conflicting) ways to represent non-trivial ADTs: Constr data encoding, or Scott encoding. You should use only one of these representations for your non-trivial types.

Aside: What's a "trivial" type? The non-data builtin types! PInteger, PByteString, PBuiltinList, PBuiltinPair, and PMap (actually just a builtin list of builtin pairs). It's important to note that Data (Constr or otherwise) is also a builtin type.

Data encoding

Constr data is essentially a sum-of-products representation. However, it can only contain other Data values (not necessarily just Constr data, could be I data, B data etc.) as its fields. Plutus Core famously lacks the ability to represent functions using this encoding, and thus Constr encoded values simply cannot contain functions.

Note: You can find out more about the deep details of Data/BuiltinData at plutonomicon.

With that said, Data encoding is ubiquitous on the chain. It's the encoding used by the ledger api types, it's the type of the arguments that can be passed to a script on the chain etc. As a result, your datums and redeemers must use data encoding.

Scott encoding

On the opposite (and conflicting) end, is Scott encoding. The internet can explain Scott encoding way better than I can. But I'll be demonstrating Scott encoding with an example anyway.

Firstly, what good is Scott encoding? Well it doesn't share the limitation of not being able to contain functions! However, you cannot use Scott encoded types within, for example, your datums and redeemers.

Briefly, Scott encoding is a way to represent data with functions. The Scott encoded representation of Maybe a would be:

(a -> b) -> b -> b

Just 42, for example, would be represented as this function:

\f _ -> f 42

Whereas Nothing would be represented as this function:

\_ n -> n

We covered construction. What about usage/deconstruction? That's also just as simple. Let's say you have a function, foo :: Maybe Integer -> Integer, it takes in a Scott encoded Maybe Integer, and adds 42 to its Just value. If it's Nothing, it just returns 0.

type Maybe a = forall b. (a -> b) -> b -> b

just :: a -> Maybe a
just x = \f _ -> f x

nothing :: Maybe a
nothing = \_ n -> n

foo :: Maybe Integer -> Integer
foo mb = mb (\x -> x + 42) 0

How does that work? Recall that mb is really just a function. Here's how the application of f would work:

foo (just 1)
foo (\f _ -> f 1)
(\f _ -> f 1) (\x -> x + 42) 0
(\x -> x + 42) 1
43
foo nothing
foo (\_ n -> n)
(\_ n -> n) (\x -> x + 42) 0
0

Neat!

This is the same recipe followed in the implementation of PMaybe. See its PlutusType impl!

imports

{-# OPTIONS_GHC -Wno-redundant-constraints #-}
module Plutarch.Docs.PMatch (Tree(..), swap, TreeRepr) where
import Plutarch.Prelude
import Plutarch.Internal.PlutusType (PlutusType (pcon', pmatch'))
import Plutarch.Builtin (pforgetData, pasConstr, pconstrBuiltin)
import Plutarch.Unsafe (punsafeCoerce)

Generic programming over Plutarch types

Prerequisites

Term

A Term or ClosedTerm represents Plutus Lambda Calculus expression in Plutarch world. Allows for additional checks and safety compared to UPLC. See more: Plutarch Terms.

Data and Scott encoding

Datatypes can be encoded using Scott and Data encoding. These concepts are well explained in Plutonomicon: Data encoding and Scott encoding.

anyclass deriving strategy

anyclass derivation strategy uses default implementation of given typeclass to derive an instance of it. Usually depends that given datatype derives Generic typeclass also or some other too.

generics-sop

A really good introduction to generics-sop by the maker of the library, Andres Löh, can be found in this YouTube video recorded at the 2020 ZuriHac

Overall image of generics-sop package.

Introduction by srid.

Why is sum-of-products considered? It's very close to what developers think JSON is.

Generic representation of ADTs as sum of products, which can be automatically derived. Some commonly used types/functions:

I - Identity functor (`newtype I a = I a`)
K - Constant functor (`newtype K a b = K a`)

Z - zero (as in Peano numbers)
S - successor (as in Peano numbers)

<https://hackage.haskell.org/package/generics-sop-0.5.1.2/docs/Generics-SOP.html#t:NS>
NS - n-ary Sum
Picking nth element of sum comes from composing Z and S

<https://hackage.haskell.org/package/generics-sop-0.5.1.2/docs/Generics-SOP.html#t:NP>
NP - n-ary Product
Value level witness for a list of types parametrized by some functor f.

SOP - sum of products
`SOP I` corresponds to haskell's structure of given SOP encoded datatype.
`SOP (Term s)` corresponds to Plutarch structure of given SOP encoded datatype.

`Code a`
The code of a datatype.

This is a list of lists of its components. The outer list contains one element per constructor. The inner list contains one element per constructor argument (field).
data Tree = Leaf Int | Node Tree Tree

is supposed to have the following Representation:

type TreeRepr =
  '[ '[ Int ]
   , '[ Tree, Tree ]
   ]
-- Generic representation of given Haskell datatype
type Rep a = SOP I (Code a)

This mechanism allows for generic programming over Haskell types and Plutarch types

Intro

As Plutarch is an eDSL in Haskell, it does not allow us to work on Plutus-level variables directly. Manipulating ADTs can be done in terms of pcon and pmatch which belong to a class called PlutusType.

How this class is implemented is not that important but can be looked up in Plutarch/Internal/PlutusType.hs by the interested reader.

These typeclass methods could be written manually, but is a bit tedious and error-prone, thus the generic representation from GHC.Generics is used. Under the hood all necessary transformations are done to be able to access the data on Haskell level.

Also - as parsing data costs computation resources, it is common to pass tagged raw data until it's really needed to parse. PlutusType typeclass serves 2 purposes:

  1. Adds derivation via anyclass for Haskell ADTs
  2. Manipulates given S -> Type on its internal representation (provided as type PInner), rather than parsing/constructing the datatype back and forth.

Examples on how to derive PlutusType to either Data or Scott encoding:

data MyType (a :: S -> Type) (b :: S -> Type) (s :: S)
  = One (Term s a)
  | Two (Term s b)
  deriving stock Generic
  deriving anyclass PlutusType
instance DerivePlutusType (MyType a b) where type DPTStrat _ = PlutusTypeScott

-- If you instead want to use data encoding, you should derive 'PlutusType' and provide data strategy:

data MyTypeD (a :: S -> Type) (b :: S -> Type) (s :: S)
  = OneD (Term s (PDataRecord '[ "_0" ':= a ]))
  | TwoD (Term s (PDataRecord '[ "_0" ':= b ]))
  deriving stock Generic
  deriving anyclass PlutusType
instance DerivePlutusType (MyTypeD a b) where type DPTStrat _ = PlutusTypeData

-- Alternatively, you may derive 'PlutusType' by hand as well. A simple example, encoding a
-- Sum type as an Enum via PInteger:

data AB (s :: S) = A | B

instance PlutusType AB where
  type PInner AB = PInteger

  pcon' A = 0
  pcon' B = 1

  pmatch' x f =
    pif (x #== 0) (f A) (f B)


-- instead of using `pcon'` and `pmatch'` directly,
-- use 'pcon' and 'pmatch', to hide the `PInner` type:

swap :: Term s AB -> Term s AB
swap x = pmatch x $ \case
  A -> pcon B
  B -> pcon A

Maybe manually encoded in both ways:

-- | Scott
data PSMaybe a s = PSJust (Term s a) | PSNothing

-- | Newtype wrapper around function that represents Scott encoding,
-- | Plutarch uses generic one for deriving.
newtype ScottEncodedMaybe a b s = ScottEncodedMaybe (Term s ((a :--> b) :--> PDelayed b :--> b))

instance PlutusType (ScottEncodedMaybe a r) where
  type PInner (ScottEncodedMaybe a r) = (a :--> r) :--> PDelayed r :--> r
  pcon' (ScottEncodedMaybe x) = x
  pmatch' x f = f (ScottEncodedMaybe x)

instance PlutusType (PSMaybe a) where
  -- The resulting type of pattern matching on Maybe is quantified via `PForall`
  type PInner (PSMaybe a) = PForall (ScottEncodedMaybe a)
  pcon' (PSJust x) = pcon $ PForall $ pcon $ ScottEncodedMaybe $ plam $ \f _ -> f # x
  pcon' PSNothing = pcon $ PForall $ pcon $ ScottEncodedMaybe $ plam $ \_ g -> pforce g
  pmatch' x' f =
    pmatch x' $ \(PForall sem) ->
      pmatch sem $ \(ScottEncodedMaybe x) ->
        x # plam (f . PSJust) # pdelay (f PSNothing)

-- | Maybe encoded using Constr
data PMaybeData a (s :: S)
  = PDJust (Term s a)
  | PDNothing

-- | Note - thing hold in PMaybeData must be able to be represented as Data too, not needed in case of Scott version
instance PIsData a => PlutusType (PMaybeData a) where
  type PInner (PMaybeData a) = PData
  pcon' (PDJust x) = pforgetData $ pconstrBuiltin # 0 #$ psingleton # pforgetData (pdata x)
  pcon' PDNothing = pforgetData $ pconstrBuiltin # 1 # pnil
  pmatch' x f = (`runTermCont` f) $ do
    constrPair <- TermCont $ plet (pasConstr # x)
    indexNum <- TermCont $ plet (pfstBuiltin # constrPair)
    TermCont $ \g -> pif (indexNum #== 0)
        (g $ PDJust $ punsafeCoerce $ phead # (psndBuiltin # constrPair))
        (pif (indexNum #== 1)
          (g PDNothing)
          perror
        )

Generic derivation of PCon/PMatch

The mechanism of PlutusType derivation relies heavily on generic representation of ADT as sum-of-products. Very high level overview: For pmatch:

  • Scott encoding - for each sum branch, create a corresponding plam handler
  • Data encoding - for each sum branch, apply each element of list in Constr to a handler

For pcon:

  • Scott encoding - encode data type as lambda
  • Data encoding - create a Constr with corresponding number of constructor

Haskell synonym of Plutarch types

Several sections of the guide use the terminology "Haskell synonym". What does it mean? It's simply the Haskell type that is supposed to correspond to a Plutarch type. There doesn't necessarily have to be some sort of concrete connection (though there can be, using PLiftable) - it's merely a connection you can establish mentally.

This detail does come into play in concrete use cases though. After compiling your Plutarch code to a Script, when you pass Haskell data types as arguments to the Script - they obviously need to correspond to the actual arguments of the Plutarch code. For example, if the Plutarch code is a function taking PByteString, after compilation to Script, you should pass in the Haskell data type that actually shares the same representation as PByteString - the "Haskell synonym", so to speak. In this case, that's ByteString*.

[*]: You can't actually pass a ByteString into a compiled script. Notice that you can only pass Data arguments using applyArguments (from Plutarch.Evaluate). The Haskell synonym to Data is PAsData a (for any a), and PData.

Also see: Figuring out the representation of a Plutarch type.

imports

module Plutarch.Docs.Hoisting (hor, (#||)) where
import Plutarch.Prelude hiding ((#||))

Hoisting, metaprogramming, and fundamentals

Plutarch has a two-stage compilation process. First GHC compiles our code, then our code generates an AST of our Plutus script, which is then serialized using compile.

The important thing to note, is that when you have a definition like:

x :: Term s PInteger
x = something complex

Any use of x will inline the full definition of x. x + x will duplicate something complex in the AST. To avoid this, you should use plet in order to avoid duplicate work. Do note that this is strictly evaluated, and hence isn't always the best solution.

There is however still a problem: what about top-level functions like fib, sum, filter, and such? We can use plet to avoid duplicating the definition, but this is error-prone. To do this perfectly means that each function that generates part of the AST would need to have access to the plet'ed definitions, meaning that we'd likely have to put it into a record or typeclass.

To solve this problem, Plutarch supports hoisting. Hoisting only works for closed terms, that is, terms that don't reference any free variables (introduced by plam).

Hoisted terms are essentially moved to a top-level plet, i.e. it's essentially common sub-expression elimination. Do note that because of this, your hoisted term is also strictly evaluated, meaning that you shouldn't hoist non-lazy complex computations (use pdelay to avoid this).

In general, you should use phoistAcyclic on every top level function:

foo = phoistAcyclic $ plam $ \x -> <something complex>

As long as the Plutarch lambda you're hoisting does not have free variables (as Plutarch terms), you will be able to hoist it!

Hoisting Operators

For the sake of convenience, you often would want to use operators - which must be Haskell level functions. This is the case for +, -, #== and many more.

Choosing convenience over efficiency is difficult, but if you notice that your operator uses complex logic and may end up creating big terms - you can trivially factor out the logic into a Plutarch level function, hoist it, and simply apply that function within the operator.

Consider "boolean or":

hor :: Term s PBool -> Term s PBool -> Term s PBool
x `hor` y = pif x (pconstant True) $ pif y (pconstant True) $ pconstant False

You can factor out most of the logic to a Plutarch level function, and apply that in the operator definition:

(#||) :: Term s PBool -> Term s PBool -> Term s PBool
x #|| y = pforce $ por # x # pdelay y

por :: Term s (PBool :--> PDelayed PBool :--> PDelayed PBool)
por = phoistAcyclic $ plam $ \x y -> pif' # x # pdelay (pconstant True) # y

In general the pattern goes like this:

(<//>) :: Term s x -> Term s y -> Term s z
x <//> y = f # x # y

f :: Term s (x :--> y :--> z)
f = phoistAcyclic $ plam $ \x y -> <complex computation>

(OR, simply inlined)

(<//>) :: Term s x -> Term s y -> Term s z
x <//> y = (\f -> f # x # y) $ phoistAcyclic $ plam $ \x y -> <complex computation>

Note: You don't even need to export the Plutarch level function or anything! You can simply have that complex logic factored out into a hoisted, internal Plutarch function and everything will work just fine!

What is the s?

The s essentially represents the context, and is like the s of ST.

It's used to distinguish between closed and open terms:

  • Closed term: type ClosedTerm = forall s. Term s a
  • Arbitrary term: exists s. Term s a
  • NB: (exists s. Term s a) -> b is isomorphic to
  • forall s. Term s a -> b

This section describes the fundamental, commonly used Plutarch types.

Note: If you spot any mistakes/have any related questions that this guide lacks the answer to, please don't hesitate to raise an issue. The goal is to have high quality documentation for Plutarch users!

imports

module Plutarch.Docs.PAsData (fooData, fooConcrete) where 
import Plutarch.Prelude

PAsData

This is a typed way of representing BuiltinData/Data. It is highly encouraged you use PAsData to keep track of what "species" of Data value you actually have. Data can be a Constr (for sum of products - ADTs), Map (for wrapping assoc maps of Data to Data), List (for wrapping builtin lists of data), I (for wrapping builtin integers), and B (for wrapping builtin bytestrings).

Consider a function that takes in and returns a B data value - aka ByteString as a Data value. If you use the direct Plutarch synonym to Data - PData, you'd have:

fooData :: Term s (PData :--> PData)
fooData = undefined

That's not very informative - you have no way to ensure that you're actually working with B data values. You could use PAsData instead:

fooConcrete :: Term s (PAsData PByteString :--> PAsData PByteString)
fooConcrete = undefined

Now, you have assurance that you're working with a Data value that actually represents a builtin bytestring!

Wrapping and unwrapping to and from PAsData terms is provided by the PIsData typeclass. Specifically, by the functions- pfromData and pdata.

Some useful instances of these functions:

pfromData :: Term s (PAsData PInteger) -> Term s PInteger

pfromData :: Term s (PAsData PByteString) -> Term s PByteString

pfromData :: Term s (PAsData (PBuiltinList (PAsData a))) -> Term s (PBuiltinList (PAsData a))

pdata :: Term s PInteger -> Term s (PAsData PInteger)

pdata :: Term s PByteString -> Term s (PAsData PByteString)

pdata :: Term s (PBuiltinList (PAsData a)) -> Term s (PAsData (PBuiltinList (PAsData a)))

Note: using pfromData and pdata on builtin primitive types (such as PByteString, PInteger, ...) has an associated cost. Use them sparingly and try to use them only once if possible (i.e. if you used pfromData once, plet the result and reuse it.)

imports

module Plutarch.Docs.PBool (pTheAnswer) where
import Plutarch.Prelude

PBool

Plutarch level boolean terms can be constructed using pconstant True and pconstant False.

pTheAnswer :: forall s. Term s PInteger
pTheAnswer = pif (pconstant False) 7 42

You can combine Plutarch booleans terms using #&& and #||, which are synonyms to && and ||. These are Haskell level operators and therefore have short circuiting. If you don't need short circuiting, you can use the Plutarch level alternatives- pand' and por' respectively.

Note: Be aware that there's a difference between pif' and pif, the former of which is strict (i.e. it evaluates both br<anches eagerly), the latter of which is lazy. pif' will be a Plutarch level function, whereas pif is Haskell level.

This is synonymous to Plutus Core builtin boolean.

imports

{-# OPTIONS_GHC -Wno-redundant-constraints #-}
module Plutarch.Docs.PBuiltinList (validBuiltinList, listOfBs, matchOnList, matchOnList') where
import Plutarch.Prelude

PBuiltinList

You'll be using builtin lists quite a lot in Plutarch. PBuiltinList has a PListLike instance, giving you access to all the goodies from there! However, PBuiltinList can only contain builtin types. In particular, it cannot contain Plutarch functions (which also implies it cannot contain scott-encoded datatypes).

You can express the constraint of "only builtin types" using PLift, exported from Plutarch.Builtin-

validBuiltinList :: forall a s. PLiftable a => Term s (PBuiltinList a)
validBuiltinList = undefined

As mentioned before, PBuiltinList gets access to all the PListLike utilities. Other than that, PLift a => PBuiltinList a also has a PlutusType instance. You can construct a PBuiltinList using pcon (but you should prefer using pcons from PListLike):

listOfBs :: forall s. Term s (PBuiltinList (PAsData PByteString))
listOfBs = pcon $ PCons (pdata $ phexByteStr "fe") $ pcon PNil

would yield a PBuiltinList (PAsData PByteString) with one element - 0xfe. Of course, you could have done that with pcons # pdata (phexByteStr "fe") # pnil instead!

You can also use pmatch to match on a list:

matchOnList :: forall s. Term s PString
matchOnList = pmatch (pcon $ PCons (phexByteStr "fe") $ pcon PNil) $ \case
  PNil -> "hey hey there's nothing here!"
  PCons _ _ -> "oooo fancy!"

But you should prefer pelimList from PListLike instead:

matchOnList' :: forall s. Term s PString
matchOnList' = pelimList (\_ _ -> "oooo fancy") "hey hey there's nothing here!" $ pcon $ PCons (phexByteStr "fe") $ pcon PNil

The first argument is a function that is invoked for the PCons case, with the head and tail of the list as arguments.

The second argument is the value to return when the list is empty. It's only evaluated if the list is empty.

The final argument is, of course, the list itself.

Aside: Interested in the lower level details of PBuiltinList (i.e. Plutus Core builtin lists)? You can find all you need to know about it at Plutonomicon.

imports

module Plutarch.Docs.PBuiltinPair () where 
import Plutarch.Prelude ()

PBuiltinPair

Much like in the case of builtin lists, you'll just be working with builtin functions (or rather, Plutarch synonyms to builtin functions) here. You can find everything about that in builtin-pairs. Feel free to only read the Plutarch examples.

In particular, you can deconstruct PBuiltinPair using pfstBuiltin and psndBuiltin. You can build PBuiltinPair (PAsData a) (PAsData b) terms with ppairDataBuiltin:

ppairDataBuiltin :: Term s (PAsData a :--> PAsData b :--> PBuiltinPair (PAsData a) (PAsData b))
imports

module Plutarch.Docs.PByteString (notQuiteTheAnswer, aChar) where
import Plutarch.Prelude
import qualified Data.ByteString as BS

PByteString

Plutarch level bytestring terms can be created using phexByteStr and pconstant (pbyteStr is deprecated). phexByteStr interprets a hex string literal as a Term s PByteString and pconstant (pbyteStr) merely converts a ByteString into a Term s PByteString.

notQuiteTheAnswer :: forall s. Term s PByteString
notQuiteTheAnswer = phexByteStr "41"
-- yields a `Term s PByteString`, which represents [65]

aChar :: forall s. Term s PByteString
aChar = pconstant (BS.pack [91])
-- yields a `Term s PByteString`, which represents [91]

Similar to PString, it has a PEq instance. As well as Semigroup and Monoid instances for its terms.

It does not have a PlutusType instance.

This is synonymous to Plutus Core builtin bytestring.

imports

module Plutarch.Docs.PData () where
import Plutarch.Prelude ()

PData

This is a direct synonym to BuiltinData/Data. As such, it doesn't keep track of what "species" of Data it actually is. Is it an I data? Is it a B data? Nobody can tell for sure!

Consider using PAsData instead for simple cases, i.e. cases other than Constr.

Consider using PDataSum/PDataList instead when dealing with ADTs, i.e. Constr data values.

You can find more information about PData at Developers' Corner.

imports

module Plutarch.Docs.PDataSumAndRecord (Foo (..), test) where
import Plutarch.Prelude

PDataSum & PDataRecord

Plutarch sum and product types are represented using PDataSum and PDataRecord respectively. These types are crucial to the PIsDataRepr machinery.

Whenever you need to represent a non-trivial ADT using Data encoding, you'll likely be reaching for these.

More often than not, you'll be using PDataRecord. This is used to denote all the fields of a constructor:

newtype Foo (s :: S) = Foo (Term s (PDataRecord '["fooField" ':= PInteger]))

Foo is a Plutarch type with a single constructor with a single field, named fooField, of type PInteger. You can implement PlutusType via Data for it so that PAsData Foo is represented as a Constr encoded data value.

You can build PDataRecord terms using pdcons and pdnil. These are the familiar cons and nil but for PDataRecord terms.

pdcons :: forall label a l s. Term s (PAsData a :--> PDataRecord l :--> PDataRecord ((label ':= a) ': l))

pdnil :: forall s. Term s (PDataRecord '[])

To add an a to the PDataRecord term, you must have a PAsData a. The other type variable of interest, is label. This is just the name of the field you're adding. You can either use type application to specify the field, or use a type annotation, or let GHC match up the types.

Here's how you'd build a PDataRecord with two integer fields, one is named foo, the other is named bar:

test :: Term s (PDataRecord '[ "foo" ':= PInteger, "bar" ':= PInteger])
test = pdcons # pdata 7 #$ pdcons # pdata 42 # pdnil

PDataSum on the other hand, is more "free-standing". In particular, the following type:

PDataSum
  [ '[ "_0" ':= PInteger
     , "_1" ':= PByteString
     ]
  , '[ "myField" ':= PBool
     ]
  ]

represents a sum type with 2 constructors. The first constructor has two fields- _0, and _1, with types PInteger and PByteString respectively. The second constructor has one field- myField, with type PBool.

Note: It's convention to give names like _0, _1 etc. to fields that don't have a canonically meaningful name. They are merely the "0th field", "1st field" etc.

Note: The underlying datatype for PDataRecords and PDataSums are builtin list and constr + builtin lists respectively.

imports

module Plutarch.Docs.PInteger () where
import Plutarch.Prelude ()

PInteger

Term s PInteger has a convenient Num instance that allows you to construct Plutarch level integer terms from integer literals. It also means you have all the typical arithmetic operations available to you:

1 + 2

where 1 and 2 are Term s PIntegers.

Alongside Num, it also has a PIntegral instance, allowing you to use division, modulus etc.

It also has a PEq and POrd instance, allowing you to do Plutarch level equality and comparison.

It does not have a PlutusType instance.

Note: be aware that GHC offers constant folding, i.e. at compile time expressions like 3 * 20000 will be folded to their result. This is important because if you were to instead use the Plutarch level function, the evaluation would instead be delayed until plutarch runtime increasing the script cost.

This is synonymous to Plutus Core builtin integer.

imports

module Plutarch.Docs.PList (pFe, pFeElim, pFeList) where
import Plutarch.Prelude

PList

Here's the Scott encoded cousin of PBuiltinList. What does that mean? Well, in practice, it just means that PList can contain any arbitrary term - not just builtin types. PList also has a PListLike instance - so you won't be missing any of those utilities here!

PList also has a PlutusType instance. You can construct a PList using pcon (but you should prefer using pcons from PListLike):

pFeList :: forall s. Term s (PList PByteString)
pFeList = pcon $ PSCons (phexByteStr "fe") $ pcon PSNil

would yield a PList PByteString with one element - 0xfe. Of course, you could have done that with pcons # phexByteStr "fe" # pnil instead!

You can also use pmatch to match on a list:

pFe :: forall s. Term s PString
pFe = pmatch (pcon $ PSCons (phexByteStr "fe") $ pcon PSNil) $ \case
  PSNil -> "hey hey there's nothing here!"
  PSCons _ _ -> "oooo fancy!"

But you should prefer pelimList from PListLike instead:

pFeElim :: forall s. Term s PString
pFeElim = pelimList (\_ _ -> "oooo fancy") "hey hey there's nothing here!" $ pcon $ PSCons (phexByteStr "fe") $ pcon PSNil
imports

{-# LANGUAGE OverloadedStrings #-}

module Plutarch.Docs.PString (pfoo) where
import Plutarch.Prelude

PString

Term s PString has a IsString instance. This allows you to make Plutarch level string terms from regular string literals, provided you have OverloadedStrings turned on.

pfoo :: forall s. Term s PString
pfoo = "foo"

It also has a PEq instance. And its terms have Semigroup and Monoid instances - which work the way you would expect.

It does not have a PlutusType instance.

This is synonymous to Plutus Core builtin string (actually Text).

imports

module Plutarch.Docs.PUnit () where
import Plutarch.Prelude ()

PUnit

The Plutarch level unit term can be constructed using pconstant () or pcon PUnit.

This is synonymous to Plutus Core builtin unit.

This section describes the primary typeclasses used in Plutarch.

Note: If you spot any mistakes/have any related questions that this guide lacks the answer to, please don't hesitate to raise an issue. The goal is to have high quality documentation for Plutarch users!

PLiftable

Prerequisites

You should be familiar with PlutusType and what it does, as well as how to make instances of it. Furthermore, understanding how associated types and via-deriving works is required. Lastly, familiarity with higher-rank arguments is helpful, but not essential.

Introduction

A PlutusType instance specifies two capabilities:

  • Constructing a value by way of pcon; and
  • Matching on a value by way of pmatch

This is enough as long as we remain entirely in the Plutarch universe. However, we often need to interact with Plutus stuff more directly, and deal with equivalents to the types built-in to the Plutus default universe (Integer, for example), as well as types that operate via a Data encoding (such as most ledger stuff). We need to be able to create a 'bridge' between the world that Plutus understands (Haskell, essentially) and Plutarch.

PLiftable is designed to act as that bridge. If a type is an instance of PLiftable, we have the following:

  • A Haskell-level equivalent of this type
  • A way of transforming a value of the Haskell-level equivalent into a Plutarch term
  • A way of transforming a closed Plutarch term into a Haskell-level equivalent value (with the possibility of erroring)

The type class

PLiftable is defined as follows:

class PlutusType a => PLiftable (a :: S -> Type) where
    type AsHaskell a :: Type
    type PlutusRepr a :: Type
    toPlutarch :: forall (s :: S) . AsHaskell a -> PLifted a s
    toPlutarchRepr :: AsHaskell a -> PlutusRepr a
    fromPlutarch :: (forall (s :: S) . PLifted a s) -> Either LiftError (AsHaskell a)
    fromPlutarchRepr :: PlutusRepr a -> Maybe (AsHaskell a)

Even though we rarely need to interact with PLiftable and its methods directly, it is worth understanding what exactly this type class requires from its instances.

Firstly, we define an associated type AsHaskell, which determines the 'Haskell equivalent' of the Plutarch type a. We can see which is which by looking at the kinds involved: a has the kind S -> Type (meaning, 'Plutarch type'), while AsHaskell a has the kind Type (meaning, 'Haskell type'). We also note that any type with a PLiftable instance must also have a PlutusType instance; this is not surprising, as we need some way of operating on whatever we bring into Plutarch.

In general, AsHaskell a must either be a type directly in the Plutus default universe, or else a type which has a Data encoding. Nearly every case you are likely to see, or define, will be one of these two. As a result, we provide two helpers to derive such instances with less effort (further description of these will come later).

We also define two methods: one for moving from the 'Haskell world' into the 'Plutarch world', and another for the opposite direction. We note that the direction specified by toPlutarch is unconditional (cannot fail), whereas the direction specified by fromPlutarch is conditional (can fail). This is because a Plutarch term may represent a computation (valid or not), and to determine its Haskell-equivalent value, we must compile and evaluate the term, which could fail.

To fully grasp how these methods work, we need to examine two more types: the PLifted wrapper, and the LiftError type:

newtype PLifted (a :: S -> Type) (s :: S) = PLifted (Term s POpaque)

data LiftError
  = CouldNotEvaluate EvalError
  | TypeError BuiltinError
  | CouldNotCompile Text
  | CouldNotDecodeData

PLifted a s is an implementation detail needed to drive via-derivation. Whenever you see it, mentally substitute it for Term s a. Unless you plan to write PLiftable instances by hand, you will never need to interact with this type directly, or know anything about the distinction between PLifted a s and Term s a. LiftError on the other hand designates all the ways in which transforming a closed Plutarch term into its Haskell-level equivalent can fail:

  • The term does not compile
  • The evaluation of the term errors instead of giving a value
  • We attempt to transform into a type not part of the Plutus default universe
  • We evaluate to an invalid Data encoding

Once again, you almost never have to interact with this type directly unless manually specifying an instance of this type class. The main advantage of having a 'structured error type' here is debugging.

Defining an instance

Aside from the manual method, we provide two via-deriving helpers, for the two most common cases. We explain how to use each of them below. In almost all situations, one of the two via-deriving helpers is what you want to use.

Via DeriveBuiltinPLiftable

This helper is designed for types which have direct representations in Haskell using a type that's part of the default Plutus universe. An example of such a type is PInteger: Term s PInteger is meant to represent computations that result in an Integer (or an error), and Integers are part of the Plutus default universe. Indeed, if you attempt to use this helper with a Haskell type that isn't part of the default Plutus universe, you will get a compile error.

The type is defined as follows: its implementation is not important.

newtype DeriveBuiltinPLiftable (a :: S -> Type) (h :: Type) (s :: S)
  = DeriveBuiltinPLiftable (a s)

We can see that this newtype has two type arguments (besides the s to make it a Plutarch type): one for the Plutarch type for which we want to derive the instance, and one for a Haskell type that is meant to be its AsHaskell equivalent. As an example of how to use this helper, consider the following:

deriving via (DeriveBuiltinPLiftable PInteger Integer) 
    instance PLiftable PInteger

This specifies that PInteger's Haskell-level equivalent is Integer by way of its presence in the default Plutarch universe.

Via DeriveDataPLiftable

This helper is designed for types which are represented onchain by way of their Data encoding, rather than being part of the Plutus universe directly. An example of such a type is PScriptContext: its equivalent in Haskell is ScriptContext from plutus-ledger-api, which is essentially a 'skin' over Data.

This type is defined as follows: its implementation is not important.

newtype DeriveDataPLiftable (a :: S -> Type) (h :: Type) (s :: S)
  = DeriveDataPLiftable (a s)

Similarly to DeriveBuiltinPLiftable, we have two relevant type arguments: one for the Plutarch type for which we want to derive an instance, and another for its Haskell-level equivalent. As an example of how to use this helper, consider the following:

deriving via (DeriveDataPLiftable PScriptContext ScriptContext) 
    instance PLiftable PScriptContext

This declares that PScriptContext's Haskell-level equivalent is ScriptContext (from plutus-ledger-api), by way of its Data encoding.

There are additional requirements for using this helper with Plutarch type a and Haskell-level equivalent h. Aside from a being an instance of PlutusType, we also must have the following:

  • PInner a is PData (namely, construction and matching is actually carried out in a computation involving Data)
  • h is an instance of both ToData and FromData (namely, it has a Data encoding that we can decode from and encode into)

Via DeriveNewtypePLiftable

This helper is for types that have the same representation as some other type that already defined PLiftable. Instance defined that way will have the same PlutusRepr.

newtype PPositive s = PPositive (Term s PInteger)
  deriving stock (Generic)
  deriving anyclass (PlutusType, PIsData)

deriving via
  DeriveNewtypePLiftable PPositive PInteger Positive
  instance PLiftable PPositive

This defines that PPositive's Haskell-level equivalent is Positive and PPositive has the same representation as PInteger.

Implementation is not important but is useful to talk about its type parameters

newtype DeriveNewtypePLiftable (wrapper :: S -> Type) (inner :: S -> Type) (h :: Type) (s :: S)
  = DeriveNewtypePLiftable (wrapper s)

To use DeriveNewtypePLiftable the following must hold:

  • inner has PLiftable instance
  • AsHaskell inner is coercible to h

Manual derivation

In the (unlikely) case that your type fits neither of the above, you will have to write the instance manually. Given how unusual this situation is, we can't really give any general guidance as to how this should be done. Instead, we recommend examining the definitions of PLiftable, as well as the two derivation helpers described above, in the source code. Alternatively, reach out to us: we might be able to advise better.

Ensuring your instance is correct

Any instance of PLiftable must obey the following laws:

1. fromPlutarch . toPlutarch = Right
2. fmap toPlutarch . fromPlutarch = Right

If you use either of DeriveBuiltinPLiftable or DeriveDataPLiftable with via derivation, these laws will automatically be satisfied. If you write an instance manually, you will have to ensure this yourself. We provide a helper for testing that these laws hold in plutarch-testlib, in the Plutarch.Test.Laws module, called checkPLiftableLaws, which uses QuickCheck to verify that the laws are maintained. For example, to check that the instances for PLiftable PInteger and PLiftable PScriptContext are correct, we would write:

main :: IO ()
main = defaultMain . testGroup "Laws" $ [
    checkPLiftableLaws @PInteger,
    checkPLiftableLaws @PScriptContext
    ]

checkPLiftableLaws requires the use of a type argument, as it is otherwise ambiguous. It also works largely by way of AsHaskell, which means that the Haskell-level equivalent of the type being tested must be an instance of Arbitrary, Eq and Show, as well as Pretty. The name of the type being tested will automatically be added to the output of the test suite.

One important caveat to any definition of PLiftable instances, manual or not: ensure that the Haskell-level equivalent that you declare is genuine. While there is nothing stopping you from defining something like PLiftable PNatural with AsHaskell PNatural = Text, this is clearly not sensible, and we cannot check this. Your intent is taken at its word: the only checks are that what you want is not literally impossible. Keep this in mind when defining your instances.

Using an instance

To simplify the use of PLiftable, we provide two functions:

pconstant :: forall (a :: S -> Type) (s :: S) .
    PLiftable a =>
    AsHaskell a -> 
    Term s a

plift :: forall (a :: S -> Type) .
    PLiftable a => 
    (forall (s :: S) . Term s a) -> 
    AsHaskell a

The type signatures more-or-less speak for themselves: pconstant is the Haskell-to-Plutarch direction, while plift is the Plutarch-to-Haskell direction. There are three minor caveats to their use:

  • pconstant is technically ambiguous, as many different Plutarch types can share the same choice for AsHaskell. A good example is that PAsData PInteger and PInteger would have the same AsHaskell (namely, Integer). Thus, you may need to use a type argument to avoid ambiguity errors from the compiler.
  • plift transforms any LiftError into a call to error.
  • plift requires a rank-2 argument for the Plutarch term (to ensure it's closed). This can occasionally confuse the compiler's inference when combined with . or similar operators: consider either manually bracketing, or using ImpredicativeTypes.

These functions are the main interface enabled by PLiftable that you should use in your own code. plift is something that should be used fairly rarely outside of testing, however: as it requires compilation and evaluation, it will never be efficient.

imports

module Plutarch.Docs.PEqAndPOrd (PMaybe'(..)) where

import Plutarch.Prelude

PEq & POrd

Plutarch level equality is provided by the PEq typeclass:

class PEq t where
  (#==) :: Term s t -> Term s t -> Term s PBool

PInteger implements PEq as you would expect. So you could do:

1 #== 2

That would yield a Term s PBool, which you would probably use with pif (or similar).

Similarly, PPartialOrd (and POrd) emulates Ord: (where PPartialOrd represents partial orders and POrd represents total orders)

class PEq => PPartialOrd t where
  (#<) :: Term s t -> Term s t -> Term s PBool
  (#<=) :: Term s t -> Term s t -> Term s PBool

class PPartialOrd => POrd t

It works as you would expect:

pif (1 #< 7) "indeed" "what"

evaluates to "indeed" - of type Term s PString.

For scott encoded types, you can easily derive PEq via generic deriving:

data PMaybe' a s
  = PNothing'
  | PJust' (Term s a)
  deriving stock Generic
  deriving anyclass (PlutusType, PEq)
instance DerivePlutusType (PMaybe' a) where type DPTStrat _ = PlutusTypeScott

For data encoded types, you can derive PEq, PPartialOrd and POrd via there data representation:

newtype PTriplet a s
  = PTriplet
      ( Term
          s
          ( PDataRecord
              '[ "x" ':= a
               , "y" ':= a
               , "z" ':= a
               ]
          )
      )
  deriving stock Generic
  deriving anyclass (PlutusType, PEq, PPartialOrd)

instance DerivePlutusType (PTriplet a) where type DPTStrat _ = PlutusTypeData

Aside: PEq derivation for data encoded types uses "Data equality". It simply ensures the structure (as represented through data encoding) of both values are exactly the same. It does not take into account any custom PEq instances for the individual fields within.

PIntegral

This is similar to the Integral typeclass. However, it only has the following class methods:

  • pdiv - similar to div
  • pmod - similar to mod
  • pquot - similar to quot
  • prem - similar to rem

Using these functions, you can do division/modulus etc. on Plutarch level values:

pdiv # 6 # 3

where 6 and 3 are Term s PIntegers yields 2 - also a Term s PInteger.

PIsData

The PIsData typeclass facilitates easy and type safe conversion between Plutarch types and their corresponding BuiltinData/Data representation. It keeps track of the type information through PAsData.

class PIsData a where
  pfromData :: Term s (PAsData a) -> Term s a
  pdata :: Term s a -> Term s (PAsData a)

PInteger has a PIsData instance. The PData representation of PInteger is, of course, an I data. And you can get the PInteger back from an I data using UnIData (i.e. pasInt).

instance PIsData PInteger where
  pfromData x = pasInt # pforgetData x
  pdata x = punsafeBuiltin PLC.IData # x

In essence, pdata wraps a PInteger into an I data value. Whereas pfromData simply unwraps the I data value to get a PInteger.

Aside: You might be asking, what's an "I data value"? This is referring to the different constructors of Data/BuiltinData. You can find a full explanation of this at Plutonomicon.

For the simple constructors that merely wrap a builtin type into Data, e.g. Integers, Bytestrings, lists, and AssocMap, PIsData works in much the same way as above. However, what about Constr data values? When you have an ADT that doesn't correspond to those simple builtin types directly - but you still need to encode it as Data (e.g. PScriptContext). In this case, you should implement PIsDataRepr and you'll get the PIsData instance for free!

imports

{-# LANGUAGE QualifiedDo #-}
module Plutarch.Docs.PDataFields (foo, foo', res, mockCtx, purpose, Vehicle (..), PVehicle (..), PVehicle' (..), PFoo (..), test) where

import Plutarch.Prelude
import Plutarch.LedgerApi.V3 (
  PScriptContext,
  PScriptPurpose (PMinting),
  PScriptInfo (
    PSpendingScript,
    PMintingScript,
    PRewardingScript,
    PCertifyingScript,
    PVotingScript,
    PProposingScript
    ),
    PCurrencySymbol
  )
import Plutarch.DataRepr (PDataFields)
import qualified Plutarch.Monadic as P
import PlutusLedgerApi.V3 (
  TxInfo (TxInfo),
  POSIXTime(POSIXTime),
  ScriptContext (ScriptContext),
  ScriptInfo (MintingScript),
  Redeemer (Redeemer)
  )
import PlutusLedgerApi.V1.Value (CurrencySymbol (CurrencySymbol))
import PlutusLedgerApi.V1.Interval (interval)
import qualified PlutusTx
import qualified PlutusTx.AssocMap as AssocMap
import qualified PlutusTx.Builtins as Builtins
import Plutarch.Docs.Run (evalWithArgsT)

PlutusType via PlutusTypeData & PDataFields

Deriving PlutusType with DPTStrat PlutusTypeData allows for easily constructing and deconstructing Constr BuiltinData/Data values. It allows fully type safe matching on Data encoded values, without embedding type information within the generated script - unlike PlutusTx. PDataFields, on top of that, allows for ergonomic field access.

Aside: What's a Constr data value? Briefly, it's how Plutus Core encodes non-trivial ADTs into Data/BuiltinData. Together with BuiltinLists it allows for a sum-of-products encoding. Essentially, whenever you have a custom non-trivial ADT (that isn't just an integer, bytestring, string/text, list, or assoc map) - and you want to represent it as a data encoded value - you should derive PIsData for it

For example, PScriptContext - which is the Plutarch synonym to ScriptContext

  • has the necessary instances. This lets you easily keep track of its type, match on it, deconstruct it - you name it!
foo :: Term s (PScriptContext :--> PString)
foo = plam $ \ctx -> P.do
  scriptInfo <- pmatch $ pfield @"scriptInfo" # ctx
  case scriptInfo of
    PMintingScript _ -> "It's minting!"
    PSpendingScript _ -> "It's spending!"
    PRewardingScript _ -> "It's rewarding!"
    PCertifyingScript _ -> "It's certifying!"
    PVotingScript _ -> "It's voting!"
    PProposingScript _ -> "It's proposing!"

Note: The above snippet uses GHC 9 features (QualifiedDo). Be sure to check out Do syntax with TermCont.

Of course, just like ScriptContext - PScriptContext is represented as a Data value in Plutus Core. Plutarch just lets you keep track of the exact representation of it within the type system.

Here's how PScriptContext is defined:

newtype PScriptContext (s :: S)
  = PScriptContext
      ( Term
          s
          ( PDataRecord
              '[ "txInfo" ':= PTxInfo
               , "purpose" ':= PScriptPurpose
               ]
          )
      )

It's a constructor containing a PDataRecord term. It has 2 fields- txInfo and purpose.

First, we extract the purpose field using pfield @"purpose":

pfield :: Term s (PScriptContext :--> PScriptPurpose)

Note: When extracting several fields from the same variable, you should instead use pletFields. See: Extracting fields

Aside: pfield is actually return type polymorhpic. It could've returned either PAsData PScriptPurpose and PScriptPurpose. In this case, GHC correctly infers that we actually want a PScriptPurpose, since pmatch doesn't work on PAsData PScriptPurpose!

Sometimes GHC isn't so smart, and you're forced to provide an explicit type annotation. Or you can simply use pfromData $ pfield .....

Now, we can pmatch on our Term s PScriptPurpose to extract the Haskell ADT (PScriptPurpose s) out of the Plutarch term:

pmatch :: Term s PScriptPurpose -> (PScriptPurpose s -> Term s PString) -> Term s PString

Now that we have PScriptPurpose s, we can just case match on it! PScriptPurpose is defined as:

data PScriptPurpose (s :: S)
  = PMinting (Term s (PDataRecord '["_0" ':= PCurrencySymbol]))
  | PSpending (Term s (PDataRecord '["_0" ':= PTxOutRef]))
  | PRewarding (Term s (PDataRecord '["_0" ':= PStakingCredential]))
  | PCertifying (Term s (PDataRecord '["_0" ':= PDCert]))

It's just a Plutarch sum type.

We're not really interested in the fields (the PDataRecord term), so we just match on the constructor with the familiar case. Easy!

Let's pass in a ScriptContext as a Data value from Haskell to this Plutarch script and see if it works!

mockCtx :: ScriptContext
mockCtx =
  ScriptContext
    (TxInfo
      mempty -- inputs
      mempty -- reference inputs
      mempty -- outputs
      0 -- fee
      mempty -- mint
      mempty -- certs
      AssocMap.empty -- withdrawals
      (interval (POSIXTime 1) (POSIXTime 2)) -- valid range
      mempty -- signatories
      AssocMap.empty -- redeemers
      AssocMap.empty -- data
      "" -- id
      AssocMap.empty -- votes
      mempty -- proposal procedures
      Nothing -- current treasury amount
      Nothing -- current treasury donation
    )
    (Redeemer . Builtins.mkI $ 0)
    (MintingScript (CurrencySymbol ""))

res :: Either _ _
res = foo `evalWithArgsT` [PlutusTx.toData mockCtx]
-- Right (Program () (Version () 1 0 0) (Constant () (Some (ValueOf string "It's minting!"))))

Aside: You can find the definition of evalWithArgsT at Compiling and Running.

All about extracting fields

We caught a glimpse of field extraction in the example above, thanks to pfield. However, that barely touched the surface.

Once a type has a PDataFields instance, field extraction can be done with these 3 functions:

Each has its own purpose. However, pletFields is arguably the most general purpose and most efficient. Whenever you need to extract several fields from the same variable, you should use pletFields:

foo' :: Term s (PScriptContext :--> PUnit)
foo' = plam $ \ctx' -> P.do
  ctx <- pletFields @["txInfo", "scriptInfo"] ctx'
  let
    _scriptInfo = ctx.scriptInfo
    _txInfo = ctx.txInfo
  -- <use scriptInfo and txInfo here>
  pconstant ()

Note: The above snippet uses GHC 9 features (QualifiedDo and OverloadedRecordDot). Be sure to check out Do syntax with TermCont and alternatives to OverloadedRecordDot.

In essence, pletFields takes in a type level list of the field names that you want to access and a continuation function that takes in an HRec. This HRec is essentially a collection of the bound fields. You don't have to worry too much about the details of HRec. This particular usage has type:

pletFields :: Term s PScriptContext
  -> (HRec
        (BoundTerms
           '[ "txInfo" ':= PTxInfo, "purpose" ':= PScriptPurpose]
           '[ 'Bind, 'Bind]
           s)
      -> Term s PUnit)
  -> Term s PUnit

You can then access the fields on this HRec using OverloadedRecordDot.

Next up is pfield. You should only ever use this if you just want one field from a variable and no more. Its usage is simply pfield @"fieldName" # variable. You can, however, also use pletFields in this case (e.g. pletFields @'["fieldName"] variable). pletFields with a singular field has the same efficiency as pfield!

Finally, getField is merely there to supplement the lack of record dot syntax. See: Alternative to OverloadedRecordDot.

Note: An important thing to realize is that pfield and getField (or overloaded record dot on HRec) are return type polymorphic. They can return both PAsData Foo or Foo terms, depending on the surrounding context. This is very useful in the case of pmatch, as pmatch doesn't work on PAsData terms. So you can simply write pmatch $ pfield ... and pfield will correctly choose to unwrap the PAsData term.

Alternatives to OverloadedRecordDot

If OverloadedRecordDot is not available, you can also try using the record dot preprocessor plugin.

If you don't want to use either, you can simply use getField. In fact, ctx.purpose above just translates to getField @"purpose" ctx. Nothing magical there!

All about constructing data values

We learned about type safe matching (through PlutusType) as well as type safe field access (through PDataFields) - how about construction? You can derive PlutusType, using a data representation by using DPTStrat _ = PlutusTypeData and PlutusType bestows the ability to not only deconstruct, but also construct values - you can do that just as easily!

Let's see how we could build a PMinting PScriptPurpose given a PCurrencySymbol:

currSym :: Term s PCurrencySymbol
currSym = pconstant $ CurrencySymbol "foo"

purpose :: Term s PScriptPurpose
purpose = pcon $ PMinting fields
  where
    currSymDat :: Term _ (PAsData PCurrencySymbol)
    currSymDat = pdata currSym
    fields :: Term _ (PDataRecord '[ "_0" ':= PCurrencySymbol ])
    fields = pdcons # currSymDat # pdnil

All the type annotations are here to help!

This is just like regular pcon usage you've from PlutusType/PCon. It takes in the Haskell ADT of your Plutarch type and gives back a Plutarch term.

What's more interesting, is the fields binding. Recall that PMinting is a constructor with one argument, that argument is a PDataRecord term. In particular, we want: Term s (PDataRecord '["_0" ':= PCurrencySymbol ]). It encodes the exact type, position, and name of the field. So, all we have to do is create a PDataRecord term!

Of course, we do that using pdcons - which is just the familiar cons but for PDataRecord terms.

pdcons :: forall label a l s. Term s (PAsData a :--> PDataRecord l :--> PDataRecord ((label ':= a) ': l))

It takes a PAsData a and adds that a to the PDataRecord heterogenous list. We feed it a PAsData PCurrencySymbol term and pdnil - the empty data record. That should give us:

pdcons # currSymDat # pdnil :: Term _ (PDataRecord '[ label ':= PCurrencySymbol ])

Cool! Wait, what's label? It's the field name associated with the field, in our case, we want the field name to be _0 - because that's what the PMinting constructor wants. You can either specify the label with a type application or you can just have a type annotation for the binding (which is what we do here). Or you can let GHC try and match up the label with the surrounding environment!

Now that we have fields, we can use it with PMinting to build a PScriptPurpose s and feed it to pcon - we're done!

Implementing PIsData and friends

Implementing these is rather simple with generic deriving. All you need is a well formed type using PDataRecord. For example, suppose you wanted to implement PIsData for the Plutarch version of this Haskell type:

data Vehicle
  = FourWheeler Integer Integer Integer Integer
  | TwoWheeler Integer Integer
  | ImmovableBox

You'd declare the corresponding Plutarch type as:

data PVehicle' (s :: S)
  = PFourWheeler' (Term s (PDataRecord '["_0" ':= PInteger, "_1" ':= PInteger, "_2" ':= PInteger, "_3" ':= PInteger]))
  | PTwoWheeler' (Term s (PDataRecord '["_0" ':= PInteger, "_1" ':= PInteger]))
  | PImmovableBox' (Term s (PDataRecord '[]))

Each field type must also have a PIsData instance. We've fulfilled this criteria above as PInteger does indeed have a PIsData instance. However, think of PBuiltinLists, as an example. PBuiltinList's PIsData instance is restricted to only PAsData elements.

instance PIsData a => PIsData (PBuiltinList (PAsData a))

Thus, you can use PBuiltinList (PAsData PInteger) as a field type, but not PBuiltinList PInteger.

Note: The constructor ordering in PVehicle matters! If you used makeIsDataIndexed on Vehicle to assign an index to each constructor - the Plutarch type's constructors must follow the same indexing order.

In this case, PFourWheeler is at the 0th index, PTwoWheeler is at the 1st index, and PImmovableBox is at the 3rd index. Thus, the corresponding makeIsDataIndexed usage should be:

PlutusTx.makeIsDataIndexed ''PVehicle [('FourWheeler,0),('TwoWheeler,1),('ImmovableBox,2)]

Also see: Isomorphism between Haskell ADTs and PIsData

And you'd simply derive PlutustType with plutus data representation using generics. You can then also derive PIsData and if the dataype only has one ocnstructor PDataFields.

Furthermore, you can also derive the following typeclasses after deriving PlutusType with DPTStrat _ = PlutusTypeData

Combine all that, and you have:

data PVehicle (s :: S)
  = PFourWheeler (Term s (PDataRecord '["_0" ':= PInteger, "_1" ':= PInteger, "_2" ':= PInteger, "_3" ':= PInteger]))
  | PTwoWheeler (Term s (PDataRecord '["_0" ':= PInteger, "_1" ':= PInteger]))
  | PImmovableBox (Term s (PDataRecord '[]))
  deriving stock (Generic)
  deriving anyclass (PlutusType, PIsData)
instance DerivePlutusType PVehicle where type DPTStrat _ = PlutusTypeData

Note: You cannot derive PIsData for types that are represented using Scott encoding. Your types must be well formed and should be using PDataRecord terms instead.

That's it! Now you can represent PVehicle as a Data value, as well as deconstruct and access its fields super ergonomically. Let's try it!

test :: Term s (PVehicle :--> PInteger)
test = plam $ \veh' -> P.do
  veh <- pmatch veh'
  case veh of
    PFourWheeler fwh' -> P.do
      fwh <- pletFields @'["_0", "_1", "_2", "_3"] fwh'
      fwh._0 + fwh._1 + fwh._2 + fwh._3
    PTwoWheeler twh' -> P.do
      twh <- pletFields @'["_0", "_1"] twh'
      twh._0 + twh._1
    PImmovableBox _ -> 0

What about types with singular constructors? It's quite similar to the sum type case. Here's how it looks:

newtype PFoo (s :: S) = PMkFoo (Term s (PDataRecord '["foo" ':= PByteString]))
  deriving stock (Generic)
  deriving anyclass (PlutusType, PDataFields, PIsData)
instance DerivePlutusType PFoo where type DPTStrat _ = PlutusTypeData

Just an extra PDataFields derivation compared to the sum type usage!

imports

{-# OPTIONS_GHC -Wno-redundant-constraints #-}
module Plutarch.Docs.PListLike (pfoo, pfoo', x, x') where 
import Plutarch.Prelude

PListLike

The PListLike typeclass bestows beautiful and familiar list utilities to its instances. Plutarch has two list types- PBuiltinList and PList. Both have PListLike instances! However, PBuiltinList can only contain builtin types. That means that, for example, it cannot contain Plutarch functions. The element type of PBuiltinList can be constrained using PLift a => PBuiltinList a.

As long as it's a PLift a => PBuiltinList a or PList a - it has access to all the PListLike goodies, out of the box. It helps to look into some of these functions at Plutarch.List.

Along the way, you might be confronted by 2 big mean baddies ...err, constraints:

PIsListLike list a

This just means that the type list a, is indeed a valid PListLike containing valid elements! Of course, all PList as are valid PListLike, but we have to think about PBuiltinList since it can only contain PLift a => a elements! So, in essence a function declared as:

pfoo :: PIsListLike list a => Term s (list a :--> list a)
pfoo = undefined

when specialized to PBuiltinList, can be simplified as:

pfoo' :: PLiftable a => Term s (PBuiltinList a :--> PBuiltinList a)
pfoo' = undefined

That's all it is. Don't be scared of it!

What about this one:

PElemConstraint list a

This one ensures that the element type a can indeed be contained within the list type - list. For PList, this constraint means nothing - it's always true. For PBuiltinList, it can be simplified as PLift a. Easy!

Here's two of my favorite PListLike utilities (not biased):

-- | Cons an element onto an existing list.
pcons :: PElemConstraint list a => Term s (a :--> list a :--> list a)

-- | The empty list
pnil :: PElemConstraint list a => Term s (list a)

What would life be without cons and nil?

Let's build a PBuiltinList of PIntegers with that:

x :: Term s (PBuiltinList PInteger)
x = pcons # 1 #$ pcons # 2 #$ pcons # 3 # pnil

Wooo! Let's not leave PList alone in the corner though:

x' :: Term s (PList PInteger)
x' = pcons # 1 #$ pcons # 2 #$ pcons # 3 # pnil

The code is the same, we just changed the type annotation. Cool!

imports

{-# OPTIONS_GHC -Wno-redundant-constraints #-}
module Plutarch.Docs.PlutusTypePConAndPMatch (PMyType(..), PMyTypeData(..)) where
import Plutarch.Prelude

PlutusType

PlutusType is the primary typeclass that determines the underlying representation for a Plutarch type. It lets you construct and deconstruct Plutus Core constants from a Plutarch type's constructors (possibly containing other Plutarch terms).

NOTE: It's essentially a combination of PCon (for term construction) and PMatch (for term deconstruction). Nowadays, PCon and PMatch are actually both just an alias for PlutusType and you'll get a deprecation warning if you use them.

class PlutusType (a :: S -> Type) where
  {-
    snip
  -}
  pcon' :: forall s. a s -> Term s (PInner a)
  default pcon' :: DerivePlutusType a => forall s. a s -> Term s (PInner a)
  pcon' = let _ = witness (Proxy @(PlutusType a)) in derivedPCon

  pmatch' :: forall s b. Term s (PInner a) -> (a s -> Term s b) -> Term s b
  default pmatch' :: DerivePlutusType a => forall s b. Term s (PInner a) -> (a s -> Term s b) -> Term s b
  pmatch' = derivedPMatch

Note: You don't need to look too much into the types! After all, you'll be using pcon and pmatch, rather than pcon' and pmatch'. PInner is meant to represent the "inner" type of a - the Plutarch type representing the Plutus Core constant used to represent a.

You should always use pcon and pmatch instead of pcon' and pmatch' - these are provided by the PCon and PMatch typeclasses:

Another feature of PlutusType instances is that you can extract out the inner type of any PlutusType instance! Above, the inner type (or representation) of PMaybe was a function. You can use pto to safely take this inner type out-

pto :: Term s a -> Term s (PInner a)

This is quite useful when working with newtypes. Notice how PCurrencySymbol, for example, is simply a newtype to a PByteString. Its PInner is also PByteString. To be able to use functions that operate on PByteStrings with your PCurrencySymbol, you can simply take out the PByteString using pto!

Implementing PlutusType for your own types (Scott Encoding)

If you want to represent your data type with Scott encoding (and therefore don't need to make it Data encoded), you should simply derive it generically:

data PMyType (a :: S -> Type) (b :: S -> Type) (s :: S)
  = POne (Term s a)
  | PTwo (Term s b)
  deriving stock (Generic)
  deriving anyclass PlutusType

instance DerivePlutusType (PMyType a b) where type DPTStrat _ = PlutusTypeScott

NOTE: you can derive PlutusType for all types you defined a DerivePlutusType instance for. The strategy it uses is determined by the type that you put after DPTStrat _ =, in this case Scottencoding

Implementing PlutusType for your own types (Data Encoding)

If your type is supposed to be represented using Data encoding instead, you can derive PlutusType via PlutusTypeData:

data PMyTypeData (a :: S -> Type) (b :: S -> Type) (s :: S)
  = POneD (Term s (PDataRecord '[ "_0" ':= a ]))
  | PTwoD (Term s (PDataRecord '[ "_0" ':= b ]))
  deriving stock Generic
  deriving anyclass (PlutusType)

instance DerivePlutusType (PMyTypeData a b) where type DPTStrat _ = PlutusTypeData

Implementing PlutusType for your own types (newtype)

See: DPTStrat PlutusTypeNewtype.

imports

{-# LANGUAGE FlexibleInstances #-}
module Plutarch.Docs.PTryFrom (recoverListFromPData, theField, untrustedRecord, recoverListPartially, recoverAB) where 

import Plutarch.Prelude
import Plutarch.Builtin (pforgetData)

PTryFrom

class PTryFrom (a :: PType) (b :: PType) where
  type PTryFromExcess a b :: PType
  ptryFrom :: forall s r. Term s a -> ((Term s b, Reduce (PTryFromExcess a b s)) -> Term s r) -> Term s r

PTryFrom is a typeclass to prove equality between a type that in some way can't be trusted about its representation and another type that we want the untrusted type to be represented as. PTryFrom proves the structure of the untrusted type and recovers it as the trusted, type which hence also carries more information.

A good example is getting a PData from a redeemer and wanting to prove that it is of a certain kind, e.g. a PAsData (PBuiltinList (PAsData PInteger)). We could do this with:

recoverListFromPData :: forall (s :: S). Term s PData -> Term s (PAsData (PBuiltinList (PAsData PInteger)))
recoverListFromPData = unTermCont . fmap fst . tcont . ptryFrom @(PAsData (PBuiltinList (PAsData PInteger)))

Note: You can find a specialized version of ptryFrom in Plutarch.Extra that is the same as ptryFrom @PData @(PAsData a)

Implementing PTryFrom

Implementing PTryFrom for your type should be easy as soon as you have a datatype deriving its Plutarch data representation via PlutusTypeData as PTryFrom also has a generic default implementation.

-- your datatype
data PAB (s :: S)
  = PA (Term s (PDataRecord '["_0" ':= PInteger, "_1" ':= PByteString]))
  | PB (Term s (PDataRecord '["_0" ':= PBuiltinList (PAsData PInteger), "_1" ':= PByteString]))
  deriving stock (Generic)
  deriving anyclass (PlutusType, PIsData)

-- getting the generic `Data` representation for your type
instance DerivePlutusType PAB where type DPTStrat _ = PlutusTypeData
-- getting a generic `PTryFrom` instance that recovers your type 
-- from an opaque `PData`
instance PTryFrom PData (PAsData PAB)

-- a valid AB
sampleAB :: Term s (PAsData PAB)
sampleAB = pdata $ pcon $ PA (pdcons @"_0" # pdata (pconstant 4) #$ pdcons # pdata (pconstant "foo") # pdnil)

-- we forget the structure of our `sampleAB`
sampleABdata :: Term s PData
sampleABdata = pforgetData sampleAB

-- recovers an `AB` from an opaque `PData`
recoverAB :: Term s (PAsData PAB)
recoverAB = unTermCont $ fst <$> tcont (ptryFrom sampleABdata)

Note: There are other valid implementations for recovering your datatype from PData, in some cases you might, for example, want to include additional checks, think making sure that some PNatural is indeed positive. In this case you will have to hand-roll the implementation of PTryFrom. For some examples, see plutarch-test's PTryFromSpec.hs

Laws

  • the operation ptryFrom mustn't change the representation of the underlying data
  • the operation ptryFrom must always prove the integrity of the whole target type
    • example: ptryFrom @PData @(PAsData (PBuiltinList PData)) ssucceeds iff the underlying representation is a BuiltinList containing any PData
  • all conversions are fallible, this happens if the representation doesn't match the expected type.
  • the operation ptryFrom @a @b proves equality between the less expressive PType a and the more expressive PType b, hence the first element of the resulting Tuple must always be wrapped in PAsData if the origin type was PData (see law 1)
  • the result type b must always be safer than the origin type a, i.e. it must carry more information

Note: doing this in a manner that doesn't error would be really costly and hence we only offer a version that fails with perror.

PTryFromExcess

An important note is, that PTryFrom carries a type PTryFromExcess which safes data that arose as "excess" during the act of verifying. For PData (PAsData PSomething) instances this most times carries a PSomething, i.e. the type that has been proven equality for but without PAsData wrapper. In cases where this type is not useful, the excess type is just an empty HRec.

In case of the recovered type being a record or anything that contains a record, the excess type is more interesting: It contains an HRec, that has all the fields that have been recoverd and all their excess stored. If you recover a PAsData (PDataRecord xs) from PData, there is another field under the accessor "unwrapped" that contains the unwrapped record, which representation wise is just a PBuiltinList PData, of course.

Generally, when recovering a PDataRecord, the procedure is as follows

untrustedRecord :: Term s PData
untrustedRecord =
  let r :: Term s (PAsData (PDataRecord '["_0" ':= (PDataRecord '["_1" ':= PInteger])]))
      r = pdata $ pdcons # (pdata $ pdcons # pdata (pconstant 42) # pdnil) # pdnil
   in pforgetData r

-- obviously, `untrustedRecord` would be what we get from our untrusted party

theField :: Term s PInteger
theField = unTermCont $ do
  (_, exc) <- tcont (ptryFrom @(PAsData (PDataRecord '["_0" ':= (PDataRecord '["_1" ':= PInteger])])) untrustedRecord)
  pure $ snd (snd $ snd (snd exc)._0)._1

Because the record excess stores the field already in its unwrapped form, you don't have to pfromData it again.

If you don't use OverloadedRecordDot, there is an equivalent function getField (from GHC.Records) that does the same and works with type applications.

Recovering only partially

In case we don't want to verify the whole structure but rather part of it (this can be a reasonable decision to lower the fees), we can just leave the part of the data that is not to be verified a PData which serves as the base case:

recoverListPartially :: forall r s. Term s PData  -> ((Term s (PAsData (PBuiltinList PData)), Term s (PBuiltinList PData)) -> Term s r) -> Term s r
recoverListPartially = ptryFrom @(PAsData (PBuiltinList PData)) @PData

This is especially important with something like PDataSum which simply cannot store the excess types over the barrier of pmatch because obviously, you don't know the type of the excess before actually matching on it. The solution would be to recover an equivalent PDataSum whose constructors contain PData and after having matched on those, recover the underlying record or whatever field you're interested in. If you're not interested in the excess, you could of course also just recover the whole Sum without issue, in this case it won't be more expensive.

Please be aware, that nuances can already make a performance difference, e.g.

  • recovering ptryFromData @(PAsData (PBuiltinList PData)) is cheaper than ptryFromData @(PAsData (PBuiltinList (PAsData PDAta))) because the latter maps over no-ops, whereas the former just asserts that the PData indeed contains a PBuiltinList.
  • If you only, say, need the head of a list, first recovering a PAsData (PBuiltinList PData) (don't forget to use the excess instead of using pfromData), then using head and after that recovering the field in there will be cheaper than recovering the whole list with the target type and using head on that.

This section describes various core Plutarch usage concepts.

Note: If you spot any mistakes/have any related questions that this guide lacks the answer to, please don't hesitate to raise an issue. The goal is to have high quality documentation for Plutarch users!

imports

module Plutarch.Docs.UsePlet (pfoo, pfoo') where
import Plutarch.Prelude

plet to avoid work duplication

Sometimes, when writing Haskell level functions working on Plutarch terms, you may find yourself needing to re-use the Haskell level function's argument(s) multiple times:

pfoo :: forall s. Term s PString -> Term s PString
pfoo x = x <> x

In such cases, you should use plet on the argument to avoid duplicating work.

pfoo' :: forall s. Term s PString -> Term s PString
pfoo' x = plet x $ \x' -> x' <> x'
imports

module Plutarch.Docs.Conditionals (one) where 
import Plutarch.Prelude 

Conditionals

You can simulate if/then/else at the Plutarch level using pif:

pif :: Term s PBool -> Term s a -> Term s a -> Term s a

This has similar semantics to Haskell's if/then/else. That is, only the branch for which the predicate holds - is evaluated.

one :: forall s. Term s PInteger
one = pif (pconstant True) 1 2

The above evaluates to 1, which has type Term s PInteger.

imports

{-# OPTIONS_GHC -Wno-redundant-constraints #-}
{-# LANGUAGE StandaloneDeriving, FlexibleInstances #-}

module Plutarch.Docs.DerivingForNewtype (PPubKeyHash'(..), PPubKeyHash(..)) where
import Plutarch.Prelude
import Plutarch.Builtin (PDataNewtype)

Deriving typeclasses for newtypes

If you're defining a newtype to an existing Plutarch type, like so:

newtype PPubKeyHash' (s :: S) = PPubKeyHash' (Term s (PDataNewtype PByteString))

You ideally want to just have this newtype be represented as a PByteString under the hood. Therefore, all the typeclass instances of PByteString make sense for PPubKeyHash as well. In this case, you can simply derive all those typeclasses for your PPubKeyHash type as well:

newtype PPubKeyHash (s :: S) = PPubKeyHash (Term s (PDataNewtype PByteString))
  deriving stock (Generic)
  deriving anyclass (PlutusType, PIsData, PEq, PPartialOrd, POrd, PShow)
instance DerivePlutusType PPubKeyHash where type DPTStrat _ = PlutusTypeNewtype

Note: It's important to note that the content of a newtype that aims to be a Plutarch type (i.e. can be represented as a Plutarch term), must also be a Plutarch term. The type PByteString s simply doesn't exist in the Plutus Core world after compilation. It's all just Terms. So, when you say Term s PPubKeyHash, you're really just describing a Term s PByteString under the hood - since that's what it is during runtime.

Aside: You can access the inner type using pto (assuming it's a PlutusType instance). For example, pto x, where x :: Term s PPubKeyHash, would give you Term s PByteString. pto converts a PlutusType term to its inner type. This is very useful, for example, when you need to use a function that operates on bytestring terms, but all you have is a Term s PPubKeyHash. You know it's literally a bytestring under the hood anyway - but how do you obtain that? Using pto!

Currently, DerivePNewtype lets you derive the following typeclasses for your Plutarch types:

  • PEq
  • PIntegral
  • PIsData
  • PNum
  • POrd
  • PPartialOrd
  • PShow
  • PlutusType

Note: You cannot derive instances for Terms anymore because of coherence issues with the previous solutions. All derivations have to be done for the PlutusType (e.g. you cannot newtype derive Semigroup for PPubKeyHash anymore)

imports

module Plutarch.Docs.DerivingGenerics (PMyType (..)) where
import Plutarch.Prelude

Deriving typeclasses with generics

Plutarch also provides sophisticated generic deriving support for completely custom types. In particular, you can easily derive PlutusType for your own type:

data PMyType (a :: S -> Type) (b :: S -> Type) (s :: S)
  = POne (Term s a)
  | PTwo (Term s b)
  deriving stock Generic
  deriving anyclass PlutusType
instance DerivePlutusType (PMyType a b) where type DPTStrat _ = PlutusTypeScott

Note: This requires the generics-sop package.

This will use a Scott encoding representation for MyType, which is typically what you want. If you want to use data encoding representation instead in your PlutusType instance - you should derive it using PlutusTypeData. Check out: implementing PIsDataRepr and friends

Currently, generic deriving supports the following typeclasses:

imports

{-# LANGUAGE QualifiedDo #-}

module Plutarch.Docs.QDo (f) where
import Plutarch.LedgerApi.V3 (PScriptPurpose (PSpending))
import qualified Plutarch.Monadic as P
import Plutarch.Prelude

Do syntax with QualifiedDo and Plutarch.Monadic

In ghc92+ we can use do notation without using the Monad instances for some type by using overloaded syntax. This overloaded syntax is provided by the -XQualifiedDo extension

The Plutarch.Monadic module exports >>=, >>, and fail functions suitable to be used with QualifiedDo.

f :: Term s (PScriptPurpose :--> PUnit)
f = plam $ \x -> P.do
  PSpending _ <- pmatch x
  ptraceInfo "matched spending script purpose"
  pconstant ()

In essence, P.do { x; y } simply translates to x y; where x :: a -> Term s b and y :: a.

Similarly, P.do { y <- x; z } translates to x $ \case { y -> z; _ -> ptraceError <msg> }; where x :: (a -> Term s b) -> Term s b, y :: a, and z :: Term s b. Of course, if y is a fully exhaustive pattern match (e.g. singular constructor), the extra _ -> ptraceError <msg> case will not be generated at all and you'd simply get x $ \y -> z.

Note: if a pattern match fails, e.g. when using the PJust a <- ... syntax, it will use Plutarch.Monadic's implementation of fail

Finally, P.do { x } is just x.

imports

module Plutarch.Docs.TermCont (test, testC, foo) where
import Plutarch.LedgerApi.V3 (PScriptPurpose (PSpending))
import Plutarch.Prelude hiding (pmatchC, ptraceC)

Do syntax with TermCont

Note: The use of qualified do is preferred compared to the use of TermCont due to some shortcomings of the implementation of the Monad typeclass in base

Continuation functions like pmatch, plet, and pletFields aren't exactly the most convenient, are they? Fortunately, TermCont makes it much easier to use. TermCont is the familiar Cont monad, specialized for Plutarch terms.

TermCont @b s a essentially represents (a -> Term s b) -> Term s b. a being the input to the continuation, and Term s b being the output. Notice the type application - b must have been brought into scope through another binding first.

Consider the snippet:

test :: Term s (PScriptPurpose :--> PUnit)
test = plam $ \x -> pmatch x $ \case
  PSpending _ -> ptraceInfo "matched spending script purpose" $ pconstant ()
  _ -> ptraceInfoError "pattern match failure"

That's rather ugly! pmatch takes in a continuation as its second argument. Can we make this a bit more ergonomic?

pmatchC :: PlutusType a => Term s a -> TermCont s (a s)
pmatchC = tcont . pmatch

ptraceInfoC :: Term s PString -> TermCont s ()
ptraceInfoC s = tcont $ \f -> ptraceInfo s (f ())

testC :: Term s (PScriptPurpose :--> PUnit)
testC = plam $ \x -> unTermCont $ do
  PSpending _ <- pmatchC x
  ptraceInfoC "matched spending script purpose"
  pure $ pconstant ()

How cool is that? You can use regular do syntax on the TermCont monad. All the continuations are flattened! Just remember to unTermCont the result.

Furthermore, this is very similar to the Cont monad - it just operates on Plutarch level terms. This means you can draw parallels to utilities and patterns one would use when utilizing the Cont monad. Here's an example:

-- | Terminate with given value on empty list, otherwise continue with head and tail.
nonEmpty :: Term s r -> PList a s -> TermCont @r s (Term s a, Term s (PList a))
nonEmpty x0 list = tcont $ \k ->
  case list of
    PSCons x xs -> k (x, xs)
    PSNil -> x0

foo :: Term s (PList PInteger :--> PInteger)
foo = plam $ \l -> unTermCont $ do
  (x, xs) <- nonEmpty 0 =<< tcont (pmatch l)
  pure $ x + plength # xs

foo adds up the first element of the given list with the length of its tail. Unless the list was empty, in which case, it just returns 0. It uses continuations with the do syntax to elegantly utilize short circuiting!

imports

{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# LANGUAGE TemplateHaskell #-}
module Plutarch.Docs.FFI () where 
import Plutarch.Prelude
import Plutarch.FFI

import PlutusTx qualified
import PlutusTx.Builtins qualified as PlutusTx
import PlutusTx.Builtins.Internal qualified as PlutusTx

import Generics.SOP qualified as SOP
import Data.Default (def)

Interoperability with PlutusTx

Note: This module needs the PlutusTx plugin. As it does not yet work under ghc92+, some of this documentation is not part of the CI, the documentation is up to date as of Plutarch 1.3.

If you already have a codebase built using PlutusTx, you can choose to re-write only its critical parts in Plutarch and to call them from PlutusTx. The function to use is Plutarch.FFI.foreignExport:

doubleInPlutarch :: ClosedTerm (PInteger :--> PInteger)
doubleInPlutarch = plam (2 *)

doubleExported :: PlutusTx.CompiledCode (Integer -> Integer)
doubleExported = foreignExport def doubleInPlutarch

doubleUseInPlutusTx :: PlutusTx.CompiledCode Integer
doubleUseInPlutusTx = doubleExported `PlutusTx.applyCode` PlutusTx.liftCode 21

Alternatively, you may go in the opposite direction and call an existing PlutusTx function from Plutarch using Plutarch.FFI.foreignImport:

doubleInPlutusTx :: PlutusTx.CompiledCode (Integer -> Integer)
doubleInPlutusTx = $$(PlutusTx.compile [||(2 *) :: Integer -> Integer||])

doubleImported :: Term s (PInteger :--> PInteger)
doubleImported = foreignImport doubleInPlutusTx

doubleUseInPlutarch :: Term s PInteger
doubleUseInPlutarch = doubleImported # 21

Note how Plutarch type PInteger :--> PInteger corresponds to Haskell function type Integer -> Integer. If the types didn't correspond, the foreignExport and foreignImport applications wouldn't compile. The following table shows the correspondence between the two universes of types:

PlutarchHaskell
pa :--> pba -> b
PTxList pa[a]
PTxMaybe paMaybe a
PIntegerInteger
PBoolBuiltinBool
PStringBuiltinString
PByteStringBuiltinByteString
PBuiltinDataData
PUnitBuiltinUnit
PDelayed paDelayed a

User-defined types

When it comes to user-defined types, you have a choice of passing their values encoded as Data or directly. In the latter case, you'll have to declare your type twice with two kinds: as a Haskell Type and as a Plutarch PType. Furthermore, both types must be instances of SOP.Generic, as in this example:

data SampleRecord = SampleRecord
  { sampleBool :: PlutusTx.BuiltinBool
  , sampleInt :: PlutusTx.Integer
  , sampleString :: PlutusTx.BuiltinString
  }
  deriving stock (Generic)
  deriving anyclass (SOP.Generic)

data PSampleRecord (s :: S) = PSampleRecord
  { psampleBool :: Term s PBool
  , psampleInt :: Term s PInteger
  , psampleString :: Term s PString
  }
  deriving stock Generic
  deriving anyclass (SOP.Generic, PlutusType)
instance DerivePlutusType PSampleRecord where type DPTStrat _ = PlutusTypeScott

With these two declarations in place, the preceding table can gain another row:

PlutarchHaskell
PDelayed PSampleRecordSampleRecord

The reason for PDelayed above is a slight difference in Scott encodings of data types between Plutarch and PlutusTx. It means you'll need to apply pdelay to a PSampleRecord value before passing it through FFI to Haskell, and pforce after passing it in the opposite direction.

This technique can be used for most data types, but it doesn't cover recursive types (such as lists) nor data types with nullary constructors (such as Maybe). To interface with these two common Haskell types, use PTxMaybe and PTxList types from Plutarch.FFI. The module also exports the means to convert between these special purpose types and the regular Plutarch PMaybe and PList.

Using the Plutarch Prelude

Plutarch exports a Prelude (Plutarch.Prelude) that contains the most commonly used Plutarch functions, types and constructors.

The Plutarch Prelude Plutarch.Prelude has no overlap with base Prelude, which is the reason why you can use both of them together without trouble. If you want to avoid importing Plutarch.Prelude in each of your modules, add the following to your *.cabal file:

mixins:
  base hiding (Prelude)
  , plutarch-preludes (PPrelude as Prelude)
imports

module Plutarch.Docs.RaiseErrs (fails) where
import Plutarch.Prelude

Raising errors

In PlutusTx, you'd signal validation failure with the error function. You can do the same in Plutarch using perror.

fails :: Term s (PData :--> PData :--> PData :--> PUnit)
fails = plam $ \_ _ _ -> perror
imports

module Plutarch.Docs.Recursion (pfac) where 
import Plutarch.Prelude

Recursion

To emulate recursion in UPLC (Untyped Plutus Core), you need to use the Y combinator. Plutarch provides the Y combinator with the name pfix:

pfix :: Term s (((a :--> b) :--> (a :--> b)) :--> (a :--> b))

It works as you would expect, though the type is scary. Think of it as the Haskell type:

fix :: ((a -> b) -> (a -> b)) -> (a -> b)

The first argument is "self", or the function you want to recurse with.

The below example implements a Plutarch-level factorial function:

pfac :: Term s (PInteger :--> PInteger)
pfac = pfix #$ plam f
  where
    f :: Term s (PInteger :--> PInteger) -> Term s PInteger -> Term s PInteger
    f self n = pif (n #== 1) n $ n * (self #$ n - 1)
-- (ignore the existence of non positives :D)

Note how f takes in a self and just recurses on it. All you have to do, is create a Plutarch level function by using plam on f and pfix the result - and that self argument will be taken care of for you.

imports

module Plutarch.Docs.Tracing () where 
import Plutarch.Prelude ()

Tracing

Fundamentally, there are two kinds of traces Plutarch can add to your code:

  • Info tracing, which is the 'regular' kind of tracing; and
  • Debug tracing, which is supposed to be more verbose and provide more detail for debugging purposes.

The basic way you can add traces to your code is using ptraceInfo to add an info trace, and ptraceDebug to add a debug trace. Plutarch.Trace (and Plutarch.Prelude) export additional functions for more specific cases, including ones that include use of PShow, and that only inject a trace under certain conditions. See those modules, and their documentation, for more details.

If you have the development flag for plutarch turned on - you'll see the trace messages appear in the trace log during script evaluation. When not in development mode, these functions basically do nothing.

Important note

Use of PShow is strongly discouraged in any production on-chain scripts. This uses a lot of resources onchain, and can easily exhaust script limits unless done carefully. In general, only resort to PShow if you absolutely have to: otherwise, prefer static strings as outputs.

imports

module Plutarch.Docs.Unsafe () where 
import Plutarch.Prelude ()

Unsafe functions

There are internal functions such as punsafeCoerce, punsafeConstant etc. that give you terms without their specific type. These should not be used by Plutarch users. It is the duty of the user of these unsafe functions to get the type right - and it is very easy to get the type wrong. You can easily make the type system believe you're creating a Term s PInteger, when in reality, you created a function.

Things will go very wrong during script evaluation if you do that kind of thing.

The good thing is that unsafe functions all have explicit indicators through the names, as long as you don't use any punsafe* functions - you should be fine!

Note: unsafe functions are exported by the Plutarch.Unsafe module

Of course, these have legitimate use cases. Most often, we use these functions to convert between types that truly have the same internal representation in UPLC - but the type system simply isn't expressive enough to infer that.

This document discusses various rules of thumb and general trivia, aiming to make life as a Plutarch user or auditor easier.

Note: If you spot any mistakes/have any related questions that this guide lacks the answer to, please don't hesitate to raise an issue. The goal is to have high quality documentation for Plutarch users!

imports

module Plutarch.Docs.DifferencePconPconstant () where
import Plutarch.Prelude
import Plutarch.Internal.PlutusType (PlutusType(pcon', pmatch'))

The difference between PlutusType/PCon and PLift's pconstant

PlutusType is especially useful for building up Plutarch terms dynamically - i.e. from arbitrary Plutarch terms. This is when your Plutarch type's constructors contain other Plutarch terms.

Another case PlutusType is useful is when you want to give your Plutarch type a custom representation, Scott encoding, enum - what have you. From the PlutusType haddock example:

data AB (s :: S) = A | B

instance PlutusType AB where
  type PInner AB = PInteger
  pcon' A = 0
  pcon' B = 1
  pmatch' x f = pif (x #== 0) (f A) (f B)

You can use the A and B constructors during building, but still have your type be represented as integers under the hood! You cannot do this with pconstant.

You should prefer pconstant/pconstantData (from PLiftable/) when you can build something up entirely from Haskell level constants and that something has the same representation as the Haskell constant.

imports

module Plutarch.Docs.WorkDuplication (abs, abs', pf, pf') where
import Plutarch.Prelude
import Prelude hiding (abs)

Don't duplicate work

Haskell bindings are simply "inlined" during Plutarch compilation.

Consider the simple snippet:

pf :: Term s PInteger
pf =
  let
    foo :: forall s. Term s PInteger
    foo = 1 + 2      -- | A Haskell binding.
  in pif
       (foo #== 3)     -- | A.) ...then inline here...
       foo             -- | B.) ...and inline here.
       7

Using the printTerm function (provided by the top level Plutarch module), we can view the computation bound to foo. The formatting below is our own; notice that foo, which becomes (addInteger 1 2) in UPLC, is inlined twice:

> printTerm pf

(...)

(force
    (force ifThenElse
       (equalsInteger
          (addInteger 1 2)      -- | A.) `foo` appears here...
          3
       )
       (delay (addInteger 1 2)) -- | B.) ...and here
       (delay 7)
    )
)

Performing this computation twice is obviously bad (in this circumstance), since it will increase the execution budget for the script.

A technique to circumvent this is to introduce a free variable via a lambda, replace the inlined expression (in our case, (addInteger 1 2)) with that variable, and them apply the lambda to the calculated expression:

> printTerm pf'

(...)

((\\i0 ->                          -- | A'.) Introduce a lambda here,...
    force
        (force ifThenElse
            (equalsInteger i1 3)   -- | B'.) ...apply the argument here,...
            (delay i1)             -- | C'.) ...and apply the argument here,
            (delay 7)
        )
 ) (addInteger 1 2)                -- | D'.) ...then calculate `foo` once and apply the lambda
)

Plutarch provides the plet :: Term s a -> (Term s a -> Term s b) -> Term s b function to accomplish exactly this. To demonstrate this technique, the implementation of pf' that will lead to the above UPLC is given as:

{-
Note: the letter labels on our annotations match the operations in the
previous example.
-}

pf' :: Term s PInteger
pf' =
  plet (1 + 2) $             -- | D.') Calculate the desired value here (strictly),...
  \foo ->                    -- | A.') ...introduce a lambda abstraction,...
    pif
      (foo #== 3)            -- | B.') ...and apply the argument here...
      foo                    -- | C.') ... and here.
      7

Another example of this would be:

abs :: Term s PInteger -> Term s PInteger
abs x = pif (x #<= -1) (negate x) x

Guess what would happen if you used it like:

abs (reallyExpensiveFunction # arg)

It'd turn into:

pif ((reallyExpensiveFunction # arg) #<= -1) (negate (reallyExpensiveFunction # arg)) (reallyExpensiveFunction # arg)

Oh no. reallyExpensiveFunction is going to be applied three times. That's 3 times the cost!

Instead, consider using plet:

abs' :: Term s PInteger -> Term s PInteger
abs' x' = plet x' $ \x -> pif (x #<= -1) (negate x) x

Of course, what you really should do , is prefer Plutarch level functions whenever possible. Since arguments to Plutarch level functions are pre-evaluated and those bindings are completely ok to use as many times as you want!

Where should arguments be pleted?

You don't have to worry about work duplication on arguments in every single scenario. In particular, the argument to plam is also a Haskell function, isn't it? But you don't need to worry about pleting your arguments there since it becomes a Plutarch level function through plam - thus, all the arguments are evaluated before being passed in.

Where else is plet unnecessary? Functions taking in continuations, such as plet (duh) and pletFields, always pre-evaluate the binding. An exception, however, is pmatch. In certain cases, you don't need to plet bindings within the pmatch case handler. For example, if you use pmatch on a PList, the x and xs in the PSCons x xs will always be pre-evaluated. On the other hand, if you use pmatch on a PBuiltinList, the x and xs in the PCons x xs are not pre-evaluated. Be sure to plet them if you use them several times!

In general, pleting something back-to-back several times will be optimized to a singular plet anyway. However, you should know that for data encoded types (types that follow "implementing PIsDataRepr and friends") and Scott encoded types, pmatch handlers get pre-evaluated bindings. For PBuiltinList, and PDataRecord - the bindings are not pre-evaluated.

You should also plet local bindings! In particular, if you applied a function (Plutarch level or Haskell level) to obtain a value, then bound that value to a variable e.g. with let or where, then avoid using it multiple times. The binding will simply get inlined as the function application - and it'll keep getting re-evaluated. You should plet it first!

This also applies to field accesses using OverloadedRecordDot. When you do ctx.purpose, it really gets translated to getField @"purpose" ctx, which is a function call! If you use the field multiple times, plet it first.

Another slightly obscure case can be observed in scott encoded types. When you build a scott encoded type using pcon - the Plutarch terms you use as fields are simply inlined within the scott encoded type. As such, pcon $ PPair <complex expr> <another complex expr> ends up like:

(\f -> f <complex expr> <another complex expr>)

This is practically pseudocode. However, it demonstrates that your expressions are not evaluated when building the scott encoded pair. Indeed, they will be evaluated when you pmatch on it. As such, if you pmatch on this pair multiple times, those expressions will evaluate multiple times!

If you must pmatch on such types several times, plet the fields before building the container type!

The isomorphism between makeIsDataIndexed, Haskell ADTs, and PIsDataRepr

When implementing PIsDataRepr for a Plutarch type, if the Plutarch type also has a Haskell synonym (e.g. ScriptContext is the Haskell synonym to PScriptContext) that uses makeIsDataIndexed - you must make sure the constructor ordering is correct.

In particular, with makeIsDataIndexed, you can assign indices to your Haskell ADT's constructors. This determines how the ADT will be represented in Plutus Core. It's important to ensure that the corresponding Plutarch type knows about these indices so it can decode the ADT correctly - in case you passed it into Plutarch code, through Haskell.

For example, consider Maybe. Plutus assigns these indices to its constructors:

makeIsDataIndexed ''Maybe [('Just, 0), ('Nothing, 1)]

0 to Just, 1 to Nothing. So the corresponding Plutarch type, PMaybeData is defined as:

data PMaybeData a (s :: S)
  = PDJust (Term s (PDataRecord '["_0" ':= a]))
  | PDNothing (Term s (PDataRecord '[]))

It'd be a very subtle mistake to instead define it as:

data PMaybeData a (s :: S)
  = PDNothing (Term s (PDataRecord '[]))
  | PDJust (Term s (PDataRecord '["_0" ':= a]))

The constructor ordering is wrong!

It's not just constructor ordering that matters - field ordering does too! Though this is self explanatory. Notice how PTxInfo shares the exact same field ordering as its Haskell synonym - TxInfo.

newtype PTxInfo (s :: S)
  = PTxInfo
      ( Term
          s
          ( PDataRecord
              '[ "inputs" ':= PBuiltinList (PAsData PTxInInfo)
               , "outputs" ':= PBuiltinList (PAsData PTxOut)
               , "fee" ':= PValue
               , "mint" ':= PValue
               , "dcert" ':= PBuiltinList (PAsData PDCert)
               , "wdrl" ':= PBuiltinList (PAsData (PBuiltinPair (PAsData PStakingCredential) (PInteger)))
               , "validRange" ':= PPOSIXTimeRange
               , "signatories" ':= PBuiltinList (PAsData PPubKeyHash)
               , "datums" ':= PBuiltinList (PAsData (PBuiltinPair (PAsData PDatumHash) (PAsData PDatum)))
               , "id" ':= PTxId
               ]
          )
      )
data TxInfo = TxInfo
  { txInfoInputs      :: [TxInInfo]
  , txInfoOutputs     :: [TxOut]
  , txInfoFee         :: Value
  , txInfoMint        :: Value
  , txInfoDCert       :: [DCert]
  , txInfoWdrl        :: [(StakingCredential, Integer)]
  , txInfoValidRange  :: POSIXTimeRange
  , txInfoSignatories :: [PubKeyHash]
  , txInfoData        :: [(DatumHash, Datum)]
  , txInfoId          :: TxId
  }

The field names don't matter though. They are merely labels that don't exist at runtime.

What about newtypes?

Of course, this does not apply when you're using newtype derivation (e.g derive newtype ...) to derive FromData or ToData for your PlutusTx types. In that case, the Data representation is simply the same as the inner type.

import qualified PlutusTx
import PlutusTx.Prelude

newtype CurrencySymbol = CurrencySymbol { unCurrencySymbol :: BuiltinByteString }
  deriving newtype (PlutusTx.ToData, PlutusTx.FromData, PlutusTx.UnsafeFromData)

Here, for example, CurrencySymbol has the very same Data representation as BuiltinByteString. No extra information is added.

note that in plutarch what matters is not whether you declare a datatype as haskell data or as haskell newtype but in what way you derive the plutuscore representation

imports

module Plutarch.Docs.OptimizingUnhoistable (pfoo, pfoo') where
import Plutarch.Prelude

Optimizing unhoistable lambdas

Often times, you'll be creating utility functions inside your Plutarch level functions that use free variables. In such cases, the function is unhoistable (i.e, you cannot use phoistAcyclic on it). However, it is likely that your goal is to use this utility function within your primary Plutarch level function several times. At which point, your unhoisted function will be inlined every time you use it and therefore increase script size.

pfoo :: Term s (PInteger :--> PBuiltinList PInteger :--> PInteger)
pfoo = plam $ \x l ->
  let innerf = plam $ \y -> x + y
  in innerf # 42 + plength # (pmap # innerf # l)

Here, both uses of innerf will inline the lambda and then apply. This is problematic since you probably wanted to have a single lambda that you could simply reference with a variable.

In these cases, you can simply use plet as you would have in other places

pfoo' :: Term s (PInteger :--> PBuiltinList PInteger :--> PInteger)
pfoo' = plam $ \x l ->
  plet (plam $ \y -> x + y) $ \innerf ->
    innerf # 42 + plength # (pmap # innerf # l)

Plutarch functions are strict

All Plutarch functions are strict. When you apply a Plutarch function to an argument using papp (or #/#$ - synonyms to papp) - the argument will be evaluated before being passed into to the function. If you don't want the argument to be evaluated, you can use pdelay.

See: Delay and Force.

imports

module Plutarch.Docs.PreferMatchingOnResult (this, this') where
import Plutarch.Prelude
import Plutarch.LedgerApi.V3 (
  PScriptPurpose (
    PSpending, 
    PMinting, 
    PRewarding, 
    PCertifying,
    PVoting,
    PProposing
    )
  )

Prefer pattern matching on the result of pmatch immediately

You should always try and pattern match on the result of pmatch immediately. This is because the semantics of pmatch will make anything you write before the pattern match be inlined for every single branch:

this :: Term s (PScriptPurpose :--> PInteger)
this = plam $ \x -> pmatch x $ \l ->
  plet (1 + 2) $ \i -> case l of
    PMinting _ -> i + 3
    PSpending _ -> i + 4
    PRewarding _ -> i + 5
    PCertifying _ -> i + 6
    PVoting _ -> i + 7
    PProposing _ -> i + 8

Notice how the above code plets a computation before matching on l, the pmatch result. This will make the plet $ 1 + 2 $ \i -> i + <something> be inlined in every branch of your pattern match! That is, not only will it compute the 1 + 2 every time, it will also plet it, which introduced an extra lambda, only to immediately apply the lambda!

You should always match on the result immediately, whenever possible:

this' :: Term s (PScriptPurpose :--> PInteger)
this' = plam $ \x -> plet  (1 + 2) $ \i ->
  pmatch x $ \case
    PMinting _ -> i + 3
    PSpending _ -> i + 4
    PRewarding _ -> i + 5
    PCertifying _ -> i + 6
    PVoting _ -> i + 7
    PProposing _ -> i + 8

This applies much the same with do syntax (whether with TermCont or with QualifiedDo). Try to use inline partial pattern matching (e.g PMinting _ <- pmatch x), or pattern match on the very next line (e.g l <- pmatch x; case l of ...).

Prefer Plutarch level functions

Plutarch level functions have a lot of advantages - they can be hoisted; they are strict so you can use their arguments however many times you like without duplicating work etc. Unless you really need laziness, like pif does, try to use Plutarch level functions.

Also see: Hoisting.

imports

module Plutarch.Docs.PreferStaticallyBuilding (viacon, viaconstant) where

import Plutarch.Prelude
import Plutarch.Builtin (PDataNewtype (PDataNewtype))
import Plutarch.LedgerApi.V3 (PScriptPurpose (PMinting), PCurrencySymbol (PCurrencySymbol))
import PlutusLedgerApi.V3 (ScriptPurpose (Minting))

Prefer statically building constants whenever possible

Whenever you can build a Plutarch constant out of a pure Haskell value - do it! Functions such as pconstant, phexByteStr operate on regular Haskell synonyms of Plutarch types. Unlike pcon, which potentially works on Plutarch terms (e.g. pcon $ PJust x, x is a Term s a). A Plutarch term is an entirely "runtime" concept. "Runtime" as in "Plutus Core Runtime". They only get evaluated during runtime!

On the other hand, whenever you transform a Haskell synonym to its corresponding Plutarch type using pconstant, phexByteStr etc. - you're directly building a Plutus Core constant. This is entirely static! There are no runtime function calls, no runtime building, it's just there, inside the compiled script.

Here's an example, let's say you want to build a PScriptPurpose - PMinting "f1e301". Which snippet, do you think, is better?

viaconstant :: Term s PScriptPurpose
viaconstant = pconstant (Minting "f1e301")
-- (or)

viacon :: Term s PScriptPurpose
viacon = let currSym = pcon . PCurrencySymbol . pcon . PDataNewtype . pdata $ phexByteStr "f1e301"
 in pcon $ PMinting $ pdcons # pdata currSym # pdnil

The semantics are both are the same. But the former (pconstant) compiles to a constant term directly. Whereas the latter compiles to some code that builds the constant during Plutus Core runtime.

Aside: Remember that Haskell runtime is actually compile-time for Plutarch! Even if you have a dynamically computed variable in the Haskell world, it's still a constant in the Plutarch world. So you can use it just as well as an argument to pconstant!

Whenever you need to build a Plutarch term of type a, from a Haskell value, use pconstant. Whenever you need to build a Plutarch term of type PAsData a, use pconstantData!

Figuring out the representation of a Plutarch type

We've discussed before how Plutarch types are merely tags and don't have a direct connection to their runtime representations. It's important to be able to intuitively figure out the runtime representations from the data type declaration though. This is why most types follow certain conventions.

The representation can only be one of two categories: builtin and Scott encoded. All trivial builtin types are already defined in Plutarch: PInteger, PByteString, PString, PBool, PUnit, PBuiltinList and PBuiltinPair.

Now, let's discuss patterns of data declarations and what representation they should hint at:

  • If it's an ADT that derives PlutusType with DPTStrat _ = PlutusTypeScott, then the ADTs will be scottencoded. This is what you generally want for non-trivial types that are not stored in datums or redeemers.

    e.g. PList derives PlutusType generically and is represented with Scott encoding.

  • If it's an ADT that derives PlutusType with DPTStrat _ = PlutusTypeData it's data encoded. Particularly, it's a Data value - which is part of the builtin types.

    e.g. PScriptContext derives PlutusType using DPTStrat _ = PlutusTypeData

  • If it's a representationally equal wrapper (think Haskell newtype) to a term containing a Plutarch type - it should have the same representation as that underlying Plutarch type.

    e.g. newtype PPositive (s :: S) = PPositive (Term s PInteger) is just represented as PInteger. This is ensured by deriving PlutusType with DPTStrat _ = PlutusTypeNewtype.

Let Haskell level functions take responsibility of evaluation

We've discussed how a Haskell level function that operates on Plutarch level terms needs to be careful about work duplication. Related to this point, it's good practice to design your Haskell level functions so that it takes responsibility for evaluation.

The user of your Haskell level function doesn't know how many times it uses the argument it has been passed! If it uses the argument multiple times without pleting it - there's duplicate work! There are two solutions here:

  • The user plets the argument before passing it to the Haskell level function.
  • The Haskell level function takes responsibility of its argument and plets it itself.

The former is problematic since it's based on assumption. What if the Haskell level function is a good rule follower, and correctly plets its argument if using it multiple times? Well, then there's a redundant plet (though back-to-back plets will be optimized away into one).

Instead, try to offload the responsibility for evaluation to the Haskell level function - so that it only plets when it needs to.

imports

module Plutarch.Docs.UsingHaskellLevelFunctions (pelimList, pelimList') where
import Plutarch.Prelude hiding (pelimList)

When to use Haskell level functions?

Although you should generally prefer Plutarch level functions, there are times when a Haskell level function is actually much better. However, figuring out when that is the case - is a delicate art.

There is one simple and straightforward use case though, when you want a function argument to be lazily evaluated. In such a case, you should use a Haskell level function that pdelays the argument before calling some Plutarch level function. Recall that Plutarch level functions are strict.

Outside of that straightforward use case, figuring out when to use Haskell level functions is quite complex. Haskell level functions will always be inlined when generating the Plutus Core. Unless the function is used only once, this sort of inlining will increase the script size - which is problematic.

However, if the function is used only once, and making it Plutarch level causes extra plams and #s to be introduced - you should just make it Haskell level. For example, consider the pelimList implementation:

pelimList ::   PElemConstraint PBuiltinList a => Term s (a :--> PBuiltinList a :--> r) -> Term s r -> Term s (PBuiltinList a) -> Term s r
pelimList match_cons match_nil ls = pmatch ls $ \case
  PCons x xs -> match_cons # x # xs
  PNil -> match_nil

It takes in a Plutarch level function, let's see a typical usage:

pelimList
  (plam $ \x xs -> pcons # x # (self # xs))
  pnil
  ls

This is rather redundant, the above snippet will translate to:

pmatch ls $ \case
  PCons x xs -> (plam $ \x xs -> pcons # x # (self # xs)) # x # xs
  PNil -> match_nil

Extra plams and #s have been introduced. Really, pelimList could have taken a Haskell level function instead:

pelimList' ::
  forall (a :: S -> Type) (r :: S -> Type) (s :: S).
  PElemConstraint PBuiltinList a
  => (Term s a -> Term s (PBuiltinList a) -> Term s r)
  -> Term s r -> Term s (PBuiltinList a)
  -> Term s r
pelimList' match_cons match_nil ls = pmatch ls $ \case
  PCons x xs -> match_cons x xs
  PNil -> match_nil

Now, the following usage:

pelimList
  (\x xs -> pcons # x # (self # xs))
  pnil
  ls

would turn into:

pmatch ls $ \case
  PCons x xs -> pcons # x # (self # xs)
  PNil -> match_nil

It turns out that using pelimList almost always involves using a one-off Haskell level function (and therefore a redundant plam). As such, pelimList benefits greatly from just taking a Haskell level function directly.

However, not all higher order functions benefit from taking Haskell level functions. In many higher order function use cases, you could benefit from passing a commonly used function argument, rather than a one-off function argument. Imagine map, you don't always map with one-off functions - often, you map with existing, commonly used functions. In these cases, that commonly used function ought to be a Plutarch level function, so it can be hoisted and map can simply reference it.

imports

module Plutarch.Docs.WorkingWithBoundFields (foo, foo', coreValidator) where

import Plutarch.Prelude
import Plutarch.DataRepr (HRec, HRecOf, PDataFields, PMemberFields)
import Plutarch.LedgerApi.V3 (PTxInfo, PScriptContext)

Working with bound fields yielded by pletFields

You may have noticed that pletFields actually returns a Haskell level heterogenous list, with all the interesting fields "bound" to it. Only the fields you actually use from these bindings are extracted and put into the resulting script. Therefore, you only pay for what you use.

pletFields ::
  forall fs a s b ps bs.
  ( PDataFields a
  , ps ~ (PFields a)
  , bs ~ (Bindings ps fs)
  , BindFields ps bs
  ) =>
  Term s a ->
  (HRecOf a fs s -> Term s b) ->
  Term s b

The real juice of that massive type is the HRecOf, which is a utility type alias you can use in functions that operate on the return value of pletFields:

newtype PFooType s
  = PFooType (Term s (PDataRecord '["frst" ':= PInteger, "scnd" ':= PBool, "thrd" ':= PString]))
  deriving stock (Generic)
  deriving anyclass (PlutusType, PDataFields)
instance DerivePlutusType PFooType where type DPTStrat _ = PlutusTypeData

foo :: HRecOf (PAsData PFooType) '[ "frst", "scnd" ] s -> Term s PInteger
foo h = pif (getField @"scnd" h) (getField @"frst" h) 0

Note: Be careful to derive PDataFields on your type if it has only one constructor

This is very useful for single use functions that you use as "branches" in your validators - they work more like macros or templates rather than real functions. For example, you might have different branches for different constructors of a redeemer, but all branches end up needing to do common field extraction. You could abstract it out using:

data PSomeRedm s
  = FirstRedm (Term s (PDataRecord '[]))
  | SecondRedm (Term s (PDataRecord '[]))
  deriving stock (Generic)
  deriving anyclass (PlutusType, PIsData)
instance DerivePlutusType PSomeRedm where type DPTStrat _ = PlutusTypeData

firstRedmCheck ::
  HRecOf PTxInfo '[ "inputs", "outputs", "mint", "datums" ] s
  -> TermCont s (Term s PUnit)
firstRedmCheck _info = do
  -- Do checks with info fields here.
  pure $ pconstant ()

secondRedmCheck ::
  HRecOf PTxInfo '[ "inputs", "outputs", "mint", "datums" ] s
  -> TermCont s (Term s PUnit)
secondRedmCheck _info = do
  -- Do checks with info fields here.
  pure $ pconstant ()

coreValidator :: Term s (PData :--> PAsData PSomeRedm :--> PScriptContext :--> PUnit)
coreValidator = plam $ \_ (pfromData -> redm) ctx' -> unTermCont $ do
  ctx <- tcont $ pletFields @'["txInfo", "purpose"] ctx'
  info <- tcont $ pletFields @'["inputs", "outputs", "mint", "datums"] $ getField @"txInfo" ctx
  pmatchC redm >>= \case
    FirstRedm _ -> firstRedmCheck info
    SecondRedm _ -> secondRedmCheck info

Without it, you may have to fallback to deconstructing info with pletFields in every single branch.

However, this is rather nominal. What if you don't need the exact same fields in all branches? Let's go back to the example with foo and FooType. What if someone has:

fooTypeHrec <- tcont $ pletFields @'["frst", "scnd", "thrd"] fooTypeValue
foo fooTypeHrec
-- uh oh

The type required by foo should morally work just fine with fooTypeHrec, but it won't! What we really want, is some sort of row polymorphism. This is where the PMemberFields type from Plutarch.DataRepr comes in:

foo' :: PMemberFields PFooType '["scnd", "frst"] s as => HRec as -> Term s PInteger
foo' h = pif (getField @"scnd" h) (getField @"frst" h) 0

Now foo merely requires the HRec to have the "scnd" and "frst" fields from PFooType, more fields are allowed just fine!