Skip to content

Commit 95ea161

Browse files
committed
Encrypt wp notifications
1 parent 763f039 commit 95ea161

File tree

3 files changed

+120
-7
lines changed

3 files changed

+120
-7
lines changed

simplexmq.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -292,6 +292,7 @@ library
292292
, attoparsec ==0.14.*
293293
, base >=4.14 && <5
294294
, base64-bytestring >=1.0 && <1.3
295+
, binary ==0.8.*
295296
, composition ==1.0.*
296297
, constraints >=0.12 && <0.14
297298
, containers ==0.6.*

src/Simplex/Messaging/Crypto.hs

Lines changed: 21 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -127,6 +127,7 @@ module Simplex.Messaging.Crypto
127127
encryptAEAD,
128128
decryptAEAD,
129129
encryptAESNoPad,
130+
encryptAES128NoPad,
130131
decryptAESNoPad,
131132
authTagSize,
132133
randomAesKey,
@@ -209,7 +210,7 @@ import Control.Exception (Exception)
209210
import Control.Monad
210211
import Control.Monad.Except
211212
import Control.Monad.Trans.Except
212-
import Crypto.Cipher.AES (AES256)
213+
import Crypto.Cipher.AES (AES256, AES128)
213214
import qualified Crypto.Cipher.Types as AES
214215
import qualified Crypto.Cipher.XSalsa as XSalsa
215216
import qualified Crypto.Error as CE
@@ -895,6 +896,8 @@ data CryptoError
895896
CERatchetEarlierMessage Word32
896897
| -- | duplicate message number
897898
CERatchetDuplicateMessage
899+
| -- | unable to decode ecc key
900+
CryptoInvalidECCKey CE.CryptoError
898901
deriving (Eq, Show, Exception)
899902

900903
aesKeySize :: Int
@@ -1021,11 +1024,22 @@ encryptAESNoPad :: Key -> GCMIV -> ByteString -> ExceptT CryptoError IO (AuthTag
10211024
encryptAESNoPad key iv = encryptAEADNoPad key iv ""
10221025
{-# INLINE encryptAESNoPad #-}
10231026

1027+
-- Used to encrypt WebPush notifications
1028+
-- This function requires 12 bytes IV, it does not transform IV.
1029+
encryptAES128NoPad :: Key -> GCMIV -> ByteString -> ExceptT CryptoError IO (AuthTag, ByteString)
1030+
encryptAES128NoPad key iv = encryptAEAD128NoPad key iv ""
1031+
{-# INLINE encryptAES128NoPad #-}
1032+
10241033
encryptAEADNoPad :: Key -> GCMIV -> ByteString -> ByteString -> ExceptT CryptoError IO (AuthTag, ByteString)
10251034
encryptAEADNoPad aesKey ivBytes ad msg = do
10261035
aead <- initAEADGCM aesKey ivBytes
10271036
pure . first AuthTag $ AES.aeadSimpleEncrypt aead ad msg authTagSize
10281037

1038+
encryptAEAD128NoPad :: Key -> GCMIV -> ByteString -> ByteString -> ExceptT CryptoError IO (AuthTag, ByteString)
1039+
encryptAEAD128NoPad aesKey ivBytes ad msg = do
1040+
aead <- initAEAD128GCM aesKey ivBytes
1041+
pure . first AuthTag $ AES.aeadSimpleEncrypt aead ad msg authTagSize
1042+
10291043
-- | AEAD-GCM decryption with associated data.
10301044
--
10311045
-- Used as part of double ratchet encryption.
@@ -1125,6 +1139,12 @@ initAEADGCM (Key aesKey) (GCMIV ivBytes) = cryptoFailable $ do
11251139
cipher <- AES.cipherInit aesKey
11261140
AES.aeadInit AES.AEAD_GCM cipher ivBytes
11271141

1142+
-- this function requires 12 bytes IV, it does not transforms IV.
1143+
initAEAD128GCM :: Key -> GCMIV -> ExceptT CryptoError IO (AES.AEAD AES128)
1144+
initAEAD128GCM (Key aesKey) (GCMIV ivBytes) = cryptoFailable $ do
1145+
cipher <- AES.cipherInit aesKey
1146+
AES.aeadInit AES.AEAD_GCM cipher ivBytes
1147+
11281148
-- | Random AES256 key.
11291149
randomAesKey :: TVar ChaChaDRG -> STM Key
11301150
randomAesKey = fmap Key . randomBytes aesKeySize

src/Simplex/Messaging/Notifications/Server/Push/WebPush.hs

Lines changed: 98 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -9,10 +9,12 @@
99
{-# HLINT ignore "Use newtype instead of data" #-}
1010
{-# LANGUAGE OverloadedRecordDot #-}
1111
{-# LANGUAGE TypeApplications #-}
12+
{-# LANGUAGE ScopedTypeVariables #-}
1213

1314
module Simplex.Messaging.Notifications.Server.Push.WebPush where
1415

1516
import Network.HTTP.Client
17+
import qualified Simplex.Messaging.Crypto as C
1618
import Simplex.Messaging.Notifications.Protocol (DeviceToken (WPDeviceToken), WPEndpoint (..), encodePNMessages, PNMessageData)
1719
import Simplex.Messaging.Notifications.Server.Store.Types
1820
import Simplex.Messaging.Notifications.Server.Push
@@ -25,36 +27,126 @@ import Control.Exception ( fromException, SomeException, try )
2527
import qualified Network.HTTP.Types as N
2628
import qualified Data.Aeson as J
2729
import Data.Aeson ((.=))
30+
import qualified Data.Binary as Bin
31+
import qualified Data.Bits as Bits
32+
import qualified Data.ByteArray as BA
2833
import qualified Data.ByteString.Lazy as BL
2934
import Data.List.NonEmpty (NonEmpty)
3035
import qualified Data.Text.Encoding as T
3136
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)
3246

3347
wpPushProviderClient :: Manager -> PushProviderClient
3448
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
3751
logDebug $ "Request to " <> tshow r.host
52+
encBody <- body e
3853
let requestHeaders = [
3954
("TTL", "2592000") -- 30 days
4055
, ("Urgency", "High")
4156
, ("Content-Encoding", "aes128gcm")
4257
-- TODO: topic for pings and interval
4358
]
44-
let req = r {
59+
req = r {
4560
method = "POST"
4661
, requestHeaders
47-
, requestBody = RequestBodyLBS $ encodePN pn
62+
, requestBody = RequestBodyBS encBody
4863
, redirectCount = 0
4964
}
5065
_ <- liftPPWPError $ httpNoBody req mg
5166
pure ()
5267
where
53-
endpoint :: NtfTknRec -> ExceptT PushProviderError IO B.ByteString
68+
endpoint :: NtfTknRec -> ExceptT PushProviderError IO WPEndpoint
5469
endpoint NtfTknRec {token} = do
5570
case token of
56-
WPDeviceToken WPEndpoint{ endpoint = e } -> pure e
71+
WPDeviceToken e -> pure e
5772
_ -> 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)
58150

59151
encodePN :: PushNotification -> BL.ByteString
60152
encodePN pn = J.encode $ case pn of

0 commit comments

Comments
 (0)