Skip to content

Commit

Permalink
Feature Flags in galley options. (#825)
Browse files Browse the repository at this point in the history
* Feature flags in galley options file.

* Honour sso feature flag.

* Honour legalhold feature flag (test).

* Honour legalhold feature flag (handler).

* Disable all LH tests if feature is disabled.
  • Loading branch information
fisx authored Aug 30, 2019
1 parent 9e0dd77 commit dbf9613
Show file tree
Hide file tree
Showing 8 changed files with 124 additions and 26 deletions.
8 changes: 8 additions & 0 deletions libs/brig-types/test/unit/Test/Brig/Types/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,7 @@ tests = testGroup "Common (types vs. aeson)"
, run @ApproveLegalHoldForUserRequest
, run @SSOStatus
, run @SSOTeamConfig
, run @FeatureFlags
, testCase "{} is a valid TeamMemberDeleteData" $ do
assertEqual "{}" (Right $ newTeamMemberDeleteData Nothing) (eitherDecode "{}")
]
Expand Down Expand Up @@ -82,3 +83,10 @@ instance Arbitrary SSOStatus where

instance Arbitrary SSOTeamConfig where
arbitrary = SSOTeamConfig <$> arbitrary

instance Arbitrary FeatureFlags where
arbitrary = FeatureFlags <$> arbitrary
shrink (FeatureFlags ls) = FeatureFlags <$> shrink ls

instance Arbitrary FeatureFlag where
arbitrary = Test.Tasty.QuickCheck.elements [minBound..]
22 changes: 22 additions & 0 deletions libs/galley-types/src/Galley/Types/Teams.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,9 @@ module Galley.Types.Teams
, TeamCreationTime (..)
, tcTime

, FeatureFlags(..)
, FeatureFlag(..)

, TeamList
, newTeamList
, teamListTeams
Expand Down Expand Up @@ -313,6 +316,25 @@ newtype TeamCreationTime = TeamCreationTime
{ _tcTime :: Int64
}

newtype FeatureFlags = FeatureFlags (Set FeatureFlag)
deriving (Eq, Show, Generic)

data FeatureFlag = FeatureSSO | FeatureLegalHold
deriving (Eq, Ord, Show, Enum, Bounded, Generic)

instance FromJSON FeatureFlags where
parseJSON = withObject "FeatureFlags" $ \obj -> do
sso <- fromMaybe False <$> obj .:? "sso"
legalhold <- fromMaybe False <$> obj .:? "legalhold"
pure . FeatureFlags . Set.fromList $
[ FeatureSSO | sso ] <>
[ FeatureLegalHold | legalhold ]

instance ToJSON FeatureFlags where
toJSON (FeatureFlags flags) = object $
[ "sso" .= (FeatureSSO `elem` flags) ] <>
[ "legalhold" .= (FeatureLegalHold `elem` flags) ]

newTeam :: TeamId -> UserId -> Text -> Text -> TeamBinding -> Team
newTeam tid uid nme ico bnd = Team tid uid nme ico Nothing bnd

Expand Down
18 changes: 18 additions & 0 deletions services/galley/galley.integration.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,24 @@ settings:
maxConvSize: 16
intraListing: false
conversationCodeURI: https://app.wire.com/join/
featureFlags:
# SSO: this sets the default setting for each time, which can
# always be overridden by customer support / backoffice.
# IMPORTANT: if you change sso from 'enabled' to 'disabled' after
# running 'enabled' in production, you need to run this migration
# script to fix all teams that have registered an idp:
# https://github.com/wireapp/wire-server/tree/master/tools/db/migrate-sso-feature-flag
# if you don't, the idp will keep working, but the admin won't be
# able to register new idps.
# disabled for integration tests (the ones who need it on will
# turn it on themselves).
sso: false

# Legal Hold: this decides whether customer support / backoffice
# is allowed to turn the feature on for individual teams. the
# default for new teams is always "false", no matter what the
# feature flag is set to.
legalhold: true

