Skip to content

Commit

Permalink
Emit event notification for file sharing feature update. (#1655)
Browse files Browse the repository at this point in the history
Authored-by: Stefan Matting <stefan@wire.com>
  • Loading branch information
fisx authored Jul 17, 2021
1 parent 9e172a3 commit 44f4bd1
Show file tree
Hide file tree
Showing 12 changed files with 251 additions and 8 deletions.
3 changes: 2 additions & 1 deletion CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -38,13 +38,14 @@ settings:

## Features

* `fileSharing` feature config (#1652, #1654)
* `fileSharing` feature config (#1652, #1654, #1655)
* Add user_id to csv export (#1663)

## Bug fixes and other updates

* New, hardened end-point for changing email
* Fix: CSV export is missing SCIM external id when SAML is also used (#1608)
* Fix: sso_id field in user record (brig) was not always filled correctly in cassandra (#1334)

## Documentation

Expand Down
101 changes: 101 additions & 0 deletions libs/wire-api/src/Wire/API/Event/FeatureConfig.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,101 @@
-- This file is part of the Wire Server implementation.
--
-- Copyright (C) 2020 Wire Swiss GmbH <opensource@wire.com>
--
-- This program is free software: you can redistribute it and/or modify it under
-- the terms of the GNU Affero General Public License as published by the Free
-- Software Foundation, either version 3 of the License, or (at your option) any
-- later version.
--
-- This program is distributed in the hope that it will be useful, but WITHOUT
-- ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
-- FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more
-- details.
--
-- You should have received a copy of the GNU Affero General Public License along
-- with this program. If not, see <https://www.gnu.org/licenses/>.

module Wire.API.Event.FeatureConfig
( Event (..),
EventType (..),
EventData (..),
)
where

import Control.Arrow ((&&&))
import Control.Lens (makePrisms, _1)
import Data.Aeson (FromJSON (..), ToJSON (..))
import qualified Data.HashMap.Strict as HashMap
import Data.Json.Util (ToJSONObject (..))
import Data.Schema
import qualified Data.Swagger as S
import Imports
import Wire.API.Team.Feature (TeamFeatureAppLockConfig, TeamFeatureClassifiedDomainsConfig, TeamFeatureName (..), TeamFeatureStatusNoConfig, TeamFeatureStatusWithConfig)

data Event = Event
{ _eventType :: EventType,
_eventFeatureName :: TeamFeatureName,
_eventData :: EventData
}
deriving (Eq, Show, Generic)

data EventType = Update
deriving (Eq, Show)

instance ToSchema EventType where
schema =
enum @Text "EventType" $
mconcat
[ element "feature-config.update" Update
]

data EventData
= EdFeatureWithoutConfigChanged TeamFeatureStatusNoConfig
| EdFeatureApplockChanged (TeamFeatureStatusWithConfig TeamFeatureAppLockConfig)
| EdFeatureClassifiedDomainsChanged (TeamFeatureStatusWithConfig TeamFeatureClassifiedDomainsConfig)
deriving (Eq, Show, Generic)

makePrisms ''EventData

taggedEventDataSchema :: ObjectSchema SwaggerDoc (TeamFeatureName, EventData)
taggedEventDataSchema =
bind
(fst .= field "name" schema)
(snd .= fieldOver _1 "data" edata)
where
edata = dispatch $ \case
TeamFeatureLegalHold -> tag _EdFeatureWithoutConfigChanged (unnamed schema)
TeamFeatureSSO -> tag _EdFeatureWithoutConfigChanged (unnamed schema)
TeamFeatureSearchVisibility -> tag _EdFeatureWithoutConfigChanged (unnamed schema)
TeamFeatureValidateSAMLEmails -> tag _EdFeatureWithoutConfigChanged (unnamed schema)
TeamFeatureDigitalSignatures -> tag _EdFeatureWithoutConfigChanged (unnamed schema)
TeamFeatureAppLock -> tag _EdFeatureApplockChanged (unnamed schema)
TeamFeatureFileSharing -> tag _EdFeatureWithoutConfigChanged (unnamed schema)
TeamFeatureClassifiedDomains -> tag _EdFeatureClassifiedDomainsChanged (unnamed schema)

eventObjectSchema :: ObjectSchema SwaggerDoc Event
eventObjectSchema =
mkEvent
<$> (_eventFeatureName &&& _eventData) .= taggedEventDataSchema
<*> _eventType .= field "type" schema
where
mkEvent :: (TeamFeatureName, EventData) -> EventType -> Event
mkEvent (feature, eventData) eventType = Event eventType feature eventData

instance ToSchema Event where
schema = object "Event" eventObjectSchema

instance ToJSONObject Event where
toJSONObject =
HashMap.fromList
. fromMaybe []
. schemaOut eventObjectSchema

instance FromJSON Event where
parseJSON = schemaParseJSON

instance ToJSON Event where
toJSON = schemaToJSON

instance S.ToSchema Event where
declareNamedSchema = schemaToSwagger
7 changes: 7 additions & 0 deletions libs/wire-api/src/Wire/API/Team/Feature.hs
Original file line number Diff line number Diff line change
Expand Up @@ -166,6 +166,13 @@ instance ToByteString TeamFeatureName where
builder TeamFeatureFileSharing = "fileSharing"
builder TeamFeatureClassifiedDomains = "classifiedDomains"

instance ToSchema TeamFeatureName where
schema =
enum @Text
"TeamFeatureName"
$ mconcat
(map (\feat -> element (cs . toByteString' $ feat) feat) [minBound .. maxBound])

class HasDeprecatedFeatureName (a :: TeamFeatureName) where
type DeprecatedFeatureName a :: Symbol

Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
{
"data": {
"status": "enabled"
},
"name": "fileSharing",
"type": "feature-config.update"
}
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
{
"data": {
"status": "disabled"
},
"name": "sso",
"type": "feature-config.update"
}
11 changes: 11 additions & 0 deletions libs/wire-api/test/golden/testObject_FeatureConfigEvent_3.json
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
{
"data": {
"status": "disabled",
"config": {
"enforceAppLock": true,
"inactivityTimeoutSecs": 300
}
},
"name": "appLock",
"type": "feature-config.update"
}
16 changes: 12 additions & 4 deletions libs/wire-api/test/unit/Test/Wire/API/Golden/Manual.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ import Test.Tasty.HUnit
import Test.Wire.API.Golden.Manual.ClientCapability
import Test.Wire.API.Golden.Manual.ClientCapabilityList
import Test.Wire.API.Golden.Manual.ConversationCoverView
import Test.Wire.API.Golden.Manual.FeatureConfigEvent
import Test.Wire.API.Golden.Manual.QualifiedUserClientPrekeyMap
import Test.Wire.API.Golden.Manual.UserClientPrekeyMap
import Test.Wire.API.Golden.Runner
Expand All @@ -31,7 +32,7 @@ tests :: TestTree
tests =
testGroup
"Manual golden tests"
[ testCase ("UserClientPrekeyMap") $
[ testCase "UserClientPrekeyMap" $
testObjects
[ (testObject_UserClientPrekeyMap_1, "testObject_UserClientPrekeyMap_1.json"),
(testObject_UserClientPrekeyMap_2, "testObject_UserClientPrekeyMap_2.json"),
Expand All @@ -42,7 +43,7 @@ tests =
(testObject_UserClientPrekeyMap_7, "testObject_UserClientPrekeyMap_7.json"),
(testObject_UserClientPrekeyMap_8, "testObject_UserClientPrekeyMap_8.json")
],
testCase ("QualifiedUserClientPrekeyMap") $
testCase "QualifiedUserClientPrekeyMap" $
testObjects
[ (testObject_QualifiedUserClientPrekeyMap_1, "testObject_QualifiedUserClientPrekeyMap_1.json"),
(testObject_QualifiedUserClientPrekeyMap_2, "testObject_QualifiedUserClientPrekeyMap_2.json")
Expand All @@ -53,12 +54,19 @@ tests =
(testObject_ConversationCoverView_2, "testObject_ConversationCoverView_2.json"),
(testObject_ConversationCoverView_3, "testObject_ConversationCoverView_3.json")
],
testCase ("ClientCapability") $
testCase "ClientCapability" $
testObjects
[(testObject_ClientCapability_1, "testObject_ClientCapability_1.json")],
testCase ("ClientCapabilityList") $
testCase "ClientCapabilityList" $
testObjects
[ (testObject_ClientCapabilityList_1, "testObject_ClientCapabilityList_1.json"),
(testObject_ClientCapabilityList_2, "testObject_ClientCapabilityList_2.json")
],
testCase
"Event.FeatureConfig.Event"
$ testObjects
[ (testObject_FeatureConfigEvent_1, "testObject_FeatureConfigEvent_1.json"),
(testObject_FeatureConfigEvent_2, "testObject_FeatureConfigEvent_2.json"),
(testObject_FeatureConfigEvent_3, "testObject_FeatureConfigEvent_3.json")
]
]
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
module Test.Wire.API.Golden.Manual.FeatureConfigEvent where

import Imports
import Wire.API.Event.FeatureConfig
import Wire.API.Team.Feature

testObject_FeatureConfigEvent_1 :: Event
testObject_FeatureConfigEvent_1 = Event Update TeamFeatureFileSharing (EdFeatureWithoutConfigChanged (TeamFeatureStatusNoConfig TeamFeatureEnabled))

testObject_FeatureConfigEvent_2 :: Event
testObject_FeatureConfigEvent_2 = Event Update TeamFeatureSSO (EdFeatureWithoutConfigChanged (TeamFeatureStatusNoConfig TeamFeatureDisabled))

testObject_FeatureConfigEvent_3 :: Event
testObject_FeatureConfigEvent_3 =
Event
Update
TeamFeatureAppLock
( EdFeatureApplockChanged
( TeamFeatureStatusWithConfig
TeamFeatureDisabled
(TeamFeatureAppLockConfig (EnforceAppLock True) 300)
)
)
4 changes: 3 additions & 1 deletion libs/wire-api/wire-api.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ cabal-version: 1.12
--
-- see: https://github.com/sol/hpack
--
-- hash: 12fc6293357c3ba08044d346991fa814c362c6e21a62896dd943feb218c09d02
-- hash: c12b754866b74213ac22c8738621201c6645b85c5afcf7535ff3bf8a86365e13

name: wire-api
version: 0.1.0
Expand Down Expand Up @@ -35,6 +35,7 @@ library
Wire.API.CustomBackend
Wire.API.ErrorDescription
Wire.API.Event.Conversation
Wire.API.Event.FeatureConfig
Wire.API.Event.Team
Wire.API.Message
Wire.API.Message.Proto
Expand Down Expand Up @@ -392,6 +393,7 @@ test-suite wire-api-tests
Test.Wire.API.Golden.Manual.ClientCapability
Test.Wire.API.Golden.Manual.ClientCapabilityList
Test.Wire.API.Golden.Manual.ConversationCoverView
Test.Wire.API.Golden.Manual.FeatureConfigEvent
Test.Wire.API.Golden.Manual.ListConversations
Test.Wire.API.Golden.Manual.QualifiedUserClientPrekeyMap
Test.Wire.API.Golden.Manual.UserClientPrekeyMap
Expand Down
22 changes: 21 additions & 1 deletion services/galley/src/Galley/API/Teams/Features.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,12 +52,16 @@ import Galley.App
import qualified Galley.Data as Data
import qualified Galley.Data.SearchVisibility as SearchVisibilityData
import qualified Galley.Data.TeamFeatures as TeamFeatures
import Galley.Intra.Push (PushEvent (FeatureConfigEvent), newPush, push1)
import Galley.Options
import Galley.Types.Teams hiding (newTeam)
import Imports
import Network.Wai
import Network.Wai.Predicate hiding (Error, or, result, setStatus)
import Network.Wai.Utilities
import qualified System.Logger.Class as Log
import Wire.API.Event.FeatureConfig (EventData (EdFeatureWithoutConfigChanged))
import qualified Wire.API.Event.FeatureConfig as Event
import qualified Wire.API.Team.Feature as Public

data DoAuth = DoAuth UserId | DontDoAuth
Expand Down Expand Up @@ -221,7 +225,9 @@ getFileSharingInternal = getFeatureStatusNoConfig @'Public.TeamFeatureFileSharin
view (options . optSettings . setFeatureFlags . flagFileSharing) <&> Public.tfwoStatus . view unDefaults

setFileSharingInternal :: TeamId -> Public.TeamFeatureStatus 'Public.TeamFeatureFileSharing -> Galley (Public.TeamFeatureStatus 'Public.TeamFeatureFileSharing)
setFileSharingInternal = setFeatureStatusNoConfig @'Public.TeamFeatureFileSharing $ \_ _ -> pure ()
setFileSharingInternal = setFeatureStatusNoConfig @'Public.TeamFeatureFileSharing $ \status tid -> do
let event = Event.Event Event.Update Public.TeamFeatureFileSharing (EdFeatureWithoutConfigChanged (Public.TeamFeatureStatusNoConfig status))
pushFeatureConfigEvent tid event

getAppLockInternal :: TeamId -> Galley (Public.TeamFeatureStatus 'Public.TeamFeatureAppLock)
getAppLockInternal tid = do
Expand All @@ -243,3 +249,17 @@ getClassifiedDomainsInternal _tid = do
Public.TeamFeatureDisabled ->
Public.TeamFeatureStatusWithConfig Public.TeamFeatureDisabled (Public.TeamFeatureClassifiedDomainsConfig [])
Public.TeamFeatureEnabled -> config

pushFeatureConfigEvent :: TeamId -> Event.Event -> Galley ()
pushFeatureConfigEvent tid event = do
memList <- Data.teamMembersForFanout tid
when ((memList ^. teamMemberListType) == ListTruncated) $ do
Log.warn $
Log.field "action" (Log.val "Features.pushFeatureConfigEvent")
. Log.field "feature" (Log.val (toByteString' . Event._eventFeatureName $ event))
. Log.field "team" (Log.val (cs . show $ tid))
. Log.msg @Text "Fanout limit exceeded. Some events will not be sent."
let recipients = membersToRecipients Nothing (memList ^. teamMembers)
for_
(newPush (memList ^. teamMemberListType) Nothing (FeatureConfigEvent event) recipients)
push1
3 changes: 3 additions & 0 deletions services/galley/src/Galley/Intra/Push.hs
Original file line number Diff line number Diff line change
Expand Up @@ -82,14 +82,17 @@ import Safe (headDef, tailDef)
import System.Logger.Class hiding (new)
import UnliftIO (mapConcurrently)
import Util.Options
import qualified Wire.API.Event.FeatureConfig as FeatureConfig

data PushEvent
= ConvEvent Event
| TeamEvent Teams.Event
| FeatureConfigEvent FeatureConfig.Event

pushEventJson :: PushEvent -> Object
pushEventJson (ConvEvent e) = toJSONObject e
pushEventJson (TeamEvent e) = toJSONObject e
pushEventJson (FeatureConfigEvent e) = toJSONObject e

type Recipient = RecipientBy UserId

Expand Down
Loading

0 comments on commit 44f4bd1

Please sign in to comment.