From c9b99ed2d2d2099383bc788bce5d1ff4aeea184c Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Fri, 10 Feb 2023 16:17:58 +0100 Subject: [PATCH 01/33] Introduce VersionNumber newtype. See `/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs` for explanation. --- .../5-internal/play-with-version-types | 1 + libs/wire-api/src/Wire/API/Routes/Version.hs | 75 ++++++++++++------- .../src/Wire/API/Routes/Version/Wai.hs | 35 ++++++--- libs/wire-api/src/Wire/API/VersionInfo.hs | 8 -- .../unit/Test/Wire/API/Roundtrip/Aeson.hs | 5 +- .../Test/Wire/API/Roundtrip/HttpApiData.hs | 5 +- .../test/unit/Test/Wire/API/Routes/Version.hs | 47 +++++++++--- services/brig/src/Brig/API/Public/Swagger.hs | 2 +- .../src/Brig/Effects/GalleyProvider/RPC.hs | 6 +- services/brig/src/Brig/Version.hs | 4 +- services/brig/test/integration/API/Version.hs | 14 ++-- services/brig/test/integration/Main.hs | 2 +- .../cargohold/test/integration/TestSetup.hs | 2 +- services/galley/test/integration/API/Util.hs | 2 +- tools/stern/src/Stern/Intra.hs | 7 +- 15 files changed, 134 insertions(+), 81 deletions(-) create mode 100644 changelog.d/5-internal/play-with-version-types diff --git a/changelog.d/5-internal/play-with-version-types b/changelog.d/5-internal/play-with-version-types new file mode 100644 index 00000000000..971e94f2da2 --- /dev/null +++ b/changelog.d/5-internal/play-with-version-types @@ -0,0 +1 @@ +Introduce VersionNumber newtype (see `/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs` for explanation) \ No newline at end of file diff --git a/libs/wire-api/src/Wire/API/Routes/Version.hs b/libs/wire-api/src/Wire/API/Routes/Version.hs index 519f7ee0867..961861f08a6 100644 --- a/libs/wire-api/src/Wire/API/Routes/Version.hs +++ b/libs/wire-api/src/Wire/API/Routes/Version.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE StandaloneKindSignatures #-} {-# LANGUAGE TemplateHaskell #-} -- This file is part of the Wire Server implementation. @@ -28,11 +29,9 @@ module Wire.API.Routes.Version -- * Version Version (..), + VersionNumber (..), supportedVersions, developmentVersions, - readVersionNumber, - mkVersion, - toPathComponent, -- * Servant combinators Until, @@ -40,6 +39,7 @@ module Wire.API.Routes.Version ) where +import Control.Error (note) import Control.Lens ((?~)) import Data.Aeson (FromJSON, ToJSON (..)) import qualified Data.Aeson as Aeson @@ -57,44 +57,63 @@ import Servant import Servant.Swagger import Wire.API.Routes.Named import Wire.API.VersionInfo +import Wire.Arbitrary (Arbitrary, GenericUniform (GenericUniform)) -- | Version of the public API. data Version = V0 | V1 | V2 | V3 - deriving stock (Eq, Ord, Bounded, Enum, Show) + deriving stock (Eq, Ord, Bounded, Enum, Show, Generic) deriving (FromJSON, ToJSON) via (Schema Version) + deriving (Arbitrary) via (GenericUniform Version) + +versionString :: IsString a => Version -> a +versionString V0 = "v0" +versionString V1 = "v1" +versionString V2 = "v2" +versionString V3 = "v3" + +versionInt :: Integral i => Version -> i +versionInt V0 = 0 +versionInt V1 = 1 +versionInt V2 = 2 +versionInt V3 = 3 instance ToSchema Version where - schema = - enum @Integer "Version" . mconcat $ - [ element 0 V0, - element 1 V1, - element 2 V2, - element 3 V3 - ] - -mkVersion :: Integer -> Maybe Version -mkVersion n = case Aeson.fromJSON (Aeson.Number (fromIntegral n)) of - Aeson.Error _ -> Nothing - Aeson.Success v -> pure v + schema = enum @Text "Version" . mconcat $ (\v -> element (versionString v) v) <$> [minBound ..] instance FromHttpApiData Version where + parseQueryParam v = note ("Unknown version: " <> v) $ + getAlt $ + flip foldMap [minBound ..] $ \s -> + guard (versionString s == v) $> s + +instance ToHttpApiData Version where + toHeader = versionString + toUrlPiece = versionString + +instance ToByteString Version where + builder = versionString + +newtype VersionNumber = VersionNumber {fromVersionNumber :: Version} + deriving stock (Eq, Ord, Show, Generic) + deriving newtype (Bounded, Enum) + deriving (FromJSON, ToJSON) via (Schema VersionNumber) + deriving (Arbitrary) via (GenericUniform Version) + +instance ToSchema VersionNumber where + schema = + enum @Integer "Version" . mconcat $ (\v -> element (versionInt v) (VersionNumber v)) <$> [minBound ..] + +instance FromHttpApiData VersionNumber where parseHeader = first Text.pack . Aeson.eitherDecode . LBS.fromStrict parseUrlPiece = parseHeader . Text.encodeUtf8 -instance ToHttpApiData Version where +instance ToHttpApiData VersionNumber where toHeader = LBS.toStrict . Aeson.encode toUrlPiece = Text.decodeUtf8 . toHeader -instance ToByteString Version where +instance ToByteString VersionNumber where builder = toEncodedUrlPiece --- | `Version` as it appears in an URL path --- --- >>> toPathComponent V1 --- "v1" -toPathComponent :: Version -> ByteString -toPathComponent v = "v" <> toHeader v - supportedVersions :: [Version] supportedVersions = [minBound .. maxBound] @@ -108,8 +127,8 @@ developmentVersions = [V3] -- backend, in order to decide how to form request paths, and how to deal with -- federated backends and qualified user IDs. data VersionInfo = VersionInfo - { vinfoSupported :: [Version], - vinfoDevelopment :: [Version], + { vinfoSupported :: [VersionNumber], + vinfoDevelopment :: [VersionNumber], vinfoFederation :: Bool, vinfoDomain :: Domain } @@ -127,7 +146,7 @@ instance ToSchema VersionInfo where example :: VersionInfo example = VersionInfo - { vinfoSupported = supportedVersions, + { vinfoSupported = VersionNumber <$> supportedVersions, vinfoDevelopment = [maxBound], vinfoFederation = False, vinfoDomain = Domain "example.com" diff --git a/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs b/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs index 545acdeae4d..3429fbced24 100644 --- a/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs +++ b/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs @@ -17,34 +17,45 @@ module Wire.API.Routes.Version.Wai where +import Control.Monad.Except (throwError) import Data.ByteString.Conversion -import qualified Data.Text.Lazy as LText +import Data.EitherR (fmapL) +import Data.String.Conversions (cs) +import qualified Data.Text as T import Imports import qualified Network.HTTP.Types as HTTP import Network.Wai import Network.Wai.Middleware.Rewrite import Network.Wai.Utilities.Error import Network.Wai.Utilities.Response +import Web.HttpApiData (parseUrlPiece, toUrlPiece) import Wire.API.Routes.Version -- | Strip off version prefix. Return 404 if the version is not supported. versionMiddleware :: Set Version -> Middleware versionMiddleware disabledAPIVersions app req k = case parseVersion (removeVersionHeader req) of - Nothing -> app req k - Just (req', n) -> case mkVersion n of - Just v | v `notElem` disabledAPIVersions -> app (addVersionHeader v req') k - _ -> - k $ - errorRs' $ - mkError HTTP.status404 "unsupported-version" $ - "Version " <> LText.pack (show n) <> " is not supported" + Right (req', v) -> + if v `elem` disabledAPIVersions + then err (toUrlPiece v) + else app (addVersionHeader v req') k + Left (BadVersion v) -> err v + Left NoVersion -> app req k + where + err :: Text -> IO ResponseReceived + err v = + k . errorRs' . mkError HTTP.status404 "unsupported-version" $ + "Version " <> cs v <> " is not supported" -parseVersion :: Request -> Maybe (Request, Integer) +data ParseVersionError = NoVersion | BadVersion Text + +parseVersion :: Request -> Either ParseVersionError (Request, Version) parseVersion req = do (version, pinfo) <- case pathInfo req of - [] -> Nothing + [] -> throwError NoVersion (x : xs) -> pure (x, xs) - n <- readVersionNumber version + when ("v" `T.isPrefixOf` version) $ + throwError (BadVersion version) + n <- fmapL (const NoVersion) $ parseUrlPiece version pure (rewriteRequestPure (\(_, q) _ -> (pinfo, q)) req, n) removeVersionHeader :: Request -> Request diff --git a/libs/wire-api/src/Wire/API/VersionInfo.hs b/libs/wire-api/src/Wire/API/VersionInfo.hs index 0d9707b5e01..e504dacfbcc 100644 --- a/libs/wire-api/src/Wire/API/VersionInfo.hs +++ b/libs/wire-api/src/Wire/API/VersionInfo.hs @@ -20,7 +20,6 @@ module Wire.API.VersionInfo vinfoObjectSchema, -- * Version utilities - readVersionNumber, versionHeader, VersionHeader, @@ -51,13 +50,6 @@ import Wire.API.Routes.ClientAlgebra vinfoObjectSchema :: ValueSchema NamedSwaggerDoc v -> ObjectSchema SwaggerDoc [v] vinfoObjectSchema sch = field "supported" (array sch) -readVersionNumber :: Text -> Maybe Integer -readVersionNumber v = do - ('v', rest) <- Text.uncons v - case Text.decimal rest of - Right (n, "") -> pure n - _ -> Nothing - type VersionHeader = "X-Wire-API-Version" versionHeader :: CI.CI ByteString diff --git a/libs/wire-api/test/unit/Test/Wire/API/Roundtrip/Aeson.hs b/libs/wire-api/test/unit/Test/Wire/API/Roundtrip/Aeson.hs index 9f0bd912dd7..967e43b479b 100644 --- a/libs/wire-api/test/unit/Test/Wire/API/Roundtrip/Aeson.hs +++ b/libs/wire-api/test/unit/Test/Wire/API/Roundtrip/Aeson.hs @@ -46,6 +46,7 @@ import qualified Wire.API.Provider.External as Provider.External import qualified Wire.API.Provider.Service as Provider.Service import qualified Wire.API.Provider.Service.Tag as Provider.Service.Tag import qualified Wire.API.Push.Token as Push.Token +import qualified Wire.API.Routes.Version as Routes.Version import qualified Wire.API.Team as Team import qualified Wire.API.Team.Conversation as Team.Conversation import qualified Wire.API.Team.Feature as Team.Feature @@ -310,7 +311,9 @@ tests = testRoundTrip @User.Search.PagingState, testRoundTrip @User.Search.TeamContact, testRoundTrip @(Wrapped.Wrapped "some_int" Int), - testRoundTrip @Conversation.Action.SomeConversationAction + testRoundTrip @Conversation.Action.SomeConversationAction, + testRoundTrip @Routes.Version.Version, + testRoundTrip @Routes.Version.VersionNumber ] testRoundTrip :: diff --git a/libs/wire-api/test/unit/Test/Wire/API/Roundtrip/HttpApiData.hs b/libs/wire-api/test/unit/Test/Wire/API/Roundtrip/HttpApiData.hs index 5ebf76a08e7..00ef20df73f 100644 --- a/libs/wire-api/test/unit/Test/Wire/API/Roundtrip/HttpApiData.hs +++ b/libs/wire-api/test/unit/Test/Wire/API/Roundtrip/HttpApiData.hs @@ -22,6 +22,7 @@ import Servant.API import qualified Test.Tasty as T import Test.Tasty.QuickCheck (Arbitrary, counterexample, testProperty, (===)) import Type.Reflection (typeRep) +import qualified Wire.API.Routes.Version import qualified Wire.API.User import qualified Wire.API.User.Search import qualified Wire.Arbitrary as Arbitrary () @@ -30,7 +31,9 @@ tests :: T.TestTree tests = T.localOption (T.Timeout (60 * 1000000) "60s") . T.testGroup "HttpApiData roundtrip tests" $ [ testRoundTrip @Wire.API.User.InvitationCode, - testRoundTrip @Wire.API.User.Search.PagingState + testRoundTrip @Wire.API.User.Search.PagingState, + testRoundTrip @Wire.API.Routes.Version.Version, + testRoundTrip @Wire.API.Routes.Version.VersionNumber ] testRoundTrip :: diff --git a/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs b/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs index 976166d0dcb..831ae6139c2 100644 --- a/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs +++ b/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs @@ -1,21 +1,44 @@ module Test.Wire.API.Routes.Version where +import Data.Aeson as Aeson +import Data.Binary.Builder +import Data.ByteString.Conversion +import Data.String.Conversions (cs) import Imports -import qualified Test.Tasty as T +import Servant.API +import Test.Tasty import Test.Tasty.HUnit import Wire.API.Routes.Version -tests :: T.TestTree +tests :: TestTree tests = - T.testGroup "Version" $ - [ T.testGroup - "toPathComponent" - [testCase "serialise different versions" testToPathComponent] + testGroup + "Version always has the shape V; serializations of Version and VersionNumber are `v`, ``, resp. is non-negative." + [ testCase "Version, show, 'v' prefix" $ do + nub (toLower . head . show <$> allVersions) @=? ['v'], + testCase "Version, show, int suffix" $ do + let expected = show $ (read @Int) . tail . show <$> allVersions + assertBool expected (isJust (Aeson.decode @[Int] (cs expected))), + testGroup "Version: all serializations are the same as `show`, up to string type" $ do + [ testCase "toByteString'" $ fmap toLower . show <$> allVersions @=? cs . toByteString' <$> allVersions, + testCase "encode" $ fmap toLower (show (show <$> allVersions)) @=? cs (encode allVersions), -- (`encode @Version` has extra double-quotes) + testCase "toUrlPiece" $ fmap toLower . show <$> allVersions @=? cs . toUrlPiece <$> allVersions, + testCase "toEncodedUrlPiece" $ fmap toLower . show <$> allVersions @=? cs . toLazyByteString . toEncodedUrlPiece <$> allVersions, + testCase "toHeader" $ fmap toLower . show <$> allVersions @=? cs . toHeader <$> allVersions, + testCase "toQueryParam" $ fmap toLower . show <$> allVersions @=? cs . toQueryParam <$> allVersions + ], + testGroup "VersionNumber: all serializations are the same as `tail . show . fromVersionNumber`, up to string type" $ + [ testCase "toByteString'" $ tail . show . fromVersionNumber <$> allVersionNumbers @=? cs . toByteString' <$> allVersionNumbers, + testCase "encode" $ tail . show . fromVersionNumber <$> allVersionNumbers @=? cs . encode <$> allVersionNumbers, + testCase "toUrlPiece" $ tail . show . fromVersionNumber <$> allVersionNumbers @=? cs . toUrlPiece <$> allVersionNumbers, + testCase "toEncodedUrlPiece" $ tail . show . fromVersionNumber <$> allVersionNumbers @=? cs . toLazyByteString . toEncodedUrlPiece <$> allVersionNumbers, + testCase "toHeader" $ tail . show . fromVersionNumber <$> allVersionNumbers @=? cs . toHeader <$> allVersionNumbers, + testCase "toQueryParam" $ tail . show . fromVersionNumber <$> allVersionNumbers @=? cs . toQueryParam <$> allVersionNumbers + ] ] -testToPathComponent :: Assertion -testToPathComponent = do - "v0" @=? toPathComponent V0 - "v1" @=? toPathComponent V1 - "v2" @=? toPathComponent V2 - "v3" @=? toPathComponent V3 +allVersions :: [Version] +allVersions = [minBound ..] + +allVersionNumbers :: [VersionNumber] +allVersionNumbers = [minBound ..] diff --git a/services/brig/src/Brig/API/Public/Swagger.hs b/services/brig/src/Brig/API/Public/Swagger.hs index 49c49e009cd..b5928d4832f 100644 --- a/services/brig/src/Brig/API/Public/Swagger.hs +++ b/services/brig/src/Brig/API/Public/Swagger.hs @@ -37,7 +37,7 @@ pregenSwagger :: Version -> Q Exp pregenSwagger v = embedLazyByteString =<< makeRelativeToProject - ("docs/swagger-v" <> T.unpack (toUrlPiece v) <> ".json") + ("docs/swagger-v" <> T.unpack (toUrlPiece (VersionNumber v)) <> ".json") swaggerPregenUIServer :: LByteString -> Server VersionedSwaggerDocsAPIBase swaggerPregenUIServer = diff --git a/services/brig/src/Brig/Effects/GalleyProvider/RPC.hs b/services/brig/src/Brig/Effects/GalleyProvider/RPC.hs index a3cb6c2e37a..71d73276cf4 100644 --- a/services/brig/src/Brig/Effects/GalleyProvider/RPC.hs +++ b/services/brig/src/Brig/Effects/GalleyProvider/RPC.hs @@ -87,7 +87,7 @@ createSelfConv u = do void $ ServiceRPC.request @'Galley POST req where req = - paths ["v" <> toHeader (maxBound :: Version), "conversations", "self"] + paths [toHeader (maxBound :: Version), "conversations", "self"] . zUser u . expect2xx @@ -115,7 +115,7 @@ getConv usr lcnv = do where req = paths - [ "v" <> toHeader (maxBound :: Version), + [ toHeader (maxBound :: Version), "conversations", toByteString' (tDomain lcnv), toByteString' (tUnqualified lcnv) @@ -147,7 +147,7 @@ getTeamConv usr tid cnv = do where req = paths - [ "v" <> toHeader (maxBound :: Version), + [ toHeader (maxBound :: Version), "teams", toByteString' tid, "conversations", diff --git a/services/brig/src/Brig/Version.hs b/services/brig/src/Brig/Version.hs index acf7603d76b..f3d6a5ca89e 100644 --- a/services/brig/src/Brig/Version.hs +++ b/services/brig/src/Brig/Version.hs @@ -40,8 +40,8 @@ versionAPI = Named $ do | otherwise = Set.difference allVersions devVersions pure $ VersionInfo - { vinfoSupported = toList supported, - vinfoDevelopment = toList devVersions, + { vinfoSupported = VersionNumber <$> toList supported, + vinfoDevelopment = VersionNumber <$> toList devVersions, vinfoFederation = isJust fed, vinfoDomain = dom } diff --git a/services/brig/test/integration/API/Version.hs b/services/brig/test/integration/API/Version.hs index bd4945e879f..5bf6cfbb1e3 100644 --- a/services/brig/test/integration/API/Version.hs +++ b/services/brig/test/integration/API/Version.hs @@ -53,7 +53,7 @@ testVersion brig = do =<< get (brig . path "/api-version") vinfoSupported vinfo) @?= supportedVersions \\ developmentVersions testVersionV1 :: Brig -> Http () testVersionV1 brig = do @@ -62,7 +62,7 @@ testVersionV1 brig = do =<< get (apiVersion "v1" . brig . path "api-version") vinfoSupported vinfo) @?= supportedVersions \\ developmentVersions testDevVersion :: Opts -> Brig -> Http () testDevVersion opts brig = withSettingsOverrides @@ -73,7 +73,7 @@ testDevVersion opts brig = withSettingsOverrides =<< get (brig . path "/api-version") vinfoSupported vinfo) @?= supportedVersions testUnsupportedVersion :: Brig -> Http () testUnsupportedVersion brig = do @@ -127,7 +127,7 @@ testDisabledVersionIsUnsupported opts brig = do testVersionDisabledSupportedVersion :: Opts -> Brig -> Http () testVersionDisabledSupportedVersion opts brig = do vinfo <- getVersionInfo brig - liftIO $ filter (== V2) (vinfoSupported vinfo) @?= [V2] + liftIO $ filter (== VersionNumber V2) (vinfoSupported vinfo) @?= [VersionNumber V2] disabledVersionIsNotAdvertised opts brig V2 testVersionDisabledDevelopmentVersion :: Opts -> Brig -> Http () @@ -135,7 +135,7 @@ testVersionDisabledDevelopmentVersion opts brig = do vinfo <- getVersionInfo brig for_ (listToMaybe (vinfoDevelopment vinfo)) $ \devVersion -> do liftIO $ filter (== devVersion) (vinfoDevelopment vinfo) @?= [devVersion] - disabledVersionIsNotAdvertised opts brig devVersion + disabledVersionIsNotAdvertised opts brig (fromVersionNumber devVersion) disabledVersionIsNotAdvertised :: Opts -> Brig -> Version -> Http () disabledVersionIsNotAdvertised opts brig version = @@ -147,8 +147,8 @@ disabledVersionIsNotAdvertised opts brig version = ) $ do vinfo <- getVersionInfo brig - liftIO $ filter (== version) (vinfoSupported vinfo) @?= [] - liftIO $ filter (== version) (vinfoDevelopment vinfo) @?= [] + liftIO $ filter (== VersionNumber version) (vinfoSupported vinfo) @?= [] + liftIO $ filter (== VersionNumber version) (vinfoDevelopment vinfo) @?= [] getVersionInfo :: (MonadIO m, MonadCatch m, MonadFail m, MonadHttp m, HasCallStack) => diff --git a/services/brig/test/integration/Main.hs b/services/brig/test/integration/Main.hs index 90b64986f4a..ad1d6a02d69 100644 --- a/services/brig/test/integration/Main.hs +++ b/services/brig/test/integration/Main.hs @@ -192,7 +192,7 @@ runTests iConf brigOpts otherArgs = do mkVersionedRequest endpoint = addPrefix . mkRequest endpoint addPrefix :: Request -> Request - addPrefix r = r {HTTP.path = "v" <> toHeader latestVersion <> "/" <> removeSlash (HTTP.path r)} + addPrefix r = r {HTTP.path = toHeader latestVersion <> "/" <> removeSlash (HTTP.path r)} where removeSlash s = case B8.uncons s of Just ('/', s') -> s' diff --git a/services/cargohold/test/integration/TestSetup.hs b/services/cargohold/test/integration/TestSetup.hs index 7b494caa43a..759c760a698 100644 --- a/services/cargohold/test/integration/TestSetup.hs +++ b/services/cargohold/test/integration/TestSetup.hs @@ -115,7 +115,7 @@ unversioned r = viewCargohold :: TestM Cargohold viewCargohold = fmap - (apiVersion ("v" <> toHeader latestVersion) .) + (apiVersion (toHeader latestVersion) .) viewUnversionedCargohold where latestVersion :: Version diff --git a/services/galley/test/integration/API/Util.hs b/services/galley/test/integration/API/Util.hs index 329097b95c6..cd0ea3f5932 100644 --- a/services/galley/test/integration/API/Util.hs +++ b/services/galley/test/integration/API/Util.hs @@ -148,7 +148,7 @@ addPrefix :: Request -> Request addPrefix = addPrefixAtVersion maxBound addPrefixAtVersion :: Version -> Request -> Request -addPrefixAtVersion v r = r {HTTP.path = "v" <> toHeader v <> "/" <> removeSlash (HTTP.path r)} +addPrefixAtVersion v r = r {HTTP.path = toHeader v <> "/" <> removeSlash (HTTP.path r)} where removeSlash s = case B8.uncons s of Just ('/', s') -> s' diff --git a/tools/stern/src/Stern/Intra.hs b/tools/stern/src/Stern/Intra.hs index d30f17d9698..f707c8aecaa 100644 --- a/tools/stern/src/Stern/Intra.hs +++ b/tools/stern/src/Stern/Intra.hs @@ -92,6 +92,7 @@ import Imports import Network.HTTP.Types.Method import Network.HTTP.Types.Status hiding (statusCode) import Network.Wai.Utilities (Error (..), mkError) +import Servant.API (toUrlPiece) import Stern.App import Stern.Types import System.Logger.Class hiding (Error, name, (.=)) @@ -129,14 +130,14 @@ assertBackendApiVersion = recoverAll (constantDelay 1000000 <> limitRetries 5) $ vinfo :: VersionInfo <- responseJsonError =<< rpc' "brig" b (method GET . Bilge.path "/api-version" . contentJson . expect2xx) - unless (maximum (vinfoSupported vinfo) == backendApiVersion) $ do + unless (fromVersionNumber (maximum (vinfoSupported vinfo)) == backendApiVersion) $ do throwIO . ErrorCall $ "newest supported backend api version must be " <> show backendApiVersion path :: ByteString -> Request -> Request -path = Bilge.path . ((toPathComponent backendApiVersion <> "/") <>) +path = Bilge.path . ((cs (toUrlPiece backendApiVersion) <> "/") <>) paths :: [ByteString] -> Request -> Request -paths = Bilge.paths . (toPathComponent backendApiVersion :) +paths = Bilge.paths . (cs (toUrlPiece backendApiVersion) :) ------------------------------------------------------------------------------- From 31c98892f5a83a541fe195fc1957e76222c4eae6 Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Sat, 11 Feb 2023 14:48:22 +0100 Subject: [PATCH 02/33] Tweak hlint. --- .hlint.yaml | 24 ++++++++++++++++++++++++ 1 file changed, 24 insertions(+) diff --git a/.hlint.yaml b/.hlint.yaml index 3aac4d9b130..ffa31ce50a6 100644 --- a/.hlint.yaml +++ b/.hlint.yaml @@ -25,3 +25,27 @@ Federator.Response, # this is just a naming conincidence Cannon.Run # we do something similar, but not identical here by hand ] } + +# I got these false positives from hlint. Following the chances leads +# to (obviously valid) compiler errors: +# +# ``` +# libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs:23:38-111: Warning: Functor law +# Found: +# fmap toLower . show <$> allVersions @=? cs . toByteString' +# <$> allVersions +# Perhaps: +# ((fmap toLower . show) . allVersions @=? cs . toByteString' +# <$> allVersions) +# +# libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs:31:38-135: Warning: Functor law +# Found: +# tail . show . fromVersionNumber +# <$> allVersionNumbers @=? cs . toByteString' +# <$> allVersionNumbers +# Perhaps: +# ((tail . show . fromVersionNumber) +# . allVersionNumbers @=? cs . toByteString' +# <$> allVersionNumbers) +# ``` +- ignore: { name: Functor law } From 86c4b1f10f815356759147433f6d90d95fb5f1f1 Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Sat, 11 Feb 2023 21:55:05 +0100 Subject: [PATCH 03/33] Fixup --- libs/wire-api/src/Wire/API/VersionInfo.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/libs/wire-api/src/Wire/API/VersionInfo.hs b/libs/wire-api/src/Wire/API/VersionInfo.hs index e504dacfbcc..46258b65e7a 100644 --- a/libs/wire-api/src/Wire/API/VersionInfo.hs +++ b/libs/wire-api/src/Wire/API/VersionInfo.hs @@ -35,8 +35,6 @@ import qualified Data.CaseInsensitive as CI import Data.Metrics.Servant import Data.Schema import Data.Singletons -import qualified Data.Text as Text -import qualified Data.Text.Read as Text import GHC.TypeLits import Imports import qualified Network.Wai as Wai From 53758c320a2b70096be100974c8108955fd67265 Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Sun, 12 Feb 2023 07:25:51 +0100 Subject: [PATCH 04/33] hi ci From a8d8ed7f1b48230e9efb7fb94fb29ee1d09e87d0 Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Mon, 13 Feb 2023 09:26:22 +0100 Subject: [PATCH 05/33] Tweak changelog entry and haddocs. --- changelog.d/5-internal/play-with-version-types | 2 +- libs/wire-api/src/Wire/API/Routes/Version.hs | 7 ++++++- 2 files changed, 7 insertions(+), 2 deletions(-) diff --git a/changelog.d/5-internal/play-with-version-types b/changelog.d/5-internal/play-with-version-types index 971e94f2da2..df6311ba8b5 100644 --- a/changelog.d/5-internal/play-with-version-types +++ b/changelog.d/5-internal/play-with-version-types @@ -1 +1 @@ -Introduce VersionNumber newtype (see `/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs` for explanation) \ No newline at end of file +Introduce VersionNumber newtype (see `/libs/wire-api/src/Wire/API/Routes/Version.hs` for explanation) \ No newline at end of file diff --git a/libs/wire-api/src/Wire/API/Routes/Version.hs b/libs/wire-api/src/Wire/API/Routes/Version.hs index 961861f08a6..44da2d1cc0d 100644 --- a/libs/wire-api/src/Wire/API/Routes/Version.hs +++ b/libs/wire-api/src/Wire/API/Routes/Version.hs @@ -59,7 +59,9 @@ import Wire.API.Routes.Named import Wire.API.VersionInfo import Wire.Arbitrary (Arbitrary, GenericUniform (GenericUniform)) --- | Version of the public API. +-- | Version of the public API. Serializes to `"v"`. See 'VersionNumber' below for one +-- that serializes to ``. See `/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs` +-- for serialization rules. data Version = V0 | V1 | V2 | V3 deriving stock (Eq, Ord, Bounded, Enum, Show, Generic) deriving (FromJSON, ToJSON) via (Schema Version) @@ -93,6 +95,9 @@ instance ToHttpApiData Version where instance ToByteString Version where builder = versionString +-- | Wrapper around 'Version' that serializes to integers ``, as needed in +-- eg. `VersionInfo`. See `/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs` for +-- serialization rules. newtype VersionNumber = VersionNumber {fromVersionNumber :: Version} deriving stock (Eq, Ord, Show, Generic) deriving newtype (Bounded, Enum) From d2e52a1bf0f94c5d5dbbc80d1443100a54e7c1af Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Mon, 13 Feb 2023 15:02:11 +0100 Subject: [PATCH 06/33] More haddocks. --- libs/wire-api/src/Wire/API/Routes/Version.hs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/libs/wire-api/src/Wire/API/Routes/Version.hs b/libs/wire-api/src/Wire/API/Routes/Version.hs index 44da2d1cc0d..be54b446fbf 100644 --- a/libs/wire-api/src/Wire/API/Routes/Version.hs +++ b/libs/wire-api/src/Wire/API/Routes/Version.hs @@ -67,12 +67,22 @@ data Version = V0 | V1 | V2 | V3 deriving (FromJSON, ToJSON) via (Schema Version) deriving (Arbitrary) via (GenericUniform Version) +-- | Manual enumeration of version strings. +-- +-- If you want to implement this using `{to,from}Enum`, continue reading the haddocs for +-- 'versionInt' below. :-) versionString :: IsString a => Version -> a versionString V0 = "v0" versionString V1 = "v1" versionString V2 = "v2" versionString V3 = "v3" +-- | Manual enumeration of version integrals. +-- +-- We don't do anything fancy with `{to,from}Enum` +-- because we'll eventually break the invariant that there is a `V` for every `` once we +-- start to deprecate old versions (we may even find a reason to discontinue `V13` but keep +-- supporting `V12`). versionInt :: Integral i => Version -> i versionInt V0 = 0 versionInt V1 = 1 From ccd465019127f717a0dc65536ff168e2c94df814 Mon Sep 17 00:00:00 2001 From: fisx Date: Mon, 13 Feb 2023 15:07:45 +0100 Subject: [PATCH 07/33] Update libs/wire-api/src/Wire/API/Routes/Version.hs Co-authored-by: Sven Tennie --- libs/wire-api/src/Wire/API/Routes/Version.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libs/wire-api/src/Wire/API/Routes/Version.hs b/libs/wire-api/src/Wire/API/Routes/Version.hs index be54b446fbf..739c3dc1ea5 100644 --- a/libs/wire-api/src/Wire/API/Routes/Version.hs +++ b/libs/wire-api/src/Wire/API/Routes/Version.hs @@ -116,7 +116,7 @@ newtype VersionNumber = VersionNumber {fromVersionNumber :: Version} instance ToSchema VersionNumber where schema = - enum @Integer "Version" . mconcat $ (\v -> element (versionInt v) (VersionNumber v)) <$> [minBound ..] + enum @Integer "VersionNumber" . mconcat $ (\v -> element (versionInt v) (VersionNumber v)) <$> [minBound ..] instance FromHttpApiData VersionNumber where parseHeader = first Text.pack . Aeson.eitherDecode . LBS.fromStrict From 5d05349ff8af2fe1088e1e775015144d8d402796 Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Mon, 13 Feb 2023 16:27:04 +0100 Subject: [PATCH 08/33] Revert "Tweak hlint." This reverts commit 31c98892f5a83a541fe195fc1957e76222c4eae6. --- .hlint.yaml | 24 ------------------------ 1 file changed, 24 deletions(-) diff --git a/.hlint.yaml b/.hlint.yaml index ffa31ce50a6..3aac4d9b130 100644 --- a/.hlint.yaml +++ b/.hlint.yaml @@ -25,27 +25,3 @@ Federator.Response, # this is just a naming conincidence Cannon.Run # we do something similar, but not identical here by hand ] } - -# I got these false positives from hlint. Following the chances leads -# to (obviously valid) compiler errors: -# -# ``` -# libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs:23:38-111: Warning: Functor law -# Found: -# fmap toLower . show <$> allVersions @=? cs . toByteString' -# <$> allVersions -# Perhaps: -# ((fmap toLower . show) . allVersions @=? cs . toByteString' -# <$> allVersions) -# -# libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs:31:38-135: Warning: Functor law -# Found: -# tail . show . fromVersionNumber -# <$> allVersionNumbers @=? cs . toByteString' -# <$> allVersionNumbers -# Perhaps: -# ((tail . show . fromVersionNumber) -# . allVersionNumbers @=? cs . toByteString' -# <$> allVersionNumbers) -# ``` -- ignore: { name: Functor law } From e599619812ea5b60c51067ebaf259be7b9ca12fa Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Mon, 13 Feb 2023 16:28:16 +0100 Subject: [PATCH 09/33] Tweak hlint *locally*. --- libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs b/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs index 831ae6139c2..6195c711f5c 100644 --- a/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs +++ b/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs @@ -10,6 +10,7 @@ import Test.Tasty import Test.Tasty.HUnit import Wire.API.Routes.Version +{-# ANN tests ("HLint: ignore Functor law" :: String) #-} tests :: TestTree tests = testGroup From ecf524913db7752761a1ff1683b6553f2cb53455 Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Mon, 13 Feb 2023 16:33:56 +0100 Subject: [PATCH 10/33] D'OH! --- libs/wire-api/src/Wire/API/Routes/Version/Wai.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs b/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs index 3429fbced24..45358d8a861 100644 --- a/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs +++ b/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs @@ -53,7 +53,7 @@ parseVersion req = do (version, pinfo) <- case pathInfo req of [] -> throwError NoVersion (x : xs) -> pure (x, xs) - when ("v" `T.isPrefixOf` version) $ + unless ("v" `T.isPrefixOf` version) $ throwError (BadVersion version) n <- fmapL (const NoVersion) $ parseUrlPiece version pure (rewriteRequestPure (\(_, q) _ -> (pinfo, q)) req, n) From 4aa8e4812aa127cb2f13d9ae0f7881482b71cc0e Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Mon, 13 Feb 2023 18:05:06 +0100 Subject: [PATCH 11/33] hi ci From 7a2bdde940585d1f85ba2beb81c575e8bb064dd6 Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Mon, 13 Feb 2023 18:42:10 +0100 Subject: [PATCH 12/33] hi ci From 7e60211e231270a71047c3f7f62cff12575e914e Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Fri, 17 Feb 2023 11:48:05 +0100 Subject: [PATCH 13/33] Generic rendering of Version strings via `versionInt`. --- libs/wire-api/src/Wire/API/Routes/Version.hs | 57 ++++++++++---------- 1 file changed, 30 insertions(+), 27 deletions(-) diff --git a/libs/wire-api/src/Wire/API/Routes/Version.hs b/libs/wire-api/src/Wire/API/Routes/Version.hs index 739c3dc1ea5..3d4437e688a 100644 --- a/libs/wire-api/src/Wire/API/Routes/Version.hs +++ b/libs/wire-api/src/Wire/API/Routes/Version.hs @@ -44,7 +44,8 @@ import Control.Lens ((?~)) import Data.Aeson (FromJSON, ToJSON (..)) import qualified Data.Aeson as Aeson import Data.Bifunctor -import Data.ByteString.Conversion (ToByteString (builder)) +import qualified Data.Binary.Builder as Builder +import Data.ByteString.Conversion (ToByteString (builder), toByteString') import qualified Data.ByteString.Lazy as LBS import Data.Domain import Data.Schema @@ -62,48 +63,56 @@ import Wire.Arbitrary (Arbitrary, GenericUniform (GenericUniform)) -- | Version of the public API. Serializes to `"v"`. See 'VersionNumber' below for one -- that serializes to ``. See `/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs` -- for serialization rules. +-- +-- If you add or remove versions from this type, make sure 'versionInt', 'supportedVersions', +-- and 'developmentVersions' stay in sync; everything else here should keep working without +-- change. data Version = V0 | V1 | V2 | V3 deriving stock (Eq, Ord, Bounded, Enum, Show, Generic) deriving (FromJSON, ToJSON) via (Schema Version) deriving (Arbitrary) via (GenericUniform Version) --- | Manual enumeration of version strings. --- --- If you want to implement this using `{to,from}Enum`, continue reading the haddocs for --- 'versionInt' below. :-) -versionString :: IsString a => Version -> a -versionString V0 = "v0" -versionString V1 = "v1" -versionString V2 = "v2" -versionString V3 = "v3" - --- | Manual enumeration of version integrals. +-- | Manual enumeration of version integrals (the `` in the constructor `V`). -- --- We don't do anything fancy with `{to,from}Enum` --- because we'll eventually break the invariant that there is a `V` for every `` once we --- start to deprecate old versions (we may even find a reason to discontinue `V13` but keep --- supporting `V12`). +-- This is not the same as 'fromEnum': we will remove unsupported versions in the future, +-- which will cause `` and `fromEnum V` to diverge. `Enum` should not be understood as +-- a bijection between meaningful integers and versions, but merely as a convenient way to say +-- `allVersions = [minBound..]`. versionInt :: Integral i => Version -> i versionInt V0 = 0 versionInt V1 = 1 versionInt V2 = 2 versionInt V3 = 3 +supportedVersions :: [Version] +supportedVersions = [minBound ..] + +developmentVersions :: [Version] +developmentVersions = [V3] + +---------------------------------------------------------------------- + +versionText :: Version -> Text +versionText = ("v" <>) . toUrlPiece . versionInt @Int + +versionByteString :: Version -> ByteString +versionByteString = ("v" <>) . toByteString' . versionInt @Int + instance ToSchema Version where - schema = enum @Text "Version" . mconcat $ (\v -> element (versionString v) v) <$> [minBound ..] + schema = enum @Text "Version" . mconcat $ (\v -> element (versionText v) v) <$> [minBound ..] instance FromHttpApiData Version where parseQueryParam v = note ("Unknown version: " <> v) $ getAlt $ flip foldMap [minBound ..] $ \s -> - guard (versionString s == v) $> s + guard (versionText s == v) $> s instance ToHttpApiData Version where - toHeader = versionString - toUrlPiece = versionString + toHeader = versionByteString + toUrlPiece = versionText instance ToByteString Version where - builder = versionString + builder = Builder.fromByteString . versionByteString -- | Wrapper around 'Version' that serializes to integers ``, as needed in -- eg. `VersionInfo`. See `/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs` for @@ -129,12 +138,6 @@ instance ToHttpApiData VersionNumber where instance ToByteString VersionNumber where builder = toEncodedUrlPiece -supportedVersions :: [Version] -supportedVersions = [minBound .. maxBound] - -developmentVersions :: [Version] -developmentVersions = [V3] - -- | Information related to the public API version. -- -- This record also contains whether federation is enabled and the federation From 8b6408591fca163250f0a17cc0b45ad6d4e32e22 Mon Sep 17 00:00:00 2001 From: Paolo Capriotti Date: Thu, 2 Mar 2023 16:57:31 +0100 Subject: [PATCH 14/33] Add pregenerated v3 swagger --- services/brig/docs/swagger-v3.json | 20848 +++++++++++++++++++++++++++ 1 file changed, 20848 insertions(+) create mode 100644 services/brig/docs/swagger-v3.json diff --git a/services/brig/docs/swagger-v3.json b/services/brig/docs/swagger-v3.json new file mode 100644 index 00000000000..c366175b56b --- /dev/null +++ b/services/brig/docs/swagger-v3.json @@ -0,0 +1,20848 @@ +{ + "definitions": { + "": { + "description": "Username to use for authenticating against the given TURN servers", + "type": "string" + }, + "ASCII": { + "example": "aGVsbG8", + "type": "string" + }, + "Access": { + "description": "Transport", + "enum": [ + "GCM", + "APNS", + "APNS_SANDBOX", + "APNS_VOIP", + "APNS_VOIP_SANDBOX" + ], + "type": "string" + }, + "AccessRole": { + "description": "Which users/services can join conversations. This replaces legacy access roles and allows a more fine grained configuration of access roles, and in particular a separation of guest and services access.\n\nThis field is optional. If it is not present, the default will be `[team_member, non_team_member, service]`. Please note that an empty list is not allowed when creating a new conversation.", + "enum": [ + "team_member", + "non_team_member", + "guest", + "service" + ], + "type": "string" + }, + "AccessRoleLegacy": { + "description": "Deprecated, please use access_role_v2", + "enum": [ + "private", + "team", + "activated", + "non_activated" + ], + "type": "string" + }, + "AccessToken": { + "properties": { + "access_token": { + "description": "The opaque access token string", + "type": "string" + }, + "expires_in": { + "description": "The number of seconds this token is valid", + "type": "integer" + }, + "token_type": { + "$ref": "#/definitions/TokenType" + }, + "user": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "user", + "access_token", + "token_type", + "expires_in" + ], + "type": "object" + }, + "AccessTokenType": { + "enum": [ + "DPoP" + ], + "type": "string" + }, + "Action": { + "enum": [ + "add_conversation_member", + "remove_conversation_member", + "modify_conversation_name", + "modify_conversation_message_timer", + "modify_conversation_receipt_mode", + "modify_conversation_access", + "modify_other_conversation_member", + "leave_conversation", + "delete_conversation" + ], + "type": "string" + }, + "Activate": { + "description": "Data for an activation request.", + "properties": { + "code": { + "$ref": "#/definitions/ASCII" + }, + "dryrun": { + "description": "At least one of key, email, or phone has to be present while key takes precedence over email, and email takes precedence over phone. Whether to perform a dryrun, i.e. to only check whether activation would succeed. Dry-runs never issue access cookies or tokens on success but failures still count towards the maximum failure count.", + "type": "boolean" + }, + "email": { + "$ref": "#/definitions/Email" + }, + "key": { + "$ref": "#/definitions/ASCII" + }, + "phone": { + "$ref": "#/definitions/PhoneNumber" + } + }, + "required": [ + "code", + "dryrun" + ], + "type": "object" + }, + "ActivationResponse": { + "description": "Response body of a successful activation request", + "properties": { + "email": { + "$ref": "#/definitions/Email" + }, + "first": { + "description": "Whether this is the first successful activation (i.e. account activation).", + "type": "boolean" + }, + "phone": { + "$ref": "#/definitions/PhoneNumber" + }, + "sso_id": { + "$ref": "#/definitions/UserSSOId" + } + }, + "type": "object" + }, + "AllFeatureConfigs": { + "properties": { + "appLock": { + "$ref": "#/definitions/AppLockConfig.WithStatus" + }, + "classifiedDomains": { + "$ref": "#/definitions/ClassifiedDomainsConfig.WithStatus" + }, + "conferenceCalling": { + "$ref": "#/definitions/ConferenceCallingConfig.WithStatus" + }, + "conversationGuestLinks": { + "$ref": "#/definitions/GuestLinksConfig.WithStatus" + }, + "digitalSignatures": { + "$ref": "#/definitions/DigitalSignaturesConfig.WithStatus" + }, + "exposeInvitationURLsToTeamAdmin": { + "$ref": "#/definitions/ExposeInvitationURLsToTeamAdminConfig.WithStatus" + }, + "fileSharing": { + "$ref": "#/definitions/FileSharingConfig.WithStatus" + }, + "legalhold": { + "$ref": "#/definitions/LegalholdConfig.WithStatus" + }, + "mls": { + "$ref": "#/definitions/MLSConfig.WithStatus" + }, + "mlsE2EId": { + "$ref": "#/definitions/MlsE2EIdConfig.WithStatus" + }, + "outlookCalIntegration": { + "$ref": "#/definitions/OutlookCalIntegrationConfig.WithStatus" + }, + "searchVisibility": { + "$ref": "#/definitions/SearchVisibilityAvailableConfig.WithStatus" + }, + "searchVisibilityInbound": { + "$ref": "#/definitions/SearchVisibilityInboundConfig.WithStatus" + }, + "selfDeletingMessages": { + "$ref": "#/definitions/SelfDeletingMessagesConfig.WithStatus" + }, + "sndFactorPasswordChallenge": { + "$ref": "#/definitions/SndFactorPasswordChallengeConfig.WithStatus" + }, + "sso": { + "$ref": "#/definitions/SSOConfig.WithStatus" + }, + "validateSAMLemails": { + "$ref": "#/definitions/ValidateSAMLEmailsConfig.WithStatus" + } + }, + "required": [ + "legalhold", + "sso", + "searchVisibility", + "searchVisibilityInbound", + "validateSAMLemails", + "digitalSignatures", + "appLock", + "fileSharing", + "classifiedDomains", + "conferenceCalling", + "selfDeletingMessages", + "conversationGuestLinks", + "sndFactorPasswordChallenge", + "mls", + "exposeInvitationURLsToTeamAdmin", + "outlookCalIntegration", + "mlsE2EId" + ], + "type": "object" + }, + "Alpha": { + "enum": [ + "AED", + "AFN", + "ALL", + "AMD", + "ANG", + "AOA", + "ARS", + "AUD", + "AWG", + "AZN", + "BAM", + "BBD", + "BDT", + "BGN", + "BHD", + "BIF", + "BMD", + "BND", + "BOB", + "BOV", + "BRL", + "BSD", + "BTN", + "BWP", + "BYN", + "BZD", + "CAD", + "CDF", + "CHE", + "CHF", + "CHW", + "CLF", + "CLP", + "CNY", + "COP", + "COU", + "CRC", + "CUC", + "CUP", + "CVE", + "CZK", + "DJF", + "DKK", + "DOP", + "DZD", + "EGP", + "ERN", + "ETB", + "EUR", + "FJD", + "FKP", + "GBP", + "GEL", + "GHS", + "GIP", + "GMD", + "GNF", + "GTQ", + "GYD", + "HKD", + "HNL", + "HRK", + "HTG", + "HUF", + "IDR", + "ILS", + "INR", + "IQD", + "IRR", + "ISK", + "JMD", + "JOD", + "JPY", + "KES", + "KGS", + "KHR", + "KMF", + "KPW", + "KRW", + "KWD", + "KYD", + "KZT", + "LAK", + "LBP", + "LKR", + "LRD", + "LSL", + "LYD", + "MAD", + "MDL", + "MGA", + "MKD", + "MMK", + "MNT", + "MOP", + "MRO", + "MUR", + "MVR", + "MWK", + "MXN", + "MXV", + "MYR", + "MZN", + "NAD", + "NGN", + "NIO", + "NOK", + "NPR", + "NZD", + "OMR", + "PAB", + "PEN", + "PGK", + "PHP", + "PKR", + "PLN", + "PYG", + "QAR", + "RON", + "RSD", + "RUB", + "RWF", + "SAR", + "SBD", + "SCR", + "SDG", + "SEK", + "SGD", + "SHP", + "SLL", + "SOS", + "SRD", + "SSP", + "STD", + "SVC", + "SYP", + "SZL", + "THB", + "TJS", + "TMT", + "TND", + "TOP", + "TRY", + "TTD", + "TWD", + "TZS", + "UAH", + "UGX", + "USD", + "USN", + "UYI", + "UYU", + "UZS", + "VEF", + "VND", + "VUV", + "WST", + "XAF", + "XAG", + "XAU", + "XBA", + "XBB", + "XBC", + "XBD", + "XCD", + "XDR", + "XOF", + "XPD", + "XPF", + "XPT", + "XSU", + "XTS", + "XUA", + "XXX", + "YER", + "ZAR", + "ZMW", + "ZWL" + ], + "type": "string" + }, + "AppLockConfig": { + "properties": { + "enforceAppLock": { + "type": "boolean" + }, + "inactivityTimeoutSecs": { + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + } + }, + "required": [ + "enforceAppLock", + "inactivityTimeoutSecs" + ], + "type": "object" + }, + "AppLockConfig.WithStatus": { + "properties": { + "config": { + "$ref": "#/definitions/AppLockConfig" + }, + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus", + "config" + ], + "type": "object" + }, + "AppLockConfig.WithStatusNoLock": { + "properties": { + "config": { + "$ref": "#/definitions/AppLockConfig" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "config" + ], + "type": "object" + }, + "ApproveLegalHoldForUserRequest": { + "properties": { + "password": { + "maxLength": 1024, + "minLength": 6, + "type": "string" + } + }, + "type": "object" + }, + "Asset": { + "properties": { + "domain": { + "$ref": "#/definitions/Domain" + }, + "expires": { + "$ref": "#/definitions/UTCTime" + }, + "key": { + "$ref": "#/definitions/AssetKey" + }, + "token": { + "$ref": "#/definitions/ASCII" + } + }, + "required": [ + "key", + "domain" + ], + "type": "object" + }, + "AssetKey": { + "example": "3-1-47de4580-ae51-4650-acbb-d10c028cb0ac", + "type": "string" + }, + "AssetSize": { + "enum": [ + "preview", + "complete" + ], + "type": "string" + }, + "AssetSource": {}, + "AssetType": { + "enum": [ + "image" + ], + "type": "string" + }, + "AuthnRequest": { + "properties": { + "iD": { + "$ref": "#/definitions/ID" + }, + "issueInstant": { + "$ref": "#/definitions/Time" + }, + "issuer": { + "type": "string" + }, + "nameIDPolicy": { + "$ref": "#/definitions/NameIdPolicy" + } + }, + "required": [ + "iD", + "issueInstant", + "issuer" + ], + "type": "object" + }, + "Base64ByteString": { + "example": "ZXhhbXBsZQo=", + "type": "string" + }, + "BindingNewTeamUser": { + "properties": { + "currency": { + "$ref": "#/definitions/Alpha" + }, + "icon": { + "$ref": "#/definitions/Icon" + }, + "icon_key": { + "description": "team icon asset key", + "maxLength": 256, + "minLength": 1, + "type": "string" + }, + "members": { + "description": "initial team member ids (between 1 and 127)" + }, + "name": { + "description": "team name", + "maxLength": 256, + "minLength": 1, + "type": "string" + } + }, + "required": [ + "name", + "icon" + ], + "type": "object" + }, + "Body": {}, + "CheckHandles": { + "properties": { + "handles": { + "items": { + "type": "string" + }, + "maxItems": 50, + "minItems": 1, + "type": "array" + }, + "return": { + "maximum": 10, + "minimum": 1, + "type": "integer" + } + }, + "required": [ + "handles", + "return" + ], + "type": "object" + }, + "CipherSuiteTag": { + "description": "The cipher suite of the corresponding MLS group", + "maximum": 65535, + "minimum": 0, + "type": "integer" + }, + "ClassifiedDomainsConfig": { + "properties": { + "domains": { + "items": { + "$ref": "#/definitions/Domain" + }, + "type": "array" + } + }, + "required": [ + "domains" + ], + "type": "object" + }, + "ClassifiedDomainsConfig.WithStatus": { + "properties": { + "config": { + "$ref": "#/definitions/ClassifiedDomainsConfig" + }, + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus", + "config" + ], + "type": "object" + }, + "Client": { + "properties": { + "capabilities": { + "$ref": "#/definitions/ClientCapabilityList" + }, + "class": { + "$ref": "#/definitions/ClientClass" + }, + "cookie": { + "type": "string" + }, + "id": { + "$ref": "#/definitions/ClientId" + }, + "label": { + "type": "string" + }, + "location": { + "$ref": "#/definitions/Location" + }, + "mls_public_keys": { + "$ref": "#/definitions/MLSPublicKeys" + }, + "model": { + "type": "string" + }, + "time": { + "$ref": "#/definitions/UTCTime" + }, + "type": { + "$ref": "#/definitions/ClientType" + } + }, + "required": [ + "id", + "type", + "time" + ], + "type": "object" + }, + "ClientCapability": { + "enum": [ + "legalhold-implicit-consent" + ], + "type": "string" + }, + "ClientCapabilityList": { + "properties": { + "capabilities": { + "description": "Hints provided by the client for the backend so it can behave in a backwards-compatible way.", + "items": { + "$ref": "#/definitions/ClientCapability" + }, + "type": "array" + } + }, + "required": [ + "capabilities" + ], + "type": "object" + }, + "ClientClass": { + "enum": [ + "phone", + "tablet", + "desktop", + "legalhold" + ], + "type": "string" + }, + "ClientId": { + "description": "Client ID", + "type": "string" + }, + "ClientMismatch": { + "properties": { + "deleted": { + "$ref": "#/definitions/UserClients" + }, + "missing": { + "$ref": "#/definitions/UserClients" + }, + "redundant": { + "$ref": "#/definitions/UserClients" + }, + "time": { + "$ref": "#/definitions/UTCTime" + } + }, + "required": [ + "time", + "missing", + "redundant", + "deleted" + ], + "type": "object" + }, + "ClientPrekey": { + "properties": { + "client": { + "$ref": "#/definitions/ClientId" + }, + "prekey": { + "$ref": "#/definitions/Prekey" + } + }, + "required": [ + "client", + "prekey" + ], + "type": "object" + }, + "ClientType": { + "enum": [ + "temporary", + "permanent", + "legalhold" + ], + "type": "string" + }, + "CompletePasswordReset": { + "description": "Data to complete a password reset", + "properties": { + "code": { + "$ref": "#/definitions/ASCII" + }, + "email": { + "$ref": "#/definitions/Email" + }, + "key": { + "$ref": "#/definitions/ASCII" + }, + "password": { + "description": "New password (6 - 1024 characters)", + "maxLength": 1024, + "minLength": 6, + "type": "string" + }, + "phone": { + "$ref": "#/definitions/PhoneNumber" + } + }, + "required": [ + "code", + "password" + ], + "type": "object" + }, + "ConferenceCallingConfig.WithStatus": { + "properties": { + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus" + ], + "type": "object" + }, + "Connect": { + "properties": { + "email": { + "type": "string" + }, + "message": { + "type": "string" + }, + "name": { + "type": "string" + }, + "qualified_recipient": { + "$ref": "#/definitions/Qualified_UserId" + }, + "recipient": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "qualified_recipient" + ], + "type": "object" + }, + "ConnectionUpdate": { + "properties": { + "status": { + "$ref": "#/definitions/Relation" + } + }, + "required": [ + "status" + ], + "type": "object" + }, + "Connections_Page": { + "properties": { + "connections": { + "items": { + "$ref": "#/definitions/UserConnection" + }, + "type": "array" + }, + "has_more": { + "type": "boolean" + }, + "paging_state": { + "$ref": "#/definitions/Connections_PagingState" + } + }, + "required": [ + "connections", + "has_more", + "paging_state" + ], + "type": "object" + }, + "Connections_PagingState": { + "type": "string" + }, + "Contact": { + "description": "Contact discovered through search", + "properties": { + "accent_id": { + "maximum": 9223372036854776000, + "minimum": -9223372036854776000, + "type": "integer" + }, + "handle": { + "type": "string" + }, + "id": { + "$ref": "#/definitions/UUID" + }, + "name": { + "type": "string" + }, + "qualified_id": { + "$ref": "#/definitions/Qualified_UserId" + }, + "team": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "qualified_id", + "name" + ], + "type": "object" + }, + "ConvMembers": { + "description": "Users of a conversation", + "properties": { + "others": { + "description": "All other current users of this conversation", + "items": { + "$ref": "#/definitions/OtherMember" + }, + "type": "array" + }, + "self": { + "$ref": "#/definitions/Member" + } + }, + "required": [ + "self", + "others" + ], + "type": "object" + }, + "ConvTeamInfo": { + "description": "Team information of this conversation", + "properties": { + "managed": { + "description": "This field MUST NOT be used by clients. It is here only for backwards compatibility of the interface." + }, + "teamid": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "teamid", + "managed" + ], + "type": "object" + }, + "ConvType": { + "enum": [ + 0, + 1, + 2, + 3 + ], + "type": "integer" + }, + "Conversation": { + "description": "A conversation object as returned from the server", + "properties": { + "access": { + "items": { + "$ref": "#/definitions/Access" + }, + "type": "array" + }, + "access_role": { + "$ref": "#/definitions/AccessRoleLegacy" + }, + "access_role_v2": { + "items": { + "$ref": "#/definitions/AccessRole" + }, + "type": "array" + }, + "cipher_suite": { + "$ref": "#/definitions/CipherSuiteTag" + }, + "creator": { + "$ref": "#/definitions/UUID" + }, + "epoch": { + "description": "The epoch number of the corresponding MLS group", + "format": "int64", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + }, + "group_id": { + "$ref": "#/definitions/GroupId" + }, + "id": { + "$ref": "#/definitions/UUID" + }, + "last_event": { + "type": "string" + }, + "last_event_time": { + "type": "string" + }, + "members": { + "$ref": "#/definitions/ConvMembers" + }, + "message_timer": { + "description": "Per-conversation message timer (can be null)", + "format": "int64", + "maximum": 9223372036854776000, + "minimum": -9223372036854776000, + "type": "integer" + }, + "name": { + "type": "string" + }, + "protocol": { + "$ref": "#/definitions/Protocol" + }, + "qualified_id": { + "$ref": "#/definitions/Qualified_ConvId" + }, + "receipt_mode": { + "description": "Conversation receipt mode", + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + }, + "team": { + "$ref": "#/definitions/UUID" + }, + "type": { + "$ref": "#/definitions/ConvType" + } + }, + "required": [ + "qualified_id", + "type", + "creator", + "access", + "members", + "group_id", + "epoch", + "cipher_suite" + ], + "type": "object" + }, + "ConversationAccessData": { + "properties": { + "access": { + "items": { + "$ref": "#/definitions/Access" + }, + "type": "array" + }, + "access_role": { + "items": { + "$ref": "#/definitions/AccessRole" + }, + "type": "array" + } + }, + "required": [ + "access", + "access_role" + ], + "type": "object" + }, + "ConversationAccessData2": { + "properties": { + "access": { + "items": { + "$ref": "#/definitions/Access" + }, + "type": "array" + }, + "access_role": { + "$ref": "#/definitions/AccessRoleLegacy" + }, + "access_role_v2": { + "items": { + "$ref": "#/definitions/AccessRole" + }, + "type": "array" + } + }, + "required": [ + "access" + ], + "type": "object" + }, + "ConversationCode": { + "description": "Contains conversation properties to update", + "properties": { + "code": { + "$ref": "#/definitions/ASCII" + }, + "key": { + "$ref": "#/definitions/ASCII" + }, + "uri": { + "$ref": "#/definitions/HttpsUrl" + } + }, + "required": [ + "key", + "code" + ], + "type": "object" + }, + "ConversationCoverView": { + "description": "Limited view of Conversation.", + "properties": { + "id": { + "$ref": "#/definitions/UUID" + }, + "name": { + "type": "string" + } + }, + "required": [ + "id" + ], + "type": "object" + }, + "ConversationIds_Page": { + "properties": { + "has_more": { + "type": "boolean" + }, + "paging_state": { + "$ref": "#/definitions/ConversationIds_PagingState" + }, + "qualified_conversations": { + "items": { + "$ref": "#/definitions/Qualified_ConvId" + }, + "type": "array" + } + }, + "required": [ + "qualified_conversations", + "has_more", + "paging_state" + ], + "type": "object" + }, + "ConversationIds_PagingState": { + "type": "string" + }, + "ConversationMessageTimerUpdate": { + "description": "Contains conversation properties to update", + "properties": { + "message_timer": { + "format": "int64", + "maximum": 9223372036854776000, + "minimum": -9223372036854776000, + "type": "integer" + } + }, + "type": "object" + }, + "ConversationReceiptModeUpdate": { + "description": "Contains conversation receipt mode to update to. Receipt mode tells clients whether certain types of receipts should be sent in the given conversation or not. How this value is interpreted is up to clients.", + "properties": { + "receipt_mode": { + "description": "Conversation receipt mode", + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + } + }, + "required": [ + "receipt_mode" + ], + "type": "object" + }, + "ConversationRename": { + "properties": { + "name": { + "description": "The new conversation name", + "type": "string" + } + }, + "required": [ + "name" + ], + "type": "object" + }, + "ConversationRole": { + "properties": { + "actions": { + "description": "The set of actions allowed for this role", + "items": { + "$ref": "#/definitions/Action" + }, + "type": "array" + }, + "conversation_role": { + "$ref": "#/definitions/RoleName" + } + } + }, + "ConversationRolesList": { + "properties": { + "conversation_roles": { + "items": { + "$ref": "#/definitions/ConversationRole" + }, + "type": "array" + } + }, + "required": [ + "conversation_roles" + ], + "type": "object" + }, + "ConversationsResponse": { + "description": "Response object for getting metadata of a list of conversations", + "properties": { + "failed": { + "description": "The server failed to fetch these conversations, most likely due to network issues while contacting a remote server", + "items": { + "$ref": "#/definitions/Qualified_ConvId" + }, + "type": "array" + }, + "found": { + "items": { + "$ref": "#/definitions/Conversation" + }, + "type": "array" + }, + "not_found": { + "description": "These conversations either don't exist or are deleted.", + "items": { + "$ref": "#/definitions/Qualified_ConvId" + }, + "type": "array" + } + }, + "required": [ + "found", + "not_found", + "failed" + ], + "type": "object" + }, + "Cookie": { + "properties": { + "created": { + "$ref": "#/definitions/UTCTime" + }, + "expires": { + "$ref": "#/definitions/UTCTime" + }, + "id": { + "format": "int32", + "maximum": 4294967295, + "minimum": 0, + "type": "integer" + }, + "label": { + "type": "string" + }, + "successor": { + "format": "int32", + "maximum": 4294967295, + "minimum": 0, + "type": "integer" + }, + "type": { + "$ref": "#/definitions/CookieType" + } + }, + "required": [ + "id", + "type", + "created", + "expires" + ], + "type": "object" + }, + "CookieList": { + "description": "List of cookie information", + "properties": { + "cookies": { + "items": { + "$ref": "#/definitions/Cookie" + }, + "type": "array" + } + }, + "required": [ + "cookies" + ], + "type": "object" + }, + "CookieType": { + "enum": [ + "session", + "persistent" + ], + "type": "string" + }, + "CreateScimToken": { + "properties": { + "description": { + "type": "string" + }, + "password": { + "type": "string" + }, + "verification_code": { + "type": "string" + } + }, + "required": [ + "description" + ], + "type": "object" + }, + "CreateScimTokenResponse": { + "properties": { + "info": { + "$ref": "#/definitions/ScimTokenInfo" + }, + "token": { + "description": "Authentication token", + "type": "string" + } + }, + "required": [ + "token", + "info" + ], + "type": "object" + }, + "CustomBackend": { + "description": "Description of a custom backend", + "properties": { + "config_json_url": { + "$ref": "#/definitions/HttpsUrl" + }, + "webapp_welcome_url": { + "$ref": "#/definitions/HttpsUrl" + } + }, + "required": [ + "config_json_url", + "webapp_welcome_url" + ], + "type": "object" + }, + "DPoPAccessToken": { + "example": "ZXhhbXBsZQo=", + "type": "string" + }, + "DPoPAccessTokenResponse": { + "properties": { + "expires_in": { + "format": "int64", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + }, + "token": { + "$ref": "#/definitions/DPoPAccessToken" + }, + "type": { + "$ref": "#/definitions/AccessTokenType" + } + }, + "required": [ + "token", + "type", + "expires_in" + ], + "type": "object" + }, + "DeleteClient": { + "properties": { + "password": { + "description": "The password of the authenticated user for verification. The password is not required for deleting temporary clients.", + "maxLength": 1024, + "minLength": 6, + "type": "string" + } + }, + "type": "object" + }, + "DeleteUser": { + "properties": { + "password": { + "maxLength": 1024, + "minLength": 6, + "type": "string" + } + }, + "type": "object" + }, + "DeletionCodeTimeout": { + "properties": { + "expires_in": { + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + } + }, + "required": [ + "expires_in" + ], + "type": "object" + }, + "DeprecatedMatchingResult": { + "properties": { + "auto-connects": { + "items": {}, + "type": "array" + }, + "results": { + "items": {}, + "type": "array" + } + }, + "required": [ + "results", + "auto-connects" + ], + "type": "object" + }, + "DigitalSignaturesConfig.WithStatus": { + "properties": { + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus" + ], + "type": "object" + }, + "DisableLegalHoldForUserRequest": { + "properties": { + "password": { + "maxLength": 1024, + "minLength": 6, + "type": "string" + } + }, + "type": "object" + }, + "Domain": { + "example": "example.com", + "type": "string" + }, + "Email": { + "description": "Email of the invitee", + "type": "string" + }, + "EmailUpdate": { + "properties": { + "email": { + "$ref": "#/definitions/Email" + } + }, + "required": [ + "email" + ], + "type": "object" + }, + "Event": { + "properties": { + "conversation": { + "$ref": "#/definitions/UUID" + }, + "data": { + "description": "Encrypted message of a conversation", + "example": "ZXhhbXBsZQo=", + "properties": { + "access": { + "items": { + "$ref": "#/definitions/Access" + }, + "type": "array" + }, + "access_role": { + "$ref": "#/definitions/AccessRoleLegacy" + }, + "access_role_v2": { + "items": { + "$ref": "#/definitions/AccessRole" + }, + "type": "array" + }, + "cipher_suite": { + "$ref": "#/definitions/CipherSuiteTag" + }, + "code": { + "$ref": "#/definitions/ASCII" + }, + "conversation_role": { + "$ref": "#/definitions/RoleName" + }, + "creator": { + "$ref": "#/definitions/UUID" + }, + "data": { + "description": "Extra (symmetric) data (i.e. ciphertext, Base64 in JSON) that is common with all other recipients.", + "type": "string" + }, + "email": { + "type": "string" + }, + "epoch": { + "description": "The epoch number of the corresponding MLS group", + "format": "int64", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + }, + "group_id": { + "$ref": "#/definitions/GroupId" + }, + "hidden": { + "type": "boolean" + }, + "hidden_ref": { + "type": "string" + }, + "id": { + "$ref": "#/definitions/UUID" + }, + "key": { + "$ref": "#/definitions/ASCII" + }, + "last_event": { + "type": "string" + }, + "last_event_time": { + "type": "string" + }, + "members": { + "$ref": "#/definitions/ConvMembers" + }, + "message": { + "type": "string" + }, + "message_timer": { + "description": "Per-conversation message timer (can be null)", + "format": "int64", + "maximum": 9223372036854776000, + "minimum": -9223372036854776000, + "type": "integer" + }, + "name": { + "type": "string" + }, + "otr_archived": { + "type": "boolean" + }, + "otr_archived_ref": { + "type": "string" + }, + "otr_muted_ref": { + "type": "string" + }, + "otr_muted_status": { + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + }, + "protocol": { + "$ref": "#/definitions/Protocol" + }, + "qualified_id": { + "$ref": "#/definitions/Qualified_ConvId" + }, + "qualified_recipient": { + "$ref": "#/definitions/Qualified_UserId" + }, + "qualified_target": { + "$ref": "#/definitions/Qualified_UserId" + }, + "qualified_user_ids": { + "items": { + "$ref": "#/definitions/Qualified_UserId" + }, + "type": "array" + }, + "receipt_mode": { + "description": "Conversation receipt mode", + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + }, + "recipient": { + "$ref": "#/definitions/ClientId" + }, + "sender": { + "$ref": "#/definitions/ClientId" + }, + "status": { + "$ref": "#/definitions/TypingStatus" + }, + "target": { + "$ref": "#/definitions/UUID" + }, + "team": { + "$ref": "#/definitions/UUID" + }, + "text": { + "description": "The ciphertext for the recipient (Base64 in JSON)", + "type": "string" + }, + "type": { + "$ref": "#/definitions/ConvType" + }, + "uri": { + "$ref": "#/definitions/HttpsUrl" + }, + "user_ids": { + "description": "Deprecated, use qualified_user_ids", + "items": { + "$ref": "#/definitions/UUID" + }, + "type": "array" + }, + "users": { + "items": { + "$ref": "#/definitions/SimpleMember" + }, + "type": "array" + } + }, + "required": [ + "users", + "qualified_user_ids", + "user_ids", + "qualified_target", + "name", + "access", + "key", + "code", + "qualified_id", + "type", + "creator", + "members", + "group_id", + "epoch", + "cipher_suite", + "qualified_recipient", + "receipt_mode", + "sender", + "recipient", + "text", + "status" + ], + "type": "object" + }, + "from": { + "$ref": "#/definitions/UUID" + }, + "qualified_conversation": { + "$ref": "#/definitions/Qualified_ConvId" + }, + "qualified_from": { + "$ref": "#/definitions/Qualified_UserId" + }, + "subconv": { + "type": "string" + }, + "time": { + "$ref": "#/definitions/UTCTime" + }, + "type": { + "$ref": "#/definitions/EventType" + } + }, + "required": [ + "type", + "data", + "qualified_conversation", + "qualified_from", + "time" + ], + "type": "object" + }, + "EventType": { + "enum": [ + "conversation.member-join", + "conversation.member-leave", + "conversation.member-update", + "conversation.rename", + "conversation.access-update", + "conversation.receipt-mode-update", + "conversation.message-timer-update", + "conversation.code-update", + "conversation.code-delete", + "conversation.create", + "conversation.delete", + "conversation.connect-request", + "conversation.typing", + "conversation.otr-message-add", + "conversation.mls-message-add", + "conversation.mls-welcome" + ], + "type": "string" + }, + "ExposeInvitationURLsToTeamAdminConfig.WithStatus": { + "properties": { + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus" + ], + "type": "object" + }, + "ExposeInvitationURLsToTeamAdminConfig.WithStatusNoLock": { + "properties": { + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status" + ], + "type": "object" + }, + "FeatureStatus": { + "enum": [ + "enabled", + "disabled" + ], + "type": "string" + }, + "FederatedUserSearchPolicy": { + "description": "Search policy that was applied when searching for users", + "enum": [ + "no_search", + "exact_handle_search", + "full_search" + ], + "type": "string" + }, + "FileSharingConfig.WithStatus": { + "properties": { + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus" + ], + "type": "object" + }, + "FileSharingConfig.WithStatusNoLock": { + "properties": { + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status" + ], + "type": "object" + }, + "Fingerprint": { + "example": "ioy3GeIjgQRsobf2EKGO3O8mq/FofFxHRqy0T4ERIZ8=", + "type": "string" + }, + "FormRedirect": { + "properties": { + "uri": { + "type": "string" + }, + "xml": { + "$ref": "#/definitions/AuthnRequest" + } + }, + "type": "object" + }, + "GetPaginated_Connections": { + "description": "A request to list some or all of a user's Connections, including remote ones", + "properties": { + "paging_state": { + "$ref": "#/definitions/Connections_PagingState" + }, + "size": { + "description": "optional, must be <= 500, defaults to 100.", + "format": "int32", + "maximum": 500, + "minimum": 1, + "type": "integer" + } + }, + "type": "object" + }, + "GetPaginated_ConversationIds": { + "description": "A request to list some or all of a user's ConversationIds, including remote ones", + "properties": { + "paging_state": { + "$ref": "#/definitions/ConversationIds_PagingState" + }, + "size": { + "description": "optional, must be <= 1000, defaults to 1000.", + "format": "int32", + "maximum": 1000, + "minimum": 1, + "type": "integer" + } + }, + "type": "object" + }, + "GroupId": { + "description": "An MLS group identifier (at most 256 bytes long)", + "example": "ZXhhbXBsZQo=", + "type": "string" + }, + "GuestLinksConfig.WithStatus": { + "properties": { + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus" + ], + "type": "object" + }, + "GuestLinksConfig.WithStatusNoLock": { + "properties": { + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status" + ], + "type": "object" + }, + "Handle": { + "type": "string" + }, + "HandleUpdate": { + "properties": { + "handle": { + "type": "string" + } + }, + "required": [ + "handle" + ], + "type": "object" + }, + "HttpsUrl": { + "example": "https://example.com", + "type": "string" + }, + "ID": { + "properties": { + "iD": { + "$ref": "#/definitions/XmlText" + } + }, + "required": [ + "iD" + ], + "type": "object" + }, + "Icon": { + "type": "string" + }, + "Id": { + "properties": { + "id": { + "$ref": "#/definitions/ClientId" + } + }, + "required": [ + "id" + ], + "type": "object" + }, + "IdPConfig": { + "properties": { + "extraInfo": { + "$ref": "#/definitions/WireIdP" + }, + "id": { + "$ref": "#/definitions/UUID" + }, + "metadata": { + "$ref": "#/definitions/IdPMetadata" + } + }, + "required": [ + "id", + "metadata", + "extraInfo" + ], + "type": "object" + }, + "IdPList": { + "properties": { + "providers": { + "items": { + "$ref": "#/definitions/IdPConfig" + }, + "type": "array" + } + }, + "required": [ + "providers" + ], + "type": "object" + }, + "IdPMetadata": { + "properties": { + "certAuthnResponse": { + "items": { + "type": "string" + }, + "minItems": 1, + "type": "array" + }, + "issuer": { + "type": "string" + }, + "requestURI": { + "type": "string" + } + }, + "required": [ + "issuer", + "requestURI", + "certAuthnResponse" + ], + "type": "object" + }, + "IdPMetadataInfo": { + "maxProperties": 1, + "minProperties": 1, + "properties": { + "value": { + "type": "string" + } + }, + "type": "object" + }, + "Invitation": { + "description": "An invitation to join a team on Wire", + "properties": { + "created_at": { + "$ref": "#/definitions/UTCTime" + }, + "created_by": { + "$ref": "#/definitions/UUID" + }, + "email": { + "$ref": "#/definitions/Email" + }, + "id": { + "$ref": "#/definitions/UUID" + }, + "name": { + "description": "Name of the invitee (1 - 128 characters)", + "maxLength": 128, + "minLength": 1, + "type": "string" + }, + "phone": { + "$ref": "#/definitions/PhoneNumber" + }, + "role": { + "$ref": "#/definitions/Role" + }, + "team": { + "$ref": "#/definitions/UUID" + }, + "url": { + "$ref": "#/definitions/URIRef Absolute" + } + }, + "required": [ + "team", + "id", + "created_at", + "email" + ], + "type": "object" + }, + "InvitationList": { + "description": "A list of sent team invitations.", + "properties": { + "has_more": { + "description": "Indicator that the server has more invitations than returned.", + "type": "boolean" + }, + "invitations": { + "items": { + "$ref": "#/definitions/Invitation" + }, + "type": "array" + } + }, + "required": [ + "invitations", + "has_more" + ], + "type": "object" + }, + "InvitationRequest": { + "description": "A request to join a team on Wire.", + "properties": { + "email": { + "$ref": "#/definitions/Email" + }, + "locale": { + "$ref": "#/definitions/Locale" + }, + "name": { + "description": "Name of the invitee (1 - 128 characters).", + "maxLength": 128, + "minLength": 1, + "type": "string" + }, + "phone": { + "$ref": "#/definitions/PhoneNumber" + }, + "role": { + "$ref": "#/definitions/Role" + } + }, + "required": [ + "email" + ], + "type": "object" + }, + "InviteQualified": { + "properties": { + "conversation_role": { + "$ref": "#/definitions/RoleName" + }, + "qualified_users": { + "items": { + "$ref": "#/definitions/Qualified_UserId" + }, + "minItems": 1, + "type": "array" + } + }, + "required": [ + "qualified_users" + ], + "type": "object" + }, + "KeyPackage": { + "example": "a2V5IHBhY2thZ2UgZGF0YQo=", + "type": "string" + }, + "KeyPackageBundle": { + "properties": { + "key_packages": { + "items": { + "$ref": "#/definitions/KeyPackageBundleEntry" + }, + "type": "array" + } + }, + "required": [ + "key_packages" + ], + "type": "object" + }, + "KeyPackageBundleEntry": { + "properties": { + "client": { + "$ref": "#/definitions/ClientId" + }, + "domain": { + "$ref": "#/definitions/Domain" + }, + "key_package": { + "$ref": "#/definitions/KeyPackage" + }, + "key_package_ref": { + "$ref": "#/definitions/KeyPackageRef" + }, + "user": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "domain", + "user", + "client", + "key_package_ref", + "key_package" + ], + "type": "object" + }, + "KeyPackageRef": { + "example": "ZXhhbXBsZQo=", + "type": "string" + }, + "KeyPackageUpload": { + "properties": { + "key_packages": { + "items": { + "$ref": "#/definitions/KeyPackage" + }, + "type": "array" + } + }, + "required": [ + "key_packages" + ], + "type": "object" + }, + "LHServiceStatus": { + "enum": [ + "configured", + "not_configured", + "disabled" + ], + "type": "string" + }, + "LegalholdConfig.WithStatus": { + "properties": { + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus" + ], + "type": "object" + }, + "LegalholdConfig.WithStatusNoLock": { + "properties": { + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status" + ], + "type": "object" + }, + "LimitedQualifiedUserIdList": { + "properties": { + "qualified_users": { + "items": { + "$ref": "#/definitions/Qualified_UserId" + }, + "type": "array" + } + }, + "required": [ + "qualified_users" + ], + "type": "object" + }, + "ListConversations": { + "description": "A request to list some of a user's conversations, including remote ones. Maximum 1000 qualified conversation IDs", + "properties": { + "qualified_ids": { + "items": { + "$ref": "#/definitions/Qualified_ConvId" + }, + "maxItems": 1000, + "minItems": 1, + "type": "array" + } + }, + "required": [ + "qualified_ids" + ], + "type": "object" + }, + "ListType": { + "description": "true if 'members' doesn't contain all team members", + "enum": [ + true, + false + ], + "type": "boolean" + }, + "ListUsersQuery": { + "description": "exactly one of qualified_ids or qualified_handles must be provided.", + "example": { + "qualified_ids": [ + { + "domain": "example.com", + "id": "00000000-0000-0000-0000-000000000000" + } + ] + }, + "properties": { + "qualified_handles": { + "items": { + "$ref": "#/definitions/Qualified_Handle" + }, + "type": "array" + }, + "qualified_ids": { + "items": { + "$ref": "#/definitions/Qualified_UserId" + }, + "type": "array" + } + }, + "type": "object" + }, + "Locale": { + "description": "Locale to use for the invitation.", + "type": "string" + }, + "LocaleUpdate": { + "properties": { + "locale": { + "$ref": "#/definitions/Locale" + } + }, + "required": [ + "locale" + ], + "type": "object" + }, + "Location": { + "properties": { + "lat": { + "format": "double", + "type": "number" + }, + "lon": { + "format": "double", + "type": "number" + } + }, + "required": [ + "lat", + "lon" + ], + "type": "object" + }, + "LockStatus": { + "enum": [ + "locked", + "unlocked" + ], + "type": "string" + }, + "Login": { + "properties": { + "code": { + "$ref": "#/definitions/LoginCode" + }, + "email": { + "$ref": "#/definitions/Email" + }, + "handle": { + "$ref": "#/definitions/Handle" + }, + "label": { + "description": "This label can be used to delete all cookies matching it (cf. /cookies/remove)", + "type": "string" + }, + "password": { + "maxLength": 1024, + "minLength": 6, + "type": "string" + }, + "phone": { + "$ref": "#/definitions/PhoneNumber" + }, + "verification_code": { + "$ref": "#/definitions/ASCII" + } + }, + "required": [ + "password", + "phone", + "code" + ], + "type": "object" + }, + "LoginCode": { + "type": "string" + }, + "LoginCodeTimeout": { + "description": "A response for a successfully sent login code", + "properties": { + "expires_in": { + "description": "Number of seconds before the login code expires", + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + } + }, + "required": [ + "expires_in" + ], + "type": "object" + }, + "MLSConfig": { + "properties": { + "allowedCipherSuites": { + "items": { + "$ref": "#/definitions/CipherSuiteTag" + }, + "type": "array" + }, + "defaultCipherSuite": { + "$ref": "#/definitions/CipherSuiteTag" + }, + "defaultProtocol": { + "$ref": "#/definitions/Protocol" + }, + "protocolToggleUsers": { + "description": "allowlist of users that may change protocols", + "items": { + "$ref": "#/definitions/UUID" + }, + "type": "array" + } + }, + "required": [ + "protocolToggleUsers", + "defaultProtocol", + "allowedCipherSuites", + "defaultCipherSuite" + ], + "type": "object" + }, + "MLSConfig.WithStatus": { + "properties": { + "config": { + "$ref": "#/definitions/MLSConfig" + }, + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus", + "config" + ], + "type": "object" + }, + "MLSConfig.WithStatusNoLock": { + "properties": { + "config": { + "$ref": "#/definitions/MLSConfig" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "config" + ], + "type": "object" + }, + "MLSMessageSendingStatus": { + "properties": { + "events": { + "description": "A list of events caused by sending the message.", + "items": { + "$ref": "#/definitions/Event" + }, + "type": "array" + }, + "time": { + "$ref": "#/definitions/UTCTime" + } + }, + "required": [ + "events", + "time" + ], + "type": "object" + }, + "MLSPublicKeys": { + "additionalProperties": { + "example": "ZXhhbXBsZQo=", + "type": "string" + }, + "description": "Mapping from signature scheme (tags) to public key data", + "example": { + "ed25519": "ZXhhbXBsZQo=" + }, + "type": "object" + }, + "ManagedBy": { + "enum": [ + "wire", + "scim" + ], + "type": "string" + }, + "Member": { + "description": "The user ID of the requestor", + "properties": { + "conversation_role": { + "$ref": "#/definitions/RoleName" + }, + "hidden": { + "type": "boolean" + }, + "hidden_ref": { + "type": "string" + }, + "id": { + "$ref": "#/definitions/UUID" + }, + "otr_archived": { + "type": "boolean" + }, + "otr_archived_ref": { + "type": "string" + }, + "otr_muted_ref": { + "type": "string" + }, + "otr_muted_status": { + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + }, + "qualified_id": { + "$ref": "#/definitions/Qualified_UserId" + }, + "service": { + "$ref": "#/definitions/ServiceRef" + }, + "status": {}, + "status_ref": {}, + "status_time": {} + }, + "required": [ + "qualified_id" + ], + "type": "object" + }, + "MemberUpdate": { + "properties": { + "hidden": { + "type": "boolean" + }, + "hidden_ref": { + "type": "string" + }, + "otr_archived": { + "type": "boolean" + }, + "otr_archived_ref": { + "type": "string" + }, + "otr_muted_ref": { + "type": "string" + }, + "otr_muted_status": { + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + } + }, + "type": "object" + }, + "MemberUpdateData": { + "properties": { + "conversation_role": { + "$ref": "#/definitions/RoleName" + }, + "hidden": { + "type": "boolean" + }, + "hidden_ref": { + "type": "string" + }, + "otr_archived": { + "type": "boolean" + }, + "otr_archived_ref": { + "type": "string" + }, + "otr_muted_ref": { + "type": "string" + }, + "otr_muted_status": { + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + }, + "qualified_target": { + "$ref": "#/definitions/Qualified_UserId" + }, + "target": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "qualified_target" + ], + "type": "object" + }, + "MessageSendingStatus": { + "properties": { + "deleted": { + "$ref": "#/definitions/QualifiedUserClients" + }, + "failed_to_send": { + "$ref": "#/definitions/QualifiedUserClients" + }, + "missing": { + "$ref": "#/definitions/QualifiedUserClients" + }, + "redundant": { + "$ref": "#/definitions/QualifiedUserClients" + }, + "time": { + "$ref": "#/definitions/UTCTime" + } + }, + "required": [ + "time", + "missing", + "redundant", + "deleted", + "failed_to_send" + ], + "type": "object" + }, + "MlsE2EIdConfig": { + "properties": { + "verificationExpiration": { + "description": "Unix timestamp (number of seconds that have passed since 00:00:00 UTC on Thursday, 1 January 1970) after which the period for clients to verify their identity expires. When the timer goes off, they will be logged out and get the certificate automatically on their devices.", + "maximum": 9223372036854776000, + "minimum": -9223372036854776000, + "type": "integer" + } + }, + "type": "object" + }, + "MlsE2EIdConfig.WithStatus": { + "properties": { + "config": { + "$ref": "#/definitions/MlsE2EIdConfig" + }, + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus", + "config" + ], + "type": "object" + }, + "MlsE2EIdConfig.WithStatusNoLock": { + "properties": { + "config": { + "$ref": "#/definitions/MlsE2EIdConfig" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "config" + ], + "type": "object" + }, + "NameIDFormat": { + "enum": [ + "NameIDFUnspecified", + "NameIDFEmail", + "NameIDFX509", + "NameIDFWindows", + "NameIDFKerberos", + "NameIDFEntity", + "NameIDFPersistent", + "NameIDFTransient" + ], + "type": "string" + }, + "NameIdPolicy": { + "properties": { + "allowCreate": { + "type": "boolean" + }, + "format": { + "$ref": "#/definitions/NameIDFormat" + }, + "spNameQualifier": { + "$ref": "#/definitions/XmlText" + } + }, + "required": [ + "format", + "allowCreate" + ], + "type": "object" + }, + "NewAssetToken": { + "properties": { + "token": { + "$ref": "#/definitions/ASCII" + } + }, + "required": [ + "token" + ], + "type": "object" + }, + "NewClient": { + "properties": { + "capabilities": { + "description": "Hints provided by the client for the backend so it can behave in a backwards-compatible way.", + "items": { + "$ref": "#/definitions/ClientCapability" + }, + "type": "array" + }, + "class": { + "$ref": "#/definitions/ClientClass" + }, + "cookie": { + "description": "The cookie label, i.e. the label used when logging in.", + "type": "string" + }, + "label": { + "type": "string" + }, + "lastkey": { + "$ref": "#/definitions/Prekey" + }, + "mls_public_keys": { + "$ref": "#/definitions/MLSPublicKeys" + }, + "model": { + "type": "string" + }, + "password": { + "description": "The password of the authenticated user for verification. Note: Required for registration of the 2nd, 3rd, ... client.", + "maxLength": 1024, + "minLength": 6, + "type": "string" + }, + "prekeys": { + "description": "Prekeys for other clients to establish OTR sessions.", + "items": { + "$ref": "#/definitions/Prekey" + }, + "type": "array" + }, + "type": { + "$ref": "#/definitions/ClientType" + }, + "verification_code": { + "$ref": "#/definitions/ASCII" + } + }, + "required": [ + "prekeys", + "lastkey", + "type" + ], + "type": "object" + }, + "NewConv": { + "description": "JSON object to create a new conversation. When using 'qualified_users' (preferred), you can omit 'users'", + "properties": { + "access": { + "items": { + "$ref": "#/definitions/Access" + }, + "type": "array" + }, + "access_role": { + "items": { + "$ref": "#/definitions/AccessRole" + }, + "type": "array" + }, + "conversation_role": { + "$ref": "#/definitions/RoleName" + }, + "creator_client": { + "$ref": "#/definitions/ClientId" + }, + "message_timer": { + "description": "Per-conversation message timer", + "format": "int64", + "maximum": 9223372036854776000, + "minimum": -9223372036854776000, + "type": "integer" + }, + "name": { + "maxLength": 256, + "minLength": 1, + "type": "string" + }, + "protocol": { + "$ref": "#/definitions/Protocol" + }, + "qualified_users": { + "description": "List of qualified user IDs (excluding the requestor) to be part of this conversation", + "items": { + "$ref": "#/definitions/Qualified_UserId" + }, + "type": "array" + }, + "receipt_mode": { + "description": "Conversation receipt mode", + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + }, + "team": { + "$ref": "#/definitions/ConvTeamInfo" + }, + "users": { + "description": "List of user IDs (excluding the requestor) to be part of this conversation (deprecated)", + "items": { + "$ref": "#/definitions/UUID" + }, + "type": "array" + } + }, + "type": "object" + }, + "NewLegalHoldService": { + "properties": { + "auth_token": { + "$ref": "#/definitions/ASCII" + }, + "base_url": { + "$ref": "#/definitions/HttpsUrl" + }, + "public_key": { + "$ref": "#/definitions/ServiceKeyPEM" + } + }, + "required": [ + "base_url", + "public_key", + "auth_token" + ], + "type": "object" + }, + "NewPasswordReset": { + "description": "Data to initiate a password reset", + "properties": { + "email": { + "$ref": "#/definitions/Email" + }, + "phone": { + "$ref": "#/definitions/PhoneNumber" + } + }, + "type": "object" + }, + "NewTeamMember": { + "description": "Required data when creating new team members", + "properties": { + "member": { + "description": "the team member to add (the legalhold_status field must be null or missing!)", + "properties": { + "created_at": { + "$ref": "#/definitions/UTCTime" + }, + "created_by": { + "$ref": "#/definitions/UUID" + }, + "permissions": { + "$ref": "#/definitions/Permissions" + }, + "user": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "user", + "permissions" + ], + "type": "object" + } + }, + "required": [ + "member" + ], + "type": "object" + }, + "NewUser": { + "properties": { + "accent_id": { + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + }, + "assets": { + "items": { + "$ref": "#/definitions/UserAsset" + }, + "type": "array" + }, + "email": { + "$ref": "#/definitions/Email" + }, + "email_code": { + "$ref": "#/definitions/ASCII" + }, + "expires_in": { + "maximum": 604800, + "minimum": 1, + "type": "integer" + }, + "invitation_code": { + "$ref": "#/definitions/ASCII" + }, + "label": { + "type": "string" + }, + "locale": { + "$ref": "#/definitions/Locale" + }, + "managed_by": { + "$ref": "#/definitions/ManagedBy" + }, + "name": { + "maxLength": 128, + "minLength": 1, + "type": "string" + }, + "password": { + "maxLength": 1024, + "minLength": 6, + "type": "string" + }, + "phone": { + "$ref": "#/definitions/PhoneNumber" + }, + "phone_code": { + "$ref": "#/definitions/ASCII" + }, + "picture": { + "$ref": "#/definitions/Pict" + }, + "sso_id": { + "$ref": "#/definitions/UserSSOId" + }, + "team": { + "$ref": "#/definitions/BindingNewTeamUser" + }, + "team_code": { + "$ref": "#/definitions/ASCII" + }, + "team_id": { + "$ref": "#/definitions/UUID" + }, + "uuid": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "name" + ], + "type": "object" + }, + "NonBindingNewTeam": { + "properties": { + "icon": { + "$ref": "#/definitions/Icon" + }, + "icon_key": { + "description": "team icon asset key", + "maxLength": 256, + "minLength": 1, + "type": "string" + }, + "members": { + "description": "initial team member ids (between 1 and 127)", + "items": { + "$ref": "#/definitions/TeamMember" + }, + "maxItems": 127, + "minItems": 1, + "type": "array" + }, + "name": { + "description": "team name", + "maxLength": 256, + "minLength": 1, + "type": "string" + } + }, + "required": [ + "name", + "icon" + ], + "type": "object" + }, + "Object": { + "additionalProperties": true, + "description": "A single notification event", + "properties": { + "type": { + "description": "Event type", + "type": "string" + } + }, + "title": "Event", + "type": "object" + }, + "OtherMember": { + "properties": { + "conversation_role": { + "$ref": "#/definitions/RoleName" + }, + "id": { + "$ref": "#/definitions/UUID" + }, + "qualified_id": { + "$ref": "#/definitions/Qualified_UserId" + }, + "service": { + "$ref": "#/definitions/ServiceRef" + }, + "status": { + "description": "deprecated", + "maximum": 9223372036854776000, + "minimum": -9223372036854776000, + "type": "integer" + } + }, + "required": [ + "qualified_id" + ], + "type": "object" + }, + "OtherMemberUpdate": { + "description": "Update user properties of other members relative to a conversation", + "properties": { + "conversation_role": { + "$ref": "#/definitions/RoleName" + } + }, + "type": "object" + }, + "OtrMessage": { + "description": "Encrypted message of a conversation", + "properties": { + "data": { + "description": "Extra (symmetric) data (i.e. ciphertext, Base64 in JSON) that is common with all other recipients.", + "type": "string" + }, + "recipient": { + "$ref": "#/definitions/ClientId" + }, + "sender": { + "$ref": "#/definitions/ClientId" + }, + "text": { + "description": "The ciphertext for the recipient (Base64 in JSON)", + "type": "string" + } + }, + "required": [ + "sender", + "recipient", + "text" + ], + "type": "object" + }, + "OutlookCalIntegrationConfig.WithStatus": { + "properties": { + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus" + ], + "type": "object" + }, + "OutlookCalIntegrationConfig.WithStatusNoLock": { + "properties": { + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status" + ], + "type": "object" + }, + "OwnKeyPackages": { + "properties": { + "count": { + "maximum": 9223372036854776000, + "minimum": -9223372036854776000, + "type": "integer" + } + }, + "required": [ + "count" + ], + "type": "object" + }, + "PagingState": { + "description": "Paging state that should be supplied to retrieve the next page of results", + "type": "string" + }, + "PasswordChange": { + "description": "Data to change a password. The old password is required if a password already exists.", + "properties": { + "new_password": { + "maxLength": 1024, + "minLength": 6, + "type": "string" + }, + "old_password": { + "maxLength": 1024, + "minLength": 6, + "type": "string" + } + }, + "required": [ + "new_password" + ], + "type": "object" + }, + "PasswordReset": { + "description": "Data to complete a password reset", + "properties": { + "code": { + "$ref": "#/definitions/ASCII" + }, + "password": { + "description": "New password (6 - 1024 characters)", + "maxLength": 1024, + "minLength": 6, + "type": "string" + } + }, + "required": [ + "code", + "password" + ], + "type": "object" + }, + "Permissions": { + "properties": { + "copy": { + "format": "int64", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + }, + "self": { + "format": "int64", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "self", + "copy" + ], + "type": "object" + }, + "PhoneNumber": { + "description": "Phone number of the invitee, in the E.164 format", + "type": "string" + }, + "PhoneUpdate": { + "properties": { + "phone": { + "$ref": "#/definitions/PhoneNumber" + } + }, + "required": [ + "phone" + ], + "type": "object" + }, + "Pict": { + "items": {}, + "maxItems": 10, + "minItems": 0, + "type": "array" + }, + "Prekey": { + "properties": { + "id": { + "maximum": 65535, + "minimum": 0, + "type": "integer" + }, + "key": { + "type": "string" + } + }, + "required": [ + "id", + "key" + ], + "type": "object" + }, + "PrekeyBundle": { + "properties": { + "clients": { + "items": { + "$ref": "#/definitions/ClientPrekey" + }, + "type": "array" + }, + "user": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "user", + "clients" + ], + "type": "object" + }, + "Priority": { + "enum": [ + "low", + "high" + ], + "type": "string" + }, + "PropertyKeysAndValues": { + "type": "object" + }, + "PropertyValue": { + "description": "An arbitrary JSON value for a property" + }, + "Protocol": { + "enum": [ + "proteus", + "mls" + ], + "type": "string" + }, + "PubClient": { + "properties": { + "class": { + "$ref": "#/definitions/ClientClass" + }, + "id": { + "$ref": "#/definitions/ClientId" + } + }, + "required": [ + "id" + ], + "type": "object" + }, + "PushToken": { + "description": "Native Push Token", + "properties": { + "app": { + "description": "Application", + "type": "string" + }, + "client": { + "$ref": "#/definitions/ClientId" + }, + "token": { + "description": "Access Token", + "type": "string" + }, + "transport": { + "$ref": "#/definitions/Access" + } + }, + "required": [ + "transport", + "app", + "token", + "client" + ], + "type": "object" + }, + "PushTokenList": { + "description": "List of Native Push Tokens", + "properties": { + "tokens": { + "description": "Push tokens", + "items": { + "$ref": "#/definitions/PushToken" + }, + "type": "array" + } + }, + "required": [ + "tokens" + ], + "type": "object" + }, + "QualifiedNewOtrMessage": { + "description": "This object can only be parsed from Protobuf.\nThe specification for the protobuf types is here: \nhttps://github.com/wireapp/generic-message-proto/blob/master/proto/otr.proto." + }, + "QualifiedUserClientPrekeyMap": { + "additionalProperties": { + "$ref": "#/definitions/UserClientPrekeyMap" + }, + "type": "object" + }, + "QualifiedUserClients": { + "additionalProperties": { + "additionalProperties": { + "items": { + "$ref": "#/definitions/ClientId" + }, + "type": "array" + }, + "type": "object" + }, + "description": "Clients that the message /should/ have been encrypted for, but wasn't.", + "example": { + "domain1.example.com": { + "000600d0-000b-9c1a-000d-a4130002c221": [ + "60f85e4b15ad3786", + "6e323ab31554353b" + ] + } + }, + "type": "object" + }, + "QualifiedUserIdList": { + "properties": { + "qualified_user_ids": { + "items": { + "$ref": "#/definitions/Qualified_UserId" + }, + "type": "array" + }, + "user_ids": { + "description": "Deprecated, use qualified_user_ids", + "items": { + "$ref": "#/definitions/UUID" + }, + "type": "array" + } + }, + "required": [ + "qualified_user_ids", + "user_ids" + ], + "type": "object" + }, + "QualifiedUserMap_Set_PubClient": { + "additionalProperties": { + "$ref": "#/definitions/UserMap_Set_PubClient" + }, + "description": "Map of Domain to (UserMap (Set_PubClient)).", + "example": { + "domain1.example.com": { + "000600d0-000b-9c1a-000d-a4130002c221": [ + { + "class": "legalhold", + "id": "d0" + } + ] + } + }, + "type": "object" + }, + "Qualified_ConvId": { + "properties": { + "domain": { + "$ref": "#/definitions/Domain" + }, + "id": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "domain", + "id" + ], + "type": "object" + }, + "Qualified_Handle": { + "properties": { + "domain": { + "$ref": "#/definitions/Domain" + }, + "handle": { + "$ref": "#/definitions/Handle" + } + }, + "required": [ + "domain", + "handle" + ], + "type": "object" + }, + "Qualified_UserId": { + "properties": { + "domain": { + "$ref": "#/definitions/Domain" + }, + "id": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "domain", + "id" + ], + "type": "object" + }, + "QueuedNotification": { + "description": "A single notification", + "properties": { + "id": { + "$ref": "#/definitions/UUID" + }, + "payload": { + "description": "List of events", + "items": { + "$ref": "#/definitions/Object" + }, + "minItems": 1, + "type": "array" + } + }, + "required": [ + "id", + "payload" + ], + "type": "object" + }, + "QueuedNotificationList": { + "description": "Zero or more notifications", + "properties": { + "has_more": { + "description": "Whether there are still more notifications.", + "type": "boolean" + }, + "notifications": { + "description": "Notifications", + "items": { + "$ref": "#/definitions/QueuedNotification" + }, + "type": "array" + }, + "time": { + "$ref": "#/definitions/UTCTime" + } + }, + "required": [ + "notifications" + ], + "type": "object" + }, + "RTCConfiguration": { + "description": "A subset of the WebRTC 'RTCConfiguration' dictionary", + "properties": { + "ice_servers": { + "description": "Array of 'RTCIceServer' objects", + "items": { + "$ref": "#/definitions/RTCIceServer" + }, + "minItems": 1, + "type": "array" + }, + "sft_servers": { + "description": "Array of 'SFTServer' objects (optional)", + "items": { + "$ref": "#/definitions/SftServer" + }, + "minItems": 1, + "type": "array" + }, + "sft_servers_all": { + "description": "Array of all SFT servers", + "items": { + "$ref": "#/definitions/SftServer" + }, + "type": "array" + }, + "ttl": { + "description": "Number of seconds after which the configuration should be refreshed (advisory)", + "format": "int32", + "maximum": 4294967295, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "ice_servers", + "ttl" + ], + "type": "object" + }, + "RTCIceServer": { + "description": "A subset of the WebRTC 'RTCIceServer' object", + "properties": { + "credential": { + "$ref": "#/definitions/ASCII" + }, + "urls": { + "description": "Array of TURN server addresses of the form 'turn::'", + "items": { + "$ref": "#/definitions/TurnURI" + }, + "minItems": 1, + "type": "array" + }, + "username": { + "$ref": "#/definitions/" + } + }, + "required": [ + "urls", + "username", + "credential" + ], + "type": "object" + }, + "Relation": { + "enum": [ + "accepted", + "blocked", + "pending", + "ignored", + "sent", + "cancelled", + "missing-legalhold-consent" + ], + "type": "string" + }, + "RemoveCookies": { + "description": "Data required to remove cookies", + "properties": { + "ids": { + "description": "A list of cookie IDs to revoke", + "items": { + "format": "int32", + "maximum": 4294967295, + "minimum": 0, + "type": "integer" + }, + "type": "array" + }, + "labels": { + "description": "A list of cookie labels for which to revoke the cookies", + "items": { + "type": "string" + }, + "type": "array" + }, + "password": { + "description": "The user's password", + "maxLength": 1024, + "minLength": 6, + "type": "string" + } + }, + "required": [ + "password" + ], + "type": "object" + }, + "RemoveLegalHoldSettingsRequest": { + "properties": { + "password": { + "maxLength": 1024, + "minLength": 6, + "type": "string" + } + }, + "type": "object" + }, + "RichField": { + "properties": { + "type": { + "type": "string" + }, + "value": { + "type": "string" + } + }, + "required": [ + "type", + "value" + ], + "type": "object" + }, + "RichInfoAssocList": { + "properties": { + "fields": { + "items": { + "$ref": "#/definitions/RichField" + }, + "type": "array" + }, + "version": { + "maximum": 9223372036854776000, + "minimum": -9223372036854776000, + "type": "integer" + } + }, + "required": [ + "version", + "fields" + ], + "type": "object" + }, + "Role": { + "description": "Role of the invited user", + "enum": [ + "owner", + "admin", + "member", + "partner" + ], + "type": "string" + }, + "RoleName": { + "description": "Role name, between 2 and 128 chars, 'wire_' prefix is reserved for roles designed by Wire (i.e., no custom roles can have the same prefix)", + "type": "string" + }, + "SSOConfig.WithStatus": { + "properties": { + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus" + ], + "type": "object" + }, + "ScimTokenInfo": { + "properties": { + "created_at": { + "$ref": "#/definitions/UTCTime" + }, + "description": { + "type": "string" + }, + "id": { + "$ref": "#/definitions/UUID" + }, + "idp": { + "$ref": "#/definitions/UUID" + }, + "team": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "team", + "id", + "created_at", + "description" + ], + "type": "object" + }, + "ScimTokenList": { + "properties": { + "tokens": { + "items": { + "$ref": "#/definitions/ScimTokenInfo" + }, + "type": "array" + } + }, + "required": [ + "tokens" + ], + "type": "object" + }, + "SearchResult": { + "properties": { + "documents": { + "description": "List of contacts found", + "items": { + "$ref": "#/definitions/TeamContact" + }, + "type": "array" + }, + "found": { + "description": "Total number of hits", + "maximum": 9223372036854776000, + "minimum": -9223372036854776000, + "type": "integer" + }, + "has_more": { + "description": "Indicates whether there are more results to be fetched", + "type": "boolean" + }, + "paging_state": { + "$ref": "#/definitions/PagingState" + }, + "returned": { + "description": "Total number of hits returned", + "maximum": 9223372036854776000, + "minimum": -9223372036854776000, + "type": "integer" + }, + "search_policy": { + "$ref": "#/definitions/FederatedUserSearchPolicy" + }, + "took": { + "description": "Search time in ms", + "maximum": 9223372036854776000, + "minimum": -9223372036854776000, + "type": "integer" + } + }, + "required": [ + "found", + "returned", + "took", + "documents", + "search_policy" + ], + "type": "object" + }, + "SearchVisibilityAvailableConfig.WithStatus": { + "properties": { + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus" + ], + "type": "object" + }, + "SearchVisibilityAvailableConfig.WithStatusNoLock": { + "properties": { + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status" + ], + "type": "object" + }, + "SearchVisibilityInboundConfig.WithStatus": { + "properties": { + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus" + ], + "type": "object" + }, + "SearchVisibilityInboundConfig.WithStatusNoLock": { + "properties": { + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status" + ], + "type": "object" + }, + "SelfDeletingMessagesConfig": { + "properties": { + "enforcedTimeoutSeconds": { + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + } + }, + "required": [ + "enforcedTimeoutSeconds" + ], + "type": "object" + }, + "SelfDeletingMessagesConfig.WithStatus": { + "properties": { + "config": { + "$ref": "#/definitions/SelfDeletingMessagesConfig" + }, + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus", + "config" + ], + "type": "object" + }, + "SelfDeletingMessagesConfig.WithStatusNoLock": { + "properties": { + "config": { + "$ref": "#/definitions/SelfDeletingMessagesConfig" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "config" + ], + "type": "object" + }, + "SendActivationCode": { + "description": "Data for requesting an email or phone activation code to be sent. One of 'email' or 'phone' must be present.", + "properties": { + "email": { + "$ref": "#/definitions/Email" + }, + "locale": { + "$ref": "#/definitions/Locale" + }, + "phone": { + "$ref": "#/definitions/PhoneNumber" + }, + "voice_call": { + "description": "Request the code with a call instead (default is SMS).", + "type": "boolean" + } + }, + "type": "object" + }, + "SendLoginCode": { + "description": "Payload for requesting a login code to be sent", + "properties": { + "force": { + "type": "boolean" + }, + "phone": { + "description": "E.164 phone number to send the code to", + "type": "string" + }, + "voice_call": { + "description": "Request the code with a call instead (default is SMS)", + "type": "boolean" + } + }, + "required": [ + "phone" + ], + "type": "object" + }, + "SendVerificationCode": { + "properties": { + "action": { + "$ref": "#/definitions/VerificationAction" + }, + "email": { + "$ref": "#/definitions/Email" + } + }, + "required": [ + "action", + "email" + ], + "type": "object" + }, + "ServiceKeyPEM": { + "example": "-----BEGIN PUBLIC KEY-----\nMIIBIjANBgkqhkiG9w0BAQEFAAOCAQ8AMIIBCgKCAQEAu+Kg/PHHU3atXrUbKnw0\nG06FliXcNt3lMwl2os5twEDcPPFw/feGiAKymxp+7JqZDrseS5D9THGrW+OQRIPH\nWvUBdiLfGrZqJO223DB6D8K2Su/odmnjZJ2z23rhXoEArTplu+Dg9K+c2LVeXTKV\nVPOaOzgtAB21XKRiQ4ermqgi3/njr03rXyq/qNkuNd6tNcg+HAfGxfGvvCSYBfiS\nbUKr/BeArYRcjzr/h5m1In6fG/if9GEI6m8dxHT9JbY53wiksowy6ajCuqskIFg8\n7X883H+LA/d6X5CTiPv1VMxXdBUiGPuC9IT/6CNQ1/LFt0P37ax58+LGYlaFo7la\nnQIDAQAB\n-----END PUBLIC KEY-----\n", + "type": "string" + }, + "ServiceRef": { + "properties": { + "id": { + "$ref": "#/definitions/UUID" + }, + "provider": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "id", + "provider" + ], + "type": "object" + }, + "SftServer": { + "description": "Inspired by WebRTC 'RTCIceServer' object, contains details of SFT servers", + "properties": { + "urls": { + "description": "Array containing exactly one SFT server address of the form 'https://:'", + "items": { + "$ref": "#/definitions/HttpsUrl" + }, + "type": "array" + } + }, + "required": [ + "urls" + ], + "type": "object" + }, + "SimpleMember": { + "properties": { + "conversation_role": { + "$ref": "#/definitions/RoleName" + }, + "id": { + "$ref": "#/definitions/UUID" + }, + "qualified_id": { + "$ref": "#/definitions/Qualified_UserId" + } + }, + "required": [ + "qualified_id" + ], + "type": "object" + }, + "SimpleMembers": { + "properties": { + "user_ids": { + "description": "deprecated", + "items": { + "$ref": "#/definitions/UUID" + }, + "type": "array" + }, + "users": { + "items": { + "$ref": "#/definitions/SimpleMember" + }, + "type": "array" + } + }, + "required": [ + "users" + ], + "type": "object" + }, + "SndFactorPasswordChallengeConfig.WithStatus": { + "properties": { + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus" + ], + "type": "object" + }, + "SndFactorPasswordChallengeConfig.WithStatusNoLock": { + "properties": { + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status" + ], + "type": "object" + }, + "Sso": { + "properties": { + "issuer": { + "type": "string" + }, + "nameid": { + "type": "string" + } + }, + "required": [ + "issuer", + "nameid" + ], + "type": "object" + }, + "SsoSettings": { + "properties": { + "default_sso_code": { + "$ref": "#/definitions/UUID" + } + }, + "type": "object" + }, + "SystemSettings": { + "properties": { + "setEnableMls": { + "description": "Whether MLS is enabled or not", + "type": "boolean" + }, + "setRestrictUserCreation": { + "description": "Do not allow certain user creation flows", + "type": "boolean" + } + }, + "required": [ + "setRestrictUserCreation", + "setEnableMls" + ], + "type": "object" + }, + "SystemSettingsPublic": { + "properties": { + "setRestrictUserCreation": { + "description": "Do not allow certain user creation flows", + "type": "boolean" + } + }, + "required": [ + "setRestrictUserCreation" + ], + "type": "object" + }, + "Team": { + "properties": { + "binding": { + "$ref": "#/definitions/TeamBinding" + }, + "creator": { + "$ref": "#/definitions/UUID" + }, + "icon": { + "$ref": "#/definitions/Icon" + }, + "icon_key": { + "type": "string" + }, + "id": { + "$ref": "#/definitions/UUID" + }, + "name": { + "type": "string" + }, + "splash_screen": { + "$ref": "#/definitions/Icon" + } + }, + "required": [ + "id", + "creator", + "name", + "icon" + ], + "type": "object" + }, + "TeamBinding": { + "enum": [ + true, + false + ], + "type": "boolean" + }, + "TeamContact": { + "properties": { + "accent_id": { + "maximum": 9223372036854776000, + "minimum": -9223372036854776000, + "type": "integer" + }, + "created_at": { + "$ref": "#/definitions/UTCTime" + }, + "email": { + "$ref": "#/definitions/Email" + }, + "email_unvalidated": { + "$ref": "#/definitions/Email" + }, + "handle": { + "type": "string" + }, + "id": { + "$ref": "#/definitions/UUID" + }, + "managed_by": { + "$ref": "#/definitions/ManagedBy" + }, + "name": { + "type": "string" + }, + "role": { + "$ref": "#/definitions/Role" + }, + "saml_idp": { + "type": "string" + }, + "scim_external_id": { + "type": "string" + }, + "sso": { + "$ref": "#/definitions/Sso" + }, + "team": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "id", + "name" + ], + "type": "object" + }, + "TeamConversation": { + "description": "Team conversation data", + "properties": { + "conversation": { + "$ref": "#/definitions/UUID" + }, + "managed": { + "description": "This field MUST NOT be used by clients. It is here only for backwards compatibility of the interface." + } + }, + "required": [ + "conversation", + "managed" + ], + "type": "object" + }, + "TeamConversationList": { + "description": "Team conversation list", + "properties": { + "conversations": { + "items": { + "$ref": "#/definitions/TeamConversation" + }, + "type": "array" + } + }, + "required": [ + "conversations" + ], + "type": "object" + }, + "TeamDeleteData": { + "properties": { + "password": { + "maxLength": 1024, + "minLength": 6, + "type": "string" + }, + "verification_code": { + "$ref": "#/definitions/ASCII" + } + }, + "type": "object" + }, + "TeamList": { + "properties": { + "has_more": { + "type": "boolean" + }, + "teams": { + "items": { + "$ref": "#/definitions/Team" + }, + "type": "array" + } + }, + "required": [ + "teams", + "has_more" + ], + "type": "object" + }, + "TeamMember": { + "description": "team member data", + "properties": { + "created_at": { + "$ref": "#/definitions/UTCTime" + }, + "created_by": { + "$ref": "#/definitions/UUID" + }, + "legalhold_status": { + "$ref": "#/definitions/UserLegalHoldStatus" + }, + "permissions": { + "$ref": "#/definitions/Permissions" + }, + "user": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "user" + ], + "type": "object" + }, + "TeamMemberDeleteData": { + "description": "Data for a team member deletion request in case of binding teams.", + "properties": { + "password": { + "description": "The account password to authorise the deletion.", + "maxLength": 1024, + "minLength": 6, + "type": "string" + } + }, + "type": "object" + }, + "TeamMemberList": { + "description": "list of team member", + "properties": { + "hasMore": { + "$ref": "#/definitions/ListType" + }, + "members": { + "description": "the array of team members", + "items": { + "$ref": "#/definitions/TeamMember" + }, + "type": "array" + } + }, + "required": [ + "members", + "hasMore" + ], + "type": "object" + }, + "TeamMembersPage": { + "properties": { + "hasMore": { + "type": "boolean" + }, + "members": { + "items": { + "$ref": "#/definitions/TeamMember" + }, + "type": "array" + }, + "pagingState": { + "$ref": "#/definitions/TeamMembers_PagingState" + } + }, + "required": [ + "members", + "hasMore", + "pagingState" + ], + "type": "object" + }, + "TeamMembers_PagingState": { + "type": "string" + }, + "TeamSearchVisibility": { + "description": "value of visibility", + "enum": [ + "standard", + "no-name-outside-team" + ], + "type": "string" + }, + "TeamSearchVisibilityView": { + "description": "Search visibility value for the team", + "properties": { + "search_visibility": { + "$ref": "#/definitions/TeamSearchVisibility" + } + }, + "required": [ + "search_visibility" + ], + "type": "object" + }, + "TeamSize": { + "description": "A simple object with a total number of team members.", + "properties": { + "teamSize": { + "description": "Team size.", + "exclusiveMinimum": false, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "teamSize" + ], + "type": "object" + }, + "TeamUpdateData": { + "properties": { + "icon": { + "$ref": "#/definitions/Icon" + }, + "icon_key": { + "maxLength": 256, + "minLength": 1, + "type": "string" + }, + "name": { + "maxLength": 256, + "minLength": 1, + "type": "string" + }, + "splash_screen": { + "$ref": "#/definitions/Icon" + } + }, + "type": "object" + }, + "Time": { + "properties": { + "time": { + "$ref": "#/definitions/UTCTime" + } + }, + "required": [ + "time" + ], + "type": "object" + }, + "TokenType": { + "enum": [ + "Bearer" + ], + "type": "string" + }, + "TurnURI": { + "type": "string" + }, + "TypingData": { + "properties": { + "status": { + "$ref": "#/definitions/TypingStatus" + } + }, + "required": [ + "status" + ], + "type": "object" + }, + "TypingStatus": { + "enum": [ + "started", + "stopped" + ], + "type": "string" + }, + "URIRef Absolute": { + "description": "URL of the invitation link to be sent to the invitee", + "type": "string" + }, + "UTCTime": { + "example": "2021-05-12T10:52:02.671Z", + "format": "yyyy-mm-ddThh:MM:ss.qqq", + "type": "string" + }, + "UUID": { + "example": "99db9768-04e3-4b5d-9268-831b6a25c4ab", + "format": "uuid", + "type": "string" + }, + "Unnamed": { + "properties": { + "created_at": { + "$ref": "#/definitions/UTCTime" + }, + "created_by": { + "$ref": "#/definitions/UUID" + }, + "permissions": { + "$ref": "#/definitions/Permissions" + }, + "user": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "user", + "permissions" + ], + "type": "object" + }, + "UpdateClient": { + "properties": { + "capabilities": { + "description": "Hints provided by the client for the backend so it can behave in a backwards-compatible way.", + "items": { + "$ref": "#/definitions/ClientCapability" + }, + "type": "array" + }, + "label": { + "description": "A new name for this client.", + "type": "string" + }, + "lastkey": { + "$ref": "#/definitions/Prekey" + }, + "mls_public_keys": { + "$ref": "#/definitions/MLSPublicKeys" + }, + "prekeys": { + "description": "New prekeys for other clients to establish OTR sessions.", + "items": { + "$ref": "#/definitions/Prekey" + }, + "type": "array" + } + }, + "type": "object" + }, + "User": { + "properties": { + "accent_id": { + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + }, + "assets": { + "items": { + "$ref": "#/definitions/UserAsset" + }, + "type": "array" + }, + "deleted": { + "type": "boolean" + }, + "email": { + "$ref": "#/definitions/Email" + }, + "expires_at": { + "$ref": "#/definitions/UTCTime" + }, + "handle": { + "$ref": "#/definitions/Handle" + }, + "id": { + "$ref": "#/definitions/UUID" + }, + "locale": { + "$ref": "#/definitions/Locale" + }, + "managed_by": { + "$ref": "#/definitions/ManagedBy" + }, + "name": { + "maxLength": 128, + "minLength": 1, + "type": "string" + }, + "phone": { + "$ref": "#/definitions/PhoneNumber" + }, + "picture": { + "$ref": "#/definitions/Pict" + }, + "qualified_id": { + "$ref": "#/definitions/Qualified_UserId" + }, + "service": { + "$ref": "#/definitions/ServiceRef" + }, + "sso_id": { + "$ref": "#/definitions/UserSSOId" + }, + "team": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "id", + "qualified_id", + "name", + "accent_id", + "locale" + ], + "type": "object" + }, + "UserAsset": { + "properties": { + "key": { + "$ref": "#/definitions/AssetKey" + }, + "size": { + "$ref": "#/definitions/AssetSize" + }, + "type": { + "$ref": "#/definitions/AssetType" + } + }, + "required": [ + "key", + "type" + ], + "type": "object" + }, + "UserClientMap": { + "additionalProperties": { + "additionalProperties": { + "type": "string" + }, + "type": "object" + }, + "type": "object" + }, + "UserClientPrekeyMap": { + "additionalProperties": { + "additionalProperties": { + "properties": { + "id": { + "maximum": 65535, + "minimum": 0, + "type": "integer" + }, + "key": { + "type": "string" + } + }, + "required": [ + "id", + "key" + ], + "type": "object" + }, + "type": "object" + }, + "example": { + "000600d0-000b-9c1a-000d-a4130002c221": { + "44901fb0712e588f": { + "id": 1, + "key": "pQABAQECoQBYIOjl7hw0D8YRNq..." + } + } + }, + "type": "object" + }, + "UserClients": { + "additionalProperties": { + "items": { + "$ref": "#/definitions/ClientId" + }, + "type": "array" + }, + "description": "Map of user id to list of client ids.", + "example": { + "000600d0-000b-9c1a-000d-a4130002c221": [ + "60f85e4b15ad3786", + "6e323ab31554353b" + ] + }, + "type": "object" + }, + "UserConnection": { + "properties": { + "conversation": { + "$ref": "#/definitions/UUID" + }, + "from": { + "$ref": "#/definitions/UUID" + }, + "last_update": { + "$ref": "#/definitions/UTCTime" + }, + "qualified_conversation": { + "$ref": "#/definitions/Qualified_ConvId" + }, + "qualified_to": { + "$ref": "#/definitions/Qualified_UserId" + }, + "status": { + "$ref": "#/definitions/Relation" + }, + "to": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "from", + "qualified_to", + "status", + "last_update" + ], + "type": "object" + }, + "UserIdList": { + "properties": { + "user_ids": { + "items": { + "$ref": "#/definitions/UUID" + }, + "type": "array" + } + }, + "required": [ + "user_ids" + ], + "type": "object" + }, + "UserLegalHoldStatus": { + "description": "The state of Legal Hold compliance for the member", + "enum": [ + "enabled", + "pending", + "disabled", + "no_consent" + ], + "type": "string" + }, + "UserLegalHoldStatusResponse": { + "properties": { + "client": { + "$ref": "#/definitions/Id" + }, + "last_prekey": { + "$ref": "#/definitions/Prekey" + }, + "status": { + "$ref": "#/definitions/UserLegalHoldStatus" + } + }, + "required": [ + "status" + ], + "type": "object" + }, + "UserMap_Set_PubClient": { + "additionalProperties": { + "items": { + "$ref": "#/definitions/PubClient" + }, + "type": "array", + "uniqueItems": true + }, + "description": "Map of UserId to (Set PubClient)", + "example": { + "000600d0-000b-9c1a-000d-a4130002c221": [ + { + "class": "legalhold", + "id": "d0" + } + ] + }, + "type": "object" + }, + "UserProfile": { + "properties": { + "accent_id": { + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + }, + "assets": { + "items": { + "$ref": "#/definitions/UserAsset" + }, + "type": "array" + }, + "deleted": { + "type": "boolean" + }, + "email": { + "$ref": "#/definitions/Email" + }, + "expires_at": { + "$ref": "#/definitions/UTCTime" + }, + "handle": { + "$ref": "#/definitions/Handle" + }, + "id": { + "$ref": "#/definitions/UUID" + }, + "legalhold_status": { + "$ref": "#/definitions/UserLegalHoldStatus" + }, + "name": { + "maxLength": 128, + "minLength": 1, + "type": "string" + }, + "picture": { + "$ref": "#/definitions/Pict" + }, + "qualified_id": { + "$ref": "#/definitions/Qualified_UserId" + }, + "service": { + "$ref": "#/definitions/ServiceRef" + }, + "team": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "qualified_id", + "name", + "accent_id", + "legalhold_status" + ], + "type": "object" + }, + "UserSSOId": { + "properties": { + "scim_external_id": { + "type": "string" + }, + "subject": { + "type": "string" + }, + "tenant": { + "type": "string" + } + }, + "type": "object" + }, + "UserUpdate": { + "properties": { + "accent_id": { + "format": "int32", + "maximum": 2147483647, + "minimum": -2147483648, + "type": "integer" + }, + "assets": { + "items": { + "$ref": "#/definitions/UserAsset" + }, + "type": "array" + }, + "name": { + "maxLength": 128, + "minLength": 1, + "type": "string" + }, + "picture": { + "$ref": "#/definitions/Pict" + } + }, + "type": "object" + }, + "ValidateSAMLEmailsConfig.WithStatus": { + "properties": { + "lockStatus": { + "$ref": "#/definitions/LockStatus" + }, + "status": { + "$ref": "#/definitions/FeatureStatus" + }, + "ttl": { + "example": "unlimited", + "maximum": 18446744073709552000, + "minimum": 0, + "type": "integer" + } + }, + "required": [ + "status", + "lockStatus" + ], + "type": "object" + }, + "VerificationAction": { + "enum": [ + "create_scim_token", + "login", + "delete_team" + ], + "type": "string" + }, + "VerifyDeleteUser": { + "description": "Data for verifying an account deletion.", + "properties": { + "code": { + "$ref": "#/definitions/ASCII" + }, + "key": { + "$ref": "#/definitions/ASCII" + } + }, + "required": [ + "key", + "code" + ], + "type": "object" + }, + "Version": { + "enum": [ + 0, + 1, + 2, + 3 + ], + "type": "integer" + }, + "VersionInfo": { + "example": { + "development": [ + 3 + ], + "domain": "example.com", + "federation": false, + "supported": [ + 0, + 1, + 2, + 3 + ] + }, + "properties": { + "development": { + "items": { + "$ref": "#/definitions/Version" + }, + "type": "array" + }, + "domain": { + "$ref": "#/definitions/Domain" + }, + "federation": { + "type": "boolean" + }, + "supported": { + "items": { + "$ref": "#/definitions/Version" + }, + "type": "array" + } + }, + "required": [ + "supported", + "development", + "federation", + "domain" + ], + "type": "object" + }, + "ViewLegalHoldService": { + "properties": { + "settings": { + "$ref": "#/definitions/ViewLegalHoldServiceInfo" + }, + "status": { + "$ref": "#/definitions/LHServiceStatus" + } + }, + "required": [ + "status" + ], + "type": "object" + }, + "ViewLegalHoldServiceInfo": { + "properties": { + "auth_token": { + "$ref": "#/definitions/ASCII" + }, + "base_url": { + "$ref": "#/definitions/HttpsUrl" + }, + "fingerprint": { + "$ref": "#/definitions/Fingerprint" + }, + "public_key": { + "$ref": "#/definitions/ServiceKeyPEM" + }, + "team_id": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "team_id", + "base_url", + "fingerprint", + "auth_token", + "public_key" + ], + "type": "object" + }, + "Welcome": { + "description": "This object can only be parsed in TLS format. Please refer to the MLS specification for details." + }, + "WireIdP": { + "properties": { + "apiVersion": { + "$ref": "#/definitions/WireIdPAPIVersion" + }, + "handle": { + "type": "string" + }, + "oldIssuers": { + "items": { + "type": "string" + }, + "type": "array" + }, + "replacedBy": { + "$ref": "#/definitions/UUID" + }, + "team": { + "$ref": "#/definitions/UUID" + } + }, + "required": [ + "team", + "oldIssuers", + "handle" + ], + "type": "object" + }, + "WireIdPAPIVersion": { + "enum": [ + "WireIdPAPIV1", + "WireIdPAPIV2" + ], + "type": "string" + }, + "XmlText": { + "properties": { + "fromXmlText": { + "type": "string" + } + }, + "required": [ + "fromXmlText" + ], + "type": "object" + }, + "new-otr-message": { + "properties": { + "data": { + "type": "string" + }, + "native_priority": { + "$ref": "#/definitions/Priority" + }, + "native_push": { + "type": "boolean" + }, + "recipients": { + "$ref": "#/definitions/UserClientMap" + }, + "report_missing": { + "items": { + "$ref": "#/definitions/UUID" + }, + "type": "array" + }, + "sender": { + "$ref": "#/definitions/ClientId" + }, + "transient": { + "type": "boolean" + } + }, + "required": [ + "sender", + "recipients" + ], + "type": "object" + } + }, + "info": { + "description": "## General\n\n### SSO Endpoints\n\n#### Overview\n\n`/sso/metadata` will be requested by the IdPs to learn how to talk to wire.\n\n`/sso/initiate-login`, `/sso/finalize-login` are for the SAML authentication handshake performed by a user in order to log into wire. They are not exactly standard in their details: they may return HTML or XML; redirect to error URLs instead of throwing errors, etc.\n\n`/identity-providers` end-points are for use in the team settings page when IdPs are registered. They talk json.\n\n\n#### Configuring IdPs\n\nIdPs usually allow you to copy the metadata into your clipboard. That should contain all the details you need to post the idp in your team under `/identity-providers`. (Team id is derived from the authorization credentials of the request.)\n\n##### okta.com\n\nOkta will ask you to provide two URLs when you set it up for talking to wireapp:\n\n1. The `Single sign on URL`. This is the end-point that accepts the user's credentials after successful authentication against the IdP. Choose `/sso/finalize-login` with schema and hostname of the wire server you are configuring.\n\n2. The `Audience URI`. You can find this in the metadata returned by the `/sso/metadata` end-point. It is the contents of the `md:OrganizationURL` element.\n\n##### centrify.com\n\nCentrify allows you to upload the metadata xml document that you get from the `/sso/metadata` end-point. You can also enter the metadata url and have centrify retrieve the xml, but to guarantee integrity of the setup, the metadata should be copied from the team settings page and pasted into the centrify setup page without any URL indirections.\n\n## Federation errors\n\nEndpoints involving federated calls to other domains can return some extra failure responses, common to all endpoints. Instead of listing them as possible responses for each endpoint, we document them here.\n\nFor errors that are more likely to be transient, we suggest clients to retry whatever request resulted in the error. Transient errors are indicated explicitly below.\n\n**Note**: when a failure occurs as a result of making a federated RPC to another backend, the error response contains the following extra fields:\n\n - `type`: \"federation\" (just the literal string in quotes, which can be used as an error type identifier when parsing errors)\n - `domain`: the target backend of the RPC that failed;\n - `path`: the path of the RPC that failed.\n\n### Domain errors\n\nErrors in this category result from trying to communicate with a backend that is considered non-existent or invalid. They can result from invalid user input or client issues, but they can also be a symptom of misconfiguration in one or multiple backends. These errors have a 4xx status code.\n\n - **Remote backend not found** (status: 422, label: `invalid-domain`): This backend attempted to contact a backend which does not exist or is not properly configured. For the most part, clients can consider this error equivalent to a domain not existing, although it should be noted that certain mistakes in the DNS configuration on a remote backend can lead to the backend not being recognized, and hence to this error. It is therefore not advisable to take any destructive action upon encountering this error, such as deleting remote users from conversations.\n - **Federation denied locally** (status: 400, label: `federation-denied`): This backend attempted an RPC to a non-whitelisted backend. Similar considerations as for the previous error apply.\n - **Federation not enabled** (status: 400, label: `federation-not-enabled`): Federation has not been configured for this backend. This will happen if a federation-aware client tries to talk to a backend for which federation is disabled, or if federation was disabled on the backend after reaching a federation-specific state (e.g. conversations with remote users). There is no way to cleanly recover from these errors at this point.\n\n### Local federation errors\n\nAn error in this category likely indicates an issue with the configuration of federation on the local backend. Possibly transient errors are indicated explicitly below. All these errors have a 500 status code.\n\n - **Federation unavailable** (status: 500, label: `federation-not-available`): Federation is configured for this backend, but the local federator cannot be reached. This can be transient, so clients should retry the request.\n - **Federation not implemented** (status: 500, label: `federation-not-implemented`): Federated behaviour for a certain endpoint is not yet implemented.\n - **Federator discovery failed** (status: 400, label: `discovery-failure`): A DNS error occurred during discovery of a remote backend. This can be transient, so clients should retry the request.\n - **Local federation error** (status: 500, label: `federation-local-error`): An error occurred in the communication between this backend and its local federator. These errors are most likely caused by bugs in the backend, and should be reported as such.\n\n### Remote federation errors\n\nErrors in this category are returned in case of communication issues between the local backend and a remote one, or if the remote side encountered an error while processing an RPC. Some errors in this category might be caused by incorrect client behaviour, wrong user input, or incorrect certificate configuration. Possibly transient errors are indicated explicitly. We use non-standard 5xx status codes for these errors.\n\n - **HTTP2 error** (status: 533, label: `federation-http2-error`): The current federator encountered an error when making an HTTP2 request to a remote one. Check the error message for more details.\n - **Connection refused** (status: 521, label: `federation-connection-refused`): The local federator could not connect to a remote one. This could be transient, so clients should retry the request.\n - **TLS failure**: (status: 525, label: `federation-tls-error`): An error occurred during the TLS handshake between the local federator and a remote one. This is most likely due to an issue with the certificate on the remote end.\n - **Remote federation error** (status: 533, label: `federation-remote-error`): The remote backend could not process a request coming from this backend. Check the error message for more details.\n - **Version negotiation error** (status: 533, label: `federation-version-error`): The remote backend returned invalid version information.\n\n### Backend compatibility errors\n\nAn error in this category will be returned when this backend makes an invalid or unsupported RPC to another backend. This can indicate some incompatibility between backends or a backend bug. These errors are unlikely to be transient, so retrying requests is *not* advised.\n\n - **Version mismatch** (status: 531, label: `federation-version-mismatch`): A remote backend is running an unsupported version of the federator.\n - **Invalid content type** (status: 533, label: `federation-invalid-content-type`): An RPC to another backend returned with an invalid content type.\n - **Unsupported content type** (status: 533, label: `federation-unsupported-content-type`): An RPC to another backend returned with an unsupported content type.\n", + "title": "Wire-Server API", + "version": "" + }, + "paths": { + "/access": { + "post": { + "description": "You can provide only a cookie or a cookie and token. Every other combination is invalid. Access tokens can be given as query parameter or authorisation header, with the latter being preferred.", + "parameters": [ + { + "in": "query", + "name": "client_id", + "required": false, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "OK", + "headers": { + "Set-Cookie": { + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/AccessToken" + } + }, + "400": { + "description": "Invalid `client_id`" + }, + "403": { + "description": "Authentication failed (label: `invalid-credentials`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-credentials", + "message": "Authentication failed" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-credentials" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Obtain an access tokens for a cookie", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "on-user-deleted-connections" + ] + ] + } + }, + "/access/logout": { + "post": { + "description": "Calling this endpoint will effectively revoke the given cookie and subsequent calls to /access with the same cookie will result in a 403.", + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Logout" + }, + "403": { + "description": "Authentication failed (label: `invalid-credentials`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-credentials", + "message": "Authentication failed" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-credentials" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Log out in order to remove a cookie from the server" + } + }, + "/access/self/email": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/EmailUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "202": { + "description": "Update accepted and pending activation of the new email", + "schema": { + "example": [], + "items": {}, + "maxItems": 0, + "type": "array" + } + }, + "204": { + "description": "No update, current and new email address are the same", + "schema": { + "example": [], + "items": {}, + "maxItems": 0, + "type": "array" + } + }, + "400": { + "description": "Invalid e-mail address. (label: `invalid-email`) or `body`", + "schema": { + "example": { + "code": 400, + "label": "invalid-email", + "message": "Invalid e-mail address." + }, + "properties": { + "code": { + "enum": [ + 400 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-email" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "403": { + "description": "Authentication failed (label: `invalid-credentials`)\n\nThe given phone number has been blacklisted due to suspected abuse or a complaint (label: `blacklisted-phone`)\n\nThe given e-mail address has been blacklisted due to a permanent bounce or a complaint. (label: `blacklisted-email`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-credentials", + "message": "Authentication failed" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-credentials", + "blacklisted-phone", + "blacklisted-email" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "The given e-mail address or phone number is in use. (label: `key-exists`)", + "schema": { + "example": { + "code": 409, + "label": "key-exists", + "message": "The given e-mail address or phone number is in use." + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "key-exists" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Change your email address" + } + }, + "/activate": { + "get": { + "description": "See also 'POST /activate' which has a larger feature set.", + "parameters": [ + { + "description": "Activation key", + "in": "query", + "name": "key", + "required": true, + "type": "string" + }, + { + "description": "Activation code", + "in": "query", + "name": "code", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Activation successful.\n\nActivation successful. (Dry run)\n\nActivation successful.", + "schema": { + "$ref": "#/definitions/ActivationResponse" + } + }, + "204": { + "description": "A recent activation was already successful." + }, + "400": { + "description": "Invalid `code` or `key`\n\nInvalid mobile phone number (label: `invalid-phone`)\n\nInvalid e-mail address. (label: `invalid-email`)" + }, + "404": { + "description": "Invalid activation code (label: `invalid-code`)\n\nUser does not exist (label: `invalid-code`)", + "schema": { + "example": { + "code": 404, + "label": "invalid-code", + "message": "Invalid activation code" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-code" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "The given e-mail address or phone number is in use. (label: `key-exists`)", + "schema": { + "example": { + "code": 409, + "label": "key-exists", + "message": "The given e-mail address or phone number is in use." + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "key-exists" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Activate (i.e. confirm) an email address or phone number.", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "on-user-deleted-connections" + ] + ] + }, + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "Activation only succeeds once and the number of failed attempts for a valid key is limited.", + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/Activate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Activation successful.\n\nActivation successful. (Dry run)\n\nActivation successful.", + "schema": { + "$ref": "#/definitions/ActivationResponse" + } + }, + "204": { + "description": "A recent activation was already successful." + }, + "400": { + "description": "Invalid `body`\n\nInvalid mobile phone number (label: `invalid-phone`)\n\nInvalid e-mail address. (label: `invalid-email`)" + }, + "404": { + "description": "Invalid activation code (label: `invalid-code`)\n\nUser does not exist (label: `invalid-code`)", + "schema": { + "example": { + "code": 404, + "label": "invalid-code", + "message": "Invalid activation code" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-code" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "The given e-mail address or phone number is in use. (label: `key-exists`)", + "schema": { + "example": { + "code": 409, + "label": "key-exists", + "message": "The given e-mail address or phone number is in use." + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "key-exists" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Activate (i.e. confirm) an email address or phone number.", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "on-user-deleted-connections" + ] + ] + } + }, + "/activate/send": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/SendActivationCode" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Activation code sent." + }, + "400": { + "description": "Invalid `body`\n\nInvalid mobile phone number (label: `invalid-phone`)\n\nInvalid e-mail address. (label: `invalid-email`)" + }, + "403": { + "description": "The given phone number has been blacklisted due to suspected abuse or a complaint (label: `blacklisted-phone`)\n\nThe given e-mail address has been blacklisted due to a permanent bounce or a complaint. (label: `blacklisted-email`)", + "schema": { + "example": { + "code": 403, + "label": "blacklisted-phone", + "message": "The given phone number has been blacklisted due to suspected abuse or a complaint" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "blacklisted-phone", + "blacklisted-email" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "The given e-mail address or phone number is in use. (label: `key-exists`)", + "schema": { + "example": { + "code": 409, + "label": "key-exists", + "message": "The given e-mail address or phone number is in use." + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "key-exists" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "451": { + "description": "[Customer extension] the email domain example.com that you are attempting to register a user with has been blocked for creating wire users. Please contact your IT department. (label: `domain-blocked-for-registration`)", + "schema": { + "example": { + "code": 451, + "label": "domain-blocked-for-registration", + "message": "[Customer extension] the email domain example.com that you are attempting to register a user with has been blocked for creating wire users. Please contact your IT department." + }, + "properties": { + "code": { + "enum": [ + 451 + ], + "type": "integer" + }, + "label": { + "enum": [ + "domain-blocked-for-registration" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Send (or resend) an email or phone activation code." + } + }, + "/api-version": { + "get": { + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/VersionInfo" + } + } + } + } + }, + "/assets": { + "post": { + "consumes": [ + "multipart/mixed" + ], + "parameters": [ + { + "description": "A body with content type `multipart/mixed body`. The first section's content type should be `application/json`. The second section's content type should be always be `application/octet-stream`. Other content types will be ignored by the server.", + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/AssetSource" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Asset posted", + "headers": { + "Location": { + "description": "Asset location", + "format": "url", + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/Asset" + } + }, + "400": { + "description": "Invalid `body`\n\nInvalid content length (label: `invalid-length`)" + }, + "413": { + "description": "Asset too large (label: `client-error`)", + "schema": { + "example": { + "code": 413, + "label": "client-error", + "message": "Asset too large" + }, + "properties": { + "code": { + "enum": [ + 413 + ], + "type": "integer" + }, + "label": { + "enum": [ + "client-error" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Upload an asset" + } + }, + "/assets/{key_domain}/{key}": { + "delete": { + "description": "**Note**: only local assets can be deleted.", + "parameters": [ + { + "in": "path", + "name": "key_domain", + "required": true, + "type": "string" + }, + { + "in": "path", + "name": "key", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Asset deleted" + }, + "400": { + "description": "Invalid `key` or `key_domain`" + }, + "403": { + "description": "Unauthorised operation (label: `unauthorised`)", + "schema": { + "example": { + "code": 403, + "label": "unauthorised", + "message": "Unauthorised operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "unauthorised" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Asset not found (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "Asset not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Delete an asset" + }, + "get": { + "description": "**Note**: local assets result in a redirect, while remote assets are streamed directly.", + "parameters": [ + { + "in": "path", + "name": "key_domain", + "required": true, + "type": "string" + }, + { + "in": "path", + "name": "key", + "required": true, + "type": "string" + }, + { + "in": "header", + "name": "Asset-Token", + "required": false, + "type": "string" + }, + { + "in": "query", + "name": "asset_token", + "required": false, + "type": "string" + } + ], + "responses": { + "200": { + "description": "Asset returned directly with content type `application/octet-stream`" + }, + "302": { + "description": "Asset found", + "headers": { + "Location": { + "description": "Asset location", + "format": "url", + "type": "string" + } + } + }, + "400": { + "description": "Invalid `asset_token` or `Asset-Token` or `key` or `key_domain`" + }, + "404": { + "description": "Asset not found (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "Asset not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Download an asset", + "x-wire-makes-federated-call-to": [ + [ + "cargohold", + "get-asset" + ], + [ + "cargohold", + "stream-asset" + ] + ] + } + }, + "/assets/{key}/token": { + "delete": { + "description": "**Note**: deleting the token makes the asset public.", + "parameters": [ + { + "in": "path", + "name": "key", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Asset token deleted" + }, + "400": { + "description": "Invalid `key`" + } + }, + "summary": "Delete an asset token" + }, + "post": { + "parameters": [ + { + "in": "path", + "name": "key", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/NewAssetToken" + } + }, + "400": { + "description": "Invalid `key`" + }, + "403": { + "description": "Unauthorised operation (label: `unauthorised`)", + "schema": { + "example": { + "code": 403, + "label": "unauthorised", + "message": "Unauthorised operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "unauthorised" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Asset not found (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "Asset not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Renew an asset token" + } + }, + "/await": { + "get": { + "externalDocs": { + "description": "RFC 6455", + "url": "https://datatracker.ietf.org/doc/html/rfc6455" + }, + "parameters": [ + { + "description": "Client ID", + "in": "query", + "name": "client", + "required": false, + "type": "string" + } + ], + "responses": { + "101": { + "description": "Connection upgraded." + }, + "400": { + "description": "Invalid `client`" + }, + "426": { + "description": "Upgrade required." + } + }, + "summary": "Establish websocket connection" + } + }, + "/bot/assets": { + "post": { + "consumes": [ + "multipart/mixed" + ], + "parameters": [ + { + "description": "A body with content type `multipart/mixed body`. The first section's content type should be `application/json`. The second section's content type should be always be `application/octet-stream`. Other content types will be ignored by the server.", + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/AssetSource" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Asset posted", + "headers": { + "Location": { + "description": "Asset location", + "format": "url", + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/Asset" + } + }, + "400": { + "description": "Invalid `body`\n\nInvalid content length (label: `invalid-length`)" + }, + "413": { + "description": "Asset too large (label: `client-error`)", + "schema": { + "example": { + "code": 413, + "label": "client-error", + "message": "Asset too large" + }, + "properties": { + "code": { + "enum": [ + 413 + ], + "type": "integer" + }, + "label": { + "enum": [ + "client-error" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Upload an asset" + } + }, + "/bot/assets/{key}": { + "delete": { + "parameters": [ + { + "in": "path", + "name": "key", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Asset deleted" + }, + "400": { + "description": "Invalid `key`" + }, + "403": { + "description": "Unauthorised operation (label: `unauthorised`)", + "schema": { + "example": { + "code": 403, + "label": "unauthorised", + "message": "Unauthorised operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "unauthorised" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Asset not found (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "Asset not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Delete an asset" + }, + "get": { + "parameters": [ + { + "in": "path", + "name": "key", + "required": true, + "type": "string" + }, + { + "in": "header", + "name": "Asset-Token", + "required": false, + "type": "string" + }, + { + "in": "query", + "name": "asset_token", + "required": false, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "302": { + "description": "Asset found", + "headers": { + "Location": { + "description": "Asset location", + "format": "url", + "type": "string" + } + } + }, + "400": { + "description": "Invalid `asset_token` or `Asset-Token` or `key`" + }, + "404": { + "description": "Asset not found (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "Asset not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Download an asset" + } + }, + "/bot/messages": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "query", + "name": "ignore_missing", + "required": false, + "type": "string" + }, + { + "in": "query", + "name": "report_missing", + "required": false, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/new-otr-message" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Message sent", + "schema": { + "$ref": "#/definitions/ClientMismatch" + } + }, + "400": { + "description": "Invalid `body` or `report_missing` or `ignore_missing`" + }, + "403": { + "description": "Unknown Client (label: `unknown-client`)\n\nFailed to connect to a user or to invite a user to a group because somebody is under legalhold and somebody else has not granted consent (label: `missing-legalhold-consent`)", + "schema": { + "example": { + "code": 403, + "label": "unknown-client", + "message": "Unknown Client" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "unknown-client", + "missing-legalhold-consent" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)\n\nConversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "412": { + "description": "Missing clients", + "schema": { + "$ref": "#/definitions/ClientMismatch" + } + } + }, + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-message-sent" + ], + [ + "brig", + "get-user-clients" + ] + ] + } + }, + "/broadcast/otr/messages": { + "post": { + "consumes": [ + "application/json;charset=utf-8", + "application/x-protobuf" + ], + "description": "This endpoint ensures that the list of clients is correct and only sends the message if the list is correct.\nTo override this, the endpoint accepts two query params:\n- `ignore_missing`: Can be 'true' 'false' or a comma separated list of user IDs.\n - When 'true' all missing clients are ignored.\n - When 'false' all missing clients are reported.\n - When comma separated list of user-ids, only clients for listed users are ignored.\n- `report_missing`: Can be 'true' 'false' or a comma separated list of user IDs.\n - When 'true' all missing clients are reported.\n - When 'false' all missing clients are ignored.\n - When comma separated list of user-ids, only clients for listed users are reported.\n\nApart from these, the request body also accepts `report_missing` which can only be a list of user ids and behaves the same way as the query parameter.\n\nAll three of these should be considered mutually exclusive. The server however does not error if more than one is specified, it reads them in this order of precedence:\n- `report_missing` in the request body has highest precedence.\n- `ignore_missing` in the query param is the next.\n- `report_missing` in the query param has the lowest precedence.\n\nThis endpoint can lead to OtrMessageAdd event being sent to the recipients.\n\n**NOTE:** The protobuf definitions of the request body can be found at https://github.com/wireapp/generic-message-proto/blob/master/proto/otr.proto.", + "parameters": [ + { + "in": "query", + "name": "ignore_missing", + "required": false, + "type": "string" + }, + { + "in": "query", + "name": "report_missing", + "required": false, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/new-otr-message" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Message sent", + "schema": { + "$ref": "#/definitions/ClientMismatch" + } + }, + "400": { + "description": "Invalid `body` or `report_missing` or `ignore_missing`\n\nToo many users to fan out the broadcast event to (label: `too-many-users-to-broadcast`)" + }, + "403": { + "description": "Unknown Client (label: `unknown-client`)\n\nFailed to connect to a user or to invite a user to a group because somebody is under legalhold and somebody else has not granted consent (label: `missing-legalhold-consent`)", + "schema": { + "example": { + "code": 403, + "label": "unknown-client", + "message": "Unknown Client" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "unknown-client", + "missing-legalhold-consent" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)\n\nNot a member of a binding team (label: `non-binding-team`)\n\nTeam not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation", + "non-binding-team", + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "412": { + "description": "Missing clients", + "schema": { + "$ref": "#/definitions/ClientMismatch" + } + } + }, + "summary": "Broadcast an encrypted message to all team members and all contacts (accepts JSON or Protobuf)" + } + }, + "/broadcast/proteus/messages": { + "post": { + "consumes": [ + "application/x-protobuf" + ], + "description": "This endpoint ensures that the list of clients is correct and only sends the message if the list is correct.\nTo override this, the endpoint accepts `client_mismatch_strategy` in the body. It can have these values:\n- `report_all`: When set, the message is not sent if any clients are missing. The missing clients are reported in the response.\n- `ignore_all`: When set, no checks about missing clients are carried out.\n- `report_only`: Takes a list of qualified UserIDs. If any clients of the listed users are missing, the message is not sent. The missing clients are reported in the response.\n- `ignore_only`: Takes a list of qualified UserIDs. If any clients of the non-listed users are missing, the message is not sent. The missing clients are reported in the response.\n\nThe sending of messages in a federated conversation could theoretically fail partially. To make this case unlikely, the backend first gets a list of clients from all the involved backends and then tries to send a message. So, if any backend is down, the message is not propagated to anyone. But the actual message fan out to multiple backends could still fail partially. This type of failure is reported as a 201, the clients for which the message sending failed are part of the response body.\n\nThis endpoint can lead to OtrMessageAdd event being sent to the recipients.\n\n**NOTE:** The protobuf definitions of the request body can be found at https://github.com/wireapp/generic-message-proto/blob/master/proto/otr.proto.", + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/QualifiedNewOtrMessage" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Message sent", + "schema": { + "$ref": "#/definitions/MessageSendingStatus" + } + }, + "400": { + "description": "Invalid `body`\n\nToo many users to fan out the broadcast event to (label: `too-many-users-to-broadcast`)" + }, + "403": { + "description": "Unknown Client (label: `unknown-client`)\n\nFailed to connect to a user or to invite a user to a group because somebody is under legalhold and somebody else has not granted consent (label: `missing-legalhold-consent`)", + "schema": { + "example": { + "code": 403, + "label": "unknown-client", + "message": "Unknown Client" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "unknown-client", + "missing-legalhold-consent" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)\n\nNot a member of a binding team (label: `non-binding-team`)\n\nTeam not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation", + "non-binding-team", + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "412": { + "description": "Missing clients", + "schema": { + "$ref": "#/definitions/MessageSendingStatus" + } + } + }, + "summary": "Post an encrypted message to all team members and all contacts (accepts only Protobuf)" + } + }, + "/calls/config": { + "get": { + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/RTCConfiguration" + } + } + }, + "summary": "[deprecated] Retrieve TURN server addresses and credentials for IP addresses, scheme `turn` and transport `udp` only" + } + }, + "/calls/config/v2": { + "get": { + "parameters": [ + { + "description": "Limit resulting list. Allowed values [1..10]", + "in": "query", + "maximum": 10, + "minimum": 1, + "name": "limit", + "required": false, + "type": "integer" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/RTCConfiguration" + } + }, + "400": { + "description": "Invalid `limit`" + } + }, + "summary": "Retrieve all TURN server addresses and credentials. Clients are expected to do a DNS lookup to resolve the IP addresses of the given hostnames " + } + }, + "/clients": { + "get": { + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "items": { + "$ref": "#/definitions/Client" + }, + "type": "array" + } + } + }, + "summary": "List the registered clients" + }, + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "header", + "name": "X-Forwarded-For", + "required": false, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/NewClient" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "201": { + "description": "", + "headers": { + "Location": { + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/Client" + } + }, + "400": { + "description": "Invalid `body` or `X-Forwarded-For`\n\nMalformed prekeys uploaded (label: `bad-request`)" + }, + "403": { + "description": "Code authentication is required (label: `code-authentication-required`)\n\nCode authentication failed (label: `code-authentication-failed`)\n\nRe-authentication via password required (label: `missing-auth`)\n\nToo many clients (label: `too-many-clients`)", + "schema": { + "example": { + "code": 403, + "label": "code-authentication-required", + "message": "Code authentication is required" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "code-authentication-required", + "code-authentication-failed", + "missing-auth", + "too-many-clients" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Register a new client", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "on-user-deleted-connections" + ] + ] + } + }, + "/clients/{cid}/access-token": { + "post": { + "description": "[implementation stub, not supported yet!] Create an JWT DPoP access token for the client CSR, given a JWT DPoP proof, specified in the `DPoP` header. The access token will be returned as JWT DPoP token in the `DPoP` header.", + "parameters": [ + { + "description": "ClientId", + "in": "path", + "name": "cid", + "required": true, + "type": "string" + }, + { + "in": "header", + "name": "DPoP", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Access token created", + "headers": { + "Cache-Control": { + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/DPoPAccessTokenResponse" + } + }, + "400": { + "description": "Invalid `DPoP` or `cid`" + } + }, + "summary": "Create a JWT DPoP access token" + } + }, + "/clients/{client}": { + "delete": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "description": "ClientId", + "in": "path", + "name": "client", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/DeleteClient" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Client deleted" + }, + "400": { + "description": "Invalid `body` or `client`" + } + }, + "summary": "Delete an existing client" + }, + "get": { + "parameters": [ + { + "description": "ClientId", + "in": "path", + "name": "client", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Client found", + "schema": { + "$ref": "#/definitions/Client" + } + }, + "400": { + "description": "Invalid `client`" + }, + "404": { + "description": "Client not found(**Note**: This error has an empty body for legacy reasons)" + } + }, + "summary": "Get a registered client by ID" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "description": "ClientId", + "in": "path", + "name": "client", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/UpdateClient" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Client updated" + }, + "400": { + "description": "Invalid `body` or `client`\n\nMalformed prekeys uploaded (label: `bad-request`)" + } + }, + "summary": "Update a registered client" + } + }, + "/clients/{client}/capabilities": { + "get": { + "parameters": [ + { + "description": "ClientId", + "in": "path", + "name": "client", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/ClientCapabilityList" + } + }, + "400": { + "description": "Invalid `client`" + } + }, + "summary": "Read back what the client has been posting about itself" + } + }, + "/clients/{client}/nonce": { + "get": { + "description": "Get a new nonce for a client CSR, specified in the response header `Replay-Nonce` as a uuidv4 in base64url encoding.", + "parameters": [ + { + "description": "ClientId", + "in": "path", + "name": "client", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "204": { + "description": "No Content", + "headers": { + "Cache-Control": { + "type": "string" + }, + "Replay-Nonce": { + "type": "string" + } + } + }, + "400": { + "description": "Invalid `client`" + } + }, + "summary": "Get a new nonce for a client CSR" + }, + "head": { + "description": "Get a new nonce for a client CSR, specified in the response header `Replay-Nonce` as a uuidv4 in base64url encoding.", + "parameters": [ + { + "description": "ClientId", + "in": "path", + "name": "client", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "No Content", + "headers": { + "Cache-Control": { + "type": "string" + }, + "Replay-Nonce": { + "type": "string" + } + } + }, + "400": { + "description": "Invalid `client`" + } + }, + "summary": "Get a new nonce for a client CSR" + } + }, + "/clients/{client}/prekeys": { + "get": { + "parameters": [ + { + "description": "ClientId", + "in": "path", + "name": "client", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "items": { + "maximum": 65535, + "minimum": 0, + "type": "integer" + }, + "type": "array" + } + }, + "400": { + "description": "Invalid `client`" + } + }, + "summary": "List the remaining prekey IDs of a client" + } + }, + "/connections/{uid_domain}/{uid}": { + "get": { + "parameters": [ + { + "in": "path", + "name": "uid_domain", + "required": true, + "type": "string" + }, + { + "description": "User Id", + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Connection found", + "schema": { + "$ref": "#/definitions/UserConnection" + } + }, + "400": { + "description": "Invalid `uid` or `uid_domain`" + }, + "404": { + "description": "Connection not found(**Note**: This error has an empty body for legacy reasons)" + } + }, + "summary": "Get an existing connection to another user (local or remote)" + }, + "post": { + "description": "You can have no more than 1000 connections in accepted or sent state", + "parameters": [ + { + "in": "path", + "name": "uid_domain", + "required": true, + "type": "string" + }, + { + "description": "User Id", + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Connection existed", + "schema": { + "$ref": "#/definitions/UserConnection" + } + }, + "201": { + "description": "Connection was created", + "schema": { + "$ref": "#/definitions/UserConnection" + } + }, + "400": { + "description": "Invalid `uid` or `uid_domain`\n\nInvalid user (label: `invalid-user`)" + }, + "403": { + "description": "The user has no verified identity (email or phone number) (label: `no-identity`)\n\nToo many sent/accepted connections (label: `connection-limit`)\n\nFailed to connect to a user or to invite a user to a group because somebody is under legalhold and somebody else has not granted consent (label: `missing-legalhold-consent`)", + "schema": { + "example": { + "code": 403, + "label": "no-identity", + "message": "The user has no verified identity (email or phone number)" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-identity", + "connection-limit", + "missing-legalhold-consent" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Create a connection to another user", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "send-connection-action" + ] + ] + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "path", + "name": "uid_domain", + "required": true, + "type": "string" + }, + { + "description": "User Id", + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ConnectionUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Connection updated", + "schema": { + "$ref": "#/definitions/UserConnection" + } + }, + "204": { + "description": "Connection unchanged" + }, + "400": { + "description": "Invalid `body` or `uid` or `uid_domain`\n\nInvalid user (label: `invalid-user`)" + }, + "403": { + "description": "The user has no verified identity (email or phone number) (label: `no-identity`)\n\nInvalid status transition (label: `bad-conn-update`)\n\nUsers are not connected (label: `not-connected`)\n\nToo many sent/accepted connections (label: `connection-limit`)\n\nFailed to connect to a user or to invite a user to a group because somebody is under legalhold and somebody else has not granted consent (label: `missing-legalhold-consent`)", + "schema": { + "example": { + "code": 403, + "label": "no-identity", + "message": "The user has no verified identity (email or phone number)" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-identity", + "bad-conn-update", + "not-connected", + "connection-limit", + "missing-legalhold-consent" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update a connection to another user", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "send-connection-action" + ] + ] + } + }, + "/conversations": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "This returns 201 when a new conversation is created, and 200 when the conversation already existed", + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/NewConv" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Conversation existed", + "headers": { + "Location": { + "description": "Conversation ID", + "format": "uuid", + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/Conversation" + } + }, + "201": { + "description": "Conversation created", + "headers": { + "Location": { + "description": "Conversation ID", + "format": "uuid", + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/Conversation" + } + }, + "400": { + "description": "Invalid `body`\n\nMLS is not configured on this backend. See docs.wire.com for instructions on how to enable it (label: `mls-not-enabled`)\n\nAttempting to add group members outside MLS (label: `non-empty-member-list`)" + }, + "403": { + "description": "Failed to connect to a user or to invite a user to a group because somebody is under legalhold and somebody else has not granted consent (label: `missing-legalhold-consent`)\n\nInsufficient permissions (label: `operation-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)\n\nUsers are not connected (label: `not-connected`)\n\nConversation access denied (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "missing-legalhold-consent", + "message": "Failed to connect to a user or to invite a user to a group because somebody is under legalhold and somebody else has not granted consent" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "missing-legalhold-consent", + "operation-denied", + "no-team-member", + "not-connected", + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Create a new conversation", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-created" + ] + ] + } + }, + "/conversations/code-check": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ConversationCode" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Valid" + }, + "400": { + "description": "Invalid `body`" + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)\n\nConversation code not found (label: `no-conversation-code`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation", + "no-conversation-code" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Check validity of a conversation code.If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled." + } + }, + "/conversations/join": { + "get": { + "parameters": [ + { + "in": "query", + "name": "key", + "required": true, + "type": "string" + }, + { + "in": "query", + "name": "code", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/ConversationCoverView" + } + }, + "400": { + "description": "Invalid `code` or `key`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nConversation access denied (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)\n\nConversation code not found (label: `no-conversation-code`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation", + "no-conversation-code" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "The guest link feature is disabled and all guest links have been revoked (label: `guest-links-disabled`)", + "schema": { + "example": { + "code": 409, + "label": "guest-links-disabled", + "message": "The guest link feature is disabled and all guest links have been revoked" + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "guest-links-disabled" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get limited conversation information by key/code pair" + }, + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ConversationCode" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Conversation joined", + "schema": { + "$ref": "#/definitions/Event" + } + }, + "204": { + "description": "Conversation unchanged" + }, + "400": { + "description": "Invalid `body`" + }, + "403": { + "description": "Maximum number of members per conversation reached (label: `too-many-members`)\n\nRequesting user is not a team member (label: `no-team-member`)\n\nInvalid operation (label: `invalid-op`)\n\nConversation access denied (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "too-many-members", + "message": "Maximum number of members per conversation reached" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "too-many-members", + "no-team-member", + "invalid-op", + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)\n\nConversation code not found (label: `no-conversation-code`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation", + "no-conversation-code" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "The guest link feature is disabled and all guest links have been revoked (label: `guest-links-disabled`)", + "schema": { + "example": { + "code": 409, + "label": "guest-links-disabled", + "message": "The guest link feature is disabled and all guest links have been revoked" + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "guest-links-disabled" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Join a conversation using a reusable code.If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled.", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/conversations/list": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ListConversations" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/ConversationsResponse" + } + }, + "400": { + "description": "Invalid `body`" + } + }, + "summary": "Get conversation metadata for a list of conversation ids", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "get-conversations" + ] + ] + } + }, + "/conversations/list-ids": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "The IDs returned by this endpoint are paginated. To get the first page, make a call with the `paging_state` field set to `null` (or omitted). Whenever the `has_more` field of the response is set to `true`, more results are available, and they can be obtained by calling the endpoint again, but this time passing the value of `paging_state` returned by the previous call. One can continue in this fashion until all results are returned, which is indicated by `has_more` being `false`. Note that `paging_state` should be considered an opaque token. It should not be inspected, or stored, or reused across multiple unrelated invocations of the endpoint.", + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/GetPaginated_ConversationIds" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/ConversationIds_Page" + } + }, + "400": { + "description": "Invalid `body`" + } + }, + "summary": "Get all conversation IDs." + } + }, + "/conversations/one2one": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/NewConv" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Conversation existed", + "headers": { + "Location": { + "description": "Conversation ID", + "format": "uuid", + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/Conversation" + } + }, + "201": { + "description": "Conversation created", + "headers": { + "Location": { + "description": "Conversation ID", + "format": "uuid", + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/Conversation" + } + }, + "400": { + "description": "Invalid `body`" + }, + "403": { + "description": "Failed to connect to a user or to invite a user to a group because somebody is under legalhold and somebody else has not granted consent (label: `missing-legalhold-consent`)\n\nInsufficient permissions (label: `operation-denied`)\n\nUsers are not connected (label: `not-connected`)\n\nRequesting user is not a team member (label: `no-team-member`)\n\nBoth users must be members of the same binding team (label: `non-binding-team-members`)\n\nInvalid operation (label: `invalid-op`)\n\nConversation access denied (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "missing-legalhold-consent", + "message": "Failed to connect to a user or to invite a user to a group because somebody is under legalhold and somebody else has not granted consent" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "missing-legalhold-consent", + "operation-denied", + "not-connected", + "no-team-member", + "non-binding-team-members", + "invalid-op", + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)\n\nNot a member of a binding team (label: `non-binding-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team", + "non-binding-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Create a 1:1 conversation", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-created" + ] + ] + } + }, + "/conversations/self": { + "post": { + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Conversation existed", + "headers": { + "Location": { + "description": "Conversation ID", + "format": "uuid", + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/Conversation" + } + }, + "201": { + "description": "Conversation created", + "headers": { + "Location": { + "description": "Conversation ID", + "format": "uuid", + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/Conversation" + } + } + }, + "summary": "Create a self-conversation" + } + }, + "/conversations/{cnv_domain}/{cnv}": { + "get": { + "parameters": [ + { + "in": "path", + "name": "cnv_domain", + "required": true, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/Conversation" + } + }, + "400": { + "description": "Invalid `cnv` or `cnv_domain`" + }, + "403": { + "description": "Conversation access denied (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "access-denied", + "message": "Conversation access denied" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get a conversation by ID", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "get-conversations" + ] + ] + } + }, + "/conversations/{cnv_domain}/{cnv}/access": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "path", + "name": "cnv_domain", + "required": true, + "type": "string" + }, + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ConversationAccessData" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Access updated", + "schema": { + "$ref": "#/definitions/Event" + } + }, + "204": { + "description": "Access unchanged" + }, + "400": { + "description": "Invalid `body` or `cnv` or `cnv_domain`" + }, + "403": { + "description": "Invalid target access (label: `invalid-op`)\n\nInvalid operation (label: `invalid-op`)\n\nConversation access denied (label: `access-denied`)\n\nInsufficient authorization (missing remove_conversation_member) (label: `action-denied`)\n\nInsufficient authorization (missing modify_conversation_access) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-op", + "message": "Invalid target access" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-op", + "access-denied", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update access modes for a conversation", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/conversations/{cnv_domain}/{cnv}/members": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "path", + "name": "cnv_domain", + "required": true, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/InviteQualified" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Conversation updated", + "schema": { + "$ref": "#/definitions/Event" + } + }, + "204": { + "description": "Conversation unchanged" + }, + "400": { + "description": "Invalid `body` or `cnv` or `cnv_domain`" + }, + "403": { + "description": "Failed to connect to a user or to invite a user to a group because somebody is under legalhold and somebody else has not granted consent (label: `missing-legalhold-consent`)\n\nUsers are not connected (label: `not-connected`)\n\nRequesting user is not a team member (label: `no-team-member`)\n\nConversation access denied (label: `access-denied`)\n\nMaximum number of members per conversation reached (label: `too-many-members`)\n\nInvalid operation (label: `invalid-op`)\n\nInsufficient authorization (missing leave_conversation) (label: `action-denied`)\n\nInsufficient authorization (missing add_conversation_member) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "missing-legalhold-consent", + "message": "Failed to connect to a user or to invite a user to a group because somebody is under legalhold and somebody else has not granted consent" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "missing-legalhold-consent", + "not-connected", + "no-team-member", + "access-denied", + "too-many-members", + "invalid-op", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Add qualified members to an existing conversation.", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/conversations/{cnv_domain}/{cnv}/members/{usr_domain}/{usr}": { + "delete": { + "parameters": [ + { + "in": "path", + "name": "cnv_domain", + "required": true, + "type": "string" + }, + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "path", + "name": "usr_domain", + "required": true, + "type": "string" + }, + { + "description": "Target User ID", + "format": "uuid", + "in": "path", + "name": "usr", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Member removed", + "schema": { + "$ref": "#/definitions/Event" + } + }, + "204": { + "description": "No change" + }, + "400": { + "description": "Invalid `usr` or `usr_domain` or `cnv` or `cnv_domain`" + }, + "403": { + "description": "Invalid operation (label: `invalid-op`)\n\nInsufficient authorization (missing remove_conversation_member) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-op", + "message": "Invalid operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-op", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Remove a member from a conversation", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "leave-conversation" + ], + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "**Note**: at least one field has to be provided.", + "parameters": [ + { + "in": "path", + "name": "cnv_domain", + "required": true, + "type": "string" + }, + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "path", + "name": "usr_domain", + "required": true, + "type": "string" + }, + { + "description": "Target User ID", + "format": "uuid", + "in": "path", + "name": "usr", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/OtherMemberUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Membership updated" + }, + "400": { + "description": "Invalid `body` or `usr` or `usr_domain` or `cnv` or `cnv_domain`" + }, + "403": { + "description": "Invalid operation (label: `invalid-op`)\n\nInvalid target (label: `invalid-op`)\n\nInsufficient authorization (missing modify_other_conversation_member) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-op", + "message": "Invalid operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-op", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation member not found (label: `no-conversation-member`)\n\nConversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation-member", + "message": "Conversation member not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation-member", + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update membership of the specified user", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/conversations/{cnv_domain}/{cnv}/message-timer": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "path", + "name": "cnv_domain", + "required": true, + "type": "string" + }, + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ConversationMessageTimerUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Message timer updated", + "schema": { + "$ref": "#/definitions/Event" + } + }, + "204": { + "description": "Message timer unchanged" + }, + "400": { + "description": "Invalid `body` or `cnv` or `cnv_domain`" + }, + "403": { + "description": "Invalid operation (label: `invalid-op`)\n\nConversation access denied (label: `access-denied`)\n\nInsufficient authorization (missing modify_conversation_message_timer) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-op", + "message": "Invalid operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-op", + "access-denied", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update the message timer for a conversation", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/conversations/{cnv_domain}/{cnv}/name": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "path", + "name": "cnv_domain", + "required": true, + "type": "string" + }, + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ConversationRename" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Name unchanged", + "schema": { + "$ref": "#/definitions/Event" + } + }, + "204": { + "description": "Name updated" + }, + "400": { + "description": "Invalid `body` or `cnv` or `cnv_domain`" + }, + "403": { + "description": "Invalid operation (label: `invalid-op`)\n\nInsufficient authorization (missing modify_conversation_name) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-op", + "message": "Invalid operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-op", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update conversation name", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/conversations/{cnv_domain}/{cnv}/proteus/messages": { + "post": { + "consumes": [ + "application/x-protobuf" + ], + "description": "This endpoint ensures that the list of clients is correct and only sends the message if the list is correct.\nTo override this, the endpoint accepts `client_mismatch_strategy` in the body. It can have these values:\n- `report_all`: When set, the message is not sent if any clients are missing. The missing clients are reported in the response.\n- `ignore_all`: When set, no checks about missing clients are carried out.\n- `report_only`: Takes a list of qualified UserIDs. If any clients of the listed users are missing, the message is not sent. The missing clients are reported in the response.\n- `ignore_only`: Takes a list of qualified UserIDs. If any clients of the non-listed users are missing, the message is not sent. The missing clients are reported in the response.\n\nThe sending of messages in a federated conversation could theoretically fail partially. To make this case unlikely, the backend first gets a list of clients from all the involved backends and then tries to send a message. So, if any backend is down, the message is not propagated to anyone. But the actual message fan out to multiple backends could still fail partially. This type of failure is reported as a 201, the clients for which the message sending failed are part of the response body.\n\nThis endpoint can lead to OtrMessageAdd event being sent to the recipients.\n\n**NOTE:** The protobuf definitions of the request body can be found at https://github.com/wireapp/generic-message-proto/blob/master/proto/otr.proto.", + "parameters": [ + { + "in": "path", + "name": "cnv_domain", + "required": true, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/QualifiedNewOtrMessage" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Message sent", + "schema": { + "$ref": "#/definitions/MessageSendingStatus" + } + }, + "400": { + "description": "Invalid `body` or `cnv` or `cnv_domain`" + }, + "403": { + "description": "Unknown Client (label: `unknown-client`)\n\nFailed to connect to a user or to invite a user to a group because somebody is under legalhold and somebody else has not granted consent (label: `missing-legalhold-consent`)", + "schema": { + "example": { + "code": 403, + "label": "unknown-client", + "message": "Unknown Client" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "unknown-client", + "missing-legalhold-consent" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "412": { + "description": "Missing clients", + "schema": { + "$ref": "#/definitions/MessageSendingStatus" + } + } + }, + "summary": "Post an encrypted message to a conversation (accepts only Protobuf)", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "get-user-clients" + ], + [ + "galley", + "on-message-sent" + ], + [ + "galley", + "send-message" + ] + ] + } + }, + "/conversations/{cnv_domain}/{cnv}/receipt-mode": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "path", + "name": "cnv_domain", + "required": true, + "type": "string" + }, + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ConversationReceiptModeUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Receipt mode updated", + "schema": { + "$ref": "#/definitions/Event" + } + }, + "204": { + "description": "Receipt mode unchanged" + }, + "400": { + "description": "Invalid `body` or `cnv` or `cnv_domain`" + }, + "403": { + "description": "Invalid operation (label: `invalid-op`)\n\nConversation access denied (label: `access-denied`)\n\nInsufficient authorization (missing modify_conversation_receipt_mode) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-op", + "message": "Invalid operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-op", + "access-denied", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update receipt mode for a conversation", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ], + [ + "galley", + "update-conversation" + ] + ] + } + }, + "/conversations/{cnv_domain}/{cnv}/self": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "**Note**: at least one field has to be provided.", + "parameters": [ + { + "in": "path", + "name": "cnv_domain", + "required": true, + "type": "string" + }, + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/MemberUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Update successful" + }, + "400": { + "description": "Invalid `body` or `cnv` or `cnv_domain`" + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update self membership properties" + } + }, + "/conversations/{cnv_domain}/{cnv}/typing": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "path", + "name": "cnv_domain", + "required": true, + "type": "string" + }, + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/TypingData" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Notification sent" + }, + "400": { + "description": "Invalid `body` or `cnv` or `cnv_domain`" + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Sending typing notifications", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-typing-indicator-updated" + ] + ] + } + }, + "/conversations/{cnv}": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "Use `/conversations/:domain/:conv/name` instead.", + "parameters": [ + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ConversationRename" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Name updated", + "schema": { + "$ref": "#/definitions/Event" + } + }, + "204": { + "description": "Name unchanged" + }, + "400": { + "description": "Invalid `body` or `cnv`" + }, + "403": { + "description": "Invalid operation (label: `invalid-op`)\n\nInsufficient authorization (missing modify_conversation_name) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-op", + "message": "Invalid operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-op", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update conversation name (deprecated)", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/conversations/{cnv}/code": { + "delete": { + "parameters": [ + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Conversation code deleted.", + "schema": { + "$ref": "#/definitions/Event" + } + }, + "400": { + "description": "Invalid `cnv`" + }, + "403": { + "description": "Conversation access denied (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "access-denied", + "message": "Conversation access denied" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Delete conversation code" + }, + "get": { + "parameters": [ + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Conversation Code", + "schema": { + "$ref": "#/definitions/ConversationCode" + } + }, + "400": { + "description": "Invalid `cnv`" + }, + "403": { + "description": "Conversation access denied (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "access-denied", + "message": "Conversation access denied" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)\n\nConversation code not found (label: `no-conversation-code`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation", + "no-conversation-code" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "The guest link feature is disabled and all guest links have been revoked (label: `guest-links-disabled`)", + "schema": { + "example": { + "code": 409, + "label": "guest-links-disabled", + "message": "The guest link feature is disabled and all guest links have been revoked" + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "guest-links-disabled" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get existing conversation code" + }, + "post": { + "parameters": [ + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Conversation code already exists.", + "schema": { + "$ref": "#/definitions/ConversationCode" + } + }, + "201": { + "description": "Conversation code created.", + "schema": { + "$ref": "#/definitions/Event" + } + }, + "400": { + "description": "Invalid `cnv`" + }, + "403": { + "description": "Conversation access denied (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "access-denied", + "message": "Conversation access denied" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "The guest link feature is disabled and all guest links have been revoked (label: `guest-links-disabled`)", + "schema": { + "example": { + "code": 409, + "label": "guest-links-disabled", + "message": "The guest link feature is disabled and all guest links have been revoked" + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "guest-links-disabled" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Create or recreate a conversation code" + } + }, + "/conversations/{cnv}/features/conversationGuestLinks": { + "get": { + "parameters": [ + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/GuestLinksConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `cnv`" + }, + "403": { + "description": "Conversation access denied (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "access-denied", + "message": "Conversation access denied" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team." + } + }, + "/conversations/{cnv}/join": { + "post": { + "parameters": [ + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Conversation joined", + "schema": { + "$ref": "#/definitions/Event" + } + }, + "204": { + "description": "Conversation unchanged" + }, + "400": { + "description": "Invalid `cnv`" + }, + "403": { + "description": "Maximum number of members per conversation reached (label: `too-many-members`)\n\nRequesting user is not a team member (label: `no-team-member`)\n\nInvalid operation (label: `invalid-op`)\n\nConversation access denied (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "too-many-members", + "message": "Maximum number of members per conversation reached" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "too-many-members", + "no-team-member", + "invalid-op", + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Join a conversation by its ID (if link access enabled)", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/conversations/{cnv}/members/{usr}": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead", + "parameters": [ + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "description": "Target User ID", + "format": "uuid", + "in": "path", + "name": "usr", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/OtherMemberUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Membership updated" + }, + "400": { + "description": "Invalid `body` or `usr` or `cnv`" + }, + "403": { + "description": "Invalid operation (label: `invalid-op`)\n\nInvalid target (label: `invalid-op`)\n\nInsufficient authorization (missing modify_other_conversation_member) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-op", + "message": "Invalid operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-op", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation member not found (label: `no-conversation-member`)\n\nConversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation-member", + "message": "Conversation member not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation-member", + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update membership of the specified user (deprecated)", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/conversations/{cnv}/message-timer": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "Use `/conversations/:domain/:cnv/message-timer` instead.", + "parameters": [ + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ConversationMessageTimerUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Message timer updated", + "schema": { + "$ref": "#/definitions/Event" + } + }, + "204": { + "description": "Message timer unchanged" + }, + "400": { + "description": "Invalid `body` or `cnv`" + }, + "403": { + "description": "Invalid operation (label: `invalid-op`)\n\nConversation access denied (label: `access-denied`)\n\nInsufficient authorization (missing modify_conversation_message_timer) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-op", + "message": "Invalid operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-op", + "access-denied", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update the message timer for a conversation (deprecated)", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/conversations/{cnv}/name": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "Use `/conversations/:domain/:conv/name` instead.", + "parameters": [ + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ConversationRename" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Name updated", + "schema": { + "$ref": "#/definitions/Event" + } + }, + "204": { + "description": "Name unchanged" + }, + "400": { + "description": "Invalid `body` or `cnv`" + }, + "403": { + "description": "Invalid operation (label: `invalid-op`)\n\nInsufficient authorization (missing modify_conversation_name) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-op", + "message": "Invalid operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-op", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update conversation name (deprecated)", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/conversations/{cnv}/otr/messages": { + "post": { + "consumes": [ + "application/json;charset=utf-8", + "application/x-protobuf" + ], + "description": "This endpoint ensures that the list of clients is correct and only sends the message if the list is correct.\nTo override this, the endpoint accepts two query params:\n- `ignore_missing`: Can be 'true' 'false' or a comma separated list of user IDs.\n - When 'true' all missing clients are ignored.\n - When 'false' all missing clients are reported.\n - When comma separated list of user-ids, only clients for listed users are ignored.\n- `report_missing`: Can be 'true' 'false' or a comma separated list of user IDs.\n - When 'true' all missing clients are reported.\n - When 'false' all missing clients are ignored.\n - When comma separated list of user-ids, only clients for listed users are reported.\n\nApart from these, the request body also accepts `report_missing` which can only be a list of user ids and behaves the same way as the query parameter.\n\nAll three of these should be considered mutually exclusive. The server however does not error if more than one is specified, it reads them in this order of precedence:\n- `report_missing` in the request body has highest precedence.\n- `ignore_missing` in the query param is the next.\n- `report_missing` in the query param has the lowest precedence.\n\nThis endpoint can lead to OtrMessageAdd event being sent to the recipients.\n\n**NOTE:** The protobuf definitions of the request body can be found at https://github.com/wireapp/generic-message-proto/blob/master/proto/otr.proto.", + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "query", + "name": "ignore_missing", + "required": false, + "type": "string" + }, + { + "in": "query", + "name": "report_missing", + "required": false, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/new-otr-message" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Message sent", + "schema": { + "$ref": "#/definitions/ClientMismatch" + } + }, + "400": { + "description": "Invalid `body` or `report_missing` or `ignore_missing` or `cnv`" + }, + "403": { + "description": "Unknown Client (label: `unknown-client`)\n\nFailed to connect to a user or to invite a user to a group because somebody is under legalhold and somebody else has not granted consent (label: `missing-legalhold-consent`)", + "schema": { + "example": { + "code": 403, + "label": "unknown-client", + "message": "Unknown Client" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "unknown-client", + "missing-legalhold-consent" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "412": { + "description": "Missing clients", + "schema": { + "$ref": "#/definitions/ClientMismatch" + } + } + }, + "summary": "Post an encrypted message to a conversation (accepts JSON or Protobuf)", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-message-sent" + ], + [ + "brig", + "get-user-clients" + ] + ] + } + }, + "/conversations/{cnv}/receipt-mode": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead.", + "parameters": [ + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ConversationReceiptModeUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Receipt mode updated", + "schema": { + "$ref": "#/definitions/Event" + } + }, + "204": { + "description": "Receipt mode unchanged" + }, + "400": { + "description": "Invalid `body` or `cnv`" + }, + "403": { + "description": "Invalid operation (label: `invalid-op`)\n\nConversation access denied (label: `access-denied`)\n\nInsufficient authorization (missing modify_conversation_receipt_mode) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-op", + "message": "Invalid operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-op", + "access-denied", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update receipt mode for a conversation (deprecated)", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ], + [ + "galley", + "update-conversation" + ] + ] + } + }, + "/conversations/{cnv}/roles": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/ConversationRolesList" + } + }, + "400": { + "description": "Invalid `cnv`" + }, + "403": { + "description": "Conversation access denied (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "access-denied", + "message": "Conversation access denied" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get existing roles available for the given conversation" + } + }, + "/conversations/{cnv}/self": { + "get": { + "parameters": [ + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/Member" + } + }, + "400": { + "description": "Invalid `cnv`" + } + }, + "summary": "Get self membership properties (deprecated)" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "Use `/conversations/:domain/:conv/self` instead.", + "parameters": [ + { + "description": "Conversation ID", + "format": "uuid", + "in": "path", + "name": "cnv", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/MemberUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Update successful" + }, + "400": { + "description": "Invalid `body` or `cnv`" + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update self membership properties (deprecated)" + } + }, + "/cookies": { + "get": { + "parameters": [ + { + "description": "Filter by label (comma-separated list)", + "in": "query", + "name": "labels", + "required": false, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "List of cookies", + "schema": { + "$ref": "#/definitions/CookieList" + } + }, + "400": { + "description": "Invalid `labels`" + } + }, + "summary": "Retrieve the list of cookies currently stored for the user" + } + }, + "/cookies/remove": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/RemoveCookies" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Cookies revoked" + }, + "400": { + "description": "Invalid `body`" + }, + "403": { + "description": "Authentication failed (label: `invalid-credentials`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-credentials", + "message": "Authentication failed" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-credentials" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Revoke stored cookies" + } + }, + "/custom-backend/by-domain/{domain}": { + "get": { + "parameters": [ + { + "description": "URL-encoded email domain", + "in": "path", + "name": "domain", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/CustomBackend" + } + }, + "400": { + "description": "Invalid `domain`" + }, + "404": { + "description": "Custom backend not found (label: `custom-backend-not-found`)", + "schema": { + "example": { + "code": 404, + "label": "custom-backend-not-found", + "message": "Custom backend not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "custom-backend-not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Shows information about custom backends related to a given email domain" + } + }, + "/delete": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/VerifyDeleteUser" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Deletion is initiated." + }, + "400": { + "description": "Invalid `body`" + }, + "403": { + "description": "Invalid verification code (label: `invalid-code`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-code", + "message": "Invalid verification code" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-code" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Verify account deletion with a code.", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "on-user-deleted-connections" + ] + ] + } + }, + "/feature-configs": { + "get": { + "description": "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults).", + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/AllFeatureConfigs" + } + }, + "403": { + "description": "Insufficient permissions (label: `operation-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)", + "schema": { + "example": { + "code": 403, + "label": "operation-denied", + "message": "Insufficient permissions" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "operation-denied", + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Gets feature configs for a user" + } + }, + "/identity-providers": { + "get": { + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/IdPList" + } + } + } + }, + "post": { + "consumes": [ + "application/xml", + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/IdPMetadataInfo" + } + }, + { + "format": "uuid", + "in": "query", + "name": "replaces", + "required": false, + "type": "string" + }, + { + "default": "v2", + "enum": [ + "v1", + "v2" + ], + "in": "query", + "name": "api_version", + "required": false, + "type": "string" + }, + { + "in": "query", + "maxLength": 1, + "minLength": 32, + "name": "handle", + "required": false, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "201": { + "description": "", + "schema": { + "$ref": "#/definitions/IdPConfig" + } + }, + "400": { + "description": "Invalid `handle` or `api_version` or `replaces` or `body`" + } + } + } + }, + "/identity-providers/{id}": { + "delete": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "id", + "required": true, + "type": "string" + }, + { + "in": "query", + "name": "purge", + "required": false, + "type": "boolean" + } + ], + "responses": { + "204": { + "description": "" + }, + "400": { + "description": "Invalid `purge` or `id`" + } + } + }, + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "id", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/IdPConfig" + } + }, + "400": { + "description": "Invalid `id`" + } + } + }, + "put": { + "consumes": [ + "application/xml", + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/IdPMetadataInfo" + } + }, + { + "format": "uuid", + "in": "path", + "name": "id", + "required": true, + "type": "string" + }, + { + "in": "query", + "maxLength": 1, + "minLength": 32, + "name": "handle", + "required": false, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/IdPConfig" + } + }, + "400": { + "description": "Invalid `handle` or `id` or `body`" + } + } + } + }, + "/identity-providers/{id}/raw": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "id", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/xml" + ], + "responses": { + "200": { + "description": "", + "schema": { + "type": "string" + } + }, + "400": { + "description": "Invalid `id`" + } + } + } + }, + "/list-connections": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "The IDs returned by this endpoint are paginated. To get the first page, make a call with the `paging_state` field set to `null` (or omitted). Whenever the `has_more` field of the response is set to `true`, more results are available, and they can be obtained by calling the endpoint again, but this time passing the value of `paging_state` returned by the previous call. One can continue in this fashion until all results are returned, which is indicated by `has_more` being `false`. Note that `paging_state` should be considered an opaque token. It should not be inspected, or stored, or reused across multiple unrelated invocations of the endpoint.", + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/GetPaginated_Connections" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/Connections_Page" + } + }, + "400": { + "description": "Invalid `body`" + } + }, + "summary": "List the connections to other users, including remote users" + } + }, + "/list-users": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "The 'qualified_ids' and 'qualified_handles' parameters are mutually exclusive.", + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ListUsersQuery" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "items": { + "$ref": "#/definitions/UserProfile" + }, + "type": "array" + } + }, + "400": { + "description": "Invalid `body`" + } + }, + "summary": "List users", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "get-users-by-ids" + ] + ] + } + }, + "/login": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "Logins are throttled at the server's discretion", + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/Login" + } + }, + { + "description": "Request a persistent cookie instead of a session cookie", + "in": "query", + "name": "persist", + "required": false, + "type": "boolean" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "OK", + "headers": { + "Set-Cookie": { + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/AccessToken" + } + }, + "400": { + "description": "Invalid `persist` or `body`" + }, + "403": { + "description": "Code authentication is required (label: `code-authentication-required`)\n\nCode authentication failed (label: `code-authentication-failed`)\n\nAccount pending activation (label: `pending-activation`)\n\nAccount suspended (label: `suspended`)\n\nAuthentication failed (label: `invalid-credentials`)", + "schema": { + "example": { + "code": 403, + "label": "code-authentication-required", + "message": "Code authentication is required" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "code-authentication-required", + "code-authentication-failed", + "pending-activation", + "suspended", + "invalid-credentials" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Authenticate a user to obtain a cookie and first access token", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "on-user-deleted-connections" + ] + ] + } + }, + "/login/send": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "This operation generates and sends a login code via sms for phone login. A login code can be used only once and times out after 10 minutes. Only one login code may be pending at a time. For 2nd factor authentication login with email and password, use the `/verification-code/send` endpoint.", + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/SendLoginCode" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "OK", + "schema": { + "$ref": "#/definitions/LoginCodeTimeout" + } + }, + "400": { + "description": "Invalid mobile phone number (label: `invalid-phone`) or `body`", + "schema": { + "example": { + "code": 400, + "label": "invalid-phone", + "message": "Invalid mobile phone number" + }, + "properties": { + "code": { + "enum": [ + 400 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-phone" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "403": { + "description": "The operation is not permitted because the user has a password set (label: `password-exists`)", + "schema": { + "example": { + "code": 403, + "label": "password-exists", + "message": "The operation is not permitted because the user has a password set" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "password-exists" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Send a login code to a verified phone number" + } + }, + "/mls/key-packages/claim/{user_domain}/{user}": { + "post": { + "parameters": [ + { + "in": "path", + "name": "user_domain", + "required": true, + "type": "string" + }, + { + "description": "User Id", + "format": "uuid", + "in": "path", + "name": "user", + "required": true, + "type": "string" + }, + { + "description": "Do not claim a key package for the given own client", + "in": "query", + "name": "skip_own", + "required": false, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Claimed key packages", + "schema": { + "$ref": "#/definitions/KeyPackageBundle" + } + }, + "400": { + "description": "Invalid `skip_own` or `user` or `user_domain`" + } + }, + "summary": "Claim one key package for each client of the given user", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "claim-key-packages" + ] + ] + } + }, + "/mls/key-packages/self/{client}": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "The request body should be a json object containing a list of base64-encoded key packages.", + "parameters": [ + { + "description": "ClientId", + "in": "path", + "name": "client", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/KeyPackageUpload" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json", + "message/mls" + ], + "responses": { + "201": { + "description": "Key packages uploaded" + }, + "400": { + "description": "Invalid `body` or `client`\n\nMLS protocol error (label: `mls-protocol-error`)" + }, + "403": { + "description": "Key package credential does not match qualified client ID (label: `mls-identity-mismatch`)", + "schema": { + "example": { + "code": 403, + "label": "mls-identity-mismatch", + "message": "Key package credential does not match qualified client ID" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "mls-identity-mismatch" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Upload a fresh batch of key packages" + } + }, + "/mls/key-packages/self/{client}/count": { + "get": { + "parameters": [ + { + "description": "ClientId", + "in": "path", + "name": "client", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Number of key packages", + "schema": { + "$ref": "#/definitions/OwnKeyPackages" + } + }, + "400": { + "description": "Invalid `client`" + } + }, + "summary": "Return the number of unused key packages for the given client" + } + }, + "/notifications": { + "get": { + "parameters": [ + { + "description": "Only return notifications more recent than this", + "format": "uuid", + "in": "query", + "name": "since", + "required": false, + "type": "string" + }, + { + "description": "Only return notifications targeted at the given client", + "in": "query", + "name": "client", + "required": false, + "type": "string" + }, + { + "description": "Maximum number of notifications to return", + "format": "int32", + "in": "query", + "maximum": 10000, + "minimum": 100, + "name": "size", + "required": false, + "type": "integer" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Notification list", + "schema": { + "$ref": "#/definitions/QueuedNotificationList" + } + }, + "400": { + "description": "Invalid `size` or `client` or `since`" + }, + "404": { + "description": "Some notifications not found (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "Some notifications not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Fetch notifications" + } + }, + "/notifications/last": { + "get": { + "parameters": [ + { + "description": "Only return notifications targeted at the given client", + "in": "query", + "name": "client", + "required": false, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Notification found", + "schema": { + "$ref": "#/definitions/QueuedNotification" + } + }, + "400": { + "description": "Invalid `client`" + }, + "404": { + "description": "Some notifications not found (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "Some notifications not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Fetch the last notification" + } + }, + "/notifications/{id}": { + "get": { + "parameters": [ + { + "description": "Notification ID", + "format": "uuid", + "in": "path", + "name": "id", + "required": true, + "type": "string" + }, + { + "description": "Only return notifications targeted at the given client", + "in": "query", + "name": "client", + "required": false, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Notification found", + "schema": { + "$ref": "#/definitions/QueuedNotification" + } + }, + "400": { + "description": "Invalid `client` or `id`" + }, + "404": { + "description": "Some notifications not found (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "Some notifications not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Fetch a notification by ID" + } + }, + "/onboarding/v3": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "DEPRECATED: the feature has been turned off, the end-point does nothing and always returns '{\"results\":[],\"auto-connects\":[]}'.", + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/Body" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/DeprecatedMatchingResult" + } + }, + "400": { + "description": "Invalid `body`" + } + }, + "summary": "Upload contacts and invoke matching." + } + }, + "/password-reset": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/NewPasswordReset" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Password reset code created and sent by email." + }, + "400": { + "description": "Invalid `body`\n\nInvalid email or mobile number for password reset. (label: `invalid-key`)" + }, + "409": { + "description": "A password reset is already in progress. (label: `code-exists`)", + "schema": { + "example": { + "code": 409, + "label": "code-exists", + "message": "A password reset is already in progress." + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "code-exists" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Initiate a password reset." + } + }, + "/password-reset/complete": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/CompletePasswordReset" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Password reset successful." + }, + "400": { + "description": "Invalid `body`\n\nInvalid password reset code. (label: `invalid-code`)" + } + }, + "summary": "Complete a password reset." + } + }, + "/password-reset/{key}": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "DEPRECATED: Use 'POST /password-reset/complete'.", + "parameters": [ + { + "description": "An opaque key for a pending password reset.", + "in": "path", + "name": "key", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/PasswordReset" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Password reset successful." + }, + "400": { + "description": "Invalid `body` or `key`\n\nInvalid password reset code. (label: `invalid-code`)\n\nInvalid email or mobile number for password reset. (label: `invalid-key`)" + }, + "409": { + "description": "For password reset, new and old password must be different. (label: `password-must-differ`)\n\nA password reset is already in progress. (label: `code-exists`)", + "schema": { + "example": { + "code": 409, + "label": "password-must-differ", + "message": "For password reset, new and old password must be different." + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "password-must-differ", + "code-exists" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Complete a password reset." + } + }, + "/properties": { + "delete": { + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Properties cleared" + } + }, + "summary": "Clear all properties" + }, + "get": { + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "List of property keys", + "schema": { + "items": { + "$ref": "#/definitions/ASCII" + }, + "type": "array" + } + } + }, + "summary": "List all property keys" + } + }, + "/properties-values": { + "get": { + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/PropertyKeysAndValues" + } + } + }, + "summary": "List all properties with key and value" + } + }, + "/properties/{key}": { + "delete": { + "parameters": [ + { + "format": "printable", + "in": "path", + "name": "key", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Property deleted" + }, + "400": { + "description": "Invalid `key`" + } + }, + "summary": "Delete a property" + }, + "get": { + "parameters": [ + { + "format": "printable", + "in": "path", + "name": "key", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "The property value", + "schema": { + "$ref": "#/definitions/PropertyValue" + } + }, + "400": { + "description": "Invalid `key`" + }, + "404": { + "description": "Property not found(**Note**: This error has an empty body for legacy reasons)" + } + }, + "summary": "Get a property value" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "printable", + "in": "path", + "name": "key", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/PropertyValue" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Property set" + }, + "400": { + "description": "Invalid `body` or `key`" + } + }, + "summary": "Set a user property" + } + }, + "/provider/assets": { + "post": { + "consumes": [ + "multipart/mixed" + ], + "parameters": [ + { + "description": "A body with content type `multipart/mixed body`. The first section's content type should be `application/json`. The second section's content type should be always be `application/octet-stream`. Other content types will be ignored by the server.", + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/AssetSource" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Asset posted", + "headers": { + "Location": { + "description": "Asset location", + "format": "url", + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/Asset" + } + }, + "400": { + "description": "Invalid `body`\n\nInvalid content length (label: `invalid-length`)" + }, + "413": { + "description": "Asset too large (label: `client-error`)", + "schema": { + "example": { + "code": 413, + "label": "client-error", + "message": "Asset too large" + }, + "properties": { + "code": { + "enum": [ + 413 + ], + "type": "integer" + }, + "label": { + "enum": [ + "client-error" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Upload an asset" + } + }, + "/provider/assets/{key}": { + "delete": { + "parameters": [ + { + "in": "path", + "name": "key", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Asset deleted" + }, + "400": { + "description": "Invalid `key`" + }, + "403": { + "description": "Unauthorised operation (label: `unauthorised`)", + "schema": { + "example": { + "code": 403, + "label": "unauthorised", + "message": "Unauthorised operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "unauthorised" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Asset not found (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "Asset not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Delete an asset" + }, + "get": { + "parameters": [ + { + "in": "path", + "name": "key", + "required": true, + "type": "string" + }, + { + "in": "header", + "name": "Asset-Token", + "required": false, + "type": "string" + }, + { + "in": "query", + "name": "asset_token", + "required": false, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "302": { + "description": "Asset found", + "headers": { + "Location": { + "description": "Asset location", + "format": "url", + "type": "string" + } + } + }, + "400": { + "description": "Invalid `asset_token` or `Asset-Token` or `key`" + }, + "404": { + "description": "Asset not found (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "Asset not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Download an asset" + } + }, + "/proxy/giphy/v1/gifs": {}, + "/proxy/googlemaps/api/staticmap": {}, + "/proxy/googlemaps/maps/api/geocode": {}, + "/proxy/youtube/v3": {}, + "/push/tokens": { + "get": { + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/PushTokenList" + } + } + }, + "summary": "List the user's registered push tokens" + }, + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/PushToken" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Push token registered", + "headers": { + "Location": { + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/PushToken" + } + }, + "400": { + "description": "Invalid `body`" + }, + "404": { + "description": "App does not exist (label: `app-not-found`)\n\nInvalid push token (label: `invalid-token`)", + "schema": { + "example": { + "code": 404, + "label": "app-not-found", + "message": "App does not exist" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "app-not-found", + "invalid-token" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "413": { + "description": "Too many concurrent calls to SNS; is SNS down? (label: `sns-thread-budget-reached`)\n\nPush token length must be < 8192 for GCM or 400 for APNS (label: `token-too-long`)\n\nTried to add token to endpoint resulting in metadata length > 2048 (label: `metadata-too-long`)", + "schema": { + "example": { + "code": 413, + "label": "sns-thread-budget-reached", + "message": "Too many concurrent calls to SNS; is SNS down?" + }, + "properties": { + "code": { + "enum": [ + 413 + ], + "type": "integer" + }, + "label": { + "enum": [ + "sns-thread-budget-reached", + "token-too-long", + "metadata-too-long" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Register a native push token" + } + }, + "/push/tokens/{pid}": { + "delete": { + "parameters": [ + { + "description": "The push token to delete", + "in": "path", + "name": "pid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "204": { + "description": "Push token unregistered" + }, + "400": { + "description": "Invalid `pid`" + }, + "404": { + "description": "Push token not found (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "Push token not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Unregister a native push token" + } + }, + "/register": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "If the environment where the registration takes place is private and a registered email address or phone number is not whitelisted, a 403 error is returned.", + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/NewUser" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "User created and pending activation", + "headers": { + "Location": { + "description": "UserId", + "format": "uuid", + "type": "string" + }, + "Set-Cookie": { + "description": "Cookie", + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/User" + } + }, + "400": { + "description": "Invalid invitation code. (label: `invalid-invitation-code`)\n\nInvalid e-mail address. (label: `invalid-email`)\n\nInvalid mobile phone number (label: `invalid-phone`) or `body`", + "schema": { + "example": { + "code": 400, + "label": "invalid-invitation-code", + "message": "Invalid invitation code." + }, + "properties": { + "code": { + "enum": [ + 400 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-invitation-code", + "invalid-email", + "invalid-phone" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "403": { + "description": "Unauthorized e-mail address or phone number. (label: `unauthorized`)\n\nUsing an invitation code requires registering the given email and/or phone. (label: `missing-identity`)\n\nThe given phone number has been blacklisted due to suspected abuse or a complaint (label: `blacklisted-phone`)\n\nThe given e-mail address has been blacklisted due to a permanent bounce or a complaint. (label: `blacklisted-email`)\n\nToo many members in this team. (label: `too-many-team-members`)\n\nThis instance does not allow creation of personal users or teams. (label: `user-creation-restricted`)", + "schema": { + "example": { + "code": 403, + "label": "unauthorized", + "message": "Unauthorized e-mail address or phone number." + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "unauthorized", + "missing-identity", + "blacklisted-phone", + "blacklisted-email", + "too-many-team-members", + "user-creation-restricted" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "User does not exist (label: `invalid-code`)\n\nInvalid activation code (label: `invalid-code`)", + "schema": { + "example": { + "code": 404, + "label": "invalid-code", + "message": "User does not exist" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-code" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "The given e-mail address or phone number is in use. (label: `key-exists`)", + "schema": { + "example": { + "code": 409, + "label": "key-exists", + "message": "The given e-mail address or phone number is in use." + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "key-exists" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Register a new user.", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "on-user-deleted-connections" + ] + ] + } + }, + "/scim/auth-tokens": { + "delete": { + "parameters": [ + { + "format": "uuid", + "in": "query", + "name": "id", + "required": true, + "type": "string" + } + ], + "responses": { + "204": { + "description": "" + }, + "400": { + "description": "Invalid `id`" + }, + "403": { + "description": "Code authentication is required (label: `code-authentication-required`)\n\nCode authentication failed (label: `code-authentication-failed`)\n\nPassword authentication failed. (label: `password-authentication-failed`)", + "schema": { + "example": { + "code": 403, + "label": "code-authentication-required", + "message": "Code authentication is required" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "code-authentication-required", + "code-authentication-failed", + "password-authentication-failed" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + } + }, + "get": { + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/ScimTokenList" + } + }, + "403": { + "description": "Code authentication is required (label: `code-authentication-required`)\n\nCode authentication failed (label: `code-authentication-failed`)\n\nPassword authentication failed. (label: `password-authentication-failed`)", + "schema": { + "example": { + "code": 403, + "label": "code-authentication-required", + "message": "Code authentication is required" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "code-authentication-required", + "code-authentication-failed", + "password-authentication-failed" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + } + }, + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/CreateScimToken" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/CreateScimTokenResponse" + } + }, + "400": { + "description": "Invalid `body`" + }, + "403": { + "description": "Code authentication is required (label: `code-authentication-required`)\n\nCode authentication failed (label: `code-authentication-failed`)\n\nPassword authentication failed. (label: `password-authentication-failed`)", + "schema": { + "example": { + "code": 403, + "label": "code-authentication-required", + "message": "Code authentication is required" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "code-authentication-required", + "code-authentication-failed", + "password-authentication-failed" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + } + } + }, + "/search/contacts": { + "get": { + "parameters": [ + { + "description": "Search query", + "in": "query", + "name": "q", + "required": true, + "type": "string" + }, + { + "description": "Searched domain. Note: This is optional only for backwards compatibility, future versions will mandate this.", + "in": "query", + "name": "domain", + "required": false, + "type": "string" + }, + { + "description": "Number of results to return (min: 1, max: 500, default 15)", + "format": "int32", + "in": "query", + "maximum": 500, + "minimum": 1, + "name": "size", + "required": false, + "type": "integer" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/SearchResult" + } + }, + "400": { + "description": "Invalid `size` or `domain` or `q`" + } + }, + "summary": "Search for users", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "get-users-by-ids" + ], + [ + "brig", + "search-users" + ] + ] + } + }, + "/self": { + "delete": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "if the account has a verified identity, a verification code is sent and needs to be confirmed to authorise the deletion. if the account has no verified identity but a password, it must be provided. if password is correct, or if neither a verified identity nor a password exists, account deletion is scheduled immediately.", + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/DeleteUser" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Deletion is initiated." + }, + "202": { + "description": "Deletion is pending verification with a code.", + "schema": { + "$ref": "#/definitions/DeletionCodeTimeout" + } + }, + "400": { + "description": "Invalid `body`\n\nInvalid user (label: `invalid-user`)" + }, + "403": { + "description": "Team owners are not allowed to delete themselves; ask a fellow owner (label: `no-self-delete-for-team-owner`)\n\nA verification code for account deletion is still pending (label: `pending-delete`)\n\nRe-authentication via password required (label: `missing-auth`)\n\nAuthentication failed (label: `invalid-credentials`)\n\nInvalid verification code (label: `invalid-code`)", + "schema": { + "example": { + "code": 403, + "label": "no-self-delete-for-team-owner", + "message": "Team owners are not allowed to delete themselves; ask a fellow owner" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-self-delete-for-team-owner", + "pending-delete", + "missing-auth", + "invalid-credentials", + "invalid-code" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Initiate account deletion.", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "on-user-deleted-connections" + ] + ] + }, + "get": { + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/User" + } + } + }, + "summary": "Get your own profile" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/UserUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "User updated" + }, + "400": { + "description": "Invalid `body`" + }, + "403": { + "description": "Updating name is not allowed, because it is managed by SCIM (label: `managed-by-scim`)", + "schema": { + "example": { + "code": 403, + "label": "managed-by-scim", + "message": "Updating name is not allowed, because it is managed by SCIM" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "managed-by-scim" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "User not found (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "User not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update your profile.", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "on-user-deleted-connections" + ] + ] + } + }, + "/self/email": { + "delete": { + "description": "Your email address can only be removed if you also have a phone number.", + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Identity Removed" + }, + "403": { + "description": "The last user identity (email or phone number) cannot be removed. (label: `last-identity`)\n\nThe user has no password. (label: `no-password`)\n\nThe user has no verified identity (email or phone number) (label: `no-identity`)", + "schema": { + "example": { + "code": 403, + "label": "last-identity", + "message": "The last user identity (email or phone number) cannot be removed." + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "last-identity", + "no-password", + "no-identity" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Remove your email address.", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "on-user-deleted-connections" + ] + ] + } + }, + "/self/handle": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/HandleUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Handle Changed" + }, + "400": { + "description": "The given handle is invalid (label: `invalid-handle`) or `body`", + "schema": { + "example": { + "code": 400, + "label": "invalid-handle", + "message": "The given handle is invalid" + }, + "properties": { + "code": { + "enum": [ + 400 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-handle" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "403": { + "description": "The user has no verified identity (email or phone number) (label: `no-identity`)\n\nUpdating handle is not allowed, because it is managed by SCIM (label: `managed-by-scim`)", + "schema": { + "example": { + "code": 403, + "label": "no-identity", + "message": "The user has no verified identity (email or phone number)" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-identity", + "managed-by-scim" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "The given handle is already taken (label: `handle-exists`)", + "schema": { + "example": { + "code": 409, + "label": "handle-exists", + "message": "The given handle is already taken" + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "handle-exists" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Change your handle.", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "on-user-deleted-connections" + ] + ] + } + }, + "/self/locale": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/LocaleUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Local Changed" + }, + "400": { + "description": "Invalid `body`" + } + }, + "summary": "Change your locale.", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "on-user-deleted-connections" + ] + ] + } + }, + "/self/password": { + "head": { + "responses": { + "200": { + "description": "Password is set" + }, + "404": { + "description": "Password is not set" + } + }, + "summary": "Check that your password is set." + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/PasswordChange" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Password Changed" + }, + "400": { + "description": "Invalid `body`" + }, + "403": { + "description": "Authentication failed (label: `invalid-credentials`)\n\nThe user has no verified identity (email or phone number) (label: `no-identity`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-credentials", + "message": "Authentication failed" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-credentials", + "no-identity" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "For password change, new and old password must be different. (label: `password-must-differ`)", + "schema": { + "example": { + "code": 409, + "label": "password-must-differ", + "message": "For password change, new and old password must be different." + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "password-must-differ" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Change your password." + } + }, + "/self/phone": { + "delete": { + "description": "Your phone number can only be removed if you also have an email address and a password.", + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Identity Removed" + }, + "403": { + "description": "The last user identity (email or phone number) cannot be removed. (label: `last-identity`)\n\nThe user has no password. (label: `no-password`)\n\nThe user has no verified identity (email or phone number) (label: `no-identity`)", + "schema": { + "example": { + "code": 403, + "label": "last-identity", + "message": "The last user identity (email or phone number) cannot be removed." + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "last-identity", + "no-password", + "no-identity" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Remove your phone number.", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "on-user-deleted-connections" + ] + ] + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/PhoneUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "202": { + "description": "Phone updated" + }, + "400": { + "description": "Invalid mobile phone number (label: `invalid-phone`) or `body`", + "schema": { + "example": { + "code": 400, + "label": "invalid-phone", + "message": "Invalid mobile phone number" + }, + "properties": { + "code": { + "enum": [ + 400 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-phone" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "403": { + "description": "The given phone number has been blacklisted due to suspected abuse or a complaint (label: `blacklisted-phone`)", + "schema": { + "example": { + "code": 403, + "label": "blacklisted-phone", + "message": "The given phone number has been blacklisted due to suspected abuse or a complaint" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "blacklisted-phone" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "The given e-mail address or phone number is in use. (label: `key-exists`)", + "schema": { + "example": { + "code": 409, + "label": "key-exists", + "message": "The given e-mail address or phone number is in use." + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "key-exists" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Change your phone number." + } + }, + "/sso/finalize-login": { + "post": { + "description": "DEPRECATED! use /sso/metadata/:tid instead! Details: https://docs.wire.com/understand/single-sign-on/trouble-shooting.html#can-i-use-the-same-sso-login-code-for-multiple-teams", + "produces": [ + "text/plain;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "type": "string" + } + } + } + } + }, + "/sso/finalize-login/{team}": { + "post": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "team", + "required": true, + "type": "string" + } + ], + "produces": [ + "text/plain;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "type": "string" + } + }, + "400": { + "description": "Invalid `team`" + } + } + } + }, + "/sso/initiate-login/{idp}": { + "get": { + "parameters": [ + { + "in": "query", + "name": "success_redirect", + "required": false, + "type": "string" + }, + { + "in": "query", + "name": "error_redirect", + "required": false, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "idp", + "required": true, + "type": "string" + } + ], + "produces": [ + "text/html" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/FormRedirect" + } + }, + "400": { + "description": "Invalid `idp` or `error_redirect` or `success_redirect`" + } + } + }, + "head": { + "parameters": [ + { + "in": "query", + "name": "success_redirect", + "required": false, + "type": "string" + }, + { + "in": "query", + "name": "error_redirect", + "required": false, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "idp", + "required": true, + "type": "string" + } + ], + "produces": [ + "text/plain;charset=utf-8" + ], + "responses": { + "200": { + "description": "" + }, + "400": { + "description": "Invalid `idp` or `error_redirect` or `success_redirect`" + } + } + } + }, + "/sso/metadata": { + "get": { + "description": "DEPRECATED! use /sso/metadata/:tid instead! Details: https://docs.wire.com/understand/single-sign-on/trouble-shooting.html#can-i-use-the-same-sso-login-code-for-multiple-teams", + "produces": [ + "application/xml" + ], + "responses": { + "200": { + "description": "", + "schema": { + "type": "string" + } + } + } + } + }, + "/sso/metadata/{team}": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "team", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/xml" + ], + "responses": { + "200": { + "description": "", + "schema": { + "type": "string" + } + }, + "400": { + "description": "Invalid `team`" + } + } + } + }, + "/sso/settings": { + "get": { + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/SsoSettings" + } + } + } + } + }, + "/system/settings": { + "get": { + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/SystemSettings" + } + } + }, + "summary": "Returns a curated set of system configuration settings for authorized users." + } + }, + "/system/settings/unauthorized": { + "get": { + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/SystemSettingsPublic" + } + } + }, + "summary": "Returns a curated set of system configuration settings." + } + }, + "/teams": { + "get": { + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/TeamList" + } + } + }, + "summary": "Get teams (deprecated); use `GET /teams/:tid`" + }, + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/NonBindingNewTeam" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Team ID as `Location` header value", + "headers": { + "Location": { + "description": "Team ID", + "format": "uuid", + "type": "string" + } + } + }, + "400": { + "description": "Invalid `body`" + }, + "403": { + "description": "User already bound to a different team (label: `binding-exists`)\n\nUsers are not connected (label: `not-connected`)", + "schema": { + "example": { + "code": 403, + "label": "binding-exists", + "message": "User already bound to a different team" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "binding-exists", + "not-connected" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Create a new non binding team" + } + }, + "/teams/invitations/by-email": { + "head": { + "parameters": [ + { + "description": "Email address", + "in": "query", + "name": "email", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Pending invitation exists." + }, + "400": { + "description": "Invalid `email`" + }, + "404": { + "description": "No pending invitations exists. (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "No pending invitations exists." + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "Multiple conflicting invitations to different teams exists. (label: `conflicting-invitations`)", + "schema": { + "example": { + "code": 409, + "label": "conflicting-invitations", + "message": "Multiple conflicting invitations to different teams exists." + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "conflicting-invitations" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Check if there is an invitation pending given an email address." + } + }, + "/teams/invitations/info": { + "get": { + "parameters": [ + { + "description": "Invitation code", + "in": "query", + "name": "code", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Invitation info", + "schema": { + "$ref": "#/definitions/Invitation" + } + }, + "400": { + "description": "Invalid `code`\n\nInvalid invitation code. (label: `invalid-invitation-code`)" + } + }, + "summary": "Get invitation info given a code." + } + }, + "/teams/notifications": { + "get": { + "description": "This is a work-around for scalability issues with gundeck user event fan-out. It does not track all team-wide events, but only `member-join`.\nNote that `/teams/notifications` behaves differently from `/notifications`:\n- If there is a gap between the notification id requested with `since` and the available data, team queues respond with 200 and the data that could be found. They do NOT respond with status 404, but valid data in the body.\n- The notification with the id given via `since` is included in the response if it exists. You should remove this and only use it to decide whether there was a gap between your last request and this one.\n- If the notification id does *not* exist, you get the more recent events from the queue (instead of all of them). This can be done because a notification id is a UUIDv1, which is essentially a time stamp.\n- There is no corresponding `/last` end-point to get only the most recent event. That end-point was only useful to avoid having to pull the entire queue. In team queues, if you have never requested the queue before and have no prior notification id, just pull with timestamp 'now'.", + "parameters": [ + { + "description": "Notification id to start with in the response (UUIDv1)", + "format": "uuid", + "in": "query", + "name": "since", + "required": false, + "type": "string" + }, + { + "description": "Maximum number of events to return (1..10000; default: 1000)", + "format": "int32", + "in": "query", + "maximum": 10000, + "minimum": 1, + "name": "size", + "required": false, + "type": "integer" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/QueuedNotificationList" + } + }, + "400": { + "description": "Invalid `size` or `since`\n\nCould not parse notification id (must be UUIDv1). (label: `invalid-notification-id`)" + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Read recently added team members from team queue" + } + }, + "/teams/{tid}": { + "delete": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/TeamDeleteData" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "202": { + "description": "Team is scheduled for removal" + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Verification code required (label: `code-authentication-required`)\n\nCode authentication failed (label: `code-authentication-failed`)\n\nThis operation requires reauthentication (label: `access-denied`)\n\nInsufficient permissions (label: `operation-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (missing DeleteTeam) (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "code-authentication-required", + "message": "Verification code required" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "code-authentication-required", + "code-authentication-failed", + "access-denied", + "operation-denied", + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "503": { + "description": "The delete queue is full; no further delete requests can be processed at the moment (label: `queue-full`)", + "schema": { + "example": { + "code": 503, + "label": "queue-full", + "message": "The delete queue is full; no further delete requests can be processed at the moment" + }, + "properties": { + "code": { + "enum": [ + 503 + ], + "type": "integer" + }, + "label": { + "enum": [ + "queue-full" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Delete a team" + }, + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/Team" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get a team by ID" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/TeamUpdateData" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Team updated" + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Insufficient permissions (missing SetTeamData) (label: `operation-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)", + "schema": { + "example": { + "code": 403, + "label": "operation-denied", + "message": "Insufficient permissions (missing SetTeamData)" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "operation-denied", + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update team properties" + } + }, + "/teams/{tid}/conversations": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/TeamConversationList" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get team conversations" + } + }, + "/teams/{tid}/conversations/roles": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/ConversationRolesList" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get existing roles available for the given team" + } + }, + "/teams/{tid}/conversations/{cid}": { + "delete": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "cid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Conversation deleted" + }, + "400": { + "description": "Invalid `cid` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInvalid operation (label: `invalid-op`)\n\nInsufficient authorization (missing delete_conversation) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "invalid-op", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Remove a team conversation", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + }, + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "cid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/TeamConversation" + } + }, + "400": { + "description": "Invalid `cid` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Conversation not found (label: `no-conversation`)", + "schema": { + "example": { + "code": 404, + "label": "no-conversation", + "message": "Conversation not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-conversation" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get one team conversation" + } + }, + "/teams/{tid}/features": { + "get": { + "description": "Gets feature configs for a team. User must be a member of the team and have permission to view team features.", + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/AllFeatureConfigs" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Insufficient permissions (label: `operation-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)", + "schema": { + "example": { + "code": 403, + "label": "operation-denied", + "message": "Insufficient permissions" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "operation-denied", + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Gets feature configs for a team" + } + }, + "/teams/{tid}/features/appLock": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/AppLockConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for appLock" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/AppLockConfig.WithStatusNoLock" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/AppLockConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Put config for appLock" + } + }, + "/teams/{tid}/features/classifiedDomains": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/ClassifiedDomainsConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for classifiedDomains" + } + }, + "/teams/{tid}/features/conferenceCalling": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/ConferenceCallingConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for conferenceCalling" + } + }, + "/teams/{tid}/features/conversationGuestLinks": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/GuestLinksConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for conversationGuestLinks" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/GuestLinksConfig.WithStatusNoLock" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/GuestLinksConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Put config for conversationGuestLinks" + } + }, + "/teams/{tid}/features/digitalSignatures": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/DigitalSignaturesConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for digitalSignatures" + } + }, + "/teams/{tid}/features/exposeInvitationURLsToTeamAdmin": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/ExposeInvitationURLsToTeamAdminConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for exposeInvitationURLsToTeamAdmin" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ExposeInvitationURLsToTeamAdminConfig.WithStatusNoLock" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/ExposeInvitationURLsToTeamAdminConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Put config for exposeInvitationURLsToTeamAdmin" + } + }, + "/teams/{tid}/features/fileSharing": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/FileSharingConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for fileSharing" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/FileSharingConfig.WithStatusNoLock" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/FileSharingConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Put config for fileSharing" + } + }, + "/teams/{tid}/features/legalhold": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/LegalholdConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for legalhold" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/LegalholdConfig.WithStatusNoLock" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/LegalholdConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `body` or `tid`\n\nlegal hold service has not been registered for this team (label: `legalhold-not-registered`)" + }, + "403": { + "description": "legal hold cannot be disabled for whitelisted teams (label: `legalhold-disable-unimplemented`)\n\nlegal hold is not enabled for this team (label: `legalhold-not-enabled`)\n\nCannot enable legalhold on large teams (reason: for removing LH from team, we need to iterate over all members, which is only supported for teams with less than 2k members) (label: `too-large-team-for-legalhold`)\n\nVerification code required (label: `code-authentication-required`)\n\nCode authentication failed (label: `code-authentication-failed`)\n\nThis operation requires reauthentication (label: `access-denied`)\n\nInsufficient authorization (missing remove_conversation_member) (label: `action-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "legalhold-disable-unimplemented", + "message": "legal hold cannot be disabled for whitelisted teams" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-disable-unimplemented", + "legalhold-not-enabled", + "too-large-team-for-legalhold", + "code-authentication-required", + "code-authentication-failed", + "access-denied", + "action-denied", + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "500": { + "description": "legal hold service: could not block connections when resolving policy conflicts. (label: `legalhold-internal`)\n\ninternal server error: inconsistent change of user's legalhold state (label: `legalhold-illegal-op`)", + "schema": { + "example": { + "code": 500, + "label": "legalhold-internal", + "message": "legal hold service: could not block connections when resolving policy conflicts." + }, + "properties": { + "code": { + "enum": [ + 500 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-internal", + "legalhold-illegal-op" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Put config for legalhold", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/teams/{tid}/features/mls": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/MLSConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for mls" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/MLSConfig.WithStatusNoLock" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/MLSConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Put config for mls" + } + }, + "/teams/{tid}/features/mlsE2EId": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/MlsE2EIdConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for mlsE2EId" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/MlsE2EIdConfig.WithStatusNoLock" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/MlsE2EIdConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Put config for mlsE2EId" + } + }, + "/teams/{tid}/features/outlookCalIntegration": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/OutlookCalIntegrationConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for outlookCalIntegration" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/OutlookCalIntegrationConfig.WithStatusNoLock" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/OutlookCalIntegrationConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Put config for outlookCalIntegration" + } + }, + "/teams/{tid}/features/searchVisibility": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/SearchVisibilityAvailableConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for searchVisibility" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/SearchVisibilityAvailableConfig.WithStatusNoLock" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/SearchVisibilityAvailableConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Put config for searchVisibility" + } + }, + "/teams/{tid}/features/searchVisibilityInbound": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/SearchVisibilityInboundConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for searchVisibilityInbound" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/SearchVisibilityInboundConfig.WithStatusNoLock" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/SearchVisibilityInboundConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Put config for searchVisibilityInbound" + } + }, + "/teams/{tid}/features/selfDeletingMessages": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/SelfDeletingMessagesConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for selfDeletingMessages" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/SelfDeletingMessagesConfig.WithStatusNoLock" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/SelfDeletingMessagesConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Put config for selfDeletingMessages" + } + }, + "/teams/{tid}/features/sndFactorPasswordChallenge": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/SndFactorPasswordChallengeConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for sndFactorPasswordChallenge" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/SndFactorPasswordChallengeConfig.WithStatusNoLock" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/SndFactorPasswordChallengeConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Put config for sndFactorPasswordChallenge" + } + }, + "/teams/{tid}/features/sso": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/SSOConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for sso" + } + }, + "/teams/{tid}/features/validateSAMLemails": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/ValidateSAMLEmailsConfig.WithStatus" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "operation-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get config for validateSAMLemails" + } + }, + "/teams/{tid}/get-members-by-ids-using-post": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "The `has_more` field in the response body is always `false`.", + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "description": "Maximum results to be returned", + "format": "int32", + "in": "query", + "maximum": 2000, + "minimum": 1, + "name": "maxResults", + "required": false, + "type": "integer" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/UserIdList" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/TeamMemberList" + } + }, + "400": { + "description": "Invalid `body` or `maxResults` or `tid`\n\nCan only process 2000 user ids per request. (label: `too-many-uids`)" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get team members by user id list" + } + }, + "/teams/{tid}/invitations": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "description": "Invitation id to start from (ascending).", + "format": "uuid", + "in": "query", + "name": "start", + "required": false, + "type": "string" + }, + { + "description": "Number of results to return (default 100, max 500).", + "format": "int32", + "in": "query", + "maximum": 500, + "minimum": 1, + "name": "size", + "required": false, + "type": "integer" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "List of sent invitations", + "schema": { + "$ref": "#/definitions/InvitationList" + } + }, + "400": { + "description": "Invalid `size` or `start` or `tid`" + }, + "403": { + "description": "Insufficient team permissions (label: `insufficient-permissions`)", + "schema": { + "example": { + "code": 403, + "label": "insufficient-permissions", + "message": "Insufficient team permissions" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "insufficient-permissions" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "List the sent team invitations" + }, + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "Invitations are sent by email. The maximum allowed number of pending team invitations is equal to the team size.", + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/InvitationRequest" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Invitation was created and sent.", + "headers": { + "Location": { + "format": "url", + "type": "string" + } + }, + "schema": { + "$ref": "#/definitions/Invitation" + } + }, + "400": { + "description": "Invalid `body` or `tid`\n\nInvalid e-mail address. (label: `invalid-email`)" + }, + "403": { + "description": "Insufficient team permissions (label: `insufficient-permissions`)\n\nToo many team invitations for this team (label: `too-many-team-invitations`)\n\nThe given e-mail address has been blacklisted due to a permanent bounce or a complaint. (label: `blacklisted-email`)\n\nThe user has no verified identity (email or phone number) (label: `no-identity`)\n\nThis operation requires the user to have a verified email address. (label: `no-email`)", + "schema": { + "example": { + "code": 403, + "label": "insufficient-permissions", + "message": "Insufficient team permissions" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "insufficient-permissions", + "too-many-team-invitations", + "blacklisted-email", + "no-identity", + "no-email" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Create and send a new team invitation." + } + }, + "/teams/{tid}/invitations/{iid}": { + "delete": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "iid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Invitation deleted" + }, + "400": { + "description": "Invalid `iid` or `tid`" + }, + "403": { + "description": "Insufficient team permissions (label: `insufficient-permissions`)", + "schema": { + "example": { + "code": 403, + "label": "insufficient-permissions", + "message": "Insufficient team permissions" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "insufficient-permissions" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Delete a pending team invitation by ID." + }, + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "iid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Invitation", + "schema": { + "$ref": "#/definitions/Invitation" + } + }, + "400": { + "description": "Invalid `iid` or `tid`" + }, + "403": { + "description": "Insufficient team permissions (label: `insufficient-permissions`)", + "schema": { + "example": { + "code": 403, + "label": "insufficient-permissions", + "message": "Insufficient team permissions" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "insufficient-permissions" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Notification not found. (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "Notification not found." + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get a pending team invitation by ID." + } + }, + "/teams/{tid}/legalhold/consent": { + "post": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Grant consent successful" + }, + "204": { + "description": "Consent already granted" + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Invalid operation (label: `invalid-op`)\n\nInsufficient authorization (missing remove_conversation_member) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "invalid-op", + "message": "Invalid operation" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "invalid-op", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team member not found (label: `no-team-member`)", + "schema": { + "example": { + "code": 404, + "label": "no-team-member", + "message": "Team member not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "500": { + "description": "legal hold service: could not block connections when resolving policy conflicts. (label: `legalhold-internal`)\n\ninternal server error: inconsistent change of user's legalhold state (label: `legalhold-illegal-op`)", + "schema": { + "example": { + "code": 500, + "label": "legalhold-internal", + "message": "legal hold service: could not block connections when resolving policy conflicts." + }, + "properties": { + "code": { + "enum": [ + 500 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-internal", + "legalhold-illegal-op" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Consent to legal hold", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/teams/{tid}/legalhold/settings": { + "delete": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "This endpoint can lead to the following events being sent:\n- ClientRemoved event to members with a legalhold client (via brig)\n- UserLegalHoldDisabled event to contacts of members with a legalhold client (via brig)", + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/RemoveLegalHoldSettingsRequest" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "204": { + "description": "Legal hold service settings deleted" + }, + "400": { + "description": "Invalid `body` or `tid`\n\nlegal hold service has not been registered for this team (label: `legalhold-not-registered`)" + }, + "403": { + "description": "legal hold cannot be disabled for whitelisted teams (label: `legalhold-disable-unimplemented`)\n\nlegal hold is not enabled for this team (label: `legalhold-not-enabled`)\n\nInvalid operation (label: `invalid-op`)\n\nInsufficient authorization (missing remove_conversation_member) (label: `action-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)\n\nInsufficient permissions (label: `operation-denied`)\n\nVerification code required (label: `code-authentication-required`)\n\nCode authentication failed (label: `code-authentication-failed`)\n\nThis operation requires reauthentication (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "legalhold-disable-unimplemented", + "message": "legal hold cannot be disabled for whitelisted teams" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-disable-unimplemented", + "legalhold-not-enabled", + "invalid-op", + "action-denied", + "no-team-member", + "operation-denied", + "code-authentication-required", + "code-authentication-failed", + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "500": { + "description": "legal hold service: could not block connections when resolving policy conflicts. (label: `legalhold-internal`)\n\ninternal server error: inconsistent change of user's legalhold state (label: `legalhold-illegal-op`)", + "schema": { + "example": { + "code": 500, + "label": "legalhold-internal", + "message": "legal hold service: could not block connections when resolving policy conflicts." + }, + "properties": { + "code": { + "enum": [ + 500 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-internal", + "legalhold-illegal-op" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Delete legal hold service settings", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + }, + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/ViewLegalHoldService" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Insufficient permissions (label: `operation-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)", + "schema": { + "example": { + "code": 403, + "label": "operation-denied", + "message": "Insufficient permissions" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "operation-denied", + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get legal hold service settings" + }, + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/NewLegalHoldService" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Legal hold service settings created", + "schema": { + "$ref": "#/definitions/ViewLegalHoldService" + } + }, + "400": { + "description": "Invalid `body` or `tid`\n\nlegal hold service: invalid response (label: `legalhold-status-bad`)\n\nlegal hold service pubkey is invalid (label: `legalhold-invalid-key`)" + }, + "403": { + "description": "legal hold is not enabled for this team (label: `legalhold-not-enabled`)\n\nInsufficient permissions (label: `operation-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)", + "schema": { + "example": { + "code": 403, + "label": "legalhold-not-enabled", + "message": "legal hold is not enabled for this team" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-not-enabled", + "operation-denied", + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Create legal hold service settings" + } + }, + "/teams/{tid}/legalhold/{uid}": { + "delete": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "This endpoint can lead to the following events being sent:\n- ClientRemoved event to the user owning the client (via brig)\n- UserLegalHoldDisabled event to contacts of the user owning the client (via brig)", + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/DisableLegalHoldForUserRequest" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Disable legal hold successful" + }, + "204": { + "description": "Legal hold was not enabled" + }, + "400": { + "description": "Invalid `body` or `uid` or `tid`\n\nlegal hold service has not been registered for this team (label: `legalhold-not-registered`)" + }, + "403": { + "description": "Insufficient permissions (label: `operation-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)\n\nInsufficient authorization (missing remove_conversation_member) (label: `action-denied`)\n\nVerification code required (label: `code-authentication-required`)\n\nCode authentication failed (label: `code-authentication-failed`)\n\nThis operation requires reauthentication (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "operation-denied", + "message": "Insufficient permissions" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "operation-denied", + "no-team-member", + "action-denied", + "code-authentication-required", + "code-authentication-failed", + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "500": { + "description": "legal hold service: could not block connections when resolving policy conflicts. (label: `legalhold-internal`)\n\ninternal server error: inconsistent change of user's legalhold state (label: `legalhold-illegal-op`)", + "schema": { + "example": { + "code": 500, + "label": "legalhold-internal", + "message": "legal hold service: could not block connections when resolving policy conflicts." + }, + "properties": { + "code": { + "enum": [ + 500 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-internal", + "legalhold-illegal-op" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Disable legal hold for user", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + }, + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/UserLegalHoldStatusResponse" + } + }, + "400": { + "description": "Invalid `uid` or `tid`" + }, + "404": { + "description": "Team member not found (label: `no-team-member`)", + "schema": { + "example": { + "code": 404, + "label": "no-team-member", + "message": "Team member not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get legal hold status" + }, + "post": { + "description": "This endpoint can lead to the following events being sent:\n- LegalHoldClientRequested event to contacts of the user the device is requested for, if they didn't already have a legalhold client (via brig)", + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "201": { + "description": "Request device successful" + }, + "204": { + "description": "Request device already pending" + }, + "400": { + "description": "Invalid `uid` or `tid`\n\nlegal hold service has not been registered for this team (label: `legalhold-not-registered`)\n\nlegal hold service: invalid response (label: `legalhold-status-bad`)" + }, + "403": { + "description": "legal hold is not enabled for this team (label: `legalhold-not-enabled`)\n\nInsufficient permissions (label: `operation-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)\n\nInsufficient authorization (missing remove_conversation_member) (label: `action-denied`)", + "schema": { + "example": { + "code": 403, + "label": "legalhold-not-enabled", + "message": "legal hold is not enabled for this team" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-not-enabled", + "operation-denied", + "no-team-member", + "action-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team member not found (label: `no-team-member`)", + "schema": { + "example": { + "code": 404, + "label": "no-team-member", + "message": "Team member not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "user has not given consent to using legal hold (label: `legalhold-no-consent`)\n\nlegal hold is already enabled for this user (label: `legalhold-already-enabled`)", + "schema": { + "example": { + "code": 409, + "label": "legalhold-no-consent", + "message": "user has not given consent to using legal hold" + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-no-consent", + "legalhold-already-enabled" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "500": { + "description": "internal server error: inconsistent change of user's legalhold state (label: `legalhold-illegal-op`)\n\nlegal hold service: could not block connections when resolving policy conflicts. (label: `legalhold-internal`)", + "schema": { + "example": { + "code": 500, + "label": "legalhold-illegal-op", + "message": "internal server error: inconsistent change of user's legalhold state" + }, + "properties": { + "code": { + "enum": [ + 500 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-illegal-op", + "legalhold-internal" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Request legal hold device", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/teams/{tid}/legalhold/{uid}/approve": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "This endpoint can lead to the following events being sent:\n- ClientAdded event to the user owning the client (via brig)\n- UserLegalHoldEnabled event to contacts of the user owning the client (via brig)\n- ClientRemoved event to the user, if removing old client due to max number (via brig)", + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/ApproveLegalHoldForUserRequest" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Legal hold approved" + }, + "400": { + "description": "Invalid `body` or `uid` or `tid`\n\nlegal hold service has not been registered for this team (label: `legalhold-not-registered`)" + }, + "403": { + "description": "legal hold is not enabled for this team (label: `legalhold-not-enabled`)\n\nRequesting user is not a team member (label: `no-team-member`)\n\nInsufficient authorization (missing remove_conversation_member) (label: `action-denied`)\n\nYou do not have permission to access this resource (label: `access-denied`)\n\nVerification code required (label: `code-authentication-required`)\n\nCode authentication failed (label: `code-authentication-failed`)\n\nThis operation requires reauthentication (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "legalhold-not-enabled", + "message": "legal hold is not enabled for this team" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-not-enabled", + "no-team-member", + "action-denied", + "access-denied", + "code-authentication-required", + "code-authentication-failed" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "no legal hold device is registered for this user. POST /teams/:tid/legalhold/:uid/ to start the flow. (label: `legalhold-no-device-allocated`)", + "schema": { + "example": { + "code": 404, + "label": "legalhold-no-device-allocated", + "message": "no legal hold device is registered for this user. POST /teams/:tid/legalhold/:uid/ to start the flow." + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-no-device-allocated" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "409": { + "description": "legal hold is already enabled for this user (label: `legalhold-already-enabled`)", + "schema": { + "example": { + "code": 409, + "label": "legalhold-already-enabled", + "message": "legal hold is already enabled for this user" + }, + "properties": { + "code": { + "enum": [ + 409 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-already-enabled" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "412": { + "description": "legal hold cannot be approved without being in a pending state (label: `legalhold-not-pending`)", + "schema": { + "example": { + "code": 412, + "label": "legalhold-not-pending", + "message": "legal hold cannot be approved without being in a pending state" + }, + "properties": { + "code": { + "enum": [ + 412 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-not-pending" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "500": { + "description": "legal hold service: could not block connections when resolving policy conflicts. (label: `legalhold-internal`)\n\ninternal server error: inconsistent change of user's legalhold state (label: `legalhold-illegal-op`)", + "schema": { + "example": { + "code": 500, + "label": "legalhold-internal", + "message": "legal hold service: could not block connections when resolving policy conflicts." + }, + "properties": { + "code": { + "enum": [ + 500 + ], + "type": "integer" + }, + "label": { + "enum": [ + "legalhold-internal", + "legalhold-illegal-op" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Approve legal hold device", + "x-wire-makes-federated-call-to": [ + [ + "galley", + "on-conversation-updated" + ], + [ + "galley", + "on-mls-message-sent" + ], + [ + "galley", + "on-new-remote-conversation" + ] + ] + } + }, + "/teams/{tid}/members": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "description": "Maximum results to be returned", + "format": "int32", + "in": "query", + "maximum": 2000, + "minimum": 1, + "name": "maxResults", + "required": false, + "type": "integer" + }, + { + "description": "Optional, when not specified, the first page will be returned.Every returned page contains a `pagingState`, this should be supplied to retrieve the next page.", + "in": "query", + "name": "pagingState", + "required": false, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/TeamMembersPage" + } + }, + "400": { + "description": "Invalid `pagingState` or `maxResults` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get team members" + }, + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/NewTeamMember" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "" + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "cannot add more members to team when legalhold service is enabled. (label: `too-many-members-for-legalhold`)\n\nUser already bound to a different team (label: `binding-exists`)\n\nMaximum number of members per team reached (label: `too-many-team-members`)\n\nInsufficient permissions (label: `operation-denied`)\n\nUsers are not connected (label: `not-connected`)\n\nRequesting user is not a team member (label: `no-team-member`)\n\nCannot add users to binding teams, invite only (label: `binding-team`)\n\nThe specified permissions are invalid (label: `invalid-permissions`)", + "schema": { + "example": { + "code": 403, + "label": "too-many-members-for-legalhold", + "message": "cannot add more members to team when legalhold service is enabled." + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "too-many-members-for-legalhold", + "binding-exists", + "too-many-team-members", + "operation-denied", + "not-connected", + "no-team-member", + "binding-team", + "invalid-permissions" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Add a new team member" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/NewTeamMember" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "" + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Insufficient permissions (label: `operation-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)\n\nThe specified permissions are invalid (label: `invalid-permissions`)\n\nYou do not have permission to access this resource (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "operation-denied", + "message": "Insufficient permissions" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "operation-denied", + "no-team-member", + "invalid-permissions", + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team member not found (label: `no-team-member`)\n\nTeam not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team-member", + "message": "Team member not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member", + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Update an existing team member" + } + }, + "/teams/{tid}/members/csv": { + "get": { + "description": "The endpoint returns data in chunked transfer encoding. Internal server errors might result in a failed transfer instead of a 500 response.", + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "text/csv" + ], + "responses": { + "200": { + "description": "CSV of team members" + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "You do not have permission to access this resource (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "access-denied", + "message": "You do not have permission to access this resource" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "access-denied" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get all members of the team as a CSV file" + } + }, + "/teams/{tid}/members/{uid}": { + "delete": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "" + }, + "202": { + "description": "Team member scheduled for deletion" + }, + "400": { + "description": "Invalid `uid` or `tid`" + }, + "403": { + "description": "Insufficient permissions (label: `operation-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)\n\nYou do not have permission to access this resource (label: `access-denied`)\n\nVerification code required (label: `code-authentication-required`)\n\nCode authentication failed (label: `code-authentication-failed`)\n\nThis operation requires reauthentication (label: `access-denied`)", + "schema": { + "example": { + "code": 403, + "label": "operation-denied", + "message": "Insufficient permissions" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "operation-denied", + "no-team-member", + "access-denied", + "code-authentication-required", + "code-authentication-failed" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)\n\nTeam member not found (label: `no-team-member`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team", + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Remove an existing team member" + }, + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/TeamMember" + } + }, + "400": { + "description": "Invalid `uid` or `tid`" + }, + "403": { + "description": "Requesting user is not a team member (label: `no-team-member`)", + "schema": { + "example": { + "code": 403, + "label": "no-team-member", + "message": "Requesting user is not a team member" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team member not found (label: `no-team-member`)", + "schema": { + "example": { + "code": 404, + "label": "no-team-member", + "message": "Team member not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get single team member" + } + }, + "/teams/{tid}/search": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "description": "Search expression", + "in": "query", + "name": "q", + "required": false, + "type": "string" + }, + { + "collectionFormat": null, + "description": "Role filter, eg. `member,partner`. Empty list means do not filter.", + "in": "query", + "items": { + "enum": [ + "owner", + "admin", + "member", + "partner" + ], + "type": "string" + }, + "name": "frole", + "required": false, + "type": "array" + }, + { + "description": "Can be one of name, handle, email, saml_idp, managed_by, role, created_at.", + "enum": [ + "name", + "handle", + "email", + "saml_idp", + "managed_by", + "role", + "created_at" + ], + "in": "query", + "name": "sortby", + "required": false, + "type": "string" + }, + { + "description": "Can be one of asc, desc.", + "enum": [ + "asc", + "desc" + ], + "in": "query", + "name": "sortorder", + "required": false, + "type": "string" + }, + { + "description": "Number of results to return (min: 1, max: 500, default: 15)", + "format": "int32", + "in": "query", + "maximum": 500, + "minimum": 1, + "name": "size", + "required": false, + "type": "integer" + }, + { + "description": "Optional, when not specified, the first page will be returned. Every returned page contains a `paging_state`, this should be supplied to retrieve the next page.", + "in": "query", + "name": "pagingState", + "required": false, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Search results", + "schema": { + "$ref": "#/definitions/SearchResult" + } + }, + "400": { + "description": "Invalid `pagingState` or `size` or `sortorder` or `sortby` or `frole` or `q` or `tid`" + } + }, + "summary": "Browse team for members (requires add-user permission)" + } + }, + "/teams/{tid}/search-visibility": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/TeamSearchVisibilityView" + } + }, + "400": { + "description": "Invalid `tid`" + }, + "403": { + "description": "Insufficient permissions (label: `operation-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)", + "schema": { + "example": { + "code": 403, + "label": "operation-denied", + "message": "Insufficient permissions" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "operation-denied", + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Shows the value for search visibility" + }, + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/TeamSearchVisibilityView" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "204": { + "description": "Search visibility set" + }, + "400": { + "description": "Invalid `body` or `tid`" + }, + "403": { + "description": "Custom search is not available for this team (label: `team-search-visibility-not-enabled`)\n\nInsufficient permissions (label: `operation-denied`)\n\nRequesting user is not a team member (label: `no-team-member`)", + "schema": { + "example": { + "code": 403, + "label": "team-search-visibility-not-enabled", + "message": "Custom search is not available for this team" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "team-search-visibility-not-enabled", + "operation-denied", + "no-team-member" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + }, + "404": { + "description": "Team not found (label: `no-team`)", + "schema": { + "example": { + "code": 404, + "label": "no-team", + "message": "Team not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "no-team" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Sets the search visibility for the whole team" + } + }, + "/teams/{tid}/size": { + "get": { + "parameters": [ + { + "format": "uuid", + "in": "path", + "name": "tid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Number of team members", + "schema": { + "$ref": "#/definitions/TeamSize" + } + }, + "400": { + "description": "Invalid `tid`\n\nInvalid invitation code. (label: `invalid-invitation-code`)" + } + }, + "summary": "Returns the number of team members as an integer. Can be out of sync by roughly the `refresh_interval` of the ES index." + } + }, + "/users/handles": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/CheckHandles" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "List of free handles", + "schema": { + "items": { + "$ref": "#/definitions/Handle" + }, + "type": "array" + } + }, + "400": { + "description": "Invalid `body`" + } + }, + "summary": "Check availability of user handles" + } + }, + "/users/handles/{handle}": { + "head": { + "parameters": [ + { + "in": "path", + "name": "handle", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Handle is taken", + "schema": { + "example": [], + "items": {}, + "maxItems": 0, + "type": "array" + } + }, + "400": { + "description": "Invalid `handle`\n\nThe given handle is invalid (label: `invalid-handle`)" + }, + "404": { + "description": "Handle not found (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "Handle not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Check whether a user handle can be taken" + } + }, + "/users/list-clients": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/LimitedQualifiedUserIdList" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "properties": { + "qualified_user_map": { + "$ref": "#/definitions/QualifiedUserMap_Set_PubClient" + } + }, + "type": "object" + } + }, + "400": { + "description": "Invalid `body`" + } + }, + "summary": "List all clients for a set of user ids", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "get-user-clients" + ] + ] + } + }, + "/users/list-prekeys": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/QualifiedUserClients" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/QualifiedUserClientPrekeyMap" + } + }, + "400": { + "description": "Invalid `body`" + } + }, + "summary": "Given a map of domain to (map of user IDs to client IDs) return a prekey for each one. You can't request information for more users than maximum conversation size.", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "claim-multi-prekey-bundle" + ] + ] + } + }, + "/users/{uid_domain}/{uid}": { + "get": { + "parameters": [ + { + "in": "path", + "name": "uid_domain", + "required": true, + "type": "string" + }, + { + "description": "User Id", + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "User found", + "schema": { + "$ref": "#/definitions/UserProfile" + } + }, + "400": { + "description": "Invalid `uid` or `uid_domain`" + }, + "404": { + "description": "User not found (label: `not-found`)", + "schema": { + "example": { + "code": 404, + "label": "not-found", + "message": "User not found" + }, + "properties": { + "code": { + "enum": [ + 404 + ], + "type": "integer" + }, + "label": { + "enum": [ + "not-found" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get a user by Domain and UserId", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "get-users-by-ids" + ] + ] + } + }, + "/users/{uid_domain}/{uid}/clients": { + "get": { + "parameters": [ + { + "in": "path", + "name": "uid_domain", + "required": true, + "type": "string" + }, + { + "description": "User Id", + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "items": { + "$ref": "#/definitions/PubClient" + }, + "type": "array" + } + }, + "400": { + "description": "Invalid `uid` or `uid_domain`" + } + }, + "summary": "Get all of a user's clients", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "get-user-clients" + ] + ] + } + }, + "/users/{uid_domain}/{uid}/clients/{client}": { + "get": { + "parameters": [ + { + "in": "path", + "name": "uid_domain", + "required": true, + "type": "string" + }, + { + "description": "User Id", + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + }, + { + "description": "ClientId", + "in": "path", + "name": "client", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/PubClient" + } + }, + "400": { + "description": "Invalid `client` or `uid` or `uid_domain`" + } + }, + "summary": "Get a specific client of a user", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "get-user-clients" + ] + ] + } + }, + "/users/{uid_domain}/{uid}/prekeys": { + "get": { + "parameters": [ + { + "in": "path", + "name": "uid_domain", + "required": true, + "type": "string" + }, + { + "description": "User Id", + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/PrekeyBundle" + } + }, + "400": { + "description": "Invalid `uid` or `uid_domain`" + } + }, + "summary": "Get a prekey for each client of a user.", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "claim-prekey-bundle" + ] + ] + } + }, + "/users/{uid_domain}/{uid}/prekeys/{client}": { + "get": { + "parameters": [ + { + "in": "path", + "name": "uid_domain", + "required": true, + "type": "string" + }, + { + "description": "User Id", + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + }, + { + "description": "ClientId", + "in": "path", + "name": "client", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "$ref": "#/definitions/ClientPrekey" + } + }, + "400": { + "description": "Invalid `client` or `uid` or `uid_domain`" + } + }, + "summary": "Get a prekey for a specific client of a user.", + "x-wire-makes-federated-call-to": [ + [ + "brig", + "claim-prekey" + ] + ] + } + }, + "/users/{uid}/email": { + "put": { + "consumes": [ + "application/json;charset=utf-8" + ], + "description": "If the user has a pending email validation, the validation email will be resent.", + "parameters": [ + { + "description": "User Id", + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + }, + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/EmailUpdate" + } + } + ], + "produces": [ + "application/json;charset=utf-8" + ], + "responses": { + "200": { + "description": "", + "schema": { + "example": [], + "items": {}, + "maxItems": 0, + "type": "array" + } + }, + "400": { + "description": "Invalid `body` or `uid`" + } + }, + "summary": "Resend email address validation email." + } + }, + "/users/{uid}/rich-info": { + "get": { + "parameters": [ + { + "description": "User Id", + "format": "uuid", + "in": "path", + "name": "uid", + "required": true, + "type": "string" + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Rich info about the user", + "schema": { + "$ref": "#/definitions/RichInfoAssocList" + } + }, + "400": { + "description": "Invalid `uid`" + }, + "403": { + "description": "Insufficient team permissions (label: `insufficient-permissions`)", + "schema": { + "example": { + "code": 403, + "label": "insufficient-permissions", + "message": "Insufficient team permissions" + }, + "properties": { + "code": { + "enum": [ + 403 + ], + "type": "integer" + }, + "label": { + "enum": [ + "insufficient-permissions" + ], + "type": "string" + }, + "message": { + "type": "string" + } + }, + "required": [ + "code", + "label", + "message" + ], + "type": "object" + } + } + }, + "summary": "Get a user's rich info" + } + }, + "/verification-code/send": { + "post": { + "consumes": [ + "application/json;charset=utf-8" + ], + "parameters": [ + { + "in": "body", + "name": "body", + "required": true, + "schema": { + "$ref": "#/definitions/SendVerificationCode" + } + } + ], + "produces": [ + "application/json;charset=utf-8", + "application/json" + ], + "responses": { + "200": { + "description": "Verification code sent." + }, + "400": { + "description": "Invalid `body`" + } + }, + "summary": "Send a verification code to a given email address." + } + } + }, + "security": [ + { + "ZAuth": [] + } + ], + "securityDefinitions": { + "ZAuth": { + "description": "Must be a token retrieved by calling 'POST /login' or 'POST /access'. It must be presented in this format: 'Bearer \\'.", + "in": "header", + "name": "Authorization", + "type": "apiKey" + } + }, + "swagger": "2.0" +} From 81d062fab9e66765872a247afdda8138f176c797 Mon Sep 17 00:00:00 2001 From: Paolo Capriotti Date: Thu, 2 Mar 2023 16:39:07 +0100 Subject: [PATCH 15/33] Finalise API v3 --- .../Network/Wire/Client/API/Conversation.hs | 2 +- libs/wire-api/src/Wire/API/Conversation.hs | 6 +--- .../API/Routes/Public/Galley/Conversation.hs | 6 ++++ .../src/Wire/API/Routes/Public/Galley/MLS.hs | 4 ++- libs/wire-api/src/Wire/API/Routes/Version.hs | 5 +-- .../Wire/API/Golden/Generated/NewConv_user.hs | 6 ++-- services/brig/src/Brig/API/Public.hs | 6 ++-- .../brig/test/integration/API/Provider.hs | 2 +- .../brig/test/integration/API/Team/Util.hs | 6 ++-- .../test/integration/Federation/End2end.hs | 1 - services/brig/test/integration/Util.hs | 6 ++-- services/galley/src/Galley/API/Create.hs | 9 ++--- services/galley/test/integration/API.hs | 36 ++++++++++++++----- .../galley/test/integration/API/Federation.hs | 11 ++++-- services/galley/test/integration/API/MLS.hs | 14 +++++--- .../galley/test/integration/API/MLS/Util.hs | 3 +- .../test/integration/API/MessageTimer.hs | 1 + services/galley/test/integration/API/Roles.hs | 6 +++- services/galley/test/integration/API/Util.hs | 33 +++++++++-------- 19 files changed, 106 insertions(+), 57 deletions(-) diff --git a/libs/api-client/src/Network/Wire/Client/API/Conversation.hs b/libs/api-client/src/Network/Wire/Client/API/Conversation.hs index da0324b4f7e..3dc4ace781d 100644 --- a/libs/api-client/src/Network/Wire/Client/API/Conversation.hs +++ b/libs/api-client/src/Network/Wire/Client/API/Conversation.hs @@ -141,6 +141,6 @@ createConv users name = sessionRequest req rsc readBody method POST . path "conversations" . acceptJson - . json (NewConv users [] (name >>= checked) mempty Nothing Nothing Nothing Nothing roleNameWireAdmin M.ProtocolProteusTag Nothing) + . json (NewConv users [] (name >>= checked) mempty Nothing Nothing Nothing Nothing roleNameWireAdmin M.ProtocolProteusTag) $ empty rsc = status201 :| [] diff --git a/libs/wire-api/src/Wire/API/Conversation.hs b/libs/wire-api/src/Wire/API/Conversation.hs index 2b47c374bd1..ee9b7c6e2af 100644 --- a/libs/wire-api/src/Wire/API/Conversation.hs +++ b/libs/wire-api/src/Wire/API/Conversation.hs @@ -609,10 +609,7 @@ data NewConv = NewConv -- | Every member except for the creator will have this role newConvUsersRole :: RoleName, -- | The protocol of the conversation. It can be Proteus or MLS (1.0). - newConvProtocol :: ProtocolTag, - -- | ID of the client creating the conversation. Only needed for MLS - -- conversations. - newConvCreatorClient :: Maybe ClientId + newConvProtocol :: ProtocolTag } deriving stock (Eq, Show, Generic) deriving (Arbitrary) via (GenericUniform NewConv) @@ -672,7 +669,6 @@ newConvSchema sch = <|> pure roleNameWireAdmin ) <*> newConvProtocol .= protocolTagSchema - <*> newConvCreatorClient .= maybe_ (optField "creator_client" schema) where usersDesc = "List of user IDs (excluding the requestor) to be \ diff --git a/libs/wire-api/src/Wire/API/Routes/Public/Galley/Conversation.hs b/libs/wire-api/src/Wire/API/Routes/Public/Galley/Conversation.hs index 65dc97b08b0..e52c3597b7d 100644 --- a/libs/wire-api/src/Wire/API/Routes/Public/Galley/Conversation.hs +++ b/libs/wire-api/src/Wire/API/Routes/Public/Galley/Conversation.hs @@ -161,6 +161,7 @@ type ConversationAPI = :<|> Named "get-group-info" ( Summary "Get MLS group information" + :> From 'V4 :> MakesFederatedCall 'Galley "query-group-info" :> CanThrow 'ConvNotFound :> CanThrow 'MLSMissingGroupInfo @@ -331,6 +332,7 @@ type ConversationAPI = :> MakesFederatedCall 'Galley "on-conversation-created" :> Until 'V3 :> CanThrow 'ConvAccessDenied + :> CanThrow 'MLSMissingSenderClient :> CanThrow 'MLSNonEmptyMemberList :> CanThrow 'MLSNotEnabled :> CanThrow 'NotConnected @@ -339,6 +341,7 @@ type ConversationAPI = :> CanThrow 'MissingLegalholdConsent :> Description "This returns 201 when a new conversation is created, and 200 when the conversation already existed" :> ZLocalUser + :> ZOptClient :> ZConn :> "conversations" :> VersionedReqBody 'V2 '[Servant.JSON] NewConv @@ -350,6 +353,7 @@ type ConversationAPI = :> MakesFederatedCall 'Galley "on-conversation-created" :> From 'V3 :> CanThrow 'ConvAccessDenied + :> CanThrow 'MLSMissingSenderClient :> CanThrow 'MLSNonEmptyMemberList :> CanThrow 'MLSNotEnabled :> CanThrow 'NotConnected @@ -358,6 +362,7 @@ type ConversationAPI = :> CanThrow 'MissingLegalholdConsent :> Description "This returns 201 when a new conversation is created, and 200 when the conversation already existed" :> ZLocalUser + :> ZOptClient :> ZConn :> "conversations" :> ReqBody '[Servant.JSON] NewConv @@ -384,6 +389,7 @@ type ConversationAPI = :<|> Named "get-mls-self-conversation" ( Summary "Get the user's MLS self-conversation" + :> From 'V4 :> ZLocalUser :> "conversations" :> "mls-self" diff --git a/libs/wire-api/src/Wire/API/Routes/Public/Galley/MLS.hs b/libs/wire-api/src/Wire/API/Routes/Public/Galley/MLS.hs index 2d6a25e5b07..f79247fa506 100644 --- a/libs/wire-api/src/Wire/API/Routes/Public/Galley/MLS.hs +++ b/libs/wire-api/src/Wire/API/Routes/Public/Galley/MLS.hs @@ -38,6 +38,7 @@ type MLSMessagingAPI = Named "mls-welcome-message" ( Summary "Post an MLS welcome message" + :> Until 'V3 :> MakesFederatedCall 'Galley "mls-welcome" :> CanThrow 'MLSKeyPackageRefNotFound :> CanThrow 'MLSNotEnabled @@ -126,7 +127,7 @@ type MLSMessagingAPI = :> MakesFederatedCall 'Galley "on-conversation-updated" :> MakesFederatedCall 'Galley "on-new-remote-conversation" :> MakesFederatedCall 'Brig "get-mls-clients" - :> From 'V3 + :> From 'V4 :> CanThrow 'ConvAccessDenied :> CanThrow 'ConvMemberNotFound :> CanThrow 'ConvNotFound @@ -157,6 +158,7 @@ type MLSMessagingAPI = :<|> Named "mls-public-keys" ( Summary "Get public keys used by the backend to sign external proposals" + :> From 'V4 :> CanThrow 'MLSNotEnabled :> "public-keys" :> ZLocalUser diff --git a/libs/wire-api/src/Wire/API/Routes/Version.hs b/libs/wire-api/src/Wire/API/Routes/Version.hs index 519f7ee0867..6212722ca5a 100644 --- a/libs/wire-api/src/Wire/API/Routes/Version.hs +++ b/libs/wire-api/src/Wire/API/Routes/Version.hs @@ -59,7 +59,7 @@ import Wire.API.Routes.Named import Wire.API.VersionInfo -- | Version of the public API. -data Version = V0 | V1 | V2 | V3 +data Version = V0 | V1 | V2 | V3 | V4 deriving stock (Eq, Ord, Bounded, Enum, Show) deriving (FromJSON, ToJSON) via (Schema Version) @@ -69,7 +69,8 @@ instance ToSchema Version where [ element 0 V0, element 1 V1, element 2 V2, - element 3 V3 + element 3 V3, + element 4 V4 ] mkVersion :: Integer -> Maybe Version diff --git a/libs/wire-api/test/golden/Test/Wire/API/Golden/Generated/NewConv_user.hs b/libs/wire-api/test/golden/Test/Wire/API/Golden/Generated/NewConv_user.hs index 571060d758e..cbd89a82607 100644 --- a/libs/wire-api/test/golden/Test/Wire/API/Golden/Generated/NewConv_user.hs +++ b/libs/wire-api/test/golden/Test/Wire/API/Golden/Generated/NewConv_user.hs @@ -52,8 +52,7 @@ testObject_NewConv_user_1 = newConvMessageTimer = Just (Ms {ms = 3320987366258987}), newConvReceiptMode = Just (ReceiptMode {unReceiptMode = 1}), newConvUsersRole = fromJust (parseRoleName "8tp2gs7b6"), - newConvProtocol = ProtocolProteusTag, - newConvCreatorClient = Nothing + newConvProtocol = ProtocolProteusTag } testObject_NewConv_user_3 :: NewConv @@ -72,6 +71,5 @@ testObject_NewConv_user_3 = ( parseRoleName "y3otpiwu615lvvccxsq0315jj75jquw01flhtuf49t6mzfurvwe3_sh51f4s257e2x47zo85rif_xyiyfldpan3g4r6zr35rbwnzm0k" ), - newConvProtocol = ProtocolMLSTag, - newConvCreatorClient = Just (ClientId "beef") + newConvProtocol = ProtocolMLSTag } diff --git a/services/brig/src/Brig/API/Public.hs b/services/brig/src/Brig/API/Public.hs index 2018a5c71e9..008ca4d5c27 100644 --- a/services/brig/src/Brig/API/Public.hs +++ b/services/brig/src/Brig/API/Public.hs @@ -160,7 +160,7 @@ docsAPI = -- -- Dual to `internalEndpointsSwaggerDocsAPI`. versionedSwaggerDocsAPI :: Servant.Server VersionedSwaggerDocsAPI -versionedSwaggerDocsAPI (Just V3) = +versionedSwaggerDocsAPI (Just V4) = swaggerSchemaUIServer $ ( brigSwagger <> versionSwagger @@ -177,6 +177,7 @@ versionedSwaggerDocsAPI (Just V3) = versionedSwaggerDocsAPI (Just V0) = swaggerPregenUIServer $(pregenSwagger V0) versionedSwaggerDocsAPI (Just V1) = swaggerPregenUIServer $(pregenSwagger V1) versionedSwaggerDocsAPI (Just V2) = swaggerPregenUIServer $(pregenSwagger V2) +versionedSwaggerDocsAPI (Just V3) = swaggerPregenUIServer $(pregenSwagger V3) versionedSwaggerDocsAPI Nothing = versionedSwaggerDocsAPI (Just maxBound) -- | Serves Swagger docs for internal endpoints @@ -190,7 +191,7 @@ internalEndpointsSwaggerDocsAPI :: PortNumber -> S.Swagger -> Servant.Server (VersionedSwaggerDocsAPIBase service) -internalEndpointsSwaggerDocsAPI service examplePort swagger (Just V3) = +internalEndpointsSwaggerDocsAPI service examplePort swagger (Just V4) = swaggerSchemaUIServer $ swagger & adjustSwaggerForInternalEndpoint service examplePort @@ -198,6 +199,7 @@ internalEndpointsSwaggerDocsAPI service examplePort swagger (Just V3) = internalEndpointsSwaggerDocsAPI _ _ _ (Just V0) = emptySwagger internalEndpointsSwaggerDocsAPI _ _ _ (Just V1) = emptySwagger internalEndpointsSwaggerDocsAPI _ _ _ (Just V2) = emptySwagger +internalEndpointsSwaggerDocsAPI _ _ _ (Just V3) = emptySwagger internalEndpointsSwaggerDocsAPI service examplePort swagger Nothing = internalEndpointsSwaggerDocsAPI service examplePort swagger (Just maxBound) diff --git a/services/brig/test/integration/API/Provider.hs b/services/brig/test/integration/API/Provider.hs index 638dc9bd9f1..88b33eb8f66 100644 --- a/services/brig/test/integration/API/Provider.hs +++ b/services/brig/test/integration/API/Provider.hs @@ -1415,7 +1415,7 @@ createConvWithAccessRoles ars g u us = . contentJson . body (RequestBodyLBS (encode conv)) where - conv = NewConv us [] Nothing Set.empty ars Nothing Nothing Nothing roleNameWireAdmin ProtocolProteusTag Nothing + conv = NewConv us [] Nothing Set.empty ars Nothing Nothing Nothing roleNameWireAdmin ProtocolProteusTag postMessage :: Galley -> diff --git a/services/brig/test/integration/API/Team/Util.hs b/services/brig/test/integration/API/Team/Util.hs index cec99bf0b3d..b809b89c489 100644 --- a/services/brig/test/integration/API/Team/Util.hs +++ b/services/brig/test/integration/API/Team/Util.hs @@ -150,7 +150,10 @@ createUserWithTeam' brig = do "password" .= defPassword, "team" .= newTeam ] - user <- responseJsonError =<< post (brig . path "/i/users" . contentJson . body p) + user <- + responseJsonError + =<< post (brig . path "/i/users" . contentJson . body p) + getSelfProfile brig (userId user) liftIO $ assertBool "Team ID in self profile and team table do not match" (selfTeam == Just tid) @@ -233,7 +236,6 @@ createTeamConvWithRole role g tid u us mtimer = do Nothing role ProtocolProteusTag - Nothing r <- post ( g diff --git a/services/brig/test/integration/Federation/End2end.hs b/services/brig/test/integration/Federation/End2end.hs index a13db52313c..95b7787970c 100644 --- a/services/brig/test/integration/Federation/End2end.hs +++ b/services/brig/test/integration/Federation/End2end.hs @@ -274,7 +274,6 @@ testAddRemoteUsersToLocalConv brig1 galley1 brig2 galley2 = do Nothing roleNameWireAdmin ProtocolProteusTag - Nothing convId <- fmap cnvQualifiedId . responseJsonError =<< post diff --git a/services/brig/test/integration/Util.hs b/services/brig/test/integration/Util.hs index 5673a274334..07b82f458c7 100644 --- a/services/brig/test/integration/Util.hs +++ b/services/brig/test/integration/Util.hs @@ -734,12 +734,12 @@ createMLSConversation galley zusr c = do Nothing roleNameWireAdmin ProtocolMLSTag - (Just c) post $ galley . path "/conversations" . zUser zusr . zConn "conn" + . zClient c . json conv createConversation :: MonadHttp m => Galley -> UserId -> [Qualified UserId] -> m ResponseLBS @@ -756,7 +756,6 @@ createConversation galley zusr usersToAdd = do Nothing roleNameWireAdmin ProtocolProteusTag - Nothing post $ galley . path "/conversations" @@ -846,6 +845,9 @@ zAuthAccess u c = header "Z-Type" "access" . zUser u . zConn c zUser :: UserId -> Request -> Request zUser = header "Z-User" . B8.pack . show +zClient :: ClientId -> Request -> Request +zClient = header "Z-Client" . toByteString' + zConn :: ByteString -> Request -> Request zConn = header "Z-Connection" diff --git a/services/galley/src/Galley/API/Create.hs b/services/galley/src/Galley/API/Create.hs index e4f2b4b9708..3c97d909096 100644 --- a/services/galley/src/Galley/API/Create.hs +++ b/services/galley/src/Galley/API/Create.hs @@ -95,6 +95,7 @@ createGroupConversation :: Member (ErrorS 'NotConnected) r, Member (ErrorS 'MLSNotEnabled) r, Member (ErrorS 'MLSNonEmptyMemberList) r, + Member (ErrorS 'MLSMissingSenderClient) r, Member (ErrorS 'MissingLegalholdConsent) r, Member FederatorAccess r, Member GundeckAccess r, @@ -106,10 +107,11 @@ createGroupConversation :: Member P.TinyLog r ) => Local UserId -> + Maybe ClientId -> ConnId -> NewConv -> Sem r ConversationResponse -createGroupConversation lusr conn newConv = do +createGroupConversation lusr mCreatorClient conn newConv = do (nc, fromConvSize -> allUsers) <- newRegularConversation lusr newConv let tinfo = newConvTeam newConv checkCreateConvPermissions lusr newConv tinfo allUsers @@ -131,12 +133,11 @@ createGroupConversation lusr conn newConv = do conv <- E.createConversation lcnv nc -- set creator client for MLS conversations - case (convProtocol conv, newConvCreatorClient newConv) of + case (convProtocol conv, mCreatorClient) of (ProtocolProteus, _) -> pure () (ProtocolMLS mlsMeta, Just c) -> E.addMLSClients (cnvmlsGroupId mlsMeta) (tUntagged lusr) (Set.singleton (c, nullKeyPackageRef)) - (ProtocolMLS _mlsMeta, Nothing) -> - throw (InvalidPayload "Missing creator_client field when creating an MLS conversation") + (ProtocolMLS _mlsMeta, Nothing) -> throwS @'MLSMissingSenderClient now <- input -- NOTE: We only send (conversation) events to members of the conversation diff --git a/services/galley/test/integration/API.hs b/services/galley/test/integration/API.hs index 7e2bf342769..01f65d16e93 100644 --- a/services/galley/test/integration/API.hs +++ b/services/galley/test/integration/API.hs @@ -279,6 +279,7 @@ testGetConvQualifiedV2 = do responseJsonError =<< postConvQualified alice + Nothing defNewProteusConv { newConvUsers = [bob] } @@ -338,7 +339,7 @@ postConvWithRemoteUsersOk = do WS.bracketR3 c alice alex amy $ \(wsAlice, wsAlex, wsAmy) -> do (rsp, federatedRequests) <- withTempMockFederator' (mockReply ()) $ - postConvQualified alice defNewProteusConv {newConvName = checked nameMaxSize, newConvQualifiedUsers = [qAlex, qAmy, qChad, qCharlie, qDee]} + postConvQualified alice Nothing defNewProteusConv {newConvName = checked nameMaxSize, newConvQualifiedUsers = [qAlex, qAmy, qChad, qCharlie, qDee]} randomId - postConvQualified alice defNewProteusConv {newConvQualifiedUsers = [bob]} + postConvQualified alice Nothing defNewProteusConv {newConvQualifiedUsers = [bob]} !!! const 403 === statusCode postTeamConvQualifiedNoConnection :: TestM () @@ -2094,6 +2101,7 @@ postTeamConvQualifiedNoConnection = do charlie <- randomQualifiedUser postConvQualified (qUnqualified alice) + Nothing defNewProteusConv { newConvQualifiedUsers = [bob], newConvTeam = Just (ConvTeamInfo tid) @@ -2101,6 +2109,7 @@ postTeamConvQualifiedNoConnection = do !!! const 403 === statusCode postConvQualified (qUnqualified alice) + Nothing defNewProteusConv { newConvQualifiedUsers = [charlie], newConvTeam = Just (ConvTeamInfo tid) @@ -2114,6 +2123,7 @@ postConvQualifiedNonExistentDomain = do connectWithRemoteUser alice bob postConvQualified alice + Nothing defNewProteusConv {newConvQualifiedUsers = [bob]} !!! do const 422 === statusCode @@ -2134,7 +2144,7 @@ postConvQualifiedFederationNotEnabled = do -- FUTUREWORK: figure out how to use functions in the TestM monad inside withSettingsOverrides and remove this duplication postConvHelper :: MonadHttp m => (Request -> Request) -> UserId -> [Qualified UserId] -> m ResponseLBS postConvHelper g zusr newUsers = do - let conv = NewConv [] newUsers (checked "gossip") (Set.fromList []) Nothing Nothing Nothing Nothing roleNameWireAdmin ProtocolProteusTag Nothing + let conv = NewConv [] newUsers (checked "gossip") (Set.fromList []) Nothing Nothing Nothing Nothing roleNameWireAdmin ProtocolProteusTag post $ g . path "/conversations" . zUser zusr . zConn "conn" . zType "access" . json conv postSelfConvOk :: TestM () @@ -2162,7 +2172,7 @@ postConvO2OFailWithSelf :: TestM () postConvO2OFailWithSelf = do g <- viewGalley alice <- randomUser - let inv = NewConv [alice] [] Nothing mempty Nothing Nothing Nothing Nothing roleNameWireAdmin ProtocolProteusTag Nothing + let inv = NewConv [alice] [] Nothing mempty Nothing Nothing Nothing Nothing roleNameWireAdmin ProtocolProteusTag post (g . path "/conversations/one2one" . zUser alice . zConn "conn" . zType "access" . json inv) !!! do const 403 === statusCode const (Just "invalid-op") === fmap label . responseJsonUnsafe @@ -2341,6 +2351,7 @@ getConvQualifiedOk = do decodeConvId <$> postConvQualified alice + Nothing defNewProteusConv { newConvQualifiedUsers = [bob, chuck], newConvName = checked "gossip" @@ -2851,6 +2862,7 @@ deleteMembersConvLocalQualifiedOk = do decodeConvId <$> postConvQualified alice + Nothing defNewProteusConv { newConvQualifiedUsers = [qBob, qEve], newConvName = checked "federated gossip" @@ -2885,6 +2897,7 @@ deleteLocalMemberConvLocalQualifiedOk = do decodeConvId <$> postConvWithRemoteUsers alice + Nothing defNewProteusConv {newConvQualifiedUsers = [qBob, qEve]} let qconvId = Qualified convId localDomain @@ -2941,6 +2954,7 @@ deleteRemoteMemberConvLocalQualifiedOk = do fmap decodeConvId $ postConvQualified alice + Nothing defNewProteusConv {newConvQualifiedUsers = [qBob, qChad, qDee, qEve]} postConv alice' [alexDel'] (Just "gossip") [] Nothing Nothing - qconvA2 <- decodeQualifiedConvId <$> postConvWithRemoteUsers alice' defNewProteusConv {newConvQualifiedUsers = [alexDel, amy, berta, dwight]} + qconvA2 <- decodeQualifiedConvId <$> postConvWithRemoteUsers alice' Nothing defNewProteusConv {newConvQualifiedUsers = [alexDel, amy, berta, dwight]} qconvA3 <- decodeQualifiedConvId <$> postConv alice' [amy'] (Just "gossip3") [] Nothing Nothing - qconvA4 <- decodeQualifiedConvId <$> postConvWithRemoteUsers alice' defNewProteusConv {newConvQualifiedUsers = [alexDel, bart, carl]} + qconvA4 <- decodeQualifiedConvId <$> postConvWithRemoteUsers alice' Nothing defNewProteusConv {newConvQualifiedUsers = [alexDel, bart, carl]} convB1 <- randomId -- a remote conversation at 'bDomain' that Alice, AlexDel and Bart will be in convB2 <- randomId -- a remote conversation at 'bDomain' that AlexDel and Bart will be in convC1 <- randomId -- a remote conversation at 'cDomain' that AlexDel and Carl will be in @@ -4112,6 +4128,7 @@ updateTypingIndicatorFromRemoteUser = do decodeConvId <$> postConvWithRemoteUsers alice + Nothing defNewProteusConv {newConvQualifiedUsers = [qBob]} let qconvId = Qualified convId localDomain @@ -4167,6 +4184,7 @@ updateTypingIndicatorToRemoteUser = do decodeConvId <$> postConvWithRemoteUsers alice + Nothing defNewProteusConv {newConvQualifiedUsers = [qBob]} let qconvId = Qualified convId localDomain diff --git a/services/galley/test/integration/API/Federation.hs b/services/galley/test/integration/API/Federation.hs index 39c03e7feec..4b2d42233ff 100644 --- a/services/galley/test/integration/API/Federation.hs +++ b/services/galley/test/integration/API/Federation.hs @@ -106,6 +106,7 @@ getConversationsAllFound = do responseJsonError =<< postConvWithRemoteUsers bob + Nothing defNewProteusConv {newConvQualifiedUsers = [aliceQ, carlQ]} -- create a one-to-one conversation between bob and alice @@ -657,6 +658,7 @@ leaveConversationSuccess = do decodeConvId <$> postConvQualified alice + Nothing defNewProteusConv { newConvQualifiedUsers = [qBob, qChad, qDee, qEve] } @@ -844,6 +846,7 @@ sendMessage = do fmap decodeConvId $ postConvQualified aliceId + Nothing defNewProteusConv { newConvQualifiedUsers = [bob, chad] } @@ -959,6 +962,7 @@ onUserDeleted = do decodeQualifiedConvId <$> ( postConvWithRemoteUsers (tUnqualified alice) + Nothing defNewProteusConv {newConvQualifiedUsers = [tUntagged bob, alex, bart, carl]} do @@ -1052,7 +1059,7 @@ updateConversationByRemoteAdmin = do WS.bracketR c alice $ \wsAlice -> do (rsp, _federatedRequests) <- withTempMockFederator' (mockReply ()) $ do - postConvQualified alice defNewProteusConv {newConvName = checked convName, newConvQualifiedUsers = [qbob, qcharlie]} + postConvQualified alice Nothing defNewProteusConv {newConvName = checked convName, newConvQualifiedUsers = [qbob, qcharlie]} do - rsp <- postConvQualified alice (defNewMLSConv aliceClient) {newConvName = checked nameMaxSize} + rsp <- + postConvQualified + alice + (Just aliceClient) + defNewMLSConv {newConvName = checked nameMaxSize} pure rsp !!! do const 201 === statusCode const Nothing === fmap Wai.label . responseJsonError @@ -527,7 +532,7 @@ testSendAnotherUsersCommit = do testAddUsersToProteus :: TestM () testAddUsersToProteus = do [alice, bob] <- createAndConnectUsers (replicate 2 Nothing) - void $ postConvQualified (qUnqualified alice) defNewProteusConv + void $ postConvQualified (qUnqualified alice) Nothing defNewProteusConv groupId <- liftIO $ fmap (GroupId . BS.pack) (replicateM 32 (generate arbitrary)) runMLSTest $ do @@ -2107,7 +2112,8 @@ postMLSConvDisabled = do withMLSDisabled $ postConvQualified (qUnqualified alice) - (defNewMLSConv (newClientId 0)) + (Just (newClientId 0)) + defNewMLSConv !!! assertMLSNotEnabled postMLSMessageDisabled :: TestM () diff --git a/services/galley/test/integration/API/MLS/Util.hs b/services/galley/test/integration/API/MLS/Util.hs index 390764bfd36..bec43f7c1ce 100644 --- a/services/galley/test/integration/API/MLS/Util.hs +++ b/services/galley/test/integration/API/MLS/Util.hs @@ -420,7 +420,8 @@ setupMLSGroup creator = setupMLSGroupWithConv action creator =<< liftTest ( postConvQualified (ciUser creator) - (defNewMLSConv (ciClient creator)) + (Just (ciClient creator)) + defNewMLSConv ) >= checked) (fromMaybe (Set.fromList []) acc) role (Just tinfo) mtimer Nothing (fromMaybe roleNameWireAdmin convRole) ProtocolProteusTag Nothing + NewConv us [] (name >>= checked) (fromMaybe (Set.fromList []) acc) role (Just tinfo) mtimer Nothing (fromMaybe roleNameWireAdmin convRole) ProtocolProteusTag post ( g . path "/conversations" @@ -648,14 +648,14 @@ createMLSTeamConv lusr c tid users name access role timer convRole = do newConvMessageTimer = timer, newConvUsersRole = fromMaybe roleNameWireAdmin convRole, newConvReceiptMode = Nothing, - newConvProtocol = ProtocolMLSTag, - newConvCreatorClient = Just c + newConvProtocol = ProtocolMLSTag } r <- post ( g . path "/conversations" . zUser (tUnqualified lusr) + . zClient c . zConn "conn" . zType "access" . json conv @@ -679,7 +679,7 @@ createOne2OneTeamConv :: UserId -> UserId -> Maybe Text -> TeamId -> TestM Respo createOne2OneTeamConv u1 u2 n tid = do g <- viewGalley let conv = - NewConv [u2] [] (n >>= checked) mempty Nothing (Just $ ConvTeamInfo tid) Nothing Nothing roleNameWireAdmin ProtocolProteusTag Nothing + NewConv [u2] [] (n >>= checked) mempty Nothing (Just $ ConvTeamInfo tid) Nothing Nothing roleNameWireAdmin ProtocolProteusTag post $ g . path "/conversations/one2one" . zUser u1 . zConn "conn" . zType "access" . json conv postConv :: @@ -693,25 +693,26 @@ postConv :: postConv u us name a r mtimer = postConvWithRole u us name a r mtimer roleNameWireAdmin defNewProteusConv :: NewConv -defNewProteusConv = NewConv [] [] Nothing mempty Nothing Nothing Nothing Nothing roleNameWireAdmin ProtocolProteusTag Nothing +defNewProteusConv = NewConv [] [] Nothing mempty Nothing Nothing Nothing Nothing roleNameWireAdmin ProtocolProteusTag -defNewMLSConv :: ClientId -> NewConv -defNewMLSConv c = +defNewMLSConv :: NewConv +defNewMLSConv = defNewProteusConv - { newConvProtocol = ProtocolMLSTag, - newConvCreatorClient = Just c + { newConvProtocol = ProtocolMLSTag } postConvQualified :: UserId -> + Maybe ClientId -> NewConv -> TestM ResponseLBS -postConvQualified u n = do +postConvQualified u c n = do g <- viewGalley post $ g . path "/conversations" . zUser u + . maybe id zClient c . zConn "conn" . zType "access" . json n @@ -719,12 +720,13 @@ postConvQualified u n = do postConvWithRemoteUsers :: HasCallStack => UserId -> + Maybe ClientId -> NewConv -> TestM (Response (Maybe LByteString)) -postConvWithRemoteUsers u n = +postConvWithRemoteUsers u c n = fmap fst $ withTempMockFederator' (mockReply ()) $ - postConvQualified u n {newConvName = setName (newConvName n)} + postConvQualified u c n {newConvName = setName (newConvName n)} UserId -> [UserId] -> Maybe Text -> [Access] -> Maybe (Set AccessRole) -> Maybe Milliseconds -> TestM ResponseLBS postTeamConv tid u us name a r mtimer = do g <- viewGalley - let conv = NewConv us [] (name >>= checked) (Set.fromList a) r (Just (ConvTeamInfo tid)) mtimer Nothing roleNameWireAdmin ProtocolProteusTag Nothing + let conv = NewConv us [] (name >>= checked) (Set.fromList a) r (Just (ConvTeamInfo tid)) mtimer Nothing roleNameWireAdmin ProtocolProteusTag post $ g . path "/conversations" . zUser u . zConn "conn" . zType "access" . json conv deleteTeamConv :: (HasGalley m, MonadIO m, MonadHttp m) => TeamId -> ConvId -> UserId -> m ResponseLBS @@ -760,6 +762,7 @@ postConvWithRole :: postConvWithRole u members name access arole timer role = postConvQualified u + Nothing defNewProteusConv { newConvUsers = members, newConvName = name >>= checked, @@ -772,7 +775,7 @@ postConvWithRole u members name access arole timer role = postConvWithReceipt :: UserId -> [UserId] -> Maybe Text -> [Access] -> Maybe (Set AccessRole) -> Maybe Milliseconds -> ReceiptMode -> TestM ResponseLBS postConvWithReceipt u us name a r mtimer rcpt = do g <- viewGalley - let conv = NewConv us [] (name >>= checked) (Set.fromList a) r Nothing mtimer (Just rcpt) roleNameWireAdmin ProtocolProteusTag Nothing + let conv = NewConv us [] (name >>= checked) (Set.fromList a) r Nothing mtimer (Just rcpt) roleNameWireAdmin ProtocolProteusTag post $ g . path "/conversations" . zUser u . zConn "conn" . zType "access" . json conv postSelfConv :: UserId -> TestM ResponseLBS @@ -783,7 +786,7 @@ postSelfConv u = do postO2OConv :: UserId -> UserId -> Maybe Text -> TestM ResponseLBS postO2OConv u1 u2 n = do g <- viewGalley - let conv = NewConv [u2] [] (n >>= checked) mempty Nothing Nothing Nothing Nothing roleNameWireAdmin ProtocolProteusTag Nothing + let conv = NewConv [u2] [] (n >>= checked) mempty Nothing Nothing Nothing Nothing roleNameWireAdmin ProtocolProteusTag post $ g . path "/conversations/one2one" . zUser u1 . zConn "conn" . zType "access" . json conv postConnectConv :: UserId -> UserId -> Text -> Text -> Maybe Text -> TestM ResponseLBS From aad079e4014835749dfe6effc35b849219bce24a Mon Sep 17 00:00:00 2001 From: Paolo Capriotti Date: Fri, 3 Mar 2023 11:22:29 +0100 Subject: [PATCH 16/33] Use v2 for welcome messages in tests --- services/galley/test/integration/API/MLS/Util.hs | 15 ++++++++++++--- 1 file changed, 12 insertions(+), 3 deletions(-) diff --git a/services/galley/test/integration/API/MLS/Util.hs b/services/galley/test/integration/API/MLS/Util.hs index bec43f7c1ce..313b0cbc61b 100644 --- a/services/galley/test/integration/API/MLS/Util.hs +++ b/services/galley/test/integration/API/MLS/Util.hs @@ -144,12 +144,21 @@ postCommitBundle sender bundle = do . bytes bundle ) -postWelcome :: (MonadIO m, MonadHttp m, HasGalley m, HasCallStack) => UserId -> ByteString -> m ResponseLBS +-- FUTUREWORK: remove this and start using commit bundles everywhere in tests +postWelcome :: + ( MonadIO m, + MonadHttp m, + MonadReader TestSetup m, + HasCallStack + ) => + UserId -> + ByteString -> + m ResponseLBS postWelcome uid welcome = do - galley <- viewGalley + galley <- view tsUnversionedGalley post ( galley - . paths ["mls", "welcome"] + . paths ["v2", "mls", "welcome"] . zUser uid . zConn "conn" . content "message/mls" From 262ccb4278083c63d26fa1af6646e853db59c575 Mon Sep 17 00:00:00 2001 From: Paolo Capriotti Date: Fri, 3 Mar 2023 14:15:20 +0100 Subject: [PATCH 17/33] Add CHANGELOG entry --- changelog.d/1-api-changes/v3 | 1 + 1 file changed, 1 insertion(+) create mode 100644 changelog.d/1-api-changes/v3 diff --git a/changelog.d/1-api-changes/v3 b/changelog.d/1-api-changes/v3 new file mode 100644 index 00000000000..73dd27e6b47 --- /dev/null +++ b/changelog.d/1-api-changes/v3 @@ -0,0 +1 @@ +API v3 is now supported. The new MLS endpoints introduced in API v3 have been removed, and are now only available under v4. From d09820d467ed9da429072033ef7949fd66230dee Mon Sep 17 00:00:00 2001 From: Paolo Capriotti Date: Fri, 3 Mar 2023 15:46:23 +0100 Subject: [PATCH 18/33] Set v4 as the development version --- libs/wire-api/src/Wire/API/Routes/Version.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libs/wire-api/src/Wire/API/Routes/Version.hs b/libs/wire-api/src/Wire/API/Routes/Version.hs index 6212722ca5a..0c4d4f2d4da 100644 --- a/libs/wire-api/src/Wire/API/Routes/Version.hs +++ b/libs/wire-api/src/Wire/API/Routes/Version.hs @@ -100,7 +100,7 @@ supportedVersions :: [Version] supportedVersions = [minBound .. maxBound] developmentVersions :: [Version] -developmentVersions = [V3] +developmentVersions = [V4] -- | Information related to the public API version. -- From 7589b2d2ba9d26b08b5e135b90fefc22910540b7 Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Sun, 5 Mar 2023 13:58:14 +0100 Subject: [PATCH 19/33] hi ci From f02ae72e1a5ba08f5c60e6d8f837c195f0310a38 Mon Sep 17 00:00:00 2001 From: Paolo Capriotti Date: Mon, 6 Mar 2023 09:25:52 +0100 Subject: [PATCH 20/33] Update golden tests --- libs/wire-api/test/golden/testObject_NewConv_user_3.json | 1 - libs/wire-api/test/golden/testObject_NewConv_v2_user_3.json | 1 - 2 files changed, 2 deletions(-) diff --git a/libs/wire-api/test/golden/testObject_NewConv_user_3.json b/libs/wire-api/test/golden/testObject_NewConv_user_3.json index 16db2cc149a..112404a3765 100644 --- a/libs/wire-api/test/golden/testObject_NewConv_user_3.json +++ b/libs/wire-api/test/golden/testObject_NewConv_user_3.json @@ -9,7 +9,6 @@ "guest" ], "conversation_role": "y3otpiwu615lvvccxsq0315jj75jquw01flhtuf49t6mzfurvwe3_sh51f4s257e2x47zo85rif_xyiyfldpan3g4r6zr35rbwnzm0k", - "creator_client": "beef", "protocol": "mls", "qualified_users": [], "users": [] diff --git a/libs/wire-api/test/golden/testObject_NewConv_v2_user_3.json b/libs/wire-api/test/golden/testObject_NewConv_v2_user_3.json index 799071f5b35..f4db13e892d 100644 --- a/libs/wire-api/test/golden/testObject_NewConv_v2_user_3.json +++ b/libs/wire-api/test/golden/testObject_NewConv_v2_user_3.json @@ -10,7 +10,6 @@ "guest" ], "conversation_role": "y3otpiwu615lvvccxsq0315jj75jquw01flhtuf49t6mzfurvwe3_sh51f4s257e2x47zo85rif_xyiyfldpan3g4r6zr35rbwnzm0k", - "creator_client": "beef", "protocol": "mls", "qualified_users": [], "users": [] From d3b4f24d881c3cb3fb083d0dca5f6e7719393e22 Mon Sep 17 00:00:00 2001 From: Paolo Capriotti Date: Mon, 6 Mar 2023 09:26:00 +0100 Subject: [PATCH 21/33] Add assertion for v4 to version test --- libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs b/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs index 976166d0dcb..9af4812e89f 100644 --- a/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs +++ b/libs/wire-api/test/unit/Test/Wire/API/Routes/Version.hs @@ -19,3 +19,4 @@ testToPathComponent = do "v1" @=? toPathComponent V1 "v2" @=? toPathComponent V2 "v3" @=? toPathComponent V3 + "v4" @=? toPathComponent V4 From d4d6ae43f9f3b070f7ff23cd9417d511e5508e6a Mon Sep 17 00:00:00 2001 From: Paolo Capriotti Date: Mon, 6 Mar 2023 10:20:28 +0100 Subject: [PATCH 22/33] Use v2 welcome in end2end tests --- services/brig/test/integration/Federation/End2end.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/services/brig/test/integration/Federation/End2end.hs b/services/brig/test/integration/Federation/End2end.hs index 95b7787970c..02a3488c406 100644 --- a/services/brig/test/integration/Federation/End2end.hs +++ b/services/brig/test/integration/Federation/End2end.hs @@ -874,9 +874,9 @@ testSendMLSMessage brig1 brig2 galley1 galley2 cannon1 cannon2 = do !!! const 201 === statusCode post - ( galley2 - . paths - ["mls", "welcome"] + ( unversioned + . galley2 + . paths ["v2", "mls", "welcome"] . zUser (userId bob) . zConn "conn" . header "Z-Type" "access" From c21c33a5793970c6c58a788728bec941a0e508fe Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Mon, 6 Mar 2023 10:45:17 +0100 Subject: [PATCH 23/33] hi ci From 45f30a1c3c866907b285d41041ab0004875fe3b6 Mon Sep 17 00:00:00 2001 From: Stefan Matting Date: Mon, 6 Mar 2023 12:11:10 +0100 Subject: [PATCH 24/33] run-services: add status reponses to failure msg --- nix/wire-server.nix | 2 +- services/run-services | 36 +++++++++++++++++++++++++++++------- 2 files changed, 30 insertions(+), 8 deletions(-) diff --git a/nix/wire-server.nix b/nix/wire-server.nix index 8fc1b22edd1..0077c4dac96 100644 --- a/nix/wire-server.nix +++ b/nix/wire-server.nix @@ -373,7 +373,7 @@ in pkgs.netcat pkgs.niv (pkgs.python3.withPackages - (ps: with ps; [ pyyaml ])) + (ps: with ps; [ pyyaml requests ])) pkgs.rsync pkgs.wget pkgs.yq diff --git a/services/run-services b/services/run-services index 9fdbf894e6e..1cbd415f36f 100755 --- a/services/run-services +++ b/services/run-services @@ -10,17 +10,17 @@ import shutil import socket import subprocess import yaml -import urllib.request -import urllib.error import sys import tempfile import time import traceback import threading +import requests @dataclass class SpawnFailException(Exception): failed_instances: object + failing_status_responses: object class Colors: GREEN = "\x1b[38;5;10m" @@ -107,6 +107,18 @@ class Nginz: if shutil.which("nginx") is None: raise Exception("nginx not found") +@dataclass +class StatusResponse: + http_response: object = None + good_status: list[int] = None + + def __bool__(self): + if self.http_response is None: + return False + else: + return self.http_response.status_code in self.good_status + + @dataclass(frozen=True) class Instance: service: Service @@ -122,9 +134,9 @@ class Instance: if not self.service.check_status: return True try: - with urllib.request.urlopen(f"http://localhost:{self.port}/i/status") as resp: - return resp.status in [200, 204] - except urllib.error.URLError: + resp = requests.get(f"http://localhost:{self.port}/i/status") + return StatusResponse(resp, [200, 204]) + except Exception as e: return False def spawn(self, service_map, environment, suffix, domain, backend_name): @@ -323,6 +335,9 @@ def start_backend(services, suffix, domain, backend_name): # check instances to_be_checked = [instance for instance in instances if instance.exception is None] + + failing_status_responses = {} + start_time = time.time() while to_be_checked: if time.time() - start_time >= 5: @@ -333,8 +348,10 @@ def start_backend(services, suffix, domain, backend_name): to_be_checked_again = set() for instance in to_be_checked: try: - if not instance.check_status(): + status = instance.check_status() + if not status: to_be_checked_again.add(instance) + failing_status_responses[instance] = status except Exception as e: failed_instances.append(replace(instance, exception=e)) @@ -346,7 +363,7 @@ def start_backend(services, suffix, domain, backend_name): if failed_instances: cleanup_instances(instances) - raise SpawnFailException(failed_instances) + raise SpawnFailException(failed_instances, failing_status_responses) return instances @@ -439,5 +456,10 @@ if __name__ == '__main__': for instance in e.failed_instances: print(f"{instance.service.name} at port {instance.port}" + (f" ({instance.exception})" if instance.exception else "")) + + for instance, status in e.failing_status_responses.items(): + if isinstance(status, StatusResponse): + print(f"{instance.service.name} responded with status " + + "{status.http_response.status_code} and body:\n " + status.http_response.text) finally: cleanup_instances(instances) From 0bbbdd8648b9b3b6eec1b1895d20813726a8eeff Mon Sep 17 00:00:00 2001 From: Leif Battermann Date: Mon, 6 Mar 2023 12:54:08 +0000 Subject: [PATCH 25/33] using proof in test with max expiration time until 2038 --- libs/jwt-tools/test/Spec.hs | 26 +++++++++++++------------- 1 file changed, 13 insertions(+), 13 deletions(-) diff --git a/libs/jwt-tools/test/Spec.hs b/libs/jwt-tools/test/Spec.hs index 0c54be31ca6..d39cb0b3e93 100644 --- a/libs/jwt-tools/test/Spec.hs +++ b/libs/jwt-tools/test/Spec.hs @@ -25,7 +25,7 @@ main :: IO () main = hspec $ do describe "generateDpopToken FFI when passing valid inputs" $ do it "should return an access token" $ do - actual <- callFFIWithValidValues + actual <- callFFIWithValidValuesValidUntil2038 isRight actual `shouldBe` True describe "generateDpopToken FFI when passing nonsense values" $ do it "should return an error" $ do @@ -98,25 +98,25 @@ callFFIWithNonsenseValues = \MCowBQYDK2VwAyEACPvhIdimF20tOPjbb+fXJrwS2RKDp7686T90AZ0+Th8=\n\ \-----END PUBLIC KEY-----\n" -callFFIWithValidValues :: IO (Either DPoPTokenGenerationError ByteString) -callFFIWithValidValues = +callFFIWithValidValuesValidUntil2038 :: IO (Either DPoPTokenGenerationError ByteString) +callFFIWithValidValuesValidUntil2038 = runExceptT $ generateDpopToken proof uid cid domain nonce uri method maxSkewSecs expires now pem where - proof = Proof "eyJhbGciOiJFZERTQSIsInR5cCI6ImRwb3Arand0IiwiandrIjp7Imt0eSI6Ik9LUCIsImNydiI6IkVkMjU1MTkiLCJ4IjoiZzQwakI3V3pmb2ZCdkxCNVlybmlZM2ZPZU1WVGtfNlpfVnNZM0tBbnpOUSJ9fQ.eyJpYXQiOjE2Nzc2NzAwODEsImV4cCI6MTY3Nzc1NjQ4MSwibmJmIjoxNjc3NjcwMDgxLCJzdWIiOiJpbXBwOndpcmVhcHA9WldKa01qY3labUk0TW1aa05ETXlZamczTm1NM1lXSmtZVFUwWkdSaU56VS8xODllNDhjNmNhODZiNWQ0QGV4YW1wbGUub3JnIiwianRpIjoiZDE5ZWExYmItNWI0Ny00ZGJiLWE1MTktNjU0ZWRmMjU0MTQ0Iiwibm9uY2UiOiJZMkZVTjJaTlExUnZSV0l6Ympsa2RGRjFjWGhHZDJKbWFXUlRiamhXZVdRIiwiaHRtIjoiUE9TVCIsImh0dSI6Imh0dHA6Ly9sb2NhbGhvc3Q6NjQwNTQvIiwiY2hhbCI6IkJpMkpkUGk1eWVTTVdhZjA5TnJEZTVUQXFjZ0FnQmE3In0._PrwHUTS7EoAflXyNDlPNqGMbjKu-JuSXwkNPyryBQdg2gDIb20amsH05Ocih78Josz9h7lAB6FvAWsXKQB1Dw" - uid = UserId "ebd272fb-82fd-432b-876c-7abda54ddb75" - cid = ClientId 1773935321869104596 - domain = Domain "example.org" - nonce = Nonce "Y2FUN2ZNQ1RvRWIzbjlkdFF1cXhGd2JmaWRTbjhWeWQ" - uri = Uri "http://localhost:64054/" + proof = Proof "eyJhbGciOiJFZERTQSIsInR5cCI6ImRwb3Arand0IiwiandrIjp7Imt0eSI6Ik9LUCIsImNydiI6IkVkMjU1MTkiLCJ4IjoiZ0tYSHpIV3QtRUh1N2ZQbmlWMXFXWGV2Rmk1eFNKd3RNcHJlSjBjdTZ3SSJ9fQ.eyJpYXQiOjE2NzgxMDcwMDksImV4cCI6MjA4ODA3NTAwOSwibmJmIjoxNjc4MTA3MDA5LCJzdWIiOiJpbXBwOndpcmVhcHA9WXpWbE1qRTVNelpqTTJKak5EQXdOMkpsWTJJd1lXTm1OVGszTW1FMVlqTS9lYWZhMDI1NzMwM2Q0MDYwQHdpcmUuY29tIiwianRpIjoiMmQzNzAzYTItNTc4Yi00MmRjLWE2MGUtYmM0NzA3OWVkODk5Iiwibm9uY2UiOiJRV1J4T1VaUVpYVnNTMlJZYjBGS05sWkhXbGgwYUV4amJUUmpTM2M1U2xnIiwiaHRtIjoiUE9TVCIsImh0dSI6Imh0dHBzOi8vd2lyZS5leGFtcGxlLmNvbS9jbGllbnRzLzE2OTMxODQ4MzIyNTQ3NTMxODcyL2FjY2Vzcy10b2tlbiIsImNoYWwiOiJZVE5HTkRSNlRqZHFabGRRZUVGYWVrMTZWMmhqYXpCVmJ6UlFWVXRWUlZJIn0.0J2sx5y0ubZ4NwmQhbKXDj6i5UWTx3cvuTPKbeXXOJFDamr-iFtE6sOnAQT90kfTx1cEoIyDfoUkj3h5GEanAA" + uid = UserId "c5e21936-c3bc-4007-becb-0acf5972a5b3" + cid = ClientId 16931848322547531872 + domain = Domain "wire.com" + nonce = Nonce "QWRxOUZQZXVsS2RYb0FKNlZHWlh0aExjbTRjS3c5Slg" + uri = Uri "https://wire.example.com/clients/16931848322547531872/access-token" method = POST - maxSkewSecs = MaxSkewSecs 2 + maxSkewSecs = MaxSkewSecs 5 now = NowEpoch 5435234232 - expires = ExpiryEpoch $ 2082008461 + expires = ExpiryEpoch $ 2136351646 pem = PemBundle $ "-----BEGIN PRIVATE KEY-----\n\ - \MC4CAQAwBQYDK2VwBCIEIKW3jzXCsRVgnclmiTu53Pu1/r6AUmnKDoghOOVMjozQ\n\ + \MC4CAQAwBQYDK2VwBCIEIMROyHqEinw8EvFSNXp0X0suu6gMQvd9i/l9v9R9UnhH\n\ \-----END PRIVATE KEY-----\n\ \-----BEGIN PUBLIC KEY-----\n\ - \MCowBQYDK2VwAyEA7t9veqi02mPhllm44JXWga8m/l4JxUeQm3qPyMlerxY=\n\ + \MCowBQYDK2VwAyEA5pDR/Yo4pkKUIxIody2fEQ56eIOW7UqeDeF7FG7WudA=\n\ \-----END PUBLIC KEY-----\n" From 5d7b5f50f5b4c047be6662d4433f1067c74aea0a Mon Sep 17 00:00:00 2001 From: Leif Battermann Date: Mon, 6 Mar 2023 12:55:15 +0000 Subject: [PATCH 26/33] changelog --- changelog.d/5-internal/pr-3125 | 1 + 1 file changed, 1 insertion(+) create mode 100644 changelog.d/5-internal/pr-3125 diff --git a/changelog.d/5-internal/pr-3125 b/changelog.d/5-internal/pr-3125 new file mode 100644 index 00000000000..6f44a39adea --- /dev/null +++ b/changelog.d/5-internal/pr-3125 @@ -0,0 +1 @@ +Fixed test of jwt-tools Rust FFI From 5213043cbc9d2f2f086aa8470b824ed17b1d019d Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Tue, 7 Mar 2023 16:10:37 +0100 Subject: [PATCH 27/33] Fix versionMiddleware. --- libs/wire-api/src/Wire/API/Routes/Version/Wai.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs b/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs index 45358d8a861..dce525da89a 100644 --- a/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs +++ b/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs @@ -54,8 +54,8 @@ parseVersion req = do [] -> throwError NoVersion (x : xs) -> pure (x, xs) unless ("v" `T.isPrefixOf` version) $ - throwError (BadVersion version) - n <- fmapL (const NoVersion) $ parseUrlPiece version + throwError NoVersion + n <- fmapL (BadVersion . ((version <> ": ") <>)) $ parseUrlPiece version pure (rewriteRequestPure (\(_, q) _ -> (pinfo, q)) req, n) removeVersionHeader :: Request -> Request From 33aefc6d16402a3c7fe1247b2e0a2b2c2613e9f2 Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Tue, 7 Mar 2023 16:11:20 +0100 Subject: [PATCH 28/33] Test versionMiddleware. (I ran this against develop to establish this tests the right thing.) --- libs/wire-api/test/unit/Main.hs | 3 + .../unit/Test/Wire/API/Routes/Version/Wai.hs | 67 +++++++++++++++++++ libs/wire-api/wire-api.cabal | 7 ++ 3 files changed, 77 insertions(+) create mode 100644 libs/wire-api/test/unit/Test/Wire/API/Routes/Version/Wai.hs diff --git a/libs/wire-api/test/unit/Main.hs b/libs/wire-api/test/unit/Main.hs index 7c3c3249c7e..3a0b5eb11a2 100644 --- a/libs/wire-api/test/unit/Main.hs +++ b/libs/wire-api/test/unit/Main.hs @@ -21,6 +21,7 @@ module Main where import Imports +import System.IO.Unsafe (unsafePerformIO) import Test.Tasty import qualified Test.Wire.API.Call.Config as Call.Config import qualified Test.Wire.API.Conversation as Conversation @@ -33,6 +34,7 @@ import qualified Test.Wire.API.Roundtrip.HttpApiData as Roundtrip.HttpApiData import qualified Test.Wire.API.Roundtrip.MLS as Roundtrip.MLS import qualified Test.Wire.API.Routes as Routes import qualified Test.Wire.API.Routes.Version as Routes.Version +import qualified Test.Wire.API.Routes.Version.Wai as Routes.Version.Wai import qualified Test.Wire.API.Swagger as Swagger import qualified Test.Wire.API.Team.Export as Team.Export import qualified Test.Wire.API.Team.Member as Team.Member @@ -63,5 +65,6 @@ main = Conversation.tests, MLS.tests, Routes.Version.tests, + unsafePerformIO Routes.Version.Wai.tests, RawJson.tests ] diff --git a/libs/wire-api/test/unit/Test/Wire/API/Routes/Version/Wai.hs b/libs/wire-api/test/unit/Test/Wire/API/Routes/Version/Wai.hs new file mode 100644 index 00000000000..6b36a60dc81 --- /dev/null +++ b/libs/wire-api/test/unit/Test/Wire/API/Routes/Version/Wai.hs @@ -0,0 +1,67 @@ +module Test.Wire.API.Routes.Version.Wai where + +import Data.Proxy +import qualified Data.Set as Set +import Data.String.Conversions +import Data.Text as T +import Imports +import Network.HTTP.Types.Status (status200, status400) +import Network.Wai +import Servant.API +import Servant.Server +import Test.Hspec +import Test.Hspec.Wai +import Test.Hspec.Wai.Matcher +import Test.Tasty +import Test.Tasty.Hspec +import Wire.API.Routes.Version +import Wire.API.Routes.Version.Wai + +implicitVersion :: Text +implicitVersion = "0" + +sndGoodVersion :: Text +sndGoodVersion = "2" + +disabledVersion :: Text +disabledVersion = T.filter isDigit . cs $ toHeader disabledVersionTyped + +disabledVersionTyped :: Version +disabledVersionTyped = V3 + +unknownVersion :: Text +unknownVersion = "100" + +tests :: IO TestTree +tests = + testSpec "versionMiddleware" . with testApp $ do + mkTest Nothing Nothing ("good", 200) + mkTest Nothing (Just implicitVersion) ("mismatch: (Nothing,Just 0)", 400) + mkTest Nothing (Just sndGoodVersion) ("mismatch: (Nothing,Just 2)", 400) + mkTest (Just implicitVersion) (Just implicitVersion) ("good", 200) + mkTest (Just sndGoodVersion) (Just sndGoodVersion) ("good", 200) + mkTest (Just disabledVersion) (Just disabledVersion) (errmsg disabledVersion, 404) + mkTest (Just unknownVersion) (Just unknownVersion) (errmsg unknownVersion, 404) + where + errmsg v = "{\"code\":404,\"label\":\"unsupported-version\",\"message\":\"Version " <> cs v <> " is not supported\"}" + +mkTest :: Maybe Text -> Maybe Text -> (LByteString, Int) -> SpecWith (st, Application) +mkTest mv1 mv2 (msg, status) = + it ("GET " <> cs path <> " => " <> show (msg, status)) $ do + get path `shouldRespondWith` (ResponseMatcher status [] (bodyEquals msg)) + where + path :: ByteString + path = cs $ maybe "" ("/v" <>) mv1 <> "/check-version" <> maybe "" ("?version=" <>) mv2 + +type TestAPI = "check-version" :> QueryParam "version" Int :> Raw + +testApp :: IO Application +testApp = pure $ versionMiddleware (Set.singleton disabledVersionTyped) (serve (Proxy @TestAPI) testHandler) + +testHandler :: Server TestAPI +testHandler mVersionNumber = Tagged $ \req cont -> + cont $ + let headerVersion = lookup "X-Wire-API-Version" (requestHeaders req) + in if headerVersion == (cs . show <$> mVersionNumber) + then responseLBS status200 [] "good" + else responseLBS status400 [] (cs $ "mismatch: " <> show (headerVersion, mVersionNumber)) diff --git a/libs/wire-api/wire-api.cabal b/libs/wire-api/wire-api.cabal index 8571f041ddf..2428be72dcb 100644 --- a/libs/wire-api/wire-api.cabal +++ b/libs/wire-api/wire-api.cabal @@ -660,6 +660,7 @@ test-suite wire-api-tests Test.Wire.API.Roundtrip.MLS Test.Wire.API.Routes Test.Wire.API.Routes.Version + Test.Wire.API.Routes.Version.Wai Test.Wire.API.Swagger Test.Wire.API.Team.Export Test.Wire.API.Team.Member @@ -734,6 +735,9 @@ test-suite wire-api-tests , filepath , hex , hscim + , hspec + , hspec-wai + , http-types , imports , iso3166-country-codes , iso639 @@ -749,11 +753,13 @@ test-suite wire-api-tests , saml2-web-sso , schema-profunctor , servant + , servant-server , servant-swagger-ui , string-conversions , swagger2 , tasty , tasty-expected-failure + , tasty-hspec , tasty-hunit , tasty-quickcheck , text @@ -764,6 +770,7 @@ test-suite wire-api-tests , uri-bytestring , uuid , vector + , wai , wire-api , wire-message-proto-lens From 759750fe30dab91f2d825e3769266dff8490de07 Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Tue, 7 Mar 2023 16:56:59 +0100 Subject: [PATCH 29/33] Recover human-readable error messages (almost). --- libs/wire-api/src/Wire/API/Routes/Version/Wai.hs | 2 +- libs/wire-api/test/unit/Test/Wire/API/Routes/Version/Wai.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs b/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs index dce525da89a..044e9bef574 100644 --- a/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs +++ b/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs @@ -55,7 +55,7 @@ parseVersion req = do (x : xs) -> pure (x, xs) unless ("v" `T.isPrefixOf` version) $ throwError NoVersion - n <- fmapL (BadVersion . ((version <> ": ") <>)) $ parseUrlPiece version + n <- fmapL (const $ BadVersion version) $ parseUrlPiece version pure (rewriteRequestPure (\(_, q) _ -> (pinfo, q)) req, n) removeVersionHeader :: Request -> Request diff --git a/libs/wire-api/test/unit/Test/Wire/API/Routes/Version/Wai.hs b/libs/wire-api/test/unit/Test/Wire/API/Routes/Version/Wai.hs index 6b36a60dc81..ec5510f489d 100644 --- a/libs/wire-api/test/unit/Test/Wire/API/Routes/Version/Wai.hs +++ b/libs/wire-api/test/unit/Test/Wire/API/Routes/Version/Wai.hs @@ -43,7 +43,7 @@ tests = mkTest (Just disabledVersion) (Just disabledVersion) (errmsg disabledVersion, 404) mkTest (Just unknownVersion) (Just unknownVersion) (errmsg unknownVersion, 404) where - errmsg v = "{\"code\":404,\"label\":\"unsupported-version\",\"message\":\"Version " <> cs v <> " is not supported\"}" + errmsg v = "{\"code\":404,\"label\":\"unsupported-version\",\"message\":\"Version v" <> cs v <> " is not supported\"}" mkTest :: Maybe Text -> Maybe Text -> (LByteString, Int) -> SpecWith (st, Application) mkTest mv1 mv2 (msg, status) = From c454df885bd2db2d080f315db99dfd1bf04327e6 Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Tue, 7 Mar 2023 20:56:08 +0100 Subject: [PATCH 30/33] Fixup --- libs/wire-api/default.nix | 9 +++++++++ .../test/unit/Test/Wire/API/Routes/Version/Wai.hs | 2 +- 2 files changed, 10 insertions(+), 1 deletion(-) diff --git a/libs/wire-api/default.nix b/libs/wire-api/default.nix index 8b7f20896ec..e502149190a 100644 --- a/libs/wire-api/default.nix +++ b/libs/wire-api/default.nix @@ -43,6 +43,8 @@ , hex , hostname-validate , hscim +, hspec +, hspec-wai , http-api-data , http-media , http-types @@ -87,6 +89,7 @@ , tagged , tasty , tasty-expected-failure +, tasty-hspec , tasty-hunit , tasty-quickcheck , text @@ -223,6 +226,9 @@ mkDerivation { filepath hex hscim + hspec + hspec-wai + http-types imports iso3166-country-codes iso639 @@ -238,11 +244,13 @@ mkDerivation { saml2-web-sso schema-profunctor servant + servant-server servant-swagger-ui string-conversions swagger2 tasty tasty-expected-failure + tasty-hspec tasty-hunit tasty-quickcheck text @@ -253,6 +261,7 @@ mkDerivation { uri-bytestring uuid vector + wai wire-message-proto-lens ]; license = lib.licenses.agpl3Only; diff --git a/libs/wire-api/test/unit/Test/Wire/API/Routes/Version/Wai.hs b/libs/wire-api/test/unit/Test/Wire/API/Routes/Version/Wai.hs index ec5510f489d..e5107205da0 100644 --- a/libs/wire-api/test/unit/Test/Wire/API/Routes/Version/Wai.hs +++ b/libs/wire-api/test/unit/Test/Wire/API/Routes/Version/Wai.hs @@ -48,7 +48,7 @@ tests = mkTest :: Maybe Text -> Maybe Text -> (LByteString, Int) -> SpecWith (st, Application) mkTest mv1 mv2 (msg, status) = it ("GET " <> cs path <> " => " <> show (msg, status)) $ do - get path `shouldRespondWith` (ResponseMatcher status [] (bodyEquals msg)) + get path `shouldRespondWith` ResponseMatcher status [] (bodyEquals msg) where path :: ByteString path = cs $ maybe "" ("/v" <>) mv1 <> "/check-version" <> maybe "" ("?version=" <>) mv2 From e94dd83151992098952be8913c3d2be062e2c18e Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Tue, 7 Mar 2023 21:21:19 +0100 Subject: [PATCH 31/33] hi ci From 1360860a0b9aa77426f6825bc1dd13ac7d5132d0 Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Tue, 7 Mar 2023 22:22:52 +0100 Subject: [PATCH 32/33] Fix: make version parser in middleware more selective. --- libs/wire-api/src/Wire/API/Routes/Version/Wai.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs b/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs index 044e9bef574..13abf64946f 100644 --- a/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs +++ b/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs @@ -53,11 +53,16 @@ parseVersion req = do (version, pinfo) <- case pathInfo req of [] -> throwError NoVersion (x : xs) -> pure (x, xs) - unless ("v" `T.isPrefixOf` version) $ + unless (looksLikeVersion version) $ throwError NoVersion n <- fmapL (const $ BadVersion version) $ parseUrlPiece version pure (rewriteRequestPure (\(_, q) _ -> (pinfo, q)) req, n) +looksLikeVersion :: Text -> Bool +looksLikeVersion version = case T.splitAt 1 version of + ("v", T.all isDigit -> True) -> True + _ -> False + removeVersionHeader :: Request -> Request removeVersionHeader req = req From 18382ab584a5b5771c2df21117c2719c89be56ea Mon Sep 17 00:00:00 2001 From: Matthias Fischmann Date: Tue, 7 Mar 2023 22:24:50 +0100 Subject: [PATCH 33/33] bike shed. --- libs/wire-api/src/Wire/API/Routes/Version/Wai.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs b/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs index 13abf64946f..50429098358 100644 --- a/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs +++ b/libs/wire-api/src/Wire/API/Routes/Version/Wai.hs @@ -59,9 +59,7 @@ parseVersion req = do pure (rewriteRequestPure (\(_, q) _ -> (pinfo, q)) req, n) looksLikeVersion :: Text -> Bool -looksLikeVersion version = case T.splitAt 1 version of - ("v", T.all isDigit -> True) -> True - _ -> False +looksLikeVersion version = case T.splitAt 1 version of (h, t) -> h == "v" && T.all isDigit t removeVersionHeader :: Request -> Request removeVersionHeader req =