Ecdh (chasing inconsistent FFI functions)

Hello,

Diffie-Helmen is way to produce a shared secret. This secret can then be used as the key for encrypted communication. Ecdh is an implementation of this over secp256k1:

foreign import ccall safe "secp256k1.h secp256k1_keypair_create" keyPairCreate
  :: Ctx -> Ptr KeyPair96 -> Ptr SecKey32 -> IO Ret

foreign import ccall safe "secp256k1.h secp256k1_ecdh" ecdh
  ::  Ctx -> Ptr CUChar -> Ptr PubKey64 -> Ptr KeyPair96 -> 
      Ptr q -> Ptr w -> IO Ret

The following should always hold? (pseudo code, actual test)

do
    (k1, p1) <- genKey 
    (k2, p2) <- genKey
    ecdh k1 p2 == ecdh k2 p1 

And it works! . . . sometimes. Generating a matrix of this assertion over 10 keys permutations (O being fail, X being true) gets a results that look like this, failure looks as likely as success:
“XOXXXOXXOX”
“OXOOOXOOXO”
“XOXXXOXXOX”
“XOXXXOXXOX”
“XOXXXOXXOX”
“OXOOOXOOXO”
“XOXXXOXXOX”
“XOXXXOXXOX”
“OXOOOXOOXO”
“XOXXXOXXOX”

Surely this must be a mistake in my haskell bindings because if it isn’t that means this encryption protocol is broken? But I can’t see it, schnorr signatures work consistently. How could it be wrong and work sometimes! Any insight or suggestion?

I’ve been scratching my head on this, I don’t have answers but I do have a few things that may help. Lets start!

I presume this is your actual ECDH test here?

