From b5869e023734860eef72d22de0db5845036a872c Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 21 Jan 2026 14:55:07 +0100 Subject: [PATCH 01/60] Import changes of #4926 The path through our system has been outlined in https://github.com/wireapp/wire-server/pull/4926 . Import and adjust the email relevant bits. --- libs/saml2-web-sso/default.nix | 2 + libs/saml2-web-sso/saml2-web-sso.cabal | 1 + .../saml2-web-sso/src/SAML2/WebSSO/Orphans.hs | 28 ++++++-- libs/saml2-web-sso/src/SAML2/WebSSO/Types.hs | 62 +++++++++++------ .../test/Test/SAML2/WebSSO/RoundtripSpec.hs | 1 + .../src/Wire/API/Routes/Internal/Brig.hs | 68 ++++++++++++++++++- .../src/Wire/API/User/IdentityProvider.hs | 32 ++++++--- libs/wire-api/src/Wire/API/User/Orphans.hs | 12 ---- .../src/Wire/EmailSubsystem.hs | 4 ++ .../src/Wire/EmailSubsystem/Interpreter.hs | 14 ++++ .../src/Wire/SAMLEmailSubsystem.hs | 11 +++ .../Wire/SAMLEmailSubsystem/Interpreter.hs | 60 ++++++++++++++++ libs/wire-subsystems/src/Wire/UserStore.hs | 1 + .../src/Wire/UserStore/Cassandra.hs | 9 +++ libs/wire-subsystems/wire-subsystems.cabal | 2 + services/brig/src/Brig/API/Internal.hs | 8 ++- .../brig/src/Brig/CanonicalInterpreter.hs | 6 +- services/spar/src/Spar/API.hs | 4 ++ services/spar/src/Spar/Intra/Brig.hs | 8 +++ services/spar/src/Spar/Sem/BrigAccess.hs | 3 + services/spar/src/Spar/Sem/BrigAccess/Http.hs | 1 + 21 files changed, 288 insertions(+), 49 deletions(-) create mode 100644 libs/wire-subsystems/src/Wire/SAMLEmailSubsystem.hs create mode 100644 libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs diff --git a/libs/saml2-web-sso/default.nix b/libs/saml2-web-sso/default.nix index e4d714b7145..d09f6565fcb 100644 --- a/libs/saml2-web-sso/default.nix +++ b/libs/saml2-web-sso/default.nix @@ -48,6 +48,7 @@ , memory , mtl , network-uri +, openapi3 , pretty-show , process , QuickCheck @@ -127,6 +128,7 @@ mkDerivation { memory mtl network-uri + openapi3 pretty-show process QuickCheck diff --git a/libs/saml2-web-sso/saml2-web-sso.cabal b/libs/saml2-web-sso/saml2-web-sso.cabal index da09daed9ed..ce29601401e 100644 --- a/libs/saml2-web-sso/saml2-web-sso.cabal +++ b/libs/saml2-web-sso/saml2-web-sso.cabal @@ -121,6 +121,7 @@ library , memory >=0.14.18 , mtl >=2.2.2 , network-uri >=2.6.1.0 + , openapi3 , pretty-show >=1.9.5 , process >=1.6.5.0 , QuickCheck >=2.13.2 diff --git a/libs/saml2-web-sso/src/SAML2/WebSSO/Orphans.hs b/libs/saml2-web-sso/src/SAML2/WebSSO/Orphans.hs index 63de8700733..a19e16c1117 100644 --- a/libs/saml2-web-sso/src/SAML2/WebSSO/Orphans.hs +++ b/libs/saml2-web-sso/src/SAML2/WebSSO/Orphans.hs @@ -11,10 +11,10 @@ import Data.Aeson import Data.ByteString import Data.ByteString.Builder import Data.Schema as Schema -import Data.String.Conversions import Data.Text (Text) import Data.Text qualified as Text import Data.Text.Encoding qualified as Text +import Data.Text.Lazy qualified as TL import Data.X509 as X509 import Data.Yaml.Aeson qualified as A import SAML2.Util (normURI, parseURI', renderURI) @@ -37,11 +37,18 @@ instance ToHttpApiData URI where instance FromHttpApiData URI where parseUrlPiece = either (Left . Text.pack) pure . parseURI' <=< parseUrlPiece -instance FromJSON X509.SignedCertificate where - parseJSON = withText "KeyInfo element" $ either fail pure . parseKeyInfo False . cs +instance Schema.ToSchema SignedCertificate where + schema = serialize Schema..= Schema.parsedText "SignedCertificate" parse + where + parse :: Text.Text -> Either String SignedCertificate + parse = parseKeyInfo False . TL.fromStrict + + serialize :: SignedCertificate -> Text.Text + serialize = TL.toStrict . renderKeyInfo + +deriving via (Schema.Schema SignedCertificate) instance FromJSON SignedCertificate -instance ToJSON X509.SignedCertificate where - toJSON = String . cs . renderKeyInfo +deriving via (Schema.Schema SignedCertificate) instance ToJSON SignedCertificate -- This can unfortunately not live in wire-api, because wire-api depends on -- saml2-web-sso. @@ -69,3 +76,14 @@ instance ToSchema Level where deriving instance Enum Level deriving instance Bounded Level + +-- | Used in tests to have no @extra@ in @IdPConfig extra@ +instance Schema.ToSchema () where + schema = Schema.named "unit" $ Schema.null_ + +-- | Used in tests to have JSON as @extra@ in @IdPConfig extra@ +instance Schema.ToSchema A.Value where + schema = + Schema.named (Text.pack "Value") $ + id + Schema..= Schema.jsonValue diff --git a/libs/saml2-web-sso/src/SAML2/WebSSO/Types.hs b/libs/saml2-web-sso/src/SAML2/WebSSO/Types.hs index 21c57322871..93039ca76d7 100644 --- a/libs/saml2-web-sso/src/SAML2/WebSSO/Types.hs +++ b/libs/saml2-web-sso/src/SAML2/WebSSO/Types.hs @@ -161,7 +161,6 @@ module SAML2.WebSSO.Types where import Control.Lens -import Control.Monad ((<=<)) import Control.Monad.Except import Data.Aeson import Data.Aeson.TH @@ -171,6 +170,7 @@ import Data.List qualified as L import Data.List.NonEmpty (NonEmpty ((:|))) import Data.List.NonEmpty qualified as NL import Data.Maybe +import Data.OpenApi qualified as S import Data.Schema qualified as Schema import Data.String.Conversions (ST, cs) import Data.Text (Text) @@ -230,14 +230,15 @@ data UserRef = UserRef {_uidTenant :: Issuer, _uidSubject :: NameID} -- | More correctly, an 'Issuer' is a 'NameID', but we only support 'URI'. newtype Issuer = Issuer {_fromIssuer :: URI} deriving (Eq, Ord, Show, Generic) + deriving (FromJSON, ToJSON, S.ToSchema) via Schema.Schema Issuer -instance FromJSON Issuer where - parseJSON = withText "Issuer" $ \uri -> case parseURI' uri of - Right i -> pure $ Issuer i - Left msg -> fail $ "Issuer: " <> show msg - -instance ToJSON Issuer where - toJSON = toJSON . renderURI . _fromIssuer +instance Schema.ToSchema Issuer where + schema = + Issuer + <$> _fromIssuer Schema..= uriSchema + where + uriSchema :: Schema.ValueSchema Schema.NamedSwaggerDoc URI + uriSchema = renderURI Schema..= Schema.parsedText "URI" parseURI' ---------------------------------------------------------------------- -- meta [4/2.3.2] @@ -307,11 +308,33 @@ data IdPMetadata = IdPMetadata _edCertAuthnResponse :: NonEmpty X509.SignedCertificate } deriving (Eq, Show, Generic) + deriving (FromJSON, ToJSON, S.ToSchema) via (Schema.Schema IdPMetadata) + +instance Schema.ToSchema IdPMetadata where + schema = + Schema.object "IdPMetadata" $ + IdPMetadata + <$> (_edIssuer Schema..= Schema.field "issuer" Schema.schema) + <*> (_edRequestURI Schema..= Schema.field "requestURI" Schema.schema) + <*> (_edCertAuthnResponse Schema..= Schema.field "certAuthnResponse" (Schema.nonEmptyArray Schema.schema)) ---------------------------------------------------------------------- -- idp info -newtype IdPId = IdPId {fromIdPId :: UUID} deriving (Eq, Show, Generic, Ord) +newtype IdPId = IdPId {fromIdPId :: UUID} + deriving (Eq, Show, Generic, Ord) + deriving (FromJSON, ToJSON, S.ToSchema) via Schema.Schema IdPId + +instance Schema.ToSchema IdPId where + schema = + IdPId + <$> fromIdPId Schema..= idpIdSchema + where + idpIdSchema :: Schema.ValueSchema Schema.NamedSwaggerDoc UUID + idpIdSchema = UUID.toText Schema..= Schema.parsedText "URI" parseUUID + + parseUUID :: Text -> Either String UUID + parseUUID = maybe (Left "Cannot parse UUID") Right . UUID.fromText type IdPConfig_ = IdPConfig () @@ -321,6 +344,15 @@ data IdPConfig extra = IdPConfig _idpExtraInfo :: extra } deriving (Eq, Show, Generic) + deriving (FromJSON, ToJSON, S.ToSchema) via (Schema.Schema (IdPConfig extra)) + +instance (Schema.ToSchema extra) => Schema.ToSchema (IdPConfig extra) where + schema = + Schema.object "IdPConfig" $ + IdPConfig + <$> (_idpId Schema..= Schema.field "id" Schema.schema) + <*> (_idpMetadata Schema..= Schema.field "metadata" Schema.schema) + <*> (_idpExtraInfo Schema..= Schema.field "extraInfo" Schema.schema) ---------------------------------------------------------------------- -- request, response @@ -721,18 +753,6 @@ makePrisms ''Statement makePrisms ''UnqualifiedNameID -deriveJSON deriveJSONOptions ''IdPMetadata - -deriveJSON deriveJSONOptions ''IdPConfig - -instance FromJSON IdPId where - parseJSON value = ((maybe unerror (pure . IdPId) . UUID.fromText) <=< parseJSON) value - where - unerror = fail ("could not parse config: " <> (show value)) - -instance ToJSON IdPId where - toJSON = toJSON . UUID.toText . fromIdPId - idPIdToST :: IdPId -> ST idPIdToST = UUID.toText . fromIdPId diff --git a/libs/saml2-web-sso/test/Test/SAML2/WebSSO/RoundtripSpec.hs b/libs/saml2-web-sso/test/Test/SAML2/WebSSO/RoundtripSpec.hs index a9aba125691..dce765a26a8 100644 --- a/libs/saml2-web-sso/test/Test/SAML2/WebSSO/RoundtripSpec.hs +++ b/libs/saml2-web-sso/test/Test/SAML2/WebSSO/RoundtripSpec.hs @@ -32,6 +32,7 @@ import Hedgehog import Hedgehog.Gen as Gen import SAML2.Core qualified as HS import SAML2.WebSSO +import SAML2.WebSSO.Orphans () import SAML2.WebSSO.Test.Arbitrary import SAML2.WebSSO.Test.Util import Servant diff --git a/libs/wire-api/src/Wire/API/Routes/Internal/Brig.hs b/libs/wire-api/src/Wire/API/Routes/Internal/Brig.hs index a4ecd447cd1..50421290da1 100644 --- a/libs/wire-api/src/Wire/API/Routes/Internal/Brig.hs +++ b/libs/wire-api/src/Wire/API/Routes/Internal/Brig.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE TemplateHaskell #-} + -- This file is part of the Wire Server implementation. -- -- Copyright (C) 2022 Wire Swiss GmbH @@ -43,10 +45,12 @@ module Wire.API.Routes.Internal.Brig module Wire.API.Routes.Internal.Brig.EJPD, FoundInvitationCode (..), EnterpriseLoginApi, + SAMLIdPAPI, + IdpChangedNotification (..), ) where -import Control.Lens ((.~), (?~)) +import Control.Lens (makePrisms, (.~), (?~), _1) import Data.Aeson (FromJSON, ToJSON, Value (Null)) import Data.Code qualified as Code import Data.CommaSeparatedList @@ -96,6 +100,8 @@ import Wire.API.User.Auth.LegalHold import Wire.API.User.Auth.ReAuth import Wire.API.User.Auth.Sso import Wire.API.User.Client +import Wire.API.User.IdentityProvider +import Wire.API.User.Orphans () import Wire.API.User.RichInfo import Wire.API.UserGroup import Wire.API.UserGroup.Pagination @@ -713,6 +719,18 @@ type API = :<|> FederationRemotesAPI :<|> ProviderAPI :<|> EnterpriseLoginApi + :<|> SAMLIdPAPI + ) + +type SAMLIdPAPI = + "idp" + :> ( Named + "send-idp-changed-email" + ( Summary "Send an email about IdP creation, deletion or update to all team admins and owners" + :> "send-idp-changed-email" + :> ReqBody '[Servant.JSON] IdpChangedNotification + :> Post '[Servant.JSON] () + ) ) type IStatusAPI = @@ -985,6 +1003,54 @@ instance S.ToSchema GetRichInfoMultiResponse where S.NamedSchema (Just $ "GetRichInfoMultiResponse") $ mempty & S.description ?~ "List of pairs of UserId and RichInfo" +data IdpChangedNotificationTag = IdPCreatedTag | IdPDeletedTag | IdPUpdatedTag + deriving (Eq, Enum, Bounded) + +data IdpChangedNotification = IdPCreated IdP | IdPDeleted IdP | IdPUpdated IdP IdP + deriving (Eq, Show, Generic) + +makePrisms ''IdpChangedNotification + +instance Data.Schema.ToSchema IdpChangedNotification where + schema = + object "IdpChangedNotification" $ + fromTagged + <$> toTagged + .= bind + (fst .= field "tag" tagSchema) + (snd .= fieldOver _1 "value" untaggedSchema) + where + toTagged :: IdpChangedNotification -> (IdpChangedNotificationTag, IdpChangedNotification) + toTagged d@(IdPCreated _) = (IdPCreatedTag, d) + toTagged d@(IdPDeleted _) = (IdPDeletedTag, d) + toTagged d@(IdPUpdated _ _) = (IdPUpdatedTag, d) + + fromTagged :: (IdpChangedNotificationTag, IdpChangedNotification) -> IdpChangedNotification + fromTagged = snd + + untaggedSchema = dispatch $ \case + IdPCreatedTag -> tag _IdPCreated (Data.Schema.unnamed schema) + IdPDeletedTag -> tag _IdPDeleted (Data.Schema.unnamed schema) + IdPUpdatedTag -> tag _IdPUpdated (Data.Schema.unnamed updatedSchema) + + tagSchema :: ValueSchema NamedSwaggerDoc IdpChangedNotificationTag + tagSchema = + enum @Text "Detail Tag" $ + mconcat [element "created" IdPCreatedTag, element "deleted" IdPDeletedTag, element "updated" IdPUpdatedTag] + + updatedSchema :: ValueSchema NamedSwaggerDoc (IdP, IdP) + updatedSchema = + object "IdPUpdated" $ + (,) + <$> fst .= field "old" schema + <*> snd .= field "new" schema + +deriving via (Schema IdpChangedNotification) instance FromJSON IdpChangedNotification + +deriving via (Schema IdpChangedNotification) instance ToJSON IdpChangedNotification + +deriving via (Schema IdpChangedNotification) instance S.ToSchema IdpChangedNotification + swaggerDoc :: OpenApi swaggerDoc = brigSwaggerDoc diff --git a/libs/wire-api/src/Wire/API/User/IdentityProvider.hs b/libs/wire-api/src/Wire/API/User/IdentityProvider.hs index 441d5dc1a3b..c65d4b66eeb 100644 --- a/libs/wire-api/src/Wire/API/User/IdentityProvider.hs +++ b/libs/wire-api/src/Wire/API/User/IdentityProvider.hs @@ -50,6 +50,7 @@ import Data.HashMap.Strict.InsOrd qualified as InsOrdHashMap import Data.Id (TeamId) import Data.OpenApi import Data.Proxy (Proxy (Proxy)) +import Data.Schema qualified as Schema import Data.Text.Encoding import Data.Text.Encoding.Error import Data.Text.Lazy qualified as LT @@ -58,10 +59,8 @@ import Network.HTTP.Media ((//)) import SAML2.WebSSO (IdPConfig) import SAML2.WebSSO qualified as SAML import SAML2.WebSSO.Test.Arbitrary () -import SAML2.WebSSO.Types.TH (deriveJSONOptions) import Servant.API as Servant hiding (MkLink, URI (..)) import Wire.API.Routes.Public (ZHostValue) -import Wire.API.User.Orphans (samlSchemaOptions) import Wire.API.Util.Aeson (defaultOptsDropChar) import Wire.Arbitrary (Arbitrary, GenericUniform (GenericUniform)) @@ -70,7 +69,7 @@ type IdP = IdPConfig WireIdP -- | Unique human-readable IdP name. newtype IdPHandle = IdPHandle {unIdPHandle :: Text} - deriving (Eq, Ord, Show, FromJSON, ToJSON, ToSchema, Arbitrary, Generic) + deriving (Eq, Ord, Show, FromJSON, ToJSON, ToSchema, Schema.ToSchema, Arbitrary, Generic) data WireIdP = WireIdP { _team :: TeamId, @@ -89,6 +88,19 @@ data WireIdP = WireIdP deriving (Eq, Show, Generic) deriving (Arbitrary) via (GenericUniform WireIdP) +instance Schema.ToSchema WireIdP where + schema = + Schema.object + "WireIdP" + ( WireIdP + <$> _team Schema..= Schema.field "team" Schema.schema + <*> _apiVersion Schema..= Schema.maybe_ (Schema.optField "apiVersion" Schema.schema) + <*> _oldIssuers Schema..= Schema.field "oldIssuers" (Schema.array Schema.schema) + <*> _replacedBy Schema..= Schema.maybe_ (Schema.optField "replacedBy" Schema.schema) + <*> _handle Schema..= Schema.field "handle" Schema.schema + <*> _domain Schema..= Schema.maybe_ (Schema.optField "domain" Schema.schema) + ) + data WireIdPAPIVersion = -- | initial API WireIdPAPIV1 @@ -96,6 +108,15 @@ data WireIdPAPIVersion WireIdPAPIV2 deriving stock (Eq, Show, Enum, Bounded, Generic) deriving (Arbitrary) via (GenericUniform WireIdPAPIVersion) + deriving (FromJSON, ToJSON, ToSchema) via (Schema.Schema WireIdPAPIVersion) + +instance Schema.ToSchema WireIdPAPIVersion where + schema = + Schema.enum @Text "WireIdPAPIVersion" $ + mconcat + [ Schema.element "v1" WireIdPAPIV1, + Schema.element "v2" WireIdPAPIV2 + ] -- | (Internal issue for making v2 the default: -- https://wearezeta.atlassian.net/browse/SQSERVICES-781. BEWARE: We probably shouldn't ever @@ -106,8 +127,6 @@ defWireIdPAPIVersion = WireIdPAPIV1 makeLenses ''WireIdP -deriveJSON deriveJSONOptions ''WireIdPAPIVersion - -- Changing the encoder since we've dropped the field prefixes deriveJSON (defaultOptsDropChar '_') ''WireIdP @@ -211,9 +230,6 @@ idPMetadataToInfo = instance ToSchema IdPList where declareNamedSchema = genericDeclareNamedSchema $ fromAesonOptions $ defaultOptsDropChar '_' -instance ToSchema WireIdPAPIVersion where - declareNamedSchema = genericDeclareNamedSchema samlSchemaOptions - instance ToSchema WireIdP where -- We don't want to use `samlSchemaOptions`, as it pulls from saml2-web-sso json options which -- as a `dropWhile not . isUpper` modifier. All we need is to drop the underscore prefix and diff --git a/libs/wire-api/src/Wire/API/User/Orphans.hs b/libs/wire-api/src/Wire/API/User/Orphans.hs index 794d4d36437..c3d44c7084e 100644 --- a/libs/wire-api/src/Wire/API/User/Orphans.hs +++ b/libs/wire-api/src/Wire/API/User/Orphans.hs @@ -118,15 +118,6 @@ instance O.ToSchema Void where instance (HasOpenApi route) => HasOpenApi (SM.MultipartForm SM.Mem resp :> route) where toOpenApi _proxy = toOpenApi (Proxy @route) -instance O.ToSchema SAML.IdPId where - declareNamedSchema _ = declareNamedSchema (Proxy @UUID) - -instance (O.ToSchema a) => O.ToSchema (SAML.IdPConfig a) where - declareNamedSchema = genericDeclareNamedSchema samlSchemaOptions - -instance O.ToSchema SAML.Issuer where - declareNamedSchema _ = declareNamedSchema (Proxy @String) - instance O.ToSchema URI where declareNamedSchema _ = declareNamedSchema (Proxy @String) @@ -136,9 +127,6 @@ instance O.ToParamSchema URI where instance O.ToSchema X509.SignedCertificate where declareNamedSchema _ = declareNamedSchema (Proxy @String) -instance O.ToSchema SAML.IdPMetadata where - declareNamedSchema = genericDeclareNamedSchema samlSchemaOptions - instance S.ToSchema Currency.Alpha where schema = S.enum @Text "Currency.Alpha" cases & S.doc' . O.schema %~ swaggerTweaks where diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem.hs index fa9f1bc7653..9047bacd807 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem.hs @@ -27,6 +27,7 @@ import Wire.API.Locale import Wire.API.User import Wire.API.User.Activation (ActivationCode, ActivationKey) import Wire.API.User.Client (Client (..)) +import Wire.API.User.IdentityProvider (IdP) data EmailSubsystem m a where SendPasswordResetMail :: EmailAddress -> PasswordResetPair -> Maybe Locale -> EmailSubsystem m () @@ -45,5 +46,8 @@ data EmailSubsystem m a where SendTeamInvitationMailPersonalUser :: EmailAddress -> TeamId -> EmailAddress -> InvitationCode -> Maybe Locale -> EmailSubsystem m Text SendMemberWelcomeEmail :: EmailAddress -> TeamId -> Text -> Maybe Locale -> EmailSubsystem m () SendNewTeamOwnerWelcomeEmail :: EmailAddress -> TeamId -> Text -> Maybe Locale -> Name -> EmailSubsystem m () + SendSAMLIdPCreated :: IdP -> EmailAddress -> EmailSubsystem m () + SendSAMLIdPDeleted :: IdP -> EmailAddress -> EmailSubsystem m () + SendSAMLIdPUpdated :: IdP -> IdP -> EmailAddress -> EmailSubsystem m () makeSem ''EmailSubsystem diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs index 3225190c16a..ef82c4df5b9 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs @@ -37,6 +37,7 @@ import Wire.API.Locale import Wire.API.User import Wire.API.User.Activation import Wire.API.User.Client (Client (..)) +import Wire.API.User.IdentityProvider (IdP) import Wire.API.User.Password import Wire.EmailSending (EmailSending, sendMail) import Wire.EmailSubsystem @@ -67,6 +68,19 @@ emailSubsystemInterpreter userTpls teamTpls branding = interpret \case SendTeamInvitationMailPersonalUser email tid from code loc -> sendTeamInvitationMailPersonalUserImpl teamTpls branding email tid from code loc SendMemberWelcomeEmail email tid teamName loc -> sendMemberWelcomeEmailImpl teamTpls branding email tid teamName loc SendNewTeamOwnerWelcomeEmail email tid teamName loc name -> sendNewTeamOwnerWelcomeEmailImpl teamTpls branding email tid teamName loc name + SendSAMLIdPCreated idp email -> sendSAMLIdPCreatedImpl idp email + SendSAMLIdPDeleted idp email -> sendSAMLIdPDeletedImpl idp email + SendSAMLIdPUpdated old new email -> sendSAMLIdPUpdatedImpl old new email + +-- TODO: Move these functions down in this file. +sendSAMLIdPUpdatedImpl :: IdP -> IdP -> EmailAddress -> Sem r () +sendSAMLIdPUpdatedImpl = todo + +sendSAMLIdPCreatedImpl :: IdP -> EmailAddress -> Sem r () +sendSAMLIdPCreatedImpl = todo + +sendSAMLIdPDeletedImpl :: IdP -> EmailAddress -> Sem r () +sendSAMLIdPDeletedImpl = todo ------------------------------------------------------------------------------- -- Verification Email for diff --git a/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem.hs b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem.hs new file mode 100644 index 00000000000..7204b12ccfa --- /dev/null +++ b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE TemplateHaskell #-} + +module Wire.SAMLEmailSubsystem where + +import Polysemy +import Wire.API.Routes.Internal.Brig (IdpChangedNotification) + +data SAMLEmailSubsystem m a where + SendSAMLIdPChanged :: IdpChangedNotification -> SAMLEmailSubsystem m () + +makeSem ''SAMLEmailSubsystem diff --git a/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs new file mode 100644 index 00000000000..5885481d6bd --- /dev/null +++ b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs @@ -0,0 +1,60 @@ +module Wire.SAMLEmailSubsystem.Interpreter + ( samlEmailSubsystemInterpreter, + ) +where + +import Control.Lens ((^.), (^..)) +import Imports +import Polysemy +import SAML2.WebSSO.Types +import Text.Email.Parser +import Wire.API.Routes.Internal.Brig +import Wire.API.Team.Member +import Wire.API.User.IdentityProvider +import Wire.EmailSubsystem qualified as Email +import Wire.SAMLEmailSubsystem +import Wire.TeamSubsystem +import Wire.UserStore + +samlEmailSubsystemInterpreter :: + ( Member TeamSubsystem r, + Member UserStore r, + Member Email.EmailSubsystem r + ) => + InterpreterFor SAMLEmailSubsystem r +samlEmailSubsystemInterpreter = interpret \case + SendSAMLIdPChanged idp -> sendSAMLIdPChangedImpl idp + +sendSAMLIdPChangedImpl :: + ( Member TeamSubsystem r, + Member UserStore r, + Member Email.EmailSubsystem r + ) => + IdpChangedNotification -> + Sem r () +sendSAMLIdPChangedImpl notif = do + emails <- getEmailAddresses origIdP + mapM_ delegate emails + where + delegate :: (Member Email.EmailSubsystem r) => EmailAddress -> Sem r () + delegate email = case notif of + IdPCreated idp -> Email.sendSAMLIdPCreated idp email + IdPDeleted idp -> Email.sendSAMLIdPDeleted idp email + IdPUpdated old new -> Email.sendSAMLIdPUpdated old new email + + origIdP :: IdP + origIdP = case notif of + IdPCreated idp -> idp + IdPDeleted idp -> idp + IdPUpdated old _new -> old + +getEmailAddresses :: + ( Member TeamSubsystem r, + Member UserStore r + ) => + IdP -> + Sem r [EmailAddress] +getEmailAddresses idp = do + admins <- internalGetTeamAdmins (idp ^. idpExtraInfo . team) + let adminUids = admins ^.. teamMembers . traverse . userId + getEmails adminUids diff --git a/libs/wire-subsystems/src/Wire/UserStore.hs b/libs/wire-subsystems/src/Wire/UserStore.hs index a7bc2e9fcdb..7eef7618280 100644 --- a/libs/wire-subsystems/src/Wire/UserStore.hs +++ b/libs/wire-subsystems/src/Wire/UserStore.hs @@ -114,6 +114,7 @@ data UserStore m a where DeleteServiceUser :: ProviderId -> ServiceId -> BotId -> UserStore m () LookupServiceUsers :: ProviderId -> ServiceId -> Maybe PagingState -> UserStore m (PageWithState (BotId, ConvId, Maybe TeamId)) LookupServiceUsersForTeam :: ProviderId -> ServiceId -> TeamId -> Maybe PagingState -> UserStore m (PageWithState (BotId, ConvId)) + GetEmails :: [UserId] -> UserStore m [EmailAddress] makeSem ''UserStore diff --git a/libs/wire-subsystems/src/Wire/UserStore/Cassandra.hs b/libs/wire-subsystems/src/Wire/UserStore/Cassandra.hs index 7a854c4ce23..2e6662cef6d 100644 --- a/libs/wire-subsystems/src/Wire/UserStore/Cassandra.hs +++ b/libs/wire-subsystems/src/Wire/UserStore/Cassandra.hs @@ -79,6 +79,15 @@ interpretUserStoreCassandra casClient = DeleteServiceUser pid sid bid -> deleteServiceUserImpl pid sid bid LookupServiceUsers pid sid mPagingState -> lookupServiceUsersImpl pid sid mPagingState LookupServiceUsersForTeam pid sid tid mPagingState -> lookupServiceUsersForTeamImpl pid sid tid mPagingState + GetEmails uids -> getEmailsImpl uids + +getEmailsImpl :: [UserId] -> Client [EmailAddress] +getEmailsImpl uids = + map runIdentity + <$> retry x1 (query selectEmailAddresses (params LocalQuorum (Identity uids))) + where + selectEmailAddresses :: PrepQuery R (Identity [UserId]) (Identity EmailAddress) + selectEmailAddresses = "SELECT email FROM user WHERE id IN ?" createUserImpl :: NewStoredUser -> Maybe (ConvId, Maybe TeamId) -> Client () createUserImpl new mbConv = retry x5 . batch $ do diff --git a/libs/wire-subsystems/wire-subsystems.cabal b/libs/wire-subsystems/wire-subsystems.cabal index 000f00229ed..e7cf35b3b03 100644 --- a/libs/wire-subsystems/wire-subsystems.cabal +++ b/libs/wire-subsystems/wire-subsystems.cabal @@ -317,6 +317,8 @@ library Wire.RateLimit Wire.RateLimit.Interpreter Wire.Rpc + Wire.SAMLEmailSubsystem + Wire.SAMLEmailSubsystem.Interpreter Wire.ScimSubsystem Wire.ScimSubsystem.Error Wire.ScimSubsystem.Interpreter diff --git a/services/brig/src/Brig/API/Internal.hs b/services/brig/src/Brig/API/Internal.hs index f025c414859..53a74652d96 100644 --- a/services/brig/src/Brig/API/Internal.hs +++ b/services/brig/src/Brig/API/Internal.hs @@ -122,6 +122,7 @@ import Wire.PasswordResetCodeStore (PasswordResetCodeStore) import Wire.PropertySubsystem import Wire.RateLimit import Wire.Rpc +import Wire.SAMLEmailSubsystem (SAMLEmailSubsystem, sendSAMLIdPChanged) import Wire.Sem.Concurrency import Wire.Sem.Now (Now) import Wire.Sem.Random (Random) @@ -180,7 +181,8 @@ servantSitemap :: Member (Input AuthenticationSubsystemConfig) r, Member Now r, Member CryptoSign r, - Member Random r + Member Random r, + Member SAMLEmailSubsystem r ) => ServerT BrigIRoutes.API (Handler r) servantSitemap = @@ -198,6 +200,7 @@ servantSitemap = :<|> federationRemotesAPI :<|> Provider.internalProviderAPI :<|> enterpriseLoginApi + :<|> samlIdPApi istatusAPI :: forall r. ServerT BrigIRoutes.IStatusAPI (Handler r) istatusAPI = Named @"get-status" (pure NoContent) @@ -517,6 +520,9 @@ enterpriseLoginApi = :<|> Named @"domain-registration-delete" (fmap (const NoContent) . lift . liftSem . deleteDomain) :<|> Named @"domain-registration-get" getDomainRegistrationH +samlIdPApi :: (Member SAMLEmailSubsystem r) => ServerT SAMLIdPAPI (Handler r) +samlIdPApi = Named @"send-idp-changed-email" (lift . liftSem . sendSAMLIdPChanged) + --------------------------------------------------------------------------- -- Handlers diff --git a/services/brig/src/Brig/CanonicalInterpreter.hs b/services/brig/src/Brig/CanonicalInterpreter.hs index 727526a406b..1ebea4fe9d1 100644 --- a/services/brig/src/Brig/CanonicalInterpreter.hs +++ b/services/brig/src/Brig/CanonicalInterpreter.hs @@ -109,6 +109,8 @@ import Wire.PropertySubsystem.Interpreter import Wire.RateLimit import Wire.RateLimit.Interpreter import Wire.Rpc +import Wire.SAMLEmailSubsystem +import Wire.SAMLEmailSubsystem.Interpreter import Wire.Sem.Concurrency import Wire.Sem.Concurrency.IO import Wire.Sem.Delay @@ -163,7 +165,8 @@ type BrigCanonicalEffects = -- | These effects have interpreters which don't depend on each other type BrigLowerLevelEffects = - '[ TeamSubsystem, + '[ SAMLEmailSubsystem, + TeamSubsystem, TeamCollaboratorsStore, AppStore, EmailSubsystem, @@ -393,6 +396,7 @@ runBrigToIO e (AppT ma) = do . interpretAppStoreToPostgres . interpretTeamCollaboratorsStoreToPostgres . interpretTeamSubsystemToGalleyAPI + . samlEmailSubsystemInterpreter . interpretTeamCollaboratorsSubsystem . userSubsystemInterpreter . interpretUserGroupSubsystem diff --git a/services/spar/src/Spar/API.hs b/services/spar/src/Spar/API.hs index f36f6f80660..58028e759e2 100644 --- a/services/spar/src/Spar/API.hs +++ b/services/spar/src/Spar/API.hs @@ -121,6 +121,7 @@ import qualified Spar.Sem.VerdictFormatStore as VerdictFormatStore import System.Logger (Msg) import qualified System.Logger as Log import qualified URI.ByteString as URI +import Wire.API.Routes.Internal.Brig (IdpChangedNotification (IdPCreated, IdPDeleted, IdPUpdated)) import Wire.API.Routes.Internal.Spar import Wire.API.Routes.Named import Wire.API.Routes.Public (ZHostValue) @@ -587,6 +588,7 @@ idpDelete mbzusr idpid (fromMaybe False -> purge) = withDebugLog "idpDelete" (co do IdPConfigStore.deleteConfig idp IdPRawMetadataStore.delete idpid + BrigAccess.sendSAMLIdPChangedEmail $ IdPDeleted idp logIdPAction "IdP deleted" idp @@ -673,6 +675,7 @@ idpCreate samlConfig tid zUser uncheckedMbHost (IdPMetadataValue rawIdpMetadata IdPConfigStore.insertConfig idp forM_ mReplaces $ \replaces -> IdPConfigStore.setReplacedBy (Replaced replaces) (Replacing (idp ^. SAML.idpId)) + BrigAccess.sendSAMLIdPChangedEmail $ IdPCreated idp logIdPAction "IdP created" idp @@ -872,6 +875,7 @@ idpUpdateXML zusr mDomain raw idpmeta idpid mHandle = withDebugLog "idpUpdateXML WireIdPAPIV1 -> Nothing WireIdPAPIV2 -> Just teamid forM_ (idp'' ^. SAML.idpExtraInfo . oldIssuers) (flip IdPConfigStore.deleteIssuer mbteamid) + BrigAccess.sendSAMLIdPChangedEmail $ IdPUpdated previousIdP idp'' logIdPUpdate idp'' previousIdP pure idp'' where diff --git a/services/spar/src/Spar/Intra/Brig.hs b/services/spar/src/Spar/Intra/Brig.hs index fee2e54616f..1f52cc05cdb 100644 --- a/services/spar/src/Spar/Intra/Brig.hs +++ b/services/spar/src/Spar/Intra/Brig.hs @@ -43,6 +43,7 @@ module Spar.Intra.Brig setStatus, getDefaultUserLocale, checkAdminGetTeamId, + sendSAMLIdPChangedEmail, ) where @@ -64,6 +65,7 @@ import Spar.Error import qualified System.Logger.Class as Log import Web.Cookie import Wire.API.Locale +import Wire.API.Routes.Internal.Brig (IdpChangedNotification) import Wire.API.Team.Role (Role) import Wire.API.User import Wire.API.User.Auth.ReAuth @@ -453,3 +455,9 @@ checkAdminGetTeamId uid = do case statusCode resp of 200 -> parseResponse @TeamId "brig" resp _ -> rethrow "brig" resp + +sendSAMLIdPChangedEmail :: (HasCallStack, MonadSparToBrig m) => IdpChangedNotification -> m () +sendSAMLIdPChangedEmail notif = do + resp <- call $ method POST . path "/i/idp/send-idp-changed-email" . json notif + unless (statusCode resp == 200) $ + rethrow "brig" resp diff --git a/services/spar/src/Spar/Sem/BrigAccess.hs b/services/spar/src/Spar/Sem/BrigAccess.hs index 85307863593..1d82622eecd 100644 --- a/services/spar/src/Spar/Sem/BrigAccess.hs +++ b/services/spar/src/Spar/Sem/BrigAccess.hs @@ -41,6 +41,7 @@ module Spar.Sem.BrigAccess setStatus, getDefaultUserLocale, checkAdminGetTeamId, + sendSAMLIdPChangedEmail, ) where @@ -55,6 +56,7 @@ import Polysemy import qualified SAML2.WebSSO as SAML import Web.Cookie import Wire.API.Locale +import Wire.API.Routes.Internal.Brig (IdpChangedNotification) import Wire.API.Team.Role import Wire.API.User import Wire.API.User.RichInfo as RichInfo @@ -82,5 +84,6 @@ data BrigAccess m a where SetStatus :: UserId -> AccountStatus -> BrigAccess m () GetDefaultUserLocale :: BrigAccess m Locale CheckAdminGetTeamId :: UserId -> BrigAccess m TeamId + SendSAMLIdPChangedEmail :: IdpChangedNotification -> BrigAccess m () makeSem ''BrigAccess diff --git a/services/spar/src/Spar/Sem/BrigAccess/Http.hs b/services/spar/src/Spar/Sem/BrigAccess/Http.hs index b3623597d39..b2f8adaaf66 100644 --- a/services/spar/src/Spar/Sem/BrigAccess/Http.hs +++ b/services/spar/src/Spar/Sem/BrigAccess/Http.hs @@ -65,3 +65,4 @@ brigAccessToHttp mgr req = SetStatus itlu a -> Intra.setStatus itlu a GetDefaultUserLocale -> Intra.getDefaultUserLocale CheckAdminGetTeamId itlu -> Intra.checkAdminGetTeamId itlu + SendSAMLIdPChangedEmail notif -> Intra.sendSAMLIdPChangedEmail notif From bc79be25ca4eb7ef93d6cc1fb53d82411045b091 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 21 Jan 2026 15:02:16 +0100 Subject: [PATCH 02/60] Add missing case to mock --- services/spar/test/Test/Spar/Saml/IdPSpec.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/services/spar/test/Test/Spar/Saml/IdPSpec.hs b/services/spar/test/Test/Spar/Saml/IdPSpec.hs index ac0c67cf8e7..8ccd38eeff4 100644 --- a/services/spar/test/Test/Spar/Saml/IdPSpec.hs +++ b/services/spar/test/Test/Spar/Saml/IdPSpec.hs @@ -454,6 +454,7 @@ brigAccessMock mbAccount = interpret $ \case SetStatus _userId _status -> undefined GetDefaultUserLocale -> undefined CheckAdminGetTeamId _userId -> undefined + SendSAMLIdPChangedEmail _notif -> pure () ignoringState :: (Functor f) => (a -> f (c, b)) -> a -> f b ignoringState f = fmap snd . f From f66a2cb641dfdc4dc15ba9ef5dec43cff472418f Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 21 Jan 2026 15:19:32 +0100 Subject: [PATCH 03/60] Prepare to assert notifications --- services/spar/test/Test/Spar/Saml/IdPSpec.hs | 78 ++++++++++---------- 1 file changed, 41 insertions(+), 37 deletions(-) diff --git a/services/spar/test/Test/Spar/Saml/IdPSpec.hs b/services/spar/test/Test/Spar/Saml/IdPSpec.hs index 8ccd38eeff4..dc2c0f6106a 100644 --- a/services/spar/test/Test/Spar/Saml/IdPSpec.hs +++ b/services/spar/test/Test/Spar/Saml/IdPSpec.hs @@ -12,6 +12,7 @@ import qualified Data.Text.Lazy.IO as TL import Imports import Polysemy import qualified Polysemy.Error +import Polysemy.State import Polysemy.TinyLog import SAML2.WebSSO import qualified SAML2.WebSSO as SAML @@ -35,6 +36,7 @@ import Test.QuickCheck import qualified Text.XML.DSig as DSig import URI.ByteString (parseURI, strictURIParserOptions) import URI.ByteString.QQ (uri) +import Wire.API.Routes.Internal.Brig (IdpChangedNotification) import Wire.API.User (User (..)) import Wire.API.User.IdentityProvider (IdPMetadataInfo (..), WireIdPAPIVersion (..)) import Wire.Sem.Logger.TinyLog (LogRecorder (..), newLogRecorder, recordLogs) @@ -123,13 +125,13 @@ spec = ) forM_ [(minBound :: WireIdPAPIVersion) .. maxBound] $ \apiVersion -> do - (logs, _res) <- + (logs, _notifs, _res) <- interpretWithLoggingMock Nothing (idpCreate singleIngressSamlConfig tid zUser host idPMetadataInfo' Nothing (Just apiVersion) idpHandle) logs `shouldContain` [expectedLogLine] - (logsV7, _res) <- + (logsV7, _notifs, _res) <- interpretWithLoggingMock Nothing (idpCreateV7 singleIngressSamlConfig tid zUser idPMetadataInfo' Nothing (Just apiVersion) idpHandle) @@ -167,7 +169,7 @@ spec = expectedLogLineWithoutDomain = expectedLogLine "None" forM_ [(minBound :: WireIdPAPIVersion) .. maxBound] $ \apiVersion -> do - (logs, _res) <- + (logs, _notifs, _res) <- interpretWithLoggingMock Nothing (idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing (Just apiVersion) idpHandle) @@ -175,7 +177,7 @@ spec = -- >=V7 does not bother with multi-ingress domains for IdPs as it can -- only have one IdP per team anyways. - (logsV7, _res) <- + (logsV7, _notifs, _res) <- interpretWithLoggingMock Nothing (idpCreateV7 multiIngressSamlConfig tid zUser idPMetadataInfo' Nothing (Just apiVersion) idpHandle) @@ -208,7 +210,7 @@ spec = <> "\n" ) - (logs, _res) <- interpretWithLoggingMock (Just user) $ do + (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do idp <- idpCreate singleIngressSamlConfig tid zUser host idPMetadataInfo' Nothing apiVersionV2 idpHandle idpDelete zUser (idp._idpId) Nothing logs `shouldContain` [expectedLogLine] @@ -241,7 +243,7 @@ spec = <> "\n" ) - (logs, _res) <- interpretWithLoggingMock (Just user) $ do + (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing apiVersionV2 idpHandle idpDelete zUser (idp._idpId) Nothing logs `shouldContain` [expectedLogLine] @@ -273,7 +275,7 @@ spec = <> "\n" ) - (logs, _res) <- interpretWithLoggingMock (Just user) $ do + (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do idp <- idpCreate singleIngressSamlConfig tid zUser host idPMetadataInfo' Nothing apiVersionV2 idpHandle idpUpdate singleIngressSamlConfig zUser host idPMetadataInfo' (idp._idpId) Nothing logs `shouldContain` [expectedLogLine] @@ -306,7 +308,7 @@ spec = <> "\n" ) - (logs, _res) <- interpretWithLoggingMock (Just user) $ do + (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing apiVersionV2 idpHandle idpUpdate multiIngressSamlConfig zUser miHost1 idPMetadataInfo' (idp._idpId) Nothing logs `shouldContain` [expectedLogLine] @@ -341,7 +343,7 @@ spec = <> "\n" ) - (logs, _res) <- interpretWithLoggingMock (Just user) $ do + (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing apiVersionV2 idpHandle idpUpdate multiIngressSamlConfig zUser miHost2 idPMetadataInfo' (idp._idpId) Nothing logs `shouldContain` [expectedLogLine] @@ -392,7 +394,7 @@ spec = <> "\n" ) - (logs, _res) <- interpretWithLoggingMock (Just user) $ do + (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do idp <- idpCreate singleIngressSamlConfig tid zUser host idPMetadataInfo' Nothing apiVersionV2 idpHandle idpUpdate singleIngressSamlConfig zUser host idPMetadataInfo'' (idp._idpId) Nothing logs `shouldContain` [expectedLogLine] @@ -402,7 +404,7 @@ type LogLine = (Level, LByteString) interpretWithLoggingMock :: Maybe User -> Sem (Effs) a -> - IO ([LogLine], a) + IO ([LogLine], [IdpChangedNotification], a) interpretWithLoggingMock mbAccount action = do lr <- newLogRecorder a <- @@ -419,7 +421,8 @@ interpretWithLoggingMock mbAccount action = do . randomToNull $ action logs <- readIORef lr.recordedLogs - pure (logs, either (error . show) id a) + let (notifs, res) = either (error . show) id a + pure (logs, notifs, res) galleyAccessMock :: Sem (GalleyAccess ': r) a -> Sem r a galleyAccessMock = interpret $ \case @@ -430,31 +433,32 @@ galleyAccessMock = interpret $ \case IsEmailValidationEnabledTeam _teamId -> undefined UpdateTeamMember _userId _teamId _role -> undefined -brigAccessMock :: Maybe User -> Sem (BrigAccess ': r) a -> Sem r a -brigAccessMock mbAccount = interpret $ \case - CreateSAML _userRef _userId _teamId _name _managedBy _mHandle _mRichInfo _mLocale _role -> undefined - CreateNoSAML _txt _email _userId _teamId _name _mLocale _role -> undefined - UpdateEmail _userId _email _activation -> undefined - GetAccount _havePendingInvitations _userId -> pure mbAccount - GetByHandle _handle -> undefined - GetByEmail _email -> undefined - SetName _userId _name -> undefined - SetHandle _userId _handle -> undefined - SetManagedBy _userId _managedBy -> undefined - SetSSOId _userId _ssoId -> undefined - SetRichInfo _userId _richInfo -> undefined - SetLocale _userId _mLocale -> undefined - GetRichInfo _userId -> undefined - CheckHandleAvailable _handle -> undefined - DeleteUser _userId -> undefined - EnsureReAuthorised _mUserId _mPassword _mCode _mAction -> undefined - SsoLogin _userId -> undefined - GetStatus _userId -> undefined - GetStatusMaybe _userId -> undefined - SetStatus _userId _status -> undefined - GetDefaultUserLocale -> undefined - CheckAdminGetTeamId _userId -> undefined - SendSAMLIdPChangedEmail _notif -> pure () +brigAccessMock :: Maybe User -> Sem (BrigAccess ': r) a -> Sem r ([IdpChangedNotification], a) +brigAccessMock mbAccount = (runState @([IdpChangedNotification]) mempty .) $ + reinterpret $ \case + CreateSAML _userRef _userId _teamId _name _managedBy _mHandle _mRichInfo _mLocale _role -> undefined + CreateNoSAML _txt _email _userId _teamId _name _mLocale _role -> undefined + UpdateEmail _userId _email _activation -> undefined + GetAccount _havePendingInvitations _userId -> pure mbAccount + GetByHandle _handle -> undefined + GetByEmail _email -> undefined + SetName _userId _name -> undefined + SetHandle _userId _handle -> undefined + SetManagedBy _userId _managedBy -> undefined + SetSSOId _userId _ssoId -> undefined + SetRichInfo _userId _richInfo -> undefined + SetLocale _userId _mLocale -> undefined + GetRichInfo _userId -> undefined + CheckHandleAvailable _handle -> undefined + DeleteUser _userId -> undefined + EnsureReAuthorised _mUserId _mPassword _mCode _mAction -> undefined + SsoLogin _userId -> undefined + GetStatus _userId -> undefined + GetStatusMaybe _userId -> undefined + SetStatus _userId _status -> undefined + GetDefaultUserLocale -> undefined + CheckAdminGetTeamId _userId -> undefined + SendSAMLIdPChangedEmail notif -> modify (notif :) ignoringState :: (Functor f) => (a -> f (c, b)) -> a -> f b ignoringState f = fmap snd . f From 7baf06e8647fd2c5c2726bf5cc3d7011495d313a Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 21 Jan 2026 15:32:07 +0100 Subject: [PATCH 04/60] Add test for mi idpCreate --- services/spar/test/Test/Spar/Saml/IdPSpec.hs | 630 ++++++++++--------- 1 file changed, 329 insertions(+), 301 deletions(-) diff --git a/services/spar/test/Test/Spar/Saml/IdPSpec.hs b/services/spar/test/Test/Spar/Saml/IdPSpec.hs index dc2c0f6106a..c75a748768e 100644 --- a/services/spar/test/Test/Spar/Saml/IdPSpec.hs +++ b/services/spar/test/Test/Spar/Saml/IdPSpec.hs @@ -36,7 +36,7 @@ import Test.QuickCheck import qualified Text.XML.DSig as DSig import URI.ByteString (parseURI, strictURIParserOptions) import URI.ByteString.QQ (uri) -import Wire.API.Routes.Internal.Brig (IdpChangedNotification) +import Wire.API.Routes.Internal.Brig (IdpChangedNotification (..)) import Wire.API.User (User (..)) import Wire.API.User.IdentityProvider (IdPMetadataInfo (..), WireIdPAPIVersion (..)) import Wire.Sem.Logger.TinyLog (LogRecorder (..), newLogRecorder, recordLogs) @@ -96,308 +96,336 @@ spec = . parseURI strictURIParserOptions . fromString $ idpEndpointString - in describe "SAML IdP change logging" $ do - describe "idp-create" $ do - it "should log IdP creation" $ do - idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary - let idPMetadataInfo' = - idPMetadataInfo - { _idpMetadataRecord = - (idPMetadataInfo._idpMetadataRecord) - { SAML._edIssuer = issuer, - SAML._edRequestURI = idpEndpoint - } - } - - expectedLogLine = - ( Info, - "IdP created, team=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid - <> ", idpId=00000000-0000-0000-0000-000000000000, issuer=" - <> fromString issuerString - <> ", domain=None, user=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser - <> ", certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" - <> ", idp-endpoint=" - <> fromString idpEndpointString - <> ", replaces=None" - <> "\n" - ) - - forM_ [(minBound :: WireIdPAPIVersion) .. maxBound] $ \apiVersion -> do - (logs, _notifs, _res) <- - interpretWithLoggingMock - Nothing - (idpCreate singleIngressSamlConfig tid zUser host idPMetadataInfo' Nothing (Just apiVersion) idpHandle) + in do + describe "SAML IdP change logging" $ do + describe "idp-create" $ do + it "should log IdP creation" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + let idPMetadataInfo' = + idPMetadataInfo + { _idpMetadataRecord = + (idPMetadataInfo._idpMetadataRecord) + { SAML._edIssuer = issuer, + SAML._edRequestURI = idpEndpoint + } + } + + expectedLogLine = + ( Info, + "IdP created, team=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid + <> ", idpId=00000000-0000-0000-0000-000000000000, issuer=" + <> fromString issuerString + <> ", domain=None, user=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser + <> ", certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" + <> ", idp-endpoint=" + <> fromString idpEndpointString + <> ", replaces=None" + <> "\n" + ) + + forM_ [(minBound :: WireIdPAPIVersion) .. maxBound] $ \apiVersion -> do + (logs, _notifs, _res) <- + interpretWithLoggingMock + Nothing + (idpCreate singleIngressSamlConfig tid zUser host idPMetadataInfo' Nothing (Just apiVersion) idpHandle) + logs `shouldContain` [expectedLogLine] + + (logsV7, _notifs, _res) <- + interpretWithLoggingMock + Nothing + (idpCreateV7 singleIngressSamlConfig tid zUser idPMetadataInfo' Nothing (Just apiVersion) idpHandle) + logsV7 `shouldContain` [expectedLogLine] + + it "should log IdP creation with domain for multi-ingress" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + let idPMetadataInfo' = + idPMetadataInfo + { _idpMetadataRecord = + (idPMetadataInfo._idpMetadataRecord) + { SAML._edIssuer = issuer, + SAML._edRequestURI = idpEndpoint + } + } + + expectedLogLine :: LByteString -> LogLine + expectedLogLine domainPart = + ( Info, + "IdP created, team=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid + <> ", idpId=00000000-0000-0000-0000-000000000000, issuer=" + <> fromString issuerString + <> ", domain=" + <> domainPart + <> ", user=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser + <> ", certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" + <> ", idp-endpoint=" + <> fromString idpEndpointString + <> ", replaces=None" + <> "\n" + ) + expectedLogLineWithDomain = expectedLogLine . TL.encodeUtf8 . TL.fromStrict $ miHost1AsText + expectedLogLineWithoutDomain = expectedLogLine "None" + + forM_ [(minBound :: WireIdPAPIVersion) .. maxBound] $ \apiVersion -> do + (logs, _notifs, _res) <- + interpretWithLoggingMock + Nothing + (idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing (Just apiVersion) idpHandle) + logs `shouldContain` [expectedLogLineWithDomain] + + -- >=V7 does not bother with multi-ingress domains for IdPs as it can + -- only have one IdP per team anyways. + (logsV7, _notifs, _res) <- + interpretWithLoggingMock + Nothing + (idpCreateV7 multiIngressSamlConfig tid zUser idPMetadataInfo' Nothing (Just apiVersion) idpHandle) + logsV7 `shouldContain` [expectedLogLineWithoutDomain] + + describe "idp-delete" $ do + it "should log IdP deletion" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + user :: User <- generate arbitrary + let idPMetadataInfo' = + idPMetadataInfo + { _idpMetadataRecord = + (idPMetadataInfo._idpMetadataRecord) + { SAML._edIssuer = issuer, + SAML._edRequestURI = idpEndpoint + } + } + + expectedLogLine = + ( Info, + "IdP deleted, team=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid + <> ", idpId=00000000-0000-0000-0000-000000000000, issuer=" + <> fromString issuerString + <> ", domain=None, user=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser + <> ", certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" + <> ", idp-endpoint=" + <> fromString idpEndpointString + <> "\n" + ) + + (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do + idp <- idpCreate singleIngressSamlConfig tid zUser host idPMetadataInfo' Nothing apiVersionV2 idpHandle + idpDelete zUser (idp._idpId) Nothing logs `shouldContain` [expectedLogLine] - (logsV7, _notifs, _res) <- - interpretWithLoggingMock - Nothing - (idpCreateV7 singleIngressSamlConfig tid zUser idPMetadataInfo' Nothing (Just apiVersion) idpHandle) - logsV7 `shouldContain` [expectedLogLine] - - it "should log IdP creation with domain for multi-ingress" $ do - idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary - let idPMetadataInfo' = - idPMetadataInfo - { _idpMetadataRecord = - (idPMetadataInfo._idpMetadataRecord) - { SAML._edIssuer = issuer, - SAML._edRequestURI = idpEndpoint - } - } - - expectedLogLine :: LByteString -> LogLine - expectedLogLine domainPart = - ( Info, - "IdP created, team=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid - <> ", idpId=00000000-0000-0000-0000-000000000000, issuer=" - <> fromString issuerString - <> ", domain=" - <> domainPart - <> ", user=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser - <> ", certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" - <> ", idp-endpoint=" - <> fromString idpEndpointString - <> ", replaces=None" - <> "\n" - ) - expectedLogLineWithDomain = expectedLogLine . TL.encodeUtf8 . TL.fromStrict $ miHost1AsText - expectedLogLineWithoutDomain = expectedLogLine "None" - - forM_ [(minBound :: WireIdPAPIVersion) .. maxBound] $ \apiVersion -> do - (logs, _notifs, _res) <- - interpretWithLoggingMock - Nothing - (idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing (Just apiVersion) idpHandle) - logs `shouldContain` [expectedLogLineWithDomain] - - -- >=V7 does not bother with multi-ingress domains for IdPs as it can - -- only have one IdP per team anyways. - (logsV7, _notifs, _res) <- - interpretWithLoggingMock - Nothing - (idpCreateV7 multiIngressSamlConfig tid zUser idPMetadataInfo' Nothing (Just apiVersion) idpHandle) - logsV7 `shouldContain` [expectedLogLineWithoutDomain] - - describe "idp-delete" $ do - it "should log IdP deletion" $ do - idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary - user :: User <- generate arbitrary - let idPMetadataInfo' = - idPMetadataInfo - { _idpMetadataRecord = - (idPMetadataInfo._idpMetadataRecord) - { SAML._edIssuer = issuer, - SAML._edRequestURI = idpEndpoint - } - } - - expectedLogLine = - ( Info, - "IdP deleted, team=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid - <> ", idpId=00000000-0000-0000-0000-000000000000, issuer=" - <> fromString issuerString - <> ", domain=None, user=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser - <> ", certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" - <> ", idp-endpoint=" - <> fromString idpEndpointString - <> "\n" - ) - - (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do - idp <- idpCreate singleIngressSamlConfig tid zUser host idPMetadataInfo' Nothing apiVersionV2 idpHandle - idpDelete zUser (idp._idpId) Nothing - logs `shouldContain` [expectedLogLine] - - it "should log IdP deletion with domain for multi-ingress" $ do - idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary - user :: User <- generate arbitrary - let idPMetadataInfo' = - idPMetadataInfo - { _idpMetadataRecord = - (idPMetadataInfo._idpMetadataRecord) - { SAML._edIssuer = issuer, - SAML._edRequestURI = idpEndpoint - } - } - - expectedLogLine = - ( Info, - "IdP deleted, team=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid - <> ", idpId=00000000-0000-0000-0000-000000000000, issuer=" - <> fromString issuerString - <> ", domain=" - <> (TL.encodeUtf8 . TL.fromStrict) miHost1AsText - <> ", user=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser - <> ", certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" - <> ", idp-endpoint=" - <> fromString idpEndpointString - <> "\n" - ) - - (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do - idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing apiVersionV2 idpHandle - idpDelete zUser (idp._idpId) Nothing - logs `shouldContain` [expectedLogLine] - - describe "idp-update" $ do - it "should log IdP update" $ do - idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary - user :: User <- generate arbitrary - let idPMetadataInfo' = - idPMetadataInfo - { _idpMetadataRecord = - (idPMetadataInfo._idpMetadataRecord) - { SAML._edIssuer = issuer, - SAML._edRequestURI = idpEndpoint - } - } - - expectedLogLine = - ( Info, - "IdP updated, team=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid - <> ", idpId=00000000-0000-0000-0000-000000000000, issuer=" - <> fromString issuerString - <> ", domain=None, user=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser - <> ", idp-endpoint=" - <> fromString idpEndpointString - <> ", certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" - <> "\n" - ) - - (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do - idp <- idpCreate singleIngressSamlConfig tid zUser host idPMetadataInfo' Nothing apiVersionV2 idpHandle - idpUpdate singleIngressSamlConfig zUser host idPMetadataInfo' (idp._idpId) Nothing - logs `shouldContain` [expectedLogLine] - - it "should log IdP update with domain for multi-ingress" $ do - idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary - user :: User <- generate arbitrary - let idPMetadataInfo' = - idPMetadataInfo - { _idpMetadataRecord = - (idPMetadataInfo._idpMetadataRecord) - { SAML._edIssuer = issuer, - SAML._edRequestURI = idpEndpoint - } - } - - expectedLogLine = - ( Info, - "IdP updated, team=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid - <> ", idpId=00000000-0000-0000-0000-000000000000, issuer=" - <> fromString issuerString - <> ", domain=" - <> (TL.encodeUtf8 . TL.fromStrict) miHost1AsText - <> ", user=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser - <> ", idp-endpoint=" - <> fromString idpEndpointString - <> ", certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" - <> "\n" - ) - - (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do - idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing apiVersionV2 idpHandle - idpUpdate multiIngressSamlConfig zUser miHost1 idPMetadataInfo' (idp._idpId) Nothing - logs `shouldContain` [expectedLogLine] - - it "should log IdP update with changed domain for multi-ingress" $ do - idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary - user :: User <- generate arbitrary - let idPMetadataInfo' = - idPMetadataInfo - { _idpMetadataRecord = - (idPMetadataInfo._idpMetadataRecord) - { SAML._edIssuer = issuer, - SAML._edRequestURI = idpEndpoint - } - } - - expectedLogLine = - ( Info, - "IdP updated, team=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid - <> ", idpId=00000000-0000-0000-0000-000000000000, issuer=" - <> fromString issuerString - <> ", old-domain=" - <> (TL.encodeUtf8 . TL.fromStrict) miHost1AsText - <> ", new-domain=" - <> (TL.encodeUtf8 . TL.fromStrict) miHost2AsText - <> ", user=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser - <> ", idp-endpoint=" - <> fromString idpEndpointString - <> ", certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" - <> "\n" - ) - - (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do - idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing apiVersionV2 idpHandle - idpUpdate multiIngressSamlConfig zUser miHost2 idPMetadataInfo' (idp._idpId) Nothing - logs `shouldContain` [expectedLogLine] - - it "should log IdP update (changed cert)" $ do - idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary - user :: User <- generate arbitrary - newKeyInfo <- readSampleIO "okta-keyinfo-1.xml" - let newIssuerString = "https://new.idp.example.com/auth" - newIssuer = Issuer . (either (error . show) id) . parseURI strictURIParserOptions . fromString $ newIssuerString - newIdpEndpointString = "https://new.idp.example.com/login" - newRequestURI = either (error . show) id . parseURI strictURIParserOptions . fromString $ newIdpEndpointString - idPMetadataInfo' = - idPMetadataInfo - { _idpMetadataRecord = - (idPMetadataInfo._idpMetadataRecord) - { SAML._edIssuer = issuer, - SAML._edRequestURI = idpEndpoint - } - } - - newCert = either (error . show) id $ DSig.parseKeyInfo False newKeyInfo - newIdPMetadata :: IdPMetadata = - IdPMetadata - { _edIssuer = newIssuer, - _edRequestURI = newRequestURI, - _edCertAuthnResponse = NonEmptyL.singleton newCert - } - idPMetadataInfo'' = IdPMetadataValue ((TL.toStrict . encode) newIdPMetadata) newIdPMetadata - expectedLogLine = - ( Info, - "IdP updated, team=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid - <> ", idpId=00000000-0000-0000-0000-000000000000" - <> ", old-issuer=" - <> fromString issuerString - <> ", new-issuer=" - <> fromString newIssuerString - <> ", domain=None, user=" - <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser - <> ", old-idp-endpoint=" - <> fromString idpEndpointString - <> ", new-idp-endpoint=" - <> fromString newIdpEndpointString - <> ", certificates=Issuer: Country=US,O=Okta,OU=SSOProvider,CN=dev-500508,Email Address=info@okta.com; Subject: Country=US,O=Okta,OU=SSOProvider,CN=dev-500508,Email Address=info@okta.com; SHA1 Fingerprint: 5C:42:5B:27:B3:96:CC:9D:1B:1F:0E:4F:2B:8A:B8:E4:3C:9E:96:34" - <> ", new-certificates=Issuer: Country=US,O=Okta,OU=SSOProvider,CN=dev-500508,Email Address=info@okta.com; Subject: Country=US,O=Okta,OU=SSOProvider,CN=dev-500508,Email Address=info@okta.com; SHA1 Fingerprint: 5C:42:5B:27:B3:96:CC:9D:1B:1F:0E:4F:2B:8A:B8:E4:3C:9E:96:34" - <> ", removed-certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" - <> "\n" - ) - - (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do - idp <- idpCreate singleIngressSamlConfig tid zUser host idPMetadataInfo' Nothing apiVersionV2 idpHandle - idpUpdate singleIngressSamlConfig zUser host idPMetadataInfo'' (idp._idpId) Nothing - logs `shouldContain` [expectedLogLine] + it "should log IdP deletion with domain for multi-ingress" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + user :: User <- generate arbitrary + let idPMetadataInfo' = + idPMetadataInfo + { _idpMetadataRecord = + (idPMetadataInfo._idpMetadataRecord) + { SAML._edIssuer = issuer, + SAML._edRequestURI = idpEndpoint + } + } + + expectedLogLine = + ( Info, + "IdP deleted, team=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid + <> ", idpId=00000000-0000-0000-0000-000000000000, issuer=" + <> fromString issuerString + <> ", domain=" + <> (TL.encodeUtf8 . TL.fromStrict) miHost1AsText + <> ", user=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser + <> ", certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" + <> ", idp-endpoint=" + <> fromString idpEndpointString + <> "\n" + ) + + (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do + idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing apiVersionV2 idpHandle + idpDelete zUser (idp._idpId) Nothing + logs `shouldContain` [expectedLogLine] + + describe "idp-update" $ do + it "should log IdP update" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + user :: User <- generate arbitrary + let idPMetadataInfo' = + idPMetadataInfo + { _idpMetadataRecord = + (idPMetadataInfo._idpMetadataRecord) + { SAML._edIssuer = issuer, + SAML._edRequestURI = idpEndpoint + } + } + + expectedLogLine = + ( Info, + "IdP updated, team=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid + <> ", idpId=00000000-0000-0000-0000-000000000000, issuer=" + <> fromString issuerString + <> ", domain=None, user=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser + <> ", idp-endpoint=" + <> fromString idpEndpointString + <> ", certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" + <> "\n" + ) + + (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do + idp <- idpCreate singleIngressSamlConfig tid zUser host idPMetadataInfo' Nothing apiVersionV2 idpHandle + idpUpdate singleIngressSamlConfig zUser host idPMetadataInfo' (idp._idpId) Nothing + logs `shouldContain` [expectedLogLine] + + it "should log IdP update with domain for multi-ingress" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + user :: User <- generate arbitrary + let idPMetadataInfo' = + idPMetadataInfo + { _idpMetadataRecord = + (idPMetadataInfo._idpMetadataRecord) + { SAML._edIssuer = issuer, + SAML._edRequestURI = idpEndpoint + } + } + + expectedLogLine = + ( Info, + "IdP updated, team=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid + <> ", idpId=00000000-0000-0000-0000-000000000000, issuer=" + <> fromString issuerString + <> ", domain=" + <> (TL.encodeUtf8 . TL.fromStrict) miHost1AsText + <> ", user=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser + <> ", idp-endpoint=" + <> fromString idpEndpointString + <> ", certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" + <> "\n" + ) + + (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do + idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing apiVersionV2 idpHandle + idpUpdate multiIngressSamlConfig zUser miHost1 idPMetadataInfo' (idp._idpId) Nothing + logs `shouldContain` [expectedLogLine] + + it "should log IdP update with changed domain for multi-ingress" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + user :: User <- generate arbitrary + let idPMetadataInfo' = + idPMetadataInfo + { _idpMetadataRecord = + (idPMetadataInfo._idpMetadataRecord) + { SAML._edIssuer = issuer, + SAML._edRequestURI = idpEndpoint + } + } + + expectedLogLine = + ( Info, + "IdP updated, team=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid + <> ", idpId=00000000-0000-0000-0000-000000000000, issuer=" + <> fromString issuerString + <> ", old-domain=" + <> (TL.encodeUtf8 . TL.fromStrict) miHost1AsText + <> ", new-domain=" + <> (TL.encodeUtf8 . TL.fromStrict) miHost2AsText + <> ", user=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser + <> ", idp-endpoint=" + <> fromString idpEndpointString + <> ", certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" + <> "\n" + ) + + (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do + idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing apiVersionV2 idpHandle + idpUpdate multiIngressSamlConfig zUser miHost2 idPMetadataInfo' (idp._idpId) Nothing + logs `shouldContain` [expectedLogLine] + + it "should log IdP update (changed cert)" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + user :: User <- generate arbitrary + newKeyInfo <- readSampleIO "okta-keyinfo-1.xml" + let newIssuerString = "https://new.idp.example.com/auth" + newIssuer = Issuer . (either (error . show) id) . parseURI strictURIParserOptions . fromString $ newIssuerString + newIdpEndpointString = "https://new.idp.example.com/login" + newRequestURI = either (error . show) id . parseURI strictURIParserOptions . fromString $ newIdpEndpointString + idPMetadataInfo' = + idPMetadataInfo + { _idpMetadataRecord = + (idPMetadataInfo._idpMetadataRecord) + { SAML._edIssuer = issuer, + SAML._edRequestURI = idpEndpoint + } + } + + newCert = either (error . show) id $ DSig.parseKeyInfo False newKeyInfo + newIdPMetadata :: IdPMetadata = + IdPMetadata + { _edIssuer = newIssuer, + _edRequestURI = newRequestURI, + _edCertAuthnResponse = NonEmptyL.singleton newCert + } + idPMetadataInfo'' = IdPMetadataValue ((TL.toStrict . encode) newIdPMetadata) newIdPMetadata + expectedLogLine = + ( Info, + "IdP updated, team=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText) tid + <> ", idpId=00000000-0000-0000-0000-000000000000" + <> ", old-issuer=" + <> fromString issuerString + <> ", new-issuer=" + <> fromString newIssuerString + <> ", domain=None, user=" + <> (TL.encodeUtf8 . TL.fromStrict . idToText . fromJust) zUser + <> ", old-idp-endpoint=" + <> fromString idpEndpointString + <> ", new-idp-endpoint=" + <> fromString newIdpEndpointString + <> ", certificates=Issuer: Country=US,O=Okta,OU=SSOProvider,CN=dev-500508,Email Address=info@okta.com; Subject: Country=US,O=Okta,OU=SSOProvider,CN=dev-500508,Email Address=info@okta.com; SHA1 Fingerprint: 5C:42:5B:27:B3:96:CC:9D:1B:1F:0E:4F:2B:8A:B8:E4:3C:9E:96:34" + <> ", new-certificates=Issuer: Country=US,O=Okta,OU=SSOProvider,CN=dev-500508,Email Address=info@okta.com; Subject: Country=US,O=Okta,OU=SSOProvider,CN=dev-500508,Email Address=info@okta.com; SHA1 Fingerprint: 5C:42:5B:27:B3:96:CC:9D:1B:1F:0E:4F:2B:8A:B8:E4:3C:9E:96:34" + <> ", removed-certificates=Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" + <> "\n" + ) + + (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do + idp <- idpCreate singleIngressSamlConfig tid zUser host idPMetadataInfo' Nothing apiVersionV2 idpHandle + idpUpdate singleIngressSamlConfig zUser host idPMetadataInfo'' (idp._idpId) Nothing + logs `shouldContain` [expectedLogLine] + describe "SAML IdP change notifications" $ do + describe "idp-create" $ do + it "should sent when multi-ingress is configured" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + let idPMetadataInfo' = + idPMetadataInfo + { _idpMetadataRecord = + (idPMetadataInfo._idpMetadataRecord) + { SAML._edIssuer = issuer, + SAML._edRequestURI = idpEndpoint + } + } + + forM_ [(minBound :: WireIdPAPIVersion) .. maxBound] $ \apiVersion -> do + (_logs, notifs, idp) <- + interpretWithLoggingMock + Nothing + (idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing (Just apiVersion) idpHandle) + notifs `shouldBe` [IdPCreated idp] + + -- >=V7 does not bother with multi-ingress domains for IdPs as it can + -- only have one IdP per team anyways. + (_logs, notifsV7, idpV7) <- + interpretWithLoggingMock + Nothing + (idpCreateV7 multiIngressSamlConfig tid zUser idPMetadataInfo' Nothing (Just apiVersion) idpHandle) + notifsV7 `shouldBe` [IdPCreated idpV7] type LogLine = (Level, LByteString) From d58d0cb8070fa55ddf9cb883b081abac0da30cfe Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 21 Jan 2026 15:38:44 +0100 Subject: [PATCH 05/60] Add mi delete test --- services/spar/test/Test/Spar/Saml/IdPSpec.hs | 73 ++++++++++++-------- 1 file changed, 46 insertions(+), 27 deletions(-) diff --git a/services/spar/test/Test/Spar/Saml/IdPSpec.hs b/services/spar/test/Test/Spar/Saml/IdPSpec.hs index c75a748768e..b16ccbfc1e7 100644 --- a/services/spar/test/Test/Spar/Saml/IdPSpec.hs +++ b/services/spar/test/Test/Spar/Saml/IdPSpec.hs @@ -399,33 +399,52 @@ spec = idp <- idpCreate singleIngressSamlConfig tid zUser host idPMetadataInfo' Nothing apiVersionV2 idpHandle idpUpdate singleIngressSamlConfig zUser host idPMetadataInfo'' (idp._idpId) Nothing logs `shouldContain` [expectedLogLine] - describe "SAML IdP change notifications" $ do - describe "idp-create" $ do - it "should sent when multi-ingress is configured" $ do - idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary - let idPMetadataInfo' = - idPMetadataInfo - { _idpMetadataRecord = - (idPMetadataInfo._idpMetadataRecord) - { SAML._edIssuer = issuer, - SAML._edRequestURI = idpEndpoint - } - } - - forM_ [(minBound :: WireIdPAPIVersion) .. maxBound] $ \apiVersion -> do - (_logs, notifs, idp) <- - interpretWithLoggingMock - Nothing - (idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing (Just apiVersion) idpHandle) - notifs `shouldBe` [IdPCreated idp] - - -- >=V7 does not bother with multi-ingress domains for IdPs as it can - -- only have one IdP per team anyways. - (_logs, notifsV7, idpV7) <- - interpretWithLoggingMock - Nothing - (idpCreateV7 multiIngressSamlConfig tid zUser idPMetadataInfo' Nothing (Just apiVersion) idpHandle) - notifsV7 `shouldBe` [IdPCreated idpV7] + describe "SAML IdP change notification emails" $ do + context "when multi-ingress is configured" $ do + describe "idp-create" $ do + it "should send" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + let idPMetadataInfo' = + idPMetadataInfo + { _idpMetadataRecord = + (idPMetadataInfo._idpMetadataRecord) + { SAML._edIssuer = issuer, + SAML._edRequestURI = idpEndpoint + } + } + + forM_ [(minBound :: WireIdPAPIVersion) .. maxBound] $ \apiVersion -> do + (_logs, notifs, idp) <- + interpretWithLoggingMock + Nothing + (idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing (Just apiVersion) idpHandle) + notifs `shouldBe` [IdPCreated idp] + + -- >=V7 does not bother with multi-ingress domains for IdPs as it can + -- only have one IdP per team anyways. + (_logs, notifsV7, idpV7) <- + interpretWithLoggingMock + Nothing + (idpCreateV7 multiIngressSamlConfig tid zUser idPMetadataInfo' Nothing (Just apiVersion) idpHandle) + notifsV7 `shouldBe` [IdPCreated idpV7] + describe "idp-delete" $ do + it "should send" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + user :: User <- generate arbitrary + let idPMetadataInfo' = + idPMetadataInfo + { _idpMetadataRecord = + (idPMetadataInfo._idpMetadataRecord) + { SAML._edIssuer = issuer, + SAML._edRequestURI = idpEndpoint + } + } + + (_logs, notifs, idp) <- interpretWithLoggingMock (Just user) $ do + idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing apiVersionV2 idpHandle + idpDelete zUser (idp._idpId) Nothing + pure idp + notifs `shouldContain` [IdPDeleted idp] type LogLine = (Level, LByteString) From a3997acda9dd94e8547212f394ad105448a4ddb9 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 21 Jan 2026 15:50:42 +0100 Subject: [PATCH 06/60] Add mi update test --- services/spar/test/Test/Spar/Saml/IdPSpec.hs | 36 ++++++++------------ 1 file changed, 15 insertions(+), 21 deletions(-) diff --git a/services/spar/test/Test/Spar/Saml/IdPSpec.hs b/services/spar/test/Test/Spar/Saml/IdPSpec.hs index b16ccbfc1e7..4b90fd408e8 100644 --- a/services/spar/test/Test/Spar/Saml/IdPSpec.hs +++ b/services/spar/test/Test/Spar/Saml/IdPSpec.hs @@ -404,20 +404,12 @@ spec = describe "idp-create" $ do it "should send" $ do idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary - let idPMetadataInfo' = - idPMetadataInfo - { _idpMetadataRecord = - (idPMetadataInfo._idpMetadataRecord) - { SAML._edIssuer = issuer, - SAML._edRequestURI = idpEndpoint - } - } forM_ [(minBound :: WireIdPAPIVersion) .. maxBound] $ \apiVersion -> do (_logs, notifs, idp) <- interpretWithLoggingMock Nothing - (idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing (Just apiVersion) idpHandle) + (idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo Nothing (Just apiVersion) idpHandle) notifs `shouldBe` [IdPCreated idp] -- >=V7 does not bother with multi-ingress domains for IdPs as it can @@ -425,26 +417,28 @@ spec = (_logs, notifsV7, idpV7) <- interpretWithLoggingMock Nothing - (idpCreateV7 multiIngressSamlConfig tid zUser idPMetadataInfo' Nothing (Just apiVersion) idpHandle) + (idpCreateV7 multiIngressSamlConfig tid zUser idPMetadataInfo Nothing (Just apiVersion) idpHandle) notifsV7 `shouldBe` [IdPCreated idpV7] describe "idp-delete" $ do it "should send" $ do idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary user :: User <- generate arbitrary - let idPMetadataInfo' = - idPMetadataInfo - { _idpMetadataRecord = - (idPMetadataInfo._idpMetadataRecord) - { SAML._edIssuer = issuer, - SAML._edRequestURI = idpEndpoint - } - } (_logs, notifs, idp) <- interpretWithLoggingMock (Just user) $ do - idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing apiVersionV2 idpHandle - idpDelete zUser (idp._idpId) Nothing + idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo Nothing apiVersionV2 idpHandle + void $ idpDelete zUser (idp._idpId) Nothing pure idp - notifs `shouldContain` [IdPDeleted idp] + notifs `shouldBe` [IdPDeleted idp, IdPCreated idp] + describe "idp-update" $ do + it "should send" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + user :: User <- generate arbitrary + + (_logs, notifs, (oldIdP, newIdP)) <- interpretWithLoggingMock (Just user) $ do + idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo Nothing apiVersionV2 idpHandle + updatedIdP <- idpUpdate multiIngressSamlConfig zUser miHost1 idPMetadataInfo (idp._idpId) Nothing + pure (idp, updatedIdP) + notifs `shouldBe` [IdPUpdated oldIdP newIdP, IdPCreated oldIdP] type LogLine = (Level, LByteString) From b3f78fff498d773e2af1d1d9de24a36298650b3a Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 21 Jan 2026 17:02:16 +0100 Subject: [PATCH 07/60] Implement the single ingress case --- libs/saml2-web-sso/src/SAML2/WebSSO/Config.hs | 4 ++ services/spar/src/Spar/API.hs | 22 +++++++--- services/spar/test/Test/Spar/Saml/IdPSpec.hs | 44 +++++++++++++++++-- 3 files changed, 60 insertions(+), 10 deletions(-) diff --git a/libs/saml2-web-sso/src/SAML2/WebSSO/Config.hs b/libs/saml2-web-sso/src/SAML2/WebSSO/Config.hs index 9d7c46a5a8f..a1a3d92a212 100644 --- a/libs/saml2-web-sso/src/SAML2/WebSSO/Config.hs +++ b/libs/saml2-web-sso/src/SAML2/WebSSO/Config.hs @@ -24,6 +24,7 @@ import Control.Lens hiding (Level, element, enum, (.=)) import Control.Monad (when) import Data.Aeson qualified as A import Data.Domain +import Data.Either import Data.Map import Data.Map qualified as Map import Data.Schema @@ -68,6 +69,9 @@ data MultiIngressDomainConfig = MultiIngressDomainConfig deriving (Eq, Show, Generic) deriving (A.ToJSON, A.FromJSON) via Schema MultiIngressDomainConfig +isMultiIngressConfig :: Config -> Bool +isMultiIngressConfig = isRight . _cfgDomainConfigs + ---------------------------------------------------------------------- -- schema-profunctor diff --git a/services/spar/src/Spar/API.hs b/services/spar/src/Spar/API.hs index 58028e759e2..9f0bddc528c 100644 --- a/services/spar/src/Spar/API.hs +++ b/services/spar/src/Spar/API.hs @@ -245,7 +245,7 @@ apiIDP opts = :<|> Named @"idp-create@v7" (idpCreateV7 opts.saml) :<|> Named @"idp-create" (idpCreate opts.saml) -- post, created :<|> Named @"idp-update" (idpUpdate opts.saml) -- put, okay - :<|> Named @"idp-delete" idpDelete -- delete, no content + :<|> Named @"idp-delete" (idpDelete opts.saml) -- delete, no content apiINTERNAL :: ( Member ScimTokenStore r, @@ -566,11 +566,12 @@ idpDelete :: Member IdPRawMetadataStore r, Member (Error SparError) r ) => + SAML.Config -> Maybe UserId -> SAML.IdPId -> Maybe Bool -> Sem r NoContent -idpDelete mbzusr idpid (fromMaybe False -> purge) = withDebugLog "idpDelete" (const Nothing) $ do +idpDelete samlConfig mbzusr idpid (fromMaybe False -> purge) = withDebugLog "idpDelete" (const Nothing) $ do idp <- IdPConfigStore.getConfig idpid (zusr, teamId) <- authorizeIdP mbzusr idp let issuer = idp ^. SAML.idpMetadata . SAML.edIssuer @@ -588,7 +589,9 @@ idpDelete mbzusr idpid (fromMaybe False -> purge) = withDebugLog "idpDelete" (co do IdPConfigStore.deleteConfig idp IdPRawMetadataStore.delete idpid - BrigAccess.sendSAMLIdPChangedEmail $ IdPDeleted idp + when (SAML.isMultiIngressConfig samlConfig) $ + BrigAccess.sendSAMLIdPChangedEmail $ + IdPDeleted idp logIdPAction "IdP deleted" idp @@ -675,7 +678,9 @@ idpCreate samlConfig tid zUser uncheckedMbHost (IdPMetadataValue rawIdpMetadata IdPConfigStore.insertConfig idp forM_ mReplaces $ \replaces -> IdPConfigStore.setReplacedBy (Replaced replaces) (Replacing (idp ^. SAML.idpId)) - BrigAccess.sendSAMLIdPChangedEmail $ IdPCreated idp + when (SAML.isMultiIngressConfig samlConfig) $ + BrigAccess.sendSAMLIdPChangedEmail $ + IdPCreated idp logIdPAction "IdP created" idp @@ -838,7 +843,7 @@ idpUpdate :: Sem r IdP idpUpdate samlConfig zusr uncheckedMbHost (IdPMetadataValue raw xml) = let mbHost = filterMultiIngressZHost (samlConfig._cfgDomainConfigs) uncheckedMbHost - in idpUpdateXML zusr mbHost raw xml + in idpUpdateXML samlConfig zusr mbHost raw xml idpUpdateXML :: ( Member Random r, @@ -849,6 +854,7 @@ idpUpdateXML :: Member IdPRawMetadataStore r, Member (Error SparError) r ) => + SAML.Config -> Maybe UserId -> Maybe ZHostValue -> Text -> @@ -856,7 +862,7 @@ idpUpdateXML :: SAML.IdPId -> Maybe (Range 1 32 Text) -> Sem r IdP -idpUpdateXML zusr mDomain raw idpmeta idpid mHandle = withDebugLog "idpUpdateXML" (Just . show . (^. SAML.idpId)) $ do +idpUpdateXML samlConfig zusr mDomain raw idpmeta idpid mHandle = withDebugLog "idpUpdateXML" (Just . show . (^. SAML.idpId)) $ do (teamid, idp, previousIdP) <- validateIdPUpdate zusr idpmeta idpid GalleyAccess.assertSSOEnabled teamid guardMultiIngressDuplicateDomain teamid mDomain idpid @@ -875,7 +881,9 @@ idpUpdateXML zusr mDomain raw idpmeta idpid mHandle = withDebugLog "idpUpdateXML WireIdPAPIV1 -> Nothing WireIdPAPIV2 -> Just teamid forM_ (idp'' ^. SAML.idpExtraInfo . oldIssuers) (flip IdPConfigStore.deleteIssuer mbteamid) - BrigAccess.sendSAMLIdPChangedEmail $ IdPUpdated previousIdP idp'' + when (SAML.isMultiIngressConfig samlConfig) $ + BrigAccess.sendSAMLIdPChangedEmail $ + IdPUpdated previousIdP idp'' logIdPUpdate idp'' previousIdP pure idp'' where diff --git a/services/spar/test/Test/Spar/Saml/IdPSpec.hs b/services/spar/test/Test/Spar/Saml/IdPSpec.hs index 4b90fd408e8..1e44f9f8053 100644 --- a/services/spar/test/Test/Spar/Saml/IdPSpec.hs +++ b/services/spar/test/Test/Spar/Saml/IdPSpec.hs @@ -213,7 +213,7 @@ spec = (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do idp <- idpCreate singleIngressSamlConfig tid zUser host idPMetadataInfo' Nothing apiVersionV2 idpHandle - idpDelete zUser (idp._idpId) Nothing + idpDelete singleIngressSamlConfig zUser (idp._idpId) Nothing logs `shouldContain` [expectedLogLine] it "should log IdP deletion with domain for multi-ingress" $ do @@ -246,7 +246,7 @@ spec = (logs, _notifs, _res) <- interpretWithLoggingMock (Just user) $ do idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo' Nothing apiVersionV2 idpHandle - idpDelete zUser (idp._idpId) Nothing + idpDelete multiIngressSamlConfig zUser (idp._idpId) Nothing logs `shouldContain` [expectedLogLine] describe "idp-update" $ do @@ -426,7 +426,7 @@ spec = (_logs, notifs, idp) <- interpretWithLoggingMock (Just user) $ do idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo Nothing apiVersionV2 idpHandle - void $ idpDelete zUser (idp._idpId) Nothing + void $ idpDelete multiIngressSamlConfig zUser (idp._idpId) Nothing pure idp notifs `shouldBe` [IdPDeleted idp, IdPCreated idp] describe "idp-update" $ do @@ -440,6 +440,44 @@ spec = pure (idp, updatedIdP) notifs `shouldBe` [IdPUpdated oldIdP newIdP, IdPCreated oldIdP] + context "when multi-ingress is NOT configured (common case)" $ do + describe "idp-create" $ do + it "should send" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + + forM_ [(minBound :: WireIdPAPIVersion) .. maxBound] $ \apiVersion -> do + (_logs, notifs, _idp) <- + interpretWithLoggingMock + Nothing + (idpCreate singleIngressSamlConfig tid zUser miHost1 idPMetadataInfo Nothing (Just apiVersion) idpHandle) + notifs `shouldBe` mempty + + -- >=V7 does not bother with multi-ingress domains for IdPs as it can + -- only have one IdP per team anyways. + (_logs, notifsV7, _idp) <- + interpretWithLoggingMock + Nothing + (idpCreateV7 singleIngressSamlConfig tid zUser idPMetadataInfo Nothing (Just apiVersion) idpHandle) + notifsV7 `shouldBe` mempty + describe "idp-delete" $ do + it "should send" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + user :: User <- generate arbitrary + + (_logs, notifs, _) <- interpretWithLoggingMock (Just user) $ do + idp <- idpCreate singleIngressSamlConfig tid zUser miHost1 idPMetadataInfo Nothing apiVersionV2 idpHandle + idpDelete singleIngressSamlConfig zUser (idp._idpId) Nothing + notifs `shouldBe` mempty + describe "idp-update" $ do + it "should send" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + user :: User <- generate arbitrary + + (_logs, notifs, _) <- interpretWithLoggingMock (Just user) $ do + idp <- idpCreate singleIngressSamlConfig tid zUser miHost1 idPMetadataInfo Nothing apiVersionV2 idpHandle + idpUpdate singleIngressSamlConfig zUser miHost1 idPMetadataInfo (idp._idpId) Nothing + notifs `shouldBe` mempty + type LogLine = (Level, LByteString) interpretWithLoggingMock :: From a909b759d1dbb9654e24964febc0dbf0a1339b97 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Thu, 22 Jan 2026 08:16:16 +0100 Subject: [PATCH 08/60] Add initiating user to message --- .../src/Wire/API/Routes/Internal/Brig.hs | 30 +++++++++++++------ .../Wire/SAMLEmailSubsystem/Interpreter.hs | 12 ++++---- services/spar/src/Spar/API.hs | 6 ++-- services/spar/test/Test/Spar/Saml/IdPSpec.hs | 8 ++--- 4 files changed, 34 insertions(+), 22 deletions(-) diff --git a/libs/wire-api/src/Wire/API/Routes/Internal/Brig.hs b/libs/wire-api/src/Wire/API/Routes/Internal/Brig.hs index 50421290da1..d0654321e4c 100644 --- a/libs/wire-api/src/Wire/API/Routes/Internal/Brig.hs +++ b/libs/wire-api/src/Wire/API/Routes/Internal/Brig.hs @@ -1006,7 +1006,7 @@ instance S.ToSchema GetRichInfoMultiResponse where data IdpChangedNotificationTag = IdPCreatedTag | IdPDeletedTag | IdPUpdatedTag deriving (Eq, Enum, Bounded) -data IdpChangedNotification = IdPCreated IdP | IdPDeleted IdP | IdPUpdated IdP IdP +data IdpChangedNotification = IdPCreated (Maybe UserId) IdP | IdPDeleted (Maybe UserId) IdP | IdPUpdated (Maybe UserId) IdP IdP deriving (Eq, Show, Generic) makePrisms ''IdpChangedNotification @@ -1021,16 +1021,16 @@ instance Data.Schema.ToSchema IdpChangedNotification where (snd .= fieldOver _1 "value" untaggedSchema) where toTagged :: IdpChangedNotification -> (IdpChangedNotificationTag, IdpChangedNotification) - toTagged d@(IdPCreated _) = (IdPCreatedTag, d) - toTagged d@(IdPDeleted _) = (IdPDeletedTag, d) - toTagged d@(IdPUpdated _ _) = (IdPUpdatedTag, d) + toTagged d@(IdPCreated {}) = (IdPCreatedTag, d) + toTagged d@(IdPDeleted {}) = (IdPDeletedTag, d) + toTagged d@(IdPUpdated {}) = (IdPUpdatedTag, d) fromTagged :: (IdpChangedNotificationTag, IdpChangedNotification) -> IdpChangedNotification fromTagged = snd untaggedSchema = dispatch $ \case - IdPCreatedTag -> tag _IdPCreated (Data.Schema.unnamed schema) - IdPDeletedTag -> tag _IdPDeleted (Data.Schema.unnamed schema) + IdPCreatedTag -> tag _IdPCreated (Data.Schema.unnamed singleIdPSchema) + IdPDeletedTag -> tag _IdPDeleted (Data.Schema.unnamed singleIdPSchema) IdPUpdatedTag -> tag _IdPUpdated (Data.Schema.unnamed updatedSchema) tagSchema :: ValueSchema NamedSwaggerDoc IdpChangedNotificationTag @@ -1038,12 +1038,24 @@ instance Data.Schema.ToSchema IdpChangedNotification where enum @Text "Detail Tag" $ mconcat [element "created" IdPCreatedTag, element "deleted" IdPDeletedTag, element "updated" IdPUpdatedTag] - updatedSchema :: ValueSchema NamedSwaggerDoc (IdP, IdP) + updatedSchema :: ValueSchema NamedSwaggerDoc (Maybe UserId, IdP, IdP) updatedSchema = + object "IdPUpdated" $ + (,,) + <$> fst3 .= maybe_ (optField "user" schema) + <*> snd3 .= field "old" schema + <*> thd3 .= field "new" schema + + fst3 (a, _, _) = a + snd3 (_, b, _) = b + thd3 (_, _, c) = c + + singleIdPSchema :: ValueSchema NamedSwaggerDoc (Maybe UserId, IdP) + singleIdPSchema = object "IdPUpdated" $ (,) - <$> fst .= field "old" schema - <*> snd .= field "new" schema + <$> fst .= maybe_ (optField "user" schema) + <*> snd .= field "idp" schema deriving via (Schema IdpChangedNotification) instance FromJSON IdpChangedNotification diff --git a/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs index 5885481d6bd..4a5af0ad338 100644 --- a/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs +++ b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs @@ -38,15 +38,15 @@ sendSAMLIdPChangedImpl notif = do where delegate :: (Member Email.EmailSubsystem r) => EmailAddress -> Sem r () delegate email = case notif of - IdPCreated idp -> Email.sendSAMLIdPCreated idp email - IdPDeleted idp -> Email.sendSAMLIdPDeleted idp email - IdPUpdated old new -> Email.sendSAMLIdPUpdated old new email + IdPCreated _userId idp -> Email.sendSAMLIdPCreated idp email + IdPDeleted _userId idp -> Email.sendSAMLIdPDeleted idp email + IdPUpdated _userId old new -> Email.sendSAMLIdPUpdated old new email origIdP :: IdP origIdP = case notif of - IdPCreated idp -> idp - IdPDeleted idp -> idp - IdPUpdated old _new -> old + IdPCreated _userId idp -> idp + IdPDeleted _userId idp -> idp + IdPUpdated _userId old _new -> old getEmailAddresses :: ( Member TeamSubsystem r, diff --git a/services/spar/src/Spar/API.hs b/services/spar/src/Spar/API.hs index 9f0bddc528c..d41f2524ad2 100644 --- a/services/spar/src/Spar/API.hs +++ b/services/spar/src/Spar/API.hs @@ -591,7 +591,7 @@ idpDelete samlConfig mbzusr idpid (fromMaybe False -> purge) = withDebugLog "idp IdPRawMetadataStore.delete idpid when (SAML.isMultiIngressConfig samlConfig) $ BrigAccess.sendSAMLIdPChangedEmail $ - IdPDeleted idp + IdPDeleted mbzusr idp logIdPAction "IdP deleted" idp @@ -680,7 +680,7 @@ idpCreate samlConfig tid zUser uncheckedMbHost (IdPMetadataValue rawIdpMetadata IdPConfigStore.setReplacedBy (Replaced replaces) (Replacing (idp ^. SAML.idpId)) when (SAML.isMultiIngressConfig samlConfig) $ BrigAccess.sendSAMLIdPChangedEmail $ - IdPCreated idp + IdPCreated zUser idp logIdPAction "IdP created" idp @@ -883,7 +883,7 @@ idpUpdateXML samlConfig zusr mDomain raw idpmeta idpid mHandle = withDebugLog "i forM_ (idp'' ^. SAML.idpExtraInfo . oldIssuers) (flip IdPConfigStore.deleteIssuer mbteamid) when (SAML.isMultiIngressConfig samlConfig) $ BrigAccess.sendSAMLIdPChangedEmail $ - IdPUpdated previousIdP idp'' + IdPUpdated zusr previousIdP idp'' logIdPUpdate idp'' previousIdP pure idp'' where diff --git a/services/spar/test/Test/Spar/Saml/IdPSpec.hs b/services/spar/test/Test/Spar/Saml/IdPSpec.hs index 1e44f9f8053..e28053c6247 100644 --- a/services/spar/test/Test/Spar/Saml/IdPSpec.hs +++ b/services/spar/test/Test/Spar/Saml/IdPSpec.hs @@ -410,7 +410,7 @@ spec = interpretWithLoggingMock Nothing (idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo Nothing (Just apiVersion) idpHandle) - notifs `shouldBe` [IdPCreated idp] + notifs `shouldBe` [IdPCreated zUser idp] -- >=V7 does not bother with multi-ingress domains for IdPs as it can -- only have one IdP per team anyways. @@ -418,7 +418,7 @@ spec = interpretWithLoggingMock Nothing (idpCreateV7 multiIngressSamlConfig tid zUser idPMetadataInfo Nothing (Just apiVersion) idpHandle) - notifsV7 `shouldBe` [IdPCreated idpV7] + notifsV7 `shouldBe` [IdPCreated zUser idpV7] describe "idp-delete" $ do it "should send" $ do idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary @@ -428,7 +428,7 @@ spec = idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo Nothing apiVersionV2 idpHandle void $ idpDelete multiIngressSamlConfig zUser (idp._idpId) Nothing pure idp - notifs `shouldBe` [IdPDeleted idp, IdPCreated idp] + notifs `shouldBe` [IdPDeleted zUser idp, IdPCreated zUser idp] describe "idp-update" $ do it "should send" $ do idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary @@ -438,7 +438,7 @@ spec = idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo Nothing apiVersionV2 idpHandle updatedIdP <- idpUpdate multiIngressSamlConfig zUser miHost1 idPMetadataInfo (idp._idpId) Nothing pure (idp, updatedIdP) - notifs `shouldBe` [IdPUpdated oldIdP newIdP, IdPCreated oldIdP] + notifs `shouldBe` [IdPUpdated zUser oldIdP newIdP, IdPCreated zUser oldIdP] context "when multi-ingress is NOT configured (common case)" $ do describe "idp-create" $ do From a477010762caf2182a1336d71040e7ecf9eb7e94 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Thu, 22 Jan 2026 09:32:56 +0100 Subject: [PATCH 09/60] Drop unnecessary UserId Maybes --- .../src/Wire/API/Routes/Internal/Brig.hs | 31 ++++++++++++------- services/spar/src/Spar/API.hs | 24 +++++++------- services/spar/test/Test/Spar/Saml/IdPSpec.hs | 4 +-- 3 files changed, 33 insertions(+), 26 deletions(-) diff --git a/libs/wire-api/src/Wire/API/Routes/Internal/Brig.hs b/libs/wire-api/src/Wire/API/Routes/Internal/Brig.hs index d0654321e4c..9324c553124 100644 --- a/libs/wire-api/src/Wire/API/Routes/Internal/Brig.hs +++ b/libs/wire-api/src/Wire/API/Routes/Internal/Brig.hs @@ -1006,7 +1006,7 @@ instance S.ToSchema GetRichInfoMultiResponse where data IdpChangedNotificationTag = IdPCreatedTag | IdPDeletedTag | IdPUpdatedTag deriving (Eq, Enum, Bounded) -data IdpChangedNotification = IdPCreated (Maybe UserId) IdP | IdPDeleted (Maybe UserId) IdP | IdPUpdated (Maybe UserId) IdP IdP +data IdpChangedNotification = IdPCreated (Maybe UserId) IdP | IdPDeleted UserId IdP | IdPUpdated UserId IdP IdP deriving (Eq, Show, Generic) makePrisms ''IdpChangedNotification @@ -1029,8 +1029,8 @@ instance Data.Schema.ToSchema IdpChangedNotification where fromTagged = snd untaggedSchema = dispatch $ \case - IdPCreatedTag -> tag _IdPCreated (Data.Schema.unnamed singleIdPSchema) - IdPDeletedTag -> tag _IdPDeleted (Data.Schema.unnamed singleIdPSchema) + IdPCreatedTag -> tag _IdPCreated (Data.Schema.unnamed createdSchema) + IdPDeletedTag -> tag _IdPDeleted (Data.Schema.unnamed deletedSchema) IdPUpdatedTag -> tag _IdPUpdated (Data.Schema.unnamed updatedSchema) tagSchema :: ValueSchema NamedSwaggerDoc IdpChangedNotificationTag @@ -1038,11 +1038,25 @@ instance Data.Schema.ToSchema IdpChangedNotification where enum @Text "Detail Tag" $ mconcat [element "created" IdPCreatedTag, element "deleted" IdPDeletedTag, element "updated" IdPUpdatedTag] - updatedSchema :: ValueSchema NamedSwaggerDoc (Maybe UserId, IdP, IdP) + createdSchema :: ValueSchema NamedSwaggerDoc (Maybe UserId, IdP) + createdSchema = + object "IdPCreated" $ + (,) + <$> fst .= maybe_ (optField "user" schema) + <*> snd .= field "idp" schema + + deletedSchema :: ValueSchema NamedSwaggerDoc (UserId, IdP) + deletedSchema = + object "IdPDeleted" $ + (,) + <$> fst .= field "user" schema + <*> snd .= field "idp" schema + + updatedSchema :: ValueSchema NamedSwaggerDoc (UserId, IdP, IdP) updatedSchema = object "IdPUpdated" $ (,,) - <$> fst3 .= maybe_ (optField "user" schema) + <$> fst3 .= field "user" schema <*> snd3 .= field "old" schema <*> thd3 .= field "new" schema @@ -1050,13 +1064,6 @@ instance Data.Schema.ToSchema IdpChangedNotification where snd3 (_, b, _) = b thd3 (_, _, c) = c - singleIdPSchema :: ValueSchema NamedSwaggerDoc (Maybe UserId, IdP) - singleIdPSchema = - object "IdPUpdated" $ - (,) - <$> fst .= maybe_ (optField "user" schema) - <*> snd .= field "idp" schema - deriving via (Schema IdpChangedNotification) instance FromJSON IdpChangedNotification deriving via (Schema IdpChangedNotification) instance ToJSON IdpChangedNotification diff --git a/services/spar/src/Spar/API.hs b/services/spar/src/Spar/API.hs index d41f2524ad2..bb90d150117 100644 --- a/services/spar/src/Spar/API.hs +++ b/services/spar/src/Spar/API.hs @@ -591,7 +591,7 @@ idpDelete samlConfig mbzusr idpid (fromMaybe False -> purge) = withDebugLog "idp IdPRawMetadataStore.delete idpid when (SAML.isMultiIngressConfig samlConfig) $ BrigAccess.sendSAMLIdPChangedEmail $ - IdPDeleted mbzusr idp + IdPDeleted zusr idp logIdPAction "IdP deleted" idp @@ -862,8 +862,8 @@ idpUpdateXML :: SAML.IdPId -> Maybe (Range 1 32 Text) -> Sem r IdP -idpUpdateXML samlConfig zusr mDomain raw idpmeta idpid mHandle = withDebugLog "idpUpdateXML" (Just . show . (^. SAML.idpId)) $ do - (teamid, idp, previousIdP) <- validateIdPUpdate zusr idpmeta idpid +idpUpdateXML samlConfig mbZUsr mDomain raw idpmeta idpid mHandle = withDebugLog "idpUpdateXML" (Just . show . (^. SAML.idpId)) $ do + (zUsr, teamid, idp, previousIdP) <- validateIdPUpdate mbZUsr idpmeta idpid GalleyAccess.assertSSOEnabled teamid guardMultiIngressDuplicateDomain teamid mDomain idpid IdPRawMetadataStore.store (idp ^. SAML.idpId) raw @@ -883,8 +883,8 @@ idpUpdateXML samlConfig zusr mDomain raw idpmeta idpid mHandle = withDebugLog "i forM_ (idp'' ^. SAML.idpExtraInfo . oldIssuers) (flip IdPConfigStore.deleteIssuer mbteamid) when (SAML.isMultiIngressConfig samlConfig) $ BrigAccess.sendSAMLIdPChangedEmail $ - IdPUpdated zusr previousIdP idp'' - logIdPUpdate idp'' previousIdP + IdPUpdated zUsr previousIdP idp'' + logIdPUpdate zUsr idp'' previousIdP pure idp'' where -- Ensure that the domain is not in use by an existing IDP @@ -908,8 +908,8 @@ idpUpdateXML samlConfig zusr mDomain raw idpmeta idpid mHandle = withDebugLog "i -- We cannot simply call `logIdPAction` here, because we need diffs for -- some values (old vs. new) - logIdPUpdate :: (Member (Logger (Msg -> Msg)) r) => IdP -> IdP -> Sem r () - logIdPUpdate idp previousIdP = + logIdPUpdate :: (Member (Logger (Msg -> Msg)) r) => UserId -> IdP -> IdP -> Sem r () + logIdPUpdate zUsr idp previousIdP = let (removedCerts, newCerts) = compareNonEmpty (previousIdP ^. SAML.idpMetadata . SAML.edCertAuthnResponse) @@ -928,7 +928,7 @@ idpUpdateXML samlConfig zusr mDomain raw idpmeta idpid mHandle = withDebugLog "i (fromMaybe "None") (previousIdP ^. SAML.idpExtraInfo . domain) (idp ^. SAML.idpExtraInfo . domain) - . Log.field "user" (maybe "None" idToText zusr) + . Log.field "user" (idToText zUsr) . logChangeableScalar "idp-endpoint" URI.serializeURIRef' @@ -977,10 +977,10 @@ validateIdPUpdate :: Maybe UserId -> SAML.IdPMetadata -> SAML.IdPId -> - m (TeamId, IdP, IdP) -validateIdPUpdate zusr _idpMetadata _idpId = withDebugLog "validateIdPUpdate" (Just . show . (_2 %~ (^. SAML.idpId))) $ do + m (UserId, TeamId, IdP, IdP) +validateIdPUpdate mbZUsr _idpMetadata _idpId = withDebugLog "validateIdPUpdate" (Just . show . (_3 %~ (^. SAML.idpId))) $ do previousIdP <- IdPConfigStore.getConfig _idpId - (_, teamId) <- authorizeIdP zusr previousIdP + (zusr, teamId) <- authorizeIdP mbZUsr previousIdP unless (previousIdP ^. SAML.idpExtraInfo . team == teamId) $ throw errUnknownIdP _idpExtraInfo <- do @@ -1010,7 +1010,7 @@ validateIdPUpdate zusr _idpMetadata _idpId = withDebugLog "validateIdPUpdate" (J let requri = _idpMetadata ^. SAML.edRequestURI enforceHttps requri - pure (teamId, SAML.IdPConfig {..}, previousIdP) + pure (zusr, teamId, SAML.IdPConfig {..}, previousIdP) where -- If the new issuer was previously used, it has to be removed from the list of old issuers, -- to prevent it from getting deleted in a later step diff --git a/services/spar/test/Test/Spar/Saml/IdPSpec.hs b/services/spar/test/Test/Spar/Saml/IdPSpec.hs index e28053c6247..db3ca613f04 100644 --- a/services/spar/test/Test/Spar/Saml/IdPSpec.hs +++ b/services/spar/test/Test/Spar/Saml/IdPSpec.hs @@ -428,7 +428,7 @@ spec = idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo Nothing apiVersionV2 idpHandle void $ idpDelete multiIngressSamlConfig zUser (idp._idpId) Nothing pure idp - notifs `shouldBe` [IdPDeleted zUser idp, IdPCreated zUser idp] + notifs `shouldBe` [IdPDeleted (fromJust zUser) idp, IdPCreated zUser idp] describe "idp-update" $ do it "should send" $ do idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary @@ -438,7 +438,7 @@ spec = idp <- idpCreate multiIngressSamlConfig tid zUser miHost1 idPMetadataInfo Nothing apiVersionV2 idpHandle updatedIdP <- idpUpdate multiIngressSamlConfig zUser miHost1 idPMetadataInfo (idp._idpId) Nothing pure (idp, updatedIdP) - notifs `shouldBe` [IdPUpdated zUser oldIdP newIdP, IdPCreated zUser oldIdP] + notifs `shouldBe` [IdPUpdated (fromJust zUser) oldIdP newIdP, IdPCreated zUser oldIdP] context "when multi-ingress is NOT configured (common case)" $ do describe "idp-create" $ do From f94a86957a51b3927425f0442fa23d1dfe670263 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Thu, 22 Jan 2026 09:33:36 +0100 Subject: [PATCH 10/60] Add test when Maybe UserId is empty for idpCreate --- services/spar/test/Test/Spar/Saml/IdPSpec.hs | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/services/spar/test/Test/Spar/Saml/IdPSpec.hs b/services/spar/test/Test/Spar/Saml/IdPSpec.hs index db3ca613f04..fa58c826602 100644 --- a/services/spar/test/Test/Spar/Saml/IdPSpec.hs +++ b/services/spar/test/Test/Spar/Saml/IdPSpec.hs @@ -419,6 +419,23 @@ spec = Nothing (idpCreateV7 multiIngressSamlConfig tid zUser idPMetadataInfo Nothing (Just apiVersion) idpHandle) notifsV7 `shouldBe` [IdPCreated zUser idpV7] + it "should send without zUser if none is given" $ do + idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary + + forM_ [(minBound :: WireIdPAPIVersion) .. maxBound] $ \apiVersion -> do + (_logs, notifs, idp) <- + interpretWithLoggingMock + Nothing + (idpCreate multiIngressSamlConfig tid Nothing miHost1 idPMetadataInfo Nothing (Just apiVersion) idpHandle) + notifs `shouldBe` [IdPCreated Nothing idp] + + -- >=V7 does not bother with multi-ingress domains for IdPs as it can + -- only have one IdP per team anyways. + (_logs, notifsV7, idpV7) <- + interpretWithLoggingMock + Nothing + (idpCreateV7 multiIngressSamlConfig tid Nothing idPMetadataInfo Nothing (Just apiVersion) idpHandle) + notifsV7 `shouldBe` [IdPCreated Nothing idpV7] describe "idp-delete" $ do it "should send" $ do idPMetadataInfo :: IdPMetadataInfo <- generate arbitrary From 7842ad32a0091d1db44899fec125606ada5e1b5f Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Thu, 22 Jan 2026 13:50:48 +0100 Subject: [PATCH 11/60] Add email (draft) templates --- .../team/email/idp-config-change-subject.txt | 0 .../de/team/email/idp-config-change.html | 1 + .../de/team/email/idp-config-change.txt | 36 +++++++++++++++++++ .../team/email/idp-config-change-subject.txt | 1 + .../en/team/email/idp-config-change.html | 1 + .../en/team/email/idp-config-change.txt | 35 ++++++++++++++++++ 6 files changed, 74 insertions(+) create mode 100644 libs/wire-subsystems/templates/de/team/email/idp-config-change-subject.txt create mode 100644 libs/wire-subsystems/templates/de/team/email/idp-config-change.html create mode 100644 libs/wire-subsystems/templates/de/team/email/idp-config-change.txt create mode 100644 libs/wire-subsystems/templates/en/team/email/idp-config-change-subject.txt create mode 100644 libs/wire-subsystems/templates/en/team/email/idp-config-change.html create mode 100644 libs/wire-subsystems/templates/en/team/email/idp-config-change.txt diff --git a/libs/wire-subsystems/templates/de/team/email/idp-config-change-subject.txt b/libs/wire-subsystems/templates/de/team/email/idp-config-change-subject.txt new file mode 100644 index 00000000000..e69de29bb2d diff --git a/libs/wire-subsystems/templates/de/team/email/idp-config-change.html b/libs/wire-subsystems/templates/de/team/email/idp-config-change.html new file mode 100644 index 00000000000..02ca62d6b1f --- /dev/null +++ b/libs/wire-subsystems/templates/de/team/email/idp-config-change.html @@ -0,0 +1 @@ +

${brand_label_url}

Änderung in der Konfiguration Ihres Identity Providers

Etwas hat sich in der IdP-Konfiguration fĂ¼r Ihr Team geändert.

Team-ID:
${teamId}

Benutzer-ID:
${userId}


Details:

IdP Aussteller:
${issuer}

IdP-Endpunkt:
${idpEndpoint}

IdP ID:
${idpId}


Wenn Sie diese Änderung nicht veranlasst haben, wenden Sie sich bitte an den Wire Support.

 

Datenschutzerklärung und Nutzungsbedingungen · Missbrauch melden
${copyright}. Alle Rechte vorbehalten.

                                                           
\ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt b/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt new file mode 100644 index 00000000000..d5a39223a55 --- /dev/null +++ b/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt @@ -0,0 +1,36 @@ +[${brand_logo}] + +${brand_label_url} [${brand_url}] + +Ă„NDERUNG IN DER KONFIGURATION IHRES IDENTITY PROVIDERS +Etwas hat sich in der IdP-Konfiguration fĂ¼r Ihr Team geändert. + +Team-ID: +${teamid} + +Benutzer-ID: +${userid} + + +-------------------------------------------------------------------------------- + +Details: + +IdP Aussteller: +${issuer} + +IdP-Endpunkt: +${idpendpoint} + +IdP ID: +${idpid} + + +-------------------------------------------------------------------------------- + +Wenn Sie diese Ă„nderung nicht veranlasst haben, wenden Sie sich bitte an den +Wire Support. [${support}] + +Datenschutzerklärung und Nutzungsbedingungen [${legal}]· Missbrauch melden +[${misuse}] +${copyright}. Alle Rechte vorbehalten. \ No newline at end of file diff --git a/libs/wire-subsystems/templates/en/team/email/idp-config-change-subject.txt b/libs/wire-subsystems/templates/en/team/email/idp-config-change-subject.txt new file mode 100644 index 00000000000..e31e5528a25 --- /dev/null +++ b/libs/wire-subsystems/templates/en/team/email/idp-config-change-subject.txt @@ -0,0 +1 @@ +Your team's identity provider configuration has changed \ No newline at end of file diff --git a/libs/wire-subsystems/templates/en/team/email/idp-config-change.html b/libs/wire-subsystems/templates/en/team/email/idp-config-change.html new file mode 100644 index 00000000000..12120efbdd5 --- /dev/null +++ b/libs/wire-subsystems/templates/en/team/email/idp-config-change.html @@ -0,0 +1 @@ +Your team's identity provider configuration has changed

${brand_label_url}

Change in your Identity Provider configuration

Something has changed in the IdP configuration for your team.

Team ID:
${teamId}

User ID:
${userId}


Details:

IdP Issuer:
${idpIssuer}

IdP Endpoint:
${idpEndpoint}

IdP ID:
${idpId}


If you did not initiate this change, please reach out to the Wire support.

 

Privacy Policy and Terms of Use · Report misuse
${copyright}. All rights reserved.

                                                           
\ No newline at end of file diff --git a/libs/wire-subsystems/templates/en/team/email/idp-config-change.txt b/libs/wire-subsystems/templates/en/team/email/idp-config-change.txt new file mode 100644 index 00000000000..b4c8aa73dee --- /dev/null +++ b/libs/wire-subsystems/templates/en/team/email/idp-config-change.txt @@ -0,0 +1,35 @@ +[${brand_logo}] + +${brand_label_url} [${brand_url}] + +CHANGE IN YOUR IDENTITY PROVIDER CONFIGURATION +Something has changed in the IdP configuration for your team. + +Team ID: +${teamid} + +User ID: +${userid} + + +-------------------------------------------------------------------------------- + +Details: + +IdP Issuer: +${idpissuer} + +IdP Endpoint: +${idpendpoint} + +IdP ID: +${idpid} + + +-------------------------------------------------------------------------------- + +If you did not initiate this change, please reach out to the Wire support. +[${support}] + +Privacy Policy and Terms of Use [${legal}]· Report misuse [${misuse}] +${copyright}. All rights reserved. \ No newline at end of file From 29d4d741e2dcf29bd47c2274102c260a98d1a9bc Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Thu, 22 Jan 2026 15:27:18 +0100 Subject: [PATCH 12/60] fill email template --- libs/extended/src/Data/X509/Extended.hs | 35 ++++-- .../src/Wire/EmailSubsystem.hs | 17 ++- .../src/Wire/EmailSubsystem/Interpreter.hs | 101 ++++++++++++++++-- .../src/Wire/EmailSubsystem/Templates/Team.hs | 15 ++- .../Wire/SAMLEmailSubsystem/Interpreter.hs | 72 +++++++++++-- libs/wire-subsystems/src/Wire/UserStore.hs | 1 + libs/wire-subsystems/wire-subsystems.cabal | 1 + services/brig/src/Brig/Team/Template.hs | 13 +++ 8 files changed, 219 insertions(+), 36 deletions(-) diff --git a/libs/extended/src/Data/X509/Extended.hs b/libs/extended/src/Data/X509/Extended.hs index 964c2ee3028..21f0c8e2912 100644 --- a/libs/extended/src/Data/X509/Extended.hs +++ b/libs/extended/src/Data/X509/Extended.hs @@ -1,4 +1,6 @@ -module Data.X509.Extended (certToString) where +{-# LANGUAGE RecordWildCards #-} + +module Data.X509.Extended (certToString, certDescription, CertDescription (..)) where import Crypto.Hash import Data.ASN1.OID @@ -12,21 +14,34 @@ import Imports certToString :: SignedCertificate -> String certToString signedCert = + let desc = certDescription signedCert + in -- Split into pairs and join with ':' + mconcat . intersperse "; " $ + [ "Issuer: " <> desc.issuer, + "Subject: " <> desc.subject, + desc.fingerprintAlgorithm <> " Fingerprint: " <> desc.fingerprint + ] + +data CertDescription = CertDescription + { fingerprintAlgorithm :: String, + fingerprint :: String, + subject :: String, + issuer :: String + } + +certDescription :: SignedCertificate -> CertDescription +certDescription signedCert = let cert = getCertificate signedCert issuer = dnToString $ certIssuerDN cert subject = dnToString $ certSubjectDN cert der = encodeSignedObject signedCert - fingerprint :: ByteString = BAE.convertToBase BAE.Base16 (hash der :: Digest SHA1) - -- Split into pairs and join with ':' - fingerprintStr = - let hex = (T.decodeUtf8 fingerprint) + fingerprintBS :: ByteString = BAE.convertToBase BAE.Base16 (hash der :: Digest SHA1) + fingerprint = + let hex = (T.decodeUtf8 fingerprintBS) pairs = T.unpack <$> T.chunksOf 2 hex in map toUpper (intercalate ":" pairs) - in mconcat . intersperse "; " $ - [ "Issuer: " <> issuer, - "Subject: " <> subject, - "SHA1 Fingerprint: " <> fingerprintStr - ] + fingerprintAlgorithm = "SHA1" + in CertDescription {..} dnToString :: DistinguishedName -> String dnToString (getDistinguishedElements -> es) = diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem.hs index 9047bacd807..c7548a42a87 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem.hs @@ -23,11 +23,12 @@ import Data.Code qualified as Code import Data.Id import Imports import Polysemy +import SAML2.WebSSO +import URI.ByteString (URI) import Wire.API.Locale import Wire.API.User import Wire.API.User.Activation (ActivationCode, ActivationKey) import Wire.API.User.Client (Client (..)) -import Wire.API.User.IdentityProvider (IdP) data EmailSubsystem m a where SendPasswordResetMail :: EmailAddress -> PasswordResetPair -> Maybe Locale -> EmailSubsystem m () @@ -46,8 +47,16 @@ data EmailSubsystem m a where SendTeamInvitationMailPersonalUser :: EmailAddress -> TeamId -> EmailAddress -> InvitationCode -> Maybe Locale -> EmailSubsystem m Text SendMemberWelcomeEmail :: EmailAddress -> TeamId -> Text -> Maybe Locale -> EmailSubsystem m () SendNewTeamOwnerWelcomeEmail :: EmailAddress -> TeamId -> Text -> Maybe Locale -> Name -> EmailSubsystem m () - SendSAMLIdPCreated :: IdP -> EmailAddress -> EmailSubsystem m () - SendSAMLIdPDeleted :: IdP -> EmailAddress -> EmailSubsystem m () - SendSAMLIdPUpdated :: IdP -> IdP -> EmailAddress -> EmailSubsystem m () + SendSAMLIdPChanged :: EmailAddress -> TeamId -> Maybe UserId -> [IdPDescription] -> [IdPDescription] -> IdPId -> Issuer -> URI -> Maybe Locale -> EmailSubsystem m () + +data IdPStatus = Added | Removed + deriving (Eq, Ord, Show) + +-- TODO: Or `IdPDetails`? +data IdPDescription = IdPDescription + { idpDescriptionFingerprintAlgorithm :: Text, + idpDescriptionFingerprint :: Text, + idpDescriptionSubject :: Text + } makeSem ''EmailSubsystem diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs index ef82c4df5b9..635febaff5f 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs @@ -24,20 +24,25 @@ import Data.Id import Data.Json.Util import Data.Map as Map import Data.Range (fromRange) +import Data.Text qualified as T import Data.Text qualified as Text import Data.Text.Ascii qualified as Ascii +import Data.Text.Encoding qualified as T import Data.Text.Lazy (toStrict) +import Data.Text.Lazy qualified as TL import Data.Text.Template +import Data.UUID (toText) import Imports import Network.Mail.Mime import Polysemy import Polysemy.Output (Output) import Polysemy.TinyLog (TinyLog) +import SAML2.WebSSO +import URI.ByteString (URI, serializeURIRef') import Wire.API.Locale import Wire.API.User import Wire.API.User.Activation import Wire.API.User.Client (Client (..)) -import Wire.API.User.IdentityProvider (IdP) import Wire.API.User.Password import Wire.EmailSending (EmailSending, sendMail) import Wire.EmailSubsystem @@ -68,19 +73,95 @@ emailSubsystemInterpreter userTpls teamTpls branding = interpret \case SendTeamInvitationMailPersonalUser email tid from code loc -> sendTeamInvitationMailPersonalUserImpl teamTpls branding email tid from code loc SendMemberWelcomeEmail email tid teamName loc -> sendMemberWelcomeEmailImpl teamTpls branding email tid teamName loc SendNewTeamOwnerWelcomeEmail email tid teamName loc name -> sendNewTeamOwnerWelcomeEmailImpl teamTpls branding email tid teamName loc name - SendSAMLIdPCreated idp email -> sendSAMLIdPCreatedImpl idp email - SendSAMLIdPDeleted idp email -> sendSAMLIdPDeletedImpl idp email - SendSAMLIdPUpdated old new email -> sendSAMLIdPUpdatedImpl old new email + SendSAMLIdPChanged email tid mbUid addedCerts removedCerts idPId iss requestUri mLocale -> + sendSAMLIdPChangedImpl teamTpls branding email tid mbUid addedCerts removedCerts idPId iss requestUri mLocale -- TODO: Move these functions down in this file. -sendSAMLIdPUpdatedImpl :: IdP -> IdP -> EmailAddress -> Sem r () -sendSAMLIdPUpdatedImpl = todo +sendSAMLIdPChangedImpl :: + (Member EmailSending r, Member TinyLog r) => + Localised TeamTemplates -> + Map Text Text -> + EmailAddress -> + TeamId -> + Maybe UserId -> + [IdPDescription] -> + [IdPDescription] -> + IdPId -> + Issuer -> + URI -> + Maybe Locale -> + Sem r () +sendSAMLIdPChangedImpl teamTemplates branding to tid mbUid addedCerts removedCerts idPId issuer endpoint mLocale = do + let tpl = idpConfigChangeEmail . snd $ forLocale mLocale teamTemplates + mail <- + logEmailRenderErrors "team deletion verification email" $ + renderIdPConfigChangeEmail to tpl branding addedCerts removedCerts tid mbUid idPId issuer endpoint + sendMail mail + +renderIdPConfigChangeEmail :: + (Member (Output Text) r) => + EmailAddress -> + IdPConfigChangeEmailTemplate -> + Map Text Text -> + [IdPDescription] -> + [IdPDescription] -> + TeamId -> + Maybe UserId -> + IdPId -> + Issuer -> + URI -> + Sem r Mail +renderIdPConfigChangeEmail email IdPConfigChangeEmailTemplate {..} branding addedCerts removedCerts tid uid idPId issuer endpoint = do + idpDetailsAddedText :: Text <- + (TL.toStrict . TL.unlines) + <$> mapM (renderTextWithBrandingSem idpConfigChangeEmailIdPDetailsAddedText . idpDetailsToMap) addedCerts + idpDetailsAddedHtml :: Text <- + (TL.toStrict . TL.unlines) + <$> mapM (renderTextWithBrandingSem idpConfigChangeEmailIdPDetailsAddedHtml . idpDetailsToMap) addedCerts + idpDetailsRemovedText :: Text <- + (TL.toStrict . TL.unlines) + <$> mapM (renderTextWithBrandingSem idpConfigChangeEmailIdPDetailsRemovedText . idpDetailsToMap) removedCerts + idpDetailsRemovedHtml :: Text <- + (TL.toStrict . TL.unlines) + <$> mapM (renderTextWithBrandingSem idpConfigChangeEmailIdPDetailsRemovedHtml . idpDetailsToMap) removedCerts -sendSAMLIdPCreatedImpl :: IdP -> EmailAddress -> Sem r () -sendSAMLIdPCreatedImpl = todo + let replace = + branding + & Map.insert "teamId" ((toText . toUUID) tid) + & Map.insert "userId" (maybe "None" (toText . toUUID) uid) + & Map.insert "idpIssuer" ((T.decodeUtf8 . serializeURIRef' . _fromIssuer) issuer) + & Map.insert "idpEndpoint" ((T.decodeUtf8 . serializeURIRef') endpoint) + & Map.insert "idpId" ((toText . fromIdPId) idPId) + replaceHtml = + replace + & Map.insert "idpDetails" (T.unlines [idpDetailsAddedHtml, idpDetailsRemovedHtml]) + replaceText = + replace + & Map.insert "idpDetails" (T.unlines [idpDetailsAddedText, idpDetailsRemovedText]) + + txt <- renderTextWithBrandingSem idpConfigChangeEmailBodyText replaceText + html <- renderHtmlWithBrandingSem idpConfigChangeEmailBodyHtml replaceHtml + subj <- renderTextWithBrandingSem idpConfigChangeEmailSubject replace + pure + (emptyMail from) + { mailTo = [to], + mailHeaders = + [ ("Subject", toStrict subj), + ("X-Zeta-Purpose", "IdPConfigChange") + ], + mailParts = [[plainPart txt, htmlPart html]] + } + where + from = Address (Just idpConfigChangeEmailSenderName) (fromEmail idpConfigChangeEmailSender) + to = Address Nothing (fromEmail email) -sendSAMLIdPDeletedImpl :: IdP -> EmailAddress -> Sem r () -sendSAMLIdPDeletedImpl = todo + idpDetailsToMap :: IdPDescription -> Map Text Text + idpDetailsToMap d = + empty @Text @Text + & Map.insert "algorithm" d.idpDescriptionFingerprintAlgorithm + & Map.insert "fingerprint" d.idpDescriptionFingerprint + & Map.insert "subject" d.idpDescriptionSubject + & Map.insert "issuer" d.idpDescriptionSubject ------------------------------------------------------------------------------- -- Verification Email for diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem/Templates/Team.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem/Templates/Team.hs index 76187fe56de..996b30729cd 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem/Templates/Team.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem/Templates/Team.hs @@ -50,9 +50,22 @@ data NewTeamOwnerWelcomeEmailTemplate = NewTeamOwnerWelcomeEmailTemplate newTeamOwnerWelcomeEmailSenderName :: !Text } +data IdPConfigChangeEmailTemplate = IdPConfigChangeEmailTemplate + { idpConfigChangeEmailIdPDetailsAddedHtml :: !Template, + idpConfigChangeEmailIdPDetailsAddedText :: !Template, + idpConfigChangeEmailIdPDetailsRemovedHtml :: !Template, + idpConfigChangeEmailIdPDetailsRemovedText :: !Template, + idpConfigChangeEmailSubject :: !Template, + idpConfigChangeEmailBodyText :: !Template, + idpConfigChangeEmailBodyHtml :: !Template, + idpConfigChangeEmailSender :: !EmailAddress, + idpConfigChangeEmailSenderName :: !Text + } + data TeamTemplates = TeamTemplates { invitationEmail :: !InvitationEmailTemplate, existingUserInvitationEmail :: !InvitationEmailTemplate, memberWelcomeEmail :: !MemberWelcomeEmailTemplate, - newTeamOwnerWelcomeEmail :: !NewTeamOwnerWelcomeEmailTemplate + newTeamOwnerWelcomeEmail :: !NewTeamOwnerWelcomeEmailTemplate, + idpConfigChangeEmail :: !IdPConfigChangeEmailTemplate } diff --git a/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs index 4a5af0ad338..83ea0ac05c0 100644 --- a/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs +++ b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs @@ -4,15 +4,23 @@ module Wire.SAMLEmailSubsystem.Interpreter where import Control.Lens ((^.), (^..)) +import Data.Id (UserId) +import Data.List.NonEmpty qualified as NE +import Data.Text qualified as T +import Data.X509 qualified as X509 +import Data.X509.Extended (CertDescription (..), certDescription) import Imports import Polysemy import SAML2.WebSSO.Types import Text.Email.Parser +import Wire.API.Locale import Wire.API.Routes.Internal.Brig import Wire.API.Team.Member import Wire.API.User.IdentityProvider +import Wire.EmailSubsystem (IdPDescription (..)) import Wire.EmailSubsystem qualified as Email import Wire.SAMLEmailSubsystem +import Wire.StoredUser import Wire.TeamSubsystem import Wire.UserStore @@ -25,6 +33,8 @@ samlEmailSubsystemInterpreter :: samlEmailSubsystemInterpreter = interpret \case SendSAMLIdPChanged idp -> sendSAMLIdPChangedImpl idp +type Receiver = (EmailAddress, Maybe Locale) + sendSAMLIdPChangedImpl :: ( Member TeamSubsystem r, Member UserStore r, @@ -33,14 +43,17 @@ sendSAMLIdPChangedImpl :: IdpChangedNotification -> Sem r () sendSAMLIdPChangedImpl notif = do - emails <- getEmailAddresses origIdP - mapM_ delegate emails + receivers <- getReceivers origIdP + mapM_ delegate receivers where - delegate :: (Member Email.EmailSubsystem r) => EmailAddress -> Sem r () - delegate email = case notif of - IdPCreated _userId idp -> Email.sendSAMLIdPCreated idp email - IdPDeleted _userId idp -> Email.sendSAMLIdPDeleted idp email - IdPUpdated _userId old new -> Email.sendSAMLIdPUpdated old new email + delegate :: (Member Email.EmailSubsystem r) => Receiver -> Sem r () + delegate (email, loc) = do + let endpoint = origIdP._idpMetadata._edRequestURI + iss = origIdP._idpMetadata._edIssuer + idPId = origIdP._idpId + tid = origIdP ^. idpExtraInfo . team + (addedCerts, removedCerts) = bimap (toDesc <$>) (toDesc <$>) certsChanges + Email.sendSAMLIdPChanged email tid mbUserId addedCerts removedCerts idPId iss endpoint loc origIdP :: IdP origIdP = case notif of @@ -48,13 +61,50 @@ sendSAMLIdPChangedImpl notif = do IdPDeleted _userId idp -> idp IdPUpdated _userId old _new -> old -getEmailAddresses :: + mbUserId :: Maybe UserId + mbUserId = case notif of + IdPCreated nofifUid _idp -> nofifUid + IdPDeleted nofifUid _idp -> Just nofifUid + IdPUpdated nofifUid _old _new -> Just nofifUid + + certsChanges :: ([X509.SignedCertificate], [X509.SignedCertificate]) + certsChanges = case notif of + IdPCreated _uid idp -> (toList idp._idpMetadata._edCertAuthnResponse, []) + IdPDeleted _uid idp -> ([], toList idp._idpMetadata._edCertAuthnResponse) + IdPUpdated _uid old new -> + bimap toList toList $ + compareNonEmpty new._idpMetadata._edCertAuthnResponse old._idpMetadata._edCertAuthnResponse + + compareNonEmpty :: (Eq a) => NE.NonEmpty a -> NE.NonEmpty a -> ([a], [a]) + compareNonEmpty xs ys = + let l = nub . toList $ xs + r = nub . toList $ ys + onlyL = l \\ r + onlyR = r \\ l + in (onlyL, onlyR) + + toDesc :: X509.SignedCertificate -> IdPDescription + toDesc cert = + let desc = certDescription cert + in IdPDescription + { idpDescriptionFingerprintAlgorithm = T.pack desc.fingerprintAlgorithm, + idpDescriptionFingerprint = T.pack desc.fingerprintAlgorithm, + idpDescriptionSubject = T.pack desc.subject + } + +getReceivers :: ( Member TeamSubsystem r, Member UserStore r ) => IdP -> - Sem r [EmailAddress] -getEmailAddresses idp = do + Sem r [Receiver] +getReceivers idp = do + -- TODO: Replace lens admins <- internalGetTeamAdmins (idp ^. idpExtraInfo . team) let adminUids = admins ^.. teamMembers . traverse . userId - getEmails adminUids + catMaybes <$> (toReceiver <$$> getUsers adminUids) + where + toReceiver :: StoredUser -> Maybe Receiver + toReceiver u = + let loc = flip Locale u.country <$> u.language + in (,loc) <$> (u.email) diff --git a/libs/wire-subsystems/src/Wire/UserStore.hs b/libs/wire-subsystems/src/Wire/UserStore.hs index 7eef7618280..a4a60848495 100644 --- a/libs/wire-subsystems/src/Wire/UserStore.hs +++ b/libs/wire-subsystems/src/Wire/UserStore.hs @@ -114,6 +114,7 @@ data UserStore m a where DeleteServiceUser :: ProviderId -> ServiceId -> BotId -> UserStore m () LookupServiceUsers :: ProviderId -> ServiceId -> Maybe PagingState -> UserStore m (PageWithState (BotId, ConvId, Maybe TeamId)) LookupServiceUsersForTeam :: ProviderId -> ServiceId -> TeamId -> Maybe PagingState -> UserStore m (PageWithState (BotId, ConvId)) + -- TODO: Delete GetEmails :: [UserId] -> UserStore m [EmailAddress] makeSem ''UserStore diff --git a/libs/wire-subsystems/wire-subsystems.cabal b/libs/wire-subsystems/wire-subsystems.cabal index e7cf35b3b03..a818b7b307e 100644 --- a/libs/wire-subsystems/wire-subsystems.cabal +++ b/libs/wire-subsystems/wire-subsystems.cabal @@ -399,6 +399,7 @@ library , containers , cql , crypton + , crypton-x509 , currency-codes , data-default , data-timeout diff --git a/services/brig/src/Brig/Team/Template.hs b/services/brig/src/Brig/Team/Template.hs index 2d2526d558e..52492a20f2b 100644 --- a/services/brig/src/Brig/Team/Template.hs +++ b/services/brig/src/Brig/Team/Template.hs @@ -60,6 +60,19 @@ loadTeamTemplates o = readLocalesDir defLocale (templateDir gOptions) "team" $ \ <*> pure (emailSender gOptions) <*> readText fp "email/sender.txt" ) + <*> + -- TODO: Template paths + ( IdPConfigChangeEmailTemplate + <$> readTemplate fp "idpConfigChangeEmailIdPDetailsAddedHtml" + <*> readTemplate fp "idpConfigChangeEmailIdPDetailsAddedText" + <*> readTemplate fp "idpConfigChangeEmailIdPDetailsRemovedHtml" + <*> readTemplate fp "idpConfigChangeEmailIdPDetailsRemovedText" + <*> readTemplate fp "idpConfigChangeEmailSubject" + <*> readTemplate fp "idpConfigChangeEmailBodyText" + <*> readTemplate fp "idpConfigChangeEmailBodyHtml" + <*> pure (emailSender gOptions) + <*> readText fp "email/sender.txt" + ) where gOptions = o.emailSMS.general tOptions = o.emailSMS.team From 7d17ba64a1424a2f96ca4596aec5ebf8aa377362 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Thu, 22 Jan 2026 17:30:41 +0100 Subject: [PATCH 13/60] Add TODO --- libs/extended/src/Data/X509/Extended.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/libs/extended/src/Data/X509/Extended.hs b/libs/extended/src/Data/X509/Extended.hs index 21f0c8e2912..255e8dfae95 100644 --- a/libs/extended/src/Data/X509/Extended.hs +++ b/libs/extended/src/Data/X509/Extended.hs @@ -29,6 +29,7 @@ data CertDescription = CertDescription issuer :: String } +-- TODO: Needs a unit test certDescription :: SignedCertificate -> CertDescription certDescription signedCert = let cert = getCertificate signedCert From c9262bab279ffdd91430b2da845724cdd87e36e3 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Thu, 22 Jan 2026 17:36:43 +0100 Subject: [PATCH 14/60] Update email templates --- .../idp-certificate-added-subject.txt | 0 .../certificates/idp-certificate-added.html | 1 + .../certificates/idp-certificate-added.txt | 17 +++++++++++++++++ .../idp-certificate-removed-subject.txt | 0 .../certificates/idp-certificate-removed.html | 1 + .../certificates/idp-certificate-removed.txt | 17 +++++++++++++++++ .../de/team/email/idp-config-change.html | 2 +- .../de/team/email/idp-config-change.txt | 2 +- .../idp-certificate-added-subject.txt | 0 .../certificates/idp-certificate-added.html | 1 + .../certificates/idp-certificate-added.txt | 17 +++++++++++++++++ .../idp-certificate-removed-subject.txt | 0 .../certificates/idp-certificate-removed.html | 1 + .../certificates/idp-certificate-removed.txt | 17 +++++++++++++++++ .../en/team/email/idp-config-change.html | 2 +- .../en/team/email/idp-config-change.txt | 2 +- 16 files changed, 76 insertions(+), 4 deletions(-) create mode 100644 libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added-subject.txt create mode 100644 libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.html create mode 100644 libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.txt create mode 100644 libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed-subject.txt create mode 100644 libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.html create mode 100644 libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.txt create mode 100644 libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added-subject.txt create mode 100644 libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.html create mode 100644 libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.txt create mode 100644 libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed-subject.txt create mode 100644 libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.html create mode 100644 libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.txt diff --git a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added-subject.txt b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added-subject.txt new file mode 100644 index 00000000000..e69de29bb2d diff --git a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.html b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.html new file mode 100644 index 00000000000..b71b2ea8307 --- /dev/null +++ b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.html @@ -0,0 +1 @@ +

${brand_label_url}

Added:

${algorithm} Fingerabdruck:
${fingerprint}

Betreff:
${subject}

Aussteller:
${issuer}


                                                           
\ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.txt b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.txt new file mode 100644 index 00000000000..7af8b11729e --- /dev/null +++ b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.txt @@ -0,0 +1,17 @@ +[${brand_logo}] + +${brand_label_url} [${brand_url}] + +Added: + +${algorithm} Fingerabdruck: +${fingerprint} + +Betreff: +${subject} + +Aussteller: +${issuer} + + +-------------------------------------------------------------------------------- \ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed-subject.txt b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed-subject.txt new file mode 100644 index 00000000000..e69de29bb2d diff --git a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.html b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.html new file mode 100644 index 00000000000..11c8e53eb66 --- /dev/null +++ b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.html @@ -0,0 +1 @@ +

${brand_label_url}

Removed:

${algorithm} Fingerabdruck:
${fingerprint}

Betreff:
${subject}

Aussteller:
${issuer}


                                                           
\ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.txt b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.txt new file mode 100644 index 00000000000..182aad0a4d8 --- /dev/null +++ b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.txt @@ -0,0 +1,17 @@ +[${brand_logo}] + +${brand_label_url} [${brand_url}] + +Removed: + +${algorithm} Fingerabdruck: +${fingerprint} + +Betreff: +${subject} + +Aussteller: +${issuer} + + +-------------------------------------------------------------------------------- \ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/team/email/idp-config-change.html b/libs/wire-subsystems/templates/de/team/email/idp-config-change.html index 02ca62d6b1f..5b3a9759b17 100644 --- a/libs/wire-subsystems/templates/de/team/email/idp-config-change.html +++ b/libs/wire-subsystems/templates/de/team/email/idp-config-change.html @@ -1 +1 @@ -

${brand_label_url}

Änderung in der Konfiguration Ihres Identity Providers

Etwas hat sich in der IdP-Konfiguration fĂ¼r Ihr Team geändert.

Team-ID:
${teamId}

Benutzer-ID:
${userId}


Details:

IdP Aussteller:
${issuer}

IdP-Endpunkt:
${idpEndpoint}

IdP ID:
${idpId}


Wenn Sie diese Änderung nicht veranlasst haben, wenden Sie sich bitte an den Wire Support.

 

Datenschutzerklärung und Nutzungsbedingungen · Missbrauch melden
${copyright}. Alle Rechte vorbehalten.

                                                           
\ No newline at end of file +

${brand_label_url}

Änderung in der Konfiguration Ihres Identity Providers

Etwas hat sich in der IdP-Konfiguration fĂ¼r Ihr Team geändert.

Team-ID:
${teamId}

Benutzer-ID:
${userId}


Details:

IdP Aussteller:
${issuer}

IdP-Endpunkt:
${idpEndpoint}

IdP ID:
${idpId}


${certificatesDetails}

Wenn Sie diese Änderung nicht veranlasst haben, wenden Sie sich bitte an den Wire Support.

 

Datenschutzerklärung und Nutzungsbedingungen · Missbrauch melden
${copyright}. Alle Rechte vorbehalten.

                                                           
\ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt b/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt index d5a39223a55..b3c25f19fcd 100644 --- a/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt +++ b/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt @@ -28,7 +28,7 @@ ${idpid} -------------------------------------------------------------------------------- -Wenn Sie diese Änderung nicht veranlasst haben, wenden Sie sich bitte an den +${certificatesdetails}Wenn Sie diese Änderung nicht veranlasst haben, wenden Sie sich bitte an den Wire Support. [${support}] Datenschutzerklärung und Nutzungsbedingungen [${legal}]· Missbrauch melden diff --git a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added-subject.txt b/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added-subject.txt new file mode 100644 index 00000000000..e69de29bb2d diff --git a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.html b/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.html new file mode 100644 index 00000000000..097e47fe8a2 --- /dev/null +++ b/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.html @@ -0,0 +1 @@ +

${brand_label_url}

Added:

${algorithm} fingerprint:
${fingerprint}

Subject:
${subject}

Issuer:
${issuer}


                                                           
\ No newline at end of file diff --git a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.txt b/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.txt new file mode 100644 index 00000000000..f5bd305191e --- /dev/null +++ b/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.txt @@ -0,0 +1,17 @@ +[${brand_logo}] + +${brand_label_url} [${brand_url}] + +Added: + +${algorithm} fingerprint: +${fingerprint} + +Subject: +${subject} + +Issuer: +${issuer} + + +-------------------------------------------------------------------------------- \ No newline at end of file diff --git a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed-subject.txt b/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed-subject.txt new file mode 100644 index 00000000000..e69de29bb2d diff --git a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.html b/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.html new file mode 100644 index 00000000000..3cfc5e9bb63 --- /dev/null +++ b/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.html @@ -0,0 +1 @@ +

${brand_label_url}

Removed:

${algorithm} fingerprint:
${fingerprint}

Subject:
${subject}

Issuer:
${issuer}


                                                           
\ No newline at end of file diff --git a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.txt b/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.txt new file mode 100644 index 00000000000..fdb87b8e833 --- /dev/null +++ b/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.txt @@ -0,0 +1,17 @@ +[${brand_logo}] + +${brand_label_url} [${brand_url}] + +Removed: + +${algorithm} fingerprint: +${fingerprint} + +Subject: +${subject} + +Issuer: +${issuer} + + +-------------------------------------------------------------------------------- \ No newline at end of file diff --git a/libs/wire-subsystems/templates/en/team/email/idp-config-change.html b/libs/wire-subsystems/templates/en/team/email/idp-config-change.html index 12120efbdd5..aab1aa79c1d 100644 --- a/libs/wire-subsystems/templates/en/team/email/idp-config-change.html +++ b/libs/wire-subsystems/templates/en/team/email/idp-config-change.html @@ -1 +1 @@ -Your team's identity provider configuration has changed

${brand_label_url}

Change in your Identity Provider configuration

Something has changed in the IdP configuration for your team.

Team ID:
${teamId}

User ID:
${userId}


Details:

IdP Issuer:
${idpIssuer}

IdP Endpoint:
${idpEndpoint}

IdP ID:
${idpId}


If you did not initiate this change, please reach out to the Wire support.

 

Privacy Policy and Terms of Use · Report misuse
${copyright}. All rights reserved.

                                                           
\ No newline at end of file +Your team's identity provider configuration has changed

${brand_label_url}

Change in your Identity Provider configuration

Something has changed in the IdP configuration for your team.

Team ID:
${teamId}

User ID:
${userId}


Details:

IdP Issuer:
${idpIssuer}

IdP Endpoint:
${idpEndpoint}

IdP ID:
${idpId}


${certificatesDetails}

If you did not initiate this change, please reach out to the Wire support.

 

Privacy Policy and Terms of Use · Report misuse
${copyright}. All rights reserved.

                                                           
\ No newline at end of file diff --git a/libs/wire-subsystems/templates/en/team/email/idp-config-change.txt b/libs/wire-subsystems/templates/en/team/email/idp-config-change.txt index b4c8aa73dee..0d909f109de 100644 --- a/libs/wire-subsystems/templates/en/team/email/idp-config-change.txt +++ b/libs/wire-subsystems/templates/en/team/email/idp-config-change.txt @@ -28,7 +28,7 @@ ${idpid} -------------------------------------------------------------------------------- -If you did not initiate this change, please reach out to the Wire support. +${certificatesdetails}If you did not initiate this change, please reach out to the Wire support. [${support}] Privacy Policy and Terms of Use [${legal}]· Report misuse [${misuse}] From 98535abc18c992c0e9b3a6320f5418fbfb05b8fe Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Thu, 22 Jan 2026 18:31:34 +0100 Subject: [PATCH 15/60] Add unit test for certDescription --- libs/extended/src/Data/X509/Extended.hs | 3 +- .../test/Test/Data/X509/ExtendedSpec.hs | 42 ++++++++++++++++--- 2 files changed, 39 insertions(+), 6 deletions(-) diff --git a/libs/extended/src/Data/X509/Extended.hs b/libs/extended/src/Data/X509/Extended.hs index 255e8dfae95..a635c5a2d86 100644 --- a/libs/extended/src/Data/X509/Extended.hs +++ b/libs/extended/src/Data/X509/Extended.hs @@ -28,8 +28,9 @@ data CertDescription = CertDescription subject :: String, issuer :: String } + deriving (Eq, Show) --- TODO: Needs a unit test +-- | Extract structured certificate description information certDescription :: SignedCertificate -> CertDescription certDescription signedCert = let cert = getCertificate signedCert diff --git a/libs/extended/test/Test/Data/X509/ExtendedSpec.hs b/libs/extended/test/Test/Data/X509/ExtendedSpec.hs index 21d5316799e..0c63713099f 100644 --- a/libs/extended/test/Test/Data/X509/ExtendedSpec.hs +++ b/libs/extended/test/Test/Data/X509/ExtendedSpec.hs @@ -22,15 +22,47 @@ spec = expected = "Issuer: CN=accounts.accesscontrol.windows.net; Subject: CN=accounts.accesscontrol.windows.net; SHA1 Fingerprint: 15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37" checkDecodingWithPEMFile pemFilePath expected + describe "certDescription" $ do + it "should extract certificate description from stars' Keycloak certificate" $ do + let pemFilePath = "test/data/" <> "sven-test.pem" + expected = + CertDescription + { fingerprintAlgorithm = "SHA1", + fingerprint = "F4:A2:73:D7:B7:2E:EA:66:E1:CB:81:E9:58:BC:1A:E9:CF:3C:95:C4", + subject = "CN=sven-test", + issuer = "CN=sven-test" + } + checkCertDescriptionWithPEMFile pemFilePath expected + + it "should extract certificate description from unit test data (saml2-web-sso)" $ do + let pemFilePath = "test/data/" <> "test-cert.pem" + expected = + CertDescription + { fingerprintAlgorithm = "SHA1", + fingerprint = "15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37", + subject = "CN=accounts.accesscontrol.windows.net", + issuer = "CN=accounts.accesscontrol.windows.net" + } + checkCertDescriptionWithPEMFile pemFilePath expected + checkDecodingWithPEMFile :: FilePath -> String -> IO () checkDecodingWithPEMFile pemFilePath expected = do + cert <- loadSignedCertificate pemFilePath + certToString cert `shouldBe` expected + +checkCertDescriptionWithPEMFile :: FilePath -> CertDescription -> IO () +checkCertDescriptionWithPEMFile pemFilePath expected = do + cert <- loadSignedCertificate pemFilePath + certDescription cert `shouldBe` expected + +-- | Load and decode a SignedCertificate from a PEM file +loadSignedCertificate :: FilePath -> IO SignedCertificate +loadSignedCertificate pemFilePath = do -- sanity check if the file even exists exists <- doesFileExist pemFilePath exists `shouldBe` True file <- BS.readFile pemFilePath - let decoded :: SignedCertificate = either error id $ do - pemBS <- pemContent . fromMaybe (error "Empty PEM list") . listToMaybe <$> pemParseBS file - decodeSignedCertificate pemBS - - certToString decoded `shouldBe` expected + pure . either error id $ do + pemBS <- pemContent . fromMaybe (error "Empty PEM list") . listToMaybe <$> pemParseBS file + decodeSignedCertificate pemBS From f2b961cc17ab3fa3b34b7e2a267575b23ff16494 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Mon, 26 Jan 2026 15:42:25 +0100 Subject: [PATCH 16/60] Update templates --- .../templates/en/partials/idp-certificate-added.html | 1 + .../email/certificates => partials}/idp-certificate-added.txt | 4 ---- .../templates/en/partials/idp-certificate-removed.html | 1 + .../certificates => partials}/idp-certificate-removed.txt | 4 ---- .../team/email/certificates/idp-certificate-added-subject.txt | 0 .../en/team/email/certificates/idp-certificate-added.html | 1 - .../email/certificates/idp-certificate-removed-subject.txt | 0 .../en/team/email/certificates/idp-certificate-removed.html | 1 - 8 files changed, 2 insertions(+), 10 deletions(-) create mode 100644 libs/wire-subsystems/templates/en/partials/idp-certificate-added.html rename libs/wire-subsystems/templates/en/{team/email/certificates => partials}/idp-certificate-added.txt (76%) create mode 100644 libs/wire-subsystems/templates/en/partials/idp-certificate-removed.html rename libs/wire-subsystems/templates/en/{team/email/certificates => partials}/idp-certificate-removed.txt (76%) delete mode 100644 libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added-subject.txt delete mode 100644 libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.html delete mode 100644 libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed-subject.txt delete mode 100644 libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.html diff --git a/libs/wire-subsystems/templates/en/partials/idp-certificate-added.html b/libs/wire-subsystems/templates/en/partials/idp-certificate-added.html new file mode 100644 index 00000000000..59b8f33a020 --- /dev/null +++ b/libs/wire-subsystems/templates/en/partials/idp-certificate-added.html @@ -0,0 +1 @@ +

Added:

${algorithm} fingerprint:
${fingerprint}

Subject:
${subject}

Issuer:
${issuer}


\ No newline at end of file diff --git a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.txt b/libs/wire-subsystems/templates/en/partials/idp-certificate-added.txt similarity index 76% rename from libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.txt rename to libs/wire-subsystems/templates/en/partials/idp-certificate-added.txt index f5bd305191e..cf8d585f9dc 100644 --- a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.txt +++ b/libs/wire-subsystems/templates/en/partials/idp-certificate-added.txt @@ -1,7 +1,3 @@ -[${brand_logo}] - -${brand_label_url} [${brand_url}] - Added: ${algorithm} fingerprint: diff --git a/libs/wire-subsystems/templates/en/partials/idp-certificate-removed.html b/libs/wire-subsystems/templates/en/partials/idp-certificate-removed.html new file mode 100644 index 00000000000..7a952614d29 --- /dev/null +++ b/libs/wire-subsystems/templates/en/partials/idp-certificate-removed.html @@ -0,0 +1 @@ +

Removed:

${algorithm} fingerprint:
${fingerprint}

Subject:
${subject}

Issuer:
${issuer}


\ No newline at end of file diff --git a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.txt b/libs/wire-subsystems/templates/en/partials/idp-certificate-removed.txt similarity index 76% rename from libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.txt rename to libs/wire-subsystems/templates/en/partials/idp-certificate-removed.txt index fdb87b8e833..4a092a0381f 100644 --- a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.txt +++ b/libs/wire-subsystems/templates/en/partials/idp-certificate-removed.txt @@ -1,7 +1,3 @@ -[${brand_logo}] - -${brand_label_url} [${brand_url}] - Removed: ${algorithm} fingerprint: diff --git a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added-subject.txt b/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added-subject.txt deleted file mode 100644 index e69de29bb2d..00000000000 diff --git a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.html b/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.html deleted file mode 100644 index 097e47fe8a2..00000000000 --- a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-added.html +++ /dev/null @@ -1 +0,0 @@ -

${brand_label_url}

Added:

${algorithm} fingerprint:
${fingerprint}

Subject:
${subject}

Issuer:
${issuer}


                                                           
\ No newline at end of file diff --git a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed-subject.txt b/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed-subject.txt deleted file mode 100644 index e69de29bb2d..00000000000 diff --git a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.html b/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.html deleted file mode 100644 index 3cfc5e9bb63..00000000000 --- a/libs/wire-subsystems/templates/en/team/email/certificates/idp-certificate-removed.html +++ /dev/null @@ -1 +0,0 @@ -

${brand_label_url}

Removed:

${algorithm} fingerprint:
${fingerprint}

Subject:
${subject}

Issuer:
${issuer}


                                                           
\ No newline at end of file From de91711ce6412155a6d602dc4a40ac0612fd1c10 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Mon, 26 Jan 2026 15:43:44 +0100 Subject: [PATCH 17/60] Move template localization to EmailSubsystem This doesn't have to be special to brig. And, these functions can be used for unit testing. --- .../src/Wire/EmailSubsystem/Template.hs | 90 +++++++++++++++++- services/brig/src/Brig/Template.hs | 95 +------------------ 2 files changed, 92 insertions(+), 93 deletions(-) diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem/Template.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem/Template.hs index cfdecce899a..85d0855d82c 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem/Template.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem/Template.hs @@ -19,16 +19,20 @@ module Wire.EmailSubsystem.Template where +import Control.Exception +import Data.ByteString qualified as BS import Data.Map qualified as Map +import Data.Text (pack, unpack) import Data.Text.Encoding qualified as T import Data.Text.Lazy qualified as Lazy import Data.Text.Template import HTMLEntities.Text qualified as HTML -import Imports +import Imports hiding (readFile) import Polysemy import Polysemy.Output import Polysemy.TinyLog (TinyLog) import Polysemy.TinyLog qualified as Log +import System.IO.Error (isDoesNotExistError) import System.Logger (field, msg, val) import Wire.API.Locale @@ -97,3 +101,87 @@ logEmailRenderErrors tplName = . field "template_name" (val (T.encodeUtf8 tplName)) . field "unreplaced_variable" (val (T.encodeUtf8 warn)) ) + +readLocalesDir :: + -- | Default locale. + Locale -> + -- | Base directory. + FilePath -> + -- | Template directory (user, provider, team) + FilePath -> + -- | Handler to load the templates for a locale. + (FilePath -> IO a) -> + IO (Localised a) +readLocalesDir defLocale base typ load = do + def <- load (basePath defLocaleDir) + Localised (defLocale, def) <$> do + -- Ignore locales if no such directory exist for the locale + ls <- + filterM (doesDirectoryExist . basePath) + . filter (/= defLocaleDir) + =<< listDirectory base + Map.fromList . zip (map readLocale ls) <$> mapM (load . basePath) ls + where + basePath :: FilePath -> FilePath + basePath loc = base <> "/" <> loc <> "/" <> typ + defLocaleDir :: FilePath + defLocaleDir = unpack (locToText defLocale) + readLocale :: FilePath -> Locale + readLocale l = + fromMaybe (error ("Invalid locale: " ++ show l)) $ + parseLocale (pack l) + +readTemplateWithDefault :: + FilePath -> + Locale -> + FilePath -> + String -> + FilePath -> + IO Template +readTemplateWithDefault = readWithDefault readTemplate + +readTemplate :: FilePath -> IO Template +readTemplate f = template <$> readText f + +readFile :: FilePath -> IO Text +readFile f = T.decodeUtf8 <$> BS.readFile f + +readTextWithDefault :: + FilePath -> + Locale -> + FilePath -> + String -> + FilePath -> + IO Text +readTextWithDefault = readWithDefault readText + +readText :: FilePath -> IO Text +readText f = + catchJust + (\e -> if isDoesNotExistError e then Just () else Nothing) + (readFile f) + (\_ -> error $ "Missing file: '" ++ f) + +readWithDefault :: + (String -> IO a) -> + FilePath -> + Locale -> + FilePath -> + String -> + FilePath -> + IO a +readWithDefault readFn baseDir defLoc typ prefix name = do + exists <- doesFileExist fileToLoad + if exists + then readFn fileToLoad + else readFn fallback + where + fileToLoad = prefix <> "/" <> name + fallback = + baseDir + <> "/" + <> unpack (locToText defLoc) + <> "/" + <> typ + <> "/" + <> name diff --git a/services/brig/src/Brig/Template.hs b/services/brig/src/Brig/Template.hs index 778c59815a3..366a92c19ab 100644 --- a/services/brig/src/Brig/Template.hs +++ b/services/brig/src/Brig/Template.hs @@ -30,16 +30,11 @@ module Brig.Template where import Brig.Options -import Control.Exception (catchJust) -import Data.ByteString qualified as BS import Data.Map.Strict qualified as Map -import Data.Text (pack, unpack) -import Data.Text.Encoding qualified as T -import Data.Text.Template (Template, template) +import Data.Text.Template (Template) import Imports hiding (readFile) -import System.IO.Error (isDoesNotExistError) -import Wire.API.User -import Wire.EmailSubsystem.Template (Localised (Localised)) +-- TODO: Eliminate re-exports +import Wire.EmailSubsystem.Template (Localised, readLocalesDir, readTemplateWithDefault, readTextWithDefault) data InvitationUrlTemplates = InvitationUrlTemplates { personalUser :: Template, @@ -49,90 +44,6 @@ data InvitationUrlTemplates = InvitationUrlTemplates -- | See 'genTemplateBranding'. type TemplateBranding = Text -> Text -readLocalesDir :: - -- | Default locale. - Locale -> - -- | Base directory. - FilePath -> - -- | Template directory (user, provider, team) - FilePath -> - -- | Handler to load the templates for a locale. - (FilePath -> IO a) -> - IO (Localised a) -readLocalesDir defLocale base typ load = do - def <- load (basePath defLocaleDir) - Localised (defLocale, def) <$> do - -- Ignore locales if no such directory exist for the locale - ls <- - filterM (doesDirectoryExist . basePath) - . filter (/= defLocaleDir) - =<< listDirectory base - Map.fromList . zip (map readLocale ls) <$> mapM (load . basePath) ls - where - basePath :: FilePath -> FilePath - basePath loc = base <> "/" <> loc <> "/" <> typ - defLocaleDir :: FilePath - defLocaleDir = unpack (locToText defLocale) - readLocale :: FilePath -> Locale - readLocale l = - fromMaybe (error ("Invalid locale: " ++ show l)) $ - parseLocale (pack l) - -readTemplateWithDefault :: - FilePath -> - Locale -> - FilePath -> - String -> - FilePath -> - IO Template -readTemplateWithDefault = readWithDefault readTemplate - -readTemplate :: FilePath -> IO Template -readTemplate f = template <$> readText f - -readFile :: FilePath -> IO Text -readFile f = T.decodeUtf8 <$> BS.readFile f - -readTextWithDefault :: - FilePath -> - Locale -> - FilePath -> - String -> - FilePath -> - IO Text -readTextWithDefault = readWithDefault readText - -readText :: FilePath -> IO Text -readText f = - catchJust - (\e -> if isDoesNotExistError e then Just () else Nothing) - (readFile f) - (\_ -> error $ "Missing file: '" ++ f) - -readWithDefault :: - (String -> IO a) -> - FilePath -> - Locale -> - FilePath -> - String -> - FilePath -> - IO a -readWithDefault readFn baseDir defLoc typ prefix name = do - exists <- doesFileExist fileToLoad - if exists - then readFn fileToLoad - else readFn fallback - where - fileToLoad = prefix <> "/" <> name - fallback = - baseDir - <> "/" - <> unpack (locToText defLoc) - <> "/" - <> typ - <> "/" - <> name - -- | Function to be applied everywhere where email/sms/call -- templating is used (ensures that placeholders are replaced -- by the appropriate branding, typically Wire) From 5e2c2e8244407c2a3d1ae13e0717845d1ec56385 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Mon, 26 Jan 2026 17:15:48 +0100 Subject: [PATCH 18/60] Snake case templates --- .../src/Wire/EmailSubsystem/Interpreter.hs | 16 ++++++++-------- .../en/team/email/idp-config-change.html | 2 +- .../en/team/email/idp-config-change.txt | 12 ++++++------ 3 files changed, 15 insertions(+), 15 deletions(-) diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs index 635febaff5f..b455b6995de 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs @@ -94,7 +94,7 @@ sendSAMLIdPChangedImpl :: sendSAMLIdPChangedImpl teamTemplates branding to tid mbUid addedCerts removedCerts idPId issuer endpoint mLocale = do let tpl = idpConfigChangeEmail . snd $ forLocale mLocale teamTemplates mail <- - logEmailRenderErrors "team deletion verification email" $ + logEmailRenderErrors "idp config change email" $ renderIdPConfigChangeEmail to tpl branding addedCerts removedCerts tid mbUid idPId issuer endpoint sendMail mail @@ -127,17 +127,17 @@ renderIdPConfigChangeEmail email IdPConfigChangeEmailTemplate {..} branding adde let replace = branding - & Map.insert "teamId" ((toText . toUUID) tid) - & Map.insert "userId" (maybe "None" (toText . toUUID) uid) - & Map.insert "idpIssuer" ((T.decodeUtf8 . serializeURIRef' . _fromIssuer) issuer) - & Map.insert "idpEndpoint" ((T.decodeUtf8 . serializeURIRef') endpoint) - & Map.insert "idpId" ((toText . fromIdPId) idPId) + & Map.insert "team_id" ((toText . toUUID) tid) + & Map.insert "user_id" (maybe "None" (toText . toUUID) uid) + & Map.insert "idp_issuer" ((T.decodeUtf8 . serializeURIRef' . _fromIssuer) issuer) + & Map.insert "idp_endpoint" ((T.decodeUtf8 . serializeURIRef') endpoint) + & Map.insert "idp_id" ((toText . fromIdPId) idPId) replaceHtml = replace - & Map.insert "idpDetails" (T.unlines [idpDetailsAddedHtml, idpDetailsRemovedHtml]) + & Map.insert "certificates_details" (T.unlines [idpDetailsAddedHtml, idpDetailsRemovedHtml]) replaceText = replace - & Map.insert "idpDetails" (T.unlines [idpDetailsAddedText, idpDetailsRemovedText]) + & Map.insert "certificates_details" (T.unlines [idpDetailsAddedText, idpDetailsRemovedText]) txt <- renderTextWithBrandingSem idpConfigChangeEmailBodyText replaceText html <- renderHtmlWithBrandingSem idpConfigChangeEmailBodyHtml replaceHtml diff --git a/libs/wire-subsystems/templates/en/team/email/idp-config-change.html b/libs/wire-subsystems/templates/en/team/email/idp-config-change.html index aab1aa79c1d..bd60a2dca4a 100644 --- a/libs/wire-subsystems/templates/en/team/email/idp-config-change.html +++ b/libs/wire-subsystems/templates/en/team/email/idp-config-change.html @@ -1 +1 @@ -Your team's identity provider configuration has changed

${brand_label_url}

Change in your Identity Provider configuration

Something has changed in the IdP configuration for your team.

Team ID:
${teamId}

User ID:
${userId}


Details:

IdP Issuer:
${idpIssuer}

IdP Endpoint:
${idpEndpoint}

IdP ID:
${idpId}


${certificatesDetails}

If you did not initiate this change, please reach out to the Wire support.

 

Privacy Policy and Terms of Use · Report misuse
${copyright}. All rights reserved.

                                                           
\ No newline at end of file +Your team's identity provider configuration has changed

${brand_label_url}

Change in your Identity Provider configuration

Something has changed in the IdP configuration for your team.

Team ID:
${team_id}

User ID:
${user_id}


Details:

IdP Issuer:
${idp_issuer}

IdP Endpoint:
${idp_endpoint}

IdP ID:
${idp_id}


${certificates_details}

If you did not initiate this change, please reach out to the Wire support.

 

Privacy Policy and Terms of Use · Report misuse
${copyright}. All rights reserved.

                                                           
\ No newline at end of file diff --git a/libs/wire-subsystems/templates/en/team/email/idp-config-change.txt b/libs/wire-subsystems/templates/en/team/email/idp-config-change.txt index 0d909f109de..75fcd408d64 100644 --- a/libs/wire-subsystems/templates/en/team/email/idp-config-change.txt +++ b/libs/wire-subsystems/templates/en/team/email/idp-config-change.txt @@ -6,10 +6,10 @@ CHANGE IN YOUR IDENTITY PROVIDER CONFIGURATION Something has changed in the IdP configuration for your team. Team ID: -${teamid} +${team_id} User ID: -${userid} +${user_id} -------------------------------------------------------------------------------- @@ -17,18 +17,18 @@ ${userid} Details: IdP Issuer: -${idpissuer} +${idp_issuer} IdP Endpoint: -${idpendpoint} +${idp_endpoint} IdP ID: -${idpid} +${idp_id} -------------------------------------------------------------------------------- -${certificatesdetails}If you did not initiate this change, please reach out to the Wire support. +${certificates_details}If you did not initiate this change, please reach out to the Wire support. [${support}] Privacy Policy and Terms of Use [${legal}]· Report misuse [${misuse}] From c0742efae1074d4465dca2cac5ba1fe8f24eec68 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Fri, 23 Jan 2026 09:43:03 +0100 Subject: [PATCH 19/60] SAMLEmailSubsystem InterpreterSpec --- .../Wire/MockInterpreters/EmailSending.hs | 7 + .../SAMLEmailSubsystem/InterpreterSpec.hs | 259 ++++++++++++++++++ libs/wire-subsystems/wire-subsystems.cabal | 1 + 3 files changed, 267 insertions(+) create mode 100644 libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs diff --git a/libs/wire-subsystems/test/unit/Wire/MockInterpreters/EmailSending.hs b/libs/wire-subsystems/test/unit/Wire/MockInterpreters/EmailSending.hs index 2c50f4c9d2c..a0f63bfc937 100644 --- a/libs/wire-subsystems/test/unit/Wire/MockInterpreters/EmailSending.hs +++ b/libs/wire-subsystems/test/unit/Wire/MockInterpreters/EmailSending.hs @@ -18,10 +18,17 @@ module Wire.MockInterpreters.EmailSending where import Imports +import Network.Mail.Mime (Mail) import Polysemy +import Polysemy.State import Wire.EmailSending noopEmailSendingInterpreter :: InterpreterFor EmailSending r noopEmailSendingInterpreter = interpret \case SendMail _ -> pure () + +recordingEmailSendingInterpreter :: (Member (State [Mail]) r) => InterpreterFor EmailSending r +recordingEmailSendingInterpreter = + interpret \case + SendMail mail -> modify (mail :) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs new file mode 100644 index 00000000000..65cdc31ed23 --- /dev/null +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -0,0 +1,259 @@ +module Wire.SAMLEmailSubsystem.InterpreterSpec where + +import Data.Default +import Data.Id +import Data.LegalHold (UserLegalHoldStatus (..)) +import Data.Map qualified as Map +import Data.Set qualified as Set +import Data.Text.Lazy.Encoding (decodeUtf8) +import Data.Text.Template +import Data.UUID qualified as UUID +import Imports +import Network.Mail.Mime (Address (..), Disposition (..), Encoding (..), Mail (..), Part (..), PartContent (..)) +import Polysemy +import Polysemy.State +import SAML2.WebSSO +import System.Logger qualified as Logger +import Test.Hspec +import Test.QuickCheck (Arbitrary (arbitrary), generate, suchThat) +import Text.Email.Parser (unsafeEmailAddress) +import Text.RawString.QQ (r) +import URI.ByteString +import Wire.API.Locale (Locale (..), parseLanguage) +import Wire.API.Routes.Internal.Brig (IdpChangedNotification (..)) +import Wire.API.Team.Member +import Wire.API.Team.Permission (fullPermissions) +import Wire.API.User.IdentityProvider +import Wire.EmailSending +import Wire.EmailSubsystem qualified as Email +import Wire.EmailSubsystem.Interpreter +import Wire.EmailSubsystem.Template +import Wire.EmailSubsystem.Templates.Team +import Wire.GalleyAPIAccess +import Wire.MockInterpreters +import Wire.SAMLEmailSubsystem +import Wire.SAMLEmailSubsystem.Interpreter (samlEmailSubsystemInterpreter) +import Wire.Sem.Logger +import Wire.Sem.Logger.TinyLog +import Wire.StoredUser +import Wire.TeamSubsystem +import Wire.TeamSubsystem.GalleyAPI (interpretTeamSubsystemToGalleyAPI) +import Wire.UserStore + +spec :: Spec +spec = do + describe "SendSAMLIdPChanged" $ do + it "should send an email" $ do + idp :: IdP <- generate arbitrary + storedUser :: StoredUser <- generate $ arbitrary `suchThat` (isJust . (.email)) + teamTemplates <- loadTeamTemplates + let notif = IdPCreated (Just uid) idp' + uid :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" + teamId :: TeamId = either error Imports.id $ parseIdFromText "99f552d8-9dad-60c1-4be9-c88fb532893a" + lang = parseLanguage "en" + idp' = + idp + { _idpId = IdPId . fromJust . UUID.fromString $ "574ddfb0-4e50-2bff-e924-33ee2b9f7064", + _idpMetadata = + idp._idpMetadata + { _edIssuer = Issuer . either (error . show) Imports.id $ parseURI strictURIParserOptions "https://issuer.example.com/realm", + _edRequestURI = either (error . show) Imports.id $ parseURI strictURIParserOptions "https://saml-endpoint.example.com/auth" + }, + _idpExtraInfo = + idp._idpExtraInfo + { _team = teamId + } + } + storedUser' = + (storedUser :: StoredUser) + { id = uid, + teamId = Just teamId, + language = lang, + country = Nothing, + email = Just $ unsafeEmailAddress "some-user" "example.com" + } + teamMember :: TeamMember = mkTeamMember uid fullPermissions Nothing UserLegalHoldDisabled + teamMap :: Map TeamId [TeamMember] = Map.singleton teamId [teamMember] + branding = + Map.fromList + [ ("brand", "Wire Test"), + ("brand_url", "https://wire.example.com"), + ("brand_label_url", "wire.example.com"), + ("brand_logo", "https://wire.example.com/p/img/email/logo-email-black.png"), + ("brand_service", "Wire Service Provider"), + ("copyright", "© WIRE SWISS GmbH"), + ("misuse", "misuse@wire.example.com"), + ("legal", "https://wire.example.com/legal/"), + ("forgot", "https://wire.example.com/forgot/"), + ("support", "https://support.wire.com/") + ] + (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do + sendSAMLIdPChanged notif + length mails `shouldBe` 1 + -- Templating issues are logged on level `Warn` + filter (\(level, _) -> level > Info) logs `shouldBe` mempty + print mails + let mail = head mails + mail.mailFrom + `shouldBe` Address + { addressName = Just "Wire", + addressEmail = "wire@example.com" + } + mail.mailTo + `shouldBe` [ Address + { addressName = Nothing, + addressEmail = "some-user@example.com" + } + ] + mail.mailCc `shouldBe` [] + mail.mailBcc `shouldBe` [] + Set.fromList mail.mailHeaders + `shouldBe` Set.fromList + [ ("Subject", "Your team's identity provider configuration has changed"), + ("X-Zeta-Purpose", "IdPConfigChange") + ] + let Just textPart :: Maybe Part = find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) + case textPart.partContent of + PartContent content -> + (decodeUtf8 content) + `shouldBe` [r|[https://wire.example.com/p/img/email/logo-email-black.png] + +wire.example.com [https://wire.example.com] + +CHANGE IN YOUR IDENTITY PROVIDER CONFIGURATION +Something has changed in the IdP configuration for your team. + +Team ID: +99f552d8-9dad-60c1-4be9-c88fb532893a + +User ID: +4a1ce4ea-5c99-d01e-018f-4dc9d08f787a + + +-------------------------------------------------------------------------------- + +Details: + +IdP Issuer: +https://issuer.example.com/realm + +IdP Endpoint: +https://saml-endpoint.example.com/auth + +IdP ID: +574ddfb0-4e50-2bff-e924-33ee2b9f7064 + + +-------------------------------------------------------------------------------- + +Added: + +SHA1 fingerprint: +SHA1 + +Subject: +CN=accounts.accesscontrol.windows.net + +Issuer: +CN=accounts.accesscontrol.windows.net + + +-------------------------------------------------------------------------------- + + +If you did not initiate this change, please reach out to the Wire support. +[https://support.wire.com/] + +Privacy Policy and Terms of Use [https://wire.example.com/legal/]· Report misuse [misuse@wire.example.com] +© WIRE SWISS GmbH. All rights reserved.|] + +runInterpreters :: + [StoredUser] -> + Map TeamId [TeamMember] -> + Localised TeamTemplates -> + Map Text Text -> + Sem + '[ SAMLEmailSubsystem, + TeamSubsystem, + Email.EmailSubsystem, + UserStore, + State [StoredUser], + GalleyAPIAccess, + Logger (Logger.Msg -> Logger.Msg), + EmailSending, + State [Mail], + Embed IO + ] + a -> + IO ([Mail], [(Level, LByteString)], a) +runInterpreters users teamMap teamTemplates branding action = do + lr <- newLogRecorder + (mails, (_userState, res)) <- + runM + . runState @[Mail] [] -- Use runState to capture and return the Mail state + . recordingEmailSendingInterpreter + . recordLogs lr + . miniGalleyAPIAccess teamMap def + . runState @[StoredUser] users + . inMemoryUserStoreInterpreter + . emailSubsystemInterpreter undefined teamTemplates branding + . interpretTeamSubsystemToGalleyAPI + . samlEmailSubsystemInterpreter + $ action + logs <- readIORef lr.recordedLogs + pure (mails, logs, res) + +loadTeamTemplates :: IO (Localised TeamTemplates) +loadTeamTemplates = readLocalesDir defLocale templateDir "team" $ \fp -> + TeamTemplates + <$> ( InvitationEmailTemplate tUrl + <$> readTemplate fp "email/invitation-subject.txt" + <*> readTemplate fp "email/invitation.txt" + <*> readTemplate fp "email/invitation.html" + <*> pure emailSender + <*> readText fp "email/sender.txt" + ) + <*> ( InvitationEmailTemplate tExistingUrl + <$> readTemplate fp "email/migration-subject.txt" + <*> readTemplate fp "email/migration.txt" + <*> readTemplate fp "email/migration.html" + <*> pure emailSender + <*> readText fp "email/sender.txt" + ) + <*> ( MemberWelcomeEmailTemplate memberWelcomeUrl + <$> readTemplate fp "email/new-member-welcome-subject.txt" + <*> readTemplate fp "email/new-member-welcome.txt" + <*> readTemplate fp "email/new-member-welcome.html" + <*> pure emailSender + <*> readText fp "email/sender.txt" + ) + <*> ( NewTeamOwnerWelcomeEmailTemplate creatorWelcomeUrl + <$> readTemplate fp "email/new-team-owner-welcome-subject.txt" + <*> readTemplate fp "email/new-team-owner-welcome.txt" + <*> readTemplate fp "email/new-team-owner-welcome.html" + <*> pure emailSender + <*> readText fp "email/sender.txt" + ) + <*> + -- TODO: Template paths + ( IdPConfigChangeEmailTemplate + <$> readTemplate fp "../partials/idp-certificate-added.html" + <*> readTemplate fp "../partials/idp-certificate-added.txt" + <*> readTemplate fp "../partials/idp-certificate-removed.html" + <*> readTemplate fp "../partials/idp-certificate-removed.txt" + <*> readTemplate fp "email/idp-config-change-subject.txt" + <*> readTemplate fp "email/idp-config-change.txt" + <*> readTemplate fp "email/idp-config-change.html" + <*> pure emailSender + <*> readText fp "email/sender.txt" + ) + where + memberWelcomeUrl = "https://example.com/member-welcome-website" + creatorWelcomeUrl = "https://example.com/creator-welcome-website" + emailSender = unsafeEmailAddress "wire" "example.com" + tUrl = template "https://example.com/join/?team-code=${code}" + tExistingUrl = template "https://example.com/accept-invitation/?team-code=${code}" + defLocale = Locale ((fromJust . parseLanguage) "en") Nothing + readTemplate = readTemplateWithDefault templateDir defLocale "team" + readText = readTextWithDefault templateDir defLocale "team" + templateDir = "templates" diff --git a/libs/wire-subsystems/wire-subsystems.cabal b/libs/wire-subsystems/wire-subsystems.cabal index a818b7b307e..b5a749fc306 100644 --- a/libs/wire-subsystems/wire-subsystems.cabal +++ b/libs/wire-subsystems/wire-subsystems.cabal @@ -525,6 +525,7 @@ test-suite wire-subsystems-tests Wire.NotificationSubsystem.InterpreterSpec Wire.PropertySubsystem.InterpreterSpec Wire.RateLimited.InterpreterSpec + Wire.SAMLEmailSubsystem.InterpreterSpec Wire.ScimSubsystem.InterpreterSpec Wire.TeamCollaboratorsSubsystem.InterpreterSpec Wire.TeamInvitationSubsystem.InterpreterSpec From d236eacdb5dfc72d4906b1217cab949a5673f528 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 07:23:18 +0100 Subject: [PATCH 20/60] Cleanup --- .../test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 65cdc31ed23..49668a24768 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -92,7 +92,6 @@ spec = do length mails `shouldBe` 1 -- Templating issues are logged on level `Warn` filter (\(level, _) -> level > Info) logs `shouldBe` mempty - print mails let mail = head mails mail.mailFrom `shouldBe` Address @@ -112,7 +111,9 @@ spec = do [ ("Subject", "Your team's identity provider configuration has changed"), ("X-Zeta-Purpose", "IdPConfigChange") ] - let Just textPart :: Maybe Part = find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) + let textPart = + fromMaybe (error "No text part found") $ + find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) case textPart.partContent of PartContent content -> (decodeUtf8 content) @@ -166,6 +167,7 @@ If you did not initiate this change, please reach out to the Wire support. Privacy Policy and Terms of Use [https://wire.example.com/legal/]· Report misuse [misuse@wire.example.com] © WIRE SWISS GmbH. All rights reserved.|] + NestedParts ns -> error $ "Enexpected NestedParts: " ++ show ns runInterpreters :: [StoredUser] -> From 88272a40e94e03e66b23371980bed4194487628d Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 07:25:47 +0100 Subject: [PATCH 21/60] Fix fingerprint --- libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs | 2 +- .../test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs index 83ea0ac05c0..c324cd38738 100644 --- a/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs +++ b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs @@ -88,7 +88,7 @@ sendSAMLIdPChangedImpl notif = do let desc = certDescription cert in IdPDescription { idpDescriptionFingerprintAlgorithm = T.pack desc.fingerprintAlgorithm, - idpDescriptionFingerprint = T.pack desc.fingerprintAlgorithm, + idpDescriptionFingerprint = T.pack desc.fingerprint, idpDescriptionSubject = T.pack desc.subject } diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 49668a24768..78f9b4d4f6d 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -150,7 +150,7 @@ IdP ID: Added: SHA1 fingerprint: -SHA1 +15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37 Subject: CN=accounts.accesscontrol.windows.net From 321ea5f10fbfbeefccda2fc2451010c330d1aa9a Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 07:43:42 +0100 Subject: [PATCH 22/60] Configure IdPConfigChangeEmailTemplate --- services/brig/src/Brig/Team/Template.hs | 24 +++++++++++------------- 1 file changed, 11 insertions(+), 13 deletions(-) diff --git a/services/brig/src/Brig/Team/Template.hs b/services/brig/src/Brig/Team/Template.hs index 52492a20f2b..477ac940160 100644 --- a/services/brig/src/Brig/Team/Template.hs +++ b/services/brig/src/Brig/Team/Template.hs @@ -60,19 +60,17 @@ loadTeamTemplates o = readLocalesDir defLocale (templateDir gOptions) "team" $ \ <*> pure (emailSender gOptions) <*> readText fp "email/sender.txt" ) - <*> - -- TODO: Template paths - ( IdPConfigChangeEmailTemplate - <$> readTemplate fp "idpConfigChangeEmailIdPDetailsAddedHtml" - <*> readTemplate fp "idpConfigChangeEmailIdPDetailsAddedText" - <*> readTemplate fp "idpConfigChangeEmailIdPDetailsRemovedHtml" - <*> readTemplate fp "idpConfigChangeEmailIdPDetailsRemovedText" - <*> readTemplate fp "idpConfigChangeEmailSubject" - <*> readTemplate fp "idpConfigChangeEmailBodyText" - <*> readTemplate fp "idpConfigChangeEmailBodyHtml" - <*> pure (emailSender gOptions) - <*> readText fp "email/sender.txt" - ) + <*> ( IdPConfigChangeEmailTemplate + <$> readTemplate fp "../partials/idp-certificate-added.html" + <*> readTemplate fp "../partials/idp-certificate-added.txt" + <*> readTemplate fp "../partials/idp-certificate-removed.html" + <*> readTemplate fp "../partials/idp-certificate-removed.txt" + <*> readTemplate fp "email/idp-config-change-subject.txt" + <*> readTemplate fp "email/idp-config-change.txt" + <*> readTemplate fp "email/idp-config-change.html" + <*> pure (emailSender gOptions) + <*> readText fp "email/sender.txt" + ) where gOptions = o.emailSMS.general tOptions = o.emailSMS.team From 3956ae070f10ea59130331272fabbc51d0cb87cf Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 08:48:27 +0100 Subject: [PATCH 23/60] Initialize test team templates with prod code Let's test the real thing. --- .../src/Wire/EmailSubsystem/Template.hs | 67 +++++++++++++++++ .../SAMLEmailSubsystem/InterpreterSpec.hs | 71 ++++--------------- services/brig/src/Brig/App.hs | 2 +- services/brig/src/Brig/Options.hs | 17 +---- services/brig/src/Brig/Team/Template.hs | 63 +++------------- services/brig/src/Brig/User/Template.hs | 1 + .../brig/test/integration/API/Template.hs | 7 +- 7 files changed, 99 insertions(+), 129 deletions(-) diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem/Template.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem/Template.hs index 85d0855d82c..5e9e8059987 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem/Template.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem/Template.hs @@ -20,6 +20,7 @@ module Wire.EmailSubsystem.Template where import Control.Exception +import Data.Aeson (FromJSON) import Data.ByteString qualified as BS import Data.Map qualified as Map import Data.Text (pack, unpack) @@ -35,6 +36,8 @@ import Polysemy.TinyLog qualified as Log import System.IO.Error (isDoesNotExistError) import System.Logger (field, msg, val) import Wire.API.Locale +import Wire.API.User.EmailAddress (EmailAddress) +import Wire.EmailSubsystem.Templates.Team -- | Lookup a localised item from a 'Localised' structure. forLocale :: @@ -185,3 +188,67 @@ readWithDefault readFn baseDir defLoc typ prefix name = do <> typ <> "/" <> name + +data TeamOpts = TeamOpts + { -- | Team Invitation URL template + tInvitationUrl :: !Text, + -- | Existing User Invitation URL template + tExistingUserInvitationUrl :: !Text, + -- | Team Activation URL template + tActivationUrl :: !Text, + -- | Team Creator Welcome URL + tCreatorWelcomeUrl :: !Text, + -- | Team Member Welcome URL + tMemberWelcomeUrl :: !Text + } + deriving (Show, Generic) + +instance FromJSON TeamOpts + +loadTeamTemplates :: TeamOpts -> FilePath -> Locale -> EmailAddress -> IO (Localised TeamTemplates) +loadTeamTemplates tOptions templatesDir defLocale sender = readLocalesDir defLocale templatesDir "team" $ \fp -> + TeamTemplates + <$> ( InvitationEmailTemplate tUrl + <$> readTemplate fp "email/invitation-subject.txt" + <*> readTemplate fp "email/invitation.txt" + <*> readTemplate fp "email/invitation.html" + <*> pure sender + <*> readText fp "email/sender.txt" + ) + <*> ( InvitationEmailTemplate tExistingUrl + <$> readTemplate fp "email/migration-subject.txt" + <*> readTemplate fp "email/migration.txt" + <*> readTemplate fp "email/migration.html" + <*> pure sender + <*> readText fp "email/sender.txt" + ) + <*> ( MemberWelcomeEmailTemplate (tMemberWelcomeUrl tOptions) + <$> readTemplate fp "email/new-member-welcome-subject.txt" + <*> readTemplate fp "email/new-member-welcome.txt" + <*> readTemplate fp "email/new-member-welcome.html" + <*> pure sender + <*> readText fp "email/sender.txt" + ) + <*> ( NewTeamOwnerWelcomeEmailTemplate (tCreatorWelcomeUrl tOptions) + <$> readTemplate fp "email/new-team-owner-welcome-subject.txt" + <*> readTemplate fp "email/new-team-owner-welcome.txt" + <*> readTemplate fp "email/new-team-owner-welcome.html" + <*> pure sender + <*> readText fp "email/sender.txt" + ) + <*> ( IdPConfigChangeEmailTemplate + <$> readTemplate fp "../partials/idp-certificate-added.html" + <*> readTemplate fp "../partials/idp-certificate-added.txt" + <*> readTemplate fp "../partials/idp-certificate-removed.html" + <*> readTemplate fp "../partials/idp-certificate-removed.txt" + <*> readTemplate fp "email/idp-config-change-subject.txt" + <*> readTemplate fp "email/idp-config-change.txt" + <*> readTemplate fp "email/idp-config-change.html" + <*> pure sender + <*> readText fp "email/sender.txt" + ) + where + tUrl = template tOptions.tInvitationUrl + tExistingUrl = template tOptions.tExistingUserInvitationUrl + readTemplate = readTemplateWithDefault templatesDir defLocale "team" + readText = readTextWithDefault templatesDir defLocale "team" diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 78f9b4d4f6d..531ea5c8d84 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -6,10 +6,9 @@ import Data.LegalHold (UserLegalHoldStatus (..)) import Data.Map qualified as Map import Data.Set qualified as Set import Data.Text.Lazy.Encoding (decodeUtf8) -import Data.Text.Template import Data.UUID qualified as UUID import Imports -import Network.Mail.Mime (Address (..), Disposition (..), Encoding (..), Mail (..), Part (..), PartContent (..)) +import Network.Mail.Mime (Address (..), Mail (..), Part (..), PartContent (..)) import Polysemy import Polysemy.State import SAML2.WebSSO @@ -46,7 +45,17 @@ spec = do it "should send an email" $ do idp :: IdP <- generate arbitrary storedUser :: StoredUser <- generate $ arbitrary `suchThat` (isJust . (.email)) - teamTemplates <- loadTeamTemplates + let teamOpts = + TeamOpts + { tInvitationUrl = "https://example.com/join/?team-code=${code}", + tExistingUserInvitationUrl = "https://example.com/accept-invitation/?team-code=${code}", + tActivationUrl = "https://example.com/verify/?key=${key}&code=${code}", + tCreatorWelcomeUrl = "https://example.com/creator-welcome-website", + tMemberWelcomeUrl = "https://example.com/member-welcome-website" + } + defLocale = Locale ((fromJust . parseLanguage) "en") Nothing + emailSender = unsafeEmailAddress "wire" "example.com" + teamTemplates <- loadTeamTemplates teamOpts "templates" defLocale emailSender let notif = IdPCreated (Just uid) idp' uid :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" teamId :: TeamId = either error Imports.id $ parseIdFromText "99f552d8-9dad-60c1-4be9-c88fb532893a" @@ -169,6 +178,7 @@ Privacy Policy and Terms of Use [https://wire.example.com/legal/]· Report misus © WIRE SWISS GmbH. All rights reserved.|] NestedParts ns -> error $ "Enexpected NestedParts: " ++ show ns +-- | Records logs and mails runInterpreters :: [StoredUser] -> Map TeamId [TeamMember] -> @@ -204,58 +214,3 @@ runInterpreters users teamMap teamTemplates branding action = do $ action logs <- readIORef lr.recordedLogs pure (mails, logs, res) - -loadTeamTemplates :: IO (Localised TeamTemplates) -loadTeamTemplates = readLocalesDir defLocale templateDir "team" $ \fp -> - TeamTemplates - <$> ( InvitationEmailTemplate tUrl - <$> readTemplate fp "email/invitation-subject.txt" - <*> readTemplate fp "email/invitation.txt" - <*> readTemplate fp "email/invitation.html" - <*> pure emailSender - <*> readText fp "email/sender.txt" - ) - <*> ( InvitationEmailTemplate tExistingUrl - <$> readTemplate fp "email/migration-subject.txt" - <*> readTemplate fp "email/migration.txt" - <*> readTemplate fp "email/migration.html" - <*> pure emailSender - <*> readText fp "email/sender.txt" - ) - <*> ( MemberWelcomeEmailTemplate memberWelcomeUrl - <$> readTemplate fp "email/new-member-welcome-subject.txt" - <*> readTemplate fp "email/new-member-welcome.txt" - <*> readTemplate fp "email/new-member-welcome.html" - <*> pure emailSender - <*> readText fp "email/sender.txt" - ) - <*> ( NewTeamOwnerWelcomeEmailTemplate creatorWelcomeUrl - <$> readTemplate fp "email/new-team-owner-welcome-subject.txt" - <*> readTemplate fp "email/new-team-owner-welcome.txt" - <*> readTemplate fp "email/new-team-owner-welcome.html" - <*> pure emailSender - <*> readText fp "email/sender.txt" - ) - <*> - -- TODO: Template paths - ( IdPConfigChangeEmailTemplate - <$> readTemplate fp "../partials/idp-certificate-added.html" - <*> readTemplate fp "../partials/idp-certificate-added.txt" - <*> readTemplate fp "../partials/idp-certificate-removed.html" - <*> readTemplate fp "../partials/idp-certificate-removed.txt" - <*> readTemplate fp "email/idp-config-change-subject.txt" - <*> readTemplate fp "email/idp-config-change.txt" - <*> readTemplate fp "email/idp-config-change.html" - <*> pure emailSender - <*> readText fp "email/sender.txt" - ) - where - memberWelcomeUrl = "https://example.com/member-welcome-website" - creatorWelcomeUrl = "https://example.com/creator-welcome-website" - emailSender = unsafeEmailAddress "wire" "example.com" - tUrl = template "https://example.com/join/?team-code=${code}" - tExistingUrl = template "https://example.com/accept-invitation/?team-code=${code}" - defLocale = Locale ((fromJust . parseLanguage) "en") Nothing - readTemplate = readTemplateWithDefault templateDir defLocale "team" - readText = readTextWithDefault templateDir defLocale "team" - templateDir = "templates" diff --git a/services/brig/src/Brig/App.hs b/services/brig/src/Brig/App.hs index cbdcbe1469f..649688f8a53 100644 --- a/services/brig/src/Brig/App.hs +++ b/services/brig/src/Brig/App.hs @@ -239,7 +239,7 @@ newEnv opts = do ext <- initExtGetManager utp <- loadUserTemplates opts ptp <- loadProviderTemplates opts - ttp <- loadTeamTemplates opts + ttp <- loadTeamTemplatesWithBrigOpts opts let branding = genTemplateBranding . Opt.templateBranding . Opt.general . Opt.emailSMS $ opts brandingAsMap = genTemplateBrandingMap . Opt.templateBranding . Opt.general . Opt.emailSMS $ opts (emailAWSOpts, emailSMTP) <- emailConn lgr $ Opt.email (Opt.emailSMS opts) diff --git a/services/brig/src/Brig/Options.hs b/services/brig/src/Brig/Options.hs index 2738d88c31a..8f01ca8394c 100644 --- a/services/brig/src/Brig/Options.hs +++ b/services/brig/src/Brig/Options.hs @@ -58,6 +58,7 @@ import Wire.API.User import Wire.AuthenticationSubsystem.Config (ZAuthSettings) import Wire.AuthenticationSubsystem.Cookie.Limit import Wire.EmailSending.SMTP (SMTPConnType (..)) +import Wire.EmailSubsystem.Template (TeamOpts) import Wire.RateLimit.Interpreter data ElasticSearchOpts = ElasticSearchOpts @@ -222,22 +223,6 @@ data ProviderOpts = ProviderOpts instance FromJSON ProviderOpts -data TeamOpts = TeamOpts - { -- | Team Invitation URL template - tInvitationUrl :: !Text, - -- | Existing User Invitation URL template - tExistingUserInvitationUrl :: !Text, - -- | Team Activation URL template - tActivationUrl :: !Text, - -- | Team Creator Welcome URL - tCreatorWelcomeUrl :: !Text, - -- | Team Member Welcome URL - tMemberWelcomeUrl :: !Text - } - deriving (Show, Generic) - -instance FromJSON TeamOpts - data EmailOpts = EmailAWS EmailAWSOpts | EmailSMTP EmailSMTPOpts diff --git a/services/brig/src/Brig/Team/Template.hs b/services/brig/src/Brig/Team/Template.hs index 477ac940160..a650b064b5a 100644 --- a/services/brig/src/Brig/Team/Template.hs +++ b/services/brig/src/Brig/Team/Template.hs @@ -19,63 +19,22 @@ module Brig.Team.Template ( TeamTemplates (..), InvitationEmailTemplate (..), MemberWelcomeEmailTemplate (..), - loadTeamTemplates, + loadTeamTemplatesWithBrigOpts, ) where import Brig.Options import Brig.Template -import Data.Text.Template import Imports +import Wire.EmailSubsystem.Template import Wire.EmailSubsystem.Templates.Team -loadTeamTemplates :: Opts -> IO (Localised TeamTemplates) -loadTeamTemplates o = readLocalesDir defLocale (templateDir gOptions) "team" $ \fp -> - TeamTemplates - <$> ( InvitationEmailTemplate tUrl - <$> readTemplate fp "email/invitation-subject.txt" - <*> readTemplate fp "email/invitation.txt" - <*> readTemplate fp "email/invitation.html" - <*> pure (emailSender gOptions) - <*> readText fp "email/sender.txt" - ) - <*> ( InvitationEmailTemplate tExistingUrl - <$> readTemplate fp "email/migration-subject.txt" - <*> readTemplate fp "email/migration.txt" - <*> readTemplate fp "email/migration.html" - <*> pure (emailSender gOptions) - <*> readText fp "email/sender.txt" - ) - <*> ( MemberWelcomeEmailTemplate (tMemberWelcomeUrl tOptions) - <$> readTemplate fp "email/new-member-welcome-subject.txt" - <*> readTemplate fp "email/new-member-welcome.txt" - <*> readTemplate fp "email/new-member-welcome.html" - <*> pure (emailSender gOptions) - <*> readText fp "email/sender.txt" - ) - <*> ( NewTeamOwnerWelcomeEmailTemplate (tCreatorWelcomeUrl tOptions) - <$> readTemplate fp "email/new-team-owner-welcome-subject.txt" - <*> readTemplate fp "email/new-team-owner-welcome.txt" - <*> readTemplate fp "email/new-team-owner-welcome.html" - <*> pure (emailSender gOptions) - <*> readText fp "email/sender.txt" - ) - <*> ( IdPConfigChangeEmailTemplate - <$> readTemplate fp "../partials/idp-certificate-added.html" - <*> readTemplate fp "../partials/idp-certificate-added.txt" - <*> readTemplate fp "../partials/idp-certificate-removed.html" - <*> readTemplate fp "../partials/idp-certificate-removed.txt" - <*> readTemplate fp "email/idp-config-change-subject.txt" - <*> readTemplate fp "email/idp-config-change.txt" - <*> readTemplate fp "email/idp-config-change.html" - <*> pure (emailSender gOptions) - <*> readText fp "email/sender.txt" - ) - where - gOptions = o.emailSMS.general - tOptions = o.emailSMS.team - tUrl = template tOptions.tInvitationUrl - tExistingUrl = template tOptions.tExistingUserInvitationUrl - defLocale = defaultTemplateLocale o.settings - readTemplate = readTemplateWithDefault (templateDir gOptions) defLocale "team" - readText = readTextWithDefault (templateDir gOptions) defLocale "team" +-- FUTUREWORK: This can be inlined once the `API.Template` have been migrated +-- to wire-subsystem unit tests. +loadTeamTemplatesWithBrigOpts :: Opts -> IO (Localised TeamTemplates) +loadTeamTemplatesWithBrigOpts o = + loadTeamTemplates + o.emailSMS.team + o.emailSMS.general.templateDir + (defaultTemplateLocale o.settings) + (emailSender o.emailSMS.general) diff --git a/services/brig/src/Brig/User/Template.hs b/services/brig/src/Brig/User/Template.hs index ff5304519e9..a7d7fa38585 100644 --- a/services/brig/src/Brig/User/Template.hs +++ b/services/brig/src/Brig/User/Template.hs @@ -21,6 +21,7 @@ import Brig.Options qualified as Opt import Brig.Template import Data.Text.Template import Imports +import Wire.EmailSubsystem.Template (TeamOpts (..)) import Wire.EmailSubsystem.Templates.User loadUserTemplates :: Opt.Opts -> IO (Localised UserTemplates) diff --git a/services/brig/test/integration/API/Template.hs b/services/brig/test/integration/API/Template.hs index d5ef52cc0e2..4c697b88ed5 100644 --- a/services/brig/test/integration/API/Template.hs +++ b/services/brig/test/integration/API/Template.hs @@ -2,7 +2,7 @@ module API.Template (tests) where import Bilge import Brig.Options -import Brig.Team.Template (loadTeamTemplates) +import Brig.Team.Template (loadTeamTemplatesWithBrigOpts) import Brig.Template import Brig.User.Template (loadUserTemplates) import Data.Code @@ -33,9 +33,12 @@ import Wire.EmailSubsystem.Template import Wire.EmailSubsystem.Templates.Team import Wire.EmailSubsystem.Templates.User +-- FUTUREWORK: This does not have to be an integration test. It could be +-- covered by unit tests in wire-subsystems. Then, the helper functions can be +-- privatized. tests :: Opts -> Manager -> IO TestTree tests opts m = do - team <- liftIO $ loadTeamTemplates opts + team <- liftIO $ loadTeamTemplatesWithBrigOpts opts user <- liftIO $ loadUserTemplates opts let teamTemplates = Map.assocs $ uncurry Map.insert team.locDefault team.locOther userTemplates = Map.assocs $ uncurry Map.insert user.locDefault user.locOther From fa10146bf47666d6ce3c13008ed2b8bb6857e877 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 10:05:39 +0100 Subject: [PATCH 24/60] Refactor --- .../Wire/SAMLEmailSubsystem/InterpreterSpec.hs | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 531ea5c8d84..c1bbfef0f9b 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -39,6 +39,10 @@ import Wire.TeamSubsystem import Wire.TeamSubsystem.GalleyAPI (interpretTeamSubsystemToGalleyAPI) import Wire.UserStore +-- TODO tests: +-- - Other local (found) +-- - Other local (not found) +-- - Update, Delete spec :: Spec spec = do describe "SendSAMLIdPChanged" $ do @@ -124,9 +128,12 @@ spec = do fromMaybe (error "No text part found") $ find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) case textPart.partContent of - PartContent content -> - (decodeUtf8 content) - `shouldBe` [r|[https://wire.example.com/p/img/email/logo-email-black.png] + PartContent content -> (decodeUtf8 content) `shouldBe` createTextEnglish + NestedParts ns -> error $ "Enexpected NestedParts: " ++ show ns + +createTextEnglish :: LText +createTextEnglish = + [r|[https://wire.example.com/p/img/email/logo-email-black.png] wire.example.com [https://wire.example.com] @@ -176,7 +183,6 @@ If you did not initiate this change, please reach out to the Wire support. Privacy Policy and Terms of Use [https://wire.example.com/legal/]· Report misuse [misuse@wire.example.com] © WIRE SWISS GmbH. All rights reserved.|] - NestedParts ns -> error $ "Enexpected NestedParts: " ++ show ns -- | Records logs and mails runInterpreters :: From 5991e9de946079edd926512359e0754075f017a4 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 10:54:18 +0100 Subject: [PATCH 25/60] Update German templates --- .../de/partials/idp-certificate-added.html | 1 + .../templates/de/partials/idp-certificate-added.txt | 13 +++++++++++++ .../de/partials/idp-certificate-removed.html | 1 + .../de/partials/idp-certificate-removed.txt | 13 +++++++++++++ .../templates/de/team/email/idp-config-change.html | 2 +- .../templates/de/team/email/idp-config-change.txt | 2 +- 6 files changed, 30 insertions(+), 2 deletions(-) create mode 100644 libs/wire-subsystems/templates/de/partials/idp-certificate-added.html create mode 100644 libs/wire-subsystems/templates/de/partials/idp-certificate-added.txt create mode 100644 libs/wire-subsystems/templates/de/partials/idp-certificate-removed.html create mode 100644 libs/wire-subsystems/templates/de/partials/idp-certificate-removed.txt diff --git a/libs/wire-subsystems/templates/de/partials/idp-certificate-added.html b/libs/wire-subsystems/templates/de/partials/idp-certificate-added.html new file mode 100644 index 00000000000..aa8f5ee9c84 --- /dev/null +++ b/libs/wire-subsystems/templates/de/partials/idp-certificate-added.html @@ -0,0 +1 @@ +

HinzugefĂ¼gt:

${algorithm} Fingerabdruck:
${fingerprint}

Betreff:
${subject}

Aussteller:
${issuer}


\ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/partials/idp-certificate-added.txt b/libs/wire-subsystems/templates/de/partials/idp-certificate-added.txt new file mode 100644 index 00000000000..341ae1d59ae --- /dev/null +++ b/libs/wire-subsystems/templates/de/partials/idp-certificate-added.txt @@ -0,0 +1,13 @@ +HinzugefĂ¼gt: + +${algorithm} Fingerabdruck: +${fingerprint} + +Betreff: +${subject} + +Aussteller: +${issuer} + + +-------------------------------------------------------------------------------- \ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/partials/idp-certificate-removed.html b/libs/wire-subsystems/templates/de/partials/idp-certificate-removed.html new file mode 100644 index 00000000000..f7e5c964d42 --- /dev/null +++ b/libs/wire-subsystems/templates/de/partials/idp-certificate-removed.html @@ -0,0 +1 @@ +

Entfernt:

${algorithm} Fingerabdruck:
${fingerprint}

Betreff:
${subject}

Aussteller:
${issuer}


\ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/partials/idp-certificate-removed.txt b/libs/wire-subsystems/templates/de/partials/idp-certificate-removed.txt new file mode 100644 index 00000000000..5469a02b7c1 --- /dev/null +++ b/libs/wire-subsystems/templates/de/partials/idp-certificate-removed.txt @@ -0,0 +1,13 @@ +Entfernt: + +${algorithm} Fingerabdruck: +${fingerprint} + +Betreff: +${subject} + +Aussteller: +${issuer} + + +-------------------------------------------------------------------------------- \ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/team/email/idp-config-change.html b/libs/wire-subsystems/templates/de/team/email/idp-config-change.html index 5b3a9759b17..b774cd1af75 100644 --- a/libs/wire-subsystems/templates/de/team/email/idp-config-change.html +++ b/libs/wire-subsystems/templates/de/team/email/idp-config-change.html @@ -1 +1 @@ -

${brand_label_url}

Änderung in der Konfiguration Ihres Identity Providers

Etwas hat sich in der IdP-Konfiguration fĂ¼r Ihr Team geändert.

Team-ID:
${teamId}

Benutzer-ID:
${userId}


Details:

IdP Aussteller:
${issuer}

IdP-Endpunkt:
${idpEndpoint}

IdP ID:
${idpId}


${certificatesDetails}

Wenn Sie diese Änderung nicht veranlasst haben, wenden Sie sich bitte an den Wire Support.

 

Datenschutzerklärung und Nutzungsbedingungen · Missbrauch melden
${copyright}. Alle Rechte vorbehalten.

                                                           
\ No newline at end of file +

${brand_label_url}

Änderung in der Konfiguration Ihres Identity Providers

Etwas hat sich in der IdP-Konfiguration fĂ¼r Ihr Team geändert.

Team-ID:
${teamId}

Benutzer-ID:
${userId}


Details:

IdP Aussteller:
${issuer}

IdP-Endpunkt:
${idpEndpoint}

IdP ID:
${idp_id}


${certificatesDetails}

Wenn Sie diese Änderung nicht veranlasst haben, wenden Sie sich bitte an den Wire Support.

 

Datenschutzerklärung und Nutzungsbedingungen · Missbrauch melden
${copyright}. Alle Rechte vorbehalten.

                                                           
\ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt b/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt index b3c25f19fcd..e8a9a0666d1 100644 --- a/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt +++ b/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt @@ -23,7 +23,7 @@ IdP-Endpunkt: ${idpendpoint} IdP ID: -${idpid} +${idp_id} -------------------------------------------------------------------------------- From 79f5a493525ab74c5ad0d9b8a9d5221b08c58bfc Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 10:54:26 +0100 Subject: [PATCH 26/60] Test locals --- .../Wire/SAMLEmailSubsystem/InterpreterSpec.hs | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index c1bbfef0f9b..318ff229912 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -1,4 +1,4 @@ -module Wire.SAMLEmailSubsystem.InterpreterSpec where +module Wire.SAMLEmailSubsystem.InterpreterSpec (spec) where import Data.Default import Data.Id @@ -18,7 +18,7 @@ import Test.QuickCheck (Arbitrary (arbitrary), generate, suchThat) import Text.Email.Parser (unsafeEmailAddress) import Text.RawString.QQ (r) import URI.ByteString -import Wire.API.Locale (Locale (..), parseLanguage) +import Wire.API.Locale import Wire.API.Routes.Internal.Brig (IdpChangedNotification (..)) import Wire.API.Team.Member import Wire.API.Team.Permission (fullPermissions) @@ -45,8 +45,9 @@ import Wire.UserStore -- - Update, Delete spec :: Spec spec = do + let testLocals :: [Locale] = fromMaybe (error "Unknown locale") . parseLocale <$> ["en", "en_EN", "en_GB", "es", "es_ES"] describe "SendSAMLIdPChanged" $ do - it "should send an email" $ do + it "should send an email on IdPCreated" $ forM_ testLocals $ \(userLocale :: Locale) -> do idp :: IdP <- generate arbitrary storedUser :: StoredUser <- generate $ arbitrary `suchThat` (isJust . (.email)) let teamOpts = @@ -63,7 +64,6 @@ spec = do let notif = IdPCreated (Just uid) idp' uid :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" teamId :: TeamId = either error Imports.id $ parseIdFromText "99f552d8-9dad-60c1-4be9-c88fb532893a" - lang = parseLanguage "en" idp' = idp { _idpId = IdPId . fromJust . UUID.fromString $ "574ddfb0-4e50-2bff-e924-33ee2b9f7064", @@ -81,8 +81,8 @@ spec = do (storedUser :: StoredUser) { id = uid, teamId = Just teamId, - language = lang, - country = Nothing, + language = Just userLocale.lLanguage, + country = userLocale.lCountry, email = Just $ unsafeEmailAddress "some-user" "example.com" } teamMember :: TeamMember = mkTeamMember uid fullPermissions Nothing UserLegalHoldDisabled @@ -128,11 +128,11 @@ spec = do fromMaybe (error "No text part found") $ find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) case textPart.partContent of - PartContent content -> (decodeUtf8 content) `shouldBe` createTextEnglish + PartContent content -> (decodeUtf8 content) `shouldBe` englishCreateMailContent NestedParts ns -> error $ "Enexpected NestedParts: " ++ show ns -createTextEnglish :: LText -createTextEnglish = +englishCreateMailContent :: LText +englishCreateMailContent = [r|[https://wire.example.com/p/img/email/logo-email-black.png] wire.example.com [https://wire.example.com] From 78ef42bd2b9e9e9d41c624d5478c1820b3088d53 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 11:47:37 +0100 Subject: [PATCH 27/60] Extract test data to files --- .../test/resources/mails/created_en.txt | 50 +++++++ .../test/resources/mails/deleted_en.txt | 50 +++++++ .../SAMLEmailSubsystem/InterpreterSpec.hs | 140 +++++++++++------- 3 files changed, 187 insertions(+), 53 deletions(-) create mode 100644 libs/wire-subsystems/test/resources/mails/created_en.txt create mode 100644 libs/wire-subsystems/test/resources/mails/deleted_en.txt diff --git a/libs/wire-subsystems/test/resources/mails/created_en.txt b/libs/wire-subsystems/test/resources/mails/created_en.txt new file mode 100644 index 00000000000..e6438445cbe --- /dev/null +++ b/libs/wire-subsystems/test/resources/mails/created_en.txt @@ -0,0 +1,50 @@ +[https://wire.example.com/p/img/email/logo-email-black.png] + +wire.example.com [https://wire.example.com] + +CHANGE IN YOUR IDENTITY PROVIDER CONFIGURATION +Something has changed in the IdP configuration for your team. + +Team ID: +99f552d8-9dad-60c1-4be9-c88fb532893a + +User ID: +4a1ce4ea-5c99-d01e-018f-4dc9d08f787a + + +-------------------------------------------------------------------------------- + +Details: + +IdP Issuer: +https://issuer.example.com/realm + +IdP Endpoint: +https://saml-endpoint.example.com/auth + +IdP ID: +574ddfb0-4e50-2bff-e924-33ee2b9f7064 + + +-------------------------------------------------------------------------------- + +Added: + +SHA1 fingerprint: +15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37 + +Subject: +CN=accounts.accesscontrol.windows.net + +Issuer: +CN=accounts.accesscontrol.windows.net + + +-------------------------------------------------------------------------------- + + +If you did not initiate this change, please reach out to the Wire support. +[https://support.wire.com/] + +Privacy Policy and Terms of Use [https://wire.example.com/legal/]· Report misuse [misuse@wire.example.com] +© WIRE SWISS GmbH. All rights reserved. diff --git a/libs/wire-subsystems/test/resources/mails/deleted_en.txt b/libs/wire-subsystems/test/resources/mails/deleted_en.txt new file mode 100644 index 00000000000..5576bc14190 --- /dev/null +++ b/libs/wire-subsystems/test/resources/mails/deleted_en.txt @@ -0,0 +1,50 @@ +[https://wire.example.com/p/img/email/logo-email-black.png] + +wire.example.com [https://wire.example.com] + +CHANGE IN YOUR IDENTITY PROVIDER CONFIGURATION +Something has changed in the IdP configuration for your team. + +Team ID: +99f552d8-9dad-60c1-4be9-c88fb532893a + +User ID: +4a1ce4ea-5c99-d01e-018f-4dc9d08f787a + + +-------------------------------------------------------------------------------- + +Details: + +IdP Issuer: +https://issuer.example.com/realm + +IdP Endpoint: +https://saml-endpoint.example.com/auth + +IdP ID: +574ddfb0-4e50-2bff-e924-33ee2b9f7064 + + +-------------------------------------------------------------------------------- + + +Removed: + +SHA1 fingerprint: +15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37 + +Subject: +CN=accounts.accesscontrol.windows.net + +Issuer: +CN=accounts.accesscontrol.windows.net + + +-------------------------------------------------------------------------------- + +If you did not initiate this change, please reach out to the Wire support. +[https://support.wire.com/] + +Privacy Policy and Terms of Use [https://wire.example.com/legal/]· Report misuse [misuse@wire.example.com] +© WIRE SWISS GmbH. All rights reserved. diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 318ff229912..e23c634ee70 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -5,7 +5,9 @@ import Data.Id import Data.LegalHold (UserLegalHoldStatus (..)) import Data.Map qualified as Map import Data.Set qualified as Set +import Data.Text.Lazy qualified as TL import Data.Text.Lazy.Encoding (decodeUtf8) +import Data.Text.Lazy.IO qualified as TL import Data.UUID qualified as UUID import Imports import Network.Mail.Mime (Address (..), Mail (..), Part (..), PartContent (..)) @@ -16,7 +18,6 @@ import System.Logger qualified as Logger import Test.Hspec import Test.QuickCheck (Arbitrary (arbitrary), generate, suchThat) import Text.Email.Parser (unsafeEmailAddress) -import Text.RawString.QQ (r) import URI.ByteString import Wire.API.Locale import Wire.API.Routes.Internal.Brig (IdpChangedNotification (..)) @@ -127,62 +128,95 @@ spec = do let textPart = fromMaybe (error "No text part found") $ find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) + englishCreateMailContent <- TL.stripEnd <$> TL.readFile "test/resources/mails/created_en.txt" case textPart.partContent of PartContent content -> (decodeUtf8 content) `shouldBe` englishCreateMailContent NestedParts ns -> error $ "Enexpected NestedParts: " ++ show ns -englishCreateMailContent :: LText -englishCreateMailContent = - [r|[https://wire.example.com/p/img/email/logo-email-black.png] - -wire.example.com [https://wire.example.com] - -CHANGE IN YOUR IDENTITY PROVIDER CONFIGURATION -Something has changed in the IdP configuration for your team. - -Team ID: -99f552d8-9dad-60c1-4be9-c88fb532893a - -User ID: -4a1ce4ea-5c99-d01e-018f-4dc9d08f787a - - --------------------------------------------------------------------------------- - -Details: - -IdP Issuer: -https://issuer.example.com/realm - -IdP Endpoint: -https://saml-endpoint.example.com/auth - -IdP ID: -574ddfb0-4e50-2bff-e924-33ee2b9f7064 - - --------------------------------------------------------------------------------- - -Added: - -SHA1 fingerprint: -15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37 - -Subject: -CN=accounts.accesscontrol.windows.net - -Issuer: -CN=accounts.accesscontrol.windows.net - - --------------------------------------------------------------------------------- - - -If you did not initiate this change, please reach out to the Wire support. -[https://support.wire.com/] - -Privacy Policy and Terms of Use [https://wire.example.com/legal/]· Report misuse [misuse@wire.example.com] -© WIRE SWISS GmbH. All rights reserved.|] + it "should send an email on IdPDeleted" $ forM_ testLocals $ \(userLocale :: Locale) -> do + idp :: IdP <- generate arbitrary + storedUser :: StoredUser <- generate $ arbitrary `suchThat` (isJust . (.email)) + let teamOpts = + TeamOpts + { tInvitationUrl = "https://example.com/join/?team-code=${code}", + tExistingUserInvitationUrl = "https://example.com/accept-invitation/?team-code=${code}", + tActivationUrl = "https://example.com/verify/?key=${key}&code=${code}", + tCreatorWelcomeUrl = "https://example.com/creator-welcome-website", + tMemberWelcomeUrl = "https://example.com/member-welcome-website" + } + defLocale = Locale ((fromJust . parseLanguage) "en") Nothing + emailSender = unsafeEmailAddress "wire" "example.com" + teamTemplates <- loadTeamTemplates teamOpts "templates" defLocale emailSender + let notif = IdPDeleted uid idp' + uid :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" + teamId :: TeamId = either error Imports.id $ parseIdFromText "99f552d8-9dad-60c1-4be9-c88fb532893a" + idp' = + idp + { _idpId = IdPId . fromJust . UUID.fromString $ "574ddfb0-4e50-2bff-e924-33ee2b9f7064", + _idpMetadata = + idp._idpMetadata + { _edIssuer = Issuer . either (error . show) Imports.id $ parseURI strictURIParserOptions "https://issuer.example.com/realm", + _edRequestURI = either (error . show) Imports.id $ parseURI strictURIParserOptions "https://saml-endpoint.example.com/auth" + }, + _idpExtraInfo = + idp._idpExtraInfo + { _team = teamId + } + } + storedUser' = + (storedUser :: StoredUser) + { id = uid, + teamId = Just teamId, + language = Just userLocale.lLanguage, + country = userLocale.lCountry, + email = Just $ unsafeEmailAddress "some-user" "example.com" + } + teamMember :: TeamMember = mkTeamMember uid fullPermissions Nothing UserLegalHoldDisabled + teamMap :: Map TeamId [TeamMember] = Map.singleton teamId [teamMember] + branding = + Map.fromList + [ ("brand", "Wire Test"), + ("brand_url", "https://wire.example.com"), + ("brand_label_url", "wire.example.com"), + ("brand_logo", "https://wire.example.com/p/img/email/logo-email-black.png"), + ("brand_service", "Wire Service Provider"), + ("copyright", "© WIRE SWISS GmbH"), + ("misuse", "misuse@wire.example.com"), + ("legal", "https://wire.example.com/legal/"), + ("forgot", "https://wire.example.com/forgot/"), + ("support", "https://support.wire.com/") + ] + (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do + sendSAMLIdPChanged notif + length mails `shouldBe` 1 + -- Templating issues are logged on level `Warn` + filter (\(level, _) -> level > Info) logs `shouldBe` mempty + let mail = head mails + mail.mailFrom + `shouldBe` Address + { addressName = Just "Wire", + addressEmail = "wire@example.com" + } + mail.mailTo + `shouldBe` [ Address + { addressName = Nothing, + addressEmail = "some-user@example.com" + } + ] + mail.mailCc `shouldBe` [] + mail.mailBcc `shouldBe` [] + Set.fromList mail.mailHeaders + `shouldBe` Set.fromList + [ ("Subject", "Your team's identity provider configuration has changed"), + ("X-Zeta-Purpose", "IdPConfigChange") + ] + let textPart = + fromMaybe (error "No text part found") $ + find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) + englishCreateMailContent <- TL.stripEnd <$> TL.readFile "test/resources/mails/deleted_en.txt" + case textPart.partContent of + PartContent content -> (decodeUtf8 content) `shouldBe` englishCreateMailContent + NestedParts ns -> error $ "Enexpected NestedParts: " ++ show ns -- | Records logs and mails runInterpreters :: From ec251afef9480c5f13c45b67fa2393845d716427 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 12:44:23 +0100 Subject: [PATCH 28/60] Reduce duplication --- .../test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs | 8 ++++++-- libs/wire-subsystems/wire-subsystems.cabal | 1 + 2 files changed, 7 insertions(+), 2 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index e23c634ee70..45354f8c851 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -14,6 +14,7 @@ import Network.Mail.Mime (Address (..), Mail (..), Part (..), PartContent (..)) import Polysemy import Polysemy.State import SAML2.WebSSO +import System.FilePath import System.Logger qualified as Logger import Test.Hspec import Test.QuickCheck (Arbitrary (arbitrary), generate, suchThat) @@ -128,7 +129,7 @@ spec = do let textPart = fromMaybe (error "No text part found") $ find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) - englishCreateMailContent <- TL.stripEnd <$> TL.readFile "test/resources/mails/created_en.txt" + englishCreateMailContent <- readTextPartFile "created_en.txt" case textPart.partContent of PartContent content -> (decodeUtf8 content) `shouldBe` englishCreateMailContent NestedParts ns -> error $ "Enexpected NestedParts: " ++ show ns @@ -213,11 +214,14 @@ spec = do let textPart = fromMaybe (error "No text part found") $ find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) - englishCreateMailContent <- TL.stripEnd <$> TL.readFile "test/resources/mails/deleted_en.txt" + englishCreateMailContent <- readTextPartFile "deleted_en.txt" case textPart.partContent of PartContent content -> (decodeUtf8 content) `shouldBe` englishCreateMailContent NestedParts ns -> error $ "Enexpected NestedParts: " ++ show ns +readTextPartFile :: FilePath -> IO TL.Text +readTextPartFile file = TL.stripEnd <$> TL.readFile ("test" "resources" "mails" file) + -- | Records logs and mails runInterpreters :: [StoredUser] -> diff --git a/libs/wire-subsystems/wire-subsystems.cabal b/libs/wire-subsystems/wire-subsystems.cabal index b5a749fc306..1b132693c1e 100644 --- a/libs/wire-subsystems/wire-subsystems.cabal +++ b/libs/wire-subsystems/wire-subsystems.cabal @@ -540,6 +540,7 @@ test-suite wire-subsystems-tests build-tool-depends: hspec-discover:hspec-discover build-depends: + , filepath , hspec , QuickCheck , quickcheck-instances From 1bbf494ef69316f056c4ea0073bc147cdc6f07c1 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 12:48:35 +0100 Subject: [PATCH 29/60] Extract assertCommmonMailAttributes --- .../SAMLEmailSubsystem/InterpreterSpec.hs | 59 ++++++++----------- 1 file changed, 23 insertions(+), 36 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 45354f8c851..e7dde9d4414 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -108,24 +108,7 @@ spec = do -- Templating issues are logged on level `Warn` filter (\(level, _) -> level > Info) logs `shouldBe` mempty let mail = head mails - mail.mailFrom - `shouldBe` Address - { addressName = Just "Wire", - addressEmail = "wire@example.com" - } - mail.mailTo - `shouldBe` [ Address - { addressName = Nothing, - addressEmail = "some-user@example.com" - } - ] - mail.mailCc `shouldBe` [] - mail.mailBcc `shouldBe` [] - Set.fromList mail.mailHeaders - `shouldBe` Set.fromList - [ ("Subject", "Your team's identity provider configuration has changed"), - ("X-Zeta-Purpose", "IdPConfigChange") - ] + assertCommonMailAttributes mail let textPart = fromMaybe (error "No text part found") $ find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) @@ -193,24 +176,7 @@ spec = do -- Templating issues are logged on level `Warn` filter (\(level, _) -> level > Info) logs `shouldBe` mempty let mail = head mails - mail.mailFrom - `shouldBe` Address - { addressName = Just "Wire", - addressEmail = "wire@example.com" - } - mail.mailTo - `shouldBe` [ Address - { addressName = Nothing, - addressEmail = "some-user@example.com" - } - ] - mail.mailCc `shouldBe` [] - mail.mailBcc `shouldBe` [] - Set.fromList mail.mailHeaders - `shouldBe` Set.fromList - [ ("Subject", "Your team's identity provider configuration has changed"), - ("X-Zeta-Purpose", "IdPConfigChange") - ] + assertCommonMailAttributes mail let textPart = fromMaybe (error "No text part found") $ find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) @@ -222,6 +188,27 @@ spec = do readTextPartFile :: FilePath -> IO TL.Text readTextPartFile file = TL.stripEnd <$> TL.readFile ("test" "resources" "mails" file) +assertCommonMailAttributes :: Mail -> IO () +assertCommonMailAttributes mail = do + mail.mailFrom + `shouldBe` Address + { addressName = Just "Wire", + addressEmail = "wire@example.com" + } + mail.mailTo + `shouldBe` [ Address + { addressName = Nothing, + addressEmail = "some-user@example.com" + } + ] + mail.mailCc `shouldBe` [] + mail.mailBcc `shouldBe` [] + Set.fromList mail.mailHeaders + `shouldBe` Set.fromList + [ ("Subject", "Your team's identity provider configuration has changed"), + ("X-Zeta-Purpose", "IdPConfigChange") + ] + -- | Records logs and mails runInterpreters :: [StoredUser] -> From d2753c70914eacdc6bc5ed7f195e23d7a9b9be7d Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 12:53:41 +0100 Subject: [PATCH 30/60] Extract assertMailTextPartWithFile --- .../SAMLEmailSubsystem/InterpreterSpec.hs | 26 +++++++++---------- 1 file changed, 12 insertions(+), 14 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index e7dde9d4414..4c71f9bca56 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -109,13 +109,7 @@ spec = do filter (\(level, _) -> level > Info) logs `shouldBe` mempty let mail = head mails assertCommonMailAttributes mail - let textPart = - fromMaybe (error "No text part found") $ - find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) - englishCreateMailContent <- readTextPartFile "created_en.txt" - case textPart.partContent of - PartContent content -> (decodeUtf8 content) `shouldBe` englishCreateMailContent - NestedParts ns -> error $ "Enexpected NestedParts: " ++ show ns + assertMailTextPartWithFile mail "created_en.txt" it "should send an email on IdPDeleted" $ forM_ testLocals $ \(userLocale :: Locale) -> do idp :: IdP <- generate arbitrary @@ -177,13 +171,7 @@ spec = do filter (\(level, _) -> level > Info) logs `shouldBe` mempty let mail = head mails assertCommonMailAttributes mail - let textPart = - fromMaybe (error "No text part found") $ - find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) - englishCreateMailContent <- readTextPartFile "deleted_en.txt" - case textPart.partContent of - PartContent content -> (decodeUtf8 content) `shouldBe` englishCreateMailContent - NestedParts ns -> error $ "Enexpected NestedParts: " ++ show ns + assertMailTextPartWithFile mail "deleted_en.txt" readTextPartFile :: FilePath -> IO TL.Text readTextPartFile file = TL.stripEnd <$> TL.readFile ("test" "resources" "mails" file) @@ -209,6 +197,16 @@ assertCommonMailAttributes mail = do ("X-Zeta-Purpose", "IdPConfigChange") ] +assertMailTextPartWithFile :: Mail -> FilePath -> IO () +assertMailTextPartWithFile mail renderedTextFile = do + let textPart = + fromMaybe (error "No text part found") $ + find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) + englishCreateMailContent <- readTextPartFile renderedTextFile + case textPart.partContent of + PartContent content -> (decodeUtf8 content) `shouldBe` englishCreateMailContent + NestedParts ns -> error $ "Enexpected NestedParts: " ++ show ns + -- | Records logs and mails runInterpreters :: [StoredUser] -> From 9e4946500a06de740b7bcc1c4abedfec82214c0a Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 12:56:14 +0100 Subject: [PATCH 31/60] Reduce duplication --- .../SAMLEmailSubsystem/InterpreterSpec.hs | 30 +++++++------------ 1 file changed, 10 insertions(+), 20 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 4c71f9bca56..5aa36e5c9d7 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -48,20 +48,20 @@ import Wire.UserStore spec :: Spec spec = do let testLocals :: [Locale] = fromMaybe (error "Unknown locale") . parseLocale <$> ["en", "en_EN", "en_GB", "es", "es_ES"] + teamOpts = + TeamOpts + { tInvitationUrl = "https://example.com/join/?team-code=${code}", + tExistingUserInvitationUrl = "https://example.com/accept-invitation/?team-code=${code}", + tActivationUrl = "https://example.com/verify/?key=${key}&code=${code}", + tCreatorWelcomeUrl = "https://example.com/creator-welcome-website", + tMemberWelcomeUrl = "https://example.com/member-welcome-website" + } + defLocale = Locale ((fromJust . parseLanguage) "en") Nothing + emailSender = unsafeEmailAddress "wire" "example.com" describe "SendSAMLIdPChanged" $ do it "should send an email on IdPCreated" $ forM_ testLocals $ \(userLocale :: Locale) -> do idp :: IdP <- generate arbitrary storedUser :: StoredUser <- generate $ arbitrary `suchThat` (isJust . (.email)) - let teamOpts = - TeamOpts - { tInvitationUrl = "https://example.com/join/?team-code=${code}", - tExistingUserInvitationUrl = "https://example.com/accept-invitation/?team-code=${code}", - tActivationUrl = "https://example.com/verify/?key=${key}&code=${code}", - tCreatorWelcomeUrl = "https://example.com/creator-welcome-website", - tMemberWelcomeUrl = "https://example.com/member-welcome-website" - } - defLocale = Locale ((fromJust . parseLanguage) "en") Nothing - emailSender = unsafeEmailAddress "wire" "example.com" teamTemplates <- loadTeamTemplates teamOpts "templates" defLocale emailSender let notif = IdPCreated (Just uid) idp' uid :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" @@ -114,16 +114,6 @@ spec = do it "should send an email on IdPDeleted" $ forM_ testLocals $ \(userLocale :: Locale) -> do idp :: IdP <- generate arbitrary storedUser :: StoredUser <- generate $ arbitrary `suchThat` (isJust . (.email)) - let teamOpts = - TeamOpts - { tInvitationUrl = "https://example.com/join/?team-code=${code}", - tExistingUserInvitationUrl = "https://example.com/accept-invitation/?team-code=${code}", - tActivationUrl = "https://example.com/verify/?key=${key}&code=${code}", - tCreatorWelcomeUrl = "https://example.com/creator-welcome-website", - tMemberWelcomeUrl = "https://example.com/member-welcome-website" - } - defLocale = Locale ((fromJust . parseLanguage) "en") Nothing - emailSender = unsafeEmailAddress "wire" "example.com" teamTemplates <- loadTeamTemplates teamOpts "templates" defLocale emailSender let notif = IdPDeleted uid idp' uid :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" From 8a1a1e43717fe6534cf332e2e5748d49062cd5f8 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 13:22:44 +0100 Subject: [PATCH 32/60] Reduce duplication --- .../SAMLEmailSubsystem/InterpreterSpec.hs | 180 ++++++++---------- 1 file changed, 77 insertions(+), 103 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 5aa36e5c9d7..25e7c4d2160 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -58,110 +58,84 @@ spec = do } defLocale = Locale ((fromJust . parseLanguage) "en") Nothing emailSender = unsafeEmailAddress "wire" "example.com" - describe "SendSAMLIdPChanged" $ do - it "should send an email on IdPCreated" $ forM_ testLocals $ \(userLocale :: Locale) -> do - idp :: IdP <- generate arbitrary - storedUser :: StoredUser <- generate $ arbitrary `suchThat` (isJust . (.email)) - teamTemplates <- loadTeamTemplates teamOpts "templates" defLocale emailSender - let notif = IdPCreated (Just uid) idp' - uid :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" - teamId :: TeamId = either error Imports.id $ parseIdFromText "99f552d8-9dad-60c1-4be9-c88fb532893a" - idp' = - idp - { _idpId = IdPId . fromJust . UUID.fromString $ "574ddfb0-4e50-2bff-e924-33ee2b9f7064", - _idpMetadata = - idp._idpMetadata - { _edIssuer = Issuer . either (error . show) Imports.id $ parseURI strictURIParserOptions "https://issuer.example.com/realm", - _edRequestURI = either (error . show) Imports.id $ parseURI strictURIParserOptions "https://saml-endpoint.example.com/auth" - }, - _idpExtraInfo = - idp._idpExtraInfo - { _team = teamId - } - } - storedUser' = - (storedUser :: StoredUser) - { id = uid, - teamId = Just teamId, - language = Just userLocale.lLanguage, - country = userLocale.lCountry, - email = Just $ unsafeEmailAddress "some-user" "example.com" - } - teamMember :: TeamMember = mkTeamMember uid fullPermissions Nothing UserLegalHoldDisabled - teamMap :: Map TeamId [TeamMember] = Map.singleton teamId [teamMember] - branding = - Map.fromList - [ ("brand", "Wire Test"), - ("brand_url", "https://wire.example.com"), - ("brand_label_url", "wire.example.com"), - ("brand_logo", "https://wire.example.com/p/img/email/logo-email-black.png"), - ("brand_service", "Wire Service Provider"), - ("copyright", "© WIRE SWISS GmbH"), - ("misuse", "misuse@wire.example.com"), - ("legal", "https://wire.example.com/legal/"), - ("forgot", "https://wire.example.com/forgot/"), - ("support", "https://support.wire.com/") - ] - (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do - sendSAMLIdPChanged notif - length mails `shouldBe` 1 - -- Templating issues are logged on level `Warn` - filter (\(level, _) -> level > Info) logs `shouldBe` mempty - let mail = head mails - assertCommonMailAttributes mail - assertMailTextPartWithFile mail "created_en.txt" + uid :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" + teamId :: TeamId = either error Imports.id $ parseIdFromText "99f552d8-9dad-60c1-4be9-c88fb532893a" + teamMember :: TeamMember = mkTeamMember uid fullPermissions Nothing UserLegalHoldDisabled + teamMap :: Map TeamId [TeamMember] = Map.singleton teamId [teamMember] + branding = + Map.fromList + [ ("brand", "Wire Test"), + ("brand_url", "https://wire.example.com"), + ("brand_label_url", "wire.example.com"), + ("brand_logo", "https://wire.example.com/p/img/email/logo-email-black.png"), + ("brand_service", "Wire Service Provider"), + ("copyright", "© WIRE SWISS GmbH"), + ("misuse", "misuse@wire.example.com"), + ("legal", "https://wire.example.com/legal/"), + ("forgot", "https://wire.example.com/forgot/"), + ("support", "https://support.wire.com/") + ] + describe "SendSAMLIdPChanged" $ forM_ testLocals $ \(userLocale :: Locale) -> do + context (show userLocale) do + it "should send an email on IdPCreated" $ do + idp :: IdP <- liftIO $ generate arbitrary + storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) + let idp' = patchIdP idp teamId + storedUser' = patchStoredUser storedUser teamId userLocale uid - it "should send an email on IdPDeleted" $ forM_ testLocals $ \(userLocale :: Locale) -> do - idp :: IdP <- generate arbitrary - storedUser :: StoredUser <- generate $ arbitrary `suchThat` (isJust . (.email)) - teamTemplates <- loadTeamTemplates teamOpts "templates" defLocale emailSender - let notif = IdPDeleted uid idp' - uid :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" - teamId :: TeamId = either error Imports.id $ parseIdFromText "99f552d8-9dad-60c1-4be9-c88fb532893a" - idp' = - idp - { _idpId = IdPId . fromJust . UUID.fromString $ "574ddfb0-4e50-2bff-e924-33ee2b9f7064", - _idpMetadata = - idp._idpMetadata - { _edIssuer = Issuer . either (error . show) Imports.id $ parseURI strictURIParserOptions "https://issuer.example.com/realm", - _edRequestURI = either (error . show) Imports.id $ parseURI strictURIParserOptions "https://saml-endpoint.example.com/auth" - }, - _idpExtraInfo = - idp._idpExtraInfo - { _team = teamId - } - } - storedUser' = - (storedUser :: StoredUser) - { id = uid, - teamId = Just teamId, - language = Just userLocale.lLanguage, - country = userLocale.lCountry, - email = Just $ unsafeEmailAddress "some-user" "example.com" - } - teamMember :: TeamMember = mkTeamMember uid fullPermissions Nothing UserLegalHoldDisabled - teamMap :: Map TeamId [TeamMember] = Map.singleton teamId [teamMember] - branding = - Map.fromList - [ ("brand", "Wire Test"), - ("brand_url", "https://wire.example.com"), - ("brand_label_url", "wire.example.com"), - ("brand_logo", "https://wire.example.com/p/img/email/logo-email-black.png"), - ("brand_service", "Wire Service Provider"), - ("copyright", "© WIRE SWISS GmbH"), - ("misuse", "misuse@wire.example.com"), - ("legal", "https://wire.example.com/legal/"), - ("forgot", "https://wire.example.com/forgot/"), - ("support", "https://support.wire.com/") - ] - (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do - sendSAMLIdPChanged notif - length mails `shouldBe` 1 - -- Templating issues are logged on level `Warn` - filter (\(level, _) -> level > Info) logs `shouldBe` mempty - let mail = head mails - assertCommonMailAttributes mail - assertMailTextPartWithFile mail "deleted_en.txt" + teamTemplates :: Localised TeamTemplates <- liftIO $ loadTeamTemplates teamOpts "templates" defLocale emailSender + + let notif = IdPCreated (Just uid) idp' + (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do + sendSAMLIdPChanged notif + length mails `shouldBe` 1 + -- Templating issues are logged on level `Warn` + filter (\(level, _) -> level > Info) logs `shouldBe` mempty + let mail = head mails + assertCommonMailAttributes mail + assertMailTextPartWithFile mail "created_en.txt" + + it "should send an email on IdPDeleted" $ do + idp :: IdP <- liftIO $ generate arbitrary + storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) + let idp' = patchIdP idp teamId + storedUser' = patchStoredUser storedUser teamId userLocale uid + + let notif = IdPDeleted uid idp' + teamTemplates :: Localised TeamTemplates <- liftIO $ loadTeamTemplates teamOpts "templates" defLocale emailSender + (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do + sendSAMLIdPChanged notif + length mails `shouldBe` 1 + -- Templating issues are logged on level `Warn` + filter (\(level, _) -> level > Info) logs `shouldBe` mempty + let mail = head mails + assertCommonMailAttributes mail + assertMailTextPartWithFile mail "deleted_en.txt" + +patchIdP :: IdPConfig WireIdP -> TeamId -> IdPConfig WireIdP +patchIdP idp teamId = + idp + { _idpId = IdPId . fromJust . UUID.fromString $ "574ddfb0-4e50-2bff-e924-33ee2b9f7064", + _idpMetadata = + idp._idpMetadata + { _edIssuer = Issuer . either (error . show) Imports.id $ parseURI strictURIParserOptions "https://issuer.example.com/realm", + _edRequestURI = either (error . show) Imports.id $ parseURI strictURIParserOptions "https://saml-endpoint.example.com/auth" + }, + _idpExtraInfo = + idp._idpExtraInfo + { _team = teamId + } + } + +patchStoredUser :: StoredUser -> TeamId -> Locale -> UserId -> StoredUser +patchStoredUser storedUser teamId userLocale uid = + (storedUser :: StoredUser) + { id = uid, + teamId = Just teamId, + language = Just userLocale.lLanguage, + country = userLocale.lCountry, + email = Just $ unsafeEmailAddress "some-user" "example.com" + } readTextPartFile :: FilePath -> IO TL.Text readTextPartFile file = TL.stripEnd <$> TL.readFile ("test" "resources" "mails" file) From 2929da094028eb4c5c357d019418729043c3acba Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 13:29:11 +0100 Subject: [PATCH 33/60] Formatting --- .../test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 25e7c4d2160..5a475d9026a 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -82,10 +82,10 @@ spec = do storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) let idp' = patchIdP idp teamId storedUser' = patchStoredUser storedUser teamId userLocale uid + notif = IdPCreated (Just uid) idp' teamTemplates :: Localised TeamTemplates <- liftIO $ loadTeamTemplates teamOpts "templates" defLocale emailSender - let notif = IdPCreated (Just uid) idp' (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do sendSAMLIdPChanged notif length mails `shouldBe` 1 @@ -100,8 +100,7 @@ spec = do storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) let idp' = patchIdP idp teamId storedUser' = patchStoredUser storedUser teamId userLocale uid - - let notif = IdPDeleted uid idp' + notif = IdPDeleted uid idp' teamTemplates :: Localised TeamTemplates <- liftIO $ loadTeamTemplates teamOpts "templates" defLocale emailSender (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do sendSAMLIdPChanged notif From f40d874963fc224d742637e17437370c5020ea49 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 13:29:17 +0100 Subject: [PATCH 34/60] Fix locale string --- .../test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 5a475d9026a..0d71a564de9 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -47,7 +47,7 @@ import Wire.UserStore -- - Update, Delete spec :: Spec spec = do - let testLocals :: [Locale] = fromMaybe (error "Unknown locale") . parseLocale <$> ["en", "en_EN", "en_GB", "es", "es_ES"] + let testLocals :: [Locale] = fromMaybe (error "Unknown locale") . parseLocale <$> ["en", "en-EN", "en-GB", "es", "es-ES"] teamOpts = TeamOpts { tInvitationUrl = "https://example.com/join/?team-code=${code}", From 5cf9396d0e2b382176273534db586487fcbe0446 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 14:09:41 +0100 Subject: [PATCH 35/60] WIP: Update test --- .../test/resources/mails/updated_en.txt | 37 +++++++++++++++++++ .../SAMLEmailSubsystem/InterpreterSpec.hs | 22 ++++++++++- 2 files changed, 57 insertions(+), 2 deletions(-) create mode 100644 libs/wire-subsystems/test/resources/mails/updated_en.txt diff --git a/libs/wire-subsystems/test/resources/mails/updated_en.txt b/libs/wire-subsystems/test/resources/mails/updated_en.txt new file mode 100644 index 00000000000..f4cdb9db92d --- /dev/null +++ b/libs/wire-subsystems/test/resources/mails/updated_en.txt @@ -0,0 +1,37 @@ +[https://wire.example.com/p/img/email/logo-email-black.png] + +wire.example.com [https://wire.example.com] + +CHANGE IN YOUR IDENTITY PROVIDER CONFIGURATION +Something has changed in the IdP configuration for your team. + +Team ID: +99f552d8-9dad-60c1-4be9-c88fb532893a + +User ID: +4a1ce4ea-5c99-d01e-018f-4dc9d08f787a + + +-------------------------------------------------------------------------------- + +Details: + +IdP Issuer: +https://issuer.example.com/realm + +IdP Endpoint: +https://saml-endpoint.example.com/auth + +IdP ID: +574ddfb0-4e50-2bff-e924-33ee2b9f7064 + + +-------------------------------------------------------------------------------- + + + +If you did not initiate this change, please reach out to the Wire support. +[https://support.wire.com/] + +Privacy Policy and Terms of Use [https://wire.example.com/legal/]· Report misuse [misuse@wire.example.com] +© WIRE SWISS GmbH. All rights reserved. diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 0d71a564de9..4a73a610265 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -43,8 +43,8 @@ import Wire.UserStore -- TODO tests: -- - Other local (found) --- - Other local (not found) --- - Update, Delete +-- - Update +-- No admin user spec :: Spec spec = do let testLocals :: [Locale] = fromMaybe (error "Unknown locale") . parseLocale <$> ["en", "en-EN", "en-GB", "es", "es-ES"] @@ -111,6 +111,24 @@ spec = do assertCommonMailAttributes mail assertMailTextPartWithFile mail "deleted_en.txt" + it "should send an email on IdPUpdated" $ do + idp :: IdP <- liftIO $ generate arbitrary + idp2 :: IdP <- liftIO $ generate arbitrary + storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) + let idp' = patchIdP idp teamId + idp2' = patchIdP idp teamId + storedUser' = patchStoredUser storedUser teamId userLocale uid + notif = IdPUpdated uid idp' idp2' + teamTemplates :: Localised TeamTemplates <- liftIO $ loadTeamTemplates teamOpts "templates" defLocale emailSender + (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do + sendSAMLIdPChanged notif + length mails `shouldBe` 1 + -- Templating issues are logged on level `Warn` + filter (\(level, _) -> level > Info) logs `shouldBe` mempty + let mail = head mails + assertCommonMailAttributes mail + assertMailTextPartWithFile mail "updated_en.txt" + patchIdP :: IdPConfig WireIdP -> TeamId -> IdPConfig WireIdP patchIdP idp teamId = idp From c505bbfbe29d28ae48ba47fc9916aa89247646b6 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 17:11:20 +0100 Subject: [PATCH 36/60] Test update --- libs/wire-subsystems/default.nix | 7 +++ .../test/resources/mails/updated_en.txt | 39 ++++++++++++++++ .../test/resources/saml/cert1.pem | 22 ++++++++++ .../test/resources/saml/cert2.pem | 22 ++++++++++ .../test/resources/saml/certs.store | 44 +++++++++++++++++++ .../test/resources/saml/generate-certs.sh | 10 +++++ .../test/resources/saml/mykey.pem | 28 ++++++++++++ .../test/resources/saml/okta-keyinfo-1.xml | 21 +++++++++ .../SAMLEmailSubsystem/InterpreterSpec.hs | 11 ++++- libs/wire-subsystems/wire-subsystems.cabal | 2 + 10 files changed, 205 insertions(+), 1 deletion(-) create mode 100644 libs/wire-subsystems/test/resources/saml/cert1.pem create mode 100644 libs/wire-subsystems/test/resources/saml/cert2.pem create mode 100644 libs/wire-subsystems/test/resources/saml/certs.store create mode 100755 libs/wire-subsystems/test/resources/saml/generate-certs.sh create mode 100644 libs/wire-subsystems/test/resources/saml/mykey.pem create mode 100644 libs/wire-subsystems/test/resources/saml/okta-keyinfo-1.xml diff --git a/libs/wire-subsystems/default.nix b/libs/wire-subsystems/default.nix index cf381ee0da6..12d832b4fce 100644 --- a/libs/wire-subsystems/default.nix +++ b/libs/wire-subsystems/default.nix @@ -28,6 +28,8 @@ , contravariant , cql , crypton +, crypton-x509 +, crypton-x509-store , currency-codes , data-default , data-timeout @@ -37,6 +39,7 @@ , extended , extra , file-embed +, filepath , galley-types , generics-sop , gitignoreSource @@ -156,6 +159,7 @@ mkDerivation { contravariant cql crypton + crypton-x509 currency-codes data-default data-timeout @@ -272,6 +276,8 @@ mkDerivation { contravariant cql crypton + crypton-x509 + crypton-x509-store currency-codes data-default data-timeout @@ -281,6 +287,7 @@ mkDerivation { extended extra file-embed + filepath galley-types generics-sop hashable diff --git a/libs/wire-subsystems/test/resources/mails/updated_en.txt b/libs/wire-subsystems/test/resources/mails/updated_en.txt index f4cdb9db92d..43d25af297f 100644 --- a/libs/wire-subsystems/test/resources/mails/updated_en.txt +++ b/libs/wire-subsystems/test/resources/mails/updated_en.txt @@ -28,7 +28,46 @@ IdP ID: -------------------------------------------------------------------------------- +Added: +SHA1 fingerprint: +54:51:B1:89:6A:A5:1A:A6:21:9B:33:17:49:05:6E:2A:86:62:22:33 + +Subject: +Country=US,O=ExampleOrg,OU=Dev1CN=CertOne,Email Address=one@example.com + +Issuer: +Country=US,O=ExampleOrg,OU=Dev1CN=CertOne,Email Address=one@example.com + + +-------------------------------------------------------------------------------- +Added: + +SHA1 fingerprint: +A8:0F:35:E2:94:8D:29:20:87:B2:59:3E:E2:4B:98:55:2B:65:B6:49 + +Subject: +Country=DE,O=ExampleOrg,OU=Dev2,CN=CertTwo,Email Address=two@example.com + +Issuer: +Country=DE,O=ExampleOrg,OU=Dev2,CN=CertTwo,Email Address=two@example.com + + +-------------------------------------------------------------------------------- + +Removed: + +SHA1 fingerprint: +15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37 + +Subject: +CN=accounts.accesscontrol.windows.net + +Issuer: +CN=accounts.accesscontrol.windows.net + + +-------------------------------------------------------------------------------- If you did not initiate this change, please reach out to the Wire support. [https://support.wire.com/] diff --git a/libs/wire-subsystems/test/resources/saml/cert1.pem b/libs/wire-subsystems/test/resources/saml/cert1.pem new file mode 100644 index 00000000000..7caa4cfc230 --- /dev/null +++ b/libs/wire-subsystems/test/resources/saml/cert1.pem @@ -0,0 +1,22 @@ +-----BEGIN CERTIFICATE----- +MIIDlzCCAn+gAwIBAgIUJMY57qbPTwE9zztSALHKIaDz3sgwDQYJKoZIhvcNAQEL +BQAwWzELMAkGA1UEBhMCVVMxEzARBgNVBAoMCkV4YW1wbGVPcmcxFzAVBgNVBAsM +DkRldjFDTj1DZXJ0T25lMR4wHAYJKoZIhvcNAQkBFg9vbmVAZXhhbXBsZS5jb20w +HhcNMjYwMTI3MTU0NDM5WhcNMzYwMTI1MTU0NDM5WjBbMQswCQYDVQQGEwJVUzET +MBEGA1UECgwKRXhhbXBsZU9yZzEXMBUGA1UECwwORGV2MUNOPUNlcnRPbmUxHjAc +BgkqhkiG9w0BCQEWD29uZUBleGFtcGxlLmNvbTCCASIwDQYJKoZIhvcNAQEBBQAD +ggEPADCCAQoCggEBAK5rbtLrTq6MnLllMC/eBfiPHrrBSHaFblSfdhUEl5AnVCGU +NQBGdBniH0qG7g8HW4mH/XIqW7+j2nTFAHgCZB69sx9DZHM9FvxsTPUG9+fsV5CO +p+mLgI4icIHUUWXYN2AQ6TTnWLWosL4AddG1Zhm8zuHqqYyyXrL0yPOIiY93ocG8 +sW9EDb/1bJi4LROdwe7v6BB7YhqVqqe7W8/BuMll2T5XSVV22NcazMb+E8BAJj9i +WqL0eVaZewpJRuJa+6io2RbVZneuX4YUQjXkzbaZe0GeAm28/E2YaDQGw+kmJ59S +vq5jdaN0wx8dW4Rjqc8tPvJKD6UEGLNbLEAT6ikCAwEAAaNTMFEwHQYDVR0OBBYE +FEEL3/og1lajIouKrJV+rW6XJMsjMB8GA1UdIwQYMBaAFEEL3/og1lajIouKrJV+ +rW6XJMsjMA8GA1UdEwEB/wQFMAMBAf8wDQYJKoZIhvcNAQELBQADggEBAD/lF2HD +NDgtIBhx0onU+WLJPsfibyMUxW8wLFivkSix8FpZAKUBcdUACMKrs8j+ObmmIo3U +Av/xUjdGlF36vS7WJpCmglwrjYaFQKQVuEc+0ssZ3E+3IZFskwDP5r00aWZQdqc3 +Tz57TDvhB4UMpBCa26k40ZTfLwpqqIlMMT1nw42dFyXcfOH0fC/EHI7emzmxgAWg +G+hGsZTGEqse1kToVPbag+0kmdoU2jW/iSylWpQByhoVno6lkBn4myKVzQT9zW/t +ZB8JY/izBJtDZ6tZi6oRIJXdM81p7KeBYe7OKdSHwokxHc86+tI5wDTslp3oM0XB +rJ1joP+m7UwHDEg= +-----END CERTIFICATE----- diff --git a/libs/wire-subsystems/test/resources/saml/cert2.pem b/libs/wire-subsystems/test/resources/saml/cert2.pem new file mode 100644 index 00000000000..0431018d8f4 --- /dev/null +++ b/libs/wire-subsystems/test/resources/saml/cert2.pem @@ -0,0 +1,22 @@ +-----BEGIN CERTIFICATE----- +MIIDpzCCAo+gAwIBAgIUTMuXC4z2pU0yxZ737ZnHSkBIXhswDQYJKoZIhvcNAQEL +BQAwYzELMAkGA1UEBhMCREUxEzARBgNVBAoMCkV4YW1wbGVPcmcxDTALBgNVBAsM +BERldjIxEDAOBgNVBAMMB0NlcnRUd28xHjAcBgkqhkiG9w0BCQEWD3R3b0BleGFt +cGxlLmNvbTAeFw0yNjAxMjcxNTQ0MzlaFw0zNjAxMjUxNTQ0MzlaMGMxCzAJBgNV +BAYTAkRFMRMwEQYDVQQKDApFeGFtcGxlT3JnMQ0wCwYDVQQLDAREZXYyMRAwDgYD +VQQDDAdDZXJ0VHdvMR4wHAYJKoZIhvcNAQkBFg90d29AZXhhbXBsZS5jb20wggEi +MA0GCSqGSIb3DQEBAQUAA4IBDwAwggEKAoIBAQCua27S606ujJy5ZTAv3gX4jx66 +wUh2hW5Un3YVBJeQJ1QhlDUARnQZ4h9Khu4PB1uJh/1yKlu/o9p0xQB4AmQevbMf +Q2RzPRb8bEz1Bvfn7FeQjqfpi4COInCB1FFl2DdgEOk051i1qLC+AHXRtWYZvM7h +6qmMsl6y9MjziImPd6HBvLFvRA2/9WyYuC0TncHu7+gQe2Ialaqnu1vPwbjJZdk+ +V0lVdtjXGszG/hPAQCY/Ylqi9HlWmXsKSUbiWvuoqNkW1WZ3rl+GFEI15M22mXtB +ngJtvPxNmGg0BsPpJiefUr6uY3WjdMMfHVuEY6nPLT7ySg+lBBizWyxAE+opAgMB +AAGjUzBRMB0GA1UdDgQWBBRBC9/6INZWoyKLiqyVfq1ulyTLIzAfBgNVHSMEGDAW +gBRBC9/6INZWoyKLiqyVfq1ulyTLIzAPBgNVHRMBAf8EBTADAQH/MA0GCSqGSIb3 +DQEBCwUAA4IBAQBWfJPmmwJ9anjpdQENzsAWOtJmGVZuQ899bLhNFKG1kecj5wIA +CdjSWynFzR6k66Kq53mf2YPG3sjyR+u+fRcxa4/QLqLGCu920o5sisPlytURU6cV +HXW5ZiImns8xT5fsohuVjtHEfzxh/G7jwh4XxMhisZxTEkj4M+rnByKFmVz675gp +D1EoxIY2yaXd1BtB2jTlMzkWH92f1uXzPPQNvhsB4nG1b282zvRqafqu7Cx2YWO/ +Oou/Q6lbe6JfxG32p4wuV3+jjGnep3WP88K7V9rsY7C014wCvP3ks29nIo/AY4u/ +Uvi2eQnet3DjY4lVLdmatamXJGf/8LA1lEGK +-----END CERTIFICATE----- diff --git a/libs/wire-subsystems/test/resources/saml/certs.store b/libs/wire-subsystems/test/resources/saml/certs.store new file mode 100644 index 00000000000..c6b64a142f6 --- /dev/null +++ b/libs/wire-subsystems/test/resources/saml/certs.store @@ -0,0 +1,44 @@ +-----BEGIN CERTIFICATE----- +MIIDlzCCAn+gAwIBAgIUJMY57qbPTwE9zztSALHKIaDz3sgwDQYJKoZIhvcNAQEL +BQAwWzELMAkGA1UEBhMCVVMxEzARBgNVBAoMCkV4YW1wbGVPcmcxFzAVBgNVBAsM +DkRldjFDTj1DZXJ0T25lMR4wHAYJKoZIhvcNAQkBFg9vbmVAZXhhbXBsZS5jb20w +HhcNMjYwMTI3MTU0NDM5WhcNMzYwMTI1MTU0NDM5WjBbMQswCQYDVQQGEwJVUzET +MBEGA1UECgwKRXhhbXBsZU9yZzEXMBUGA1UECwwORGV2MUNOPUNlcnRPbmUxHjAc +BgkqhkiG9w0BCQEWD29uZUBleGFtcGxlLmNvbTCCASIwDQYJKoZIhvcNAQEBBQAD +ggEPADCCAQoCggEBAK5rbtLrTq6MnLllMC/eBfiPHrrBSHaFblSfdhUEl5AnVCGU +NQBGdBniH0qG7g8HW4mH/XIqW7+j2nTFAHgCZB69sx9DZHM9FvxsTPUG9+fsV5CO +p+mLgI4icIHUUWXYN2AQ6TTnWLWosL4AddG1Zhm8zuHqqYyyXrL0yPOIiY93ocG8 +sW9EDb/1bJi4LROdwe7v6BB7YhqVqqe7W8/BuMll2T5XSVV22NcazMb+E8BAJj9i +WqL0eVaZewpJRuJa+6io2RbVZneuX4YUQjXkzbaZe0GeAm28/E2YaDQGw+kmJ59S +vq5jdaN0wx8dW4Rjqc8tPvJKD6UEGLNbLEAT6ikCAwEAAaNTMFEwHQYDVR0OBBYE +FEEL3/og1lajIouKrJV+rW6XJMsjMB8GA1UdIwQYMBaAFEEL3/og1lajIouKrJV+ +rW6XJMsjMA8GA1UdEwEB/wQFMAMBAf8wDQYJKoZIhvcNAQELBQADggEBAD/lF2HD +NDgtIBhx0onU+WLJPsfibyMUxW8wLFivkSix8FpZAKUBcdUACMKrs8j+ObmmIo3U +Av/xUjdGlF36vS7WJpCmglwrjYaFQKQVuEc+0ssZ3E+3IZFskwDP5r00aWZQdqc3 +Tz57TDvhB4UMpBCa26k40ZTfLwpqqIlMMT1nw42dFyXcfOH0fC/EHI7emzmxgAWg +G+hGsZTGEqse1kToVPbag+0kmdoU2jW/iSylWpQByhoVno6lkBn4myKVzQT9zW/t +ZB8JY/izBJtDZ6tZi6oRIJXdM81p7KeBYe7OKdSHwokxHc86+tI5wDTslp3oM0XB +rJ1joP+m7UwHDEg= +-----END CERTIFICATE----- +-----BEGIN CERTIFICATE----- +MIIDpzCCAo+gAwIBAgIUTMuXC4z2pU0yxZ737ZnHSkBIXhswDQYJKoZIhvcNAQEL +BQAwYzELMAkGA1UEBhMCREUxEzARBgNVBAoMCkV4YW1wbGVPcmcxDTALBgNVBAsM +BERldjIxEDAOBgNVBAMMB0NlcnRUd28xHjAcBgkqhkiG9w0BCQEWD3R3b0BleGFt +cGxlLmNvbTAeFw0yNjAxMjcxNTQ0MzlaFw0zNjAxMjUxNTQ0MzlaMGMxCzAJBgNV +BAYTAkRFMRMwEQYDVQQKDApFeGFtcGxlT3JnMQ0wCwYDVQQLDAREZXYyMRAwDgYD +VQQDDAdDZXJ0VHdvMR4wHAYJKoZIhvcNAQkBFg90d29AZXhhbXBsZS5jb20wggEi +MA0GCSqGSIb3DQEBAQUAA4IBDwAwggEKAoIBAQCua27S606ujJy5ZTAv3gX4jx66 +wUh2hW5Un3YVBJeQJ1QhlDUARnQZ4h9Khu4PB1uJh/1yKlu/o9p0xQB4AmQevbMf +Q2RzPRb8bEz1Bvfn7FeQjqfpi4COInCB1FFl2DdgEOk051i1qLC+AHXRtWYZvM7h +6qmMsl6y9MjziImPd6HBvLFvRA2/9WyYuC0TncHu7+gQe2Ialaqnu1vPwbjJZdk+ +V0lVdtjXGszG/hPAQCY/Ylqi9HlWmXsKSUbiWvuoqNkW1WZ3rl+GFEI15M22mXtB +ngJtvPxNmGg0BsPpJiefUr6uY3WjdMMfHVuEY6nPLT7ySg+lBBizWyxAE+opAgMB +AAGjUzBRMB0GA1UdDgQWBBRBC9/6INZWoyKLiqyVfq1ulyTLIzAfBgNVHSMEGDAW +gBRBC9/6INZWoyKLiqyVfq1ulyTLIzAPBgNVHRMBAf8EBTADAQH/MA0GCSqGSIb3 +DQEBCwUAA4IBAQBWfJPmmwJ9anjpdQENzsAWOtJmGVZuQ899bLhNFKG1kecj5wIA +CdjSWynFzR6k66Kq53mf2YPG3sjyR+u+fRcxa4/QLqLGCu920o5sisPlytURU6cV +HXW5ZiImns8xT5fsohuVjtHEfzxh/G7jwh4XxMhisZxTEkj4M+rnByKFmVz675gp +D1EoxIY2yaXd1BtB2jTlMzkWH92f1uXzPPQNvhsB4nG1b282zvRqafqu7Cx2YWO/ +Oou/Q6lbe6JfxG32p4wuV3+jjGnep3WP88K7V9rsY7C014wCvP3ks29nIo/AY4u/ +Uvi2eQnet3DjY4lVLdmatamXJGf/8LA1lEGK +-----END CERTIFICATE----- diff --git a/libs/wire-subsystems/test/resources/saml/generate-certs.sh b/libs/wire-subsystems/test/resources/saml/generate-certs.sh new file mode 100755 index 00000000000..e3a71030aa2 --- /dev/null +++ b/libs/wire-subsystems/test/resources/saml/generate-certs.sh @@ -0,0 +1,10 @@ +#!/usr/bin/env sh + +# Generate a key and certs for testing +openssl genpkey -algorithm RSA -out mykey.pem -pkeyopt rsa_keygen_bits:2048 +openssl req -new -x509 -key mykey.pem -out cert1.pem -days 3650 \ + -subj "/C=US/O=ExampleOrg/OU=Dev1CN=CertOne/emailAddress=one@example.com" +openssl req -new -x509 -key mykey.pem -out cert2.pem -days 3650 \ + -subj "/C=DE/O=ExampleOrg/OU=Dev2/CN=CertTwo/emailAddress=two@example.com" + +cat cert1.pem cert2.pem > certs.store diff --git a/libs/wire-subsystems/test/resources/saml/mykey.pem b/libs/wire-subsystems/test/resources/saml/mykey.pem new file mode 100644 index 00000000000..df4752c7ef6 --- /dev/null +++ b/libs/wire-subsystems/test/resources/saml/mykey.pem @@ -0,0 +1,28 @@ +-----BEGIN PRIVATE KEY----- +MIIEvAIBADANBgkqhkiG9w0BAQEFAASCBKYwggSiAgEAAoIBAQCua27S606ujJy5 +ZTAv3gX4jx66wUh2hW5Un3YVBJeQJ1QhlDUARnQZ4h9Khu4PB1uJh/1yKlu/o9p0 +xQB4AmQevbMfQ2RzPRb8bEz1Bvfn7FeQjqfpi4COInCB1FFl2DdgEOk051i1qLC+ +AHXRtWYZvM7h6qmMsl6y9MjziImPd6HBvLFvRA2/9WyYuC0TncHu7+gQe2Ialaqn +u1vPwbjJZdk+V0lVdtjXGszG/hPAQCY/Ylqi9HlWmXsKSUbiWvuoqNkW1WZ3rl+G +FEI15M22mXtBngJtvPxNmGg0BsPpJiefUr6uY3WjdMMfHVuEY6nPLT7ySg+lBBiz +WyxAE+opAgMBAAECggEAGYxL+eIUrtWS2UcclU5Yoo1YK3PHSPEHdaa71Z1MFAXm +uVprnwQy2l24RqLX+OSTgGQmeBQDR2FZTNRUWr/C6YvQ0mn9KzIODWBRr2xbYKHK +O7bhmoBgDrG1uBag66GNjuk7N5ARet5gMRyBJXwEHg39YbMNLbosy9q2GpHr0FMw +BRWO5Tf93QRlAVevqrIfNhKsP+Tr7UFU3N+XFCIAFRineG4p33k3VxRmzr9JzOkv +2kG0ieqtD41tg/CCXZ4Yh7HBLJVW6MgwlXCrMEBy6RhzCN95ntp1CpWIQnQGm9Xz +c7pCJMio0PknFoPMztXU7xYNC3LUea3VoLNugOdzVwKBgQDlkTNeKeUrA3jwicPj +EqEeteOU+5SBZPZBOSZibIjr1r8FTV75c33xpoHrUfEnvZxtUh5adfyZNyLK2U78 +a1z2U/83ryy93Nn0gvTBBwrT3ajeCJPCWJcOMs9DH6RB9p0Ewb9yG9KCeCYfQ0Ld +PCjh3oynx217MRRMSDsJ2F7rHwKBgQDCgK9oZeU14xTWrviHb9aZHEbCTIpKgqBh +0BF5qxcWH1dNTivXCGKexzZAfCDXeHkBpvC/m+o8QUQEYssAEiXmInqlFuTtuaRd +onwQ5jekp7bjPpmeMuGHgvL9vqBE6G1JfUxP6xHEaqGduH6gZnsVd1dlgvMW+rxH +7jzIpRJJtwKBgHv8xEWjUwa8RWGExqupsCOqEVSx3C9WnDn15+lYvUrDHUB73UPV +QLx3Ncwm4ZyZKBdTNtmcx+Tohn4QiDyEsBzKmRk2H3AcDAunfxGSACMVoNLqxwM8 +Xblpb8/NEyYdUAj1q7SxmiylP9G6vi5HA72aOVWUvGjAxTm9+UUD+5/5AoGAdrCA +WXyUemWv+bGcB0m/8n7GzxpV6VH8/LMzdsNoux807v+c0QNU6v81o/QbNmFVtiRh +FQvXzB0nnGWM6uYoKl8v6D4oRMjb/CeC/ez+V4Pgnps8ssTpyv+luCHzOxl6VzYW +s04G8Y0AQnarDsZ6pYbF1jQqkwM+kcZXYTkaB9ECgYAiJYbEiCU/3QeCv/8bxr65 +4IuHibDLjc584tLTl8rbLdeElAtDncmTnE80Iv2w0v/Vs28Ct6cGr4WRZ74P66i6 +auJnfeeBRmPpFx3XYJQzojcR4v9BIGeQTtwRVNpsZIXQv09WE1czF6/1HVeO7zDx +Ub16W5YorejB32u0QecYqg== +-----END PRIVATE KEY----- diff --git a/libs/wire-subsystems/test/resources/saml/okta-keyinfo-1.xml b/libs/wire-subsystems/test/resources/saml/okta-keyinfo-1.xml new file mode 100644 index 00000000000..5eacdb59013 --- /dev/null +++ b/libs/wire-subsystems/test/resources/saml/okta-keyinfo-1.xml @@ -0,0 +1,21 @@ + + +MIIDpDCCAoygAwIBAgIGAWSx7x1HMA0GCSqGSIb3DQEBCwUAMIGSMQswCQYDVQQGEwJVUzETMBEG +A1UECAwKQ2FsaWZvcm5pYTEWMBQGA1UEBwwNU2FuIEZyYW5jaXNjbzENMAsGA1UECgwET2t0YTEU +MBIGA1UECwwLU1NPUHJvdmlkZXIxEzARBgNVBAMMCmRldi01MDA1MDgxHDAaBgkqhkiG9w0BCQEW +DWluZm9Ab2t0YS5jb20wHhcNMTgwNzE5MDk0NTM1WhcNMjgwNzE5MDk0NjM0WjCBkjELMAkGA1UE +BhMCVVMxEzARBgNVBAgMCkNhbGlmb3JuaWExFjAUBgNVBAcMDVNhbiBGcmFuY2lzY28xDTALBgNV +BAoMBE9rdGExFDASBgNVBAsMC1NTT1Byb3ZpZGVyMRMwEQYDVQQDDApkZXYtNTAwNTA4MRwwGgYJ +KoZIhvcNAQkBFg1pbmZvQG9rdGEuY29tMIIBIjANBgkqhkiG9w0BAQEFAAOCAQ8AMIIBCgKCAQEA +hUaQm/3dgPws1A5IjFK9ZQpj170vIqENuDG0tapAzkvk6+9vyhduGckHTeZF3k5MMlW9iix2Eg0q +a1oS/Wrq/aBf7+BH6y1MJlQnaKQ3hPL+OFvYzbnrN8k2uC2LivP7Y90dXwtN3P63rA4QSyDPYEMv +dKSubUKX/HNsUg4I2PwHmpfWBNgoMkqe0bxQILBv+84L62IYSd6k77XXnCFb/usHpG/gY6sJsTQ2 +aFl9FuJ51uf67AOj8RzPXstgtUaXbdJI0kAqKIb3j9Zv3mpPCy/GHnyB3PMalvtc1uaz1ZnwO2el +iqhwB6/8W6CPutFo1Bhq1glQIX+1OD7906iORwIDAQABMA0GCSqGSIb3DQEBCwUAA4IBAQB0h6vK +AywJwH3g0RnocOpBvT42QW57TZ3Wzm9gbg6dQL0rB+NHDx2V0VIh51E3YHL1os9W09MreM7I74D/ +fX27r1Q3+qAsL1v3CN8WIVh9eYitBCtF7DwZmL2UXTia+GWPrabO14qAztFmTXfqNuCZej7gJd/K +2r0KBiZtZ6o58WBREW2F70a6nN6Nk1yjzBkDTJMMf8OMXHphTaalMBXojN9W6HEDpGBE0qY7c70P +qvfUEzd8wHWcDxo6+3jajajelk0V4rg7Cqxccr+WwjYtENEuQypNG2mbI52iPZked0QWKy0WzhSM +w5wjJ+QDG31vJInAB2769C2KmhPDyNhU + + diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 4a73a610265..ad3026a065a 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -3,12 +3,14 @@ module Wire.SAMLEmailSubsystem.InterpreterSpec (spec) where import Data.Default import Data.Id import Data.LegalHold (UserLegalHoldStatus (..)) +import Data.List.NonEmpty qualified as NE import Data.Map qualified as Map import Data.Set qualified as Set import Data.Text.Lazy qualified as TL import Data.Text.Lazy.Encoding (decodeUtf8) import Data.Text.Lazy.IO qualified as TL import Data.UUID qualified as UUID +import Data.X509.CertificateStore qualified as X509 import Imports import Network.Mail.Mime (Address (..), Mail (..), Part (..), PartContent (..)) import Polysemy @@ -114,9 +116,16 @@ spec = do it "should send an email on IdPUpdated" $ do idp :: IdP <- liftIO $ generate arbitrary idp2 :: IdP <- liftIO $ generate arbitrary + newCerts <- X509.readCertificates "test/resources/saml/certs.store" storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) let idp' = patchIdP idp teamId - idp2' = patchIdP idp teamId + idp2' = + (patchIdP idp2 teamId) + { _idpMetadata = + idp2._idpMetadata + { _edCertAuthnResponse = NE.fromList newCerts + } + } storedUser' = patchStoredUser storedUser teamId userLocale uid notif = IdPUpdated uid idp' idp2' teamTemplates :: Localised TeamTemplates <- liftIO $ loadTeamTemplates teamOpts "templates" defLocale emailSender diff --git a/libs/wire-subsystems/wire-subsystems.cabal b/libs/wire-subsystems/wire-subsystems.cabal index 1b132693c1e..ec8fb5eba2b 100644 --- a/libs/wire-subsystems/wire-subsystems.cabal +++ b/libs/wire-subsystems/wire-subsystems.cabal @@ -540,6 +540,8 @@ test-suite wire-subsystems-tests build-tool-depends: hspec-discover:hspec-discover build-depends: + , crypton-x509 + , crypton-x509-store , filepath , hspec , QuickCheck From 5275938f9524be1ec59b58db75037781a0140091 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 17:18:14 +0100 Subject: [PATCH 37/60] Update certs --- .../test/resources/mails/updated_en.txt | 8 +-- .../test/resources/saml/cert1.pem | 40 +++++------ .../test/resources/saml/cert2.pem | 32 ++++----- .../test/resources/saml/certs.store | 72 +++++++++---------- .../test/resources/saml/generate-certs.sh | 2 +- .../test/resources/saml/mykey.pem | 52 +++++++------- 6 files changed, 103 insertions(+), 103 deletions(-) diff --git a/libs/wire-subsystems/test/resources/mails/updated_en.txt b/libs/wire-subsystems/test/resources/mails/updated_en.txt index 43d25af297f..640dc8ae862 100644 --- a/libs/wire-subsystems/test/resources/mails/updated_en.txt +++ b/libs/wire-subsystems/test/resources/mails/updated_en.txt @@ -31,20 +31,20 @@ IdP ID: Added: SHA1 fingerprint: -54:51:B1:89:6A:A5:1A:A6:21:9B:33:17:49:05:6E:2A:86:62:22:33 +11:DE:AC:24:34:30:3D:05:81:02:77:26:41:3D:FC:09:01:92:E4:40 Subject: -Country=US,O=ExampleOrg,OU=Dev1CN=CertOne,Email Address=one@example.com +Country=US,O=ExampleOrg,OU=Dev1,CN=CertOne,Email Address=one@example.com Issuer: -Country=US,O=ExampleOrg,OU=Dev1CN=CertOne,Email Address=one@example.com +Country=US,O=ExampleOrg,OU=Dev1,CN=CertOne,Email Address=one@example.com -------------------------------------------------------------------------------- Added: SHA1 fingerprint: -A8:0F:35:E2:94:8D:29:20:87:B2:59:3E:E2:4B:98:55:2B:65:B6:49 +DF:CB:99:7D:C7:1A:4A:AC:D3:F6:94:22:97:07:6D:59:7B:BF:7B:57 Subject: Country=DE,O=ExampleOrg,OU=Dev2,CN=CertTwo,Email Address=two@example.com diff --git a/libs/wire-subsystems/test/resources/saml/cert1.pem b/libs/wire-subsystems/test/resources/saml/cert1.pem index 7caa4cfc230..5d47da663ea 100644 --- a/libs/wire-subsystems/test/resources/saml/cert1.pem +++ b/libs/wire-subsystems/test/resources/saml/cert1.pem @@ -1,22 +1,22 @@ -----BEGIN CERTIFICATE----- -MIIDlzCCAn+gAwIBAgIUJMY57qbPTwE9zztSALHKIaDz3sgwDQYJKoZIhvcNAQEL -BQAwWzELMAkGA1UEBhMCVVMxEzARBgNVBAoMCkV4YW1wbGVPcmcxFzAVBgNVBAsM -DkRldjFDTj1DZXJ0T25lMR4wHAYJKoZIhvcNAQkBFg9vbmVAZXhhbXBsZS5jb20w -HhcNMjYwMTI3MTU0NDM5WhcNMzYwMTI1MTU0NDM5WjBbMQswCQYDVQQGEwJVUzET -MBEGA1UECgwKRXhhbXBsZU9yZzEXMBUGA1UECwwORGV2MUNOPUNlcnRPbmUxHjAc -BgkqhkiG9w0BCQEWD29uZUBleGFtcGxlLmNvbTCCASIwDQYJKoZIhvcNAQEBBQAD -ggEPADCCAQoCggEBAK5rbtLrTq6MnLllMC/eBfiPHrrBSHaFblSfdhUEl5AnVCGU -NQBGdBniH0qG7g8HW4mH/XIqW7+j2nTFAHgCZB69sx9DZHM9FvxsTPUG9+fsV5CO -p+mLgI4icIHUUWXYN2AQ6TTnWLWosL4AddG1Zhm8zuHqqYyyXrL0yPOIiY93ocG8 -sW9EDb/1bJi4LROdwe7v6BB7YhqVqqe7W8/BuMll2T5XSVV22NcazMb+E8BAJj9i -WqL0eVaZewpJRuJa+6io2RbVZneuX4YUQjXkzbaZe0GeAm28/E2YaDQGw+kmJ59S -vq5jdaN0wx8dW4Rjqc8tPvJKD6UEGLNbLEAT6ikCAwEAAaNTMFEwHQYDVR0OBBYE -FEEL3/og1lajIouKrJV+rW6XJMsjMB8GA1UdIwQYMBaAFEEL3/og1lajIouKrJV+ -rW6XJMsjMA8GA1UdEwEB/wQFMAMBAf8wDQYJKoZIhvcNAQELBQADggEBAD/lF2HD -NDgtIBhx0onU+WLJPsfibyMUxW8wLFivkSix8FpZAKUBcdUACMKrs8j+ObmmIo3U -Av/xUjdGlF36vS7WJpCmglwrjYaFQKQVuEc+0ssZ3E+3IZFskwDP5r00aWZQdqc3 -Tz57TDvhB4UMpBCa26k40ZTfLwpqqIlMMT1nw42dFyXcfOH0fC/EHI7emzmxgAWg -G+hGsZTGEqse1kToVPbag+0kmdoU2jW/iSylWpQByhoVno6lkBn4myKVzQT9zW/t -ZB8JY/izBJtDZ6tZi6oRIJXdM81p7KeBYe7OKdSHwokxHc86+tI5wDTslp3oM0XB -rJ1joP+m7UwHDEg= +MIIDpzCCAo+gAwIBAgIUGPNyUrrhoMIonvkYvigqvqFF/3gwDQYJKoZIhvcNAQEL +BQAwYzELMAkGA1UEBhMCVVMxEzARBgNVBAoMCkV4YW1wbGVPcmcxDTALBgNVBAsM +BERldjExEDAOBgNVBAMMB0NlcnRPbmUxHjAcBgkqhkiG9w0BCQEWD29uZUBleGFt +cGxlLmNvbTAeFw0yNjAxMjcxNjE2MzFaFw0zNjAxMjUxNjE2MzFaMGMxCzAJBgNV +BAYTAlVTMRMwEQYDVQQKDApFeGFtcGxlT3JnMQ0wCwYDVQQLDAREZXYxMRAwDgYD +VQQDDAdDZXJ0T25lMR4wHAYJKoZIhvcNAQkBFg9vbmVAZXhhbXBsZS5jb20wggEi +MA0GCSqGSIb3DQEBAQUAA4IBDwAwggEKAoIBAQDxC0fakb82wXpg6b5rhjJT1tcX +hn+zY7HTs7oJxIGGmC/QZf9hTFkkp/ECQ6c3S7heSFjL3Rm7rH5+e4Oidfr6OCn4 +8sGR55a2i2gOkOKczyOOuOqshXVMzZvon358WuzDq7jWC4chmhliax6wLS3qZOYN +1tJ2hUFs2rchJVms1DOQl3bzldgdCn1U3Vr2JQfseuifrQxdkqJyCnyOzyLumRYf +4Jpakdbk0enmjRu9E/0utIhQ5pgS2Jt/rsSXOXxuW4SG2tTpJkhtrpPERSjlOnG6 +CRuY5ITbNhIqFI1nW8U7Duiie1qzxiO9rTGSEFH4kjQv365A2q1Ya+NjKZQlAgMB +AAGjUzBRMB0GA1UdDgQWBBTn6D8HS6JX+OK+GIf+PGKzFP7nfjAfBgNVHSMEGDAW +gBTn6D8HS6JX+OK+GIf+PGKzFP7nfjAPBgNVHRMBAf8EBTADAQH/MA0GCSqGSIb3 +DQEBCwUAA4IBAQBqCvchFQztrnCTLcr5fDVngbYzAw2YVnbxj6ufbU+rY+NsZM8T +RIybUmSntyiHoJ58H15ITkAu+dhwtBbEQ2iKMgBBvtAk152y+07weL1eFyTMnn2k +IYd8V+gvowidPcOL9TVgtZU57vwQ4hLngyl/scTbtbeYg4Nojpb4Wznyoliar0Ro +/uItPYd8I/ls4MIs429i3J22dybUQhiugqFsiAwus3NOwU8I7sr48DUQlGu84LdQ +ggGMYx//tNn4PH8HYAAP2icgypvKsLsiagSBbXB0AnJ7Ui8RPTm4880oeFTDJNKu +87XeJwRhFbVQZzubnw/4sf45ZdUfwtnVdbKW -----END CERTIFICATE----- diff --git a/libs/wire-subsystems/test/resources/saml/cert2.pem b/libs/wire-subsystems/test/resources/saml/cert2.pem index 0431018d8f4..fd1cc362f7b 100644 --- a/libs/wire-subsystems/test/resources/saml/cert2.pem +++ b/libs/wire-subsystems/test/resources/saml/cert2.pem @@ -1,22 +1,22 @@ -----BEGIN CERTIFICATE----- -MIIDpzCCAo+gAwIBAgIUTMuXC4z2pU0yxZ737ZnHSkBIXhswDQYJKoZIhvcNAQEL +MIIDpzCCAo+gAwIBAgIUPo/JjMajp0dK6m94JFl6f7k/FkUwDQYJKoZIhvcNAQEL BQAwYzELMAkGA1UEBhMCREUxEzARBgNVBAoMCkV4YW1wbGVPcmcxDTALBgNVBAsM BERldjIxEDAOBgNVBAMMB0NlcnRUd28xHjAcBgkqhkiG9w0BCQEWD3R3b0BleGFt -cGxlLmNvbTAeFw0yNjAxMjcxNTQ0MzlaFw0zNjAxMjUxNTQ0MzlaMGMxCzAJBgNV +cGxlLmNvbTAeFw0yNjAxMjcxNjE2MzFaFw0zNjAxMjUxNjE2MzFaMGMxCzAJBgNV BAYTAkRFMRMwEQYDVQQKDApFeGFtcGxlT3JnMQ0wCwYDVQQLDAREZXYyMRAwDgYD VQQDDAdDZXJ0VHdvMR4wHAYJKoZIhvcNAQkBFg90d29AZXhhbXBsZS5jb20wggEi -MA0GCSqGSIb3DQEBAQUAA4IBDwAwggEKAoIBAQCua27S606ujJy5ZTAv3gX4jx66 -wUh2hW5Un3YVBJeQJ1QhlDUARnQZ4h9Khu4PB1uJh/1yKlu/o9p0xQB4AmQevbMf -Q2RzPRb8bEz1Bvfn7FeQjqfpi4COInCB1FFl2DdgEOk051i1qLC+AHXRtWYZvM7h -6qmMsl6y9MjziImPd6HBvLFvRA2/9WyYuC0TncHu7+gQe2Ialaqnu1vPwbjJZdk+ -V0lVdtjXGszG/hPAQCY/Ylqi9HlWmXsKSUbiWvuoqNkW1WZ3rl+GFEI15M22mXtB -ngJtvPxNmGg0BsPpJiefUr6uY3WjdMMfHVuEY6nPLT7ySg+lBBizWyxAE+opAgMB -AAGjUzBRMB0GA1UdDgQWBBRBC9/6INZWoyKLiqyVfq1ulyTLIzAfBgNVHSMEGDAW -gBRBC9/6INZWoyKLiqyVfq1ulyTLIzAPBgNVHRMBAf8EBTADAQH/MA0GCSqGSIb3 -DQEBCwUAA4IBAQBWfJPmmwJ9anjpdQENzsAWOtJmGVZuQ899bLhNFKG1kecj5wIA -CdjSWynFzR6k66Kq53mf2YPG3sjyR+u+fRcxa4/QLqLGCu920o5sisPlytURU6cV -HXW5ZiImns8xT5fsohuVjtHEfzxh/G7jwh4XxMhisZxTEkj4M+rnByKFmVz675gp -D1EoxIY2yaXd1BtB2jTlMzkWH92f1uXzPPQNvhsB4nG1b282zvRqafqu7Cx2YWO/ -Oou/Q6lbe6JfxG32p4wuV3+jjGnep3WP88K7V9rsY7C014wCvP3ks29nIo/AY4u/ -Uvi2eQnet3DjY4lVLdmatamXJGf/8LA1lEGK +MA0GCSqGSIb3DQEBAQUAA4IBDwAwggEKAoIBAQDxC0fakb82wXpg6b5rhjJT1tcX +hn+zY7HTs7oJxIGGmC/QZf9hTFkkp/ECQ6c3S7heSFjL3Rm7rH5+e4Oidfr6OCn4 +8sGR55a2i2gOkOKczyOOuOqshXVMzZvon358WuzDq7jWC4chmhliax6wLS3qZOYN +1tJ2hUFs2rchJVms1DOQl3bzldgdCn1U3Vr2JQfseuifrQxdkqJyCnyOzyLumRYf +4Jpakdbk0enmjRu9E/0utIhQ5pgS2Jt/rsSXOXxuW4SG2tTpJkhtrpPERSjlOnG6 +CRuY5ITbNhIqFI1nW8U7Duiie1qzxiO9rTGSEFH4kjQv365A2q1Ya+NjKZQlAgMB +AAGjUzBRMB0GA1UdDgQWBBTn6D8HS6JX+OK+GIf+PGKzFP7nfjAfBgNVHSMEGDAW +gBTn6D8HS6JX+OK+GIf+PGKzFP7nfjAPBgNVHRMBAf8EBTADAQH/MA0GCSqGSIb3 +DQEBCwUAA4IBAQCW/X6PE9cLIHUkBbEBmar0X3GAjUIYuFnPem1ljKbk7G+1h2Q9 +Yr9ETBw4+1IfuiML6AgVKFzpxlP36Y5+pJ5sVr4z/O/mfN2NLMFlAyY9x9FPsP3/ +E9NptyMssZhc0L4JSw3XU8KqhZvC9FYOa61XPnpXh4veXXTY9CLslz0WG/G/Iprf +j5kkjpaw1Mt1A6hpyfhqokx4EgJENWWh70Txy+tPnuyL9LDF24CMuwgL9HugATQ+ +uZ4SyucS3OzPMciaY69xRP8afxqKczzdqv60cXhVJzf5PZmtgHQIuEawWX+cULsM +eSLnQV58FsPqgebqNpm0EQWAwYIKedhkul1B -----END CERTIFICATE----- diff --git a/libs/wire-subsystems/test/resources/saml/certs.store b/libs/wire-subsystems/test/resources/saml/certs.store index c6b64a142f6..0ce78139974 100644 --- a/libs/wire-subsystems/test/resources/saml/certs.store +++ b/libs/wire-subsystems/test/resources/saml/certs.store @@ -1,44 +1,44 @@ -----BEGIN CERTIFICATE----- -MIIDlzCCAn+gAwIBAgIUJMY57qbPTwE9zztSALHKIaDz3sgwDQYJKoZIhvcNAQEL -BQAwWzELMAkGA1UEBhMCVVMxEzARBgNVBAoMCkV4YW1wbGVPcmcxFzAVBgNVBAsM -DkRldjFDTj1DZXJ0T25lMR4wHAYJKoZIhvcNAQkBFg9vbmVAZXhhbXBsZS5jb20w -HhcNMjYwMTI3MTU0NDM5WhcNMzYwMTI1MTU0NDM5WjBbMQswCQYDVQQGEwJVUzET -MBEGA1UECgwKRXhhbXBsZU9yZzEXMBUGA1UECwwORGV2MUNOPUNlcnRPbmUxHjAc -BgkqhkiG9w0BCQEWD29uZUBleGFtcGxlLmNvbTCCASIwDQYJKoZIhvcNAQEBBQAD -ggEPADCCAQoCggEBAK5rbtLrTq6MnLllMC/eBfiPHrrBSHaFblSfdhUEl5AnVCGU -NQBGdBniH0qG7g8HW4mH/XIqW7+j2nTFAHgCZB69sx9DZHM9FvxsTPUG9+fsV5CO -p+mLgI4icIHUUWXYN2AQ6TTnWLWosL4AddG1Zhm8zuHqqYyyXrL0yPOIiY93ocG8 -sW9EDb/1bJi4LROdwe7v6BB7YhqVqqe7W8/BuMll2T5XSVV22NcazMb+E8BAJj9i -WqL0eVaZewpJRuJa+6io2RbVZneuX4YUQjXkzbaZe0GeAm28/E2YaDQGw+kmJ59S -vq5jdaN0wx8dW4Rjqc8tPvJKD6UEGLNbLEAT6ikCAwEAAaNTMFEwHQYDVR0OBBYE -FEEL3/og1lajIouKrJV+rW6XJMsjMB8GA1UdIwQYMBaAFEEL3/og1lajIouKrJV+ -rW6XJMsjMA8GA1UdEwEB/wQFMAMBAf8wDQYJKoZIhvcNAQELBQADggEBAD/lF2HD -NDgtIBhx0onU+WLJPsfibyMUxW8wLFivkSix8FpZAKUBcdUACMKrs8j+ObmmIo3U -Av/xUjdGlF36vS7WJpCmglwrjYaFQKQVuEc+0ssZ3E+3IZFskwDP5r00aWZQdqc3 -Tz57TDvhB4UMpBCa26k40ZTfLwpqqIlMMT1nw42dFyXcfOH0fC/EHI7emzmxgAWg -G+hGsZTGEqse1kToVPbag+0kmdoU2jW/iSylWpQByhoVno6lkBn4myKVzQT9zW/t -ZB8JY/izBJtDZ6tZi6oRIJXdM81p7KeBYe7OKdSHwokxHc86+tI5wDTslp3oM0XB -rJ1joP+m7UwHDEg= +MIIDpzCCAo+gAwIBAgIUGPNyUrrhoMIonvkYvigqvqFF/3gwDQYJKoZIhvcNAQEL +BQAwYzELMAkGA1UEBhMCVVMxEzARBgNVBAoMCkV4YW1wbGVPcmcxDTALBgNVBAsM +BERldjExEDAOBgNVBAMMB0NlcnRPbmUxHjAcBgkqhkiG9w0BCQEWD29uZUBleGFt +cGxlLmNvbTAeFw0yNjAxMjcxNjE2MzFaFw0zNjAxMjUxNjE2MzFaMGMxCzAJBgNV +BAYTAlVTMRMwEQYDVQQKDApFeGFtcGxlT3JnMQ0wCwYDVQQLDAREZXYxMRAwDgYD +VQQDDAdDZXJ0T25lMR4wHAYJKoZIhvcNAQkBFg9vbmVAZXhhbXBsZS5jb20wggEi +MA0GCSqGSIb3DQEBAQUAA4IBDwAwggEKAoIBAQDxC0fakb82wXpg6b5rhjJT1tcX +hn+zY7HTs7oJxIGGmC/QZf9hTFkkp/ECQ6c3S7heSFjL3Rm7rH5+e4Oidfr6OCn4 +8sGR55a2i2gOkOKczyOOuOqshXVMzZvon358WuzDq7jWC4chmhliax6wLS3qZOYN +1tJ2hUFs2rchJVms1DOQl3bzldgdCn1U3Vr2JQfseuifrQxdkqJyCnyOzyLumRYf +4Jpakdbk0enmjRu9E/0utIhQ5pgS2Jt/rsSXOXxuW4SG2tTpJkhtrpPERSjlOnG6 +CRuY5ITbNhIqFI1nW8U7Duiie1qzxiO9rTGSEFH4kjQv365A2q1Ya+NjKZQlAgMB +AAGjUzBRMB0GA1UdDgQWBBTn6D8HS6JX+OK+GIf+PGKzFP7nfjAfBgNVHSMEGDAW +gBTn6D8HS6JX+OK+GIf+PGKzFP7nfjAPBgNVHRMBAf8EBTADAQH/MA0GCSqGSIb3 +DQEBCwUAA4IBAQBqCvchFQztrnCTLcr5fDVngbYzAw2YVnbxj6ufbU+rY+NsZM8T +RIybUmSntyiHoJ58H15ITkAu+dhwtBbEQ2iKMgBBvtAk152y+07weL1eFyTMnn2k +IYd8V+gvowidPcOL9TVgtZU57vwQ4hLngyl/scTbtbeYg4Nojpb4Wznyoliar0Ro +/uItPYd8I/ls4MIs429i3J22dybUQhiugqFsiAwus3NOwU8I7sr48DUQlGu84LdQ +ggGMYx//tNn4PH8HYAAP2icgypvKsLsiagSBbXB0AnJ7Ui8RPTm4880oeFTDJNKu +87XeJwRhFbVQZzubnw/4sf45ZdUfwtnVdbKW -----END CERTIFICATE----- -----BEGIN CERTIFICATE----- -MIIDpzCCAo+gAwIBAgIUTMuXC4z2pU0yxZ737ZnHSkBIXhswDQYJKoZIhvcNAQEL +MIIDpzCCAo+gAwIBAgIUPo/JjMajp0dK6m94JFl6f7k/FkUwDQYJKoZIhvcNAQEL BQAwYzELMAkGA1UEBhMCREUxEzARBgNVBAoMCkV4YW1wbGVPcmcxDTALBgNVBAsM BERldjIxEDAOBgNVBAMMB0NlcnRUd28xHjAcBgkqhkiG9w0BCQEWD3R3b0BleGFt -cGxlLmNvbTAeFw0yNjAxMjcxNTQ0MzlaFw0zNjAxMjUxNTQ0MzlaMGMxCzAJBgNV +cGxlLmNvbTAeFw0yNjAxMjcxNjE2MzFaFw0zNjAxMjUxNjE2MzFaMGMxCzAJBgNV BAYTAkRFMRMwEQYDVQQKDApFeGFtcGxlT3JnMQ0wCwYDVQQLDAREZXYyMRAwDgYD VQQDDAdDZXJ0VHdvMR4wHAYJKoZIhvcNAQkBFg90d29AZXhhbXBsZS5jb20wggEi -MA0GCSqGSIb3DQEBAQUAA4IBDwAwggEKAoIBAQCua27S606ujJy5ZTAv3gX4jx66 -wUh2hW5Un3YVBJeQJ1QhlDUARnQZ4h9Khu4PB1uJh/1yKlu/o9p0xQB4AmQevbMf -Q2RzPRb8bEz1Bvfn7FeQjqfpi4COInCB1FFl2DdgEOk051i1qLC+AHXRtWYZvM7h -6qmMsl6y9MjziImPd6HBvLFvRA2/9WyYuC0TncHu7+gQe2Ialaqnu1vPwbjJZdk+ -V0lVdtjXGszG/hPAQCY/Ylqi9HlWmXsKSUbiWvuoqNkW1WZ3rl+GFEI15M22mXtB -ngJtvPxNmGg0BsPpJiefUr6uY3WjdMMfHVuEY6nPLT7ySg+lBBizWyxAE+opAgMB -AAGjUzBRMB0GA1UdDgQWBBRBC9/6INZWoyKLiqyVfq1ulyTLIzAfBgNVHSMEGDAW -gBRBC9/6INZWoyKLiqyVfq1ulyTLIzAPBgNVHRMBAf8EBTADAQH/MA0GCSqGSIb3 -DQEBCwUAA4IBAQBWfJPmmwJ9anjpdQENzsAWOtJmGVZuQ899bLhNFKG1kecj5wIA -CdjSWynFzR6k66Kq53mf2YPG3sjyR+u+fRcxa4/QLqLGCu920o5sisPlytURU6cV -HXW5ZiImns8xT5fsohuVjtHEfzxh/G7jwh4XxMhisZxTEkj4M+rnByKFmVz675gp -D1EoxIY2yaXd1BtB2jTlMzkWH92f1uXzPPQNvhsB4nG1b282zvRqafqu7Cx2YWO/ -Oou/Q6lbe6JfxG32p4wuV3+jjGnep3WP88K7V9rsY7C014wCvP3ks29nIo/AY4u/ -Uvi2eQnet3DjY4lVLdmatamXJGf/8LA1lEGK +MA0GCSqGSIb3DQEBAQUAA4IBDwAwggEKAoIBAQDxC0fakb82wXpg6b5rhjJT1tcX +hn+zY7HTs7oJxIGGmC/QZf9hTFkkp/ECQ6c3S7heSFjL3Rm7rH5+e4Oidfr6OCn4 +8sGR55a2i2gOkOKczyOOuOqshXVMzZvon358WuzDq7jWC4chmhliax6wLS3qZOYN +1tJ2hUFs2rchJVms1DOQl3bzldgdCn1U3Vr2JQfseuifrQxdkqJyCnyOzyLumRYf +4Jpakdbk0enmjRu9E/0utIhQ5pgS2Jt/rsSXOXxuW4SG2tTpJkhtrpPERSjlOnG6 +CRuY5ITbNhIqFI1nW8U7Duiie1qzxiO9rTGSEFH4kjQv365A2q1Ya+NjKZQlAgMB +AAGjUzBRMB0GA1UdDgQWBBTn6D8HS6JX+OK+GIf+PGKzFP7nfjAfBgNVHSMEGDAW +gBTn6D8HS6JX+OK+GIf+PGKzFP7nfjAPBgNVHRMBAf8EBTADAQH/MA0GCSqGSIb3 +DQEBCwUAA4IBAQCW/X6PE9cLIHUkBbEBmar0X3GAjUIYuFnPem1ljKbk7G+1h2Q9 +Yr9ETBw4+1IfuiML6AgVKFzpxlP36Y5+pJ5sVr4z/O/mfN2NLMFlAyY9x9FPsP3/ +E9NptyMssZhc0L4JSw3XU8KqhZvC9FYOa61XPnpXh4veXXTY9CLslz0WG/G/Iprf +j5kkjpaw1Mt1A6hpyfhqokx4EgJENWWh70Txy+tPnuyL9LDF24CMuwgL9HugATQ+ +uZ4SyucS3OzPMciaY69xRP8afxqKczzdqv60cXhVJzf5PZmtgHQIuEawWX+cULsM +eSLnQV58FsPqgebqNpm0EQWAwYIKedhkul1B -----END CERTIFICATE----- diff --git a/libs/wire-subsystems/test/resources/saml/generate-certs.sh b/libs/wire-subsystems/test/resources/saml/generate-certs.sh index e3a71030aa2..f9eea1b4b88 100755 --- a/libs/wire-subsystems/test/resources/saml/generate-certs.sh +++ b/libs/wire-subsystems/test/resources/saml/generate-certs.sh @@ -3,7 +3,7 @@ # Generate a key and certs for testing openssl genpkey -algorithm RSA -out mykey.pem -pkeyopt rsa_keygen_bits:2048 openssl req -new -x509 -key mykey.pem -out cert1.pem -days 3650 \ - -subj "/C=US/O=ExampleOrg/OU=Dev1CN=CertOne/emailAddress=one@example.com" + -subj "/C=US/O=ExampleOrg/OU=Dev1/CN=CertOne/emailAddress=one@example.com" openssl req -new -x509 -key mykey.pem -out cert2.pem -days 3650 \ -subj "/C=DE/O=ExampleOrg/OU=Dev2/CN=CertTwo/emailAddress=two@example.com" diff --git a/libs/wire-subsystems/test/resources/saml/mykey.pem b/libs/wire-subsystems/test/resources/saml/mykey.pem index df4752c7ef6..a44cc6bd0dc 100644 --- a/libs/wire-subsystems/test/resources/saml/mykey.pem +++ b/libs/wire-subsystems/test/resources/saml/mykey.pem @@ -1,28 +1,28 @@ -----BEGIN PRIVATE KEY----- -MIIEvAIBADANBgkqhkiG9w0BAQEFAASCBKYwggSiAgEAAoIBAQCua27S606ujJy5 -ZTAv3gX4jx66wUh2hW5Un3YVBJeQJ1QhlDUARnQZ4h9Khu4PB1uJh/1yKlu/o9p0 -xQB4AmQevbMfQ2RzPRb8bEz1Bvfn7FeQjqfpi4COInCB1FFl2DdgEOk051i1qLC+ -AHXRtWYZvM7h6qmMsl6y9MjziImPd6HBvLFvRA2/9WyYuC0TncHu7+gQe2Ialaqn -u1vPwbjJZdk+V0lVdtjXGszG/hPAQCY/Ylqi9HlWmXsKSUbiWvuoqNkW1WZ3rl+G -FEI15M22mXtBngJtvPxNmGg0BsPpJiefUr6uY3WjdMMfHVuEY6nPLT7ySg+lBBiz -WyxAE+opAgMBAAECggEAGYxL+eIUrtWS2UcclU5Yoo1YK3PHSPEHdaa71Z1MFAXm -uVprnwQy2l24RqLX+OSTgGQmeBQDR2FZTNRUWr/C6YvQ0mn9KzIODWBRr2xbYKHK -O7bhmoBgDrG1uBag66GNjuk7N5ARet5gMRyBJXwEHg39YbMNLbosy9q2GpHr0FMw -BRWO5Tf93QRlAVevqrIfNhKsP+Tr7UFU3N+XFCIAFRineG4p33k3VxRmzr9JzOkv -2kG0ieqtD41tg/CCXZ4Yh7HBLJVW6MgwlXCrMEBy6RhzCN95ntp1CpWIQnQGm9Xz -c7pCJMio0PknFoPMztXU7xYNC3LUea3VoLNugOdzVwKBgQDlkTNeKeUrA3jwicPj -EqEeteOU+5SBZPZBOSZibIjr1r8FTV75c33xpoHrUfEnvZxtUh5adfyZNyLK2U78 -a1z2U/83ryy93Nn0gvTBBwrT3ajeCJPCWJcOMs9DH6RB9p0Ewb9yG9KCeCYfQ0Ld -PCjh3oynx217MRRMSDsJ2F7rHwKBgQDCgK9oZeU14xTWrviHb9aZHEbCTIpKgqBh -0BF5qxcWH1dNTivXCGKexzZAfCDXeHkBpvC/m+o8QUQEYssAEiXmInqlFuTtuaRd -onwQ5jekp7bjPpmeMuGHgvL9vqBE6G1JfUxP6xHEaqGduH6gZnsVd1dlgvMW+rxH -7jzIpRJJtwKBgHv8xEWjUwa8RWGExqupsCOqEVSx3C9WnDn15+lYvUrDHUB73UPV -QLx3Ncwm4ZyZKBdTNtmcx+Tohn4QiDyEsBzKmRk2H3AcDAunfxGSACMVoNLqxwM8 -Xblpb8/NEyYdUAj1q7SxmiylP9G6vi5HA72aOVWUvGjAxTm9+UUD+5/5AoGAdrCA -WXyUemWv+bGcB0m/8n7GzxpV6VH8/LMzdsNoux807v+c0QNU6v81o/QbNmFVtiRh -FQvXzB0nnGWM6uYoKl8v6D4oRMjb/CeC/ez+V4Pgnps8ssTpyv+luCHzOxl6VzYW -s04G8Y0AQnarDsZ6pYbF1jQqkwM+kcZXYTkaB9ECgYAiJYbEiCU/3QeCv/8bxr65 -4IuHibDLjc584tLTl8rbLdeElAtDncmTnE80Iv2w0v/Vs28Ct6cGr4WRZ74P66i6 -auJnfeeBRmPpFx3XYJQzojcR4v9BIGeQTtwRVNpsZIXQv09WE1czF6/1HVeO7zDx -Ub16W5YorejB32u0QecYqg== +MIIEvAIBADANBgkqhkiG9w0BAQEFAASCBKYwggSiAgEAAoIBAQDxC0fakb82wXpg +6b5rhjJT1tcXhn+zY7HTs7oJxIGGmC/QZf9hTFkkp/ECQ6c3S7heSFjL3Rm7rH5+ +e4Oidfr6OCn48sGR55a2i2gOkOKczyOOuOqshXVMzZvon358WuzDq7jWC4chmhli +ax6wLS3qZOYN1tJ2hUFs2rchJVms1DOQl3bzldgdCn1U3Vr2JQfseuifrQxdkqJy +CnyOzyLumRYf4Jpakdbk0enmjRu9E/0utIhQ5pgS2Jt/rsSXOXxuW4SG2tTpJkht +rpPERSjlOnG6CRuY5ITbNhIqFI1nW8U7Duiie1qzxiO9rTGSEFH4kjQv365A2q1Y +a+NjKZQlAgMBAAECggEABVZdxnILZ7UmtmZRRZnom7ZPoqE4oFUY9xpCiHyAmRAz +StbfWJ0IrPOdC2hKbRfbosF7rzPw9xi4NP5w0+mZ35gxHGaVBlvi7fLYoINGc/jF +jZ+m7qAGkLyiyFFedcwg9FTlQwlpT23/7uUhU6mvG8K/3KxA58fxQsL1uCGsF9QQ +uTlDhmVh7ONYsB0KZQKXYHmturWqHQI4sLJHQ+simDld0jeUXIdZncPolLA4IIgG +qTTGdZk0h65j9nsIyuQYqPK9wS0b70bW52y8DKGe1MhmZrLJr4ZZ6NAPXpPnlpD1 +NyDbOJO2tq+kJVz08Maz8iJxsQHcgRRLRlZu3Ge2IQKBgQD+JaaQvi7M41JKWVPt +X/lHTBMDjcvV9HvmLyZvt0He0E6WtGMqO0X+m5zLJDiDMyPfoANiXNCGeV5WeIzd +ags0N0jC68/qE3V4De2O+76sy7n4g0WGqY/j/82h3SaH1IIAXZr1PSjXf4h1Pid9 +FO/1ruGVkNmK8Llb1pcm06Ub0QKBgQDyzSyR8dqYKJbYI3uUGALQ37onY+ZNBOrN +vYfS8eJDjhy9pfzDOLiEYf0bmJYEhCXyAIRXIqEdpRNtPh0uE7WMzSCRk/OVD5fK +au56adn99EwismxeGsAS0XnA5T2ctAHw1a2iSdfixuwBDqGcx4RB6fK+xAgEgrUH +TblbpuiMFQKBgDlA6iE5dvmZTHSLYyjasiGpta7bRsxQY4kbniEUu7YiX1H8GUru +R3pwPAZXhpOn9bDvL1P9bMyeku4QAkvvE88TlUS0Mwack54UJSxM8kujKaYejI8l +q9DFU+HfHEsFSLQkYkBVItpJVMh01BiNmvFSEGfNVfTC/j7+PNb2Xv/BAoGAU09R +Jracsa7jqz/pjDP861yIzDE7+VthkbyhmSDD6Tge5nfI1ddlgI76wPhHKT+KoZHJ +1vgb3kcg9k/kxUWf+rL7pNfmMVRLWfn83+XoFXo4kYM1Kcj19L8JjsVZsaYWMGOx +E0lRGQ/2NJqnm1reJ5u1Xf13XszWfq4NlsQbcM0CgYAx4oSxX6c+c9HmaAg1L5ZV +zCHMtQdoxoel4tFNpu4lTz5RBMZPQM02I2IlsP7hTRv66QA92C/kIs8JXvm7lPR4 +Ys+kMK2XNoIcMDzLQw74SldqVS+BQXPp/9QOdMAhae3mmeuWkrk34O/TW19OJWSX +DuYvVKofnhdVpIYS/38I2g== -----END PRIVATE KEY----- From 2549a672b9a7b6026cb30c646954a471507d24f3 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Tue, 27 Jan 2026 17:30:11 +0100 Subject: [PATCH 38/60] Speed up test --- .../unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index ad3026a065a..fbcc11ab40a 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -77,6 +77,11 @@ spec = do ("forgot", "https://wire.example.com/forgot/"), ("support", "https://support.wire.com/") ] + + -- Run duplicated IO tasks here to save some time + teamTemplates :: Localised TeamTemplates <- runIO $ loadTeamTemplates teamOpts "templates" defLocale emailSender + newCerts <- runIO $ X509.readCertificates "test/resources/saml/certs.store" + describe "SendSAMLIdPChanged" $ forM_ testLocals $ \(userLocale :: Locale) -> do context (show userLocale) do it "should send an email on IdPCreated" $ do @@ -86,8 +91,6 @@ spec = do storedUser' = patchStoredUser storedUser teamId userLocale uid notif = IdPCreated (Just uid) idp' - teamTemplates :: Localised TeamTemplates <- liftIO $ loadTeamTemplates teamOpts "templates" defLocale emailSender - (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do sendSAMLIdPChanged notif length mails `shouldBe` 1 @@ -103,7 +106,6 @@ spec = do let idp' = patchIdP idp teamId storedUser' = patchStoredUser storedUser teamId userLocale uid notif = IdPDeleted uid idp' - teamTemplates :: Localised TeamTemplates <- liftIO $ loadTeamTemplates teamOpts "templates" defLocale emailSender (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do sendSAMLIdPChanged notif length mails `shouldBe` 1 @@ -116,7 +118,6 @@ spec = do it "should send an email on IdPUpdated" $ do idp :: IdP <- liftIO $ generate arbitrary idp2 :: IdP <- liftIO $ generate arbitrary - newCerts <- X509.readCertificates "test/resources/saml/certs.store" storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) let idp' = patchIdP idp teamId idp2' = @@ -128,7 +129,6 @@ spec = do } storedUser' = patchStoredUser storedUser teamId userLocale uid notif = IdPUpdated uid idp' idp2' - teamTemplates :: Localised TeamTemplates <- liftIO $ loadTeamTemplates teamOpts "templates" defLocale emailSender (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do sendSAMLIdPChanged notif length mails `shouldBe` 1 From 1df3ffd00008558c3b261fca37bcf693c55d7953 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 11:34:51 +0100 Subject: [PATCH 39/60] Cleanup templates folder --- .../idp-certificate-added-subject.txt | 0 .../certificates/idp-certificate-added.html | 1 - .../certificates/idp-certificate-added.txt | 17 ----------------- .../idp-certificate-removed-subject.txt | 0 .../certificates/idp-certificate-removed.html | 1 - .../certificates/idp-certificate-removed.txt | 17 ----------------- 6 files changed, 36 deletions(-) delete mode 100644 libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added-subject.txt delete mode 100644 libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.html delete mode 100644 libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.txt delete mode 100644 libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed-subject.txt delete mode 100644 libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.html delete mode 100644 libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.txt diff --git a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added-subject.txt b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added-subject.txt deleted file mode 100644 index e69de29bb2d..00000000000 diff --git a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.html b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.html deleted file mode 100644 index b71b2ea8307..00000000000 --- a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.html +++ /dev/null @@ -1 +0,0 @@ -

${brand_label_url}

Added:

${algorithm} Fingerabdruck:
${fingerprint}

Betreff:
${subject}

Aussteller:
${issuer}


                                                           
\ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.txt b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.txt deleted file mode 100644 index 7af8b11729e..00000000000 --- a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-added.txt +++ /dev/null @@ -1,17 +0,0 @@ -[${brand_logo}] - -${brand_label_url} [${brand_url}] - -Added: - -${algorithm} Fingerabdruck: -${fingerprint} - -Betreff: -${subject} - -Aussteller: -${issuer} - - --------------------------------------------------------------------------------- \ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed-subject.txt b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed-subject.txt deleted file mode 100644 index e69de29bb2d..00000000000 diff --git a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.html b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.html deleted file mode 100644 index 11c8e53eb66..00000000000 --- a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.html +++ /dev/null @@ -1 +0,0 @@ -

${brand_label_url}

Removed:

${algorithm} Fingerabdruck:
${fingerprint}

Betreff:
${subject}

Aussteller:
${issuer}


                                                           
\ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.txt b/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.txt deleted file mode 100644 index 182aad0a4d8..00000000000 --- a/libs/wire-subsystems/templates/de/team/email/certificates/idp-certificate-removed.txt +++ /dev/null @@ -1,17 +0,0 @@ -[${brand_logo}] - -${brand_label_url} [${brand_url}] - -Removed: - -${algorithm} Fingerabdruck: -${fingerprint} - -Betreff: -${subject} - -Aussteller: -${issuer} - - --------------------------------------------------------------------------------- \ No newline at end of file From 8d5af480f7fc7a1dc9291e41018f0099eba05385 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 11:35:05 +0100 Subject: [PATCH 40/60] Update German templates --- .../de/team/email/idp-config-change-subject.txt | 1 + .../templates/de/team/email/idp-config-change.html | 2 +- .../templates/de/team/email/idp-config-change.txt | 14 +++++++------- 3 files changed, 9 insertions(+), 8 deletions(-) diff --git a/libs/wire-subsystems/templates/de/team/email/idp-config-change-subject.txt b/libs/wire-subsystems/templates/de/team/email/idp-config-change-subject.txt index e69de29bb2d..dff03eba7d3 100644 --- a/libs/wire-subsystems/templates/de/team/email/idp-config-change-subject.txt +++ b/libs/wire-subsystems/templates/de/team/email/idp-config-change-subject.txt @@ -0,0 +1 @@ +Die Konfiguration des Identity Providers Ihres Teams hat sich geändert \ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/team/email/idp-config-change.html b/libs/wire-subsystems/templates/de/team/email/idp-config-change.html index b774cd1af75..1f2fd3078c5 100644 --- a/libs/wire-subsystems/templates/de/team/email/idp-config-change.html +++ b/libs/wire-subsystems/templates/de/team/email/idp-config-change.html @@ -1 +1 @@ -

${brand_label_url}

Änderung in der Konfiguration Ihres Identity Providers

Etwas hat sich in der IdP-Konfiguration fĂ¼r Ihr Team geändert.

Team-ID:
${teamId}

Benutzer-ID:
${userId}


Details:

IdP Aussteller:
${issuer}

IdP-Endpunkt:
${idpEndpoint}

IdP ID:
${idp_id}


${certificatesDetails}

Wenn Sie diese Änderung nicht veranlasst haben, wenden Sie sich bitte an den Wire Support.

 

Datenschutzerklärung und Nutzungsbedingungen · Missbrauch melden
${copyright}. Alle Rechte vorbehalten.

                                                           
\ No newline at end of file +Die Konfiguration des Identity Providers Ihres Teams hat sich geändert

${brand_label_url}

Änderung in der Konfiguration Ihres Identity Providers

Etwas hat sich in der IdP-Konfiguration fĂ¼r Ihr Team geändert.

Team-ID:
${team_id}

Benutzer-ID:
${user_id}


Details:

IdP-Aussteller:
${idp_issuer}

IdP-Endpunkt:
${idp_endpoint}

IdP-ID:
${idp_id}


${certificates_details}

Wenn Sie diese Änderung nicht veranlasst haben, wenden Sie sich bitte an den Wire Support.

 

Datenschutzerklärung und Nutzungsbedingungen · Missbrauch melden
${copyright}. Alle Rechte vorbehalten.

                                                           
\ No newline at end of file diff --git a/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt b/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt index e8a9a0666d1..3c2707fab92 100644 --- a/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt +++ b/libs/wire-subsystems/templates/de/team/email/idp-config-change.txt @@ -6,29 +6,29 @@ ${brand_label_url} [${brand_url}] Etwas hat sich in der IdP-Konfiguration fĂ¼r Ihr Team geändert. Team-ID: -${teamid} +${team_id} Benutzer-ID: -${userid} +${user_id} -------------------------------------------------------------------------------- Details: -IdP Aussteller: -${issuer} +IdP-Aussteller: +${idp_issuer} IdP-Endpunkt: -${idpendpoint} +${idp_endpoint} -IdP ID: +IdP-ID: ${idp_id} -------------------------------------------------------------------------------- -${certificatesdetails}Wenn Sie diese Ă„nderung nicht veranlasst haben, wenden Sie sich bitte an den +${certificates_details}Wenn Sie diese Ă„nderung nicht veranlasst haben, wenden Sie sich bitte an den Wire Support. [${support}] Datenschutzerklärung und Nutzungsbedingungen [${legal}]· Missbrauch melden From 5dca7e7bca98e4eb96b6839d160572b9d399e2ab Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 11:35:28 +0100 Subject: [PATCH 41/60] Test with German Templates --- .../test/resources/mails/created_de.txt | 51 ++++++++++++ .../test/resources/mails/deleted_de.txt | 51 ++++++++++++ .../test/resources/mails/subject_de.txt | 1 + .../test/resources/mails/subject_en.txt | 1 + .../test/resources/mails/updated_de.txt | 77 +++++++++++++++++++ .../SAMLEmailSubsystem/InterpreterSpec.hs | 51 ++++++++---- 6 files changed, 215 insertions(+), 17 deletions(-) create mode 100644 libs/wire-subsystems/test/resources/mails/created_de.txt create mode 100644 libs/wire-subsystems/test/resources/mails/deleted_de.txt create mode 100644 libs/wire-subsystems/test/resources/mails/subject_de.txt create mode 100644 libs/wire-subsystems/test/resources/mails/subject_en.txt create mode 100644 libs/wire-subsystems/test/resources/mails/updated_de.txt diff --git a/libs/wire-subsystems/test/resources/mails/created_de.txt b/libs/wire-subsystems/test/resources/mails/created_de.txt new file mode 100644 index 00000000000..56311d7662e --- /dev/null +++ b/libs/wire-subsystems/test/resources/mails/created_de.txt @@ -0,0 +1,51 @@ +[https://wire.example.com/p/img/email/logo-email-black.png] + +wire.example.com [https://wire.example.com] + +Ă„NDERUNG IN DER KONFIGURATION IHRES IDENTITY PROVIDERS +Etwas hat sich in der IdP-Konfiguration fĂ¼r Ihr Team geändert. + +Team-ID: +99f552d8-9dad-60c1-4be9-c88fb532893a + +Benutzer-ID: +4a1ce4ea-5c99-d01e-018f-4dc9d08f787a + + +-------------------------------------------------------------------------------- + +Details: + +IdP-Aussteller: +https://issuer.example.com/realm + +IdP-Endpunkt: +https://saml-endpoint.example.com/auth + +IdP-ID: +574ddfb0-4e50-2bff-e924-33ee2b9f7064 + + +-------------------------------------------------------------------------------- + +HinzugefĂ¼gt: + +SHA1 Fingerabdruck: +15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37 + +Betreff: +CN=accounts.accesscontrol.windows.net + +Aussteller: +CN=accounts.accesscontrol.windows.net + + +-------------------------------------------------------------------------------- + + +Wenn Sie diese Ă„nderung nicht veranlasst haben, wenden Sie sich bitte an den +Wire Support. [https://support.wire.com/] + +Datenschutzerklärung und Nutzungsbedingungen [https://wire.example.com/legal/]· Missbrauch melden +[misuse@wire.example.com] +© WIRE SWISS GmbH. Alle Rechte vorbehalten. diff --git a/libs/wire-subsystems/test/resources/mails/deleted_de.txt b/libs/wire-subsystems/test/resources/mails/deleted_de.txt new file mode 100644 index 00000000000..07fa70ba6af --- /dev/null +++ b/libs/wire-subsystems/test/resources/mails/deleted_de.txt @@ -0,0 +1,51 @@ +[https://wire.example.com/p/img/email/logo-email-black.png] + +wire.example.com [https://wire.example.com] + +Ă„NDERUNG IN DER KONFIGURATION IHRES IDENTITY PROVIDERS +Etwas hat sich in der IdP-Konfiguration fĂ¼r Ihr Team geändert. + +Team-ID: +99f552d8-9dad-60c1-4be9-c88fb532893a + +Benutzer-ID: +4a1ce4ea-5c99-d01e-018f-4dc9d08f787a + + +-------------------------------------------------------------------------------- + +Details: + +IdP-Aussteller: +https://issuer.example.com/realm + +IdP-Endpunkt: +https://saml-endpoint.example.com/auth + +IdP-ID: +574ddfb0-4e50-2bff-e924-33ee2b9f7064 + + +-------------------------------------------------------------------------------- + + +Entfernt: + +SHA1 Fingerabdruck: +15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37 + +Betreff: +CN=accounts.accesscontrol.windows.net + +Aussteller: +CN=accounts.accesscontrol.windows.net + + +-------------------------------------------------------------------------------- + +Wenn Sie diese Ă„nderung nicht veranlasst haben, wenden Sie sich bitte an den +Wire Support. [https://support.wire.com/] + +Datenschutzerklärung und Nutzungsbedingungen [https://wire.example.com/legal/]· Missbrauch melden +[misuse@wire.example.com] +© WIRE SWISS GmbH. Alle Rechte vorbehalten. diff --git a/libs/wire-subsystems/test/resources/mails/subject_de.txt b/libs/wire-subsystems/test/resources/mails/subject_de.txt new file mode 100644 index 00000000000..dff03eba7d3 --- /dev/null +++ b/libs/wire-subsystems/test/resources/mails/subject_de.txt @@ -0,0 +1 @@ +Die Konfiguration des Identity Providers Ihres Teams hat sich geändert \ No newline at end of file diff --git a/libs/wire-subsystems/test/resources/mails/subject_en.txt b/libs/wire-subsystems/test/resources/mails/subject_en.txt new file mode 100644 index 00000000000..e31e5528a25 --- /dev/null +++ b/libs/wire-subsystems/test/resources/mails/subject_en.txt @@ -0,0 +1 @@ +Your team's identity provider configuration has changed \ No newline at end of file diff --git a/libs/wire-subsystems/test/resources/mails/updated_de.txt b/libs/wire-subsystems/test/resources/mails/updated_de.txt new file mode 100644 index 00000000000..324c24d42d7 --- /dev/null +++ b/libs/wire-subsystems/test/resources/mails/updated_de.txt @@ -0,0 +1,77 @@ +[https://wire.example.com/p/img/email/logo-email-black.png] + +wire.example.com [https://wire.example.com] + +Ă„NDERUNG IN DER KONFIGURATION IHRES IDENTITY PROVIDERS +Etwas hat sich in der IdP-Konfiguration fĂ¼r Ihr Team geändert. + +Team-ID: +99f552d8-9dad-60c1-4be9-c88fb532893a + +Benutzer-ID: +4a1ce4ea-5c99-d01e-018f-4dc9d08f787a + + +-------------------------------------------------------------------------------- + +Details: + +IdP-Aussteller: +https://issuer.example.com/realm + +IdP-Endpunkt: +https://saml-endpoint.example.com/auth + +IdP-ID: +574ddfb0-4e50-2bff-e924-33ee2b9f7064 + + +-------------------------------------------------------------------------------- + +HinzugefĂ¼gt: + +SHA1 Fingerabdruck: +11:DE:AC:24:34:30:3D:05:81:02:77:26:41:3D:FC:09:01:92:E4:40 + +Betreff: +Country=US,O=ExampleOrg,OU=Dev1,CN=CertOne,Email Address=one@example.com + +Aussteller: +Country=US,O=ExampleOrg,OU=Dev1,CN=CertOne,Email Address=one@example.com + + +-------------------------------------------------------------------------------- +HinzugefĂ¼gt: + +SHA1 Fingerabdruck: +DF:CB:99:7D:C7:1A:4A:AC:D3:F6:94:22:97:07:6D:59:7B:BF:7B:57 + +Betreff: +Country=DE,O=ExampleOrg,OU=Dev2,CN=CertTwo,Email Address=two@example.com + +Aussteller: +Country=DE,O=ExampleOrg,OU=Dev2,CN=CertTwo,Email Address=two@example.com + + +-------------------------------------------------------------------------------- + +Entfernt: + +SHA1 Fingerabdruck: +15:28:A6:B8:5A:C5:36:80:B4:B0:95:C6:9A:FD:77:9C:D6:5C:78:37 + +Betreff: +CN=accounts.accesscontrol.windows.net + +Aussteller: +CN=accounts.accesscontrol.windows.net + + +-------------------------------------------------------------------------------- + +Wenn Sie diese Ă„nderung nicht veranlasst haben, wenden Sie sich bitte an den +Wire Support. [https://support.wire.com/] + +Datenschutzerklärung und Nutzungsbedingungen [https://wire.example.com/legal/]· Missbrauch melden +[misuse@wire.example.com] +© WIRE SWISS GmbH. Alle Rechte vorbehalten. diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index fbcc11ab40a..4531659b4d9 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -43,13 +43,31 @@ import Wire.TeamSubsystem import Wire.TeamSubsystem.GalleyAPI (interpretTeamSubsystemToGalleyAPI) import Wire.UserStore +data RenderedTextParts = RenderedTextParts + { created :: LText, + deleted :: LText, + updated :: LText, + subject :: LText + } + -- TODO tests: -- - Other local (found) --- - Update -- No admin user spec :: Spec spec = do - let testLocals :: [Locale] = fromMaybe (error "Unknown locale") . parseLocale <$> ["en", "en-EN", "en-GB", "es", "es-ES"] + let createTextParts lang = + RenderedTextParts + <$> readTextPartFile ("created_" <> lang <> ".txt") + <*> readTextPartFile ("deleted_" <> lang <> ".txt") + <*> readTextPartFile ("updated_" <> lang <> ".txt") + <*> readTextPartFile ("subject_" <> lang <> ".txt") + + enTextParts <- runIO $ createTextParts "en" + deTextParts <- runIO $ createTextParts "de" + let testLocals :: [(Locale, RenderedTextParts)] = + flip zip ((replicate 5 enTextParts) ++ (replicate 2 deTextParts)) $ + parseLocalUnsafe <$> ["en", "en-EN", "en-GB", "es", "es-ES", "de", "de_DE"] + parseLocalUnsafe = fromMaybe (error "Unknown locale") . parseLocale teamOpts = TeamOpts { tInvitationUrl = "https://example.com/join/?team-code=${code}", @@ -82,8 +100,8 @@ spec = do teamTemplates :: Localised TeamTemplates <- runIO $ loadTeamTemplates teamOpts "templates" defLocale emailSender newCerts <- runIO $ X509.readCertificates "test/resources/saml/certs.store" - describe "SendSAMLIdPChanged" $ forM_ testLocals $ \(userLocale :: Locale) -> do - context (show userLocale) do + describe "SendSAMLIdPChanged" $ forM_ testLocals $ \(userLocale :: Locale, textParts) -> do + context ("locale: " ++ show userLocale) do it "should send an email on IdPCreated" $ do idp :: IdP <- liftIO $ generate arbitrary storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) @@ -97,8 +115,8 @@ spec = do -- Templating issues are logged on level `Warn` filter (\(level, _) -> level > Info) logs `shouldBe` mempty let mail = head mails - assertCommonMailAttributes mail - assertMailTextPartWithFile mail "created_en.txt" + assertCommonMailAttributes mail textParts.subject + assertMailTextPartWithFile mail textParts.created it "should send an email on IdPDeleted" $ do idp :: IdP <- liftIO $ generate arbitrary @@ -112,8 +130,8 @@ spec = do -- Templating issues are logged on level `Warn` filter (\(level, _) -> level > Info) logs `shouldBe` mempty let mail = head mails - assertCommonMailAttributes mail - assertMailTextPartWithFile mail "deleted_en.txt" + assertCommonMailAttributes mail textParts.subject + assertMailTextPartWithFile mail textParts.deleted it "should send an email on IdPUpdated" $ do idp :: IdP <- liftIO $ generate arbitrary @@ -135,8 +153,8 @@ spec = do -- Templating issues are logged on level `Warn` filter (\(level, _) -> level > Info) logs `shouldBe` mempty let mail = head mails - assertCommonMailAttributes mail - assertMailTextPartWithFile mail "updated_en.txt" + assertCommonMailAttributes mail textParts.subject + assertMailTextPartWithFile mail textParts.updated patchIdP :: IdPConfig WireIdP -> TeamId -> IdPConfig WireIdP patchIdP idp teamId = @@ -166,8 +184,8 @@ patchStoredUser storedUser teamId userLocale uid = readTextPartFile :: FilePath -> IO TL.Text readTextPartFile file = TL.stripEnd <$> TL.readFile ("test" "resources" "mails" file) -assertCommonMailAttributes :: Mail -> IO () -assertCommonMailAttributes mail = do +assertCommonMailAttributes :: Mail -> LText -> IO () +assertCommonMailAttributes mail expectedSubject = do mail.mailFrom `shouldBe` Address { addressName = Just "Wire", @@ -183,18 +201,17 @@ assertCommonMailAttributes mail = do mail.mailBcc `shouldBe` [] Set.fromList mail.mailHeaders `shouldBe` Set.fromList - [ ("Subject", "Your team's identity provider configuration has changed"), + [ ("Subject", TL.toStrict expectedSubject), ("X-Zeta-Purpose", "IdPConfigChange") ] -assertMailTextPartWithFile :: Mail -> FilePath -> IO () -assertMailTextPartWithFile mail renderedTextFile = do +assertMailTextPartWithFile :: Mail -> LText -> IO () +assertMailTextPartWithFile mail expectedTextPart = do let textPart = fromMaybe (error "No text part found") $ find (\p -> p.partType == "text/plain; charset=utf-8") (head mail.mailParts) - englishCreateMailContent <- readTextPartFile renderedTextFile case textPart.partContent of - PartContent content -> (decodeUtf8 content) `shouldBe` englishCreateMailContent + PartContent content -> (decodeUtf8 content) `shouldBe` expectedTextPart NestedParts ns -> error $ "Enexpected NestedParts: " ++ show ns -- | Records logs and mails From 83f8df99fb1b2db9acae9447dcb71f697143e94d Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 13:15:18 +0100 Subject: [PATCH 42/60] Add test to send not send to usual members --- .../SAMLEmailSubsystem/InterpreterSpec.hs | 110 ++++++++++-------- 1 file changed, 63 insertions(+), 47 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 4531659b4d9..04fbac5e2b3 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -26,6 +26,7 @@ import Wire.API.Locale import Wire.API.Routes.Internal.Brig (IdpChangedNotification (..)) import Wire.API.Team.Member import Wire.API.Team.Permission (fullPermissions) +import Wire.API.Team.Role (Role (..)) import Wire.API.User.IdentityProvider import Wire.EmailSending import Wire.EmailSubsystem qualified as Email @@ -51,7 +52,6 @@ data RenderedTextParts = RenderedTextParts } -- TODO tests: --- - Other local (found) -- No admin user spec :: Spec spec = do @@ -100,61 +100,77 @@ spec = do teamTemplates :: Localised TeamTemplates <- runIO $ loadTeamTemplates teamOpts "templates" defLocale emailSender newCerts <- runIO $ X509.readCertificates "test/resources/saml/certs.store" - describe "SendSAMLIdPChanged" $ forM_ testLocals $ \(userLocale :: Locale, textParts) -> do - context ("locale: " ++ show userLocale) do - it "should send an email on IdPCreated" $ do - idp :: IdP <- liftIO $ generate arbitrary - storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) - let idp' = patchIdP idp teamId - storedUser' = patchStoredUser storedUser teamId userLocale uid - notif = IdPCreated (Just uid) idp' + describe "SendSAMLIdPChanged" $ do + describe "localized emails" $ forM_ testLocals $ \(userLocale :: Locale, textParts) -> do + context ("locale: " ++ show userLocale) do + it "should send an email on IdPCreated" $ do + idp :: IdP <- liftIO $ generate arbitrary + storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) + let idp' = patchIdP idp teamId + storedUser' = patchStoredUser storedUser teamId userLocale uid + notif = IdPCreated (Just uid) idp' - (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do - sendSAMLIdPChanged notif - length mails `shouldBe` 1 - -- Templating issues are logged on level `Warn` - filter (\(level, _) -> level > Info) logs `shouldBe` mempty - let mail = head mails - assertCommonMailAttributes mail textParts.subject - assertMailTextPartWithFile mail textParts.created + (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do + sendSAMLIdPChanged notif + length mails `shouldBe` 1 + -- Templating issues are logged on level `Warn` + filter (\(level, _) -> level > Info) logs `shouldBe` mempty + let mail = head mails + assertCommonMailAttributes mail textParts.subject + assertMailTextPartWithFile mail textParts.created - it "should send an email on IdPDeleted" $ do - idp :: IdP <- liftIO $ generate arbitrary - storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) - let idp' = patchIdP idp teamId - storedUser' = patchStoredUser storedUser teamId userLocale uid - notif = IdPDeleted uid idp' - (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do - sendSAMLIdPChanged notif - length mails `shouldBe` 1 - -- Templating issues are logged on level `Warn` - filter (\(level, _) -> level > Info) logs `shouldBe` mempty - let mail = head mails - assertCommonMailAttributes mail textParts.subject - assertMailTextPartWithFile mail textParts.deleted + it "should send an email on IdPDeleted" $ do + idp :: IdP <- liftIO $ generate arbitrary + storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) + let idp' = patchIdP idp teamId + storedUser' = patchStoredUser storedUser teamId userLocale uid + notif = IdPDeleted uid idp' + (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do + sendSAMLIdPChanged notif + length mails `shouldBe` 1 + -- Templating issues are logged on level `Warn` + filter (\(level, _) -> level > Info) logs `shouldBe` mempty + let mail = head mails + assertCommonMailAttributes mail textParts.subject + assertMailTextPartWithFile mail textParts.deleted - it "should send an email on IdPUpdated" $ do + it "should send an email on IdPUpdated" $ do + idp :: IdP <- liftIO $ generate arbitrary + idp2 :: IdP <- liftIO $ generate arbitrary + storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) + let idp' = patchIdP idp teamId + idp2' = + (patchIdP idp2 teamId) + { _idpMetadata = + idp2._idpMetadata + { _edCertAuthnResponse = NE.fromList newCerts + } + } + storedUser' = patchStoredUser storedUser teamId userLocale uid + notif = IdPUpdated uid idp' idp2' + (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do + sendSAMLIdPChanged notif + length mails `shouldBe` 1 + -- Templating issues are logged on level `Warn` + filter (\(level, _) -> level > Info) logs `shouldBe` mempty + let mail = head mails + assertCommonMailAttributes mail textParts.subject + assertMailTextPartWithFile mail textParts.updated + describe "logic" $ do + it "should not send emails to usual members (not admin or owner)" $ do idp :: IdP <- liftIO $ generate arbitrary - idp2 :: IdP <- liftIO $ generate arbitrary storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) let idp' = patchIdP idp teamId - idp2' = - (patchIdP idp2 teamId) - { _idpMetadata = - idp2._idpMetadata - { _edCertAuthnResponse = NE.fromList newCerts - } - } - storedUser' = patchStoredUser storedUser teamId userLocale uid - notif = IdPUpdated uid idp' idp2' + storedUser' = patchStoredUser storedUser teamId (parseLocalUnsafe "en") uid + notif = IdPCreated (Just uid) idp' + teamMember :: TeamMember = mkTeamMember uid (rolePermissions RoleMember) Nothing UserLegalHoldDisabled + teamMap :: Map TeamId [TeamMember] = Map.singleton teamId [teamMember] + (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do sendSAMLIdPChanged notif - length mails `shouldBe` 1 - -- Templating issues are logged on level `Warn` + length mails `shouldBe` 0 + -- Expect no issues to be logged filter (\(level, _) -> level > Info) logs `shouldBe` mempty - let mail = head mails - assertCommonMailAttributes mail textParts.subject - assertMailTextPartWithFile mail textParts.updated patchIdP :: IdPConfig WireIdP -> TeamId -> IdPConfig WireIdP patchIdP idp teamId = From aa4da6f25061e3a1a479c003ee8de879d7c5eaa1 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 13:25:20 +0100 Subject: [PATCH 43/60] Test allowed receivers --- .../SAMLEmailSubsystem/InterpreterSpec.hs | 44 +++++++++++++------ 1 file changed, 31 insertions(+), 13 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 04fbac5e2b3..ad26cdfd55b 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -157,20 +157,38 @@ spec = do assertCommonMailAttributes mail textParts.subject assertMailTextPartWithFile mail textParts.updated describe "logic" $ do - it "should not send emails to usual members (not admin or owner)" $ do - idp :: IdP <- liftIO $ generate arbitrary - storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) - let idp' = patchIdP idp teamId - storedUser' = patchStoredUser storedUser teamId (parseLocalUnsafe "en") uid - notif = IdPCreated (Just uid) idp' - teamMember :: TeamMember = mkTeamMember uid (rolePermissions RoleMember) Nothing UserLegalHoldDisabled - teamMap :: Map TeamId [TeamMember] = Map.singleton teamId [teamMember] + forM_ ([minBound .. maxBound] \\ [RoleAdmin, RoleOwner]) $ \role -> + it ("should not send to role " ++ show role) $ do + idp :: IdP <- liftIO $ generate arbitrary + storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) + let idp' = patchIdP idp teamId + storedUser' = patchStoredUser storedUser teamId (parseLocalUnsafe "en") uid + notif = IdPCreated (Just uid) idp' + -- TODO: Test external + teamMember :: TeamMember = mkTeamMember uid (rolePermissions role) Nothing UserLegalHoldDisabled + teamMap :: Map TeamId [TeamMember] = Map.singleton teamId [teamMember] - (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do - sendSAMLIdPChanged notif - length mails `shouldBe` 0 - -- Expect no issues to be logged - filter (\(level, _) -> level > Info) logs `shouldBe` mempty + (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do + sendSAMLIdPChanged notif + length mails `shouldBe` 0 + -- Expect no issues to be logged + filter (\(level, _) -> level > Info) logs `shouldBe` mempty + + forM_ [RoleAdmin, RoleOwner] $ \role -> + it ("should send to role " ++ show role) $ do + idp :: IdP <- liftIO $ generate arbitrary + storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) + let idp' = patchIdP idp teamId + storedUser' = patchStoredUser storedUser teamId (parseLocalUnsafe "en") uid + notif = IdPCreated (Just uid) idp' + teamMember :: TeamMember = mkTeamMember uid (rolePermissions role) Nothing UserLegalHoldDisabled + teamMap :: Map TeamId [TeamMember] = Map.singleton teamId [teamMember] + + (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do + sendSAMLIdPChanged notif + length mails `shouldBe` 1 + -- Expect no issues to be logged + filter (\(level, _) -> level > Info) logs `shouldBe` mempty patchIdP :: IdPConfig WireIdP -> TeamId -> IdPConfig WireIdP patchIdP idp teamId = From de342f586090a6cff9dfb42d6aedd08a02e2887a Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 13:29:37 +0100 Subject: [PATCH 44/60] Delete done TODO --- .../test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index ad26cdfd55b..bf66af8e2fe 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -164,7 +164,6 @@ spec = do let idp' = patchIdP idp teamId storedUser' = patchStoredUser storedUser teamId (parseLocalUnsafe "en") uid notif = IdPCreated (Just uid) idp' - -- TODO: Test external teamMember :: TeamMember = mkTeamMember uid (rolePermissions role) Nothing UserLegalHoldDisabled teamMap :: Map TeamId [TeamMember] = Map.singleton teamId [teamMember] From b2204f78ec8a1d8da69d8f15f3a0455e6e3eeafc Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 13:57:46 +0100 Subject: [PATCH 45/60] Test multiple receivers --- .../SAMLEmailSubsystem/InterpreterSpec.hs | 25 +++++++++++++++++++ 1 file changed, 25 insertions(+) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index bf66af8e2fe..485927bc76d 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -27,6 +27,7 @@ import Wire.API.Routes.Internal.Brig (IdpChangedNotification (..)) import Wire.API.Team.Member import Wire.API.Team.Permission (fullPermissions) import Wire.API.Team.Role (Role (..)) +import Wire.API.User.EmailAddress (fromEmail) import Wire.API.User.IdentityProvider import Wire.EmailSending import Wire.EmailSubsystem qualified as Email @@ -189,6 +190,30 @@ spec = do -- Expect no issues to be logged filter (\(level, _) -> level > Info) logs `shouldBe` mempty + it ("can send to multiple receivers") $ do + idp :: IdP <- liftIO $ generate arbitrary + storedUser1 :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) + storedUser2 :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) + let idp' = patchIdP idp teamId + storedUser1' = patchStoredUser storedUser1 teamId (parseLocalUnsafe "en") uid + storedUser2' = patchStoredUser storedUser2 teamId (parseLocalUnsafe "en") uid + notif = IdPCreated (Just uid) idp' + uid1 :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" + uid2 :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" + teamMember1 :: TeamMember = mkTeamMember uid1 (rolePermissions RoleAdmin) Nothing UserLegalHoldDisabled + teamMember2 :: TeamMember = mkTeamMember uid2 (rolePermissions RoleAdmin) Nothing UserLegalHoldDisabled + teamMap :: Map TeamId [TeamMember] = Map.singleton teamId [teamMember1, teamMember2] + + (mails, logs, _res) <- runInterpreters [storedUser1', storedUser2'] teamMap teamTemplates branding $ do + sendSAMLIdPChanged notif + length mails `shouldBe` 2 + let receiverAddresses :: [Text] = addressEmail <$> concatMap (.mailTo) mails + expectedAddresses :: [Text] = fromEmail . fromJust <$> [storedUser1'.email, storedUser2'.email] + length receiverAddresses `shouldBe` 2 + receiverAddresses `shouldContain` expectedAddresses + -- Expect no issues to be logged + filter (\(level, _) -> level > Info) logs `shouldBe` mempty + patchIdP :: IdPConfig WireIdP -> TeamId -> IdPConfig WireIdP patchIdP idp teamId = idp From 98c6f454778853d9abfa05bbd71af555247ab829 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 15:32:41 +0100 Subject: [PATCH 46/60] Add property tests to excercise the logic a bit more --- .../SAMLEmailSubsystem/InterpreterSpec.hs | 72 +++++++++++++------ 1 file changed, 49 insertions(+), 23 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 485927bc76d..f911e420475 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -19,7 +19,9 @@ import SAML2.WebSSO import System.FilePath import System.Logger qualified as Logger import Test.Hspec +import Test.Hspec.QuickCheck import Test.QuickCheck (Arbitrary (arbitrary), generate, suchThat) +import Test.QuickCheck.Gen import Text.Email.Parser (unsafeEmailAddress) import URI.ByteString import Wire.API.Locale @@ -40,7 +42,7 @@ import Wire.SAMLEmailSubsystem import Wire.SAMLEmailSubsystem.Interpreter (samlEmailSubsystemInterpreter) import Wire.Sem.Logger import Wire.Sem.Logger.TinyLog -import Wire.StoredUser +import Wire.StoredUser (StoredUser (..)) import Wire.TeamSubsystem import Wire.TeamSubsystem.GalleyAPI (interpretTeamSubsystemToGalleyAPI) import Wire.UserStore @@ -190,29 +192,53 @@ spec = do -- Expect no issues to be logged filter (\(level, _) -> level > Info) logs `shouldBe` mempty - it ("can send to multiple receivers") $ do - idp :: IdP <- liftIO $ generate arbitrary - storedUser1 :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) - storedUser2 :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) - let idp' = patchIdP idp teamId - storedUser1' = patchStoredUser storedUser1 teamId (parseLocalUnsafe "en") uid - storedUser2' = patchStoredUser storedUser2 teamId (parseLocalUnsafe "en") uid - notif = IdPCreated (Just uid) idp' - uid1 :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" - uid2 :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" - teamMember1 :: TeamMember = mkTeamMember uid1 (rolePermissions RoleAdmin) Nothing UserLegalHoldDisabled - teamMember2 :: TeamMember = mkTeamMember uid2 (rolePermissions RoleAdmin) Nothing UserLegalHoldDisabled - teamMap :: Map TeamId [TeamMember] = Map.singleton teamId [teamMember1, teamMember2] + prop ("can send to multiple receivers") $ + \idp (TestTeam teamId users) -> do + let idp' = patchIdP idp teamId + notif = IdPCreated (Just uid) idp' + teamMap :: Map TeamId [TeamMember] = Map.singleton teamId (snd <$> users) + adminsAndOwners :: [(StoredUser, TeamMember)] = + filter + ( \(_u, tm) -> + permissionsRole (Wire.API.Team.Member.getPermissions tm) `elem` [Just RoleAdmin, Just RoleOwner] + ) + users + + (mails, logs, _res) <- runInterpreters (fst <$> users) teamMap teamTemplates branding $ do + sendSAMLIdPChanged notif + length mails `shouldBe` length adminsAndOwners + let receiverAddresses :: [Text] = addressEmail <$> concatMap (.mailTo) mails + expectedAddresses :: [Text] = fromEmail . fromJust . email . fst <$> adminsAndOwners + length receiverAddresses `shouldBe` length adminsAndOwners + Set.fromList receiverAddresses `shouldBe` Set.fromList expectedAddresses + -- Expect no issues to be logged + filter (\(level, _) -> level > Info) logs `shouldBe` mempty + +data TestTeam = TestTeam TeamId [(StoredUser, TeamMember)] + deriving (Show) + +instance Arbitrary TestTeam where + arbitrary = do + teamId :: TeamId <- arbitrary + users :: [StoredUserWithEmail] <- + (\(StoredUserWithEmail r) -> StoredUserWithEmail r {teamId = Just teamId}) + <$$> arbitrary + teamMbrs <- mapM (\(StoredUserWithEmail u) -> makeTeamMember u) users + pure $ TestTeam teamId (zip (getStoredUser <$> users) teamMbrs) + where + makeTeamMember :: StoredUser -> Gen TeamMember + makeTeamMember user = do + userRole :: Role <- arbitrary + mkTeamMember user.id (rolePermissions userRole) <$> arbitrary <*> arbitrary + +newtype StoredUserWithEmail = StoredUserWithEmail {getStoredUser :: StoredUser} + deriving (Show) - (mails, logs, _res) <- runInterpreters [storedUser1', storedUser2'] teamMap teamTemplates branding $ do - sendSAMLIdPChanged notif - length mails `shouldBe` 2 - let receiverAddresses :: [Text] = addressEmail <$> concatMap (.mailTo) mails - expectedAddresses :: [Text] = fromEmail . fromJust <$> [storedUser1'.email, storedUser2'.email] - length receiverAddresses `shouldBe` 2 - receiverAddresses `shouldContain` expectedAddresses - -- Expect no issues to be logged - filter (\(level, _) -> level > Info) logs `shouldBe` mempty +instance Arbitrary StoredUserWithEmail where + arbitrary = + StoredUserWithEmail + <$> arbitrary + `suchThat` (isJust . (.email)) patchIdP :: IdPConfig WireIdP -> TeamId -> IdPConfig WireIdP patchIdP idp teamId = From 581c3172f193461109f68acb491e5473245055b7 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 16:17:09 +0100 Subject: [PATCH 47/60] Cleanup --- .../SAMLEmailSubsystem/InterpreterSpec.hs | 51 +++++++++++-------- 1 file changed, 30 insertions(+), 21 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index f911e420475..c48a64c7f41 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -54,8 +54,6 @@ data RenderedTextParts = RenderedTextParts subject :: LText } --- TODO tests: --- No admin user spec :: Spec spec = do let createTextParts lang = @@ -138,19 +136,19 @@ spec = do assertMailTextPartWithFile mail textParts.deleted it "should send an email on IdPUpdated" $ do - idp :: IdP <- liftIO $ generate arbitrary - idp2 :: IdP <- liftIO $ generate arbitrary + idpOld :: IdP <- liftIO $ generate arbitrary + idpNew :: IdP <- liftIO $ generate arbitrary storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) - let idp' = patchIdP idp teamId - idp2' = - (patchIdP idp2 teamId) + let idpOld' = patchIdP idpOld teamId + idpNew' = + (patchIdP idpNew teamId) { _idpMetadata = - idp2._idpMetadata + idpNew._idpMetadata { _edCertAuthnResponse = NE.fromList newCerts } } storedUser' = patchStoredUser storedUser teamId userLocale uid - notif = IdPUpdated uid idp' idp2' + notif = IdPUpdated uid idpOld' idpNew' (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do sendSAMLIdPChanged notif length mails `shouldBe` 1 @@ -160,10 +158,8 @@ spec = do assertCommonMailAttributes mail textParts.subject assertMailTextPartWithFile mail textParts.updated describe "logic" $ do - forM_ ([minBound .. maxBound] \\ [RoleAdmin, RoleOwner]) $ \role -> - it ("should not send to role " ++ show role) $ do - idp :: IdP <- liftIO $ generate arbitrary - storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) + prop "should not send to non-management roles" $ + \idp (StoredUserWithEmail storedUser) (OtherTeamRole role) -> do let idp' = patchIdP idp teamId storedUser' = patchStoredUser storedUser teamId (parseLocalUnsafe "en") uid notif = IdPCreated (Just uid) idp' @@ -176,10 +172,8 @@ spec = do -- Expect no issues to be logged filter (\(level, _) -> level > Info) logs `shouldBe` mempty - forM_ [RoleAdmin, RoleOwner] $ \role -> - it ("should send to role " ++ show role) $ do - idp :: IdP <- liftIO $ generate arbitrary - storedUser :: StoredUser <- liftIO . generate $ arbitrary `suchThat` (isJust . (.email)) + prop "should send to team managers" $ + \idp (StoredUserWithEmail storedUser) (TeamManagementRole role) -> do let idp' = patchIdP idp teamId storedUser' = patchStoredUser storedUser teamId (parseLocalUnsafe "en") uid notif = IdPCreated (Just uid) idp' @@ -193,14 +187,14 @@ spec = do filter (\(level, _) -> level > Info) logs `shouldBe` mempty prop ("can send to multiple receivers") $ - \idp (TestTeam teamId users) -> do - let idp' = patchIdP idp teamId + \idp (TestTeam tid users) -> do + let idp' = patchIdP idp tid notif = IdPCreated (Just uid) idp' - teamMap :: Map TeamId [TeamMember] = Map.singleton teamId (snd <$> users) + teamMap :: Map TeamId [TeamMember] = Map.singleton tid (snd <$> users) adminsAndOwners :: [(StoredUser, TeamMember)] = filter ( \(_u, tm) -> - permissionsRole (Wire.API.Team.Member.getPermissions tm) `elem` [Just RoleAdmin, Just RoleOwner] + permissionsRole (Wire.API.Team.Member.getPermissions tm) `elem` (Just <$> teamManagementRoles) ) users @@ -214,6 +208,21 @@ spec = do -- Expect no issues to be logged filter (\(level, _) -> level > Info) logs `shouldBe` mempty +newtype OtherTeamRole = OtherTeamRole Role + deriving (Show) + +instance Arbitrary OtherTeamRole where + arbitrary = OtherTeamRole <$> elements ([minBound .. maxBound] \\ [RoleAdmin, RoleOwner]) + +newtype TeamManagementRole = TeamManagementRole Role + deriving (Show) + +instance Arbitrary TeamManagementRole where + arbitrary = TeamManagementRole <$> elements teamManagementRoles + +teamManagementRoles :: [Role] +teamManagementRoles = [RoleAdmin, RoleOwner] + data TestTeam = TestTeam TeamId [(StoredUser, TeamMember)] deriving (Show) From 353cf4df12b85998277b67dd81d43508975480b5 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 16:22:11 +0100 Subject: [PATCH 48/60] Same assertions levels --- .../SAMLEmailSubsystem/InterpreterSpec.hs | 35 ++++++++++++------- 1 file changed, 23 insertions(+), 12 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index c48a64c7f41..c77a56b1819 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -113,9 +113,10 @@ spec = do (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do sendSAMLIdPChanged notif + + assertNoWarnLogs logs + length mails `shouldBe` 1 - -- Templating issues are logged on level `Warn` - filter (\(level, _) -> level > Info) logs `shouldBe` mempty let mail = head mails assertCommonMailAttributes mail textParts.subject assertMailTextPartWithFile mail textParts.created @@ -128,9 +129,10 @@ spec = do notif = IdPDeleted uid idp' (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do sendSAMLIdPChanged notif + + assertNoWarnLogs logs + length mails `shouldBe` 1 - -- Templating issues are logged on level `Warn` - filter (\(level, _) -> level > Info) logs `shouldBe` mempty let mail = head mails assertCommonMailAttributes mail textParts.subject assertMailTextPartWithFile mail textParts.deleted @@ -151,12 +153,14 @@ spec = do notif = IdPUpdated uid idpOld' idpNew' (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do sendSAMLIdPChanged notif + + assertNoWarnLogs logs + length mails `shouldBe` 1 - -- Templating issues are logged on level `Warn` - filter (\(level, _) -> level > Info) logs `shouldBe` mempty let mail = head mails assertCommonMailAttributes mail textParts.subject assertMailTextPartWithFile mail textParts.updated + describe "logic" $ do prop "should not send to non-management roles" $ \idp (StoredUserWithEmail storedUser) (OtherTeamRole role) -> do @@ -168,9 +172,10 @@ spec = do (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do sendSAMLIdPChanged notif + + assertNoWarnLogs logs + length mails `shouldBe` 0 - -- Expect no issues to be logged - filter (\(level, _) -> level > Info) logs `shouldBe` mempty prop "should send to team managers" $ \idp (StoredUserWithEmail storedUser) (TeamManagementRole role) -> do @@ -182,9 +187,10 @@ spec = do (mails, logs, _res) <- runInterpreters [storedUser'] teamMap teamTemplates branding $ do sendSAMLIdPChanged notif + + assertNoWarnLogs logs + length mails `shouldBe` 1 - -- Expect no issues to be logged - filter (\(level, _) -> level > Info) logs `shouldBe` mempty prop ("can send to multiple receivers") $ \idp (TestTeam tid users) -> do @@ -200,13 +206,18 @@ spec = do (mails, logs, _res) <- runInterpreters (fst <$> users) teamMap teamTemplates branding $ do sendSAMLIdPChanged notif + + assertNoWarnLogs logs + length mails `shouldBe` length adminsAndOwners let receiverAddresses :: [Text] = addressEmail <$> concatMap (.mailTo) mails expectedAddresses :: [Text] = fromEmail . fromJust . email . fst <$> adminsAndOwners length receiverAddresses `shouldBe` length adminsAndOwners Set.fromList receiverAddresses `shouldBe` Set.fromList expectedAddresses - -- Expect no issues to be logged - filter (\(level, _) -> level > Info) logs `shouldBe` mempty + +-- Templating issues are logged on level `Warn` +assertNoWarnLogs :: (Show b, Eq b) => [(Level, b)] -> Expectation +assertNoWarnLogs logs = filter (\(level, _) -> level > Info) logs `shouldBe` mempty newtype OtherTeamRole = OtherTeamRole Role deriving (Show) From 6fc7af77b5d242d16772afb918ee42c9f3083fc0 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 16:37:56 +0100 Subject: [PATCH 49/60] Fix scopes of bindings --- .../SAMLEmailSubsystem/InterpreterSpec.hs | 22 ++++++++++--------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index c77a56b1819..668c2cbedd8 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -20,8 +20,7 @@ import System.FilePath import System.Logger qualified as Logger import Test.Hspec import Test.Hspec.QuickCheck -import Test.QuickCheck (Arbitrary (arbitrary), generate, suchThat) -import Test.QuickCheck.Gen +import Test.QuickCheck import Text.Email.Parser (unsafeEmailAddress) import URI.ByteString import Wire.API.Locale @@ -65,7 +64,10 @@ spec = do enTextParts <- runIO $ createTextParts "en" deTextParts <- runIO $ createTextParts "de" - let testLocals :: [(Locale, RenderedTextParts)] = + let -- We don't test all locals such that we do not have to adjust this test + -- for every new translation. So far, there are translations for Germand + -- and English. There's none for Spanish (falls back to English). + testLocals :: [(Locale, RenderedTextParts)] = flip zip ((replicate 5 enTextParts) ++ (replicate 2 deTextParts)) $ parseLocalUnsafe <$> ["en", "en-EN", "en-GB", "es", "es-ES", "de", "de_DE"] parseLocalUnsafe = fromMaybe (error "Unknown locale") . parseLocale @@ -79,10 +81,6 @@ spec = do } defLocale = Locale ((fromJust . parseLanguage) "en") Nothing emailSender = unsafeEmailAddress "wire" "example.com" - uid :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" - teamId :: TeamId = either error Imports.id $ parseIdFromText "99f552d8-9dad-60c1-4be9-c88fb532893a" - teamMember :: TeamMember = mkTeamMember uid fullPermissions Nothing UserLegalHoldDisabled - teamMap :: Map TeamId [TeamMember] = Map.singleton teamId [teamMember] branding = Map.fromList [ ("brand", "Wire Test"), @@ -103,6 +101,10 @@ spec = do describe "SendSAMLIdPChanged" $ do describe "localized emails" $ forM_ testLocals $ \(userLocale :: Locale, textParts) -> do + let uid :: UserId = either error Imports.id $ parseIdFromText "4a1ce4ea-5c99-d01e-018f-4dc9d08f787a" + teamId :: TeamId = either error Imports.id $ parseIdFromText "99f552d8-9dad-60c1-4be9-c88fb532893a" + teamMember :: TeamMember = mkTeamMember uid fullPermissions Nothing UserLegalHoldDisabled + teamMap :: Map TeamId [TeamMember] = Map.singleton teamId [teamMember] context ("locale: " ++ show userLocale) do it "should send an email on IdPCreated" $ do idp :: IdP <- liftIO $ generate arbitrary @@ -163,7 +165,7 @@ spec = do describe "logic" $ do prop "should not send to non-management roles" $ - \idp (StoredUserWithEmail storedUser) (OtherTeamRole role) -> do + \idp (StoredUserWithEmail storedUser) (OtherTeamRole role) uid teamId -> do let idp' = patchIdP idp teamId storedUser' = patchStoredUser storedUser teamId (parseLocalUnsafe "en") uid notif = IdPCreated (Just uid) idp' @@ -178,7 +180,7 @@ spec = do length mails `shouldBe` 0 prop "should send to team managers" $ - \idp (StoredUserWithEmail storedUser) (TeamManagementRole role) -> do + \idp (StoredUserWithEmail storedUser) (TeamManagementRole role) uid teamId -> do let idp' = patchIdP idp teamId storedUser' = patchStoredUser storedUser teamId (parseLocalUnsafe "en") uid notif = IdPCreated (Just uid) idp' @@ -193,7 +195,7 @@ spec = do length mails `shouldBe` 1 prop ("can send to multiple receivers") $ - \idp (TestTeam tid users) -> do + \idp (TestTeam tid users) uid -> do let idp' = patchIdP idp tid notif = IdPCreated (Just uid) idp' teamMap :: Map TeamId [TeamMember] = Map.singleton tid (snd <$> users) From eebd7ad054609b25c937121c46b551ecfc8fcd94 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 17:40:04 +0100 Subject: [PATCH 50/60] Add changelog --- changelog.d/2-features/send-email-on-idp-change | 3 +++ 1 file changed, 3 insertions(+) create mode 100644 changelog.d/2-features/send-email-on-idp-change diff --git a/changelog.d/2-features/send-email-on-idp-change b/changelog.d/2-features/send-email-on-idp-change new file mode 100644 index 00000000000..8bd6a7679c5 --- /dev/null +++ b/changelog.d/2-features/send-email-on-idp-change @@ -0,0 +1,3 @@ +Send an email to team admins and owners when an IdP is changed via API (create, +update, delete). This behaviour is for now only enabled for multi-ingress +setups. From afcc4bf12769372c5996cd0b7c7d4e98687755c9 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 17:55:40 +0100 Subject: [PATCH 51/60] Rename: IdPDescription -> IdPDetails --- libs/wire-subsystems/src/Wire/EmailSubsystem.hs | 5 ++--- .../src/Wire/EmailSubsystem/Interpreter.hs | 10 +++++----- .../src/Wire/SAMLEmailSubsystem/Interpreter.hs | 6 +++--- 3 files changed, 10 insertions(+), 11 deletions(-) diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem.hs index c7548a42a87..6781fbe5a64 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem.hs @@ -47,13 +47,12 @@ data EmailSubsystem m a where SendTeamInvitationMailPersonalUser :: EmailAddress -> TeamId -> EmailAddress -> InvitationCode -> Maybe Locale -> EmailSubsystem m Text SendMemberWelcomeEmail :: EmailAddress -> TeamId -> Text -> Maybe Locale -> EmailSubsystem m () SendNewTeamOwnerWelcomeEmail :: EmailAddress -> TeamId -> Text -> Maybe Locale -> Name -> EmailSubsystem m () - SendSAMLIdPChanged :: EmailAddress -> TeamId -> Maybe UserId -> [IdPDescription] -> [IdPDescription] -> IdPId -> Issuer -> URI -> Maybe Locale -> EmailSubsystem m () + SendSAMLIdPChanged :: EmailAddress -> TeamId -> Maybe UserId -> [IdPDetails] -> [IdPDetails] -> IdPId -> Issuer -> URI -> Maybe Locale -> EmailSubsystem m () data IdPStatus = Added | Removed deriving (Eq, Ord, Show) --- TODO: Or `IdPDetails`? -data IdPDescription = IdPDescription +data IdPDetails = IdPDetails { idpDescriptionFingerprintAlgorithm :: Text, idpDescriptionFingerprint :: Text, idpDescriptionSubject :: Text diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs index b455b6995de..b3e5dee6d17 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs @@ -84,8 +84,8 @@ sendSAMLIdPChangedImpl :: EmailAddress -> TeamId -> Maybe UserId -> - [IdPDescription] -> - [IdPDescription] -> + [IdPDetails] -> + [IdPDetails] -> IdPId -> Issuer -> URI -> @@ -103,8 +103,8 @@ renderIdPConfigChangeEmail :: EmailAddress -> IdPConfigChangeEmailTemplate -> Map Text Text -> - [IdPDescription] -> - [IdPDescription] -> + [IdPDetails] -> + [IdPDetails] -> TeamId -> Maybe UserId -> IdPId -> @@ -155,7 +155,7 @@ renderIdPConfigChangeEmail email IdPConfigChangeEmailTemplate {..} branding adde from = Address (Just idpConfigChangeEmailSenderName) (fromEmail idpConfigChangeEmailSender) to = Address Nothing (fromEmail email) - idpDetailsToMap :: IdPDescription -> Map Text Text + idpDetailsToMap :: IdPDetails -> Map Text Text idpDetailsToMap d = empty @Text @Text & Map.insert "algorithm" d.idpDescriptionFingerprintAlgorithm diff --git a/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs index c324cd38738..8bf1ffb5fed 100644 --- a/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs +++ b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs @@ -17,7 +17,7 @@ import Wire.API.Locale import Wire.API.Routes.Internal.Brig import Wire.API.Team.Member import Wire.API.User.IdentityProvider -import Wire.EmailSubsystem (IdPDescription (..)) +import Wire.EmailSubsystem (IdPDetails (..)) import Wire.EmailSubsystem qualified as Email import Wire.SAMLEmailSubsystem import Wire.StoredUser @@ -83,10 +83,10 @@ sendSAMLIdPChangedImpl notif = do onlyR = r \\ l in (onlyL, onlyR) - toDesc :: X509.SignedCertificate -> IdPDescription + toDesc :: X509.SignedCertificate -> IdPDetails toDesc cert = let desc = certDescription cert - in IdPDescription + in IdPDetails { idpDescriptionFingerprintAlgorithm = T.pack desc.fingerprintAlgorithm, idpDescriptionFingerprint = T.pack desc.fingerprint, idpDescriptionSubject = T.pack desc.subject From ce9bc06ee19aada4bec1a0b804e28a56671251ff Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 17:59:46 +0100 Subject: [PATCH 52/60] Move function down in file Keep the existing order. --- .../src/Wire/EmailSubsystem/Interpreter.hs | 176 +++++++++--------- 1 file changed, 89 insertions(+), 87 deletions(-) diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs index b3e5dee6d17..b25f9696659 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs @@ -76,93 +76,6 @@ emailSubsystemInterpreter userTpls teamTpls branding = interpret \case SendSAMLIdPChanged email tid mbUid addedCerts removedCerts idPId iss requestUri mLocale -> sendSAMLIdPChangedImpl teamTpls branding email tid mbUid addedCerts removedCerts idPId iss requestUri mLocale --- TODO: Move these functions down in this file. -sendSAMLIdPChangedImpl :: - (Member EmailSending r, Member TinyLog r) => - Localised TeamTemplates -> - Map Text Text -> - EmailAddress -> - TeamId -> - Maybe UserId -> - [IdPDetails] -> - [IdPDetails] -> - IdPId -> - Issuer -> - URI -> - Maybe Locale -> - Sem r () -sendSAMLIdPChangedImpl teamTemplates branding to tid mbUid addedCerts removedCerts idPId issuer endpoint mLocale = do - let tpl = idpConfigChangeEmail . snd $ forLocale mLocale teamTemplates - mail <- - logEmailRenderErrors "idp config change email" $ - renderIdPConfigChangeEmail to tpl branding addedCerts removedCerts tid mbUid idPId issuer endpoint - sendMail mail - -renderIdPConfigChangeEmail :: - (Member (Output Text) r) => - EmailAddress -> - IdPConfigChangeEmailTemplate -> - Map Text Text -> - [IdPDetails] -> - [IdPDetails] -> - TeamId -> - Maybe UserId -> - IdPId -> - Issuer -> - URI -> - Sem r Mail -renderIdPConfigChangeEmail email IdPConfigChangeEmailTemplate {..} branding addedCerts removedCerts tid uid idPId issuer endpoint = do - idpDetailsAddedText :: Text <- - (TL.toStrict . TL.unlines) - <$> mapM (renderTextWithBrandingSem idpConfigChangeEmailIdPDetailsAddedText . idpDetailsToMap) addedCerts - idpDetailsAddedHtml :: Text <- - (TL.toStrict . TL.unlines) - <$> mapM (renderTextWithBrandingSem idpConfigChangeEmailIdPDetailsAddedHtml . idpDetailsToMap) addedCerts - idpDetailsRemovedText :: Text <- - (TL.toStrict . TL.unlines) - <$> mapM (renderTextWithBrandingSem idpConfigChangeEmailIdPDetailsRemovedText . idpDetailsToMap) removedCerts - idpDetailsRemovedHtml :: Text <- - (TL.toStrict . TL.unlines) - <$> mapM (renderTextWithBrandingSem idpConfigChangeEmailIdPDetailsRemovedHtml . idpDetailsToMap) removedCerts - - let replace = - branding - & Map.insert "team_id" ((toText . toUUID) tid) - & Map.insert "user_id" (maybe "None" (toText . toUUID) uid) - & Map.insert "idp_issuer" ((T.decodeUtf8 . serializeURIRef' . _fromIssuer) issuer) - & Map.insert "idp_endpoint" ((T.decodeUtf8 . serializeURIRef') endpoint) - & Map.insert "idp_id" ((toText . fromIdPId) idPId) - replaceHtml = - replace - & Map.insert "certificates_details" (T.unlines [idpDetailsAddedHtml, idpDetailsRemovedHtml]) - replaceText = - replace - & Map.insert "certificates_details" (T.unlines [idpDetailsAddedText, idpDetailsRemovedText]) - - txt <- renderTextWithBrandingSem idpConfigChangeEmailBodyText replaceText - html <- renderHtmlWithBrandingSem idpConfigChangeEmailBodyHtml replaceHtml - subj <- renderTextWithBrandingSem idpConfigChangeEmailSubject replace - pure - (emptyMail from) - { mailTo = [to], - mailHeaders = - [ ("Subject", toStrict subj), - ("X-Zeta-Purpose", "IdPConfigChange") - ], - mailParts = [[plainPart txt, htmlPart html]] - } - where - from = Address (Just idpConfigChangeEmailSenderName) (fromEmail idpConfigChangeEmailSender) - to = Address Nothing (fromEmail email) - - idpDetailsToMap :: IdPDetails -> Map Text Text - idpDetailsToMap d = - empty @Text @Text - & Map.insert "algorithm" d.idpDescriptionFingerprintAlgorithm - & Map.insert "fingerprint" d.idpDescriptionFingerprint - & Map.insert "subject" d.idpDescriptionSubject - & Map.insert "issuer" d.idpDescriptionSubject - ------------------------------------------------------------------------------- -- Verification Email for -- - Login @@ -682,6 +595,95 @@ renderNewTeamOwnerWelcomeEmail emailTo tid teamName profileName NewTeamOwnerWelc from = Address (Just newTeamOwnerWelcomeEmailSenderName) (fromEmail newTeamOwnerWelcomeEmailSender) to = Address Nothing (fromEmail emailTo) +------------------------------------------------------------------------------- +-- IdP change email for team admins and owners + +sendSAMLIdPChangedImpl :: + (Member EmailSending r, Member TinyLog r) => + Localised TeamTemplates -> + Map Text Text -> + EmailAddress -> + TeamId -> + Maybe UserId -> + [IdPDetails] -> + [IdPDetails] -> + IdPId -> + Issuer -> + URI -> + Maybe Locale -> + Sem r () +sendSAMLIdPChangedImpl teamTemplates branding to tid mbUid addedCerts removedCerts idPId issuer endpoint mLocale = do + let tpl = idpConfigChangeEmail . snd $ forLocale mLocale teamTemplates + mail <- + logEmailRenderErrors "idp config change email" $ + renderIdPConfigChangeEmail to tpl branding addedCerts removedCerts tid mbUid idPId issuer endpoint + sendMail mail + +renderIdPConfigChangeEmail :: + (Member (Output Text) r) => + EmailAddress -> + IdPConfigChangeEmailTemplate -> + Map Text Text -> + [IdPDetails] -> + [IdPDetails] -> + TeamId -> + Maybe UserId -> + IdPId -> + Issuer -> + URI -> + Sem r Mail +renderIdPConfigChangeEmail email IdPConfigChangeEmailTemplate {..} branding addedCerts removedCerts tid uid idPId issuer endpoint = do + idpDetailsAddedText :: Text <- + (TL.toStrict . TL.unlines) + <$> mapM (renderTextWithBrandingSem idpConfigChangeEmailIdPDetailsAddedText . idpDetailsToMap) addedCerts + idpDetailsAddedHtml :: Text <- + (TL.toStrict . TL.unlines) + <$> mapM (renderTextWithBrandingSem idpConfigChangeEmailIdPDetailsAddedHtml . idpDetailsToMap) addedCerts + idpDetailsRemovedText :: Text <- + (TL.toStrict . TL.unlines) + <$> mapM (renderTextWithBrandingSem idpConfigChangeEmailIdPDetailsRemovedText . idpDetailsToMap) removedCerts + idpDetailsRemovedHtml :: Text <- + (TL.toStrict . TL.unlines) + <$> mapM (renderTextWithBrandingSem idpConfigChangeEmailIdPDetailsRemovedHtml . idpDetailsToMap) removedCerts + + let replace = + branding + & Map.insert "team_id" ((toText . toUUID) tid) + & Map.insert "user_id" (maybe "None" (toText . toUUID) uid) + & Map.insert "idp_issuer" ((T.decodeUtf8 . serializeURIRef' . _fromIssuer) issuer) + & Map.insert "idp_endpoint" ((T.decodeUtf8 . serializeURIRef') endpoint) + & Map.insert "idp_id" ((toText . fromIdPId) idPId) + replaceHtml = + replace + & Map.insert "certificates_details" (T.unlines [idpDetailsAddedHtml, idpDetailsRemovedHtml]) + replaceText = + replace + & Map.insert "certificates_details" (T.unlines [idpDetailsAddedText, idpDetailsRemovedText]) + + txt <- renderTextWithBrandingSem idpConfigChangeEmailBodyText replaceText + html <- renderHtmlWithBrandingSem idpConfigChangeEmailBodyHtml replaceHtml + subj <- renderTextWithBrandingSem idpConfigChangeEmailSubject replace + pure + (emptyMail from) + { mailTo = [to], + mailHeaders = + [ ("Subject", toStrict subj), + ("X-Zeta-Purpose", "IdPConfigChange") + ], + mailParts = [[plainPart txt, htmlPart html]] + } + where + from = Address (Just idpConfigChangeEmailSenderName) (fromEmail idpConfigChangeEmailSender) + to = Address Nothing (fromEmail email) + + idpDetailsToMap :: IdPDetails -> Map Text Text + idpDetailsToMap d = + empty @Text @Text + & Map.insert "algorithm" d.idpDescriptionFingerprintAlgorithm + & Map.insert "fingerprint" d.idpDescriptionFingerprint + & Map.insert "subject" d.idpDescriptionSubject + & Map.insert "issuer" d.idpDescriptionSubject + ------------------------------------------------------------------------------- -- MIME Conversions From c92c3a5aa2a5e7c4ddca1486b965b67a5475a2b7 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 18:13:09 +0100 Subject: [PATCH 53/60] Remove re-exports of Brig.Template --- services/brig/src/Brig/App.hs | 4 ++-- services/brig/src/Brig/Provider/Template.hs | 2 +- services/brig/src/Brig/Team/Template.hs | 1 - services/brig/src/Brig/Template.hs | 8 +------- services/brig/src/Brig/User/Template.hs | 3 +-- 5 files changed, 5 insertions(+), 13 deletions(-) diff --git a/services/brig/src/Brig/App.hs b/services/brig/src/Brig/App.hs index 649688f8a53..20cb7da4257 100644 --- a/services/brig/src/Brig/App.hs +++ b/services/brig/src/Brig/App.hs @@ -114,7 +114,7 @@ import Brig.Queue.Stomp qualified as Stomp import Brig.Queue.Types import Brig.Schema.Run qualified as Migrations import Brig.Team.Template -import Brig.Template (InvitationUrlTemplates (..), Localised, genTemplateBranding, genTemplateBrandingMap) +import Brig.Template (InvitationUrlTemplates (..), genTemplateBranding, genTemplateBrandingMap) import Brig.User.Search.Index (IndexEnv (..), MonadIndexIO (..), runIndexIO) import Brig.User.Template import Cassandra (runClient) @@ -165,7 +165,7 @@ import Wire.API.User.Identity import Wire.AuthenticationSubsystem.Config (ZAuthEnv) import Wire.AuthenticationSubsystem.Config qualified as AuthenticationSubsystem import Wire.EmailSending.SMTP qualified as SMTP -import Wire.EmailSubsystem.Template (TemplateBranding, forLocale) +import Wire.EmailSubsystem.Template (Localised, TemplateBranding, forLocale) import Wire.EmailSubsystem.Templates.User import Wire.ExternalAccess.External import Wire.RateLimit.Interpreter diff --git a/services/brig/src/Brig/Provider/Template.hs b/services/brig/src/Brig/Provider/Template.hs index 50a0eab4c93..7de713abb89 100644 --- a/services/brig/src/Brig/Provider/Template.hs +++ b/services/brig/src/Brig/Provider/Template.hs @@ -26,13 +26,13 @@ module Brig.Provider.Template where import Brig.Options -import Brig.Template import Data.ByteString.Conversion (fromByteString) import Data.Misc (HttpsUrl) import Data.Text.Encoding (encodeUtf8) import Data.Text.Template import Imports import Wire.API.User.Identity +import Wire.EmailSubsystem.Template hiding (readTemplate, readText) import Wire.EmailSubsystem.Templates.User data ProviderTemplates = ProviderTemplates diff --git a/services/brig/src/Brig/Team/Template.hs b/services/brig/src/Brig/Team/Template.hs index a650b064b5a..caffd40e85d 100644 --- a/services/brig/src/Brig/Team/Template.hs +++ b/services/brig/src/Brig/Team/Template.hs @@ -24,7 +24,6 @@ module Brig.Team.Template where import Brig.Options -import Brig.Template import Imports import Wire.EmailSubsystem.Template import Wire.EmailSubsystem.Templates.Team diff --git a/services/brig/src/Brig/Template.hs b/services/brig/src/Brig/Template.hs index 366a92c19ab..0b530261d05 100644 --- a/services/brig/src/Brig/Template.hs +++ b/services/brig/src/Brig/Template.hs @@ -20,10 +20,6 @@ -- | Common templating utilities. module Brig.Template ( InvitationUrlTemplates (..), - Localised, - readLocalesDir, - readTemplateWithDefault, - readTextWithDefault, genTemplateBranding, genTemplateBrandingMap, ) @@ -32,9 +28,7 @@ where import Brig.Options import Data.Map.Strict qualified as Map import Data.Text.Template (Template) -import Imports hiding (readFile) --- TODO: Eliminate re-exports -import Wire.EmailSubsystem.Template (Localised, readLocalesDir, readTemplateWithDefault, readTextWithDefault) +import Imports data InvitationUrlTemplates = InvitationUrlTemplates { personalUser :: Template, diff --git a/services/brig/src/Brig/User/Template.hs b/services/brig/src/Brig/User/Template.hs index a7d7fa38585..ea7193faadf 100644 --- a/services/brig/src/Brig/User/Template.hs +++ b/services/brig/src/Brig/User/Template.hs @@ -18,10 +18,9 @@ module Brig.User.Template (loadUserTemplates) where import Brig.Options qualified as Opt -import Brig.Template import Data.Text.Template import Imports -import Wire.EmailSubsystem.Template (TeamOpts (..)) +import Wire.EmailSubsystem.Template hiding (readTemplate, readText) import Wire.EmailSubsystem.Templates.User loadUserTemplates :: Opt.Opts -> IO (Localised UserTemplates) From 4cb4f243205b0e542d47bc1f8dc287efd971d7f8 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 18:17:35 +0100 Subject: [PATCH 54/60] Delete now used action --- libs/wire-subsystems/src/Wire/UserStore.hs | 2 -- libs/wire-subsystems/src/Wire/UserStore/Cassandra.hs | 9 --------- 2 files changed, 11 deletions(-) diff --git a/libs/wire-subsystems/src/Wire/UserStore.hs b/libs/wire-subsystems/src/Wire/UserStore.hs index a4a60848495..a7bc2e9fcdb 100644 --- a/libs/wire-subsystems/src/Wire/UserStore.hs +++ b/libs/wire-subsystems/src/Wire/UserStore.hs @@ -114,8 +114,6 @@ data UserStore m a where DeleteServiceUser :: ProviderId -> ServiceId -> BotId -> UserStore m () LookupServiceUsers :: ProviderId -> ServiceId -> Maybe PagingState -> UserStore m (PageWithState (BotId, ConvId, Maybe TeamId)) LookupServiceUsersForTeam :: ProviderId -> ServiceId -> TeamId -> Maybe PagingState -> UserStore m (PageWithState (BotId, ConvId)) - -- TODO: Delete - GetEmails :: [UserId] -> UserStore m [EmailAddress] makeSem ''UserStore diff --git a/libs/wire-subsystems/src/Wire/UserStore/Cassandra.hs b/libs/wire-subsystems/src/Wire/UserStore/Cassandra.hs index 2e6662cef6d..7a854c4ce23 100644 --- a/libs/wire-subsystems/src/Wire/UserStore/Cassandra.hs +++ b/libs/wire-subsystems/src/Wire/UserStore/Cassandra.hs @@ -79,15 +79,6 @@ interpretUserStoreCassandra casClient = DeleteServiceUser pid sid bid -> deleteServiceUserImpl pid sid bid LookupServiceUsers pid sid mPagingState -> lookupServiceUsersImpl pid sid mPagingState LookupServiceUsersForTeam pid sid tid mPagingState -> lookupServiceUsersForTeamImpl pid sid tid mPagingState - GetEmails uids -> getEmailsImpl uids - -getEmailsImpl :: [UserId] -> Client [EmailAddress] -getEmailsImpl uids = - map runIdentity - <$> retry x1 (query selectEmailAddresses (params LocalQuorum (Identity uids))) - where - selectEmailAddresses :: PrepQuery R (Identity [UserId]) (Identity EmailAddress) - selectEmailAddresses = "SELECT email FROM user WHERE id IN ?" createUserImpl :: NewStoredUser -> Maybe (ConvId, Maybe TeamId) -> Client () createUserImpl new mbConv = retry x5 . batch $ do From 3e9bb52d92d667adcee6e4de9f89f08e2874818f Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 18:53:14 +0100 Subject: [PATCH 55/60] Replace trivial lens usage --- .../wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs index 8bf1ffb5fed..ac3153efe23 100644 --- a/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs +++ b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs @@ -99,8 +99,7 @@ getReceivers :: IdP -> Sem r [Receiver] getReceivers idp = do - -- TODO: Replace lens - admins <- internalGetTeamAdmins (idp ^. idpExtraInfo . team) + admins <- internalGetTeamAdmins idp._idpExtraInfo._team let adminUids = admins ^.. teamMembers . traverse . userId catMaybes <$> (toReceiver <$$> getUsers adminUids) where From 9a1324a14027eaeb851a77d598b1d31484e55731 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 19:00:14 +0100 Subject: [PATCH 56/60] Remove obsolete type --- libs/wire-subsystems/src/Wire/EmailSubsystem.hs | 3 --- 1 file changed, 3 deletions(-) diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem.hs index 6781fbe5a64..432076dbea2 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem.hs @@ -49,9 +49,6 @@ data EmailSubsystem m a where SendNewTeamOwnerWelcomeEmail :: EmailAddress -> TeamId -> Text -> Maybe Locale -> Name -> EmailSubsystem m () SendSAMLIdPChanged :: EmailAddress -> TeamId -> Maybe UserId -> [IdPDetails] -> [IdPDetails] -> IdPId -> Issuer -> URI -> Maybe Locale -> EmailSubsystem m () -data IdPStatus = Added | Removed - deriving (Eq, Ord, Show) - data IdPDetails = IdPDetails { idpDescriptionFingerprintAlgorithm :: Text, idpDescriptionFingerprint :: Text, From bf876adb75164ddf4b5eb4c0c6e902b5a420bf24 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 19:00:28 +0100 Subject: [PATCH 57/60] Add missing action to noop interpreter --- .../test/unit/Wire/MockInterpreters/EmailSubsystem.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/libs/wire-subsystems/test/unit/Wire/MockInterpreters/EmailSubsystem.hs b/libs/wire-subsystems/test/unit/Wire/MockInterpreters/EmailSubsystem.hs index fcb8cb27168..305bebed550 100644 --- a/libs/wire-subsystems/test/unit/Wire/MockInterpreters/EmailSubsystem.hs +++ b/libs/wire-subsystems/test/unit/Wire/MockInterpreters/EmailSubsystem.hs @@ -57,3 +57,4 @@ noopEmailSubsystemInterpreter = interpret \case SendTeamInvitationMailPersonalUser {} -> pure "" SendMemberWelcomeEmail {} -> pure () SendNewTeamOwnerWelcomeEmail {} -> pure () + SendSAMLIdPChanged {} -> pure () From b2be718ac5e65de4636069259e7e0b1ba3084099 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 19:12:08 +0100 Subject: [PATCH 58/60] Remove superfluos data type --- .../src/Wire/EmailSubsystem.hs | 9 ++------- .../src/Wire/EmailSubsystem/Interpreter.hs | 19 ++++++++++--------- .../Wire/SAMLEmailSubsystem/Interpreter.hs | 15 ++------------- 3 files changed, 14 insertions(+), 29 deletions(-) diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem.hs index 432076dbea2..8a4c2221c92 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem.hs @@ -21,6 +21,7 @@ module Wire.EmailSubsystem where import Data.Code qualified as Code import Data.Id +import Data.X509.Extended (CertDescription) import Imports import Polysemy import SAML2.WebSSO @@ -47,12 +48,6 @@ data EmailSubsystem m a where SendTeamInvitationMailPersonalUser :: EmailAddress -> TeamId -> EmailAddress -> InvitationCode -> Maybe Locale -> EmailSubsystem m Text SendMemberWelcomeEmail :: EmailAddress -> TeamId -> Text -> Maybe Locale -> EmailSubsystem m () SendNewTeamOwnerWelcomeEmail :: EmailAddress -> TeamId -> Text -> Maybe Locale -> Name -> EmailSubsystem m () - SendSAMLIdPChanged :: EmailAddress -> TeamId -> Maybe UserId -> [IdPDetails] -> [IdPDetails] -> IdPId -> Issuer -> URI -> Maybe Locale -> EmailSubsystem m () - -data IdPDetails = IdPDetails - { idpDescriptionFingerprintAlgorithm :: Text, - idpDescriptionFingerprint :: Text, - idpDescriptionSubject :: Text - } + SendSAMLIdPChanged :: EmailAddress -> TeamId -> Maybe UserId -> [CertDescription] -> [CertDescription] -> IdPId -> Issuer -> URI -> Maybe Locale -> EmailSubsystem m () makeSem ''EmailSubsystem diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs index b25f9696659..9f9bf8a6e69 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs @@ -32,6 +32,7 @@ import Data.Text.Lazy (toStrict) import Data.Text.Lazy qualified as TL import Data.Text.Template import Data.UUID (toText) +import Data.X509.Extended import Imports import Network.Mail.Mime import Polysemy @@ -605,8 +606,8 @@ sendSAMLIdPChangedImpl :: EmailAddress -> TeamId -> Maybe UserId -> - [IdPDetails] -> - [IdPDetails] -> + [CertDescription] -> + [CertDescription] -> IdPId -> Issuer -> URI -> @@ -624,8 +625,8 @@ renderIdPConfigChangeEmail :: EmailAddress -> IdPConfigChangeEmailTemplate -> Map Text Text -> - [IdPDetails] -> - [IdPDetails] -> + [CertDescription] -> + [CertDescription] -> TeamId -> Maybe UserId -> IdPId -> @@ -676,13 +677,13 @@ renderIdPConfigChangeEmail email IdPConfigChangeEmailTemplate {..} branding adde from = Address (Just idpConfigChangeEmailSenderName) (fromEmail idpConfigChangeEmailSender) to = Address Nothing (fromEmail email) - idpDetailsToMap :: IdPDetails -> Map Text Text + idpDetailsToMap :: CertDescription -> Map Text Text idpDetailsToMap d = empty @Text @Text - & Map.insert "algorithm" d.idpDescriptionFingerprintAlgorithm - & Map.insert "fingerprint" d.idpDescriptionFingerprint - & Map.insert "subject" d.idpDescriptionSubject - & Map.insert "issuer" d.idpDescriptionSubject + & Map.insert "algorithm" (T.pack d.fingerprintAlgorithm) + & Map.insert "fingerprint" (T.pack d.fingerprint) + & Map.insert "subject" (T.pack d.subject) + & Map.insert "issuer" (T.pack d.issuer) ------------------------------------------------------------------------------- -- MIME Conversions diff --git a/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs index ac3153efe23..f858ba63552 100644 --- a/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs +++ b/libs/wire-subsystems/src/Wire/SAMLEmailSubsystem/Interpreter.hs @@ -6,9 +6,8 @@ where import Control.Lens ((^.), (^..)) import Data.Id (UserId) import Data.List.NonEmpty qualified as NE -import Data.Text qualified as T import Data.X509 qualified as X509 -import Data.X509.Extended (CertDescription (..), certDescription) +import Data.X509.Extended (certDescription) import Imports import Polysemy import SAML2.WebSSO.Types @@ -17,7 +16,6 @@ import Wire.API.Locale import Wire.API.Routes.Internal.Brig import Wire.API.Team.Member import Wire.API.User.IdentityProvider -import Wire.EmailSubsystem (IdPDetails (..)) import Wire.EmailSubsystem qualified as Email import Wire.SAMLEmailSubsystem import Wire.StoredUser @@ -52,7 +50,7 @@ sendSAMLIdPChangedImpl notif = do iss = origIdP._idpMetadata._edIssuer idPId = origIdP._idpId tid = origIdP ^. idpExtraInfo . team - (addedCerts, removedCerts) = bimap (toDesc <$>) (toDesc <$>) certsChanges + (addedCerts, removedCerts) = bimap (certDescription <$>) (certDescription <$>) certsChanges Email.sendSAMLIdPChanged email tid mbUserId addedCerts removedCerts idPId iss endpoint loc origIdP :: IdP @@ -83,15 +81,6 @@ sendSAMLIdPChangedImpl notif = do onlyR = r \\ l in (onlyL, onlyR) - toDesc :: X509.SignedCertificate -> IdPDetails - toDesc cert = - let desc = certDescription cert - in IdPDetails - { idpDescriptionFingerprintAlgorithm = T.pack desc.fingerprintAlgorithm, - idpDescriptionFingerprint = T.pack desc.fingerprint, - idpDescriptionSubject = T.pack desc.subject - } - getReceivers :: ( Member TeamSubsystem r, Member UserStore r From f47d6bc1d165897d159b8d513978dcc56db56b0a Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 19:45:03 +0100 Subject: [PATCH 59/60] Fix empty newlines in text mails --- libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs | 4 ++-- libs/wire-subsystems/test/resources/mails/created_de.txt | 1 - libs/wire-subsystems/test/resources/mails/created_en.txt | 1 - libs/wire-subsystems/test/resources/mails/deleted_de.txt | 1 - libs/wire-subsystems/test/resources/mails/deleted_en.txt | 1 - 5 files changed, 2 insertions(+), 6 deletions(-) diff --git a/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs b/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs index 9f9bf8a6e69..2d0161d6d5a 100644 --- a/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs +++ b/libs/wire-subsystems/src/Wire/EmailSubsystem/Interpreter.hs @@ -656,10 +656,10 @@ renderIdPConfigChangeEmail email IdPConfigChangeEmailTemplate {..} branding adde & Map.insert "idp_id" ((toText . fromIdPId) idPId) replaceHtml = replace - & Map.insert "certificates_details" (T.unlines [idpDetailsAddedHtml, idpDetailsRemovedHtml]) + & Map.insert "certificates_details" ((T.unlines . Imports.filter (not . T.null)) [idpDetailsAddedHtml, idpDetailsRemovedHtml]) replaceText = replace - & Map.insert "certificates_details" (T.unlines [idpDetailsAddedText, idpDetailsRemovedText]) + & Map.insert "certificates_details" ((T.unlines . Imports.filter (not . T.null)) [idpDetailsAddedText, idpDetailsRemovedText]) txt <- renderTextWithBrandingSem idpConfigChangeEmailBodyText replaceText html <- renderHtmlWithBrandingSem idpConfigChangeEmailBodyHtml replaceHtml diff --git a/libs/wire-subsystems/test/resources/mails/created_de.txt b/libs/wire-subsystems/test/resources/mails/created_de.txt index 56311d7662e..fb648c54957 100644 --- a/libs/wire-subsystems/test/resources/mails/created_de.txt +++ b/libs/wire-subsystems/test/resources/mails/created_de.txt @@ -42,7 +42,6 @@ CN=accounts.accesscontrol.windows.net -------------------------------------------------------------------------------- - Wenn Sie diese Ă„nderung nicht veranlasst haben, wenden Sie sich bitte an den Wire Support. [https://support.wire.com/] diff --git a/libs/wire-subsystems/test/resources/mails/created_en.txt b/libs/wire-subsystems/test/resources/mails/created_en.txt index e6438445cbe..c1eb08a1a89 100644 --- a/libs/wire-subsystems/test/resources/mails/created_en.txt +++ b/libs/wire-subsystems/test/resources/mails/created_en.txt @@ -42,7 +42,6 @@ CN=accounts.accesscontrol.windows.net -------------------------------------------------------------------------------- - If you did not initiate this change, please reach out to the Wire support. [https://support.wire.com/] diff --git a/libs/wire-subsystems/test/resources/mails/deleted_de.txt b/libs/wire-subsystems/test/resources/mails/deleted_de.txt index 07fa70ba6af..29a4a6c8b96 100644 --- a/libs/wire-subsystems/test/resources/mails/deleted_de.txt +++ b/libs/wire-subsystems/test/resources/mails/deleted_de.txt @@ -28,7 +28,6 @@ IdP-ID: -------------------------------------------------------------------------------- - Entfernt: SHA1 Fingerabdruck: diff --git a/libs/wire-subsystems/test/resources/mails/deleted_en.txt b/libs/wire-subsystems/test/resources/mails/deleted_en.txt index 5576bc14190..c70c157d2f3 100644 --- a/libs/wire-subsystems/test/resources/mails/deleted_en.txt +++ b/libs/wire-subsystems/test/resources/mails/deleted_en.txt @@ -28,7 +28,6 @@ IdP ID: -------------------------------------------------------------------------------- - Removed: SHA1 fingerprint: From 4407ad5a31d5c97acb56aa32d6c1bd1d07f8fe91 Mon Sep 17 00:00:00 2001 From: Sven Tennie Date: Wed, 28 Jan 2026 19:45:50 +0100 Subject: [PATCH 60/60] Fix typo --- .../test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs index 668c2cbedd8..85def35b0fc 100644 --- a/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs +++ b/libs/wire-subsystems/test/unit/Wire/SAMLEmailSubsystem/InterpreterSpec.hs @@ -65,7 +65,7 @@ spec = do enTextParts <- runIO $ createTextParts "en" deTextParts <- runIO $ createTextParts "de" let -- We don't test all locals such that we do not have to adjust this test - -- for every new translation. So far, there are translations for Germand + -- for every new translation. So far, there are translations for German -- and English. There's none for Spanish (falls back to English). testLocals :: [(Locale, RenderedTextParts)] = flip zip ((replicate 5 enTextParts) ++ (replicate 2 deTextParts)) $