Skip to content

Commit

Permalink
Merge pull request #1105 from michaelpj/imp/tutorial-callouts
Browse files Browse the repository at this point in the history
plutus-tutorial: revamp
  • Loading branch information
michaelpj authored Jun 6, 2019
2 parents e48da94 + 1c4b0ab commit 4824cea
Show file tree
Hide file tree
Showing 19 changed files with 589 additions and 1,582 deletions.
14 changes: 2 additions & 12 deletions pkgs/default.nix

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 2 additions & 0 deletions plutus-tutorial/.gitignore
Original file line number Diff line number Diff line change
@@ -1 +1,3 @@
*.html
asciidoctor.css
pygments-tango.css
109 changes: 55 additions & 54 deletions plutus-tutorial/doc/01-plutus-tx.adoc
Original file line number Diff line number Diff line change
Expand Up @@ -13,9 +13,7 @@ in a transaction, hence the "Tx").

This means that Plutus Tx _is just Haskell_. Strictly, only a subset of
Haskell is supported, but most simple Haskell should work, and the
compiler will tell you if you use something that is unsupported. (See
link:../../../plutus-tx/README.md#haskell-language-support[Haskell
language support] for more details on what is supported.)
compiler will tell you if you use something that is unsupported.

The key technique that the Plutus Platform uses is called _staged
metaprogramming_. What that means is that the main Haskell program
Expand All @@ -35,25 +33,27 @@ share types and defintions between the two.
{-# LANGUAGE ScopedTypeVariables #-}
module Tutorial.PlutusTx where
-- Main Plutus Tx module
import Language.PlutusTx
-- Additional support for lifting
import Language.PlutusTx.Lift
-- Builtin functions
import Language.PlutusTx.Builtins
import Language.PlutusTx -- <1>
import Language.PlutusTx.Lift -- <2>
import Language.PlutusTx.Builtins -- <3>
-- Used for examples
import Language.PlutusCore
import Language.PlutusCore.Pretty
import Language.PlutusCore.Quote
import Language.PlutusCore.Evaluation.CkMachine
import Data.Text.Prettyprint.Doc
import Data.Text.Prettyprint.Doc -- <4>
----
<1> Main Plutus Tx module.
<2> Additional support for lifting.
<3> Builtin functions.
<4> Used for examples.

Plutus Tx makes some use of Template Haskell. There are a few reasons
for this: - Template Haskell allows us to do work at compile time, which
is when we do Plutus Tx compilation. - It allows us to wire up the
machinery that actually invokes the Plutus Tx compiler.
for this:

. Template Haskell allows us to do work at compile time, which
is when we do Plutus Tx compilation.
. It allows us to wire up the machinery that actually invokes the Plutus Tx compiler.

Consequently, we will see some use of Template Haskell quotes. A
Template Haskell quote is introduced with the special brackets `[||` and
Expand All @@ -62,12 +62,12 @@ expression of type `a`, which lives in the `Q` type of quotes. You can
splice a definition with this type into your program using the `$$`
operator.

(There is also an abbreviation `TExpQ a` for `Q (TExp a)`, which avoids
some parentheses.)
NOTE: There is also an abbreviation `TExpQ a` for `Q (TExp a)`, which avoids
some parentheses.

The key function we will use is the `compile` function. `compile` has
type `Q (TExp a) -> Q (TExp (CompiledCode a))`. What does this mean? -
`Q` and `TExp` we have already seen - `CompiledCode a` is a compiled
type `TExpQ a -> TExpQ (CompiledCode a)`. What does this mean? -
`TExpQ` we have already seen - `CompiledCode a` is a compiled
Plutus Core program corresponding to a Haskell program of type `a`

What this means is that `compile` lets you take a (quoted) Haskell
Expand All @@ -89,7 +89,7 @@ write inside the quote is just normal Haskell.
Here’s the most basic program we can write: one that just evaluates to
the integer `1`.

The Plutus Core syntax will look unfamiliar. This is fine, since it is
NOTE: The Plutus Core syntax will look unfamiliar. This is fine, since it is
the "assembly language" and you won’t need to inspect the output of
the compiler. However, for the purposes of this tutorial it’s
instructive to look at it to get a vague idea of what’s going on.
Expand All @@ -103,16 +103,16 @@ instructive to look at it to get a vague idea of what’s going on.
)
-}
integerOne :: CompiledCode Integer
integerOne = $$( -- The splice inserts the `Q (CompiledCode Integer)` into the program
-- compile turns the `Q Integer` into a `Q (CompiledCode Integer)`
compile
-- The quote has type `Q Integer`
[||
-- We always use unbounded integers in Plutus Core, so we have to pin
-- down this numeric literal to an `Integer` rather than an `Int`
(1 :: Integer)
||])
integerOne = $$(compile -- <3> <4>
[|| -- <2>
(1 :: Integer) -- <1>
||])
----
<1> We always use unbounded integers in Plutus Core, so we have to pin
down this numeric literal to an `Integer` rather than an `Int`.
<2> The quote has type `TExpQ Integer`.
<3> `compile` turns the `TExpQ Integer` into a `TExpQ (CompiledCode Integer)`.
<4> The splice inserts the `TExpQ (CompiledCode Integer)` into the program.

