What is going on with these ByteStrings? Hex

I’m getting a confusing result and think that I am missing something basic about how ByteStrings work. I have a signed event:

data Event = Event {
      eid :: ByteString  -- < hash of the Ev
    , sig :: ByteString  -- < schnorr signature
    , ev  :: Ev 
    }

And I have example data that I can use to verify:

goldid :: ByteString
goldid = "43 ... "
goldsig :: ByteString
goldsig = "908a ... "

The eventId calculation works as expected

eventId :: Ev -> ByteString
eventId =~ Hex.encode . SHA256.hash . BS.toStrict . J.encode

Next, the Validation function passes, but I do not understand why and think the next step, generating the signature, is not working because of what I don’t understand here. From the secp256 bindings

import Crypto.Schnorr (
    xOnlyPubKey, schnorrSig, msg, verifyMsgSchnorr)
isValid :: Event -> Bool 
isValid (Event i s e) = 
    let p = xOnlyPubKey . Hex.decodeLenient . pubkey $ e
        s' = schnorrSig . Hex.decodeLenient $ s
        m = msg . Hex.decodeLenient $ i
    in maybe False id $ verifyMsgSchnorr <$> p  <*> s'  <*> m

What is Hex.decodeLenient actually doing and (I doubt) should I rely on it? When using the ByteStrings directly they are double the expected length and result in Nothing. Just by guessing I tried decodeLenient and it cut the length in half and then the signature verified so it must not be losing data, but I don’t understand what is happening.

For reference this is the source of decodeLenient:

-- base16-bytestring
decodeLenient :: ByteString -> ByteString
decodeLenient = LBS.fromChunks
    . fmap B16.decodeLenient
    . reChunk
    . fmap (BS.filter (flip BS.elem extendedHex))
    . LBS.toChunks
  where
    extendedHex = BS.pack (fmap c2w "0123456789abcdefABCDEF")

-- base16
decodeLenient :: ByteString -> ByteString
decodeLenient bs = withBS bs go
  where
    go !sptr !slen
      | slen == 0 = return empty
      | otherwise = do
        dfp <- mallocPlainForeignPtrBytes (q * 2)
        withForeignPtr dfp $ \dptr ->
          lenientLoop dfp dptr sptr (plusPtr sptr slen)
      where
        !q = slen `quot` 2

link to stack project github /Spec.hs

I was hoping to find a Haskell crypto library that could do the schnorr signatures. Does that exist? Can’t find it.

I’m a bit confused because the decodeLenient that you say is from base16 actually appears to be the one from base16-bytestring. You can see from its Haddock that it’s converting an ASCII-encoded hexadecimal literal into a sequence of bytes. That’s in line with the length halving!

Does that match your expectation? If not could you clarify, because I’m having trouble understanding what you’re asking.

I was missing something basic here. So to recap. The default encoding from OverloadedStrings puts it into ASCII which represents each character by a single byte and converting it to Hex means a byte represents two characters and thus it halves the length without losing any data and this is safe & expected.

Now going in the opposite direction from the ByteString created from KeyPair:

-- same problem twice as big as expected
bkey :: KeyPair -> ByteString

-- 128 (4x too big)
bkey = Hex.encode . getXOnlyPubKey . deriveXOnlyPubKey

-- 64 (2x too big still) 
bkey' = Hex.decodeLenient . bkey

I guess when working with ByteString there is this underlying unknown of the encoding. What encoding would be expected to come out of (getXOnlyPubKey . deriveXOnlyPubKey). It’s not ascii or hex. How can I know?

edit: From the schnorr library. It looks like 64 allocated on the export, but 32 is required to create it. Could this be a mistake from this bindings library?

deriveXOnlyPubKeyFromPubKey (PubKey bs) =
  unsafePerformIO $
  unsafeUseByteString bs $ \(pub_key_ptr, _) -> do
    x_only_pub_key <- mallocBytes 64
    ret <- xOnlyPubKeyFromPubKey ctx x_only_pub_key nullPtr pub_key_ptr
    if isSuccess ret
      then XOnlyPubKey <$> unsafePackByteString (x_only_pub_key, 64)
      else do
        free x_only_pub_key
        error "could not derive xonly pub key from pub key"

xOnlyPubKey bs
  | BS.length bs == 32 =
    unsafePerformIO $
    unsafeUseByteString bs $ \(input, len) -> do
      pub_key <- mallocBytes 64
      ret <- schnorrXOnlyPubKeyParse ctx pub_key input
      if isSuccess ret
        then do
          out <- unsafePackByteString (pub_key, 64)
          return $ Just $ XOnlyPubKey out
        else do
          return Nothing
  | otherwise = Nothing

bump - cryptonite has the curve and there are elliptical curve functions . . .