Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
63 changes: 63 additions & 0 deletions src/Simplex/Messaging/Crypto.hs
Original file line number Diff line number Diff line change
Expand Up @@ -87,13 +87,17 @@ module Simplex.Messaging.Crypto
signatureKeyPair,
publicToX509,
encodeASNObj,
readECPrivateKey,

-- * key encoding/decoding
encodePubKey,
decodePubKey,
encodePrivKey,
decodePrivKey,
pubKeyBytes,
uncompressEncodePoint,
uncompressDecodePoint,
uncompressDecodePrivateNumber,

-- * sign/verify
Signature (..),
Expand Down Expand Up @@ -252,6 +256,12 @@ import Simplex.Messaging.Encoding
import Simplex.Messaging.Encoding.String
import Simplex.Messaging.Parsers (parseAll, parseString)
import Simplex.Messaging.Util ((<$?>))
import qualified Crypto.PubKey.ECC.ECDSA as ECDSA
import qualified Crypto.Store.PKCS8 as PK
import qualified Crypto.PubKey.ECC.Types as ECC
import qualified Data.ByteString.Lazy as BL
import qualified Data.Binary as Bin
import qualified Data.Bits as Bits

-- | Cryptographic algorithms.
data Algorithm = Ed25519 | Ed448 | X25519 | X448
Expand Down Expand Up @@ -1542,3 +1552,56 @@ keyError :: (a, [ASN1]) -> Either String b
keyError = \case
(_, []) -> Left "unknown key algorithm"
_ -> Left "more than one key"

readECPrivateKey :: FilePath -> IO ECDSA.PrivateKey
readECPrivateKey f = do
-- this pattern match is specific to APNS key type, it may need to be extended for other push providers
[PK.Unprotected (X.PrivKeyEC X.PrivKeyEC_Named {privkeyEC_name, privkeyEC_priv})] <- PK.readKeyFile f
pure ECDSA.PrivateKey {private_curve = ECC.getCurveByName privkeyEC_name, private_d = privkeyEC_priv}

-- | Elliptic-Curve-Point-to-Octet-String Conversion without compression
-- | as required by RFC8291
-- | https://www.secg.org/sec1-v2.pdf#subsubsection.2.3.3
uncompressEncodePoint :: ECC.Point -> BL.ByteString
uncompressEncodePoint (ECC.Point x y) = "\x04" <> encodeBigInt x <> encodeBigInt y
uncompressEncodePoint ECC.PointO = "\0"

uncompressDecodePoint :: BL.ByteString -> Either CE.CryptoError ECC.Point
uncompressDecodePoint "\0" = pure ECC.PointO
uncompressDecodePoint s
| BL.take 1 s /= prefix = Left CE.CryptoError_PointFormatUnsupported
| BL.length s /= 65 = Left CE.CryptoError_KeySizeInvalid
| otherwise = do
let s' = BL.drop 1 s
x <- decodeBigInt $ BL.take 32 s'
y <- decodeBigInt $ BL.drop 32 s'
pure $ ECC.Point x y
where
prefix = "\x04" :: BL.ByteString

-- Used to test encryption against the RFC8291 Example - which gives the AS private key
uncompressDecodePrivateNumber :: BL.ByteString -> Either CE.CryptoError ECC.PrivateNumber
uncompressDecodePrivateNumber s
| BL.length s /= 32 = Left CE.CryptoError_KeySizeInvalid
| otherwise = do
decodeBigInt s

encodeBigInt :: Integer -> BL.ByteString
encodeBigInt i = do
let s1 = Bits.shiftR i 64
s2 = Bits.shiftR s1 64
s3 = Bits.shiftR s2 64
Bin.encode (w64 s3, w64 s2, w64 s1, w64 i)
where
w64 :: Integer -> Bin.Word64
w64 = fromIntegral

decodeBigInt :: BL.ByteString -> Either CE.CryptoError Integer
decodeBigInt s
| BL.length s /= 32 = Left CE.CryptoError_PointSizeInvalid
| otherwise = do
let (w3, w2, w1, w0) = Bin.decode s :: (Bin.Word64, Bin.Word64, Bin.Word64, Bin.Word64 )
pure $ shift 3 w3 + shift 2 w2 + shift 1 w1 + shift 0 w0
where
shift i w = Bits.shiftL (fromIntegral w) (64 * i)

