Skip to content

Commit

Permalink
Move post otr message endpoint to servant
Browse files Browse the repository at this point in the history
The tests are not enough, they don't test lists being sent to ignore_missing and
report_missing
  • Loading branch information
akshaymankar committed May 31, 2021
1 parent a843ef2 commit 480340f
Show file tree
Hide file tree
Showing 6 changed files with 190 additions and 150 deletions.
92 changes: 38 additions & 54 deletions libs/wire-api/src/Wire/API/Message.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,11 +42,12 @@ module Wire.API.Message
)
where

import Data.Aeson
import qualified Data.Aeson as A
import Data.Id
import Data.Json.Util
import Data.Schema
import qualified Data.Swagger as S
import qualified Data.Swagger.Build.Api as Doc
import Data.Time
import Imports
import Wire.API.Arbitrary (Arbitrary (..), GenericUniform (..))
import Wire.API.User.Client (UserClientMap (..), UserClients (..), modelOtrClientMap, modelUserClients)
Expand All @@ -69,6 +70,7 @@ data NewOtrMessage = NewOtrMessage
}
deriving stock (Eq, Show, Generic)
deriving (Arbitrary) via (GenericUniform NewOtrMessage)
deriving (A.ToJSON, A.FromJSON, S.ToSchema) via (Schema NewOtrMessage)

modelNewOtrMessage :: Doc.Model
modelNewOtrMessage = Doc.defineModel "NewOtrMessage" $ do
Expand All @@ -95,28 +97,17 @@ modelNewOtrMessage = Doc.defineModel "NewOtrMessage" $ do
Doc.description "List of user IDs"
Doc.optional

instance ToJSON NewOtrMessage where
toJSON otr =
object $
"sender" .= newOtrSender otr
# "recipients" .= newOtrRecipients otr
# "native_push" .= newOtrNativePush otr
# "transient" .= newOtrTransient otr
# "native_priority" .= newOtrNativePriority otr
# "data" .= newOtrData otr
# "report_missing" .= newOtrReportMissing otr
# []

instance FromJSON NewOtrMessage where
parseJSON = withObject "new-otr-message" $ \o ->
NewOtrMessage
<$> o .: "sender"
<*> o .: "recipients"
<*> o .:? "native_push" .!= True
<*> o .:? "transient" .!= False
<*> o .:? "native_priority"
<*> o .:? "data"
<*> o .:? "report_missing"
instance ToSchema NewOtrMessage where
schema =
object "new-otr-message" $
NewOtrMessage
<$> newOtrSender .= field "sender" schema
<*> newOtrRecipients .= field "recipients" schema
<*> newOtrNativePush .= (field "native_push" schema <|> pure True)
<*> newOtrTransient .= (field "transient" schema <|> pure False)
<*> newOtrNativePriority .= opt (field "native_priority" schema)
<*> newOtrData .= opt (field "data" schema)
<*> newOtrReportMissing .= opt (field "report_missing" (array schema))

--------------------------------------------------------------------------------
-- Priority
Expand All @@ -134,6 +125,7 @@ instance FromJSON NewOtrMessage where
data Priority = LowPriority | HighPriority
deriving stock (Eq, Show, Ord, Enum, Generic)
deriving (Arbitrary) via (GenericUniform Priority)
deriving (A.ToJSON, A.FromJSON, S.ToSchema) via Schema Priority

typePriority :: Doc.DataType
typePriority =
Expand All @@ -143,15 +135,13 @@ typePriority =
"high"
]

instance ToJSON Priority where
toJSON LowPriority = String "low"
toJSON HighPriority = String "high"

instance FromJSON Priority where
parseJSON = withText "Priority" $ \case
"low" -> pure LowPriority
"high" -> pure HighPriority
x -> fail $ "Invalid push priority: " ++ show x
instance ToSchema Priority where
schema =
enum @Text "Priority" $
mconcat
[ element "low" LowPriority,
element "high" HighPriority
]

--------------------------------------------------------------------------------
-- Recipients
Expand All @@ -161,7 +151,7 @@ newtype OtrRecipients = OtrRecipients
{ otrRecipientsMap :: UserClientMap Text
}
deriving stock (Eq, Show)
deriving newtype (ToJSON, FromJSON, Semigroup, Monoid, Arbitrary)
deriving newtype (ToSchema, A.ToJSON, A.FromJSON, Semigroup, Monoid, Arbitrary)

-- FUTUREWORK: Remove when 'NewOtrMessage' has ToSchema
modelOtrRecipients :: Doc.Model
Expand Down Expand Up @@ -189,22 +179,24 @@ data OtrFilterMissing
deriving stock (Eq, Show, Generic)
deriving (Arbitrary) via (GenericUniform OtrFilterMissing)

