Skip to content

Commit

Permalink
PLT-712: Update and add Haddock to some functions in `plutus-ledger-a…
Browse files Browse the repository at this point in the history
…pi`. (IntersectMBO#4814)

* Document lengths of ByteString newtypes.

* Document instances that use hex.

* Add haddock.

* Apply suggestions from code review

Co-authored-by: Jared Corduan <[email protected]>

* Apply suggestions from Nikos.

* Apply suggestions from code review

Co-authored-by: Michael Peyton Jones <[email protected]>

Co-authored-by: Zaabson <[email protected]>
Co-authored-by: Jared Corduan <[email protected]>
Co-authored-by: Michael Peyton Jones <[email protected]>
  • Loading branch information
4 people authored and brainrake committed Dec 8, 2022
1 parent 13930ba commit ecad3b4
Show file tree
Hide file tree
Showing 10 changed files with 189 additions and 83 deletions.
11 changes: 9 additions & 2 deletions plutus-ledger-api/src/PlutusLedgerApi/V1/Bytes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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

Expand Down
2 changes: 1 addition & 1 deletion plutus-ledger-api/src/PlutusLedgerApi/V1/Contexts.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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"
Expand Down
27 changes: 21 additions & 6 deletions plutus-ledger-api/src/PlutusLedgerApi/V1/Credential.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)

Expand All @@ -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)

Expand Down
15 changes: 12 additions & 3 deletions plutus-ledger-api/src/PlutusLedgerApi/V1/Crypto.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
2 changes: 1 addition & 1 deletion plutus-ledger-api/src/PlutusLedgerApi/V1/DCert.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand Down
78 changes: 66 additions & 12 deletions plutus-ledger-api/src/PlutusLedgerApi/V1/Scripts.hs
Original file line number Diff line number Diff line change
Expand Up @@ -223,50 +223,104 @@ newtype StakeValidator = StakeValidator { getStakeValidator :: Script }
instance Haskell.Show StakeValidator where
show = const "StakeValidator { <script> }"