53 changes: 5 additions & 48 deletions src/Simplex/Messaging/Notifications/Protocol.hs
Original file line number Diff line number Diff line change
Expand Up @@ -394,6 +394,9 @@ newtype WPSrvLoc = WPSrvLoc SrvLoc
newtype WPProvider = WPP WPSrvLoc
deriving (Eq, Ord, Show)

wpAud :: WPProvider -> B.ByteString
wpAud (WPP (WPSrvLoc (SrvLoc aud _))) = B.pack aud

instance Encoding PushProvider where
smpEncode = \case
PPAPNS p -> smpEncode p
Expand Down Expand Up @@ -484,57 +487,11 @@ data WPKey = WPKey
}
deriving (Eq, Ord, Show)

-- | Elliptic-Curve-Point-to-Octet-String Conversion without compression
-- | as required by RFC8291
-- | https://www.secg.org/sec1-v2.pdf#subsubsection.2.3.3
uncompressEncodePoint :: ECC.Point -> BL.ByteString
uncompressEncodePoint (ECC.Point x y) = "\x04" <> encodeBigInt x <> encodeBigInt y
uncompressEncodePoint ECC.PointO = "\0"

uncompressDecodePoint :: BL.ByteString -> Either CE.CryptoError ECC.Point
uncompressDecodePoint "\0" = pure ECC.PointO
uncompressDecodePoint s
| BL.take 1 s /= prefix = Left CE.CryptoError_PointFormatUnsupported
| BL.length s /= 65 = Left CE.CryptoError_KeySizeInvalid
| otherwise = do
let s' = BL.drop 1 s
x <- decodeBigInt $ BL.take 32 s'
y <- decodeBigInt $ BL.drop 32 s'
pure $ ECC.Point x y
where
prefix = "\x04" :: BL.ByteString

-- Used to test encryption against the RFC8291 Example - which gives the AS private key
uncompressDecodePrivateNumber :: BL.ByteString -> Either CE.CryptoError ECC.PrivateNumber
uncompressDecodePrivateNumber s
| BL.length s /= 32 = Left CE.CryptoError_KeySizeInvalid
| otherwise = do
decodeBigInt s

uncompressEncode :: WPP256dh -> BL.ByteString
uncompressEncode (WPP256dh p) = uncompressEncodePoint p
uncompressEncode (WPP256dh p) = C.uncompressEncodePoint p

uncompressDecode :: BL.ByteString -> Either CE.CryptoError WPP256dh
uncompressDecode bs = WPP256dh <$> uncompressDecodePoint bs

encodeBigInt :: Integer -> BL.ByteString
encodeBigInt i = do
let s1 = Bits.shiftR i 64
s2 = Bits.shiftR s1 64
s3 = Bits.shiftR s2 64
Bin.encode (w64 s3, w64 s2, w64 s1, w64 i)
where
w64 :: Integer -> Bin.Word64
w64 = fromIntegral

decodeBigInt :: BL.ByteString -> Either CE.CryptoError Integer
decodeBigInt s
| BL.length s /= 32 = Left CE.CryptoError_PointSizeInvalid
| otherwise = do
let (w3, w2, w1, w0) = Bin.decode s :: (Bin.Word64, Bin.Word64, Bin.Word64, Bin.Word64 )
pure $ shift 3 w3 + shift 2 w2 + shift 1 w1 + shift 0 w0
where
shift i w = Bits.shiftL (fromIntegral w) (64 * i)
uncompressDecode bs = WPP256dh <$> C.uncompressDecodePoint bs

