@@ -62,7 +62,6 @@ import qualified Brig.User.EJPD
6262import qualified Brig.User.Search.Index as Index
6363import Control.Error hiding (bool )
6464import Control.Lens (view )
65- import Data.Aeson hiding (json )
6665import Data.ByteString.Conversion
6766import qualified Data.ByteString.Conversion as List
6867import Data.CommaSeparatedList
@@ -72,6 +71,7 @@ import qualified Data.Map.Strict as Map
7271import Data.Qualified
7372import qualified Data.Set as Set
7473import Imports hiding (cs , head )
74+ import qualified Imports
7575import Network.HTTP.Types.Status
7676import Network.Wai (Response )
7777import Network.Wai.Predicate hiding (result , setStatus )
@@ -98,7 +98,6 @@ import qualified Wire.API.Team.Feature as ApiFt
9898import Wire.API.User
9999import Wire.API.User.Activation
100100import Wire.API.User.Client
101- import Wire.API.User.Password
102101import Wire.API.User.RichInfo
103102
104103---------------------------------------------------------------------------
@@ -107,6 +106,8 @@ import Wire.API.User.RichInfo
107106servantSitemap ::
108107 forall r p .
109108 ( Member BlacklistStore r ,
109+ Member CodeStore r ,
110+ Member PasswordResetStore r ,
110111 Member GalleyProvider r ,
111112 Member (UserPendingActivationStore p ) r
112113 ) =>
@@ -153,6 +154,8 @@ mlsAPI =
153154
154155accountAPI ::
155156 ( Member BlacklistStore r ,
157+ Member CodeStore r ,
158+ Member PasswordResetStore r ,
156159 Member GalleyProvider r ,
157160 Member (UserPendingActivationStore p ) r
158161 ) =>
@@ -166,6 +169,9 @@ accountAPI =
166169 :<|> Named @ " iGetUserStatus" getAccountStatusH
167170 :<|> Named @ " iGetUsersByEmailOrPhone" listAccountsByIdentityH
168171 :<|> Named @ " iGetUsersByIdsOrHandles" listActivatedAccountsH
172+ :<|> Named @ " iGetUserContacts" getContactListH
173+ :<|> Named @ " iGetUserActivationCode" getActivationCodeH
174+ :<|> Named @ " iGetUserPasswordResetCode" getPasswordResetCodeH
169175
170176teamsAPI :: ServerT BrigIRoutes. TeamsAPI (Handler r )
171177teamsAPI = Named @ " updateSearchVisibilityInbound" Index. updateSearchVisibilityInbound
@@ -293,9 +299,7 @@ internalSearchIndexAPI =
293299-- Sitemap (wai-route)
294300
295301sitemap ::
296- ( Member CodeStore r ,
297- Member PasswordResetStore r ,
298- Member BlacklistStore r ,
302+ ( Member BlacklistStore r ,
299303 Member BlacklistPhonePrefixStore r ,
300304 Member GalleyProvider r ,
301305 Member (UserPendingActivationStore p ) r
@@ -306,18 +310,6 @@ sitemap = unsafeCallsFed @'Brig @"on-user-deleted-connections" $ do
306310 accept " application" " json"
307311 .&. jsonRequest @ UpdateConnectionsInternal
308312
309- get " /i/users/:uid/contacts" (continue getContactListH) $
310- accept " application" " json"
311- .&. capture " uid"
312-
313- get " /i/users/activation-code" (continue getActivationCodeH) $
314- accept " application" " json"
315- .&. (param " email" ||| param " phone" )
316-
317- get " /i/users/password-reset-code" (continue getPasswordResetCodeH) $
318- accept " application" " json"
319- .&. (param " email" ||| param " phone" )
320-
321313 -- This endpoint can lead to the following events being sent:
322314 -- - UserIdentityRemoved event to target user
323315 post " /i/users/revoke-identity" (continue revokeIdentityH) $
@@ -579,42 +571,35 @@ listAccountsByIdentityH mbEmail mbPhone (fromMaybe False -> includePendingInvita
579571 u2 <- maybe (pure [] ) (\ phone -> API. lookupAccountsByIdentity (Right phone) includePendingInvitations) mbPhone
580572 pure $ u1 <> u2
581573
582- getActivationCodeH :: JSON ::: Either Email Phone -> (Handler r ) Response
583- getActivationCodeH (_ ::: emailOrPhone) = do
584- json <$> getActivationCode emailOrPhone
574+ getActivationCodeH :: Maybe Email -> Maybe Phone -> (Handler r ) GetActivationCodeResp
575+ getActivationCodeH (Just email) Nothing = getActivationCode (Left email)
576+ getActivationCodeH Nothing (Just phone) = getActivationCode (Right phone)
577+ getActivationCodeH bade badp = throwStd (badRequest (" need exactly one of email, phone: " <> Imports. cs (show (bade, badp))))
585578
586579getActivationCode :: Either Email Phone -> (Handler r ) GetActivationCodeResp
587580getActivationCode emailOrPhone = do
588581 apair <- lift . wrapClient $ API. lookupActivationCode emailOrPhone
589582 maybe (throwStd activationKeyNotFound) (pure . GetActivationCodeResp ) apair
590583
591- newtype GetActivationCodeResp = GetActivationCodeResp (ActivationKey , ActivationCode )
592-
593- instance ToJSON GetActivationCodeResp where
594- toJSON (GetActivationCodeResp (k, c)) = object [" key" .= k, " code" .= c]
595-
596584getPasswordResetCodeH ::
597585 ( Member CodeStore r ,
598586 Member PasswordResetStore r
599587 ) =>
600- JSON ::: Either Email Phone ->
601- (Handler r ) Response
602- getPasswordResetCodeH (_ ::: emailOrPhone) = do
603- maybe (throwStd (errorToWai @ 'E.InvalidPasswordResetKey )) (pure . json) =<< lift (getPasswordResetCode emailOrPhone)
588+ Maybe Email ->
589+ Maybe Phone ->
590+ (Handler r ) GetPasswordResetCodeResp
591+ getPasswordResetCodeH (Just email) Nothing = getPasswordResetCode (Left email)
592+ getPasswordResetCodeH Nothing (Just phone) = getPasswordResetCode (Right phone)
593+ getPasswordResetCodeH bade badp = throwStd (badRequest (" need exactly one of email, phone: " <> Imports. cs (show (bade, badp))))
604594
605595getPasswordResetCode ::
606596 ( Member CodeStore r ,
607597 Member PasswordResetStore r
608598 ) =>
609599 Either Email Phone ->
610- (AppT r ) ( Maybe GetPasswordResetCodeResp )
600+ (Handler r ) GetPasswordResetCodeResp
611601getPasswordResetCode emailOrPhone =
612- GetPasswordResetCodeResp <$$> API. lookupPasswordResetCode emailOrPhone
613-
614- newtype GetPasswordResetCodeResp = GetPasswordResetCodeResp (PasswordResetKey , PasswordResetCode )
615-
616- instance ToJSON GetPasswordResetCodeResp where
617- toJSON (GetPasswordResetCodeResp (k, c)) = object [" key" .= k, " code" .= c]
602+ (GetPasswordResetCodeResp <$$> lift (API. lookupPasswordResetCode emailOrPhone)) >>= maybe (throwStd (errorToWai @ 'E.InvalidPasswordResetKey )) pure
618603
619604changeAccountStatusH :: UserId -> AccountStatusUpdate -> (Handler r ) NoContent
620605changeAccountStatusH usr (suStatus -> status) = do
@@ -798,7 +783,5 @@ checkHandleInternalH =
798783 API. CheckHandleFound -> pure $ setStatus status200 empty
799784 API. CheckHandleNotFound -> pure $ setStatus status404 empty
800785
801- getContactListH :: JSON ::: UserId -> (Handler r ) Response
802- getContactListH (_ ::: uid) = do
803- contacts <- lift . wrapClient $ API. lookupContactList uid
804- pure $ json $ UserIds contacts
786+ getContactListH :: UserId -> (Handler r ) UserIds
787+ getContactListH uid = lift . wrapClient $ UserIds <$> API. lookupContactList uid
0 commit comments