Copyright | (c) 2025 Jose Storopoli |
---|---|
License | MIT |
Maintainer | Jose Storopoli <jose@storopoli.com> |
Safe Haskell | None |
Language | Haskell2010 |
Crypto.Curve.Secp256k1.MuSig2
Contents
Description
Pure BIP0327 MuSig2 (partial)signatures with tweak support on the elliptic curve secp256k1.
Usage
A sample GHCi session:
> -- pragmas and b16 import for illustration only; not required > :set -XOverloadedStrings > :set -XBangPatterns > import qualified Data.ByteString.Base16 as B16 > > -- import qualified > import qualified Crypto.Curve.Secp256k1.MuSig2 as MuSig2 > import qualified Crypto.Curve.Secp256k1 as Secp256k1 > > -- secret keys for a 2-of-2 multisig > let sec1 = MuSig2.SecKey 0xB7E151628AED2A6ABF7158809CF4F3C762E7160F38B4DA56A784D9045190CFEF > let sec2 = MuSig2.SecKey 0x68E151628AED2A6ABF7158809CF4F3C762E7160F38B4DA56A784D9045190CFEF > > -- derive public keys > let pub1 = Secp256k1.derive_pub 0xB7E151628AED2A6ABF7158809CF4F3C762E7160F38B4DA56A784D9045190CFEF > let pub2 = Secp256k1.derive_pub 0x68E151628AED2A6ABF7158809CF4F3C762E7160F38B4DA56A784D9045190CFEF > let pubkeys = [pub1, pub2] > > -- create key aggregation context > let keyagg_ctx = MuSig2.mkKeyAggContext pubkeys Nothing > let agg_pk = MuSig2.aggregatedPubkey keyagg_ctx > > -- message to sign > let msg = "i approve of this message" > > -- generate nonces for each signer > let params1 = MuSig2.defaultSecNonceGenParams pub1 > let params2 = MuSig2.defaultSecNonceGenParams pub2 > secnonce1 <- MuSig2.secNonceGen params1 > secnonce2 <- MuSig2.secNonceGen params2 > let pubnonce1 = MuSig2.publicNonce secnonce1 > let pubnonce2 = MuSig2.publicNonce secnonce2 > let pubnonces = [pubnonce1, pubnonce2] > > -- aggregate nonces and create session context > let Just aggnonce = MuSig2.aggNonces pubnonces > let session_ctx = MuSig2.mkSessionContext aggnonce pubkeys [] msg > > -- each signer creates a partial signature > let psig1 = MuSig2.sign secnonce1 sec1 session_ctx > let psig2 = MuSig2.sign secnonce2 sec2 session_ctx > let psigs = [psig1, psig2] > > -- aggregate partial signatures into final signature > let final_sig = MuSig2.aggPartials psigs session_ctx > > -- verify the aggregated signature > Secp256k1.verify_schnorr msg agg_pk final_sig > True
Synopsis
- sign :: SecNonce -> SecKey -> SessionContext -> PartialSignature
- newtype SecKey = SecKey Integer
- type PartialSignature = Integer
- partialSigVerify :: Traversable t => PartialSignature -> t PubNonce -> t Pub -> t Tweak -> ByteString -> Int -> Bool
- aggPartials :: Traversable t => t PartialSignature -> SessionContext -> ByteString
- data SessionContext
- mkSessionContext :: Traversable t => PubNonce -> t Pub -> t Tweak -> ByteString -> SessionContext
- data KeyAggContext
- mkKeyAggContext :: Traversable t => t Pub -> Maybe Tweak -> KeyAggContext
- aggregatedPubkey :: KeyAggContext -> Pub
- applyTweak :: KeyAggContext -> Tweak -> KeyAggContext
- data Tweak
- sortPublicKeys :: Traversable t => t Pub -> Seq Pub
- data SecNonce = SecNonce {}
- mkSecNonce :: IO SecNonce
- data SecNonceGenParams = SecNonceGenParams {}
- defaultSecNonceGenParams :: Pub -> SecNonceGenParams
- secNonceGen :: SecNonceGenParams -> IO SecNonce
- secNonceGenWithRand :: ByteString -> SecNonceGenParams -> SecNonce
- data PubNonce = PubNonce {}
- publicNonce :: SecNonce -> PubNonce
- aggNonces :: Traversable t => t PubNonce -> Maybe PubNonce
Documentation
Arguments
:: SecNonce | Secret nonce. |
-> SecKey | Secret key. |
-> SessionContext | Session context. |
-> PartialSignature | Partial signature. |
Compute a partial signature on a message.
The partial signature returned from this function is a potentially-zero scalar value which can then be passed to other signers for verification and aggregation.
Secret key.
type PartialSignature = Integer Source #
A partial signature which is a scalar in the range \(0 \leq x < n\) where (n) is the curve order.
Arguments
:: Traversable t | |
=> PartialSignature | Partial signature to verify. |
-> t PubNonce | |
-> t Pub |
|
-> t Tweak | |
-> ByteString | Message. |
-> Int | Index of the signer. |
-> Bool | If the partial signature is valid. |
Verifies a PartialSignature
.
Arguments
:: Traversable t | |
=> t PartialSignature | Partial signatures. |
-> SessionContext | Session context. |
-> ByteString | 64-byte Schnorr signature. |
Aggregates PartialSignature
s into a 64-byte Schnorr signature.
data SessionContext Source #
Session aggregation context that holds the relevant context for a MuSig2 signing session.
Arguments
:: Traversable t | |
=> PubNonce | Aggregated |
-> t Pub |
|
-> t Tweak |
|
-> ByteString | Message to be signed. |
-> SessionContext | Resulting |
Creates a SessionContext
.
The order in which the Pub
keys are presented will be preserved.
A specific ordering of Pub
keys will uniquely determine the aggregated Pub
key.
If the same keys are provided again in a different sorting order, a different
aggregated Pub
key will result. It is recommended to sort keys ahead of time
using sortPublicKeys
before creating a SessionContext
.
NOTE
Internally it validates if all keys, the resulting aggregated key, and the aggregated public nonce are not points at infinity, if the tweaks are within the curve order, and if the length of the collection of keys is not bigger than 32 bits.
data KeyAggContext Source #
Key aggregation context that holds the aggregated public key and a tweak, if applicable.
Arguments
:: Traversable t | |
=> t Pub |
|
-> Maybe Tweak | Optional |
-> KeyAggContext | Resulting |
Creates a KeyAggContext
.
The order in which the Pub
keys are presented will be preserved.
A specific ordering of Pub
keys will uniquely determine the aggregated Pub
key.
If the same keys are provided again in a different sorting order, a different
aggregated Pub
key will result. It is recommended to sort keys ahead of time
using sortPublicKeys
before creating a KeyAggContext
.
NOTE
Internally it validates if all keys and the resulting aggregated key are not points at infinity, if the optional tweak is within the curve order, and if the length of the collection of keys is not bigger than 32 bits.
aggregatedPubkey :: KeyAggContext -> Pub Source #
Gets the aggregated public key from a KeyAggContext
.
applyTweak :: KeyAggContext -> Tweak -> KeyAggContext Source #
Applies a tweak to a KeyAggContext and returns a new KeyAggContext following BIP327.
Tweak that can be added to an aggregated Pub
key.
Constructors
XOnlyTweak !Integer | X-only tweak required by Taproot tweaking to add script paths to a Taproot output. See BIP341. |
PlainTweak !Integer | Plain tweak that can be used to derive child aggregated |
Instances
sortPublicKeys :: Traversable t => t Pub -> Seq Pub Source #
Lexicographically sort
s a Traversable
of Pub
keys.
Secret nonce.
The secret nonce provides randomness, blinding a signer's private key when
signing. It is imperative that the same SecNonce
is not used to sign more
than one message with the same key, as this would allow an observer to
compute the private key used to create both signatures.
If you want to follow
BIP327
suggestions, then use secNonceGen
otherwise use mkSecNonce
.
Instances
Generic SecNonce Source # | |||||
Defined in Crypto.Curve.Secp256k1.MuSig2 Associated Types
| |||||
Read SecNonce Source # | |||||
Eq SecNonce Source # | |||||
Ord SecNonce Source # | |||||
Defined in Crypto.Curve.Secp256k1.MuSig2 | |||||
type Rep SecNonce Source # | |||||
Defined in Crypto.Curve.Secp256k1.MuSig2 type Rep SecNonce = D1 ('MetaData "SecNonce" "Crypto.Curve.Secp256k1.MuSig2" "musig2-0.1.0-inplace" 'False) (C1 ('MetaCons "SecNonce" 'PrefixI 'True) (S1 ('MetaSel ('Just "k1") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Just "k2") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer))) |
mkSecNonce :: IO SecNonce Source #
data SecNonceGenParams Source #
Required and Optional data to generate a SecNonce
.
Constructors
SecNonceGenParams | |
Instances
Generic SecNonceGenParams Source # | |||||
Defined in Crypto.Curve.Secp256k1.MuSig2 Associated Types
Methods from :: SecNonceGenParams -> Rep SecNonceGenParams x # to :: Rep SecNonceGenParams x -> SecNonceGenParams # | |||||
Eq SecNonceGenParams Source # | |||||
Defined in Crypto.Curve.Secp256k1.MuSig2 Methods (==) :: SecNonceGenParams -> SecNonceGenParams -> Bool # (/=) :: SecNonceGenParams -> SecNonceGenParams -> Bool # | |||||
Ord SecNonceGenParams Source # | |||||
Defined in Crypto.Curve.Secp256k1.MuSig2 Methods compare :: SecNonceGenParams -> SecNonceGenParams -> Ordering # (<) :: SecNonceGenParams -> SecNonceGenParams -> Bool # (<=) :: SecNonceGenParams -> SecNonceGenParams -> Bool # (>) :: SecNonceGenParams -> SecNonceGenParams -> Bool # (>=) :: SecNonceGenParams -> SecNonceGenParams -> Bool # max :: SecNonceGenParams -> SecNonceGenParams -> SecNonceGenParams # min :: SecNonceGenParams -> SecNonceGenParams -> SecNonceGenParams # | |||||
type Rep SecNonceGenParams Source # | |||||
Defined in Crypto.Curve.Secp256k1.MuSig2 type Rep SecNonceGenParams = D1 ('MetaData "SecNonceGenParams" "Crypto.Curve.Secp256k1.MuSig2" "musig2-0.1.0-inplace" 'False) (C1 ('MetaCons "SecNonceGenParams" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_pk") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pub) :*: S1 ('MetaSel ('Just "_sk") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SecKey))) :*: (S1 ('MetaSel ('Just "_aggpk") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Pub)) :*: (S1 ('MetaSel ('Just "_msg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ByteString)) :*: S1 ('MetaSel ('Just "_extraIn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ByteString)))))) |
secNonceGenWithRand :: ByteString -> SecNonceGenParams -> SecNonce Source #
Generates a SecNonce
using a given random ByteString
and the inputs and
algorithms from
BIP327.
WARNING
You should probably use secNonceGen
.
Use this function if you really have a randomly-generated ByteString
.
Public nonce.
Represents a public nonce derived from a secret nonce. It is composed
of two public points, r1
and r2
, derived by base-point multiplying
the two scalars in a SecNonce
.
A PubNonce
can be derived from a SecNonce
using publicNonce
.
Instances
Monoid PubNonce Source # |
|
Semigroup PubNonce Source # |
|
Show PubNonce Source # | |
Eq PubNonce Source # | |
Ord PubNonce Source # | |
Defined in Crypto.Curve.Secp256k1.MuSig2 |
aggNonces :: Traversable t => t PubNonce -> Maybe PubNonce Source #
Aggregates a Traversable
of PubNonce
s using the
Nonce Aggregation algorithm in BIP327.
Orphan instances
Monoid Projective Source # |
|
Methods mempty :: Projective # mappend :: Projective -> Projective -> Projective # mconcat :: [Projective] -> Projective # | |
Semigroup Projective Source # |
|
Methods (<>) :: Projective -> Projective -> Projective # sconcat :: NonEmpty Projective -> Projective # stimes :: Integral b => b -> Projective -> Projective # | |
Ord Projective Source # | Manual |
Methods compare :: Projective -> Projective -> Ordering # (<) :: Projective -> Projective -> Bool # (<=) :: Projective -> Projective -> Bool # (>) :: Projective -> Projective -> Bool # (>=) :: Projective -> Projective -> Bool # max :: Projective -> Projective -> Projective # min :: Projective -> Projective -> Projective # |