Skip to content

Commit

Permalink
Adding public key checks (#10)
Browse files Browse the repository at this point in the history
* Adding public key checks

* Fixing the style
  • Loading branch information
kubek2k authored Jan 19, 2021
1 parent 3921c68 commit 4b2efe3
Show file tree
Hide file tree
Showing 3 changed files with 29 additions and 11 deletions.
21 changes: 17 additions & 4 deletions src/WebAuthn.hs
Original file line number Diff line number Diff line change
Expand Up @@ -60,6 +60,7 @@ import qualified WebAuthn.TPM as TPM
import qualified WebAuthn.FIDOU2F as U2F
import qualified WebAuthn.Packed as Packed
import qualified WebAuthn.AndroidSafetyNet as Android
import Control.Monad (when)
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.Trans.Except (runExceptT, ExceptT(..), throwE)
import Data.Text (pack)
Expand Down Expand Up @@ -137,25 +138,27 @@ encodeAttestation attestationObject = CBOR.encodeMapLen 3
AF_None -> CBOR.encodeString ""

-- | 7.1. Registering a New Credential
registerCredential :: MonadIO m => X509.CertificateStore
registerCredential :: MonadIO m => PublicKeyCredentialCreationOptions
-> X509.CertificateStore
-> Challenge
-> RelyingParty
-> Maybe Text -- ^ Token Binding ID in base64
-> Bool -- ^ require user verification?
-> ByteString -- ^ clientDataJSON
-> ByteString -- ^ attestationObject
-> m (Either VerificationFailure AttestedCredentialData)
registerCredential cs challenge (RelyingParty rpOrigin rpId _ _) tbi verificationRequired clientDataJSON attestationObjectBS = runExceptT $ do
registerCredential opts cs challenge (RelyingParty rpOrigin rpId _ _) tbi verificationRequired clientDataJSON attestationObjectBS = runExceptT $ do
_ <- hoistEither runAttestationCheck
attestationObject <- hoistEither $ either (Left . CBORDecodeError "registerCredential") (pure . snd)
$ CBOR.deserialiseFromBytes decodeAttestation
$ BL.fromStrict
$ attestationObjectBS
ad <- hoistEither $ extractAuthData attestationObject
-- TODO: extensions here
mAdPubKey <- verifyPubKey ad
-- TODO: extensions here
case (attStmt attestationObject) of
AF_FIDO_U2F s -> hoistEither $ U2F.verify s ad clientDataHash
AF_Packed s -> hoistEither $ Packed.verify s ad (authData attestationObject) clientDataHash
AF_Packed s -> hoistEither $ Packed.verify s mAdPubKey (authData attestationObject) clientDataHash
AF_TPM s -> hoistEither $ TPM.verify s ad (authData attestationObject) clientDataHash
AF_AndroidSafetyNet s -> Android.verify cs s (authData attestationObject) clientDataHash
AF_None -> pure ()
Expand Down Expand Up @@ -186,6 +189,16 @@ registerCredential cs challenge (RelyingParty rpOrigin rpId _ _) tbi verificatio
userPresent ad ?? UserNotPresent
not verificationRequired || userVerified ad ?? UserUnverified
pure ad
verifyPubKey ad = do
let pubKey = credentialPublicKey <$> attestedCredentialData ad
case pubKey of
Just k -> do
parsedPubKey <- either throwE return $ parsePublicKey k
let hasProperAlg pubKeyParam = hasMatchingAlg parsedPubKey $ alg (pubKeyParam :: PubKeyCredParam)
when (not . any hasProperAlg $ pubKeyCredParams opts) $ throwE MalformedAuthenticatorData
return $ Just parsedPubKey
-- non present public key will fail anyway or the fmt == 'none'
Nothing -> return Nothing

-- | 7.2. Verifying an Authentication Assertion
verify :: Challenge
Expand Down
10 changes: 4 additions & 6 deletions src/WebAuthn/Packed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,18 +30,16 @@ decode (CBOR.TMap xs) = do
decode _ = fail "Packed.decode: expected a Map"

verify :: Stmt
-> AuthenticatorData
-> Maybe PublicKey
-> ByteString
-> Digest SHA256
-> Either VerificationFailure ()
verify (Stmt _ sig cert) ad adRaw clientDataHash = do
verify (Stmt _ sig cert) mAdPubKey adRaw clientDataHash = do
let dat = adRaw <> BA.convert clientDataHash
case cert of
Just x509 -> do
let pub = X509.certPubKey $ X509.getCertificate x509
verifyX509Sig (X509.SignatureALG X509.HashSHA256 X509.PubKeyALG_EC) pub dat sig "Packed"
Nothing -> do
pub <- case attestedCredentialData ad of
Nothing -> Left MalformedAuthenticatorData
Just c -> parsePublicKey $ credentialPublicKey c
verifySig pub sig dat
adPubKey <- maybe (Left MalformedAuthenticatorData) return mAdPubKey
verifySig adPubKey sig dat
9 changes: 8 additions & 1 deletion src/WebAuthn/Signature.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ module WebAuthn.Signature (PublicKey(..)
, verifySig
, verifyX509Sig
, encodeECSSignature
, hasMatchingAlg
) where

import Control.Monad ((>=>))
Expand Down Expand Up @@ -41,6 +42,12 @@ verifySig (PubRSA pub) sig dat
| Just dat' <- parseRS256Signature (RSA.ep pub sig), dat' == BA.convert (hashWith SHA256 dat) = pure ()
| otherwise = Left $ SignatureFailure "RS256"

hasMatchingAlg :: PublicKey -> PubKeyCredAlg -> Bool
hasMatchingAlg key algo =
case key of
PubEC (EC.PublicKey curve _) -> algo == ES256 && curve == EC.getCurveByName EC.SEC_p256r1
PubRSA (RSA.PublicKey size _ _) -> algo == RS256 && size == 256

parsePublicKey :: CredentialPublicKey -> Either VerificationFailure PublicKey
parsePublicKey pub = do
m <- either (Left . CBORDecodeError "parsePublicKey") pure
Expand Down Expand Up @@ -98,4 +105,4 @@ unpad packed
verifyX509Sig :: X509.SignatureALG -> X509.PubKey -> B.ByteString -> B.ByteString -> [Char] -> Either VerificationFailure ()
verifyX509Sig sigType pub dat sig msg = case X509.verifySignature sigType pub dat sig of
X509.SignaturePass -> pure ()
X509.SignatureFailed e -> Left (SignatureFailure (msg <> " " <> show e))
X509.SignatureFailed e -> Left (SignatureFailure (msg <> " " <> show e))

0 comments on commit 4b2efe3

Please sign in to comment.