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

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 3 additions & 1 deletion libs/galley-types/src/Galley/Types/Teams.hs
Original file line number Diff line number Diff line change
Expand Up @@ -321,6 +321,7 @@ data HiddenPerm
| ChangeTeamSearchVisibility
| ViewTeamSearchVisibility
| ViewSameTeamEmails
| CreateUpdateDeleteIdp
deriving (Eq, Ord, Show)

-- | See Note [hidden team roles]
Expand All @@ -344,7 +345,8 @@ roleHiddenPermissions role = HiddenPermissions p p
[ ChangeLegalHoldTeamSettings,
ChangeLegalHoldUserSettings,
ChangeTeamSearchVisibility,
ChangeTeamFeature TeamFeatureAppLock
ChangeTeamFeature TeamFeatureAppLock {- the other features can only be changed in stern -},
CreateUpdateDeleteIdp
]
roleHiddenPerms RoleMember =
(roleHiddenPerms RoleExternalPartner <>) $
Expand Down
8 changes: 5 additions & 3 deletions services/spar/src/Spar/API.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,6 +51,7 @@ import Data.Id
import Data.Proxy
import Data.String.Conversions
import Data.Time
import Galley.Types.Teams (HiddenPerm (CreateUpdateDeleteIdp))
import Imports
import OpenSSL.Random (randBytes)
import qualified SAML2.WebSSO as SAML
Expand Down Expand Up @@ -395,9 +396,10 @@ authorizeIdP ::
Maybe UserId ->
IdP ->
m TeamId
authorizeIdP zusr idp = do
teamid <- Brig.getZUsrOwnedTeam zusr
when (teamid /= idp ^. SAML.idpExtraInfo . wiTeam) $ throwSpar SparNotInTeam
authorizeIdP Nothing _ = throwSpar (SparNoPermission (cs $ show CreateUpdateDeleteIdp))
authorizeIdP (Just zusr) idp = do
let teamid = idp ^. SAML.idpExtraInfo . wiTeam
Galley.assertHasPermission teamid CreateUpdateDeleteIdp zusr
pure teamid

enforceHttps :: URI.URI -> Spar ()
Expand Down
2 changes: 2 additions & 0 deletions services/spar/src/Spar/Error.hs
Original file line number Diff line number Diff line change
Expand Up @@ -72,6 +72,7 @@ data SparCustomError
| SparMissingZUsr
| SparNotInTeam
| SparNotTeamOwner
| SparNoPermission LT
| SparSSODisabled
| SparInitLoginWithAuth
| SparInitBindWithoutAuth
Expand Down Expand Up @@ -161,6 +162,7 @@ renderSparError (SAML.CustomError SparIdPNotFound) = Right $ Wai.Error status404
renderSparError (SAML.CustomError SparMissingZUsr) = Right $ Wai.Error status400 "client-error" "[header] 'Z-User' required"
renderSparError (SAML.CustomError SparNotInTeam) = Right $ Wai.Error status403 "no-team-member" "Requesting user is not a team member or not a member of this team."
renderSparError (SAML.CustomError SparNotTeamOwner) = Right $ Wai.Error status403 "insufficient-permissions" "You need to be a team owner."
renderSparError (SAML.CustomError (SparNoPermission perm)) = Right $ Wai.Error status403 "insufficient-permissions" ("You need permission " <> cs perm <> ".")
renderSparError (SAML.CustomError SparSSODisabled) = Right $ Wai.Error status403 "sso-disabled" "Please ask customer support to enable this feature for your team."
renderSparError (SAML.CustomError SparInitLoginWithAuth) = Right $ Wai.Error status403 "login-with-auth" "This end-point is only for login, not binding."
renderSparError (SAML.CustomError SparInitBindWithoutAuth) = Right $ Wai.Error status403 "bind-without-auth" "This end-point is only for binding, not login."
Expand Down
17 changes: 17 additions & 0 deletions services/spar/src/Spar/Intra/Galley.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,7 @@ import Control.Lens
import Control.Monad.Except
import Data.ByteString.Conversion
import Data.Id (TeamId, UserId)
import Data.String.Conversions (cs)
import Galley.Types.Teams
import Imports
import Network.HTTP.Types (status403)
Expand Down Expand Up @@ -62,6 +63,22 @@ assertIsTeamOwner tid uid = do
when (responseStatus r == status403) $ do
throwSpar SparNotTeamOwner

-- | user is member of a given team and has a given permission there.
assertHasPermission ::
(HasCallStack, MonadSparToGalley m, MonadError SparError m, IsPerm perm, Show perm) =>
TeamId ->
perm ->
UserId ->
m ()
assertHasPermission tid perm uid = do
resp <-
call $
method GET
. (paths ["i", "teams", toByteString' tid, "members", toByteString' uid])
case (statusCode resp, parseResponse @TeamMember "galley" resp) of
(200, Right member) | hasPermission member perm -> pure ()
_ -> throwSpar (SparNoPermission (cs $ show perm))

assertSSOEnabled ::
(HasCallStack, MonadError SparError m, MonadSparToGalley m) =>
TeamId ->
Expand Down
44 changes: 29 additions & 15 deletions services/spar/test-integration/Test/Spar/APISpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -479,7 +479,7 @@ specBindingUsers = describe "binding existing users to sso identities" $ do
(uid, teamid, idp, (_, privcreds)) <- registerTestIdPWithMeta
(subj, _, _) <- initialBind uid idp privcreds
uid' <-
let Just perms = Galley.newPermissions mempty mempty
let perms = Galley.noPermissions
in call $ createTeamMember (env ^. teBrig) (env ^. teGalley) teamid perms
(_, sparresp) <- reBindSame uid' idp privcreds subj
checkDenyingAuthnResp sparresp "subject-id-taken"
Expand Down Expand Up @@ -530,24 +530,25 @@ testGetPutDelete whichone = do
whichone (env ^. teSpar) Nothing (IdPId UUID.nil) idpmeta
`shouldRespondWith` checkErrHspec 404 "not-found"
context "no zuser" $ do
it "responds with 'client error'" $ do
it "responds with 'insufficient permissions'" $ do
env <- ask
(_, _, (^. idpId) -> idpid, (idpmeta, _)) <- registerTestIdPWithMeta
whichone (env ^. teSpar) Nothing idpid idpmeta
`shouldRespondWith` checkErrHspec 400 "client-error"
`shouldRespondWith` checkErrHspec 403 "insufficient-permissions"

