Plutus.V1.Ledger.Credential

  • 1. 📜 Overview

  • 2. đź”§ LANGUAGE EXTENSIONS AND IMPORTS

  • 3. 🗄️ Data Types

    • 3.1 🌾 StakingCredential

    • 3.2 🛂 Credential

  • 4. 🤝 Typeclass Instances

  • 5. 🏭 On‑chain Derivations

  • 6. 📚 Glossary


1 📜 Overview

The Plutus.V1.Ledger.Credential module defines how spending and staking rights are represented on‑chain:

  • StakingCredential: credentials used for staking rewards.

  • Credential: credentials required to unlock a transaction output (either a public key or a script).

  • Implements Pretty and on‑chain equality (PlutusTx.Eq) for both types.

  • Derives serialization and lifting instances for on‑chain use.


2 đź”§ LANGUAGE EXTENSIONS AND IMPORTS

{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DeriveAnyClass             #-}
{-# LANGUAGE DerivingVia                #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE TemplateHaskell            #-}
{-# OPTIONS_GHC -fno-specialise                      #-}
{-# OPTIONS_GHC -Wno-simplifiable-class-constraints #-}
{-# OPTIONS_GHC -fno-omit-interface-pragmas         #-}

module Plutus.V1.Ledger.Credential (
    StakingCredential(..)
  , Credential(..)
  ) where

import Control.DeepSeq (NFData)
import GHC.Generics    (Generic)
import Plutus.V1.Ledger.Crypto   (PubKeyHash)
import Plutus.V1.Ledger.Scripts  (ValidatorHash)
import PlutusTx                  qualified as PlutusTx
import PlutusTx.Bool             qualified as PlutusTx
import PlutusTx.Eq               qualified as PlutusTx
import Prettyprinter             (Pretty(..), (<+>))
  • Pragmas:

    • DataKinds, DeriveAnyClass, DerivingVia, OverloadedStrings, TemplateHaskell for deriving and on‑chain support.

    • Compiler options to control specialization and interface pragmas.

  • Imports:

    • NFData, Generic for deep evaluation and generic deriving.

    • PubKeyHash, ValidatorHash for credential types.

    • PlutusTx modules for on‑chain equality and serialization.

    • Prettyprinter for human‑readable instances.


3 🗄️ Data Types

3.1 🌾 StakingCredential

data StakingCredential
    = StakingHash Credential
    | StakingPtr Integer Integer Integer
    deriving stock (Eq, Ord, Show, Generic)
    deriving anyclass (NFData)
  • Constructors:

    • StakingHash Credential: staking via a hash of a payment credential.

    • StakingPtr i j k: pointer to a certificate (slot, tx index, cert index).

  • Use case: associates staking rewards with credentials.

3.2 🛂 Credential

data Credential
  = PubKeyCredential PubKeyHash
  | ScriptCredential ValidatorHash
    deriving stock (Eq, Ord, Show, Generic)
    deriving anyclass (NFData)
  • Constructors:

    • PubKeyCredential pkh: unlocked by a signature matching pkh.

    • ScriptCredential vh: unlocked by providing a validator script with hash vh.

  • Use case: specifies how an output can be spent.


4 🤝 Typeclass Instances

instance Pretty StakingCredential where
    pretty (StakingHash h)    = "StakingHash" <+> pretty h
    pretty (StakingPtr a b c) = "StakingPtr:" <+> pretty a <+> pretty b <+> pretty c
  • Class: Pretty from Prettyprinter.

  • Behavior: formats each constructor with its contents.

instance PlutusTx.Eq StakingCredential where
    {-# INLINABLE (==) #-}
    StakingHash l == StakingHash r         = l PlutusTx.== r
    StakingPtr a b c == StakingPtr a' b' c' = a PlutusTx.== a'
                                          PlutusTx.&& b PlutusTx.== b'
                                          PlutusTx.&& c PlutusTx.== c'
    _ == _                                 = False
  • Class: Eq from PlutusTx, used in on‑chain code.

  • Behavior: memberwise equality, INLINABLE for compiler support.

instance Pretty Credential where
    pretty (PubKeyCredential pkh)  = "PubKeyCredential:" <+> pretty pkh
    pretty (ScriptCredential vh) = "ScriptCredential:" <+> pretty vh
  • Formats credentials with labels.

instance PlutusTx.Eq Credential where
    {-# INLINABLE (==) #-}
    PubKeyCredential l == PubKeyCredential r   = l PlutusTx.== r
    ScriptCredential a == ScriptCredential a'  = a PlutusTx.== a'
    _ == _                                   = False
  • Compares credentials by matching constructor and underlying hash.


5 🏭 On‑chain Derivations

PlutusTx.makeIsDataIndexed ''Credential
    [('PubKeyCredential,0),('ScriptCredential,1)]
PlutusTx.makeIsDataIndexed ''StakingCredential
    [('StakingHash,0),('StakingPtr,1)]
PlutusTx.makeLift ''Credential
PlutusTx.makeLift ''StakingCredential
  • makeIsDataIndexed: generates IsData for serializing to Plutus Core, with explicit constructor indices.

  • makeLift: generates Lift instances to embed Haskell values in on‑chain code.


6 📚 Glossary

  • StakingCredential: credential for staking rewards, either hash or pointer.

  • Credential: spending credential, either public key or script hash.

  • PubKeyHash: hash of a public key.

  • ValidatorHash: hash of a validator script.

  • NFData: class for deep (normal form) evaluation.

  • Generic: GHC generics for deriving boilerplate.

  • Pretty: class for pretty printing.

  • PlutusTx.Eq: on‑chain equality class.

  • makeIsDataIndexed: Template Haskell for on‑chain data serialization.

  • makeLift: Template Haskell for lifting values into PlutusTx code.

Last updated