-- TODO: Verify if the change from UTCTime to UTCTimeMillis has any significant
-- effect. The ToJSON instance was already translating it to millis and fromJSON
-- didn't care for it (as it is never being sent by clients)
data ClientMismatch = ClientMismatch
{ cmismatchTime :: UTCTime,
{ cmismatchTime :: UTCTimeMillis,
-- | Clients that the message /should/ have been encrypted for, but wasn't.
missingClients :: UserClients,
-- | Clients that the message /should not/ have been encrypted for, but was.
redundantClients :: UserClients,
deletedClients :: UserClients
}
deriving stock (Eq, Show, Generic)
deriving (A.ToJSON, A.FromJSON, S.ToSchema) via Schema ClientMismatch

instance Arbitrary ClientMismatch where
arbitrary =
ClientMismatch
<$> (milli <$> arbitrary) <*> arbitrary <*> arbitrary <*> arbitrary
where
milli = fromUTCTimeMillis . toUTCTimeMillis
<$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary

modelClientMismatch :: Doc.Model
modelClientMismatch = Doc.defineModel "ClientMismatch" $ do
Expand All @@ -218,19 +210,11 @@ modelClientMismatch = Doc.defineModel "ClientMismatch" $ do
Doc.property "deleted" (Doc.ref modelUserClients) $
Doc.description "Map of deleted clients per user."

instance ToJSON ClientMismatch where
toJSON m =
object
[ "time" .= toUTCTimeMillis (cmismatchTime m),
"missing" .= missingClients m,
"redundant" .= redundantClients m,
"deleted" .= deletedClients m
]

instance FromJSON ClientMismatch where
parseJSON = withObject "ClientMismatch" $ \o ->
ClientMismatch
<$> o .: "time"
<*> o .: "missing"
<*> o .: "redundant"
<*> o .: "deleted"
instance ToSchema ClientMismatch where
schema =
object "ClientMismatch" $
ClientMismatch
<$> cmismatchTime .= field "time" schema
<*> missingClients .= field "missing" schema
<*> redundantClients .= field "redundant" schema
<*> deletedClients .= field "deleted" schema
99 changes: 97 additions & 2 deletions libs/wire-api/src/Wire/API/Routes/Public/Galley.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,8 +21,9 @@
module Wire.API.Routes.Public.Galley where

import Data.CommaSeparatedList
import Data.Id (ConvId, TeamId)
import Data.Id (ConvId, TeamId, UserId)
import Data.Range
import qualified Data.Set as Set
import Data.Swagger
import Imports hiding (head)
import Servant hiding (Handler, JSON, addHeader, contentType, respond)
Expand All @@ -34,6 +35,7 @@ import qualified Wire.API.Conversation as Public
import qualified Wire.API.Conversation.Role as Public
import qualified Wire.API.Event.Conversation as Public
import qualified Wire.API.Event.Team as Public ()
import qualified Wire.API.Message as Public
import Wire.API.Routes.Public (EmptyResult, ZConn, ZUser)
import qualified Wire.API.Team.Conversation as Public

Expand All @@ -47,6 +49,11 @@ type UpdateResponses =
NoContent
]

type PostOtrResponses =
'[ WithStatus 201 Public.ClientMismatch,
WithStatus 412 Public.ClientMismatch
]

-- FUTUREWORK: Make a PR to the servant-swagger package with this instance
instance ToSchema Servant.NoContent where
declareNamedSchema _ = declareNamedSchema (Proxy @())
Expand Down Expand Up @@ -205,11 +212,99 @@ data Api routes = Api
:> Capture "tid" TeamId
:> "conversations"
:> Capture "cid" ConvId
:> Delete '[] (EmptyResult 200)
:> Delete '[] (EmptyResult 200),
-- | This endpoint can lead to the following events being sent:
--
-- - OtrMessageAdd event to recipients
--
-- TODO: Add 404 for conv not found
-- TODO: Add 403 for unknown sending client
postOtrMessage ::
routes
:- Summary "Post an encrypted message to a conversation (accepts JSON)"
:> ZUser
:> ZConn
:> "conversations"
:> Capture "cnv" ConvId
:> QueryParam "ignore_missing" IgnoreMissing
:> QueryParam "report_missing" ReportMissing
:> "otr"
:> "messages"
:> ReqBody '[Servant.JSON] Public.NewOtrMessage
:> UVerb 'POST '[Servant.JSON] PostOtrResponses
}
deriving (Generic)

type ServantAPI = ToServantApi Api

data IgnoreMissing
= IgnoreMissingAll
| IgnoreMissingList (Set UserId)
deriving (Show, Eq)

-- TODO: Fill this in
instance ToParamSchema IgnoreMissing where
toParamSchema _ = mempty

-- TODO: Test what happens when empty string is sent, is it backwards compatible?
-- TODO: Test what happens when true and false have different cases, is it backwards compatible?
instance FromHttpApiData IgnoreMissing where
parseQueryParam = \case
"true" -> Right IgnoreMissingAll
"false" -> Right $ IgnoreMissingList mempty
list -> IgnoreMissingList . Set.fromList . fromCommaSeparatedList <$> parseQueryParam list

data ReportMissing
= ReportMissingAll
| ReportMissingList (Set UserId)

instance ToParamSchema ReportMissing where
toParamSchema _ = mempty

