plutus-contract-1.2.0.0
Safe HaskellNone
LanguageHaskell2010

Plutus.Contract.Oracle

Synopsis

Signed messages

This module provides a way to verify signed messages, and a type for observations (for example, the price of a commodity on a given date). Together, the two can be used to implement trusted oracles:

  • The oracle observes a value, for example Price and constructs a value o = Observation Price.
  • The oracle then calls signMessage o pk with its own private key to produce a SignedMessage (Observation Price).
  • The signed message is passed to the contract as the redeemer of some unspent output. Important: The redeeming transaction must include the message o as a datum. This is because we can't hash anything in on-chain code, and therefore have to rely on the node to do it for us via the pending transaction's map of datum hashes to datums. (The constraints resolution mechanism takes care of including the message)
  • The contract then calls checkSignature to check the signature, and produces a constraint ensuring that the signed hash is really the hash of the datum.

data Observation a Source #

A value that was observed at a specific point in time

Constructors

Observation 

Fields

  • obsValue :: a

    The value

  • obsTime :: POSIXTime

    The time at which the value was observed

Instances

Instances details
(Typeable DefaultUni a, Lift DefaultUni a) => Lift DefaultUni (Observation a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Methods

lift :: Observation a -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())

Eq a => Eq (Observation a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Show a => Show (Observation a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Generic (Observation a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Associated Types

type Rep (Observation a) :: Type -> Type Source #

Eq a => Eq (Observation a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Methods

(==) :: Observation a -> Observation a -> Bool

FromData a => FromData (Observation a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Methods

fromBuiltinData :: BuiltinData -> Maybe (Observation a)

ToData a => ToData (Observation a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Methods

toBuiltinData :: Observation a -> BuiltinData

UnsafeFromData a => UnsafeFromData (Observation a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Methods

unsafeFromBuiltinData :: BuiltinData -> Observation a

Typeable DefaultUni Observation Source # 
Instance details

Defined in Plutus.Contract.Oracle

Methods

typeRep :: Proxy Observation -> RTCompile DefaultUni fun (Type TyName DefaultUni ())

type Rep (Observation a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

type Rep (Observation a) = D1 ('MetaData "Observation" "Plutus.Contract.Oracle" "plutus-contract-1.2.0.0-FH8LC9wh7UV4Nmv68NHXrC" 'False) (C1 ('MetaCons "Observation" 'PrefixI 'True) (S1 ('MetaSel ('Just "obsValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "obsTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime)))

data SignedMessage a Source #

SignedMessage a contains the signature of a hash of a Datum. The Datum can be decoded to a value of type a.

Constructors

SignedMessage 

Fields

Instances

Instances details
Typeable DefaultUni a => Lift DefaultUni (SignedMessage a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Methods

lift :: SignedMessage a -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())

Eq (SignedMessage a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Show (SignedMessage a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Generic (SignedMessage a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Associated Types

type Rep (SignedMessage a) :: Type -> Type Source #

FromJSON (SignedMessage a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Methods

parseJSON :: Value -> Parser (SignedMessage a)

parseJSONList :: Value -> Parser [SignedMessage a]

ToJSON (SignedMessage a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Methods

toJSON :: SignedMessage a -> Value

toEncoding :: SignedMessage a -> Encoding

toJSONList :: [SignedMessage a] -> Value

toEncodingList :: [SignedMessage a] -> Encoding

Eq a => Eq (SignedMessage a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Methods

(==) :: SignedMessage a -> SignedMessage a -> Bool

FromData a => FromData (SignedMessage a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Methods

fromBuiltinData :: BuiltinData -> Maybe (SignedMessage a)

ToData a => ToData (SignedMessage a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Methods

toBuiltinData :: SignedMessage a -> BuiltinData

UnsafeFromData a => UnsafeFromData (SignedMessage a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

Methods

unsafeFromBuiltinData :: BuiltinData -> SignedMessage a

Typeable DefaultUni SignedMessage Source # 
Instance details

Defined in Plutus.Contract.Oracle

Methods

typeRep :: Proxy SignedMessage -> RTCompile DefaultUni fun (Type TyName DefaultUni ())

type Rep (SignedMessage a) Source # 
Instance details

Defined in Plutus.Contract.Oracle

type Rep (SignedMessage a) = D1 ('MetaData "SignedMessage" "Plutus.Contract.Oracle" "plutus-contract-1.2.0.0-FH8LC9wh7UV4Nmv68NHXrC" 'False) (C1 ('MetaCons "SignedMessage" 'PrefixI 'True) (S1 ('MetaSel ('Just "osmSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Signature) :*: (S1 ('MetaSel ('Just "osmMessageHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatumHash) :*: S1 ('MetaSel ('Just "osmDatum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Datum))))

Checking signed messages

data SignedMessageCheckError Source #

Constructors

SignatureMismatch Signature PaymentPubKey DatumHash

The signature did not match the public key

DatumMissing DatumHash

The datum was missing from the pending transaction

DecodingError

The datum had the wrong shape

DatumNotEqualToExpected

The datum that corresponds to the hash is wrong

Instances

Instances details
Show SignedMessageCheckError Source # 
Instance details

Defined in Plutus.Contract.Oracle

Generic SignedMessageCheckError Source # 
Instance details

Defined in Plutus.Contract.Oracle

Associated Types

type Rep SignedMessageCheckError :: Type -> Type Source #

type Rep SignedMessageCheckError Source # 
Instance details

Defined in Plutus.Contract.Oracle

type Rep SignedMessageCheckError = D1 ('MetaData "SignedMessageCheckError" "Plutus.Contract.Oracle" "plutus-contract-1.2.0.0-FH8LC9wh7UV4Nmv68NHXrC" 'False) ((C1 ('MetaCons "SignatureMismatch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Signature) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PaymentPubKey) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatumHash))) :+: C1 ('MetaCons "DatumMissing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatumHash))) :+: (C1 ('MetaCons "DecodingError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DatumNotEqualToExpected" 'PrefixI 'False) (U1 :: Type -> Type)))

checkSignature Source #

Arguments

:: DatumHash

The hash of the message

-> PaymentPubKey

The public key of the signatory

-> Signature

The signed message

-> Either SignedMessageCheckError () 

Verify the signature on a signed datum hash

checkHashConstraints Source #

Arguments

:: FromData a 
=> SignedMessage a

The signed message

-> Either SignedMessageCheckError (a, TxConstraints i o) 

Extract the contents of the message and produce a constraint that checks that the hash is correct. In off-chain code, where we check the hash straightforwardly, checkHashOffChain can be used instead of this.

checkHashOffChain :: FromData a => SignedMessage a -> Either SignedMessageCheckError a Source #

The off-chain version of checkHashConstraints, using the hash function directly instead of obtaining the hash from a ScriptContext value

verifySignedMessageOffChain :: FromData a => PaymentPubKey -> SignedMessage a -> Either SignedMessageCheckError a Source #

Check the signature on a SignedMessage and extract the contents of the message.

verifySignedMessageOnChain :: FromData a => ScriptContext -> PaymentPubKey -> SignedMessage a -> Either SignedMessageCheckError a Source #

Check the signature on a SignedMessage and extract the contents of the message, using the pending transaction in lieu of a hash function. See verifySignedMessageConstraints for a version that does not require a ScriptContext value.

verifySignedMessageConstraints :: FromData a => PaymentPubKey -> SignedMessage a -> Either SignedMessageCheckError (a, TxConstraints i o) Source #

Check the signature on a SignedMessage and extract the contents of the message, producing a TxConstraint value that ensures the hashes match up.

Signing messages

signMessage :: ToData a => a -> PaymentPrivateKey -> Passphrase -> SignedMessage a Source #

Encode a message of type a as a Data value and sign the hash of the datum.

signObservation :: ToData a => POSIXTime -> a -> PaymentPrivateKey -> Passphrase -> SignedMessage (Observation a) Source #

Encode an observation of a value of type a that was made at the given time

Signing messages with no passphrase

signMessage' :: ToData a => a -> XPrv -> SignedMessage a Source #

Encode a message of type a as a Data value and sign the hash of the datum.

signObservation' :: ToData a => POSIXTime -> a -> XPrv -> SignedMessage (Observation a) Source #

Encode an observation of a value of type a that was made at the given time