data WPTokenParams = WPTokenParams
{ wpPath :: ByteString,
Expand Down
23 changes: 14 additions & 9 deletions src/Simplex/Messaging/Notifications/Server/Env.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,9 +46,10 @@ import Simplex.Messaging.Transport.Server (AddHTTP, ServerCredentials, Transport
import System.Exit (exitFailure)
import System.Mem.Weak (Weak)
import UnliftIO.STM
import Simplex.Messaging.Notifications.Server.Push.WebPush (wpPushProviderClient)
import Simplex.Messaging.Notifications.Server.Push.WebPush (wpPushProviderClient, WebPushConfig)
import Network.HTTP.Client (newManager, ManagerSettings (..), Request (..), Manager)
import Network.HTTP.Client.TLS (tlsManagerSettings)
import Data.IORef (newIORef)

data NtfServerConfig = NtfServerConfig
{ transports :: [(ServiceName, ASrvTransport, AddHTTP)],
Expand All @@ -61,6 +62,7 @@ data NtfServerConfig = NtfServerConfig
pushQSize :: Natural,
smpAgentCfg :: SMPClientAgentConfig,
apnsConfig :: APNSPushClientConfig,
wpConfig :: WebPushConfig,
subsBatchSize :: Int,
inactiveClientExpiration :: Maybe ExpirationConfig,
dbStoreConfig :: PostgresStoreCfg,
Expand Down Expand Up @@ -100,7 +102,7 @@ data NtfEnv = NtfEnv
}

newNtfServerEnv :: NtfServerConfig -> IO NtfEnv
newNtfServerEnv config@NtfServerConfig {pushQSize, smpAgentCfg, apnsConfig, dbStoreConfig, ntfCredentials, useServiceCreds, startOptions} = do
newNtfServerEnv config@NtfServerConfig {pushQSize, smpAgentCfg, apnsConfig, wpConfig, dbStoreConfig, ntfCredentials, useServiceCreds, startOptions} = do
when (compactLog startOptions) $ compactDbStoreLog $ dbStoreLogPath dbStoreConfig
random <- C.newRandom
store <- newNtfDbStore dbStoreConfig
Expand All @@ -116,7 +118,7 @@ newNtfServerEnv config@NtfServerConfig {pushQSize, smpAgentCfg, apnsConfig, dbSt
pure smpAgentCfg {smpCfg = (smpCfg smpAgentCfg) {serviceCredentials = Just service}}
else pure smpAgentCfg
subscriber <- newNtfSubscriber smpAgentCfg' random
pushServer <- newNtfPushServer pushQSize apnsConfig
pushServer <- newNtfPushServer pushQSize apnsConfig wpConfig
serverStats <- newNtfServerStats =<< getCurrentTime
pure NtfEnv {config, subscriber, pushServer, store, random, tlsServerCreds, serverIdentity = C.KeyHash fp, serverStats}
where
Expand Down Expand Up @@ -153,14 +155,15 @@ data SMPSubscriber = SMPSubscriber
data NtfPushServer = NtfPushServer
{ pushQ :: TBQueue (Maybe T.Text, NtfTknRec, PushNotification), -- Maybe Text is a hostname of "own" server
pushClients :: TMap PushProvider PushProviderClient,
apnsConfig :: APNSPushClientConfig
apnsConfig :: APNSPushClientConfig,
wpConfig :: WebPushConfig
}

newNtfPushServer :: Natural -> APNSPushClientConfig -> IO NtfPushServer
newNtfPushServer qSize apnsConfig = do
newNtfPushServer :: Natural -> APNSPushClientConfig -> WebPushConfig -> IO NtfPushServer
newNtfPushServer qSize apnsConfig wpConfig = do
pushQ <- newTBQueueIO qSize
pushClients <- TM.emptyIO
pure NtfPushServer {pushQ, pushClients, apnsConfig}
pure NtfPushServer {pushQ, pushClients, apnsConfig, wpConfig}

newPushClient :: NtfPushServer -> PushProvider -> IO PushProviderClient
newPushClient s pp = do
Expand All @@ -177,10 +180,12 @@ newAPNSPushClient NtfPushServer {apnsConfig, pushClients} pp = do
Just host -> apnsPushProviderClient <$> createAPNSPushClient host apnsConfig

newWPPushClient :: NtfPushServer -> WPProvider -> IO PushProviderClient
newWPPushClient NtfPushServer {pushClients} pp = do
newWPPushClient NtfPushServer {wpConfig, pushClients} pp = do
logDebug "New WP Client requested"
-- We use one http manager per push server (which may be used by different clients)
wpPushProviderClient <$> wpHTTPManager
manager <- wpHTTPManager
cache <- newIORef Nothing
pure $ wpPushProviderClient wpConfig cache manager

wpHTTPManager :: IO Manager
wpHTTPManager = newManager tlsManagerSettings {
Expand Down
28 changes: 25 additions & 3 deletions src/Simplex/Messaging/Notifications/Server/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@
module Simplex.Messaging.Notifications.Server.Main where

import Control.Logger.Simple (setLogLevel)
import Control.Monad ((<$!>))
import Control.Monad ( (<$!>), unless, void )
import qualified Data.ByteString.Char8 as B
import Data.Functor (($>))
import Data.Ini (lookupValue, readIniFile)
Expand Down Expand Up @@ -56,6 +56,8 @@ import System.Exit (exitFailure)
import System.FilePath (combine)
import System.IO (BufferMode (..), hSetBuffering, stderr, stdout)
import Text.Read (readMaybe)
import System.Process (readCreateProcess, shell)
import Simplex.Messaging.Notifications.Server.Push.WebPush (WebPushConfig(..), VapidKey, mkVapid)

ntfServerCLI :: FilePath -> FilePath -> IO ()
ntfServerCLI cfgPath logPath =
Expand Down Expand Up @@ -146,6 +148,7 @@ ntfServerCLI cfgPath logPath =
clearDirIfExists logPath
createDirectoryIfMissing True cfgPath
createDirectoryIfMissing True logPath
_ <- genVapidKey vapidKeyPath
let x509cfg = defaultX509Config {commonName = fromMaybe ip fqdn, signAlgorithm}
fp <- createServerX509 cfgPath x509cfg
let host = fromMaybe (if ip == "127.0.0.1" then "<hostnames>" else ip) fqdn
Expand Down Expand Up @@ -212,9 +215,10 @@ ntfServerCLI cfgPath logPath =
hSetBuffering stdout LineBuffering
hSetBuffering stderr LineBuffering
fp <- checkSavedFingerprint cfgPath defaultX509Config
vapidKey <- getVapidKey vapidKeyPath
let host = either (const "<hostnames>") T.unpack $ lookupValue "TRANSPORT" "host" ini
port = T.unpack $ strictIni "TRANSPORT" "port" ini
cfg@NtfServerConfig {transports} = serverConfig
cfg@NtfServerConfig {transports} = serverConfig vapidKey
srv = ProtoServerWithAuth (NtfServer [THDomainName host] (if port == "443" then "" else port) (C.KeyHash fp)) Nothing
printServiceInfo serverVersion srv
printNtfServerConfig transports dbStoreConfig
Expand All @@ -230,7 +234,7 @@ ntfServerCLI cfgPath logPath =
confirmMigrations = MCYesUp,
deletedTTL = iniDeletedTTL ini
}
serverConfig =
serverConfig vapidKey =
NtfServerConfig
{ transports = iniTransports ini,
controlPort = either (const Nothing) (Just . T.unpack) $ lookupValue "TRANSPORT" "control_port" ini,
Expand Down Expand Up @@ -258,6 +262,7 @@ ntfServerCLI cfgPath logPath =
persistErrorInterval = 0 -- seconds
},
apnsConfig = defaultAPNSPushClientConfig,
wpConfig = WebPushConfig {vapidKey},
subsBatchSize = 900,
inactiveClientExpiration =
settingIsOn "INACTIVE_CLIENTS" "disconnect" ini
Expand Down Expand Up @@ -294,6 +299,7 @@ ntfServerCLI cfgPath logPath =
putStrLn $ "Error: both " <> storeLogFilePath <> " file and " <> B.unpack schema <> " schema are present (database: " <> B.unpack connstr <> ")."
putStrLn "Configure notification server storage."
exitFailure
vapidKeyPath = combine cfgPath "vapid.privkey"

printNtfServerConfig :: [(ServiceName, ASrvTransport, AddHTTP)] -> PostgresStoreCfg -> IO ()
printNtfServerConfig transports PostgresStoreCfg {dbOpts = DBOpts {connstr, schema}, dbStoreLogPath} = do
Expand Down Expand Up @@ -395,3 +401,19 @@ cliCommandP cfgPath logPath iniFile =
<> metavar "FQDN"
)
pure InitOptions {enableStoreLog, dbOptions, signAlgorithm, ip, fqdn}

genVapidKey :: FilePath -> IO VapidKey
genVapidKey file = do
cfgExists <- doesFileExist file
unless cfgExists $ run $ "openssl ecparam -name prime256v1 -genkey -noout -out " <> file
key <- C.readECPrivateKey file
pure $ mkVapid key
where
run cmd = void $ readCreateProcess (shell cmd) ""

getVapidKey :: FilePath -> IO VapidKey
getVapidKey file = do
cfgExists <- doesFileExist file
unless cfgExists $ error $ "VAPID key not found: " <> file
key <- C.readECPrivateKey file
pure $ mkVapid key
25 changes: 20 additions & 5 deletions src/Simplex/Messaging/Notifications/Server/Push.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,14 +39,21 @@ import Control.Monad.Except (ExceptT)
import GHC.Exception (SomeException)

data JWTHeader = JWTHeader
{ alg :: Text, -- key algorithm, ES256 for APNS
kid :: Text -- key ID
{ typ :: Text, -- "JWT"
alg :: Text, -- key algorithm, ES256 for APNS
kid :: Maybe Text -- key ID
}
deriving (Show)

mkJWTHeader :: Text -> Maybe Text -> JWTHeader
mkJWTHeader alg kid = JWTHeader { typ = "JWT", alg, kid }

data JWTClaims = JWTClaims
{ iss :: Text, -- issuer, team ID for APNS
iat :: Int64 -- issue time, seconds from epoch
{ iss :: Maybe Text, -- issuer, team ID for APNS
iat :: Maybe Int64, -- issue time, seconds from epoch for APNS
exp :: Maybe Int64, -- expired time, seconds from epoch for web push
aud :: Maybe Text, -- audience, for web push
sub :: Maybe Text -- subject, to be inform if there is an issue, for web push
}
deriving (Show)

Expand All @@ -56,7 +63,15 @@ data JWTToken = JWTToken JWTHeader JWTClaims
mkJWTToken :: JWTHeader -> Text -> IO JWTToken
mkJWTToken hdr iss = do
iat <- systemSeconds <$> getSystemTime
pure $ JWTToken hdr JWTClaims {iss, iat}
pure $ JWTToken hdr $ jwtClaims iat
where
jwtClaims iat = JWTClaims
{ iss = Just iss,
iat = Just iat,
exp = Nothing,
aud = Nothing,
sub = Nothing
}

type SignedJWTToken = ByteString

Expand Down
7 changes: 4 additions & 3 deletions src/Simplex/Messaging/Notifications/Server/Push/APNS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -160,9 +160,9 @@ createAPNSPushClient :: HostName -> APNSPushClientConfig -> IO APNSPushClient
createAPNSPushClient apnsHost apnsCfg@APNSPushClientConfig {authKeyFileEnv, authKeyAlg, authKeyIdEnv, appTeamId} = do
https2Client <- newTVarIO Nothing
void $ connectHTTPS2 apnsHost apnsCfg https2Client
privateKey <- readECPrivateKey =<< getEnv authKeyFileEnv
privateKey <- C.readECPrivateKey =<< getEnv authKeyFileEnv
authKeyId <- T.pack <$> getEnv authKeyIdEnv
let jwtHeader = JWTHeader {alg = authKeyAlg, kid = authKeyId}
let jwtHeader = mkJWTHeader authKeyAlg (Just authKeyId)
jwtToken <- newTVarIO =<< mkApnsJWTToken appTeamId jwtHeader privateKey
nonceDrg <- C.newRandom
pure APNSPushClient {https2Client, privateKey, jwtHeader, jwtToken, nonceDrg, apnsHost, apnsCfg}
Expand All @@ -178,7 +178,8 @@ getApnsJWTToken APNSPushClient {apnsCfg = APNSPushClientConfig {appTeamId, token
atomically $ writeTVar jwtToken t
pure signedJWT'
where
jwtTokenAge (JWTToken _ JWTClaims {iat}) = subtract iat . systemSeconds <$> getSystemTime
jwtTokenAge (JWTToken _ JWTClaims {iat = Just iat}) = subtract iat . systemSeconds <$> getSystemTime
jwtTokenAge (JWTToken _ JWTClaims {iat = Nothing}) = pure maxBound :: IO Int64

mkApnsJWTToken :: Text -> JWTHeader -> EC.PrivateKey -> IO (JWTToken, SignedJWTToken)
mkApnsJWTToken appTeamId jwtHeader privateKey = do
Expand Down
Loading
Loading