logLevel: Info
logNetStrings: false
Expand Down
3 changes: 3 additions & 0 deletions services/galley/src/Galley/API/Error.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,6 +124,9 @@ legalHoldServiceNotRegistered = Error status400 "legalhold-not-registered" "lega
legalHoldServiceBadResponse :: Error
legalHoldServiceBadResponse = Error status400 "legalhold-status-bad" "legal hold service: invalid response"

legalHoldFeatureFlagNotEnabled :: Error
legalHoldFeatureFlagNotEnabled = Error status403 "legalhold-not-enabled" "legal hold is not enabled for this wire instance"

legalHoldNotEnabled :: Error
legalHoldNotEnabled = Error status403 "legalhold-not-enabled" "legal hold is not enabled for this team"

Expand Down
12 changes: 9 additions & 3 deletions services/galley/src/Galley/API/Teams.hs
Original file line number Diff line number Diff line change
Expand Up @@ -523,13 +523,16 @@ getLegalholdStatus (uid ::: tid ::: ct) = do
-- These endpoints are internal only and meant to be called
-- only from authorized personnel (e.g., from a backoffice tool)

-- | Get legal SSO status for a team.
-- | Get SSO status for a team.
getSSOStatusInternal :: TeamId ::: JSON -> Galley Response
getSSOStatusInternal (tid ::: _) = do
defConfig <- do
featureSSO <- view (options . optSettings . featureEnabled FeatureSSO)
pure $ if featureSSO
then SSOTeamConfig SSOEnabled
else SSOTeamConfig SSODisabled
ssoTeamConfig <- SSOData.getSSOTeamConfig tid
pure . json . fromMaybe defConfig $ ssoTeamConfig
where
defConfig = SSOTeamConfig SSODisabled

-- | Enable or disable SSO for a team.
setSSOStatusInternal :: TeamId ::: JsonRequest SSOTeamConfig ::: JSON -> Galley Response
Expand All @@ -552,6 +555,9 @@ getLegalholdStatusInternal (tid ::: _) = do
-- | Enable or disable legal hold for a team.
setLegalholdStatusInternal :: TeamId ::: JsonRequest LegalHoldTeamConfig ::: JSON -> Galley Response
setLegalholdStatusInternal (tid ::: req ::: _) = do
do featureLegalHold <- view (options . optSettings . featureEnabled FeatureLegalHold)
unless featureLegalHold $ throwM legalHoldFeatureFlagNotEnabled

legalHoldTeamConfig <- fromJsonBody req
case legalHoldTeamConfigStatus legalHoldTeamConfig of
LegalHoldDisabled -> removeSettings' tid Nothing
Expand Down
9 changes: 9 additions & 0 deletions services/galley/src/Galley/Options.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ import Util.Options
import Util.Options.Common
import System.Logger.Extended (Level, LogFormat)
import Data.Misc
import Galley.Types.Teams (FeatureFlags(..), FeatureFlag)

data Settings = Settings
{
Expand All @@ -20,11 +21,19 @@ data Settings = Settings
, _setIntraListing :: !Bool
-- | URI prefix for conversations with access mode @code@
, _setConversationCodeURI :: !HttpsUrl
, _setFeatureFlags :: !(Maybe FeatureFlags)
} deriving (Show, Generic)

deriveFromJSON toOptionFieldName ''Settings
makeLenses ''Settings

featureEnabled :: FeatureFlag -> Getter Settings Bool
featureEnabled flag
= setFeatureFlags
. to (\case
Nothing -> False
Just (FeatureFlags flags) -> flag `elem` flags)

