diff --git a/changelog.d/1-api-changes/mls-enabled-galley b/changelog.d/1-api-changes/mls-enabled-galley
new file mode 100644
index 00000000000..e69819275b8
--- /dev/null
+++ b/changelog.d/1-api-changes/mls-enabled-galley
@@ -0,0 +1 @@
+Fail early in galley when the MLS removal key is not configured
diff --git a/libs/wire-api-federation/src/Wire/API/Federation/API/Galley.hs b/libs/wire-api-federation/src/Wire/API/Federation/API/Galley.hs
index b29a03ca629..f35c497b4b8 100644
--- a/libs/wire-api-federation/src/Wire/API/Federation/API/Galley.hs
+++ b/libs/wire-api-federation/src/Wire/API/Federation/API/Galley.hs
@@ -67,8 +67,8 @@ type GalleyApi =
:<|> FedEndpoint "send-message" MessageSendRequest MessageSendResponse
:<|> FedEndpoint "on-user-deleted-conversations" UserDeletedConversationsNotification EmptyResponse
:<|> FedEndpoint "update-conversation" ConversationUpdateRequest ConversationUpdateResponse
- :<|> FedEndpoint "mls-welcome" MLSWelcomeRequest EmptyResponse
- :<|> FedEndpoint "on-mls-message-sent" RemoteMLSMessage EmptyResponse
+ :<|> FedEndpoint "mls-welcome" MLSWelcomeRequest MLSWelcomeResponse
+ :<|> FedEndpoint "on-mls-message-sent" RemoteMLSMessage RemoteMLSMessageResponse
:<|> FedEndpoint "send-mls-message" MessageSendRequest MLSMessageResponse
:<|> FedEndpoint "send-mls-commit-bundle" MessageSendRequest MLSMessageResponse
:<|> FedEndpoint "query-group-info" GetGroupInfoRequest GetGroupInfoResponse
@@ -244,6 +244,12 @@ data RemoteMLSMessage = RemoteMLSMessage
deriving (Arbitrary) via (GenericUniform RemoteMLSMessage)
deriving (ToJSON, FromJSON) via (CustomEncoded RemoteMLSMessage)
+data RemoteMLSMessageResponse
+ = RemoteMLSMessageOk
+ | RemoteMLSMessageMLSNotEnabled
+ deriving stock (Eq, Show, Generic)
+ deriving (ToJSON, FromJSON) via (CustomEncoded RemoteMLSMessageResponse)
+
data MessageSendRequest = MessageSendRequest
{ -- | Conversation is assumed to be owned by the target domain, this allows
-- us to protect against relay attacks
@@ -316,6 +322,12 @@ newtype MLSWelcomeRequest = MLSWelcomeRequest
deriving (Arbitrary) via (GenericUniform MLSWelcomeRequest)
deriving (FromJSON, ToJSON) via (CustomEncoded MLSWelcomeRequest)
+data MLSWelcomeResponse
+ = MLSWelcomeSent
+ | MLSWelcomeMLSNotEnabled
+ deriving stock (Eq, Generic, Show)
+ deriving (FromJSON, ToJSON) via (CustomEncoded MLSWelcomeResponse)
+
data MLSMessageResponse
= MLSMessageResponseError GalleyError
| MLSMessageResponseProtocolError Text
diff --git a/libs/wire-api/src/Wire/API/Error/Galley.hs b/libs/wire-api/src/Wire/API/Error/Galley.hs
index d714737c03c..6c2dd332e8f 100644
--- a/libs/wire-api/src/Wire/API/Error/Galley.hs
+++ b/libs/wire-api/src/Wire/API/Error/Galley.hs
@@ -68,7 +68,8 @@ data GalleyError
| ConvNotFound
| ConvAccessDenied
| -- MLS Errors
- MLSNonEmptyMemberList
+ MLSNotEnabled
+ | MLSNonEmptyMemberList
| MLSDuplicatePublicKey
| MLSKeyPackageRefNotFound
| MLSUnsupportedMessage
@@ -178,6 +179,13 @@ type instance MapError 'ConvNotFound = 'StaticError 404 "no-conversation" "Conve
type instance MapError 'ConvAccessDenied = 'StaticError 403 "access-denied" "Conversation access denied"
+type instance
+ MapError 'MLSNotEnabled =
+ 'StaticError
+ 400
+ "mls-not-enabled"
+ "MLS is not configured on this backend. See docs.wire.com for instructions on how to enable it"
+
type instance MapError 'MLSNonEmptyMemberList = 'StaticError 400 "non-empty-member-list" "Attempting to add group members outside MLS"
type instance MapError 'MLSDuplicatePublicKey = 'StaticError 400 "mls-duplicate-public-key" "MLS public key for the given signature scheme already exists"
diff --git a/libs/wire-api/src/Wire/API/Routes/Public/Galley/Conversation.hs b/libs/wire-api/src/Wire/API/Routes/Public/Galley/Conversation.hs
index 45b1bbbc2f9..59da0e111d7 100644
--- a/libs/wire-api/src/Wire/API/Routes/Public/Galley/Conversation.hs
+++ b/libs/wire-api/src/Wire/API/Routes/Public/Galley/Conversation.hs
@@ -158,6 +158,7 @@ type ConversationAPI =
( Summary "Get MLS group information"
:> CanThrow 'ConvNotFound
:> CanThrow 'MLSMissingGroupInfo
+ :> CanThrow 'MLSNotEnabled
:> ZLocalUser
:> "conversations"
:> QualifiedCapture "cnv" ConvId
@@ -321,6 +322,7 @@ type ConversationAPI =
:> Until 'V3
:> CanThrow 'ConvAccessDenied
:> CanThrow 'MLSNonEmptyMemberList
+ :> CanThrow 'MLSNotEnabled
:> CanThrow 'NotConnected
:> CanThrow 'NotATeamMember
:> CanThrow OperationDenied
@@ -338,6 +340,7 @@ type ConversationAPI =
:> From 'V3
:> CanThrow 'ConvAccessDenied
:> CanThrow 'MLSNonEmptyMemberList
+ :> CanThrow 'MLSNotEnabled
:> CanThrow 'NotConnected
:> CanThrow 'NotATeamMember
:> CanThrow OperationDenied
@@ -373,6 +376,7 @@ type ConversationAPI =
:> ZLocalUser
:> "conversations"
:> "mls-self"
+ :> CanThrow 'MLSNotEnabled
:> MultiVerb1
'GET
'[JSON]
diff --git a/libs/wire-api/src/Wire/API/Routes/Public/Galley/MLS.hs b/libs/wire-api/src/Wire/API/Routes/Public/Galley/MLS.hs
index 03421544b04..b8f0dfe2008 100644
--- a/libs/wire-api/src/Wire/API/Routes/Public/Galley/MLS.hs
+++ b/libs/wire-api/src/Wire/API/Routes/Public/Galley/MLS.hs
@@ -38,6 +38,7 @@ type MLSMessagingAPI =
"mls-welcome-message"
( Summary "Post an MLS welcome message"
:> CanThrow 'MLSKeyPackageRefNotFound
+ :> CanThrow 'MLSNotEnabled
:> "welcome"
:> ZConn
:> ReqBody '[MLS] (RawMLS Welcome)
@@ -54,6 +55,7 @@ type MLSMessagingAPI =
:> CanThrow 'MLSClientMismatch
:> CanThrow 'MLSCommitMissingReferences
:> CanThrow 'MLSKeyPackageRefNotFound
+ :> CanThrow 'MLSNotEnabled
:> CanThrow 'MLSProposalNotFound
:> CanThrow 'MLSProtocolErrorTag
:> CanThrow 'MLSSelfRemovalNotAllowed
@@ -83,6 +85,7 @@ type MLSMessagingAPI =
:> CanThrow 'MLSClientMismatch
:> CanThrow 'MLSCommitMissingReferences
:> CanThrow 'MLSKeyPackageRefNotFound
+ :> CanThrow 'MLSNotEnabled
:> CanThrow 'MLSProposalNotFound
:> CanThrow 'MLSProtocolErrorTag
:> CanThrow 'MLSSelfRemovalNotAllowed
@@ -112,6 +115,7 @@ type MLSMessagingAPI =
:> CanThrow 'MLSClientMismatch
:> CanThrow 'MLSCommitMissingReferences
:> CanThrow 'MLSKeyPackageRefNotFound
+ :> CanThrow 'MLSNotEnabled
:> CanThrow 'MLSProposalNotFound
:> CanThrow 'MLSProtocolErrorTag
:> CanThrow 'MLSSelfRemovalNotAllowed
@@ -134,6 +138,7 @@ type MLSMessagingAPI =
:<|> Named
"mls-public-keys"
( Summary "Get public keys used by the backend to sign external proposals"
+ :> CanThrow 'MLSNotEnabled
:> "public-keys"
:> MultiVerb1 'GET '[JSON] (Respond 200 "Public keys" MLSPublicKeys)
)
diff --git a/services/galley/galley.cabal b/services/galley/galley.cabal
index 470372cc4a7..69cb4423385 100644
--- a/services/galley/galley.cabal
+++ b/services/galley/galley.cabal
@@ -31,6 +31,7 @@ library
Galley.API.Mapping
Galley.API.Message
Galley.API.MLS
+ Galley.API.MLS.Enabled
Galley.API.MLS.GroupInfo
Galley.API.MLS.KeyPackage
Galley.API.MLS.Keys
diff --git a/services/galley/src/Galley/API/Create.hs b/services/galley/src/Galley/API/Create.hs
index d6a1e736f6f..110f1d23f8d 100644
--- a/services/galley/src/Galley/API/Create.hs
+++ b/services/galley/src/Galley/API/Create.hs
@@ -40,6 +40,7 @@ import qualified Data.Set as Set
import Data.Time
import qualified Data.UUID.Tagged as U
import Galley.API.Error
+import Galley.API.MLS
import Galley.API.MLS.KeyPackage (nullKeyPackageRef)
import Galley.API.MLS.Keys (getMLSRemovalKey)
import Galley.API.Mapping
@@ -93,6 +94,7 @@ createGroupConversation ::
ErrorS 'NotATeamMember,
ErrorS OperationDenied,
ErrorS 'NotConnected,
+ ErrorS 'MLSNotEnabled,
ErrorS 'MLSNonEmptyMemberList,
ErrorS 'MissingLegalholdConsent,
FederatorAccess,
@@ -117,8 +119,9 @@ createGroupConversation lusr conn newConv = do
case newConvProtocol newConv of
ProtocolMLSTag -> do
+ -- Here we fail early in order to notify users of this misconfiguration
+ assertMLSEnabled
unlessM (isJust <$> getMLSRemovalKey) $
- -- We fail here to notify users early about this misconfiguration
throw (InternalErrorWithDescription "No backend removal key is configured (See 'mlsPrivateKeyPaths' in galley's config). Refusing to create MLS conversation.")
ProtocolProteusTag -> pure ()
diff --git a/services/galley/src/Galley/API/Federation.hs b/services/galley/src/Galley/API/Federation.hs
index 01ea8942860..c6818ff6768 100644
--- a/services/galley/src/Galley/API/Federation.hs
+++ b/services/galley/src/Galley/API/Federation.hs
@@ -39,6 +39,7 @@ import qualified Data.Text.Lazy as LT
import Data.Time.Clock
import Galley.API.Action
import Galley.API.Error
+import Galley.API.MLS.Enabled
import Galley.API.MLS.GroupInfo
import Galley.API.MLS.KeyPackage
import Galley.API.MLS.Message
@@ -138,11 +139,12 @@ onClientRemoved ::
Sem r EmptyResponse
onClientRemoved domain req = do
let qusr = Qualified (F.crrUser req) domain
- for_ (F.crrConvs req) $ \convId -> do
- mConv <- E.getConversation convId
- for mConv $ \conv -> do
- lconv <- qualifyLocal conv
- removeClient lconv qusr (F.crrClient req)
+ whenM isMLSEnabled $ do
+ for_ (F.crrConvs req) $ \convId -> do
+ mConv <- E.getConversation convId
+ for mConv $ \conv -> do
+ lconv <- qualifyLocal conv
+ removeClient lconv qusr (F.crrClient req)
pure EmptyResponse
onConversationCreated ::
@@ -632,16 +634,17 @@ sendMLSCommitBundle remoteDomain msr =
. runError
. fmap (either (F.MLSMessageResponseProposalFailure . pfInner) id)
. runError
+ . mapToGalleyError @MLSBundleStaticErrors
$ do
+ assertMLSEnabled
loc <- qualifyLocal ()
let sender = toRemoteUnsafe remoteDomain (F.msrSender msr)
bundle <- either (throw . mlsProtocolError) pure $ deserializeCommitBundle (fromBase64ByteString (F.msrRawMessage msr))
- mapToGalleyError @MLSBundleStaticErrors $ do
- let msg = rmValue (cbCommitMsg bundle)
- qcnv <- E.getConversationIdByGroupId (msgGroupId msg) >>= noteS @'ConvNotFound
- when (qUnqualified qcnv /= F.msrConvId msr) $ throwS @'MLSGroupConversationMismatch
- F.MLSMessageResponseUpdates . map lcuUpdate
- <$> postMLSCommitBundle loc (qUntagged sender) Nothing qcnv Nothing bundle
+ let msg = rmValue (cbCommitMsg bundle)
+ qcnv <- E.getConversationIdByGroupId (msgGroupId msg) >>= noteS @'ConvNotFound
+ when (qUnqualified qcnv /= F.msrConvId msr) $ throwS @'MLSGroupConversationMismatch
+ F.MLSMessageResponseUpdates . map lcuUpdate
+ <$> postMLSCommitBundle loc (qUntagged sender) Nothing qcnv Nothing bundle
sendMLSMessage ::
( Members
@@ -675,17 +678,18 @@ sendMLSMessage remoteDomain msr =
. runError
. fmap (either (F.MLSMessageResponseProposalFailure . pfInner) id)
. runError
+ . mapToGalleyError @MLSMessageStaticErrors
$ do
+ assertMLSEnabled
loc <- qualifyLocal ()
let sender = toRemoteUnsafe remoteDomain (F.msrSender msr)
raw <- either (throw . mlsProtocolError) pure $ decodeMLS' (fromBase64ByteString (F.msrRawMessage msr))
- mapToGalleyError @MLSMessageStaticErrors $ do
- case rmValue raw of
- SomeMessage _ msg -> do
- qcnv <- E.getConversationIdByGroupId (msgGroupId msg) >>= noteS @'ConvNotFound
- when (qUnqualified qcnv /= F.msrConvId msr) $ throwS @'MLSGroupConversationMismatch
- F.MLSMessageResponseUpdates . map lcuUpdate
- <$> postMLSMessage loc (qUntagged sender) Nothing qcnv Nothing raw
+ case rmValue raw of
+ SomeMessage _ msg -> do
+ qcnv <- E.getConversationIdByGroupId (msgGroupId msg) >>= noteS @'ConvNotFound
+ when (qUnqualified qcnv /= F.msrConvId msr) $ throwS @'MLSGroupConversationMismatch
+ F.MLSMessageResponseUpdates . map lcuUpdate
+ <$> postMLSMessage loc (qUntagged sender) Nothing qcnv Nothing raw
class ToGalleyRuntimeError (effs :: EffectRow) r where
mapToGalleyError ::
@@ -715,75 +719,84 @@ mlsSendWelcome ::
'[ BrigAccess,
Error InternalError,
GundeckAccess,
+ Input Env,
Input (Local ()),
Input UTCTime
]
r =>
Domain ->
F.MLSWelcomeRequest ->
- Sem r EmptyResponse
-mlsSendWelcome _origDomain (fromBase64ByteString . F.unMLSWelcomeRequest -> rawWelcome) = do
- loc <- qualifyLocal ()
- now <- input
- welcome <- either (throw . InternalErrorWithDescription . LT.fromStrict) pure $ decodeMLS' rawWelcome
- -- Extract only recipients local to this backend
- rcpts <-
- fmap catMaybes
- $ traverse
- ( fmap (fmap cidQualifiedClient . hush)
- . runError @(Tagged 'MLSKeyPackageRefNotFound ())
- . derefKeyPackage
- . gsNewMember
- )
- $ welSecrets welcome
- let lrcpts = qualifyAs loc $ fst $ partitionQualified loc rcpts
- sendLocalWelcomes Nothing now rawWelcome lrcpts
- pure EmptyResponse
+ Sem r F.MLSWelcomeResponse
+mlsSendWelcome _origDomain (fromBase64ByteString . F.unMLSWelcomeRequest -> rawWelcome) =
+ fmap (either (const MLSWelcomeMLSNotEnabled) (const MLSWelcomeSent))
+ . runError @(Tagged 'MLSNotEnabled ())
+ $ do
+ assertMLSEnabled
+ loc <- qualifyLocal ()
+ now <- input
+ welcome <- either (throw . InternalErrorWithDescription . LT.fromStrict) pure $ decodeMLS' rawWelcome
+ -- Extract only recipients local to this backend
+ rcpts <-
+ fmap catMaybes
+ $ traverse
+ ( fmap (fmap cidQualifiedClient . hush)
+ . runError @(Tagged 'MLSKeyPackageRefNotFound ())
+ . derefKeyPackage
+ . gsNewMember
+ )
+ $ welSecrets welcome
+ let lrcpts = qualifyAs loc $ fst $ partitionQualified loc rcpts
+ sendLocalWelcomes Nothing now rawWelcome lrcpts
onMLSMessageSent ::
Members
'[ ExternalAccess,
GundeckAccess,
Input (Local ()),
+ Input Env,
MemberStore,
P.TinyLog
]
r =>
Domain ->
F.RemoteMLSMessage ->
- Sem r EmptyResponse
-onMLSMessageSent domain rmm = do
- loc <- qualifyLocal ()
- let rcnv = toRemoteUnsafe domain (F.rmmConversation rmm)
- let users = Set.fromList (map fst (F.rmmRecipients rmm))
- (members, allMembers) <-
- first Set.fromList
- <$> E.selectRemoteMembers (toList users) rcnv
- unless allMembers $
- P.warn $
- Log.field "conversation" (toByteString' (tUnqualified rcnv))
- Log.~~ Log.field "domain" (toByteString' (tDomain rcnv))
- Log.~~ Log.msg
- ( "Attempt to send remote message to local\
- \ users not in the conversation" ::
- ByteString
- )
- let recipients = filter (\(u, _) -> Set.member u members) (F.rmmRecipients rmm)
- -- FUTUREWORK: support local bots
- let e =
- Event (qUntagged rcnv) (F.rmmSender rmm) (F.rmmTime rmm) $
- EdMLSMessage (fromBase64ByteString (F.rmmMessage rmm))
- let mkPush :: (UserId, ClientId) -> MessagePush 'NormalMessage
- mkPush uc = newMessagePush loc mempty Nothing (F.rmmMetadata rmm) uc e
-
- runMessagePush loc (Just (qUntagged rcnv)) $
- foldMap mkPush recipients
- pure EmptyResponse
+ Sem r F.RemoteMLSMessageResponse
+onMLSMessageSent domain rmm =
+ fmap (either (const RemoteMLSMessageMLSNotEnabled) (const RemoteMLSMessageOk))
+ . runError @(Tagged 'MLSNotEnabled ())
+ $ do
+ assertMLSEnabled
+ loc <- qualifyLocal ()
+ let rcnv = toRemoteUnsafe domain (F.rmmConversation rmm)
+ let users = Set.fromList (map fst (F.rmmRecipients rmm))
+ (members, allMembers) <-
+ first Set.fromList
+ <$> E.selectRemoteMembers (toList users) rcnv
+ unless allMembers $
+ P.warn $
+ Log.field "conversation" (toByteString' (tUnqualified rcnv))
+ Log.~~ Log.field "domain" (toByteString' (tDomain rcnv))
+ Log.~~ Log.msg
+ ( "Attempt to send remote message to local\
+ \ users not in the conversation" ::
+ ByteString
+ )
+ let recipients = filter (\(u, _) -> Set.member u members) (F.rmmRecipients rmm)
+ -- FUTUREWORK: support local bots
+ let e =
+ Event (qUntagged rcnv) (F.rmmSender rmm) (F.rmmTime rmm) $
+ EdMLSMessage (fromBase64ByteString (F.rmmMessage rmm))
+ let mkPush :: (UserId, ClientId) -> MessagePush 'NormalMessage
+ mkPush uc = newMessagePush loc mempty Nothing (F.rmmMetadata rmm) uc e
+
+ runMessagePush loc (Just (qUntagged rcnv)) $
+ foldMap mkPush recipients
queryGroupInfo ::
( Members
'[ ConversationStore,
- Input (Local ())
+ Input (Local ()),
+ Input Env
]
r,
Member MemberStore r
@@ -796,6 +809,7 @@ queryGroupInfo origDomain req =
. runError @GalleyError
. mapToGalleyError @MLSGroupInfoStaticErrors
$ do
+ assertMLSEnabled
lconvId <- qualifyLocal . ggireqConv $ req
let sender = toRemoteUnsafe origDomain . ggireqSender $ req
state <- getGroupInfoFromLocalConv (qUntagged sender) lconvId
diff --git a/services/galley/src/Galley/API/MLS.hs b/services/galley/src/Galley/API/MLS.hs
index 242414a4420..cbd8307232e 100644
--- a/services/galley/src/Galley/API/MLS.hs
+++ b/services/galley/src/Galley/API/MLS.hs
@@ -16,7 +16,9 @@
-- with this program. If not, see .
module Galley.API.MLS
- ( postMLSWelcomeFromLocalUser,
+ ( isMLSEnabled,
+ assertMLSEnabled,
+ postMLSWelcomeFromLocalUser,
postMLSMessage,
postMLSCommitBundleFromLocalUser,
postMLSMessageFromLocalUser,
@@ -25,6 +27,27 @@ module Galley.API.MLS
)
where
-import Galley.API.MLS.Keys
+import Control.Lens (view)
+import Data.Id
+import Data.Qualified
+import Galley.API.MLS.Enabled
import Galley.API.MLS.Message
import Galley.API.MLS.Welcome
+import Galley.Env
+import Imports
+import Polysemy
+import Polysemy.Input
+import Wire.API.Error
+import Wire.API.Error.Galley
+import Wire.API.MLS.Keys
+
+getMLSPublicKeys ::
+ ( Member (Input Env) r,
+ Member (ErrorS 'MLSNotEnabled) r
+ ) =>
+ Local UserId ->
+ Sem r MLSPublicKeys
+getMLSPublicKeys _ = do
+ assertMLSEnabled
+ keys <- inputs (view mlsKeys)
+ pure $ mlsKeysToPublic keys
diff --git a/services/galley/src/Galley/API/MLS/Enabled.hs b/services/galley/src/Galley/API/MLS/Enabled.hs
new file mode 100644
index 00000000000..1af66279a2a
--- /dev/null
+++ b/services/galley/src/Galley/API/MLS/Enabled.hs
@@ -0,0 +1,44 @@
+-- This file is part of the Wire Server implementation.
+--
+-- Copyright (C) 2022 Wire Swiss GmbH
+--
+-- This program is free software: you can redistribute it and/or modify it under
+-- the terms of the GNU Affero General Public License as published by the Free
+-- Software Foundation, either version 3 of the License, or (at your option) any
+-- later version.
+--
+-- This program is distributed in the hope that it will be useful, but WITHOUT
+-- ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
+-- FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more
+-- details.
+--
+-- You should have received a copy of the GNU Affero General Public License along
+-- with this program. If not, see .
+
+module Galley.API.MLS.Enabled
+ ( isMLSEnabled,
+ assertMLSEnabled,
+ )
+where
+
+import Galley.API.MLS.Keys
+import Galley.Env
+import Imports
+import Polysemy
+import Polysemy.Input
+import Wire.API.Error
+import Wire.API.Error.Galley
+
+isMLSEnabled :: Member (Input Env) r => Sem r Bool
+isMLSEnabled = isJust <$> getMLSRemovalKey
+
+-- | Fail if MLS is not enabled. Only use this function at the beginning of an
+-- MLS endpoint, NOT in utility functions.
+assertMLSEnabled ::
+ ( Member (Input Env) r,
+ Member (ErrorS 'MLSNotEnabled) r
+ ) =>
+ Sem r ()
+assertMLSEnabled =
+ unlessM isMLSEnabled $
+ throwS @'MLSNotEnabled
diff --git a/services/galley/src/Galley/API/MLS/GroupInfo.hs b/services/galley/src/Galley/API/MLS/GroupInfo.hs
index 2a25d1ac5fd..16111e9026e 100644
--- a/services/galley/src/Galley/API/MLS/GroupInfo.hs
+++ b/services/galley/src/Galley/API/MLS/GroupInfo.hs
@@ -20,11 +20,13 @@ module Galley.API.MLS.GroupInfo where
import Data.Id as Id
import Data.Json.Util
import Data.Qualified
+import Galley.API.MLS.Enabled
import Galley.API.MLS.Util
import Galley.API.Util
import Galley.Effects
import qualified Galley.Effects.ConversationStore as E
import qualified Galley.Effects.FederatorAccess as E
+import Galley.Env
import Imports
import Polysemy
import Polysemy.Error
@@ -38,7 +40,8 @@ import Wire.API.MLS.PublicGroupState
type MLSGroupInfoStaticErrors =
'[ ErrorS 'ConvNotFound,
- ErrorS 'MLSMissingGroupInfo
+ ErrorS 'MLSMissingGroupInfo,
+ ErrorS 'MLSNotEnabled
]
getGroupInfo ::
@@ -46,7 +49,7 @@ getGroupInfo ::
'[ ConversationStore,
Error FederationError,
FederatorAccess,
- Input (Local ()),
+ Input Env,
MemberStore
]
r =>
@@ -54,7 +57,8 @@ getGroupInfo ::
Local UserId ->
Qualified ConvId ->
Sem r OpaquePublicGroupState
-getGroupInfo lusr qcnvId =
+getGroupInfo lusr qcnvId = do
+ assertMLSEnabled
foldQualified
lusr
(getGroupInfoFromLocalConv . qUntagged $ lusr)
diff --git a/services/galley/src/Galley/API/MLS/Keys.hs b/services/galley/src/Galley/API/MLS/Keys.hs
index e214bc0a63c..3db1ebfd9c3 100644
--- a/services/galley/src/Galley/API/MLS/Keys.hs
+++ b/services/galley/src/Galley/API/MLS/Keys.hs
@@ -15,12 +15,10 @@
-- You should have received a copy of the GNU Affero General Public License along
-- with this program. If not, see .
-module Galley.API.MLS.Keys where
+module Galley.API.MLS.Keys (getMLSRemovalKey) where
import Control.Lens (view)
import Crypto.PubKey.Ed25519 (PublicKey, SecretKey)
-import Data.Id
-import Data.Qualified
import Galley.Env
import Imports
import Polysemy
@@ -28,13 +26,5 @@ import Polysemy.Input
import Wire.API.MLS.Credential (SignaturePurpose (RemovalPurpose))
import Wire.API.MLS.Keys
-getMLSPublicKeys ::
- Member (Input Env) r =>
- Local UserId ->
- Sem r MLSPublicKeys
-getMLSPublicKeys _ = do
- keys <- inputs (view mlsKeys)
- pure $ mlsKeysToPublic keys
-
getMLSRemovalKey :: Member (Input Env) r => Sem r (Maybe (SecretKey, PublicKey))
getMLSRemovalKey = mlsKeyPair_ed25519 <$> (inputs (view mlsKeys) <*> pure RemovalPurpose)
diff --git a/services/galley/src/Galley/API/MLS/Message.hs b/services/galley/src/Galley/API/MLS/Message.hs
index 7080b94941f..9b06ab40a92 100644
--- a/services/galley/src/Galley/API/MLS/Message.hs
+++ b/services/galley/src/Galley/API/MLS/Message.hs
@@ -39,6 +39,7 @@ import qualified Data.Text as T
import Data.Time
import Galley.API.Action
import Galley.API.Error
+import Galley.API.MLS.Enabled
import Galley.API.MLS.KeyPackage
import Galley.API.MLS.Propagate
import Galley.API.MLS.Removal
@@ -95,6 +96,7 @@ type MLSMessageStaticErrors =
'[ ErrorS 'ConvAccessDenied,
ErrorS 'ConvMemberNotFound,
ErrorS 'ConvNotFound,
+ ErrorS 'MLSNotEnabled,
ErrorS 'MLSUnsupportedMessage,
ErrorS 'MLSStaleMessage,
ErrorS 'MLSProposalNotFound,
@@ -127,6 +129,7 @@ postMLSMessageFromLocalUserV1 ::
ErrorS 'MLSCommitMissingReferences,
ErrorS 'MLSGroupConversationMismatch,
ErrorS 'MLSMissingSenderClient,
+ ErrorS 'MLSNotEnabled,
ErrorS 'MLSProposalNotFound,
ErrorS 'MLSSelfRemovalNotAllowed,
ErrorS 'MLSStaleMessage,
@@ -145,11 +148,13 @@ postMLSMessageFromLocalUserV1 ::
ConnId ->
RawMLS SomeMessage ->
Sem r [Event]
-postMLSMessageFromLocalUserV1 lusr mc conn smsg = case rmValue smsg of
- SomeMessage _ msg -> do
- qcnv <- getConversationIdByGroupId (msgGroupId msg) >>= noteS @'ConvNotFound
- map lcuEvent
- <$> postMLSMessage lusr (qUntagged lusr) mc qcnv (Just conn) smsg
+postMLSMessageFromLocalUserV1 lusr mc conn smsg = do
+ assertMLSEnabled
+ case rmValue smsg of
+ SomeMessage _ msg -> do
+ qcnv <- getConversationIdByGroupId (msgGroupId msg) >>= noteS @'ConvNotFound
+ map lcuEvent
+ <$> postMLSMessage lusr (qUntagged lusr) mc qcnv (Just conn) smsg
postMLSMessageFromLocalUser ::
( HasProposalEffects r,
@@ -163,6 +168,7 @@ postMLSMessageFromLocalUser ::
ErrorS 'MLSCommitMissingReferences,
ErrorS 'MLSGroupConversationMismatch,
ErrorS 'MLSMissingSenderClient,
+ ErrorS 'MLSNotEnabled,
ErrorS 'MLSProposalNotFound,
ErrorS 'MLSSelfRemovalNotAllowed,
ErrorS 'MLSStaleMessage,
@@ -184,6 +190,7 @@ postMLSMessageFromLocalUser ::
postMLSMessageFromLocalUser lusr mc conn msg = do
-- FUTUREWORK: Inline the body of 'postMLSMessageFromLocalUserV1' once version
-- V1 is dropped
+ assertMLSEnabled
events <- postMLSMessageFromLocalUserV1 lusr mc conn msg
t <- toUTCTimeMillis <$> input
pure $ MLSMessageSendingStatus events t
@@ -227,6 +234,7 @@ postMLSCommitBundleFromLocalUser ::
'[ BrigAccess,
Error FederationError,
Error InternalError,
+ ErrorS 'MLSNotEnabled,
Input (Local ()),
Input Opts,
Input UTCTime,
@@ -243,6 +251,7 @@ postMLSCommitBundleFromLocalUser ::
CommitBundle ->
Sem r MLSMessageSendingStatus
postMLSCommitBundleFromLocalUser lusr mc conn bundle = do
+ assertMLSEnabled
let msg = rmValue (cbCommitMsg bundle)
qcnv <- getConversationIdByGroupId (msgGroupId msg) >>= noteS @'ConvNotFound
events <-
@@ -370,6 +379,7 @@ postMLSMessage ::
ErrorS 'ConvAccessDenied,
ErrorS 'ConvMemberNotFound,
ErrorS 'ConvNotFound,
+ ErrorS 'MLSNotEnabled,
ErrorS 'MLSClientSenderUserMismatch,
ErrorS 'MLSCommitMissingReferences,
ErrorS 'MLSGroupConversationMismatch,
diff --git a/services/galley/src/Galley/API/MLS/Propagate.hs b/services/galley/src/Galley/API/MLS/Propagate.hs
index 8356619baa3..7468e7ed9e0 100644
--- a/services/galley/src/Galley/API/MLS/Propagate.hs
+++ b/services/galley/src/Galley/API/MLS/Propagate.hs
@@ -32,12 +32,14 @@ import Galley.Effects
import Galley.Effects.FederatorAccess
import Galley.Types.Conversations.Members
import Imports
+import qualified Network.Wai.Utilities.Error as Wai
import Network.Wai.Utilities.Server
import Polysemy
import Polysemy.Input
import Polysemy.TinyLog
import qualified System.Logger.Class as Logger
import Wire.API.Error
+import Wire.API.Error.Galley
import Wire.API.Event.Conversation
import Wire.API.Federation.API
import Wire.API.Federation.API.Galley
@@ -105,10 +107,18 @@ propagateMessage qusr lconv cm con raw = do
(\(c, _) -> (remoteUserId, c))
(toList (Map.findWithDefault mempty remoteUserQId cm))
- handleError :: Member TinyLog r => Either (Remote [a], FederationError) x -> Sem r ()
- handleError (Right _) = pure ()
- handleError (Left (r, e)) =
+ handleError ::
+ Member TinyLog r =>
+ Either (Remote [a], FederationError) (Remote RemoteMLSMessageResponse) ->
+ Sem r ()
+ handleError (Right x) = case tUnqualified x of
+ RemoteMLSMessageOk -> pure ()
+ RemoteMLSMessageMLSNotEnabled -> logFedError x (errorToWai @'MLSNotEnabled)
+ handleError (Left (r, e)) = logFedError r (toWai e)
+
+ logFedError :: Member TinyLog r => Remote x -> Wai.Error -> Sem r ()
+ logFedError r e =
warn $
Logger.msg ("A message could not be delivered to a remote backend" :: ByteString)
. Logger.field "remote_domain" (domainText (tDomain r))
- . logErrorMsg (toWai e)
+ . logErrorMsg e
diff --git a/services/galley/src/Galley/API/MLS/Welcome.hs b/services/galley/src/Galley/API/MLS/Welcome.hs
index 2e52592d9c5..548a8d1733c 100644
--- a/services/galley/src/Galley/API/MLS/Welcome.hs
+++ b/services/galley/src/Galley/API/MLS/Welcome.hs
@@ -28,13 +28,16 @@ import Data.Id
import Data.Json.Util
import Data.Qualified
import Data.Time
+import Galley.API.MLS.Enabled
import Galley.API.MLS.KeyPackage
import Galley.API.Push
import Galley.Data.Conversation
import Galley.Effects.BrigAccess
import Galley.Effects.FederatorAccess
import Galley.Effects.GundeckAccess
+import Galley.Env
import Imports
+import qualified Network.Wai.Utilities.Error as Wai
import Network.Wai.Utilities.Server
import Polysemy
import Polysemy.Input
@@ -78,7 +81,9 @@ postMLSWelcomeFromLocalUser ::
FederatorAccess,
GundeckAccess,
ErrorS 'MLSKeyPackageRefNotFound,
+ ErrorS 'MLSNotEnabled,
Input UTCTime,
+ Input Env,
P.TinyLog
]
r =>
@@ -86,7 +91,9 @@ postMLSWelcomeFromLocalUser ::
ConnId ->
RawMLS Welcome ->
Sem r ()
-postMLSWelcomeFromLocalUser loc con wel = postMLSWelcome loc (Just con) wel
+postMLSWelcomeFromLocalUser loc con wel = do
+ assertMLSEnabled
+ postMLSWelcome loc (Just con) wel
welcomeRecipients ::
Members
@@ -138,10 +145,18 @@ sendRemoteWelcomes rawWelcome clients = do
traverse_ handleError <=< runFederatedConcurrentlyEither clients $
const rpc
where
- handleError :: Member P.TinyLog r => Either (Remote [a], FederationError) x -> Sem r ()
- handleError (Right _) = pure ()
- handleError (Left (r, e)) =
+ handleError ::
+ Member P.TinyLog r =>
+ Either (Remote [a], FederationError) (Remote MLSWelcomeResponse) ->
+ Sem r ()
+ handleError (Right x) = case tUnqualified x of
+ MLSWelcomeSent -> pure ()
+ MLSWelcomeMLSNotEnabled -> logFedError x (errorToWai @'MLSNotEnabled)
+ handleError (Left (r, e)) = logFedError r (toWai e)
+
+ logFedError :: Member P.TinyLog r => Remote x -> Wai.Error -> Sem r ()
+ logFedError r e =
P.warn $
Logger.msg ("A welcome message could not be delivered to a remote backend" :: ByteString)
. Logger.field "remote_domain" (domainText (tDomain r))
- . logErrorMsg (toWai e)
+ . logErrorMsg e
diff --git a/services/galley/src/Galley/API/Query.hs b/services/galley/src/Galley/API/Query.hs
index aefb08a8100..38c848c66c4 100644
--- a/services/galley/src/Galley/API/Query.hs
+++ b/services/galley/src/Galley/API/Query.hs
@@ -55,6 +55,7 @@ import Data.Range
import qualified Data.Set as Set
import Data.Tagged
import Galley.API.Error
+import Galley.API.MLS
import Galley.API.MLS.Keys
import Galley.API.MLS.Types
import Galley.API.Mapping
@@ -715,6 +716,7 @@ getMLSSelfConversationWithError ::
Members
'[ ConversationStore,
Error InternalError,
+ ErrorS 'MLSNotEnabled,
Input Env,
P.TinyLog
]
@@ -722,13 +724,8 @@ getMLSSelfConversationWithError ::
Local UserId ->
Sem r Conversation
getMLSSelfConversationWithError lusr = do
- unlessM (isJust <$> getMLSRemovalKey) $
- throw (InternalErrorWithDescription noKeyMsg)
+ assertMLSEnabled
getMLSSelfConversation lusr
- where
- noKeyMsg =
- "No backend removal key is configured (See 'mlsPrivateKeyPaths'"
- <> "in galley's config). Refusing to create MLS conversation."
-- | Get an MLS self conversation. In case it does not exist, it is partially
-- created in the database. The part that is not written is the epoch number;
diff --git a/services/galley/test/integration/API/MLS.hs b/services/galley/test/integration/API/MLS.hs
index 1928d98eea3..9f0c8965b15 100644
--- a/services/galley/test/integration/API/MLS.hs
+++ b/services/galley/test/integration/API/MLS.hs
@@ -25,7 +25,7 @@ import API.Util as Util
import Bilge hiding (head)
import Bilge.Assert
import Cassandra
-import Control.Lens (view, (%~), (.~))
+import Control.Lens (view)
import qualified Control.Monad.State as State
import Crypto.Error
import qualified Crypto.PubKey.Ed25519 as Ed25519
@@ -46,7 +46,6 @@ import Data.String.Conversions
import qualified Data.Text as T
import Data.Time
import Federator.MockServer hiding (withTempMockFederator)
-import qualified Galley.Options as Opts
import Imports
import qualified Network.Wai.Utilities.Error as Wai
import Test.QuickCheck (Arbitrary (arbitrary), generate)
@@ -210,6 +209,13 @@ tests s =
test s "listing conversations without MLS configured" testSelfConversationMLSNotConfigured,
test s "attempt to add another user to a conversation fails" testSelfConversationOtherUser,
test s "attempt to leave fails" testSelfConversationLeave
+ ],
+ testGroup
+ "MLS disabled"
+ [ test s "cannot create MLS conversations" postMLSConvDisabled,
+ test s "cannot send an MLS message" postMLSMessageDisabled,
+ test s "cannot send a commit bundle" postMLSBundleDisabled,
+ test s "cannot get group info" getGroupInfoDisabled
]
]
@@ -321,7 +327,7 @@ testRemoteWelcome = do
let mockedResponse fedReq =
case frRPC fedReq of
- "mls-welcome" -> pure (Aeson.encode EmptyResponse)
+ "mls-welcome" -> pure (Aeson.encode MLSWelcomeSent)
ms -> assertFailure ("unmocked endpoint called: " <> cs ms)
runMLSTest $ do
@@ -645,7 +651,7 @@ testAddRemoteUser = do
. Set.fromList
. map (flip ClientInfo True . ciClient)
$ [bob1]
- "mls-welcome" -> pure (Aeson.encode EmptyResponse)
+ "mls-welcome" -> pure (Aeson.encode MLSWelcomeSent)
ms -> assertFailure ("unmocked endpoint called: " <> cs ms)
commit <- createAddCommit alice1 [bob]
@@ -829,8 +835,8 @@ testRemoteAppMessage = do
let mock req = case frRPC req of
"on-conversation-updated" -> pure (Aeson.encode ())
"on-new-remote-conversation" -> pure (Aeson.encode EmptyResponse)
- "on-mls-message-sent" -> pure (Aeson.encode EmptyResponse)
- "mls-welcome" -> pure (Aeson.encode EmptyResponse)
+ "on-mls-message-sent" -> pure (Aeson.encode RemoteMLSMessageOk)
+ "mls-welcome" -> pure (Aeson.encode MLSWelcomeSent)
"get-mls-clients" ->
pure
. Aeson.encode
@@ -1216,7 +1222,7 @@ testRemoteToLocal = do
let mockedResponse fedReq =
case frRPC fedReq of
- "mls-welcome" -> pure (Aeson.encode EmptyResponse)
+ "mls-welcome" -> pure (Aeson.encode MLSWelcomeSent)
"on-new-remote-conversation" -> pure (Aeson.encode EmptyResponse)
"on-conversation-updated" -> pure (Aeson.encode ())
"get-mls-clients" ->
@@ -1274,7 +1280,7 @@ testRemoteToLocalWrongConversation = do
let mockedResponse fedReq =
case frRPC fedReq of
- "mls-welcome" -> pure (Aeson.encode EmptyResponse)
+ "mls-welcome" -> pure (Aeson.encode MLSWelcomeSent)
"on-new-remote-conversation" -> pure (Aeson.encode EmptyResponse)
"on-conversation-updated" -> pure (Aeson.encode ())
"get-mls-clients" ->
@@ -1645,8 +1651,8 @@ testBackendRemoveProposalLocalConvRemoteUser = do
let mock req = case frRPC req of
"on-conversation-updated" -> pure (Aeson.encode ())
"on-new-remote-conversation" -> pure (Aeson.encode EmptyResponse)
- "on-mls-message-sent" -> pure (Aeson.encode EmptyResponse)
- "mls-welcome" -> pure (Aeson.encode EmptyResponse)
+ "on-mls-message-sent" -> pure (Aeson.encode RemoteMLSMessageOk)
+ "mls-welcome" -> pure (Aeson.encode MLSWelcomeSent)
"get-mls-clients" ->
pure
. Aeson.encode
@@ -1822,8 +1828,8 @@ testBackendRemoveProposalLocalConvRemoteLeaver = do
let mock req = case frRPC req of
"on-conversation-updated" -> pure (Aeson.encode ())
"on-new-remote-conversation" -> pure (Aeson.encode EmptyResponse)
- "on-mls-message-sent" -> pure (Aeson.encode EmptyResponse)
- "mls-welcome" -> pure (Aeson.encode EmptyResponse)
+ "on-mls-message-sent" -> pure (Aeson.encode RemoteMLSMessageOk)
+ "mls-welcome" -> pure (Aeson.encode MLSWelcomeSent)
"get-mls-clients" ->
pure
. Aeson.encode
@@ -1898,8 +1904,8 @@ testBackendRemoveProposalLocalConvRemoteClient = do
let mock req = case frRPC req of
"on-conversation-updated" -> pure (Aeson.encode ())
"on-new-remote-conversation" -> pure (Aeson.encode EmptyResponse)
- "mls-welcome" -> pure (Aeson.encode EmptyResponse)
- "on-mls-message-sent" -> pure (Aeson.encode EmptyResponse)
+ "mls-welcome" -> pure (Aeson.encode MLSWelcomeSent)
+ "on-mls-message-sent" -> pure (Aeson.encode RemoteMLSMessageOk)
"get-mls-clients" ->
pure
. Aeson.encode
@@ -2003,7 +2009,7 @@ testFederatedGetGroupInfo = do
let mock req = case frRPC req of
"on-new-remote-conversation" -> pure (Aeson.encode EmptyResponse)
"on-conversation-updated" -> pure (Aeson.encode ())
- "mls-welcome" -> pure (Aeson.encode EmptyResponse)
+ "mls-welcome" -> pure (Aeson.encode MLSWelcomeSent)
"get-mls-clients" ->
pure
. Aeson.encode
@@ -2124,7 +2130,7 @@ testRemoteUserPostsCommitBundle = do
. Set.fromList
. map (flip ClientInfo True . ciClient)
$ [bob1]
- "mls-welcome" -> pure (Aeson.encode EmptyResponse)
+ "mls-welcome" -> pure (Aeson.encode MLSWelcomeSent)
ms -> assertFailure ("unmocked endpoint called: " <> cs ms)
commit <- createAddCommit alice1 [bob]
@@ -2404,8 +2410,7 @@ testSelfConversationList isBelowV3 = do
testSelfConversationMLSNotConfigured :: TestM ()
testSelfConversationMLSNotConfigured = do
alice <- randomUser
- let noMLS = Opts.optSettings %~ Opts.setMlsPrivateKeyPaths .~ Nothing
- withSettingsOverrides noMLS $
+ withMLSDisabled $
getConvPage alice Nothing (Just 100) !!! const 200 === statusCode
testSelfConversationOtherUser :: TestM ()
@@ -2477,3 +2482,55 @@ testAddTeamUserWithBundle = do
returnedGS
+
+assertMLSNotEnabled :: Assertions ()
+assertMLSNotEnabled = do
+ const 400 === statusCode
+ const (Just "mls-not-enabled") === fmap Wai.label . responseJsonError
+
+postMLSConvDisabled :: TestM ()
+postMLSConvDisabled = do
+ alice <- randomQualifiedUser
+ withMLSDisabled $
+ postConvQualified
+ (qUnqualified alice)
+ (defNewMLSConv (newClientId 0))
+ !!! assertMLSNotEnabled
+
+postMLSMessageDisabled :: TestM ()
+postMLSMessageDisabled = do
+ [alice, bob] <- createAndConnectUsers [Nothing, Nothing]
+ runMLSTest $ do
+ [alice1, bob1] <- traverse createMLSClient [alice, bob]
+ void $ uploadNewKeyPackage bob1
+ void $ setupMLSGroup alice1
+ mp <- createAddCommit alice1 [bob]
+ withMLSDisabled $
+ postMessage (mpSender mp) (mpMessage mp)
+ !!! assertMLSNotEnabled
+
+postMLSBundleDisabled :: TestM ()
+postMLSBundleDisabled = do
+ [alice, bob] <- createAndConnectUsers [Nothing, Nothing]
+ runMLSTest $ do
+ [alice1, bob1] <- traverse createMLSClient [alice, bob]
+ void $ uploadNewKeyPackage bob1
+ void $ setupMLSGroup alice1
+ mp <- createAddCommit alice1 [bob]
+ withMLSDisabled $ do
+ bundle <- createBundle mp
+ postCommitBundle (mpSender mp) bundle
+ !!! assertMLSNotEnabled
+
+getGroupInfoDisabled :: TestM ()
+getGroupInfoDisabled = do
+ [alice, bob] <- createAndConnectUsers [Nothing, Nothing]
+ runMLSTest $ do
+ [alice1, bob1] <- traverse createMLSClient [alice, bob]
+ void $ uploadNewKeyPackage bob1
+ (_, qcnv) <- setupMLSGroup alice1
+ void $ createAddCommit alice1 [bob] >>= sendAndConsumeCommit
+
+ withMLSDisabled $
+ getGroupInfo (qUnqualified alice) qcnv
+ !!! assertMLSNotEnabled
diff --git a/services/galley/test/integration/API/MLS/Util.hs b/services/galley/test/integration/API/MLS/Util.hs
index 275fc401f37..069b48cedfc 100644
--- a/services/galley/test/integration/API/MLS/Util.hs
+++ b/services/galley/test/integration/API/MLS/Util.hs
@@ -24,7 +24,7 @@ import Bilge
import Bilge.Assert
import Control.Arrow ((&&&))
import Control.Error.Util
-import Control.Lens (preview, to, view, (^..))
+import Control.Lens (preview, to, view, (.~), (^..))
import Control.Monad.Catch
import Control.Monad.State (StateT, evalStateT)
import qualified Control.Monad.State as State
@@ -48,6 +48,7 @@ import qualified Data.Text.Encoding as T
import Data.Time.Clock (getCurrentTime)
import Galley.Keys
import Galley.Options
+import qualified Galley.Options as Opts
import Imports hiding (getSymbolicLinkTarget)
import System.Directory (getSymbolicLinkTarget)
import System.FilePath
@@ -1047,3 +1048,8 @@ getSelfConv u = do
. zUser u
. zConn "conn"
. zType "access"
+
+withMLSDisabled :: HasSettingsOverrides m => m a -> m a
+withMLSDisabled = withSettingsOverrides noMLS
+ where
+ noMLS = Opts.optSettings . Opts.setMlsPrivateKeyPaths .~ Nothing