module Network.Wai.Middleware.HttpAuth
( basicAuth
, CheckCreds
, AuthSettings
, authRealm
, authOnNoAuth
, authIsProtected
) where
import Network.Wai
import Network.HTTP.Types (status401)
import Data.ByteString (ByteString)
import qualified Data.ByteString as S
import Data.String (IsString (..))
import Data.Word8 (isSpace, _colon, toLower)
import Data.ByteString.Base64 (decodeLenient)
type CheckCreds = ByteString
-> ByteString
-> IO Bool
basicAuth :: CheckCreds
-> AuthSettings
-> Middleware
basicAuth checkCreds AuthSettings {..} app req sendResponse = do
isProtected <- authIsProtected req
allowed <- if isProtected then check else return True
if allowed
then app req sendResponse
else authOnNoAuth authRealm req sendResponse
where
check =
case lookup "Authorization" $ requestHeaders req of
Nothing -> return False
Just bs ->
let (x, y) = S.break isSpace bs
in if S.map toLower x == "basic"
then checkB64 $ S.dropWhile isSpace y
else return False
checkB64 encoded =
case S.uncons password' of
Just (_, password) -> checkCreds username password
Nothing -> return False
where
raw = decodeLenient encoded
(username, password') = S.breakByte _colon raw
data AuthSettings = AuthSettings
{ authRealm :: !ByteString
, authOnNoAuth :: !(ByteString -> Application)
, authIsProtected :: !(Request -> IO Bool)
}
instance IsString AuthSettings where
fromString s = AuthSettings
{ authRealm = fromString s
, authOnNoAuth = \realm _req f -> f $ responseLBS
status401
[ ("Content-Type", "text/plain")
, ("WWW-Authenticate", S.concat
[ "Basic realm=\""
, realm
, "\""
])
]
"Basic authentication is required"
, authIsProtected = const $ return True
}