data JournalOpts = JournalOpts
{ _awsQueueName :: !Text -- ^ SQS queue name to send team events
, _awsEndpoint :: !AWSEndpoint -- ^ AWS endpoint
Expand Down
47 changes: 35 additions & 12 deletions services/galley/test/integration/API/Teams.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,14 +15,15 @@ import Data.Id
import Data.List1
import Data.Misc (PlainTextPassword (..))
import Data.Range
import Galley.Options (optSettings, featureEnabled)
import Galley.Types hiding (EventType (..), EventData (..), MemberUpdate (..))
import Galley.Types.Teams
import Galley.Types.Teams.Intra
import Galley.Types.Teams.SSO
import Gundeck.Types.Notification
import Network.HTTP.Types.Status (status403)
import TestHelpers (test)
import TestSetup (TestSetup, TestM, tsCannon, tsGalley)
import TestSetup (TestSetup, TestM, tsCannon, tsGalley, tsGConf)
import Test.Tasty
import Test.Tasty.Cannon (TimeoutUnit (..), (#))
import Test.Tasty.HUnit
Expand Down Expand Up @@ -175,7 +176,12 @@ testEnableSSOPerTeam = do
assertEqual "bad status" status403 status
assertEqual "bad label" "not-implemented" label

check "Teams should start with SSO disabled" SSODisabled
featureSSO <- view (tsGConf . optSettings . featureEnabled FeatureSSO)
if not featureSSO
then do
check "Teams should start with SSO disabled" SSODisabled
else do
check "Teams should start with SSO enabled" SSOEnabled

putSSOEnabledInternal tid SSOEnabled
check "Calling 'putEnabled True' should enable SSO" SSOEnabled
Expand Down Expand Up @@ -1138,12 +1144,15 @@ getLegalHoldEnabledInternal tid = do
. paths ["i", "teams", toByteString' tid, "features", "legalhold"]

putLegalHoldEnabledInternal :: HasCallStack => TeamId -> LegalHoldStatus -> TestM ()
putLegalHoldEnabledInternal tid enabled = do
putLegalHoldEnabledInternal = putLegalHoldEnabledInternal' expect2xx

putLegalHoldEnabledInternal' :: HasCallStack => (Request -> Request) -> TeamId -> LegalHoldStatus -> TestM ()
putLegalHoldEnabledInternal' reqmod tid enabled = do
g <- view tsGalley
void . put $ g
. paths ["i", "teams", toByteString' tid, "features", "legalhold"]
. json (LegalHoldTeamConfig enabled)
. expect2xx
. reqmod


testFeatureFlags :: TestM ()
Expand All @@ -1166,12 +1175,21 @@ testFeatureFlags = do
setSSOInternal :: HasCallStack => SSOStatus -> TestM ()
setSSOInternal = putSSOEnabledInternal tid

getSSO SSODisabled
getSSOInternal SSODisabled
featureSSO <- view (tsGConf . optSettings . featureEnabled FeatureSSO)
if not featureSSO
then do -- disabled
getSSO SSODisabled
getSSOInternal SSODisabled

setSSOInternal SSOEnabled
getSSO SSOEnabled
getSSOInternal SSOEnabled

setSSOInternal SSOEnabled
getSSO SSOEnabled
getSSOInternal SSOEnabled
else do -- enabled
-- since we don't allow to disable (see 'disableSsoNotImplemented'), we can't test
-- much here. (disable failure is covered in "enable/disable SSO" above.)
getSSO SSOEnabled
getSSOInternal SSOEnabled

-- legalhold

Expand All @@ -1191,6 +1209,11 @@ testFeatureFlags = do
getLegalHold LegalHoldDisabled
getLegalHoldInternal LegalHoldDisabled

setLegalHoldInternal LegalHoldEnabled
getLegalHold LegalHoldEnabled
getLegalHoldInternal LegalHoldEnabled
featureLegalHold <- view (tsGConf . optSettings . featureEnabled FeatureLegalHold)
if featureLegalHold
then do
setLegalHoldInternal LegalHoldEnabled
getLegalHold LegalHoldEnabled
getLegalHoldInternal LegalHoldEnabled
else do
putLegalHoldEnabledInternal' expect4xx tid LegalHoldEnabled
31 changes: 20 additions & 11 deletions services/galley/test/integration/API/Teams/LegalHold.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@ import Data.Text.Encoding (encodeUtf8)
import Galley.API.Swagger (GalleyRoutes)
import Galley.External.LegalHoldService (validateServiceKey)
import Galley.Types.Teams
import Galley.Options (optSettings, featureEnabled)
import GHC.Generics hiding (to)
import GHC.TypeLits
import Gundeck.Types.Notification (ntfPayload)
Expand All @@ -39,6 +40,7 @@ import Network.Wai
import Network.Wai as Wai
import Servant.Swagger (validateEveryToJSON)
import System.Environment (withArgs)
import System.IO (hPutStrLn)
import TestHelpers
import Test.Hspec (hspec)
import Test.QuickCheck.Instances ()
Expand All @@ -65,27 +67,34 @@ import qualified Galley.Types.Clients as Clients
import qualified Test.Tasty.Cannon as WS


onlyIfLhEnabled :: TestM () -> TestM ()
onlyIfLhEnabled action = do
featureLegalHold <- view (tsGConf . optSettings . featureEnabled FeatureLegalHold)
if featureLegalHold
then action
else liftIO $ hPutStrLn stderr "*** legalhold feature flag disabled, not running integration tests"

tests :: IO TestSetup -> TestTree
tests s = testGroup "Teams LegalHold API"
[ test s "swagger / json consistency" testSwaggerJsonConsistency
[ test s "swagger / json consistency" (onlyIfLhEnabled testSwaggerJsonConsistency)

-- device handling (CRUD)
, test s "POST /teams/{tid}/legalhold/{uid}" testRequestLegalHoldDevice
, test s "PUT /teams/{tid}/legalhold/approve" testApproveLegalHoldDevice
, test s "POST /teams/{tid}/legalhold/{uid}" (onlyIfLhEnabled testRequestLegalHoldDevice)
, test s "PUT /teams/{tid}/legalhold/approve" (onlyIfLhEnabled testApproveLegalHoldDevice)
, test s "(user denies approval: nothing needs to be done in backend)" (pure ())
, test s "GET /teams/{tid}/legalhold/{uid}" testGetLegalHoldDeviceStatus
, test s "DELETE /teams/{tid}/legalhold/{uid}" testDisableLegalHoldForUser
, test s "GET /teams/{tid}/legalhold/{uid}" (onlyIfLhEnabled testGetLegalHoldDeviceStatus)
, test s "DELETE /teams/{tid}/legalhold/{uid}" (onlyIfLhEnabled testDisableLegalHoldForUser)

-- legal hold settings
, test s "POST /teams/{tid}/legalhold/settings" testCreateLegalHoldTeamSettings
, test s "GET /teams/{tid}/legalhold/settings" testGetLegalHoldTeamSettings
, test s "DELETE /teams/{tid}/legalhold/settings" testRemoveLegalHoldFromTeam
, test s "GET, PUT [/i]?/teams/{tid}/legalhold" testEnablePerTeam
, test s "POST /teams/{tid}/legalhold/settings" (onlyIfLhEnabled testCreateLegalHoldTeamSettings)
, test s "GET /teams/{tid}/legalhold/settings" (onlyIfLhEnabled testGetLegalHoldTeamSettings)
, test s "DELETE /teams/{tid}/legalhold/settings" (onlyIfLhEnabled testRemoveLegalHoldFromTeam)
, test s "GET, PUT [/i]?/teams/{tid}/legalhold" (onlyIfLhEnabled testEnablePerTeam)

-- behavior of existing end-points
, test s "POST /clients" testCannotCreateLegalHoldDeviceOldAPI
, test s "POST /clients" (onlyIfLhEnabled testCannotCreateLegalHoldDeviceOldAPI)

, test s "GET /teams/{tid}/members" testGetTeamMembersIncludesLHStatus
, test s "GET /teams/{tid}/members" (onlyIfLhEnabled testGetTeamMembersIncludesLHStatus)

-- See also Client Tests in Brig; where behaviour around deleting/adding LH clients is
-- tested
Expand Down

0 comments on commit dbf9613

Please sign in to comment.