diff --git a/plutus-ledger-api/src/PlutusLedgerApi/V1/Bytes.hs b/plutus-ledger-api/src/PlutusLedgerApi/V1/Bytes.hs index e45303c9d54..172fbd96f8e 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/V1/Bytes.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/V1/Bytes.hs @@ -28,12 +28,14 @@ import PlutusTx import PlutusTx.Prelude qualified as P import Prettyprinter.Extras (Pretty, PrettyShow (..)) +{- | An error that is encountered when converting a `ByteString` to a `LedgerBytes`. -} data LedgerBytesError = - UnpairedDigit - | NotHexit Char + UnpairedDigit -- ^ Odd number of bytes. + | NotHexit Char -- ^ Not a hex digit. deriving stock (Show) deriving anyclass (Exception) +{- | Convert a hex encoded `ByteString` to a `LedgerBytes`. May return an error (`LedgerBytesError`). -} fromHex :: BS.ByteString -> Either LedgerBytesError LedgerBytes fromHex = fmap (LedgerBytes . P.toBuiltin) . asBSLiteral where @@ -76,12 +78,17 @@ bytes = P.fromBuiltin . getLedgerBytes fromBytes :: BS.ByteString -> LedgerBytes fromBytes = LedgerBytes . P.toBuiltin +{- | The `IsString` instance of `LedgerBytes` could throw an exception of `LedgerBytesError`. -} instance IsString LedgerBytes where fromString = unsafeFromEither . fromHex . fromString +{- | The `Show` instance of `LedgerBytes` is its base16/hex encoded bytestring, +decoded with UTF-8, unpacked to `String`. -} instance Show LedgerBytes where show = Text.unpack . encodeByteString . bytes +{- | Encode a ByteString value in base16 (i.e. hexadecimal), then +decode with UTF-8 to a `Text`. -} encodeByteString :: BS.ByteString -> Text.Text encodeByteString = TE.decodeUtf8 . Base16.encode diff --git a/plutus-ledger-api/src/PlutusLedgerApi/V1/Contexts.hs b/plutus-ledger-api/src/PlutusLedgerApi/V1/Contexts.hs index d064ae3ca52..e50ac12a147 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/V1/Contexts.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/V1/Contexts.hs @@ -227,7 +227,7 @@ pubKeyOutput :: TxOut -> Maybe PubKeyHash pubKeyOutput TxOut{txOutAddress} = toPubKeyHash txOutAddress {-# INLINABLE ownHashes #-} --- | Get the validator and datum hashes of the output that is curently being validated +-- | Get the validator and datum hashes of the output that is currently being validated ownHashes :: ScriptContext -> (ValidatorHash, DatumHash) ownHashes (findOwnInput -> Just TxInInfo{txInInfoResolved=TxOut{txOutAddress=Address (ScriptCredential s) _, txOutDatumHash=Just dh}}) = (s,dh) ownHashes _ = traceError "Lg" -- "Can't get validator and datum hashes" diff --git a/plutus-ledger-api/src/PlutusLedgerApi/V1/Credential.hs b/plutus-ledger-api/src/PlutusLedgerApi/V1/Credential.hs index a06e00b8017..7fafb451d70 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/V1/Credential.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/V1/Credential.hs @@ -17,15 +17,25 @@ import Control.DeepSeq (NFData) import GHC.Generics (Generic) import PlutusLedgerApi.V1.Crypto (PubKeyHash) import PlutusLedgerApi.V1.Scripts (ValidatorHash) -import PlutusTx qualified as PlutusTx +import PlutusTx qualified import PlutusTx.Bool qualified as PlutusTx import PlutusTx.Eq qualified as PlutusTx import Prettyprinter (Pretty (..), (<+>)) --- | Staking credential used to assign rewards +-- | Staking credential used to assign rewards. data StakingCredential + -- | The staking hash is the `Credential` required to unlock a transaction output. Either + -- a public key credential (`Crypto.PubKeyHash`) or + -- a script credential (`Scripts.ValidatorHash`). Both are hashed with /BLAKE2b-244/. 28 byte. = StakingHash Credential - | StakingPtr Integer Integer Integer -- NB: The fields should really be Word64 / Natural / Natural, but 'Integer' is our only integral type so we need to use it instead. + -- | The certificate pointer, constructed by the given + -- slot number, transaction and certificate indices. + -- NB: The fields should really be all `Word64`, as they are implemented in `Word64`, + -- but 'Integer' is our only integral type so we need to use it instead. + | StakingPtr + Integer -- ^ the slot number + Integer -- ^ the transaction index (within the block) + Integer -- ^ the certificate index (within the transaction) deriving stock (Eq, Ord, Show, Generic) deriving anyclass (NFData) @@ -42,10 +52,15 @@ instance PlutusTx.Eq StakingCredential where PlutusTx.&& c PlutusTx.== c' _ == _ = False --- | Credential required to unlock a transaction output +-- | Credentials required to unlock a transaction output. data Credential - = PubKeyCredential PubKeyHash -- ^ The transaction that spends this output must be signed by the private key - | ScriptCredential ValidatorHash -- ^ The transaction that spends this output must include the validator script and be accepted by the validator. + = + -- | The transaction that spends this output must be signed by the private key. + -- See `Crypto.PubKeyHash`. + PubKeyCredential PubKeyHash + -- | The transaction that spends this output must include the validator script and + -- be accepted by the validator. See `Scripts.ValidatorHash`. + | ScriptCredential ValidatorHash deriving stock (Eq, Ord, Show, Generic) deriving anyclass (NFData) diff --git a/plutus-ledger-api/src/PlutusLedgerApi/V1/Crypto.hs b/plutus-ledger-api/src/PlutusLedgerApi/V1/Crypto.hs index 997bdd63f35..f61ccce2071 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/V1/Crypto.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/V1/Crypto.hs @@ -18,11 +18,20 @@ import PlutusTx.Lift (makeLift) import PlutusTx.Prelude qualified as PlutusTx import Prettyprinter --- | The hash of a public key. This is frequently used to identify the public key, rather than the key itself. +{- | The hash of a public key. This is frequently used to identify the public key, +rather than the key itself. Hashed with /BLAKE2b-224/. 28 bytes. + +This is a simple type without any validation, __use with caution__. +You may want to add checks for its invariants. See the + [Shelley ledger specification](https://hydra.iohk.io/build/16861845/download/1/ledger-spec.pdf). +-} newtype PubKeyHash = PubKeyHash { getPubKeyHash :: PlutusTx.BuiltinByteString } deriving stock (Eq, Ord, Generic) deriving anyclass (NFData) deriving newtype (PlutusTx.Eq, PlutusTx.Ord, PlutusTx.ToData, PlutusTx.FromData, PlutusTx.UnsafeFromData) - deriving IsString via LedgerBytes - deriving (Show, Pretty) via LedgerBytes + deriving + (IsString -- ^ from hex encoding + , Show -- ^ using hex encoding + , Pretty -- ^ using hex encoding + ) via LedgerBytes makeLift ''PubKeyHash diff --git a/plutus-ledger-api/src/PlutusLedgerApi/V1/DCert.hs b/plutus-ledger-api/src/PlutusLedgerApi/V1/DCert.hs index df269922707..00ce3623030 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/V1/DCert.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/V1/DCert.hs @@ -15,7 +15,7 @@ import Control.DeepSeq (NFData) import GHC.Generics (Generic) import PlutusLedgerApi.V1.Credential (StakingCredential) import PlutusLedgerApi.V1.Crypto (PubKeyHash) -import PlutusTx qualified as PlutusTx +import PlutusTx qualified import PlutusTx.Prelude qualified as P import Prettyprinter.Extras diff --git a/plutus-ledger-api/src/PlutusLedgerApi/V1/Scripts.hs b/plutus-ledger-api/src/PlutusLedgerApi/V1/Scripts.hs index 551229643a3..b9b66e0f855 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/V1/Scripts.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/V1/Scripts.hs @@ -223,50 +223,104 @@ newtype StakeValidator = StakeValidator { getStakeValidator :: Script } instance Haskell.Show StakeValidator where show = const "StakeValidator {