We can see how the metaprogramming works here: the Haskell program `1`
was turned into a `CompiledCode Integer` at compile time, which we
Expand Down Expand Up @@ -144,37 +144,34 @@ So far, so familiar: we compiled a lambda into a lambda (the "lam").

== Functions and datatypes

You can also use functions inside your expression. In practice, you may
well want to define the entirety of your Plutus Tx program as a
You can also use functions inside your expression. In practice, you
will usually want to define the entirety of your Plutus Tx program as a
definition outside the quote, and then simply call it inside the quote.

[source,haskell]
----
{-# INLINABLE plusOne #-}
{-# INLINABLE plusOne #-} -- <2>
plusOne :: Integer -> Integer
plusOne x = x `addInteger` 1
plusOne x = x `addInteger` 1 -- <1>
{-# INLINABLE myProgram #-}
{-# INLINABLE myProgram #-} -- <2>
myProgram :: Integer
myProgram =
let
plusOneLocal :: Integer -> Integer
plusOneLocal x = x `addInteger` 1
plusOneLocal x = x `addInteger` 1 -- <1>
localPlus = plusOneLocal 1
externalPlus = plusOne 1
in localPlus `addInteger` externalPlus
in localPlus `addInteger` externalPlus -- <1>
functions :: CompiledCode Integer
functions = $$(compile [|| myProgram ||])
----

Here we used the function `addInteger` from
`Language.PlutusTx.Builtins`, which is mapped on the builtin integer
addition in Plutus Core.

The previous example marked the functions that we used using GHC’s
`INLINABLE` pragma. This is usually necessary for non-local functions to
<1> `addInteger` comes from `Language.PlutusTx.Builtins`, and is
which is mapped to the builtin integer addition in Plutus Core.
<2> Functions for reuse are marked with GHC’s `INLINABLE` pragma.
This is usually necessary for non-local functions to
be usable in Plutus Tx blocks, as it instructs GHC to keep the
information that the Plutus Tx compiler needs. While this is not always
necessary, it is a good idea to simply mark all such functions as
Expand All @@ -191,8 +188,9 @@ matchMaybe = $$(compile [|| \(x:: Maybe Integer) -> case x of
||])
----

Unlike functions, datatypes do not need to be defined inside the
expression, hence why we can use types like `Maybe` from the `Prelude`.
Unlike functions, datatypes do not need any kind of special annotation to be
used inside the
expression, hence we can use types like `Maybe` from the `Prelude`.
This works for your own datatypes too!

Here’s a small example with a datatype of our own representing a
Expand Down Expand Up @@ -255,7 +253,8 @@ program that computes to `5`. Well, we need to _lift_ the argument (`4`)
from Haskell to Plutus Core, and then we need to apply the function to
it.

....
[source,haskell]
----
{- |
>>> let program = addOneToN 4
>>> pretty program
Expand All @@ -276,18 +275,24 @@ it.
(con 8 ! 5)
-}
addOneToN :: Integer -> CompiledCode Integer
addOneToN n = addOne `applyCode` unsafeLiftCode n
....
addOneToN n =
addOne
`applyCode` -- <1>
unsafeLiftCode n -- <2>
----
<1> `applyCode` applies one `CompiledCode` to another.
<2> `unsafeLiftCode` lifts the argument `n` into a `CompiledCode Integer`.

We lifted the argument `n` using the `unsafeLiftCode` function
("unsafe" because we’re ignoring any errors that might occur from
lifting something that we don’t support). In order to use this, a type
We lifted the argument using the `unsafeLiftCode` function. In order to use this, a type
must have an instance of the `Lift` class. In practice, you should
generate these with the `makeLift` TH function from
`Language.PlutusTx.Lift`. Lifting makes it easy to use the same types
both inside your Plutus Tx program and in the external code that uses
it.

NOTE: `unsafeLiftCode` is "unsafe" because it ignores any errors that might occur from
lifting something that isn't supported.

The combined program applies the original compiled lambda to the lifted
value (notice that the lambda is a bit complicated now since we have
compiled the addition into a builtin). We’ve then used the CK evaluator
Expand Down Expand Up @@ -316,7 +321,3 @@ pastEndAt end current =
`applyCode`
unsafeLiftCode current
----

The xref:02-validator-scripts#validator-scripts[next part] of the tutorial explains
how to get Plutus onto the blockchain, using a simple guessing game as
an example.
Loading

0 comments on commit 4824cea

Please sign in to comment.