{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Wordpress.Auth
(
authorizeWordpressRequest
, WPAuthConfig(..)
, UserAuthData(..)
, WPAuthorization(..)
, WPAuthError(..)
, CookieName(..)
, cookieName
, findCookie
, CookieHeaderError(..)
, findNonce
, WPCookie(..)
, CookieToken(..)
, parseWordpressCookie
, CookieParseError(..)
, validateCookie
, WordpressUserPass(..)
, CookieValidationError(..)
, validateCookieHash
, SessionToken(..)
, decodeSessionTokens
, validateSessionToken
, NonceTick(..)
, wordpressNonceTick
, validateNonce
, WordpressUserId(..)
, wordpressHash
, wordpressSalt
, AuthScheme(..)
, WordpressKey
, WordpressSalt
, wpConfigKey
, wpConfigSalt
)
where
import Control.Applicative ( (<|>) )
import Control.Monad ( (<=<)
, join
, void
, unless
)
import Control.Monad.Except ( MonadIO
, ExceptT
, withExceptT
, runExceptT
, liftEither
, liftIO
, lift
, throwError
)
import qualified Crypto.Hash.MD5 as MD5
import qualified Crypto.Hash.SHA256 as SHA256
import qualified Data.ByteString as B
import qualified Data.ByteString.Base16 as Base16
import qualified Data.ByteString.Lazy as LBS
import qualified Data.List as L
import Data.Maybe ( mapMaybe
, isJust
)
import Data.PHPSession ( PHPSessionValue(..)
, decodePHPSessionValue
)
import qualified Data.Text as T
import Data.Text ( Text )
import Data.Text.Encoding ( encodeUtf8
, decodeUtf8
)
import Data.Time.Clock ( NominalDiffTime )
import Data.Time.Clock.POSIX ( POSIXTime
, getPOSIXTime
)
import Network.HTTP.Types ( RequestHeaders
, QueryItem
)
import qualified Network.URI.Encode as URI
import Text.Read ( readMaybe )
import Web.Cookie ( parseCookiesText )
authorizeWordpressRequest
:: forall m a
. MonadIO m
=> WPAuthConfig m a
-> RequestHeaders
-> [QueryItem]
-> m (WPAuthorization a)
authorizeWordpressRequest cfg headers query =
either (onAuthenticationFailure cfg) return <=< runExceptT $ do
name <- lift $ getCookieName cfg
currentTime <- liftIO getPOSIXTime
either (const $ validateAnonymousUser currentTime)
(validateAuthorizedUser currentTime)
$ findCookie name headers
where
validateAnonymousUser
:: POSIXTime -> ExceptT WPAuthError m (WPAuthorization a)
validateAnonymousUser currentTime =
checkNonce currentTime Nothing Nothing >> return WPAnonymousUser
validateAuthorizedUser
:: POSIXTime -> Text -> ExceptT WPAuthError m (WPAuthorization a)
validateAuthorizedUser currentTime rawCookie = do
parsedCookie <- liftWith EParse $ parseWordpressCookie rawCookie
UserAuthData { userData, wpUser, wpPass, wpTokens } <-
lift (getUserData cfg $ username parsedCookie)
>>= liftMaybe UserDataNotFound
void . liftWith EValid $ validateCookie (loggedInScheme cfg)
currentTime
parsedCookie
wpPass
wpTokens
checkNonce currentTime (Just $ token parsedCookie) (Just wpUser)
return $ WPAuthorizedUser userData
checkNonce
:: POSIXTime
-> Maybe CookieToken
-> Maybe WordpressUserId
-> ExceptT WPAuthError m ()
checkNonce time mToken mUser = do
nonce <- liftMaybe NoNonce $ findNonce headers query
let nonceTick = wordpressNonceTick (nonceLifetime cfg) time
nonceIsValid = validateNonce (nonceScheme cfg)
mToken
nonceTick
mUser
"wp_rest"
nonce
unless nonceIsValid $ throwError InvalidNonce
liftMaybe :: e -> Maybe b -> ExceptT e m b
liftMaybe e m = liftEither $ maybe (Left e) Right m
liftWith :: (e2 -> e1) -> Either e2 b -> ExceptT e1 m b
liftWith e = withExceptT e . liftEither
data WPAuthorization a
= WPAuthorizedUser a
| WPAnonymousUser
deriving (Show, Eq)
data WPAuthConfig m a
= WPAuthConfig
{ getCookieName :: m CookieName
, loggedInScheme :: AuthScheme
, nonceScheme :: AuthScheme
, nonceLifetime :: NominalDiffTime
, getUserData :: Text -> m (Maybe (UserAuthData a))
, onAuthenticationFailure :: WPAuthError -> m (WPAuthorization a)
}
data UserAuthData a =
UserAuthData
{ userData :: a
, wpUser :: WordpressUserId
, wpPass :: WordpressUserPass
, wpTokens :: [SessionToken]
}
deriving (Show, Eq)
data WPAuthError
= EHeader CookieHeaderError
| EParse CookieParseError
| EValid CookieValidationError
| UserDataNotFound
| NoNonce
| InvalidNonce
deriving (Show, Eq)
data CookieName
= CustomCookieName Text
| CookieNameWithMD5 Text Text
deriving (Show, Eq)
cookieName :: CookieName -> Text
cookieName = \case
CustomCookieName n -> n
CookieNameWithMD5 name textToHash ->
name <> hashText MD5.hash (HashMessage textToHash)
findCookie :: CookieName -> RequestHeaders -> Either CookieHeaderError Text
findCookie name headers = do
header <- liftMaybe NoCookieHeader $ lookup "cookie" headers
let cookieBody = parseCookiesText header
authCookie = URI.decodeText <$> lookup (cookieName name) cookieBody
liftMaybe NoCookieMatches authCookie
where liftMaybe e = maybe (Left e) Right
data CookieHeaderError
= NoCookieHeader
| NoCookieMatches
deriving (Show, Eq)
findNonce :: RequestHeaders -> [QueryItem] -> Maybe Text
findNonce headers query =
fmap decodeUtf8 $ lookup "x-wp-nonce" headers <|> join
(lookup "_wpnonce" query)
data WPCookie
= WPCookie
{ username :: Text
, expiration :: POSIXTime
, token :: CookieToken
, hmac :: Text
}
deriving (Show, Eq)
newtype CookieToken
= CookieToken { cookieToken :: Text }
deriving (Show, Eq)
data CookieParseError
= MalformedCookie
| InvalidExpiration
deriving (Show, Eq)
parseWordpressCookie :: Text -> Either CookieParseError WPCookie
parseWordpressCookie rawCookie = case T.splitOn "|" rawCookie of
[username, expiration_, token_, hmac] ->
let token = CookieToken token_
in case fromInteger <$> readMaybe (T.unpack expiration_) of
Just expiration -> Right WPCookie { .. }
Nothing -> Left InvalidExpiration
_ -> Left MalformedCookie
newtype WordpressUserId
= WordpressUserId { wordpressUserId :: Integer }
deriving (Show, Eq)
newtype WordpressUserPass
= WordpressUserPass { wordpressUserPass :: Text }
deriving (Show, Eq)
validateCookieHash :: AuthScheme -> WPCookie -> WordpressUserPass -> Bool
validateCookieHash scheme cookie userPass =
let
passwordFragment = T.take 4 $ T.drop 8 $ wordpressUserPass userPass
user = username cookie
tok = cookieToken $ token cookie
secret = wordpressHash scheme $ joinHashParts
[user, passwordFragment, posixText $ expiration cookie, tok]
hash =
hmacText SHA256.hmac (HashSecret secret)
$ HashMessage
$ joinHashParts [user, posixText $ expiration cookie, tok]
in
hash == hmac cookie
where
posixText :: POSIXTime -> Text
posixText t = T.pack $ show (floor t :: Integer)
validateCookie
:: AuthScheme
-> POSIXTime
-> WPCookie
-> WordpressUserPass
-> [SessionToken]
-> Either CookieValidationError ()
validateCookie scheme currentTime cookie userPass sessionTokens =
let validHash = validateCookieHash scheme cookie userPass
validSessionToken =
validateSessionToken currentTime (token cookie) sessionTokens
in if currentTime > expiration cookie
then Left CookieExpired
else case (validHash, validSessionToken) of
(False, _ ) -> Left InvalidHash
(_ , False) -> Left InvalidToken
(True , True ) -> Right ()
data CookieValidationError
= CookieExpired
| InvalidHash
| InvalidToken
deriving (Show, Eq)
wordpressHash :: AuthScheme -> Text -> Text
wordpressHash scheme textToHash =
let secret = HashSecret $ wordpressSalt scheme
in hmacText MD5.hmac secret $ HashMessage textToHash
wordpressSalt :: AuthScheme -> Text
wordpressSalt AuthScheme { schemeKey, schemeSalt } =
unKey schemeKey <> unSalt schemeSalt
data SessionToken
= SessionToken
{ sessionToken :: Text
, tokenExpiration :: POSIXTime
}
deriving (Show, Eq)
decodeSessionTokens :: Text -> [SessionToken]
decodeSessionTokens serializedText =
case decodePHPSessionValue (LBS.fromStrict $ encodeUtf8 serializedText) of
Nothing -> []
Just phpValue -> decodeTokenArray phpValue
where
decodeTokenArray :: PHPSessionValue -> [SessionToken]
decodeTokenArray = \case
PHPSessionValueArray sessionTokens ->
mapMaybe decodeToken sessionTokens
_ -> []
decodeToken :: (PHPSessionValue, PHPSessionValue) -> Maybe SessionToken
decodeToken = \case
(PHPSessionValueString token, expirationData) ->
let decodedExpiration = case expirationData of
PHPSessionValueInt posixExpiration ->
Just . fromInteger $ fromIntegral posixExpiration
PHPSessionValueArray tokenData -> decodeTokenData tokenData
_ -> Nothing
sessionToken = decodeUtf8 $ LBS.toStrict token
in (\tokenExpiration -> SessionToken { .. }) <$> decodedExpiration
_ -> Nothing
decodeTokenData :: [(PHPSessionValue, PHPSessionValue)] -> Maybe POSIXTime
decodeTokenData = \case
[] -> Nothing
(PHPSessionValueString "expiration", PHPSessionValueInt expiration) : _
-> Just $ fromInteger $ fromIntegral expiration
_ : rest -> decodeTokenData rest
validateSessionToken
:: POSIXTime
-> CookieToken
-> [SessionToken]
-> Bool
validateSessionToken currentTime (CookieToken cookieToken) sessionTokens =
let hashedCookieToken = hashText SHA256.hash $ HashMessage cookieToken
in isJust $ L.find ((== hashedCookieToken) . sessionToken) $ filter
(\tok -> tokenExpiration tok >= currentTime)
sessionTokens
newtype NonceTick
= NonceTick
{ tickCount :: Integer
}
deriving (Show, Eq)
wordpressNonceTick
:: NominalDiffTime
-> POSIXTime
-> NonceTick
wordpressNonceTick nonceLifetime currentTime =
let currentTick = toRational currentTime / (toRational nonceLifetime / 2)
in NonceTick $ ceiling currentTick
validateNonce
:: AuthScheme
-> Maybe CookieToken
-> NonceTick
-> Maybe WordpressUserId
-> Text
-> Text
-> Bool
validateNonce scheme maybeToken tick maybeUserId action nonce =
let
userId = maybe "" (T.pack . show . wordpressUserId) maybeUserId
token = maybe "" cookieToken maybeToken
thisCycleHash = hashAndTrim $ joinHashParts
[T.pack $ show $ tickCount tick, action, userId, token]
lastCycleHash = hashAndTrim $ joinHashParts
[T.pack $ show $ tickCount tick - 1, action, userId, token]
in
nonce /= "" && nonce `elem` [thisCycleHash, lastCycleHash]
where
hashAndTrim s =
let hashed = wordpressHash scheme s
in T.take 10 $ T.drop (T.length hashed - 12) hashed
data AuthScheme
= AuthScheme
{ schemeKey :: WordpressKey
, schemeSalt :: WordpressSalt
}
deriving (Show, Eq)
newtype WordpressKey
= WordpressKey { unKey :: Text }
deriving (Show, Eq)
newtype WordpressSalt
= WordpressSalt { unSalt :: Text }
deriving (Show, Eq)
wpConfigKey :: Text -> WordpressKey
wpConfigKey = WordpressKey
wpConfigSalt :: Text -> WordpressSalt
wpConfigSalt = WordpressSalt
newtype HashSecret = HashSecret Text
newtype HashMessage = HashMessage { hashMessage :: Text }
hmacText
:: (B.ByteString -> B.ByteString -> B.ByteString)
-> HashSecret
-> HashMessage
-> Text
hmacText hasher (HashSecret secret) =
decodeUtf8
. Base16.encode
. hasher (encodeUtf8 secret)
. encodeUtf8
. hashMessage
hashText :: (B.ByteString -> B.ByteString) -> HashMessage -> Text
hashText hasher =
decodeUtf8 . Base16.encode . hasher . encodeUtf8 . hashMessage
joinHashParts :: [Text] -> Text
joinHashParts = T.intercalate "|"