-- | Script runtime representation of a @Digest SHA256@.
{- | Type representing the /BLAKE2b-224/ hash of a script. 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 ScriptHash =
ScriptHash { getScriptHash :: Builtins.BuiltinByteString }
deriving (IsString, Haskell.Show, Pretty) via LedgerBytes
deriving
(IsString -- ^ from hex encoding
, Haskell.Show -- ^ using hex encoding
, Pretty -- ^ using hex encoding
) via LedgerBytes
deriving stock (Generic)
deriving newtype (Haskell.Eq, Haskell.Ord, Eq, Ord, ToData, FromData, UnsafeFromData)
deriving anyclass (NFData)

-- | Script runtime representation of a @Digest SHA256@.
{- | Type representing the /BLAKE2b-224/ hash of a validator. 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 ValidatorHash =
ValidatorHash Builtins.BuiltinByteString
deriving (IsString, Haskell.Show, Pretty) via LedgerBytes
deriving
(IsString -- ^ from hex encoding
, Haskell.Show -- ^ using hex encoding
, Pretty -- ^ using hex encoding
) via LedgerBytes
deriving stock (Generic)
deriving newtype (Haskell.Eq, Haskell.Ord, Eq, Ord, ToData, FromData, UnsafeFromData)
deriving anyclass (NFData)

-- | Script runtime representation of a @Digest SHA256@.
{- | Type representing the /BLAKE2b-256/ hash of a datum. 32 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 DatumHash =
DatumHash Builtins.BuiltinByteString
deriving (IsString, Haskell.Show, Pretty) via LedgerBytes
deriving
(IsString -- ^ from hex encoding
, Haskell.Show -- ^ using hex encoding
, Pretty -- ^ using hex encoding
) via LedgerBytes
deriving stock (Generic)
deriving newtype (Haskell.Eq, Haskell.Ord, Eq, Ord, ToData, FromData, UnsafeFromData)
deriving anyclass (NFData)

-- | Script runtime representation of a @Digest SHA256@.
{- | Type representing the /BLAKE2b-256/ hash of a redeemer. 32 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 RedeemerHash =
RedeemerHash Builtins.BuiltinByteString
deriving (IsString, Haskell.Show, Pretty) via LedgerBytes
deriving
(IsString -- ^ from hex encoding
, Haskell.Show -- ^ using hex encoding
, Pretty -- ^ using hex encoding
) via LedgerBytes
deriving stock (Generic)
deriving newtype (Haskell.Eq, Haskell.Ord, Eq, Ord, ToData, FromData, UnsafeFromData)
deriving anyclass (NFData)

-- | Script runtime representation of a @Digest SHA256@.
{- | Type representing the /BLAKE2b-224/ hash of a minting policy. 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 MintingPolicyHash =
MintingPolicyHash Builtins.BuiltinByteString
deriving (IsString, Haskell.Show, Pretty) via LedgerBytes
deriving
(IsString -- ^ from hex encoding
, Haskell.Show -- ^ using hex encoding
, Pretty -- ^ using hex encoding
) via LedgerBytes
deriving stock (Generic)
deriving newtype (Haskell.Eq, Haskell.Ord, Eq, Ord, ToData, FromData, UnsafeFromData)
deriving anyclass (NFData)

-- | Script runtime representation of a @Digest SHA256@.
{- | Type representing the /BLAKE2b-224/ hash of a stake validator. 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 StakeValidatorHash =
StakeValidatorHash Builtins.BuiltinByteString
deriving (IsString, Haskell.Show, Pretty) via LedgerBytes
deriving
(IsString -- ^ from hex encoding
, Haskell.Show -- ^ using hex encoding
, Pretty -- ^ using hex encoding
) via LedgerBytes
deriving stock (Generic)
deriving newtype (Haskell.Eq, Haskell.Ord, Eq, Ord, ToData, FromData, UnsafeFromData)
deriving anyclass (NFData)
Expand Down
3 changes: 2 additions & 1 deletion plutus-ledger-api/src/PlutusLedgerApi/V1/Time.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,8 @@ newtype DiffMilliSeconds = DiffMilliSeconds Integer

makeLift ''DiffMilliSeconds

-- | POSIX time is measured as the number of milliseconds since 1970-01-01T00:00:00Z
-- | POSIX time is measured as the number of /milliseconds/ since 1970-01-01T00:00:00Z.
-- This is not the same as Haskell's `Data.Time.Clock.POSIX.POSIXTime`
newtype POSIXTime = POSIXTime { getPOSIXTime :: Integer }
deriving stock (Haskell.Eq, Haskell.Ord, Haskell.Show, Generic)
deriving anyclass (NFData)
Expand Down
25 changes: 17 additions & 8 deletions plutus-ledger-api/src/PlutusLedgerApi/V1/Tx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,32 +48,41 @@ import PlutusLedgerApi.V1.Bytes
import PlutusLedgerApi.V1.Crypto
import PlutusLedgerApi.V1.Scripts
import PlutusLedgerApi.V1.Value
{- | A transaction ID, i.e. the hash of a transaction. Hashed with BLAKE2b-256. 32 byte.
-- | A transaction ID, using a SHA256 hash as the transaction id.
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 TxId = TxId { getTxId :: PlutusTx.BuiltinByteString }
deriving stock (Eq, Ord, Generic)
deriving anyclass (NFData)
deriving newtype (PlutusTx.Eq, PlutusTx.Ord)
deriving (Show, Pretty, IsString) via LedgerBytes
deriving
(IsString -- ^ from hex encoding
, Show -- ^ using hex encoding
, Pretty -- ^ using hex encoding
) via LedgerBytes

-- | A tag indicating the type of script that we are pointing to.
data ScriptTag = Spend | Mint | Cert | Reward
deriving stock (Show, Eq, Ord, Generic)
deriving anyclass (NFData)

-- | A redeemer pointer is a pair of a script type tag t and an index i, picking out the ith
-- script of type t in the transaction.
-- | A redeemer pointer is a pair of a script type tag ('ScriptTag') `t` and an index `i`,
-- picking out the i-th script of type `t` in the transaction.
data RedeemerPtr = RedeemerPtr ScriptTag Integer
deriving stock (Show, Eq, Ord, Generic)
deriving anyclass (NFData)

-- | Redeemers is a `Map` of redeemer pointer ('RedeemerPtr') and its 'Redeemer'.
type Redeemers = Map RedeemerPtr Redeemer

-- | A reference to a transaction output. This is a
-- pair of a transaction reference, and an index indicating which of the outputs
-- pair of a transaction ID (`TxId`), and an index indicating which of the outputs
-- of that transaction we are referring to.
data TxOutRef = TxOutRef {
txOutRefId :: TxId,
txOutRefId :: TxId, -- ^ The transaction ID.
txOutRefIdx :: Integer -- ^ Index into the referenced transaction's outputs
}
deriving stock (Show, Eq, Ord, Generic)
Expand All @@ -87,8 +96,8 @@ instance PlutusTx.Eq TxOutRef where
l == r =
txOutRefId l PlutusTx.== txOutRefId r
PlutusTx.&& txOutRefIdx l PlutusTx.== txOutRefIdx r

-- | A transaction output, consisting of a target address, a value, and optionally a datum hash.
-- | A transaction output, consisting of a target address ('Address'), a value ('Value'),
-- and optionally a datum hash ('DatumHash').
data TxOut = TxOut {
txOutAddress :: Address,
txOutValue :: Value,
Expand Down
Loading

0 comments on commit ecad3b4

Please sign in to comment.