Skip to content

Commit baa6496

Browse files
arianvpinfinisil
andauthored
Pass a list of allowed origins instead of a single origin (#184)
* Pass a list of allowed origins instead of a single origin Android and iOS also support WebAuthn just like browsers. The apps will use their AppStore/PlayStore AppID as the origin. This means we need to allow a list of origins instead of a single origin. Apple uses https://developer.apple.com/documentation/xcode/supporting-associated-domains to link the app origin to the RpId Google uses an assetlinks.json file: https://developers.google.com/identity/fido/android/native-apps#interoperability_with_your_website * Add haddocks * add comment * Add changelog item * Fix copy/paste mistake * point to steps * make imports consistent * consistent imports * Remove redundant import * Last import fixed * Remove pure * Add test * Fix precondition * Fix style * Fix hlint * Update changelog.md Co-authored-by: Silvan Mosberger <[email protected]> --------- Co-authored-by: Silvan Mosberger <[email protected]>
1 parent 7229e9b commit baa6496

File tree

6 files changed

+123
-29
lines changed

6 files changed

+123
-29
lines changed

Diff for: changelog.md

+10
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,13 @@
1+
### 0.10.0.0
2+
3+
* [#184](https://github.com/tweag/webauthn/pull/184) Pass a list of allowed origins instead of a single origin.
4+
This is a breaking change needed for allowing native apps to use WebAuthn. It is also needed for Relying Parties
5+
that want to allow multiple subdomains to access WebAuthn credentials.
6+
Unlike the rest of this library, which strictly follows the L2 version of this spec, this feature is defined
7+
in the [L3 draft](https://www.w3.org/TR/webauthn-3/#sctn-validating-origin). However because WebAuthn on
8+
Native Apps is widely deployed through the push of Passkeys we decided to include this feature in this library early.
9+
10+
111
### 0.9.0.0
212

313
* [#182](https://github.com/tweag/webauthn/pull/182) Migrate to the crypton library ecosystem.

Diff for: server/src/Main.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,7 @@ import System.Hourglass (dateCurrent)
4747
import qualified Web.Cookie as Cookie
4848
import Web.Scotty (ScottyM)
4949
import qualified Web.Scotty as Scotty
50+
import qualified Data.List.NonEmpty as NE
5051

5152
data RegisterBeginReq = RegisterBeginReq
5253
{ accountName :: Text,
@@ -261,7 +262,7 @@ completeRegistration origin rpIdHash db pending registryVar = do
261262
-- FIXME
262263
registry <- Scotty.liftAndCatchIO $ readTVarIO registryVar
263264
now <- Scotty.liftAndCatchIO dateCurrent
264-
result <- case WA.verifyRegistrationResponse origin rpIdHash registry now options cred of
265+
result <- case WA.verifyRegistrationResponse (NE.singleton origin) rpIdHash registry now options cred of
265266
Failure errs@(err :| _) -> do
266267
Scotty.liftAndCatchIO $ TIO.putStrLn $ "Register complete had errors: " <> Text.pack (show errs)
267268
fail $ show err
@@ -376,7 +377,7 @@ completeLogin origin rpIdHash db pending = do
376377
-- not be verified.
377378
let verificationResult =
378379
WA.verifyAuthenticationResponse
379-
origin
380+
(NE.singleton origin)
380381
rpIdHash
381382
(Just (WA.ceUserHandle entry))
382383
entry

Diff for: src/Crypto/WebAuthn/Operation/Authentication.hs

+30-6
Original file line numberDiff line numberDiff line change
@@ -36,6 +36,7 @@ import qualified Data.ByteString.Lazy as LBS
3636
import Data.List.NonEmpty (NonEmpty)
3737
import Data.Text (Text)
3838
import Data.Validation (Validation)
39+
import qualified Data.List.NonEmpty as NE
3940

4041
-- | Errors that may occur during [assertion](https://www.w3.org/TR/webauthn-2/#sctn-verifying-assertion)
4142
data AuthenticationError
@@ -78,7 +79,7 @@ data AuthenticationError
7879
AuthenticationOriginMismatch
7980
{ -- | The origin explicitly passed to the `verifyAuthenticationResponse`
8081
-- response, set by the RP
81-
aeExpectedOrigin :: M.Origin,
82+
aeExpectedOrigin :: NonEmpty M.Origin,
8283
-- | The origin received from the client as part of the client data
8384
aeReceivedOrigin :: M.Origin
8485
}
@@ -157,11 +158,32 @@ newtype AuthenticationResult = AuthenticationResult
157158

158159
-- | [(spec)](https://www.w3.org/TR/webauthn-2/#sctn-verifying-assertion)
159160
-- Verifies a 'M.Credential' response for an [authentication ceremony](https://www.w3.org/TR/webauthn-2/#authentication).
161+
--
160162
-- The 'arSignatureCounterResult' field of the result should be inspected to
161163
-- enforce Relying Party policy regarding potentially cloned authenticators.
164+
--
165+
-- Though this library implements the WebAuthn L2 spec, for origin validation we
166+
-- follow the L3 draft. This is because allowing multiple origins is often
167+
-- needed in the wild. See [Validating the origin of a credential](https://www.w3.org/tr/webauthn-3/#sctn-validating-origin)
168+
-- more details.
169+
-- In the simplest case, just a single origin is allowed and this is the 'M.RpId' with @https://@ prepended:
170+
--
171+
-- > verifyAuthenticationResponse (NE.singleton (M.Origin "https://example.org")) ...
172+
--
173+
-- In the more complex case, multiple origins are allowed:
174+
--
175+
-- > verifyAuthenticationResponse (M.Origin <$> "https://example.org" :| ["https://signin.example.org"]) ...
176+
--
177+
-- One might also allow native apps to authenticate:
178+
--
179+
-- > verifyAuthenticationResponse (M.Origin <$> "https://example.org" :| ["ios:bundle-id:org.example.ourapp"]) ...
180+
--
181+
-- See Apple's documentation on [associated domains](https://developer.apple.com/documentation/authenticationservices/public-private_key_authentication/supporting_passkeys/)
182+
-- and Google's documentation on [Digital Asset Links](https://developers.google.com/identity/passkeys/developer-guides) for more information on how to link app
183+
-- origins to your Relying Party ID.
162184
verifyAuthenticationResponse ::
163-
-- | The origin of the server
164-
M.Origin ->
185+
-- | The list of allowed origins for the ceremony
186+
NonEmpty M.Origin ->
165187
-- | The hash of the relying party id
166188
M.RpIdHash ->
167189
-- | The user handle, in case the user is identified already
@@ -179,7 +201,7 @@ verifyAuthenticationResponse ::
179201
-- Or in case of success a signature counter result, which should be dealt
180202
-- with
181203
Validation (NonEmpty AuthenticationError) AuthenticationResult
182-
verifyAuthenticationResponse origin rpIdHash midentifiedUser entry options credential = do
204+
verifyAuthenticationResponse origins rpIdHash midentifiedUser entry options credential = do
183205
-- 1. Let options be a new PublicKeyCredentialRequestOptions structure
184206
-- configured to the Relying Party's needs for the ceremony.
185207
-- NOTE: Implemented by caller
@@ -290,9 +312,11 @@ verifyAuthenticationResponse origin rpIdHash midentifiedUser entry options crede
290312
AuthenticationChallengeMismatch (M.coaChallenge options) (M.ccdChallenge c)
291313

292314
-- 13. Verify that the value of C.origin matches the Relying Party's origin.
293-
unless (M.ccdOrigin c == origin) $
315+
-- NOTE: We follow the L3 draft of the spec here, which allows for multiple origins.
316+
-- https://www.w3.org/TR/webauthn-3/#rp-op-verifying-assertion-step-origin
317+
unless (M.ccdOrigin c `elem` NE.toList origins) $
294318
failure $
295-
AuthenticationOriginMismatch origin (M.ccdOrigin c)
319+
AuthenticationOriginMismatch origins (M.ccdOrigin c)
296320

297321
-- 14. Verify that the value of C.tokenBinding.status matches the state of
298322
-- Token Binding for the TLS connection over which the attestation was

Diff for: src/Crypto/WebAuthn/Operation/Registration.hs

+30-6
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,7 @@ data RegistrationError
7272
RegistrationOriginMismatch
7373
{ -- | The origin explicitly passed to the `verifyRegistrationResponse`
7474
-- response, set by the RP
75-
reExpectedOrigin :: M.Origin,
75+
reExpectedOrigin :: NonEmpty M.Origin,
7676
-- | The origin received from the client as part of the client data
7777
reReceivedOrigin :: M.Origin
7878
}
@@ -264,13 +264,35 @@ data RegistrationResult = RegistrationResult
264264
deriving instance ToJSON RegistrationResult
265265

266266
-- | [(spec)](https://www.w3.org/TR/webauthn-2/#sctn-registering-a-new-credential)
267+
-- Verifies a 'M.Credential' response for a [registration ceremony](https://www.w3.org/TR/webauthn-2/#registration-ceremony).
268+
--
267269
-- The resulting 'rrEntry' of this call should be stored in a database by the
268270
-- Relying Party. The 'rrAttestationStatement' contains the result of the
269271
-- attempted attestation, allowing the Relying Party to reject certain
270272
-- authenticators/attempted entry creations based on policy.
273+
--
274+
-- Though this library implements the WebAuthn L2 spec, for origin validation we
275+
-- follow the L3 draft. This is because allowing multiple origins is often
276+
-- needed in the wild. See [Validating the origin of a credential](https://www.w3.org/TR/webauthn-3/#sctn-validating-origin)
277+
-- more details.
278+
-- In the simplest case, just a single origin is allowed and this is the 'M.RpId' with @https://@ prepended:
279+
--
280+
-- > verifyRegistrationResponse (NE.singleton (M.Origin "https://example.org")) ...
281+
--
282+
-- In the more complex case, multiple origins are allowed:
283+
--
284+
-- > verifyRegistrationResponse (M.Origin <$> "https://example.org" :| ["https://signin.example.org"]) ...
285+
--
286+
-- One might also allow native apps to authenticate:
287+
--
288+
-- > verifyRegistrationResponse (M.Origin <$> "https://example.org" :| ["ios:bundle-id:org.example.ourapp"]) ...
289+
--
290+
-- See Apple's documentation on [associated domains](https://developer.apple.com/documentation/authenticationservices/public-private_key_authentication/supporting_passkeys/)
291+
-- and Google's documentation on [Digital Asset Links](https://developers.google.com/identity/passkeys/developer-guides) for more information on how to link app
292+
-- origins to your Relying Party ID.
271293
verifyRegistrationResponse ::
272-
-- | The origin of the server
273-
M.Origin ->
294+
-- | The list of allowed origins for the ceremony
295+
NonEmpty M.Origin ->
274296
-- | The relying party id
275297
M.RpIdHash ->
276298
-- | The metadata registry, used for verifying the validity of the
@@ -287,7 +309,7 @@ verifyRegistrationResponse ::
287309
-- Or () in case of a result.
288310
Validation (NonEmpty RegistrationError) RegistrationResult
289311
verifyRegistrationResponse
290-
rpOrigin
312+
origins
291313
rpIdHash
292314
registry
293315
currentTime
@@ -349,9 +371,11 @@ verifyRegistrationResponse
349371
RegistrationChallengeMismatch corChallenge (M.ccdChallenge c)
350372

351373
-- 9. Verify that the value of C.origin matches the Relying Party's origin.
352-
unless (rpOrigin == M.ccdOrigin c) $
374+
-- NOTE: We follow the L3 draft of the spec here, which allows for multiple origins.
375+
-- https://www.w3.org/TR/webauthn-3/#rp-op-registering-a-new-credential-step-origin
376+
unless (M.ccdOrigin c `elem` NE.toList origins) $
353377
failure $
354-
RegistrationOriginMismatch rpOrigin (M.ccdOrigin c)
378+
RegistrationOriginMismatch origins (M.ccdOrigin c)
355379

356380
-- 10. Verify that the value of C.tokenBinding.status matches the state of
357381
-- Token Binding for the TLS connection over which the assertion was

Diff for: tests/Emulation.hs

+45-10
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ import Emulation.Client
3737
import Emulation.Client.Arbitrary ()
3838
import Spec.Util (predeterminedDateTime)
3939
import Test.Hspec (SpecWith, describe, it, shouldSatisfy)
40-
import Test.QuickCheck (property)
40+
import Test.QuickCheck (property, (==>))
4141

4242
-- | Custom type to combine the MonadPseudoRandom with the Except monad. We
4343
-- force the ChaChaDRG to ensure the App type is completely pure, and
@@ -61,12 +61,13 @@ runApp seed (App except) =
6161
register ::
6262
(Random.MonadRandom m, MonadFail m) =>
6363
AnnotatedOrigin ->
64+
NE.NonEmpty M.Origin ->
6465
UserAgentConformance ->
6566
Authenticator ->
6667
Meta.MetadataServiceRegistry ->
6768
DateTime ->
6869
m (Either (NE.NonEmpty O.RegistrationError) O.RegistrationResult, Authenticator, M.CredentialOptions 'M.Registration)
69-
register ao conformance authenticator registry now = do
70+
register ao allowedOrigins conformance authenticator registry now = do
7071
-- Generate new random input
7172
assertionChallenge <- M.generateChallenge
7273
userId <- M.generateUserHandle
@@ -84,7 +85,7 @@ register ao conformance authenticator registry now = do
8485
let registerResult =
8586
toEither $
8687
O.verifyRegistrationResponse
87-
(aoOrigin ao)
88+
allowedOrigins
8889
(M.RpIdHash . hash . encodeUtf8 . M.unRpId $ aoRpId ao)
8990
registry
9091
now
@@ -95,11 +96,12 @@ register ao conformance authenticator registry now = do
9596
login ::
9697
(Random.MonadRandom m, MonadFail m) =>
9798
AnnotatedOrigin ->
99+
NE.NonEmpty M.Origin ->
98100
UserAgentConformance ->
99101
Authenticator ->
100102
O.CredentialEntry ->
101103
m (Either (NE.NonEmpty O.AuthenticationError) O.SignatureCounterResult)
102-
login ao conformance authenticator ce@O.CredentialEntry {..} = do
104+
login ao allowedOrigins conformance authenticator ce@O.CredentialEntry {..} = do
103105
attestationChallenge <- M.generateChallenge
104106
let options = defaultCog attestationChallenge
105107
-- Perform client assertion emulation with the same authenticator, this
@@ -109,7 +111,7 @@ login ao conformance authenticator [email protected] {..} = do
109111
. second O.arSignatureCounterResult
110112
. toEither
111113
$ O.verifyAuthenticationResponse
112-
(aoOrigin ao)
114+
allowedOrigins
113115
(M.RpIdHash . hash . encodeUtf8 . M.unRpId $ aoRpId ao)
114116
(Just ceUserHandle)
115117
ce
@@ -118,27 +120,60 @@ login ao conformance authenticator [email protected] {..} = do
118120

119121
spec :: SpecWith ()
120122
spec =
121-
describe "None" $
123+
describe "None" $ do
124+
it "rejects unknown origin during registration" $ do
125+
property $ \seed authenticator allowedOrigins' origin' -> not (null allowedOrigins') && origin' `notElem` allowedOrigins' ==> do
126+
let origin = M.Origin origin'
127+
let allowedOrigins = M.Origin <$> NE.fromList allowedOrigins'
128+
let annotatedOrigin = AnnotatedOrigin { aoRpId = M.RpId "localhost", aoOrigin = origin }
129+
let registry = mempty
130+
let userAgentConformance = mempty
131+
let Right (registerResult, _, _) = runApp seed (register annotatedOrigin allowedOrigins userAgentConformance authenticator registry predeterminedDateTime)
132+
registerResult `shouldSatisfy` \case
133+
Left errors -> any (\case O.RegistrationOriginMismatch _ _ -> True; _ -> False) errors
134+
Right _ -> False
135+
it "rejects unknown origin during login" $ do
136+
property $ \seed authenticator allowedOrigins' origin' -> not (null allowedOrigins') && origin' `notElem` allowedOrigins' ==> do
137+
let allowedOrigins = M.Origin <$> NE.fromList allowedOrigins'
138+
let origin = NE.head allowedOrigins
139+
let wrongOrigin = M.Origin origin'
140+
let annotatedOrigin = AnnotatedOrigin { aoRpId = M.RpId "localhost", aoOrigin = origin }
141+
let wrongAnnotatedOrigin = AnnotatedOrigin { aoRpId = M.RpId "localhost", aoOrigin = wrongOrigin }
142+
let registry = mempty
143+
let userAgentConformance = mempty
144+
let Right (registerResult, authenticator', options) = runApp seed (register annotatedOrigin allowedOrigins userAgentConformance authenticator registry predeterminedDateTime)
145+
let registerResult' = second O.rrEntry registerResult
146+
registerResult' `shouldSatisfy` validAttestationResult authenticator userAgentConformance options
147+
case registerResult' of
148+
Right credentialEntry -> do
149+
let Right loginResult = runApp (seed + 1) (login wrongAnnotatedOrigin allowedOrigins userAgentConformance authenticator' credentialEntry)
150+
loginResult `shouldSatisfy` \case
151+
Left errors -> any (\case O.AuthenticationOriginMismatch _ _ -> True; _ -> False) errors
152+
Right _ -> False
153+
_ -> pure ()
154+
122155
it "succeeds" $
123-
property $ \seed authenticator userAgentConformance -> do
156+
property $ \seed authenticator userAgentConformance allowedOrigins' -> length allowedOrigins' > 1 ==> do
157+
let allowedOrigins = M.Origin <$> NE.fromList allowedOrigins'
124158
let annotatedOrigin =
125159
AnnotatedOrigin
126160
{ aoRpId = M.RpId "localhost",
127-
aoOrigin = M.Origin "https://localhost:8080"
161+
aoOrigin = NE.head allowedOrigins
128162
}
163+
129164
-- Since our emulator only supports None attestation the registry can be left empty.
130165
let registry = mempty
131166
-- We are not currently interested in client or authenticator fails, we
132167
-- only wish to test our relying party implementation and are thus only
133168
-- interested in its errors.
134-
let Right (registerResult, authenticator', options) = runApp seed (register annotatedOrigin userAgentConformance authenticator registry predeterminedDateTime)
169+
let Right (registerResult, authenticator', options) = runApp seed (register annotatedOrigin allowedOrigins userAgentConformance authenticator registry predeterminedDateTime)
135170
-- Since we only do None attestation, we only care about the resulting entry
136171
let registerResult' = second O.rrEntry registerResult
137172
registerResult' `shouldSatisfy` validAttestationResult authenticator userAgentConformance options
138173
-- Only if attestation succeeded can we continue with assertion
139174
case registerResult' of
140175
Right credentialEntry -> do
141-
let Right loginResult = runApp (seed + 1) (login annotatedOrigin userAgentConformance authenticator' credentialEntry)
176+
let Right loginResult = runApp (seed + 1) (login annotatedOrigin allowedOrigins userAgentConformance authenticator' credentialEntry)
142177
loginResult `shouldSatisfy` validAssertionResult authenticator userAgentConformance
143178
_ -> pure ()
144179

Diff for: tests/Main.hs

+5-5
Original file line numberDiff line numberDiff line change
@@ -80,7 +80,7 @@ registerTestFromFile fp origin rpId verifiable service now = do
8080
let registerResult =
8181
toEither $
8282
O.verifyRegistrationResponse
83-
origin
83+
(NE.singleton origin)
8484
(M.RpIdHash . hash . encodeUtf8 . M.unRpId $ rpId)
8585
service
8686
now
@@ -125,7 +125,7 @@ main = Hspec.hspec $ do
125125
registerResult =
126126
toEither $
127127
O.verifyRegistrationResponse
128-
(M.Origin "http://localhost:8080")
128+
(NE.singleton $ M.Origin "http://localhost:8080")
129129
(M.RpIdHash . hash $ ("localhost" :: ByteString.ByteString))
130130
registry
131131
predeterminedDateTime
@@ -142,7 +142,7 @@ main = Hspec.hspec $ do
142142
signInResult =
143143
toEither $
144144
O.verifyAuthenticationResponse
145-
(M.Origin "http://localhost:8080")
145+
(NE.singleton $ M.Origin "http://localhost:8080")
146146
(M.RpIdHash . hash $ ("localhost" :: ByteString.ByteString))
147147
(Just (M.UserHandle "UserId"))
148148
credentialEntry
@@ -163,7 +163,7 @@ main = Hspec.hspec $ do
163163
registerResult =
164164
toEither $
165165
O.verifyRegistrationResponse
166-
(M.Origin "http://localhost:8080")
166+
(NE.singleton $ M.Origin "http://localhost:8080")
167167
(M.RpIdHash . hash $ ("localhost" :: ByteString.ByteString))
168168
registry
169169
predeterminedDateTime
@@ -180,7 +180,7 @@ main = Hspec.hspec $ do
180180
signInResult =
181181
toEither $
182182
O.verifyAuthenticationResponse
183-
(M.Origin "http://localhost:8080")
183+
(NE.singleton $ M.Origin "http://localhost:8080")
184184
(M.RpIdHash . hash $ ("localhost" :: ByteString.ByteString))
185185
(Just (M.UserHandle "UserId"))
186186
credentialEntry

0 commit comments

Comments
 (0)