getShared :: Hex96 -> Hex32 -> IO Hex32 
getShared kp pu = do 
    sh <- mallocBytes 32 
    (sec', 96) <- getPtr $ un96 kp 
    (pub', 64) <- parsePub pu >>= getPtr . un64 
    r <- ecdh ctx sh pub' sec' nullPtr nullPtr  
    if r == 1 
        then Hex32 <$> packPtr (sh, 32)
        else error "hh" -- getShared kp pu 

It takes a secret and a public key, and does stuff with it before passing it into ecdh. I noticed that you call parsePub on the public key before sending it in.

parsePub :: Hex32 -> IO Hex64
parsePub (Hex32 bs) = do 
    pub64 <- mallocBytes 64
    (pub32, 32) <- getPtr bs
    ret <- schnorrXOnlyPubKeyParse ctx pub64 pub32
    case ret of
        1 -> Hex64 <$> packPtr (pub64, 64) 
        _ -> free pub64 >> error "parsePub error"

If we look at it, we see that it uses schnorrXOnlyPubKeyParse, and we’re not doing schnorr keys, we’re doing secp256k1 ecdh! So that’s one item of concern, but then I realize its actually binding to secp256k1_xonly_pubkey_parse, using only the x coordinate of the public point - I don’t know if this is wrong here, but the ECDH example does not do this. More on that later.

Alrighty, lets hop up a level, and see how getShared is itself being used - I want to know about key generation and stuff. We find that getShared is only used in getNipTest4 so lets look at the relevant bits:

getNip4Test = do 
    -- ...
    kx <- M.replicateM 100 do 
        k' <- genKeyPair 
        p' <- exportPub k'
        pure (k', p')
    let keys = P.map fst kx 
    let pubs = P.map snd kx
    matrikx <- V.fromList . P.map V.fromList <$> sequenceA [ sequenceA  [ getShared ki pj 
            | pj <- pubs] 
            | ki <- keys]
    -- ...

Here, we see you are using genKeyPair (all good) to get the keypair, and then exportPub to extract the public key, and then getShared gets called with all the permutations. Neat, but then I notice that you are passing in the keypair and public key to getShared - and not just the secret key and public key. Less good. This means that instead of getting passed a secret key, ecdh is passed a keypair!

It may work by accident, if the keypair (96 bytes) starts with the secret key (32 bytes) then its just a longer-than-expected buffer, but the following note makes it clear we should not rely on this behavior. This is another concern.

From secp256k1_extrakeys.h describing secp256k1_keypair
“The exact representation of data inside is implementation defined and not guaranteed to be portable between different platforms or versions.”

Alright, lets take a look at exportPub, our last mystery!

exportPub :: Hex96 -> IO Hex32 
exportPub (Hex96 bs) = do 
    (priv, 96) <- getPtr bs
    pub64 <- mallocBytes 64
    void $ keyPairXOnlyPubKey ctx pub64 nullPtr priv
    pub <- mallocBytes 32
    void $ schnorrPubKeySerialize ctx pub (castPtr pub64)
    Hex32 <$> packPtr (pub, 32)

More schnorr secp256k1_xonly_pubkey_parse? Also, why do we need to export and then parse the public key?

So, all of that looks a little bit funky. A few more things jump out at me:

  • you have a global ctx that isn’t randomized, stays alive, and gets reused

  • You are using the xonly functions, instead of secp256k1_ec_pubkey_create?

  • secp256k1_pubkey and secp256k1_xonly_pubkey are different structures

  • secp256k1_ecdh expects a secp256k1_pubkey, but are giving it a secp256k1_xonly_pubkey

From: secp256k1_extrakeys.h describing the xonly functions
“An x-only pubkey encodes a point whose Y coordinate is even.”

This may not be relevant, but it might explain your apparent 50/50 success / failure.


I did find a nice lovely C example for libsecp256k1 ECDH, and its usage looks very different from what you are doing here. You might try re-implementing the example line-by-line, and see how that work for you.

4 Likes

Thank you! I haven’t figured it yet, but you are correct the format for the ecdh keys is not either of the formats that were used in the schnorr signatures. The fact that asymmetric symmetry existed part of the time must be some math magic. We have:

  • Pub32 - xonly serialized (used nostr pubkey)
  • PubS64 - parsed or signing (used schnorr signing)
  • PubXo64 - x only but 64
  • PubC33 - compressed ecdsa (think this is the one I need for ecdh)
  • PubF65 - full ecdsa
  • … more I think … For esdsa verify the documentation just says *pubkey: pointer to an initialized public key to verify with. Without size information or anything so this means nothing to me :frowning:

And no type errors and if you mix and match it can partially work sometimes. I can say I am gaining a further appreciation for how wonderful it is to code in Haskell proper. Thanks again, you shook me out of the mental block that the passing tests must mean the format is right. All the tests fail now, which is a coherent reality I can work with!

1 Like

That’s the spirit! Cryptography can be a pain to wrangle, but one can force it into submission given due care.

1 Like

You already got a great answer from @ApothecaLabs, I just want to add thanks for not blindly assuming everything just works. Also it would be neat to have something like the checkers and tasty-quickcheck-laws but for cryptography libraries.

1 Like

Thought I would share what worked, doesn’t seem to match the example :confused:

foreign import ccall safe "secp256k1.h secp256k1_ecdh" ecdh
  ::  Ctx -> Ptr CUChar -> Ptr p -> Ptr s -> 
      FunPtr q -> Ptr w -> IO Ret

foreign import ccall "wrapper"
  hashPtr 
    :: (Ptr a -> Ptr a -> Ptr a -> Ptr () -> IO CInt) 
    -> IO (FunPtr (Ptr a -> Ptr a -> Ptr a -> Ptr () -> IO CInt))

copyX :: Ptr CUChar -> Ptr CUChar -> Ptr CUChar -> Ptr () -> IO CInt
copyX h x _ _ = do 
    memcpy h x 32
    return 1     

getShared :: Hex96 -> Hex32 -> IO Hex32 
getShared kp pu = do 
    se <- mallocBytes 32 
    (kp', 96) <- getPtr $ un96 kp 
    keyPairSec ctx se kp' 
    sh <- mallocBytes 32 
    ha <- hashPtr copyX
    -- (pu', 33) <- getPtr . (Hex.decodeLenient "02" <>) . un32 $ pu
    (pu', 64) <- parsePub pu >>= getPtr . un64
    r <- ecdh ctx sh pu' se ha nullPtr  
    if r == 1 
        then Hex32 <$> packPtr (sh, 32)
        else error "hh"