{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}
module Network.Wai.Middleware.HttpAuth
(
basicAuth
, basicAuth'
, CheckCreds
, AuthSettings
, authRealm
, authOnNoAuth
, authIsProtected
, extractBasicAuth
, extractBearerAuth
) where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
#endif
import Data.ByteString (ByteString)
import qualified Data.ByteString as S
import Data.ByteString.Base64 (decodeLenient)
import Data.String (IsString (..))
import Data.Word8 (isSpace, toLower, _colon)
import Network.HTTP.Types (hAuthorization, hContentType, status401)
import Network.Wai (Application, Middleware, Request (requestHeaders), responseLBS)
type CheckCreds = ByteString
-> ByteString
-> IO Bool
basicAuth :: CheckCreds
-> AuthSettings
-> Middleware
basicAuth :: CheckCreds -> AuthSettings -> Middleware
basicAuth CheckCreds
checkCreds = (Request -> CheckCreds) -> AuthSettings -> Middleware
basicAuth' (\Request
_ -> CheckCreds
checkCreds)
basicAuth' :: (Request -> CheckCreds)
-> AuthSettings
-> Middleware
basicAuth' :: (Request -> CheckCreds) -> AuthSettings -> Middleware
basicAuth' Request -> CheckCreds
checkCreds AuthSettings {ByteString
ByteString -> Application
Request -> IO Bool
authIsProtected :: Request -> IO Bool
authOnNoAuth :: ByteString -> Application
authRealm :: ByteString
authIsProtected :: AuthSettings -> Request -> IO Bool
authOnNoAuth :: AuthSettings -> ByteString -> Application
authRealm :: AuthSettings -> ByteString
..} Application
app Request
req Response -> IO ResponseReceived
sendResponse = do
Bool
isProtected <- Request -> IO Bool
authIsProtected Request
req
Bool
allowed <- if Bool
isProtected then IO Bool
check else forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
if Bool
allowed
then Application
app Request
req Response -> IO ResponseReceived
sendResponse
else ByteString -> Application
authOnNoAuth ByteString
authRealm Request
req Response -> IO ResponseReceived
sendResponse
where
check :: IO Bool
check =
case forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup HeaderName
hAuthorization (Request -> RequestHeaders
requestHeaders Request
req)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> Maybe (ByteString, ByteString)
extractBasicAuth of
Maybe (ByteString, ByteString)
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
Just (ByteString
username, ByteString
password) -> Request -> CheckCreds
checkCreds Request
req ByteString
username ByteString
password
data AuthSettings = AuthSettings
{ AuthSettings -> ByteString
authRealm :: !ByteString
, AuthSettings -> ByteString -> Application
authOnNoAuth :: !(ByteString -> Application)
, AuthSettings -> Request -> IO Bool
authIsProtected :: !(Request -> IO Bool)
}
instance IsString AuthSettings where
fromString :: String -> AuthSettings
fromString String
s = AuthSettings
{ authRealm :: ByteString
authRealm = forall a. IsString a => String -> a
fromString String
s
, authOnNoAuth :: ByteString -> Application
authOnNoAuth = \ByteString
realm Request
_req Response -> IO ResponseReceived
f -> Response -> IO ResponseReceived
f forall a b. (a -> b) -> a -> b
$ Status -> RequestHeaders -> ByteString -> Response
responseLBS
Status
status401
[ (HeaderName
hContentType, ByteString
"text/plain")
, (HeaderName
"WWW-Authenticate", [ByteString] -> ByteString
S.concat
[ ByteString
"Basic realm=\""
, ByteString
realm
, ByteString
"\""
])
]
ByteString
"Basic authentication is required"
, authIsProtected :: Request -> IO Bool
authIsProtected = forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
}
extractBasicAuth :: ByteString -> Maybe (ByteString, ByteString)
ByteString
bs =
let (ByteString
x, ByteString
y) = (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
S.break Word8 -> Bool
isSpace ByteString
bs
in if (Word8 -> Word8) -> ByteString -> ByteString
S.map Word8 -> Word8
toLower ByteString
x forall a. Eq a => a -> a -> Bool
== ByteString
"basic"
then ByteString -> Maybe (ByteString, ByteString)
extract forall a b. (a -> b) -> a -> b
$ (Word8 -> Bool) -> ByteString -> ByteString
S.dropWhile Word8 -> Bool
isSpace ByteString
y
else forall a. Maybe a
Nothing
where
extract :: ByteString -> Maybe (ByteString, ByteString)
extract ByteString
encoded =
let raw :: ByteString
raw = ByteString -> ByteString
decodeLenient ByteString
encoded
(ByteString
username, ByteString
password') = (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
S.break (forall a. Eq a => a -> a -> Bool
== Word8
_colon) ByteString
raw
in ((ByteString
username,) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (Word8, ByteString)
S.uncons ByteString
password'
extractBearerAuth :: ByteString -> Maybe ByteString
ByteString
bs =
let (ByteString
x, ByteString
y) = (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
S.break Word8 -> Bool
isSpace ByteString
bs
in if (Word8 -> Word8) -> ByteString -> ByteString
S.map Word8 -> Word8
toLower ByteString
x forall a. Eq a => a -> a -> Bool
== ByteString
"bearer"
then forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ (Word8 -> Bool) -> ByteString -> ByteString
S.dropWhile Word8 -> Bool
isSpace ByteString
y
else forall a. Maybe a
Nothing