Do You Even PLift? Bridging Haskell & Plutarch with PLiftable for Efficient On-Chain Data
Introduction
Writing Cardano scripts poses a range of challenges, but one of the most significant is performance. Due to the limited operations and data types available onchain, as well as the significant limitations imposed on computing resources per transaction, getting good (or even sufficient) performance can be a challenge. Plutarch was designed with this problem in mind, and provides a range of helpers to allow more clarity with regard to performance, as well as making optimizations easier and more transparent.
However, some aspects of how Plutarch does this can be downright cryptic. Plutarch frequently uses quite advanced features of Haskell, as well as techniques not all application developers would be familiar with. This often led to confusion, which made Plutarch more difficult to use than it should be.
As part of MLabs' work for Project Catalyst Fund13, we wanted to improve the situation with regard to Plutarch's usability. One major part of this work was the introduction of the PLiftable
type class, designed to deal with issues of translation between Haskell and Plutarch, as well as onchain data type representation. PLiftable
was designed to replace the older PUnsafeLiftDecl
and PConstantDecl
type classes and their associated mechanisms, while being clearer, more law-abiding and more powerful.
In this article, we will discuss the problem that PLiftable
is designed to solve. We will also provide an overview of PLiftable
itself, while demonstrating its use for a range of data types. Lastly, we will discuss how Plutarch makes defining PLiftable
instances easier in cases where total manual control isn't necessary.
The problem
An important choice when defining data types in Plutarch is their representation: essentially, how those data types will look onchain. There are essentially three possible choices of representation: builtin, SOP or Data
[5]. Which choice is correct depends on what your data type is composed of, and what you want to use it for. We will describe the options, and give examples.
The builtin representation is the most efficient, as it is what gets used for onchain primitive data types, such as Integer
and ByteString
. Plutarch types can only use the builtin representation if they correspond to an onchain primitive type (PInteger
) or if they are a newtype
around one (PScriptHash
). This means that it can't be used very often, especially for more complex data types.
The SOP representation uses a sum-of-products encoding, which is also native to onchain. Provided that all fields are themselves using SOP or builtin representations, SOP representation can be used for any algebraic data type. It is also fairly efficient, second only to the builtin representation; it is particularly good if we need to do modifications. Plutarch uses SOP representations for types like PMaybe
and PEither
. The primary downside of the SOP representation is that it cannot be exchanged onchain in something like a datum or redeemer.
Lastly, the Data
representation essentially is just Data
from plutus-tx
: the structure we impose on it is tracked only by Plutarch itself. You can think of this as being similar to JSON encodings: while we can impose structure of our own, in practice it is simply text. Data
representations must be used for any type that will be exchanged onchain, such as anything that is part of a datum or redeemer. As a result, Data
representations are used for most of the ledger, including all the types in plutus-ledger-api
, and much of plutus-tx
as well. Plutarch mirrors this in plutarch-ledger-api
, as well as for types like PMaybeData
and PRationalData
, as they are designed to be equivalents to their Plutus versions. Despite their ubiquity, Data
representations are the least efficient, both in terms of time and space.
Representations aren't merely an efficiency or functionality concern: they also tie directly into a concern we have whenever we write Plutarch, or indeed anything onchain. This concern is that of universes; specifically that we have to deal simultaneously with multiple 'worlds' or 'systems' of values:
The Haskell 'universe', consisting of regular Haskell values
The Plutus 'universe', consisting of types from
plutus-core
,plutus-tx
andplutus-ledger-api
, as well as their onchain equivalentsThe Plutarch 'universe', consisting of Plutarch types, both user-defined and provided by Plutarch itself
Any given value in one such 'universe' can (and must) be translated into the others to be useful. We need translations between the Haskell and Plutarch 'universes' to perform computations too complex or expensive to do onchain, and ultimately, any script written in Plutarch must be translated to work over the Plutus 'universe'. While the Haskell-Plutarch interface is the one that tends to be most interesting to application developers, we cannot ignore the Plutarch-Plutus interface completely. This already creates no small amount of complexity:
Some translations are efficient, while others are not
Some translations are unconditional, while others can fail
Some translations are unique, others are not
To see examples of why this is difficult, consider the Haskell 'universe' Integer
. This potentially has two translations into the Plutus universe: either as a Plutus Integer
(builtin representation) or its Data
encoding (Data
representation). For types more complex than Integer
, this gets much more complicated quickly.
In order to handle this problem predictably, efficiently and on a per-type basis, we need a solution in Plutarch that does all of the following:
Allows us to clearly designate how a given Plutarch type translates to other universes;
What representation that type should use;
An interface for performing translations most useful to application developers.
PLiftable and how it solves the problem
Much as the PlutusType
type class provides a uniform interface for operating over data types in Plutarch itself, Plutarch provides the PLiftable
type class. This type class is designed to solve both the problem of representations and universes, giving us precise control when we want it, but without forcing us to deal with it if we don't want to. Furthermore, the type class has laws, allowing us to verify that we are doing the right thing. Lastly, Plutarch provides a convenient set of interfaces for both defining PLiftable
in typical cases, and also using instances of PLiftable
.
The PLiftable
type class is as follows:
data LiftError =
CouldNotEvaluate EvalError |
TypeError BuiltinError |
CouldNotCompile Text |
CouldNotDecodeData |
OtherLiftError Text
data PLifted s a = ... -- details aren't critical here
class PlutusType => PLiftable (a :: S -> Type) where
type AsHaskell a :: Type
type PlutusRepr a :: Type
haskToRepr :: AsHaskell a -> PlutusRepr a
reprToHask :: PlutusRepr a -> Either LiftError (AsHaskell a)
reprToPlut :: forall (s :: S) . PlutusRepr a -> PLifted s a
plutToRepr :: (forall (s :: S) . PLifted s a) -> Either LiftError (PlutusRepr a)
PLiftable
's definition consists of the following conceptual ideas:
The Haskell and Plutus equivalents of the Plutarch type
a
;The translation between the Haskell and Plutus 'universe' equivalents of
a
; andThe translation between
a
and its Plutus 'universe' equivalent.
We note that one direction of these translations (Haskell to Plutus and Plutus to Plutarch) is unconditional, while the other direction of both translations can fail. We use the LiftError
type to indicate these failures.
Given these definitions, we gain the ability to convert from, and to, any of the 'universe' equivalents to any other:
We can see that, given any starting 'universe', we can follow the arrows to reach any other 'universe'[6]. Here, solid arrows are unconditional translations, while dashed arrows are conditional (and can fail). To ensure that these relationships sensibly hold, the following laws apply:
reprToHask . haskToRepr = Right
plutToRepr . reprToPlut = Right
This essentially captures the essence of the diagram above: if we follow an unconditional arrow, then return using a conditional arrow, we should end up exactly where we started from.
For convenience, instead of using the functionality of PLiftable
directly, Plutarch provides two functions of most interest to application developers:
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
pconstant
represents the translation between the Haskell and Plutarch 'universes', essentially acting as a composite of both unconditional arrows from our definition. plift
does the opposite: it is the translation between the Plutarch and Haskell 'universes', acting as the composite of both conditional arrows. The laws we defined for PLiftable
together imply that plift . pconstant = id
.
It is worth pointing out here that pconstant
and plift
have vastly different costs. pconstant
is a cheap operation: to onchain, pconstant
effectively creates a literal value. This allows us to 'offload' complex computations to Haskell so as not to do them onchain. plift
, on the other hand, is a costly operation, as it involves evaluation (as a Term
can represent an arbitrary computation, which might fail). Thus, plift
should be used sparingly if ever. The main use of plift
is for testing purposes: thus, plutarch-testlib
makes heavy use of plift
.
We can see that PLiftable
meets the first of our requirements: we must designate associated types for the Haskell and Plutus 'universe' equivalents of any type that is an instance. Furthermore, pconstant
and plift
provide a convenient interface for application developers, dealing with the most common 'directions' of translation. What is not completely clear is how we solve the representation problem. We will demonstrate this with some examples next.
An example: builtin representation
To see how we can define PLiftable
instances, and how they solve the representation problem, let's define the equivalent of Vector Word8
in Plutarch. This could be useful if we wanted to use the rich API provided by vector
to do a complex operation offchain but then have the result of that put onchain as the convenient and efficient ByteString
.
We will define the instance completely by hand to show how everything works as well as show some of the helpers provided by Plutarch for manual instances. We normally wouldn't do this; instead, Plutarch provides a range of helpers to automate this process for common cases. We will show these later.
It makes the most sense to choose PByteString
as our Plutarch 'universe' representation as this corresponds to the Plutus ByteString
. We can define our type using a newtype
to have this effect:
newtype PByteVector (s :: S) = PByteVector (Term s PByteString)
deriving stock (Generic)
deriving anyclass (SOP.Generic)
deriving PlutusType via (DeriveNewtypePlutusType PByteString)
This is similar to Haskell-level newtype
s, except that we need to wrap a Term
. We use the Generic
instance to derive Generic
from generics-sop
, which we use to drive the via
-derivation of PlutusType
[1]. As we have a newtype, we can delegate PlutusType
to PByteString
, which is what the DeriveNewtypePlutusType
helper allows us to do.
As PByteString
is already an instance of PLiftable
, a lot of our work involves 'borrowing' from its instance. In particular, PlutusRepr PByteVector
must be ByteString
, as this is PlutusRepr PByteString
; however, AsHaskell PByteVector
should be Vector Word8
. Filling this in, we get the following:
instance PLiftable PByteVector where
type AsHaskell PByteVector = Vector Word8
type PlutusRepr PByteVector = ByteString
-- expanded type signatures for clarity
-- haskToRepr :: Vector Word8 -> ByteString
haskToRepr = _
-- reprToHask :: ByteString -> Either LiftError (Vector Word8)
reprToHask = _
-- reprToPlut :: forall s . ByteString -> PLifted s PByteVector
reprToPlut = _
-- plutToRepr :: (forall s . PLifted s PByteVector) -> Either LiftError ByteString
plutToRepr = _
To define haskToRepr
, we need to convert a Vector Word8
to a ByteString
, with reprToHask
being the reverse. Since reprToHask
happens to be unconditional in our case, this is straightforward:
-- Duplicated for clarity
instance PLiftable PByteVector where
type AsHaskell PByteVector = Vector Word8
type PlutusRepr PByteVector = ByteString
-- expanded type signatures for clarity
-- haskToRepr :: Vector Word8 -> ByteString
haskToRepr = ByteString.pack . Vector.toList
-- reprToHask :: ByteString -> Either LiftError (Vector Word8)
reprToHask bs = do
let len = ByteString.length bs
pure . Vector.generate len $ ByteString.index bs
-- reprToPlut :: forall s . ByteString -> PLifted s PByteVector
reprToPlut = _
-- plutToRepr :: (forall s . PLifted s PByteVector) -> Either LiftError ByteString
plutToRepr = _
It might seem a bit strange that neither haskToRepr nor reprToHask mention PByteVector at all. However, this matches our intent precisely: as far as both the Haskell and Plutus 'universes' are concerned, PByteVector is just a ByteString. Therefore, as long as we can translate ByteString into Vector Word8 and back again, Plutarch is able to handle the necessary wrapping for us.
This leaves only reprToPlut and plutToRepr. Here, we have the additional complication of PLifted; this is essentially Plutarch-level Identity, which we need for complex, but important reasons[2]. We can wrap into a PLifted using mkPLifted while unwrapping a PLifted is done using getPLifted. plutToRepr is a little awkward, but is also straightforward, as it cannot fail. This gives us the following finished instance:
-- Duplicated for clarity
instance PLiftable PByteVector where
type AsHaskell PByteVector = Vector Word8
type PlutusRepr PByteVector = ByteString
-- expanded type signatures for clarity
-- haskToRepr :: Vector Word8 -> ByteString
haskToRepr = ByteString.pack . Vector.toList
-- reprToHask :: ByteString -> Either LiftError (Vector Word8)
reprToHask bs = do
let len = ByteString.length bs
pure . Vector.generate len $ ByteString.index bs
-- reprToPlut :: forall s . ByteString -> PLifted s PByteVector
reprToPlut = mkPLifted . pcon PByteVector . getPLifted . reprToPlut
-- plutToRepr :: (forall s . PLifted s PByteVector) -> Either LiftError ByteString
plutToRepr t = plutToRepr (pmatch (getPLifted t) $ \(PByteVector t') -> t')
Once again, we 'borrow' capabilities from the PLifted PByteString
instance to write our translation. plutToRepr
requires us to use pmatch
first to 'unpack' the PByteVector
newtype
but is essentially the reverse of reprToPlut
from a logical standpoint.
By careful choice of AsHaskell
and PlutusRepr
, we have ensured that PByteVector
uses a builtin representation. Furthermore, most of the logic we needed could be borrowed from a different type (namely PByteString
). For builtin representations, this is usually the best we can do. We can see that this gives us quite a high degree of control over what representation is used, thus solving the representation problem.
Another example: SOP representation
Let us try a more complex example: defining the Plutarch equivalent of Haskell's These
. We want this to use the SOP representation, similarly to PMaybe
or PEither
in Plutarch.
First, we must define the type itself, as well as make it an instance of PlutusType
. This is an almost direct copy of the definition of These
:
data PThese (a :: S -> Type) (b :: S -> Type) (s :: S) =
PThis (Term s a) |
PThat (Term s b) |
PThese (Term s a) (Term s b)
deriving stock (Generic)
deriving anyclass (SOP.Generic)
deriving via DeriveAsSOPStruct (PThese a b) instance PlutusType (PThese a b)
The main differences between our definition above and the Haskell 'universe' These
are as follows:
There is an extra, final type parameter of kind
S
; andEach field of each 'arm' of the type is wrapped in
Term s
.
Just like before, we drive the derivation of PlutusType
using a via
-deriving helper and Generic
from generics-sop
.
To define the PLiftable
instance for PThese
, we first need to decide what types we will choose for AsHaskell (PThese a b)
and PlutusRepr (PThese a b)
. Then, we can define both of the necessary translations to complete the instance.
Our choice for AsHaskell (PThese a b)
seems straightforward, as PThese
is meant to correspond directly with These
. However, we cannot simply write type AsHaskell (PThese a b) = These a b
, as this won't kind check: a
and b
have kind S -> Type
(as they are Plutarch types), but These
expects its type parameters to have kind Type
instead. It thus follows that we can only have an instance for PThese a b
if instances for a
and b
also exist, as we need to apply AsHaskell
recursively.
The choice for PlutusRepr (PThese a b)
is also tricky: what part of the Plutus universe corresponds to an SOP encoding? For this purpose, Plutarch provides the type PLiftedClosed
, which is intended to represent 'some SOP encoding'. Its type parameter directly wraps the type whose encoding we want to represent.
Putting these together, our (partial) instance would look like this:
instance (PLiftable a, PLiftable b) => PLiftable (PThese a b) where
type AsHaskell (PThese a b) = These (AsHaskell a) (AsHaskell b)
type PlutusRepr (PThese a b) = PLiftedClosed (PThese a b)
-- Expanded type signatures for these functions for clarity
-- haskToRepr :: These (AsHaskell a) (AsHaskell b) -> PLiftedClosed (PThese a b)
haskToRepr = _
-- reprToHask :: PLiftedClosed (PThese a b) -> Either LiftError (These (AsHaskell a) (AsHaskell b))
reprToHask = _
-- reprToPlut :: forall s . PLiftedClosed (PThese a b) -> PLifted s (PThese a b)
reprToPlut = _
-- plutToRepr :: (forall s . PLifted s (PThese a b)) -> Either LiftError (PLiftedClosed (PThese a b))
plutToRepr = _
We can now define the translation between the Haskell and Plutus 'universes'. We will start with haskToRepr
, which essentially has to do the following:
Check which 'arm' of
These
we have.Lift each field of that 'arm' into Plutarch using
pconstant
.Wrap all the fields from step 2 into the corresponding data constructor of
PThese
.Wrap the result of step 3 into a
PLiftedClosed
usingmkPLiftedClosed
.
Put simply, haskToRepr
tells us how to construct the required SOP form from a Haskell form, using Plutarch as a helping hand along the way. The result looks like this:
-- Duplicated for clarity
instance (PLiftable a, PLiftable b) => PLiftable (PThese a b) where
type AsHaskell (PThese a b) = These (AsHaskell a) (AsHaskell b)
type PlutusRepr (PThese a b) = PLiftedClosed (PThese a b)
-- Expanded type signatures for these functions for clarity
-- haskToRepr :: These (AsHaskell a) (AsHaskell b) -> PLiftedClosed (PThese a b)
haskToRepr = \case
This x -> mkPLiftedClosed $ pcon $ PThis (pconstant @a x)
That y -> mkPLiftedClosed $ pcon $ PThat (pconstant @b y)
These x y -> mkPLiftedClosed $ pcon $ PThese (pconstant @a x) (pconstant @b y)
-- reprToHask :: PLiftedClosed (PThese a b) -> Either LiftError (These (AsHaskell a) (AsHaskell b))
reprToHask = _
-- reprToPlut :: forall s . PLiftedClosed (PThese a b) -> PLifted s (PThese a b)
reprToPlut = _
-- plutToRepr :: (forall s . PLifted s (PThese a b)) -> Either LiftError (PLiftedClosed (PThese a b))
plutToRepr = _
Three notable features of the above definition deserve some explanation. Firstly, we note the duplicate use of mkPLiftedClosed $ pcon
in all three case
arms; an experienced Haskeller would be tempted to factor these out. We have to do this, however, due to the higher-rank polymorphism of mkPLiftedClosed
, which can have some issues with such refactoring. Secondly, we use pconstant
. This is only for convenience - we could replace it with uses of the relevant PLiftable
methods, but this would be longer for no reason. Thirdly, we observe that we must provide explicit type parameters to pconstant
in each arm. This is required because, as we previously mentioned, a given Haskell type may be 'liftable' into Plutarch in multiple ways, thus requiring a type argument to specify what our desired 'target' is[4]. In all other ways, however, this is simply a combination of case
analysis and rewrapping.
reprToHask
poses more of an issue: how do we scrutinize a PLiftedClosed
? Directly, we can't, but once again, Plutarch can come to our rescue. For that purpose, we will define a couple of additional helpers first:
-- We elide kind signatures here, as there is no mixing
pisThis :: Term s (PThese a b :--> PBool)
pisThis = phoistAcyclic $ plam $ \t -> pmatch t $ \case
PThis _ -> pcon PTrue
_ -> pcon PFalse
pisThat :: Term s (PThese a b :--> PBool)
pisThat = phoistAcyclic $ plam $ \t -> pmatch t $ \case
PThat _ -> pcon PTrue
_ -> pcon PFalse
ptryThis :: Term s (PThese a b :--> a)
ptryThis = phoistAcyclic $ plam $ \t -> pmatch t $ \case
PThis x -> x
PThese x _ -> x
PThat _ -> ptraceInfoError "ptryThis: used on a PThat"
ptryThat :: Term s (PThese a b :--> b)
ptryThat = phoistAcyclic $ plam $ \t -> pmatch t $ \case
PThat y -> y
PThese _ y -> y
PThis _ -> ptraceInfoError "ptryThat: used on a PThis"
These functions, together with the fact that Bool
, a
and b
have PLiftable
instances already, means we can use them to scrutinize PLiftedClosed (PThese a b)
. This is a much more 'manual' process than haskToRepr
, but works similarly:
-- Duplicated for clarity
instance (PLiftable a, PLiftable b) => PLiftable (PThese a b) where
type AsHaskell (PThese a b) = These (AsHaskell a) (AsHaskell b)
type PlutusRepr (PThese a b) = PLiftedClosed (PThese a b)
-- Expanded type signatures for these functions for clarity
-- haskToRepr :: These (AsHaskell a) (AsHaskell b) -> PLiftedClosed (PThese a b)
haskToRepr = \case
This x -> mkPLiftedClosed $ pcon $ PThis (pconstant @a x)
That y -> mkPLiftedClosed $ pcon $ PThat (pconstant @b y)
These x y -> mkPLiftedClosed $ pcon $ PThese (pconstant @a x) (pconstant @b y)
-- reprToHask :: PLiftedClosed (PThese a b) -> Either LiftError (These (AsHaskell a) (AsHaskell b))
reprToHask x = do
isThis :: Bool <- plutToRepr $ mkPLifted (pisThis # getPLiftedClosed x)
if isThis
then do
thisR :: PlutusRepr a <- plutToRepr $ mkPLifted (ptryThis # getPLiftedClosed x)
thisH :: AsHaskell a <- reprToHask @a thisR
pure $ This thisH
else do
isThat :: Bool <- plutToRepr $ mkPLifted (pisThat # getPLiftedClosed x)
if isThat
then do
thatR :: PlutusRepr b <- plutToRepr $ mkPLifted (ptryThat # getPLiftedClosed x)
thatH :: AsHaskell b <- reprToHask @b thatR
pure $ That thatH
else do
thisR :: PlutusRepr a <- plutToRepr $ mkPLifted (ptryThis # getPLiftedClosed x)
thatR :: PlutusRepr b <- plutToRepr $ mkPLifted (ptryThat # getPLiftedClosed x)
thisH :: AsHaskell a <- reprToHask @a thisR
thatH :: AsHaskell b <- reprToHask @b thatR
pure $ These thisH thatH
-- reprToPlut :: forall s . PLiftedClosed (PThese a b) -> PLifted s (PThese a b)
reprToPlut = _
-- plutToRepr :: (forall s . PLifted s (PThese a b)) -> Either LiftError (PLiftedClosed (PThese a b))
plutToRepr = _
The definition of reprToHask
above makes use of a standard pattern for performing useful work on a PLiftedClosed
:
Use
getPLiftedClosed
to remove the wrapper to expose the (Plutarch) value its represents.Perform whichever operations we need to produce a 'simpler' (Plutarch) value.
Wrap the result of step 2 into a
PLifted
usingmkPLifted
.Transform the result into something more useful using
plutToRepr
and possiblyreprToHask
.
Essentially, steps 1 and 2 use Plutarch as a fulcrum, together with 'simpler' types, to scrutinize or disassemble our SOP encoding. The reason why our transformation sometimes requires the use of only plutToRepr
and sometimes both plutToRepr
and reprToHask
stems from the fact that Bool
has a builtin representation, whereas a
and b
don't necessarily.
The rest of the definition follows from the description: we verify whether we have a This
or That
, and disassemble them into their fields, then rewrap. If we have neither, we must have a These
, and thus we extract both fields and rewrap. Throughout, we are in Either LiftError
, which in our case doesn't matter, as we cannot fail directly. We need this capability for certain types which are 'smaller' than their Plutarch representations would suggest.
This brings us to the last conversion pair, connecting the Plutarch and Plutus universes. Fortunately for us, PLiftedClosed
does almost all the work for us:
-- Duplicated for clarity
instance (PLiftable a, PLiftable b) => PLiftable (PThese a b) where
type AsHaskell (PThese a b) = These (AsHaskell a) (AsHaskell b)
type PlutusRepr (PThese a b) = PLiftedClosed (PThese a b)
-- Expanded type signatures for these functions for clarity
-- haskToRepr :: These (AsHaskell a) (AsHaskell b) -> PLiftedClosed (PThese a b)
haskToRepr = \case
This x -> mkPLiftedClosed $ pcon $ PThis (pconstant @a x)
That y -> mkPLiftedClosed $ pcon $ PThat (pconstant @b y)
These x y -> mkPLiftedClosed $ pcon $ PThese (pconstant @a x) (pconstant @b y)
-- reprToHask :: PLiftedClosed (PThese a b) -> Either LiftError (These (AsHaskell a) (AsHaskell b))
reprToHask x = do
isThis :: Bool <- plutToRepr $ mkPLifted (pisThis # getPLiftedClosed x)
if isThis
then do
thisR :: PlutusRepr a <- plutToRepr $ mkPLifted (ptryThis # getPLiftedClosed x)
thisH :: AsHaskell a <- reprToHask @a thisR
pure $ This thisH
else do
isThat :: Bool <- plutToRepr $ mkPLifted (pisThat # getPLiftedClosed x)
if isThat
then do
thatR :: PlutusRepr b <- plutToRepr $ mkPLifted (ptryThat # getPLiftedClosed x)
thatH :: AsHaskell b <- reprToHask @b thatR
pure $ That thatH
else do
thisR :: PlutusRepr a <- plutToRepr $ mkPLifted (ptryThis # getPLiftedClosed x)
thatR :: PlutusRepr b <- plutToRepr $ mkPLifted (ptryThat # getPLiftedClosed x)
thisH :: AsHaskell a <- reprToHask @a thisR
thatH :: AsHaskell b <- reprToHask @b thatR
pure $ These thisH thatH
-- reprToPlut :: forall s . PLiftedClosed (PThese a b) -> PLifted s (PThese a b)
reprToPlut = pliftedFromClosed
-- plutToRepr :: (forall s . PLifted s (PThese a b)) -> Either LiftError (PLiftedClosed (PThese a b))
plutToRepr = Right . pliftedToClosed
This follows directly from our earlier statement that PThese
is SOP-encoded, which means its Plutus-level representation is 'some SOP encoding'. Since PLiftedClosed
represents 'some SOP encoding', the conversion is direct.
One last example: Data representation
To finish our examples, we show the definition for a similar type to PThese
but using a Data
representation instead.
data PTheseData (a :: S -> Type) (b :: S -> Type) (s :: S) =
PDThis (Term s (PAsData a)) |
PDThat (Term s (PAsData b)) |
PDThese (Term s (PAsData b)) (Term s (PAsData b))
deriving stock (Generic)
deriving anyclass (SOP.Generic)
deriving via DeriveAsDataStruct (PTheseData a b) instance PlutusType (PTheseData a b)
This is almost the same as PThese
in many ways, with a few important differences:
The constructors are prefixed with
PD
instead ofP
;The name of the type is suffixed with
Data
[3];Each occurrence of
a
orb
in a field must be wrapped withPAsData
;We use
DeriveAsDataStruct
instead ofDeriveAsSOPStruct
for the helper to derivePlutusType
.
Just as for our other two examples, constructing a PLiftable
will involve choosing AsHaskell (PTheseData a b)
and PlutusRepr (PTheseData a b)
. At first glance, it seems that the right choice for AsHaskell (PTheseData a b)
should again be These
from Data.These
. However, there is a better match, in These
from plutus-tx
; in general, if you are defining a Plutarch type with a Data
representation, a plutus-tx
equivalent should be used if it exists. For PlutusRepr (PTheseData a b)
, the choice is straightforward: Data
from plutus-tx
, as that is what having a Data
representation means. This gives us the following (partial) instance:
instance (PLiftable a, PLiftable b) => PLiftable (PTheseData a b) where
type AsHaskell (PTheseData a b) = PTx.These (AsHaskell a) (AsHaskell b)
type PlutusRepr (PTheseData a b) = PTx.Data
-- Expanded type signatures for these functions for clarity
-- haskToRepr :: PTx.These (AsHaskell a) (AsHaskell b) -> PTx.Data
haskToRepr = _
-- reprToHask :: PTx.Data -> Either LiftError (PTx.These (AsHaskell a) (AsHaskell b))
reprToHask = _
-- reprToPlut :: forall s . PTx.Data -> PLifted s (PTheseData a b)
reprToPlut = _
-- plutToRepr :: (forall s . PLifted s (PTheseData a b)) -> Either LiftError PTx.Data
plutToRepr = _
When we consider the (expanded) signatures of haskToRepr
and reprToHask
, we see that these effectively amount to Data
encoding and decoding respectively, with reprToHask
producing a slightly different error type. As These a b
from plutus-tx
is Data
-encodable and decodable if both a
and b
also are, we add these requirements to the prerequisite constraints of our PLiftable
instance, and then borrow the Data
encoding and decoding functionality from plutus-tx
:
-- Duplicated for clarity
instance (PLiftable a,
PLiftable b,
PTx.FromData (AsHaskell a),
PTx.FromData (AsHaskell b),
PTx.ToData (AsHaskell a),
PTx.ToData (AsHaskell b)) => PLiftable (PTheseData a b) where
type AsHaskell (PTheseData a b) = PTx.These (AsHaskell a) (AsHaskell b)
type PlutusRepr (PTheseData a b) = PTx.Data
-- Expanded type signatures for these functions for clarity
-- haskToRepr :: PTx.These (AsHaskell a) (AsHaskell b) -> PTx.Data
haskToRepr = PTx.toData
-- reprToHask :: PTx.Data -> Either LiftError (PTx.These (AsHaskell a) (AsHaskell b))
reprToHask = maybe (Left CouldNotDecodeData) Right . PTx.fromData
-- reprToPlut :: forall s . PTx.Data -> PLifted s (PTheseData a b)
reprToPlut = _
-- plutToRepr :: (forall s . PLifted s (PTheseData a b)) -> Either LiftError PTx.Data
plutToRepr = _
We use the CouldNotDecodeData
constructor of LiftError
to indicate Data
decoding failures. Our definitions for reprToPlut
and plutToRepr
are similarly straightforward: PTheseData a b
are just Data
underneath it all as far as Plutus is concerned. Since Data
is a part of the Plutus default universe, we can use helpers from Plutarch to define the rest:
-- Duplicated for clarity
instance (PLiftable a,
PLiftable b,
PTx.FromData (AsHaskell a),
PTx.FromData (AsHaskell b),
PTx.ToData (AsHaskell a),
PTx.ToData (AsHaskell b)) => PLiftable (PTheseData a b) where
type AsHaskell (PTheseData a b) = PTx.These (AsHaskell a) (AsHaskell b)
type PlutusRepr (PTheseData a b) = PTx.Data
-- Expanded type signatures for these functions for clarity
-- haskToRepr :: PTx.These (AsHaskell a) (AsHaskell b) -> PTx.Data
haskToRepr = PTx.toData
-- reprToHask :: PTx.Data -> Either LiftError (PTx.These (AsHaskell a) (AsHaskell b))
reprToHask = maybe (Left CouldNotDecodeData) Right . PTx.fromData
-- reprToPlut :: forall s . PTx.Data -> PLifted s (PTheseData a b)
reprToPlut = reprToPlutUni
-- plutToRepr :: (forall s . PLifted s (PTheseData a b)) -> Either LiftError PTx.Data
plutToRepr = plutToReprUni
The pair of functions reprToPlutUni
and plutToReprUni
are valid definitions for reprToPlut
and plutToRepr
respectively, provided the source and target type respectively are members of the default Plutus universe. With this, our instance is done.
Helpers for PLiftable
Our examples are an unfortunate combination of tedious, error-prone and completely cookbook for most types. Rather than forcing us to write such instances manually, Plutarch provides multiple derivation helpers, designed for use with deriving via
, which automate most of this drudgery away. While some manual instances are needed on occasion, these derivation helpers mean that most projects will never need a manual instance for any of their types.
We will begin by presenting the three most 'typical' helpers:
DeriveBuiltinPLiftable a h
, which states thata
should be treated as the Plutarch equivalent ofh
, and thath
is directly part of the Plutus default universe.DeriveDataPLiftable a h
, which states thata
should be treated as the Plutarch equivalent ofh
, and thath
has aData
encoding.DeriveNewtypePLiftable wrapper h
, which states thatwrapper
should be treated as the Plutarch equivalent ofh
by 'borrowing' the instance ofPInner wrapper
.
These helpers cover many typical cases. For example, we can replace our entire first example instance with the following:
deriving via DeriveNewtypePLiftable PByteVector ByteString
instance PLiftable PByteVector
And our third example instance with the following:
deriving via DeriveDataPLiftable (PTheseData a b) (PTx.These (AsHaskell a) (AsHaskell b))
instance (PTx.ToData a, PTx.ToData b, PTx.FromData a, PTx.FromData b) =>
PLiftable (PTheseData a b)
While the rewritten third example is still somewhat wordy due to the constraints we have to provide, both of the rewritten versions are much shorter, and less error-prone, than the manual methods we showed previously. Furthermore, we can see a useful property of these derivations: they check that any requirements have been met, and notify the user if something is missing.
These three helpers cover the most typical situations a Plutarch application developer would need. However, some specific situations allow more efficient encodings than these. One helper Plutarch provides fitting this description is DeriveTagPLiftable
, which can be used on sum types with no fields ('enums', essentially). This encoding represents such types as Integer
s via their builtin representation. We can use this helper in the following way:
-- Haskell-level type
data Answer = Yes | No | Unknown
deriving stock (Generic)
deriving anyclass (SOP.Generic)
-- Plutarch equivalent
data PAnswer (s :: S) = PYes | PNo | PUnknown
deriving stock (Generic)
deriving anyclass (SOP.Generic)
deriving via (DeriveTagPlutusType PAnswer) instance PlutusType PAnswer
deriving via (DeriveTagPLiftable PAnswer Answer) instance PLiftable PAnswer
Lastly, Plutarch provides[7] a truly general helper in DerivePLiftableAsRepr
. This will use the definition of PlutusType
(whether derived or not), along with some constraint checks over the structure of the data type it's applied to, to derive whatever representation seems sensible. This is currently the only way to automatically derive SOP representation PLiftable
instances. We can use it to replace our second example:
deriving via DerivePLiftableAsRepr (PThese a b) (These (AsHaskell a) (AsHaskell b))
instance (PLiftable a, PLiftable b) => PLiftable (PThese a b)
However, DerivePLiftableAsRepr
is not limited to SOP representations: it can be used for Data
and even builtin representations too. While the convenience seems like an obvious choice in all circumstances, we do not export it globally as it can sometimes have unexpected, but silent, results when small refactors happen. Thus, if possible, we recommend using a 'narrower' helper to protect you from accidental surprises when refactoring.
Conclusion
There are many challenges to writing Cardano scripts, particularly with regard to performance. Plutarch's stated goal is to make performance both possible and accessible, and it achieves this through a range of features. PLiftable
is one such feature: by allowing precise control over representation choices where needed but still giving easy and convenient defaults.
We have seen both the 'low-level' and 'high-level' use of PLiftable
, across all three representation choices Plutarch supports for onchain data. While doing so, we have seen how Plutarch offers help at every level, whether through helpers like PLiftedClosed
for low-level instances, or through deriving via
helpers like DeriveTagPLiftable
. While it shouldn't be necessary for most application developers to write PLiftable
instances by hand, the option exists for cases where control over representation is paramount. However, common cases are covered by simpler and less verbose helpers.
We believe that PLiftable
is the beginning of a better Plutarch. Unlike the mechanisms it replaced, it is clearer, more law-abiding and easier to use. We feel that the design of PLiftable
strikes a good balance between being straightforward for common cases and also giving total manual control where needed. Furthermore, the laws provided for PLiftable
allow application developers to test their PLiftable
instances in ways the previous mechanisms simply didn't allow for. The improvements to Plutarch itself that PLiftable
enabled were considerable: we are confident that application code will benefit just as much, if not more.
We hope this article encourages more Plutarch developers to leverage PLiftable for clear, efficient on-chain data representations. If you’re building Cardano scripts and need support integrating these patterns into your codebase—or want to explore how Plutarch can improve performance and correctness—please reach out.
- You could also derive Generic from generics-sop more directly using Template Haskell if you prefer.
- To be more precise, this is needed for coerceing for via-deriving helpers, as Term is nominal in both of its type parameters. This is for good reason, but the convenience of via derivations is such that we felt this extra layer of indirection in PLiftable instances was an acceptable cost.
- Both of these are conventions in Plutarch itself. You can see this with PMaybe versus PMaybeData, PRational versus PRationalData, and others. Following these conventions for your own types is a good idea if you ever plan to have both a Data and an SOP representation for an equivalent type: not only is this less confusing, it will also be clearer to other developers familiar with Plutarch.
- More specifically, the reason for us having to use a manual type parameter is because for any instance of PLiftable a, a determines AsHaskell a, but not the other way around, as associated type families are not necessarily injective.
- Technically there is a fourth option (the Scott representation), but as it is completely superceded by the SOP representation in both generality and performance, we will not discuss it here.
- Fans of category theory will note that this is a commutative diagram.
- Via an internal module for now.