verify signatures

This commit is contained in:
me 2024-12-17 10:47:00 +02:00
parent d4a5f2422a
commit 1687444f00
4 changed files with 57 additions and 13 deletions

View file

@ -61,6 +61,8 @@ library
, crypton , crypton
, crypton-x509 , crypton-x509
, cryptostore , cryptostore
, case-insensitive
, http-types
hs-source-dirs: src hs-source-dirs: src
default-language: GHC2021 default-language: GHC2021

View file

@ -19,7 +19,7 @@ verifyPub pubkeypem sig message = do
case Crypto.readPubKeyFileFromMemory pubkeypem of case Crypto.readPubKeyFileFromMemory pubkeypem of
[Crypto.PubKeyRSA pubkey'] -> pure pubkey' [Crypto.PubKeyRSA pubkey'] -> pure pubkey'
_ -> throw "failed to read pubkey pem" _ -> throw "failed to read pubkey pem"
pure $ Crypto.verify (Just Crypto.SHA256) pubkey message sig pure $ Crypto.verify (Just Crypto.SHA256) pubkey message (decodeBase64 sig)
sign :: FilePath -> ByteString -> IO Signed sign :: FilePath -> ByteString -> IO Signed
sign privatePemFile message = do sign privatePemFile message = do

View file

@ -68,7 +68,6 @@ sendGet :: (A.FromJSON a) => String -> IO a
sendGet url = do sendGet url = do
uri <- URI.mkURI $ fromString url uri <- URI.mkURI $ fromString url
(url', scheme) <- maybe (throw "couldn't parse uri") pure (Req.useHttpsURI uri) (url', scheme) <- maybe (throw "couldn't parse uri") pure (Req.useHttpsURI uri)
print ("url", url')
Req.runReq Req.defaultHttpConfig do Req.runReq Req.defaultHttpConfig do
r <- r <-

View file

@ -1,4 +1,5 @@
{-# language RecordWildCards #-} {-# language RecordWildCards #-}
{-# language ViewPatterns #-}
module Fedi.Signature.Check module Fedi.Signature.Check
( module Fedi.Signature.Types ( module Fedi.Signature.Types
@ -15,12 +16,15 @@ import Fedi.Helpers
import Web.Twain qualified as Twain import Web.Twain qualified as Twain
import Data.Text qualified as T import Data.Text qualified as T
import Network.Wai qualified as Wai import Network.Wai qualified as Wai
import Network.HTTP.Types.URI qualified as HTTP
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import Text.ParserCombinators.ReadP qualified as P import Text.ParserCombinators.ReadP qualified as P
import Data.Text.Encoding qualified as T import Data.Text.Encoding qualified as T
import Data.ByteString qualified as BS
import Data.ByteString.Lazy qualified as BSL import Data.ByteString.Lazy qualified as BSL
import Fedi.Crypto import Fedi.Crypto
import Fedi.Signature.Types import Fedi.Signature.Types
import Data.CaseInsensitive qualified as CI
-- * Check -- * Check
@ -38,28 +42,62 @@ checkSignatureAndParseBody = do
let personPkid = person.otype.publicKey.pkid let personPkid = person.otype.publicKey.pkid
let personPublicKey = pemToBS person.otype.publicKey.publicKeyPem let personPublicKey = pemToBS person.otype.publicKey.publicKeyPem
signatureString <-
makeSignatureString request sigheader.headers
-- check -- check
liftIO $ liftIO $
checkSignature personPkid personPublicKey sigheader digest (BSL.toStrict body) checkSignature personPkid personPublicKey sigheader signatureString digest (BSL.toStrict body)
-- parse the body and return it -- parse the body and return it
parseJson body parseJson body
makeSignatureString
:: forall m. MonadThrow m => Wai.Request -> [T.Text] -> m ByteString
makeSignatureString request (map (T.encodeUtf8 . T.toLower) -> headers) = do
let
requestHeaders = Wai.requestHeaders request
method = T.encodeUtf8 $ T.toLower $ T.decodeUtf8 $ Wai.requestMethod request
path = T.encodeUtf8 (T.intercalate "/" $ Wai.pathInfo request)
<> HTTP.renderQuery True (Wai.queryString request)
requestTarget = method <> " " <> path
let
mylookup :: ByteString -> m ByteString
mylookup header
| header == "(request-target)" =
pure $ header <> ": " <> requestTarget
| header == "host" = do
let result = lookup (CI.mk header) requestHeaders
case result of
Nothing -> throw $ "Missing header '" <> show header <> "'."
Just value -> pure $ header <> ": "
<> if ":443" `BS.isSuffixOf` value
then BS.dropEnd (BS.length ":443") value
else value
| otherwise = do
let result = lookup (CI.mk header) requestHeaders
case result of
Nothing -> throw $ "Missing header '" <> show header <> "'."
Just value -> pure $ header <> ": " <> value
BS.intercalate "\n" <$> traverse mylookup headers
checkSignature checkSignature
:: MonadThrow m :: MonadThrow m
=> Url -> ByteString -> SignatureHeader -> ByteString -> ByteString -> m () => Url -> ByteString -> SignatureHeader -> ByteString -> ByteString -> ByteString -> m ()
checkSignature personPkid personPublicKey sigheader _digest body = do checkSignature personPkid personPublicKey sigheader signatureString digest body = do
-- check -- check
unless (personPkid == sigheader.keyId) $ unless (personPkid == sigheader.keyId) $
throw "public key mismatch with signature." throw "public key mismatch with signature."
pub <- verifyPub personPublicKey sigheader.signature body pub <- verifyPub personPublicKey sigheader.signature signatureString
unless pub $ unless pub $
throw "signature verification failed." throw "signature verification failed."
-- dig <- verifyDigest personPublicKey digest body let
-- unless dig $ mydigest = "SHA-256=" <> encodeBase64 (makeDigest body)
-- throw "digest verification failed." unless (mydigest == digest) $
throw "digest verification failed."
-- todo: check date -- todo: check date
@ -80,6 +118,7 @@ parseSignature minput = do
( decodeBase64 ( decodeBase64
. fromString . fromString
) <$> lookup' Signature components ) <$> lookup' Signature components
P.eof
pure SignatureHeader{..} pure SignatureHeader{..}
component = P.choice component = P.choice
[ do [ do
@ -95,8 +134,12 @@ parseSignature minput = do
url <- P.between (P.char '\"') (P.char '\"') (P.munch1 (/= '\"')) url <- P.between (P.char '\"') (P.char '\"') (P.munch1 (/= '\"'))
pure (Signature, url) pure (Signature, url)
, do , do
key <- P.munch1 (/= '=') _ <- P.string "algorithm="
_ <- P.char '=' alg <- P.between (P.char '\"') (P.char '\"') (P.string "rsa-sha256")
value <- P.between (P.char '\"') (P.char '\"') (P.munch1 (/= '\"')) pure (Algorithm, alg)
pure (Other key, value) -- , do
-- key <- P.munch1 (/= '=')
-- _ <- P.char '='
-- value <- P.between (P.char '\"') (P.char '\"') (P.munch1 (/= '\"'))
-- pure (Other key, value)
] ]