Export AuthenticateRequest instance for BasicAuth

This commit is contained in:
aaron levin 2015-08-20 15:16:05 -04:00 committed by Arian van Putten
parent 1ba6dc8300
commit d9c2ebeb01
3 changed files with 16 additions and 11 deletions

View file

@ -33,6 +33,7 @@ library
base >=4.7 && <5 base >=4.7 && <5
, aeson , aeson
, attoparsec , attoparsec
, base64-bytestring
, bytestring , bytestring
, exceptions , exceptions
, http-client , http-client
@ -65,7 +66,6 @@ test-suite spec
, transformers , transformers
, transformers-compat , transformers-compat
, aeson , aeson
, base64-bytestring
, bytestring , bytestring
, deepseq , deepseq
, hspec == 2.* , hspec == 2.*

View file

@ -1,12 +1,25 @@
{-# LANGUAGE OverloadedStrings #-}
-- | Authentication for clients -- | Authentication for clients
module Servant.Client.Authentication ( module Servant.Client.Authentication (
AuthenticateRequest ( authReq ) AuthenticateRequest ( authReq )
) where ) where
import Servant.Common.Req (Req) import Data.ByteString.Base64 (encode)
import Data.Monoid ((<>))
import Data.Text.Encoding (decodeUtf8)
import Servant.API.Authentication (BasicAuth(BasicAuth))
import Servant.Common.Req (addHeader, Req)
-- | Class to represent the ability to authenticate a 'Request' -- | Class to represent the ability to authenticate a 'Request'
-- object. For example, we may add special headers to the 'Request'. -- object. For example, we may add special headers to the 'Request'.
class AuthenticateRequest a where class AuthenticateRequest a where
authReq :: a -> Req -> Req authReq :: a -> Req -> Req
instance AuthenticateRequest (BasicAuth realm) where
authReq (BasicAuth user pass) req =
let authText = decodeUtf8 ("Basic " <> encode (user <> ":" <> pass)) in
addHeader "Authorization" authText req

View file

@ -20,14 +20,12 @@ import Control.Concurrent
import Control.Exception import Control.Exception
import Control.Monad.Trans.Except import Control.Monad.Trans.Except
import Data.Aeson import Data.Aeson
import qualified Data.ByteString.Base64 as B64
import Data.ByteString.Lazy (ByteString) import Data.ByteString.Lazy (ByteString)
import Data.Char import Data.Char
import Data.Foldable (forM_) import Data.Foldable (forM_)
import Data.Monoid import Data.Monoid
import Data.Proxy import Data.Proxy
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import GHC.Generics import GHC.Generics
import qualified Network.HTTP.Client as C import qualified Network.HTTP.Client as C
import Network.HTTP.Media import Network.HTTP.Media
@ -44,8 +42,7 @@ import Test.QuickCheck
import Servant.API import Servant.API
import Servant.API.Authentication import Servant.API.Authentication
import Servant.Client import Servant.Client
import qualified Servant.Common.Req as SCR import Servant.Client.Authentication()
import Servant.Client.Authentication (AuthenticateRequest(authReq))
import Servant.Server import Servant.Server
import Servant.Server.Internal.Authentication import Servant.Server.Internal.Authentication
@ -113,11 +110,6 @@ basicAuthCheck (BasicAuth user pass) = if user == "servant" && pass == "server"
then return (Just $ Person "servant" 17) then return (Just $ Person "servant" 17)
else return Nothing else return Nothing
instance AuthenticateRequest (BasicAuth realm) where
authReq (BasicAuth user pass) req =
let authText = TE.decodeUtf8 ("Basic " <> B64.encode (user <> ":" <> pass)) in
SCR.addHeader "Authorization" authText req
api :: Proxy Api api :: Proxy Api
api = Proxy api = Proxy