module Web.WebPush
(
generateVAPIDKeys
, readVAPIDKeys
, vapidPublicKeyBytes
, sendPushNotification
, VAPIDKeys
, VAPIDKeysMinDetails(..)
, PushNotificationDetails(..)
, PushNotificationMessage(..)
, PushNotificationError(..)
) where
import Web.WebPush.Internal
import Crypto.Random (MonadRandom(getRandomBytes))
import qualified Crypto.PubKey.ECC.Types as ECC
import qualified Crypto.PubKey.ECC.Generate as ECC
import qualified Crypto.PubKey.ECC.ECDSA as ECDSA
import qualified Crypto.PubKey.ECC.DH as ECDH
import Crypto.JWT (NumericDate(..))
import qualified Crypto.JWT as JWT
import qualified Data.Bits as Bits
import Data.Word (Word8)
import GHC.Int (Int64)
import qualified Data.List as L
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import qualified Data.Text.Encoding.Error as TE
import Data.Monoid ((<>))
import qualified Data.ByteString.Lazy as LB
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as C8
import qualified Data.Aeson as A
import qualified Data.ByteString.Base64.URL as B64.URL
import qualified Data.ByteString.Base64.URL.Lazy as B64.URL.Lazy
import Data.Time.Clock (getCurrentTime)
import Data.Time (addUTCTime)
import Network.HTTP.Client (Manager, httpLbs, parseRequest, HttpException(HttpExceptionRequest), HttpExceptionContent(StatusCodeException), RequestBody(..), requestBody, requestHeaders, method, host, secure, responseStatus)
import Network.HTTP.Types (hContentType, hAuthorization, hContentEncoding)
import Network.HTTP.Types.Status (Status(statusCode))
import qualified Crypto.JOSE.Error as JOSE.Error
import Crypto.Error (CryptoError)
import Control.Exception.Base (SomeException(..), fromException)
import Control.Monad.Catch.Pure (runCatchT)
import Control.Monad.IO.Class (MonadIO, liftIO)
import System.Random (randomRIO)
generateVAPIDKeys :: MonadRandom m => m VAPIDKeysMinDetails
generateVAPIDKeys = do
(pubKey, privKey) <- ECC.generate $ ECC.getCurveByName ECC.SEC_p256r1
let ECC.Point pubX pubY = ECDSA.public_q pubKey
return $ VAPIDKeysMinDetails { privateNumber = ECDSA.private_d privKey
, publicCoordX = pubX
, publicCoordY = pubY
}
readVAPIDKeys :: VAPIDKeysMinDetails -> VAPIDKeys
readVAPIDKeys VAPIDKeysMinDetails {..} =
let vapidPublicKeyPoint = ECC.Point publicCoordX publicCoordY
in ECDSA.KeyPair (ECC.getCurveByName ECC.SEC_p256r1) vapidPublicKeyPoint privateNumber
vapidPublicKeyBytes :: VAPIDKeys -> [Word8]
vapidPublicKeyBytes keys =
let ECC.Point vapidPublicKeyX vapidPublicKeyY = ECDSA.public_q $ ECDSA.toPublicKey keys
in 4 : ( (extract32Bytes vapidPublicKeyX) ++ (extract32Bytes vapidPublicKeyY) )
where
extract32Bytes :: Integer -> [Word8]
extract32Bytes number = snd $ L.foldl' (\(integer, bytes) _ -> (Bits.shiftR integer 8, (fromIntegral integer) : bytes))
(number, ([] :: [Word8]))
([1..32] :: [Int])
sendPushNotification :: MonadIO m
=> VAPIDKeys
-> Manager
-> PushNotificationDetails
-> m (Either PushNotificationError ())
sendPushNotification vapidKeys httpManager pushNotification = do
eitherInitReq <- runCatchT $ parseRequest $ T.unpack $ endpoint pushNotification
case eitherInitReq of
Left exc@(SomeException _) -> return $ Left $ EndpointParseFailed exc
Right initReq -> do
time <- liftIO $ getCurrentTime
eitherJwt <- webPushJWT vapidKeys $ VAPIDClaims { vapidAud = JWT.Audience [ JWT.fromString $ TE.decodeUtf8With TE.lenientDecode $
BS.append (if secure initReq then "https://" else "http://") (host initReq)
]
, vapidSub = JWT.fromString $ T.append "mailto:" $ senderEmail pushNotification
, vapidExp = NumericDate $ addUTCTime 3000 time
}
case eitherJwt of
Left err -> return $ Left $ JWTGenerationFailed err
Right jwt -> do
ecdhServerPrivateKey <- liftIO $ ECDH.generatePrivate $ ECC.getCurveByName ECC.SEC_p256r1
randSalt <- liftIO $ getRandomBytes 16
padLen <- liftIO $ randomRIO (0, 20)
let authSecretBytes = B64.URL.decodeLenient $ TE.encodeUtf8 $ auth pushNotification
subscriptionPublicKeyBytes = B64.URL.decodeLenient $ TE.encodeUtf8 $ p256dh pushNotification
plainMessage64Encoded = B64.URL.Lazy.encode $ A.encode $ A.toJSON $ message pushNotification
eitherEncryptionOutput = webPushEncrypt $ EncryptionInput { applicationServerPrivateKey = ecdhServerPrivateKey
, userAgentPublicKeyBytes = subscriptionPublicKeyBytes
, authenticationSecret = authSecretBytes
, salt = randSalt
, plainText = plainMessage64Encoded
, paddingLength = padLen
}
case eitherEncryptionOutput of
Left err -> return $ Left $ MessageEncryptionFailed err
Right encryptionOutput -> do
let ecdhServerPublicKeyBytes = LB.toStrict $ ecPublicKeyToBytes $
ECDH.calculatePublic (ECC.getCurveByName ECC.SEC_p256r1) $
ecdhServerPrivateKey
let postHeaders = let authorizationHeader = LB.toStrict $ "WebPush " <> jwt
cryptoKeyHeader = BS.concat [ "dh=", b64UrlNoPadding ecdhServerPublicKeyBytes
, ";"
, "p256ecdsa=", b64UrlNoPadding vapidPublicKeyBytestring
]
in [ ("TTL", C8.pack $ show (60*60*(expireInHours pushNotification)))
, (hContentType, "application/octet-stream")
, (hAuthorization, authorizationHeader)
, ("Crypto-Key", cryptoKeyHeader)
, (hContentEncoding, "aesgcm")
, ("Encryption", "salt=" <> (b64UrlNoPadding randSalt))
]
request = initReq { method = "POST"
, requestHeaders = postHeaders ++
(filter (\(x, _) -> L.notElem x $ map fst postHeaders)
(requestHeaders initReq)
)
, requestBody = RequestBodyBS $ encryptedMessage encryptionOutput
}
eitherResp <- runCatchT $ liftIO $ httpLbs request httpManager
case eitherResp of
Left err@(SomeException _) -> case fromException err of
Just (HttpExceptionRequest _ (StatusCodeException resp _))
|(statusCode (responseStatus resp) == 404) -> return $ Left RecepientEndpointNotFound
_ -> return $ Left $ PushRequestFailed err
Right _ -> return $ Right ()
where
vapidPublicKeyBytestring = LB.toStrict $ ecPublicKeyToBytes $
ECDSA.public_q $ ECDSA.toPublicKey vapidKeys
data PushNotificationDetails = PushNotificationDetails { endpoint :: Text
, p256dh :: Text
, auth :: Text
, senderEmail :: Text
, expireInHours :: Int64
, message :: PushNotificationMessage
}
data VAPIDKeysMinDetails = VAPIDKeysMinDetails { privateNumber :: Integer
, publicCoordX :: Integer
, publicCoordY :: Integer
}
data PushNotificationError = EndpointParseFailed SomeException
| JWTGenerationFailed JOSE.Error.Error
| MessageEncryptionFailed CryptoError
| RecepientEndpointNotFound
| PushRequestFailed SomeException