Schnorr Signatures with direct FFI bindings

Hello.

So I guess this is really a story about the sorry state of libsecp256k1 bindings. There is a library on hackage libsecp256k1 but it has not been kept up to date with the underlying library so it fails to build and the maintainer has removed the code from github. Another version exists on github secp256k1-schnorr but there is a mistake (that I have communicated to the author) where 64 bytes was being allocated with 32 was expected. A category of error I do not appreciate! I didn’t figure this out until getting the sign and verify working with direct bindings:

verifyE :: Event -> IO Bool 
verifyE Event{..}  
    | idE con == eid = do 
        signPub <- parsePub . pubkey $ con
        (msg', 32) <- getPtr (un32 eid) -- \(msg', 32) ->  
        (sig', 64) <- getPtr (un64 sig) 
        (pub', 64) <- getPtr (un64 signPub)
        (== 1) <$> schnorrSignatureVerify ctx sig' msg' 32 pub' 
    | otherwise = pure False 

signE :: Hex96 -> Keyless -> IO Event
signE kp keyless = do
    content <- keyless <$> exportPub kp
    let eid = idE content
    (priv, 96) <- getPtr (un96 kp)
    sig <- mallocBytes 64
    (msg, 32) <- getPtr . un32 $ eid 
    (salt, 32) <- genSalt
    ret <- schnorrSign ctx sig msg priv salt
    case ret of 
        1 -> do 
            sig' <- Hex64 <$> packPtr (sig, 64)
            let newE = Event eid sig' content
            trust <- verifyE newE
            if trust 
                then pure newE
        -- XXX handle failure? 
                else undefined -- signE kp keyless 
        _ -> undefined -- pure $ signE kp c

I have a couple questions.

  • How do I know when I need to clean up the memory I’ve allocated?
  • Can signing fail? How should I handle the error case?
  • The other binding libraries used unsafePerformIO but I chose to just keep it in IO? Is there a performance trade-off or some other reason for unsafePerformIO?

Code is here futr2; stack build && stack test. Specific files:

207 src/Nostr/Event.hs
60 src/Secp256k1/Internal.hs

The design space for nostr is interesting. What is complete is the over the wire protocol for both client and relay. It doesn’t seem to me there is any reason that a client shouldn’t also be a relay. Thinking about creating and managing many different identities. Publishing new events over tor to keep privacy. A monomer UI x_x. Discovering, switching and exploring relays. But the next step is the database and am going to try to use Beam and a relational structure that makes queries on Filter-Match options indexed/fast (srcNostr/Relay).

Happy coding out there!

1 Like

Memory ownership is something C libraries don’t specify in the type system, so you have to read the code and find out how it’s expected to work. But if a passed in pointer is e.g. const, you can know that they wouldn’t free it on you.

Let’s say that you own the memory:

You can then use with functions like e.g. withForeignPtr to get a closure where the typical Ptr is available.

One nice thing about ForeignPtr is that the RTS will free the memory when it wants. Since you’re working with cryptographically sensitive data, you might wanna zero the memory when you’re done with it. Once it’s zeroed you shouldn’t need to get it freed promptly, but if you do, there is finalizeForeignPtr (EDIT: finalizing doesn’t actually free)

1 Like

If you look at the BIP-340 spec, you can see that it specifies the verification as part of the signature algorithm, with the footnote:

Verifying the signature before leaving the signer prevents random or attacker provoked computation errors. This prevents publishing invalid signatures which may leak information about the secret key. It is recommended, but can be omitted if the computation cost is prohibitive.

From a quick glance, there are also two other instances of fail in that listing.

And if you look at the tests, they check that signing fails in the case of overflowing or negative s.

how bad an idea is a recursive call to signE? this is handling the case when attempt to make signature failed (return 1 from schnorrSign) or validation check failed

I think this is a deterministic function, so there is no point in retrying with the same data. For example, if you look at the second bullet point of the Sign spec, which says “Fail if d’ = 0 or d’ ≥ n”, that’s a deterministic failure in case you use the zeroed secret key.

I am not sure what you’re trying to achieve with recursion since the c in your commented out code isn’t defined.