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 Data.ByteString.Base64 (decodeLenient)
import Data.String (IsString (..))
import Data.Word8 (isSpace, _colon, toLower)
import Network.HTTP.Types (status401, hContentType, hAuthorization)
import Network.Wai
import qualified Data.ByteString as S
type CheckCreds = ByteString
               -> ByteString
               -> IO Bool
basicAuth :: CheckCreds
          -> AuthSettings
          -> Middleware
basicAuth checkCreds = basicAuth' (\_ -> checkCreds)
basicAuth' :: (Request -> 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 hAuthorization $ requestHeaders req)
             >>= extractBasicAuth of
            Nothing -> return False
            Just (username, password) -> checkCreds req username password
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
            [ (hContentType, "text/plain")
            , ("WWW-Authenticate", S.concat
                [ "Basic realm=\""
                , realm
                , "\""
                ])
            ]
            "Basic authentication is required"
        , authIsProtected = const $ return True
        }
extractBasicAuth :: ByteString -> Maybe (ByteString, ByteString)
extractBasicAuth bs =
    let (x, y) = S.break isSpace bs
    in if S.map toLower x == "basic"
       then extract $ S.dropWhile isSpace y
       else Nothing
  where
    extract encoded =
        let raw = decodeLenient encoded
            (username, password') = S.break (== _colon) raw
        in ((username,) . snd) <$> S.uncons password'
extractBearerAuth :: ByteString -> Maybe ByteString
extractBearerAuth bs =
    let (x, y) = S.break isSpace bs
    in if S.map toLower x == "bearer"
        then Just $ S.dropWhile isSpace y
        else Nothing