mirror of
https://github.com/simplex-chat/simplex-chat.git
synced 2025-03-14 09:45:42 +00:00
core: use 12 bytes IV for WebRTC frame encryption with AES-GCM (#1951)
* core: use 12 bytes IV for WebRTC frame encryption with AES-GCM * refactor
This commit is contained in:
parent
6eddb5f30f
commit
50b90c4814
5 changed files with 36 additions and 37 deletions
|
@ -7,7 +7,7 @@ constraints: zip +disable-bzip2 +disable-zstd
|
|||
source-repository-package
|
||||
type: git
|
||||
location: https://github.com/simplex-chat/simplexmq.git
|
||||
tag: a8121fc8add20f4f63ba6ba598e4adbe25c52605
|
||||
tag: e4aad7583f425765c605cd8042e3136e048bdbec
|
||||
|
||||
source-repository-package
|
||||
type: git
|
||||
|
|
|
@ -1,5 +1,5 @@
|
|||
{
|
||||
"https://github.com/simplex-chat/simplexmq.git"."a8121fc8add20f4f63ba6ba598e4adbe25c52605" = "08rjzw759iqkfdmdicnqj8aam7r9irnrr6129hz8s3mxz9g7d2jp";
|
||||
"https://github.com/simplex-chat/simplexmq.git"."e4aad7583f425765c605cd8042e3136e048bdbec" = "043b0k4ivnd4h5ja5qddq8zqr91g2198sii78njwcj1nc6nnhrdd";
|
||||
"https://github.com/simplex-chat/hs-socks.git"."a30cc7a79a08d8108316094f8f2f82a0c5e1ac51" = "0yasvnr7g91k76mjkamvzab2kvlb1g5pspjyjn2fr6v83swjhj38";
|
||||
"https://github.com/simplex-chat/direct-sqlcipher.git"."34309410eb2069b029b8fc1872deb1e0db123294" = "0kwkmhyfsn2lixdlgl15smgr1h5gjk7fky6abzh8rng2h5ymnffd";
|
||||
"https://github.com/simplex-chat/sqlcipher-simple.git"."5e154a2aeccc33ead6c243ec07195ab673137221" = "1d1gc5wax4vqg0801ajsmx1sbwvd9y7p7b8mmskvqsmpbwgbh0m0";
|
||||
|
|
|
@ -1,10 +1,15 @@
|
|||
{-# LANGUAGE FlexibleContexts #-}
|
||||
|
||||
module Simplex.Chat.Mobile.WebRTC where
|
||||
module Simplex.Chat.Mobile.WebRTC (
|
||||
cChatEncryptMedia,
|
||||
cChatDecryptMedia,
|
||||
chatEncryptMedia,
|
||||
chatDecryptMedia,
|
||||
reservedSize,
|
||||
) where
|
||||
|
||||
import Control.Monad.Except
|
||||
import qualified Crypto.Cipher.Types as AES
|
||||
import Crypto.Random (getRandomBytes)
|
||||
import Data.Bifunctor (bimap)
|
||||
import qualified Data.ByteArray as BA
|
||||
import qualified Data.ByteString as B
|
||||
|
@ -41,44 +46,37 @@ cTransformMedia f cKey cFrame cFrameLen = do
|
|||
|
||||
chatEncryptMedia :: ByteString -> ByteString -> ExceptT String IO ByteString
|
||||
chatEncryptMedia keyStr frame = do
|
||||
checkFrameLen frame
|
||||
len <- checkFrameLen frame
|
||||
key <- decodeKey keyStr
|
||||
iv <- liftIO $ getRandomBytes ivSize
|
||||
let (frame', _) = B.splitAt (B.length frame - reservedSize) frame
|
||||
(tag, frame'') <- withExceptT show $ C.encryptAESNoPad key (C.IV $ iv <> ivPad) frame'
|
||||
let authTag = BA.convert $ C.unAuthTag tag
|
||||
pure $ frame'' <> authTag <> iv
|
||||
iv <- liftIO C.randomGCMIV
|
||||
(tag, frame') <- withExceptT show $ C.encryptAESNoPad key iv $ B.take len frame
|
||||
pure $ frame' <> BA.convert (C.unAuthTag tag) <> C.unGCMIV iv
|
||||
|
||||
chatDecryptMedia :: ByteString -> ByteString -> ExceptT String IO ByteString
|
||||
chatDecryptMedia keyStr frame = do
|
||||
checkFrameLen frame
|
||||
len <- checkFrameLen frame
|
||||
key <- decodeKey keyStr
|
||||
let (rest, iv) = B.splitAt (B.length frame - ivSize) frame
|
||||
(frame', tag) = B.splitAt (B.length rest - C.authTagSize) rest
|
||||
let (frame', rest) = B.splitAt len frame
|
||||
(tag, iv) = B.splitAt C.authTagSize rest
|
||||
authTag = C.AuthTag $ AES.AuthTag $ BA.convert tag
|
||||
frame'' <- withExceptT show $ C.decryptAESNoPad key (C.IV $ iv <> ivPad) frame' authTag
|
||||
pure $ frame'' <> B.replicate reservedSize 0
|
||||
withExceptT show $ do
|
||||
iv' <- liftEither $ C.gcmIV iv
|
||||
frame'' <- C.decryptAESNoPad key iv' frame' authTag
|
||||
pure $ frame'' <> framePad
|
||||
|
||||
checkFrameLen :: ByteString -> ExceptT String IO ()
|
||||
checkFrameLen frame =
|
||||
when (B.length frame < reservedSize) $ throwError "frame has no [reserved space] IV and/or auth tag"
|
||||
checkFrameLen :: ByteString -> ExceptT String IO Int
|
||||
checkFrameLen frame = do
|
||||
let len = B.length frame - reservedSize
|
||||
when (len < 0) $ throwError "frame has no [reserved space for] IV and/or auth tag"
|
||||
pure len
|
||||
{-# INLINE checkFrameLen #-}
|
||||
|
||||
decodeKey :: ByteString -> ExceptT String IO C.Key
|
||||
decodeKey = liftEither . bimap ("invalid key: " <>) C.Key . U.decode
|
||||
{-# INLINE decodeKey #-}
|
||||
|
||||
authTagSize :: Int
|
||||
authTagSize = C.authTagSize
|
||||
{-# INLINE authTagSize #-}
|
||||
|
||||
ivSize :: Int
|
||||
ivSize = 12
|
||||
{-# INLINE ivSize #-}
|
||||
|
||||
ivPad :: ByteString
|
||||
ivPad = B.replicate 4 0
|
||||
|
||||
reservedSize :: Int
|
||||
reservedSize = authTagSize + ivSize
|
||||
{-# INLINE reservedSize #-}
|
||||
reservedSize = C.authTagSize + C.gcmIVSize
|
||||
|
||||
framePad :: ByteString
|
||||
framePad = B.replicate reservedSize 0
|
||||
|
|
|
@ -49,7 +49,7 @@ extra-deps:
|
|||
# - simplexmq-1.0.0@sha256:34b2004728ae396e3ae449cd090ba7410781e2b3cefc59259915f4ca5daa9ea8,8561
|
||||
# - ../simplexmq
|
||||
- github: simplex-chat/simplexmq
|
||||
commit: a8121fc8add20f4f63ba6ba598e4adbe25c52605
|
||||
commit: e4aad7583f425765c605cd8042e3136e048bdbec
|
||||
# - ../direct-sqlcipher
|
||||
- github: simplex-chat/direct-sqlcipher
|
||||
commit: 34309410eb2069b029b8fc1872deb1e0db123294
|
||||
|
|
|
@ -5,6 +5,7 @@ import Crypto.Random (getRandomBytes)
|
|||
import qualified Data.ByteString.Base64.URL as U
|
||||
import qualified Data.ByteString.Char8 as B
|
||||
import Simplex.Chat.Mobile.WebRTC
|
||||
import qualified Simplex.Messaging.Crypto as C
|
||||
import Test.Hspec
|
||||
|
||||
webRTCTests :: Spec
|
||||
|
@ -19,8 +20,8 @@ webRTCTests = describe "WebRTC crypto" $ do
|
|||
it "should fail on invalid frame size" $ do
|
||||
key <- U.encode <$> getRandomBytes 32
|
||||
frame <- getRandomBytes 10
|
||||
runExceptT (chatEncryptMedia key frame) `shouldReturn` Left "frame has no [reserved space] IV and/or auth tag"
|
||||
runExceptT (chatDecryptMedia key frame) `shouldReturn` Left "frame has no [reserved space] IV and/or auth tag"
|
||||
runExceptT (chatEncryptMedia key frame) `shouldReturn` Left "frame has no [reserved space for] IV and/or auth tag"
|
||||
runExceptT (chatDecryptMedia key frame) `shouldReturn` Left "frame has no [reserved space for] IV and/or auth tag"
|
||||
it "should fail on invalid key" $ do
|
||||
let key = B.replicate 32 '#'
|
||||
frame <- (<> B.replicate reservedSize '\NUL') <$> getRandomBytes 100
|
||||
|
@ -32,7 +33,7 @@ webRTCTests = describe "WebRTC crypto" $ do
|
|||
Right frame' <- runExceptT $ chatEncryptMedia key $ frame <> B.replicate reservedSize '\NUL'
|
||||
Right frame'' <- runExceptT $ chatDecryptMedia key frame'
|
||||
frame'' `shouldBe` frame <> B.replicate reservedSize '\NUL'
|
||||
let (rest, iv) = B.splitAt (B.length frame' - ivSize) frame
|
||||
(encFrame, _tag) = B.splitAt (B.length rest - authTagSize) rest
|
||||
badFrame = encFrame <> B.replicate authTagSize '\NUL' <> iv
|
||||
let (encFrame, rest) = B.splitAt (B.length frame' - reservedSize) frame
|
||||
(_tag, iv) = B.splitAt C.authTagSize rest
|
||||
badFrame = encFrame <> B.replicate C.authTagSize '\NUL' <> iv
|
||||
runExceptT (chatDecryptMedia key badFrame) `shouldReturn` Left "AESDecryptError"
|
||||
|
|
Loading…
Add table
Reference in a new issue