Change JSON to be the bearing type of JWT auth.

This way both client and server can be the same API type.
This commit is contained in:
Arian van Putten 2015-10-01 14:36:11 +02:00
parent c19efbcec0
commit 297f5743ec
2 changed files with 14 additions and 6 deletions

View file

@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeSynonymInstances #-}
-- | Authentication for clients -- | Authentication for clients
@ -8,6 +9,7 @@ module Servant.Client.Authentication (
import Data.ByteString.Base64 (encode) import Data.ByteString.Base64 (encode)
import Data.Monoid ((<>)) import Data.Monoid ((<>))
import Data.Text (Text)
import Data.Text.Encoding (decodeUtf8) import Data.Text.Encoding (decodeUtf8)
import Servant.API.Authentication (BasicAuth(BasicAuth)) import Servant.API.Authentication (BasicAuth(BasicAuth))
import Servant.Common.Req (addHeader, Req) import Servant.Common.Req (addHeader, Req)
@ -23,3 +25,8 @@ instance AuthenticateRequest (BasicAuth realm) where
let authText = decodeUtf8 ("Basic " <> encode (user <> ":" <> pass)) in let authText = decodeUtf8 ("Basic " <> encode (user <> ":" <> pass)) in
addHeader "Authorization" authText req addHeader "Authorization" authText req
type JSON = Text
instance AuthenticateRequest JSON where
authReq token req =
let authText = ("Bearer " <> token)
in addHeader "Authorization" authText req

View file

@ -38,7 +38,7 @@ import Servant.API.Authentication (AuthPolicy (Strict, Lax),
AuthProtected, AuthProtected,
BasicAuth (BasicAuth)) BasicAuth (BasicAuth))
import Web.JWT (JWT, UnverifiedJWT, VerifiedJWT, Secret) import Web.JWT (JWT, UnverifiedJWT, VerifiedJWT, Secret, JSON)
import qualified Web.JWT as JWT (decode, verify) import qualified Web.JWT as JWT (decode, verify)
-- | Class to represent the ability to extract authentication-related -- | Class to represent the ability to extract authentication-related
@ -116,15 +116,16 @@ basicAuthLax = laxProtect
instance AuthData (JWT UnverifiedJWT) where instance AuthData JSON where
authData req = do authData req = do
-- We might want to write a proper parser for this? but split works fine... -- We might want to write a proper parser for this? but split works fine...
hdr <- lookup "Authorization" . requestHeaders $ req hdr <- lookup "Authorization" . requestHeaders $ req
["Bearer", token] <- return . splitOn " " . decodeUtf8 $ hdr ["Bearer", token] <- return . splitOn " " . decodeUtf8 $ hdr
JWT.decode token _ <- JWT.decode token -- try decode it. otherwise it's not a proper token
return token
jwtAuthHandlers :: AuthHandlers (JWT UnverifiedJWT) jwtAuthHandlers :: AuthHandlers JSON
jwtAuthHandlers = jwtAuthHandlers =
let authFailure = responseBuilder status401 [] mempty let authFailure = responseBuilder status401 [] mempty
in AuthHandlers (return authFailure) ((const . return) authFailure) in AuthHandlers (return authFailure) ((const . return) authFailure)
@ -134,6 +135,6 @@ jwtAuthHandlers =
-- Use this to quickly add jwt authentication to your project. -- Use this to quickly add jwt authentication to your project.
-- One can use strictProtect and laxProtect to make more complex authentication -- One can use strictProtect and laxProtect to make more complex authentication
-- and authorization schemes. For an example of that, see our tutorial: @placeholder@ -- and authorization schemes. For an example of that, see our tutorial: @placeholder@
jwtAuth :: Secret -> subserver -> AuthProtected (JWT UnverifiedJWT) (JWT VerifiedJWT) subserver 'Strict jwtAuth :: Secret -> subserver -> AuthProtected JSON (JWT VerifiedJWT) subserver 'Strict
jwtAuth secret subserver = strictProtect (return . JWT.verify secret) jwtAuthHandlers subserver jwtAuth secret subserver = strictProtect (return . (JWT.verify secret <=< JWT.decode)) jwtAuthHandlers subserver