context "zuser has no team" $ do
it "responds with 'no team member'" $ do
it "responds with 'insufficient permissions'" $ do
env <- ask
(_, _, (^. idpId) -> idpid, (idpmeta, _)) <- registerTestIdPWithMeta
(uid, _) <- call $ createRandomPhoneUser (env ^. teBrig)
whichone (env ^. teSpar) (Just uid) idpid idpmeta
`shouldRespondWith` checkErrHspec 403 "no-team-member"
`shouldRespondWith` checkErrHspec 403 "insufficient-permissions"
context "zuser is a team member, but not a team owner" $ do
it "responds with 'insufficient-permissions' and a helpful message" $ do
env <- ask
(_, teamid, (^. idpId) -> idpid, (idpmeta, _)) <- registerTestIdPWithMeta
newmember <-
let Just perms = Galley.newPermissions mempty mempty
let perms = Galley.noPermissions
in call $ createTeamMember (env ^. teBrig) (env ^. teGalley) teamid perms
whichone (env ^. teSpar) (Just newmember) idpid idpmeta
`shouldRespondWith` checkErrHspec 403 "insufficient-permissions"
Expand All @@ -571,12 +572,12 @@ specCRUDIdentityProvider = do
describe "GET /identity-providers/:idp" $ do
testGetPutDelete (\o t i _ -> callIdpGet' o t i)
context "zuser has wrong team" $ do
it "responds with 'no team member'" $ do
it "responds with 'insufficient permissions'" $ do
env <- ask
(_, _, (^. idpId) -> idpid) <- registerTestIdP
(uid, _) <- call $ createUserWithTeam (env ^. teBrig) (env ^. teGalley)
callIdpGet' (env ^. teSpar) (Just uid) idpid
`shouldRespondWith` checkErrHspec 403 "no-team-member"
`shouldRespondWith` checkErrHspec 403 "insufficient-permissions"
context "known IdP, client is team owner" $ do
it "responds with 2xx and IdP" $ do
env <- ask
Expand All @@ -595,7 +596,7 @@ specCRUDIdentityProvider = do
(_owner :: UserId, teamid :: TeamId) <-
call $ createUserWithTeam (env ^. teBrig) (env ^. teGalley)
member :: UserId <-
let Just perms = Galley.newPermissions mempty mempty
let perms = Galley.noPermissions
in call $ createTeamMember (env ^. teBrig) (env ^. teGalley) teamid perms
callIdpGetAll' (env ^. teSpar) (Just member)
`shouldRespondWith` checkErrHspec 403 "insufficient-permissions"
Expand Down Expand Up @@ -631,7 +632,21 @@ specCRUDIdentityProvider = do
(_, _, (^. idpId) -> idpid) <- registerTestIdP
(uid, _) <- call $ createUserWithTeam (env ^. teBrig) (env ^. teGalley)
callIdpDelete' (env ^. teSpar) (Just uid) idpid
`shouldRespondWith` checkErrHspec 403 "no-team-member"
`shouldRespondWith` checkErrHspec 403 "insufficient-permissions"
context "zuser is admin resp. member" $ do
it "responds 204 resp. 403" $ do
env <- ask
(_, tid, (^. idpId) -> idpid) <- registerTestIdP
let mkUser :: Galley.Role -> TestSpar UserId
mkUser role = do
let perms = Galley.rolePermissions role
call $ createTeamMember (env ^. teBrig) (env ^. teGalley) tid perms
admin <- mkUser Galley.RoleAdmin
member <- mkUser Galley.RoleMember
callIdpDelete' (env ^. teSpar) (Just member) idpid
`shouldRespondWith` checkErrHspec 403 "insufficient-permissions"
callIdpDelete' (env ^. teSpar) (Just admin) idpid
`shouldRespondWith` ((== 204) . statusCode)
context "known IdP, IdP empty, client is team owner, without email" $ do
it "responds with 2xx and removes IdP" $ do
env <- ask
Expand Down Expand Up @@ -838,7 +853,7 @@ specCRUDIdentityProvider = do
env <- ask
(_owner, tid, idp) <- registerTestIdP
newmember <-
let Just perms = Galley.newPermissions mempty mempty
let perms = Galley.noPermissions
in call $ createTeamMember (env ^. teBrig) (env ^. teGalley) tid perms
callIdpCreate' (env ^. teSpar) (Just newmember) (idp ^. idpMetadata)
`shouldRespondWith` checkErrHspec 403 "insufficient-permissions"
Expand Down Expand Up @@ -1144,10 +1159,9 @@ specAux = do
liftIO $ userTeam parsedResp `shouldSatisfy` isJust
permses :: [Galley.Permissions]
permses =
fromJust
<$> [ Just Galley.fullPermissions,
Galley.newPermissions mempty mempty
]
[ Galley.fullPermissions,
Galley.noPermissions
]
sequence_ [check tryowner perms | tryowner <- [minBound ..], perms <- [0 .. (length permses - 1)]]

specSsoSettings :: SpecWith TestEnv
Expand Down