9
9
{-# HLINT ignore "Use newtype instead of data" #-}
10
10
{-# LANGUAGE OverloadedRecordDot #-}
11
11
{-# LANGUAGE TypeApplications #-}
12
+ {-# LANGUAGE ScopedTypeVariables #-}
12
13
13
14
module Simplex.Messaging.Notifications.Server.Push.WebPush where
14
15
15
16
import Network.HTTP.Client
17
+ import qualified Simplex.Messaging.Crypto as C
16
18
import Simplex.Messaging.Notifications.Protocol (DeviceToken (WPDeviceToken ), WPEndpoint (.. ), encodePNMessages , PNMessageData )
17
19
import Simplex.Messaging.Notifications.Server.Store.Types
18
20
import Simplex.Messaging.Notifications.Server.Push
@@ -25,36 +27,126 @@ import Control.Exception ( fromException, SomeException, try )
25
27
import qualified Network.HTTP.Types as N
26
28
import qualified Data.Aeson as J
27
29
import Data.Aeson ((.=) )
30
+ import qualified Data.Binary as Bin
31
+ import qualified Data.Bits as Bits
32
+ import qualified Data.ByteArray as BA
28
33
import qualified Data.ByteString.Lazy as BL
29
34
import Data.List.NonEmpty (NonEmpty )
30
35
import qualified Data.Text.Encoding as T
31
36
import qualified Data.Text as T
37
+ import Control.Monad.Trans.Except (throwE )
38
+ import Crypto.Hash.Algorithms (SHA256 )
39
+ import Crypto.Random (MonadRandom (getRandomBytes ))
40
+ import qualified Crypto.Cipher.Types as CT
41
+ import qualified Crypto.Error as CE
42
+ import qualified Crypto.MAC.HMAC as HMAC
43
+ import qualified Crypto.PubKey.ECC.DH as ECDH
44
+ import qualified Crypto.PubKey.ECC.Types as ECC
45
+ import GHC.Base (when )
32
46
33
47
wpPushProviderClient :: Manager -> PushProviderClient
34
48
wpPushProviderClient mg tkn pn = do
35
- e <- B. unpack <$> endpoint tkn
36
- r <- liftPPWPError $ parseUrlThrow e
49
+ e <- endpoint tkn
50
+ r <- liftPPWPError $ parseUrlThrow $ B. unpack e . endpoint
37
51
logDebug $ " Request to " <> tshow r. host
52
+ encBody <- body e
38
53
let requestHeaders = [
39
54
(" TTL" , " 2592000" ) -- 30 days
40
55
, (" Urgency" , " High" )
41
56
, (" Content-Encoding" , " aes128gcm" )
42
57
-- TODO: topic for pings and interval
43
58
]
44
- let req = r {
59
+ req = r {
45
60
method = " POST"
46
61
, requestHeaders
47
- , requestBody = RequestBodyLBS $ encodePN pn
62
+ , requestBody = RequestBodyBS encBody
48
63
, redirectCount = 0
49
64
}
50
65
_ <- liftPPWPError $ httpNoBody req mg
51
66
pure ()
52
67
where
53
- endpoint :: NtfTknRec -> ExceptT PushProviderError IO B. ByteString
68
+ endpoint :: NtfTknRec -> ExceptT PushProviderError IO WPEndpoint
54
69
endpoint NtfTknRec {token} = do
55
70
case token of
56
- WPDeviceToken WPEndpoint { endpoint = e } -> pure e
71
+ WPDeviceToken e -> pure e
57
72
_ -> fail " Wrong device token"
73
+ -- TODO: move to PPIndalidPusher ? WPEndpoint should be invalidated and removed if the key is invalid, but the validation key is never sent
74
+ body :: WPEndpoint -> ExceptT PushProviderError IO B. ByteString
75
+ body e = withExceptT PPCryptoError $ wpEncrypt e. auth e. p256dh (BL. toStrict $ encodePN pn)
76
+
77
+ -- | encrypt :: auth -> key -> clear -> cipher
78
+ -- | https://www.rfc-editor.org/rfc/rfc8291#section-3.4
79
+ wpEncrypt :: B. ByteString -> B. ByteString -> B. ByteString -> ExceptT C. CryptoError IO B. ByteString
80
+ wpEncrypt auth uaPubKS clearT = do
81
+ salt :: B. ByteString <- liftIO $ getRandomBytes 16
82
+ asPrivK <- liftIO $ ECDH. generatePrivate $ ECC. getCurveByName ECC. SEC_p256r1
83
+ uaPubK <- point uaPubKS
84
+ let asPubK = BL. toStrict . uncompressEncode . ECDH. calculatePublic (ECC. getCurveByName ECC. SEC_p256r1 ) $ asPrivK
85
+ ecdhSecret = ECDH. getShared (ECC. getCurveByName ECC. SEC_p256r1 ) asPrivK uaPubK
86
+ prkKey = hmac auth ecdhSecret
87
+ keyInfo = " WebPush: info\0" <> uaPubKS <> asPubK
88
+ ikm = hmac prkKey (keyInfo <> " \x01 " )
89
+ prk = hmac salt ikm
90
+ cekInfo = " Content-Encoding: aes128gcm\0" :: B. ByteString
91
+ cek = takeHM 16 $ hmac prk (cekInfo <> " \x01 " )
92
+ nonceInfo = " Content-Encoding: nonce\0" :: B. ByteString
93
+ nonce = takeHM 12 $ hmac prk (nonceInfo <> " \x01 " )
94
+ rs = BL. toStrict $ Bin. encode (4096 :: Bin. Word32 ) -- with RFC8291, it's ok to always use 4096 because there is only one single record and the final record can be smaller than rs (RFC8188)
95
+ idlen = BL. toStrict $ Bin. encode (65 :: Bin. Word8 ) -- with RFC8291, keyid is the pubkey, so always 65 bytes
96
+ header = salt <> rs <> idlen <> asPubK
97
+ iv <- ivFrom nonce
98
+ -- The last record uses a padding delimiter octet set to the value 0x02
99
+ (C. AuthTag (CT. AuthTag tag), cipherT) <- C. encryptAES128NoPad (C. Key cek) iv $ clearT <> " \x02 "
100
+ pure $ header <> cipherT <> BA. convert tag
101
+ where
102
+ point :: B. ByteString -> ExceptT C. CryptoError IO ECC. Point
103
+ point s = withExceptT C. CryptoInvalidECCKey $ uncompressDecode $ BL. fromStrict s
104
+ hmac k v = HMAC. hmac k v :: HMAC. HMAC SHA256
105
+ takeHM :: Int -> HMAC. HMAC SHA256 -> B. ByteString
106
+ takeHM n v = BL. toStrict $ BL. pack $ take n $ BA. unpack v
107
+ ivFrom :: B. ByteString -> ExceptT C. CryptoError IO C. GCMIV
108
+ ivFrom s = case C. gcmIV s of
109
+ Left e -> throwE e
110
+ Right iv -> pure iv
111
+
112
+ -- | Elliptic-Curve-Point-to-Octet-String Conversion without compression
113
+ -- | as required by RFC8291
114
+ -- | https://www.secg.org/sec1-v2.pdf#subsubsection.2.3.3
115
+ uncompressEncode :: ECC. Point -> BL. ByteString
116
+ uncompressEncode (ECC. Point x y) = " \x04 " <>
117
+ encodeBigInt x <>
118
+ encodeBigInt y
119
+ uncompressEncode ECC. PointO = " \0"
120
+
121
+ uncompressDecode :: BL. ByteString -> ExceptT CE. CryptoError IO ECC. Point
122
+ uncompressDecode " \0" = pure ECC. PointO
123
+ uncompressDecode s = do
124
+ when (BL. take 1 s /= prefix) $ throwError CE. CryptoError_PointFormatUnsupported
125
+ when (BL. length s /= 65 ) $ throwError CE. CryptoError_KeySizeInvalid
126
+ let s' = BL. drop 1 s
127
+ x <- decodeBigInt $ BL. take 32 s'
128
+ y <- decodeBigInt $ BL. drop 32 s'
129
+ pure $ ECC. Point x y
130
+ where
131
+ prefix = " \x04 " :: BL. ByteString
132
+
133
+ encodeBigInt :: Integer -> BL. ByteString
134
+ encodeBigInt i = do
135
+ let s1 = Bits. shiftR i 64
136
+ s2 = Bits. shiftR s1 64
137
+ s3 = Bits. shiftR s2 64
138
+ Bin. encode ( w64 s3, w64 s2, w64 s1, w64 i )
139
+ where
140
+ w64 :: Integer -> Bin. Word64
141
+ w64 = fromIntegral
142
+
143
+ decodeBigInt :: BL. ByteString -> ExceptT CE. CryptoError IO Integer
144
+ decodeBigInt s = do
145
+ when (BL. length s /= 32 ) $ throwError CE. CryptoError_PointSizeInvalid
146
+ let (w3, w2, w1, w0) = Bin. decode s :: (Bin. Word64 , Bin. Word64 , Bin. Word64 , Bin. Word64 )
147
+ pure $ shift 3 w3 + shift 2 w2 + shift 1 w1 + shift 0 w0
148
+ where
149
+ shift i w = Bits. shiftL (fromIntegral w) (64 * i)
58
150
59
151
encodePN :: PushNotification -> BL. ByteString
60
152
encodePN pn = J. encode $ case pn of
0 commit comments