musig2
Copyright(c) 2025 Jose Storopoli
LicenseMIT
MaintainerJose Storopoli <jose@storopoli.com>
Safe HaskellNone
LanguageHaskell2010

Crypto.Curve.Secp256k1.MuSig2

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

Documentation

sign Source #

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.

newtype SecKey Source #

Secret key.

Constructors

SecKey Integer 

Instances

Instances details
Generic SecKey Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Associated Types

type Rep SecKey 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

type Rep SecKey = D1 ('MetaData "SecKey" "Crypto.Curve.Secp256k1.MuSig2" "musig2-0.1.0-inplace" 'True) (C1 ('MetaCons "SecKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

Methods

from :: SecKey -> Rep SecKey x #

to :: Rep SecKey x -> SecKey #

Num SecKey Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Read SecKey Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Eq SecKey Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Methods

(==) :: SecKey -> SecKey -> Bool #

(/=) :: SecKey -> SecKey -> Bool #

Ord SecKey Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

type Rep SecKey Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

type Rep SecKey = D1 ('MetaData "SecKey" "Crypto.Curve.Secp256k1.MuSig2" "musig2-0.1.0-inplace" 'True) (C1 ('MetaCons "SecKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

type PartialSignature = Integer Source #

A partial signature which is a scalar in the range \(0 \leq x < n\) where (n) is the curve order.

partialSigVerify Source #

Arguments

:: Traversable t 
=> PartialSignature

Partial signature to verify.

-> t PubNonce

PubNonces

-> t Pub

Public keys.

-> t Tweak

Tweaks

-> ByteString

Message.

-> Int

Index of the signer.

-> Bool

If the partial signature is valid.

Verifies a PartialSignature.

aggPartials Source #

Arguments

:: Traversable t 
=> t PartialSignature

Partial signatures.

-> SessionContext

Session context.

-> ByteString

64-byte Schnorr signature.

Aggregates PartialSignatures into a 64-byte Schnorr signature.

data SessionContext Source #

Session aggregation context that holds the relevant context for a MuSig2 signing session.

mkSessionContext Source #

Arguments

:: Traversable t 
=> PubNonce

Aggregated PubNonce.

-> t Pub

Pubkeys.

-> t Tweak

Tweaks.

-> ByteString

Message to be signed.

-> SessionContext

Resulting SessionContext.

Creates a SessionContext.

The order in which the Pubkeys are presented will be preserved. A specific ordering of Pubkeys will uniquely determine the aggregated Pubkey.

If the same keys are provided again in a different sorting order, a different aggregated Pubkey 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.

mkKeyAggContext Source #

Arguments

:: Traversable t 
=> t Pub

Pubkeys.

-> Maybe Tweak

Optional Tweak value.

-> KeyAggContext

Resulting KeyAggContext.

Creates a KeyAggContext.

The order in which the Pubkeys are presented will be preserved. A specific ordering of Pubkeys will uniquely determine the aggregated Pubkey.

If the same keys are provided again in a different sorting order, a different aggregated Pubkey 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.

data Tweak Source #

Tweak that can be added to an aggregated Pubkey.

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 Pubkeys per BIP32

Instances

Instances details
Generic Tweak Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Associated Types

type Rep Tweak 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

type Rep Tweak = D1 ('MetaData "Tweak" "Crypto.Curve.Secp256k1.MuSig2" "musig2-0.1.0-inplace" 'False) (C1 ('MetaCons "XOnlyTweak" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer)) :+: C1 ('MetaCons "PlainTweak" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer)))

Methods

from :: Tweak -> Rep Tweak x #

to :: Rep Tweak x -> Tweak #

Read Tweak Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Show Tweak Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Methods

showsPrec :: Int -> Tweak -> ShowS #

show :: Tweak -> String #

showList :: [Tweak] -> ShowS #

Eq Tweak Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Methods

(==) :: Tweak -> Tweak -> Bool #

(/=) :: Tweak -> Tweak -> Bool #

Ord Tweak Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Methods

compare :: Tweak -> Tweak -> Ordering #

(<) :: Tweak -> Tweak -> Bool #

(<=) :: Tweak -> Tweak -> Bool #

(>) :: Tweak -> Tweak -> Bool #

(>=) :: Tweak -> Tweak -> Bool #

max :: Tweak -> Tweak -> Tweak #

min :: Tweak -> Tweak -> Tweak #

type Rep Tweak Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

type Rep Tweak = D1 ('MetaData "Tweak" "Crypto.Curve.Secp256k1.MuSig2" "musig2-0.1.0-inplace" 'False) (C1 ('MetaCons "XOnlyTweak" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer)) :+: C1 ('MetaCons "PlainTweak" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer)))

sortPublicKeys :: Traversable t => t Pub -> Seq Pub Source #

Lexicographically sorts a Traversable of Pubkeys.

data SecNonce Source #

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.

Constructors

SecNonce 

Fields

Instances

Instances details
Generic SecNonce Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Associated Types

type Rep SecNonce 
Instance details

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)))

Methods

from :: SecNonce -> Rep SecNonce x #

to :: Rep SecNonce x -> SecNonce #

Read SecNonce Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Eq SecNonce Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Ord SecNonce Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

type Rep SecNonce Source # 
Instance details

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 #

Generates a SecNonce using only the system's underlying Cryptographic Secure Pseudorandom Number Generator (CSPRNG) using the entropy package.

WARNING

Make sure that you have access to a good CSPRNG in your system before calling this function.

Note that this does not follow the BIP327 algorithm.

data SecNonceGenParams Source #

Required and Optional data to generate a SecNonce.

Constructors

SecNonceGenParams 

Fields

Instances

Instances details
Generic SecNonceGenParams Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Eq SecNonceGenParams Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Ord SecNonceGenParams Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

type Rep SecNonceGenParams Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

defaultSecNonceGenParams :: Pub -> SecNonceGenParams Source #

Default approach to generate SecNonces with the only required Public key.

secNonceGen :: SecNonceGenParams -> IO SecNonce Source #

Generates a SecNonce using the inputs and algorithms from BIP327.

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.

data PubNonce Source #

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.

Constructors

PubNonce 

Fields

  • r1 :: Pub

    First public point.

  • r2 :: Pub

    Second public point.

Instances

Instances details
Monoid PubNonce Source #

Monoid implementation of PubNonce for algebraic sound combination of public nonces.

Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Semigroup PubNonce Source #

Semigroup implementation of PubNonce for algebraic sound combination of public nonces.

Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Show PubNonce Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Eq PubNonce Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Ord PubNonce Source # 
Instance details

Defined in Crypto.Curve.Secp256k1.MuSig2

Orphan instances

Monoid Projective Source #

Monoid implementation of Projective for algebraic sound combination of points.

Instance details

Semigroup Projective Source #

Semigroup implementation of Projective for algebraic sound combination of points.

Instance details

Ord Projective Source #

Manual Ord implementation of Projective for lexicography sorting.

Instance details