-- TODO: Test what happens when empty string is sent, is it backwards compatible?
-- TODO: Test what happens when true and false have different cases, is it backwards compatible?
instance FromHttpApiData ReportMissing where
parseQueryParam = \case
"true" -> Right ReportMissingAll
"false" -> Right $ ReportMissingList mempty
list -> ReportMissingList . Set.fromList . fromCommaSeparatedList <$> parseQueryParam list

swaggerDoc :: Swagger
swaggerDoc = toSwagger (Proxy @ServantAPI)

-- post "/conversations/:cnv/otr/messages" (continue Update.postOtrMessageH) $
-- zauthUserId
-- .&. zauthConnId
-- .&. capture "cnv"
-- .&. def Public.OtrReportAllMissing filterMissing
-- .&. jsonRequest @Public.NewOtrMessage
-- document "POST" "postOtrMessage" $ do
-- summary "Post an encrypted message to a conversation (accepts JSON)"
-- parameter Path "cnv" bytes' $
-- description "Conversation ID"
-- parameter Query "ignore_missing" bool' $ do
-- description
-- "Force message delivery even when clients are missing. \
-- \NOTE: can also be a comma-separated list of user IDs, \
-- \in which case it specifies who exactly is allowed to \
-- \have missing clients."
-- optional
-- parameter Query "report_missing" bool' $ do
-- description
-- "Don't allow message delivery when clients are missing \
-- \('ignore_missing' takes precedence when present). \
-- \NOTE: can also be a comma-separated list of user IDs, \
-- \in which case it specifies who exactly is forbidden from \
-- \having missing clients. \
-- \To support large lists of user IDs exceeding the allowed \
-- \URL length, you can also put this list in the body, in \
-- \the optional field 'report_missing'. That body field takes \
-- \prhttps://wearezeta.atlassian.net/wiki/spaces/ENGINEERIN/pages/376439791/Use%2Bcase%2BClassified%2Bdomains?focusedCommentId=384861252#comment-384861252ecedence over both query params."
-- optional
-- body (ref Public.modelNewOtrMessage) $
-- description "JSON body"
-- returns (ref Public.modelClientMismatch)
-- response 201 "Message posted" end
-- response 412 "Missing clients" end
-- errorResponse Error.convNotFound
-- errorResponse Error.unknownClient
35 changes: 12 additions & 23 deletions libs/wire-api/src/Wire/API/User/Client.hs
Original file line number Diff line number Diff line change
Expand Up @@ -334,46 +334,35 @@ newtype UserClients = UserClients
}
deriving stock (Eq, Show, Generic)
deriving newtype (Semigroup, Monoid)
deriving (ToJSON, FromJSON, Swagger.ToSchema) via Schema UserClients

mkUserClients :: [(UserId, [ClientId])] -> UserClients
mkUserClients xs = UserClients $ Map.fromList (xs <&> second Set.fromList)

instance Swagger.ToSchema UserClients where
declareNamedSchema _ = do
mapSch <- Swagger.declareSchema (Proxy @(Map UserId (Set ClientId)))
return $
Swagger.NamedSchema (Just "UserClients") $
mapSch
& Swagger.description ?~ "Map of user id to list of client ids."
& Swagger.example
-- TODO: Is using genericToSchema OK here? Maybe it is better to write a `set`
-- combinator?
instance ToSchema UserClients where
schema =
addDoc . named "UserClients" $ UserClients <$> userClients .= map_ (genericToSchema @(Set ClientId))
where
addDoc sch =
sch
& Swagger.schema . Swagger.description ?~ "Map of user id to list of client ids."
& Swagger.schema . Swagger.example
?~ toJSON
( Map.fromList
[ (generateExample @UserId, [newClientId 1684636986166846496, newClientId 4940483633899001999]),
(generateExample @UserId, [newClientId 6987438498444556166, newClientId 7940473633839002939])
]
)

-- FUTUREWORK: Remove when 'NewOtrMessage' has ToSchema
-- TODO: Remove when 'NewOtrMessage' has ToSchema
modelUserClients :: Doc.Model
modelUserClients =
Doc.defineModel "UserClients" $
Doc.property "" (Doc.unique $ Doc.array Doc.bytes') $
Doc.description "Map of user IDs to sets of client IDs ({ UserId: [ClientId] })."

instance ToJSON UserClients where
toJSON =
toJSON . Map.foldrWithKey' fn Map.empty . userClients
where
fn u c m =
let k = Text.E.decodeLatin1 (toASCIIBytes (toUUID u))
in Map.insert k c m

instance FromJSON UserClients where
parseJSON =
A.withObject "UserClients" (fmap UserClients . foldrM fn Map.empty . HashMap.toList)
where
fn (k, v) m = Map.insert <$> parseJSON (A.String k) <*> parseJSON v <*> pure m

instance Arbitrary UserClients where
arbitrary = UserClients <$> mapOf' arbitrary (setOf' arbitrary)

Expand Down
Loading

0 comments on commit 480340f

Please sign in to comment.