Skip to content

Commit 371f02a

Browse files
committed
post "/push/tokens"
1 parent 6d97233 commit 371f02a

File tree

13 files changed

+273
-105
lines changed

13 files changed

+273
-105
lines changed

libs/wire-api/src/Wire/API/Asset.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -416,7 +416,7 @@ instance
416416
fromUnion (Z (I _)) = Nothing
417417
fromUnion (S (Z (I loc))) = Just (LocalAsset loc)
418418
fromUnion (S (S (Z (I asset)))) = Just (RemoteAsset asset)
419-
fromUnion (S (S (S x))) = case x of {}
419+
fromUnion (S (S (S x))) = case x of
420420

421421
makeLenses ''Asset'
422422
makeLenses ''AssetSettings
Lines changed: 40 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,40 @@
1+
-- This file is part of the Wire Server implementation.
2+
--
3+
-- Copyright (C) 2022 Wire Swiss GmbH <[email protected]>
4+
--
5+
-- This program is free software: you can redistribute it and/or modify it under
6+
-- the terms of the GNU Affero General Public License as published by the Free
7+
-- Software Foundation, either version 3 of the License, or (at your option) any
8+
-- later version.
9+
--
10+
-- This program is distributed in the hope that it will be useful, but WITHOUT
11+
-- ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
12+
-- FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more
13+
-- details.
14+
--
15+
-- You should have received a copy of the GNU Affero General Public License along
16+
-- with this program. If not, see <https://www.gnu.org/licenses/>.
17+
18+
module Wire.API.Error.Gundeck where
19+
20+
import Wire.API.Error
21+
22+
data GundeckError
23+
= AddTokenErrorNoBudget
24+
| AddTokenErrorNotFound
25+
| AddTokenErrorInvalid
26+
| AddTokenErrorTooLong
27+
| AddTokenErrorMetadataTooLong
28+
29+
instance KnownError (MapError e) => IsSwaggerError (e :: GundeckError) where
30+
addToSwagger = addStaticErrorToSwagger @(MapError e)
31+
32+
type instance MapError 'AddTokenErrorNoBudget = 'StaticError 413 "sns-thread-budget-reached" "Too many concurrent calls to SNS; is SNS down?"
33+
34+
type instance MapError 'AddTokenErrorNotFound = 'StaticError 404 "app-not-found" "App does not exist"
35+
36+
type instance MapError 'AddTokenErrorInvalid = 'StaticError 404 "invalid-token" "Invalid push token"
37+
38+
type instance MapError 'AddTokenErrorTooLong = 'StaticError 413 "token-too-long" "Push token length must be < 8192 for GCM or 400 for APNS"
39+
40+
type instance MapError 'AddTokenErrorMetadataTooLong = 'StaticError 413 "metadata-too-long" "Tried to add token to endpoint resulting in metadata length > 2048"

libs/wire-api/src/Wire/API/Push/V2/Token.hs

Lines changed: 53 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -41,12 +41,15 @@ module Wire.API.Push.V2.Token
4141
)
4242
where
4343

44-
import Control.Lens (makeLenses)
45-
import Data.Aeson
44+
import Control.Lens (makeLenses, (?~))
45+
import qualified Data.Aeson as A
4646
import Data.Attoparsec.ByteString (takeByteString)
4747
import Data.ByteString.Conversion
4848
import Data.Id
49-
import Data.Json.Util
49+
import Data.Proxy (Proxy (Proxy))
50+
import Data.Schema
51+
import Data.Swagger (ToParamSchema)
52+
import qualified Data.Swagger as S
5053
import qualified Data.Swagger.Build.Api as Doc
5154
import Imports
5255
import Wire.Arbitrary (Arbitrary, GenericUniform (..))
@@ -59,19 +62,20 @@ newtype PushTokenList = PushTokenList
5962
}
6063
deriving stock (Eq, Show)
6164
deriving newtype (Arbitrary)
65+
deriving (A.ToJSON, A.FromJSON) via (Schema PushTokenList)
6266

67+
-- todo(leif): remove when last endpoint is servantified
6368
modelPushTokenList :: Doc.Model
6469
modelPushTokenList = Doc.defineModel "PushTokenList" $ do
6570
Doc.description "List of Native Push Tokens"
6671
Doc.property "tokens" (Doc.array (Doc.ref modelPushToken)) $
6772
Doc.description "Push tokens"
6873

69-
instance ToJSON PushTokenList where
70-
toJSON (PushTokenList t) = object ["tokens" .= t]
71-
72-
instance FromJSON PushTokenList where
73-
parseJSON = withObject "PushTokenList" $ \p ->
74-
PushTokenList <$> p .: "tokens"
74+
instance ToSchema PushTokenList where
75+
schema =
76+
objectWithDocModifier "PushTokenList" (description ?~ "List of Native Push Tokens") $
77+
PushTokenList
78+
<$> pushTokens .= fieldWithDocModifier "tokens" (description ?~ "Push tokens") (array schema)
7579

7680
data PushToken = PushToken
7781
{ _tokenTransport :: Transport,
@@ -81,10 +85,15 @@ data PushToken = PushToken
8185
}
8286
deriving stock (Eq, Ord, Show, Generic)
8387
deriving (Arbitrary) via (GenericUniform PushToken)
88+
deriving (A.ToJSON, A.FromJSON, S.ToSchema) via (Schema PushToken)
8489

8590
pushToken :: Transport -> AppName -> Token -> ClientId -> PushToken
8691
pushToken = PushToken
8792

93+
instance ToParamSchema PushToken where
94+
toParamSchema _ = S.toParamSchema (Proxy @Text)
95+
96+
-- todo(leif): remove when last endpoint is servantified
8897
modelPushToken :: Doc.Model
8998
modelPushToken = Doc.defineModel "PushToken" $ do
9099
Doc.description "Native Push Token"
@@ -98,22 +107,20 @@ modelPushToken = Doc.defineModel "PushToken" $ do
98107
Doc.description "Client ID"
99108
Doc.optional
100109

101-
instance ToJSON PushToken where
102-
toJSON p =
103-
object $
104-
"transport" .= _tokenTransport p
105-
# "app" .= _tokenApp p
106-
# "token" .= _token p
107-
# "client" .= _tokenClient p
108-
# []
109-
110-
instance FromJSON PushToken where
111-
parseJSON = withObject "PushToken" $ \p ->
112-
PushToken
113-
<$> p .: "transport"
114-
<*> p .: "app"
115-
<*> p .: "token"
116-
<*> p .: "client"
110+
instance ToSchema PushToken where
111+
schema =
112+
objectWithDocModifier "PushToken" desc $
113+
PushToken
114+
<$> _tokenTransport .= fieldWithDocModifier "transport" transDesc schema
115+
<*> _tokenApp .= fieldWithDocModifier "app" appDesc schema
116+
<*> _token .= fieldWithDocModifier "token" tokenDesc schema
117+
<*> _tokenClient .= fieldWithDocModifier "client" clientIdDesc schema
118+
where
119+
desc = description ?~ "Native Push Token"
120+
transDesc = description ?~ "Transport"
121+
appDesc = description ?~ "Application"
122+
tokenDesc = description ?~ "Access Token"
123+
clientIdDesc = description ?~ "Client ID"
117124

118125
--------------------------------------------------------------------------------
119126
-- Transport
@@ -126,6 +133,7 @@ data Transport
126133
| APNSVoIPSandbox
127134
deriving stock (Eq, Ord, Show, Bounded, Enum, Generic)
128135
deriving (Arbitrary) via (GenericUniform Transport)
136+
deriving (A.ToJSON, A.FromJSON, S.ToSchema) via (Schema Transport)
129137

130138
typeTransport :: Doc.DataType
131139
typeTransport =
@@ -138,21 +146,16 @@ typeTransport =
138146
"APNS_VOIP_SANDBOX"
139147
]
140148

141-
instance ToJSON Transport where
142-
toJSON GCM = "GCM"
143-
toJSON APNS = "APNS"
144-
toJSON APNSSandbox = "APNS_SANDBOX"
145-
toJSON APNSVoIP = "APNS_VOIP"
146-
toJSON APNSVoIPSandbox = "APNS_VOIP_SANDBOX"
147-
148-
instance FromJSON Transport where
149-
parseJSON = withText "transport" $ \case
150-
"GCM" -> pure GCM
151-
"APNS" -> pure APNS
152-
"APNS_SANDBOX" -> pure APNSSandbox
153-
"APNS_VOIP" -> pure APNSVoIP
154-
"APNS_VOIP_SANDBOX" -> pure APNSVoIPSandbox
155-
x -> fail $ "Invalid push transport: " ++ show x
149+
instance ToSchema Transport where
150+
schema =
151+
enum @Text "Access" $
152+
mconcat
153+
[ element "GCM" GCM,
154+
element "APNS" APNS,
155+
element "APNS_SANDBOX" APNSSandbox,
156+
element "APNS_VOIP" APNSVoIP,
157+
element "APNS_VOIP_SANDBOX" APNSVoIPSandbox
158+
]
156159

157160
instance FromByteString Transport where
158161
parser =
@@ -168,12 +171,20 @@ newtype Token = Token
168171
{ tokenText :: Text
169172
}
170173
deriving stock (Eq, Ord, Show)
171-
deriving newtype (FromJSON, ToJSON, FromByteString, ToByteString, Arbitrary)
174+
deriving newtype (FromByteString, ToByteString, Arbitrary)
175+
deriving (A.ToJSON, A.FromJSON, S.ToSchema) via (Schema Token)
176+
177+
instance ToSchema Token where
178+
schema = Token <$> tokenText .= schema
172179

173180
newtype AppName = AppName
174181
{ appNameText :: Text
175182
}
176183
deriving stock (Eq, Ord, Show)
177-
deriving newtype (FromJSON, ToJSON, IsString, Arbitrary)
184+
deriving newtype (IsString, Arbitrary)
185+
deriving (A.ToJSON, A.FromJSON, S.ToSchema) via (Schema AppName)
186+
187+
instance ToSchema AppName where
188+
schema = AppName <$> appNameText .= schema
178189

179190
makeLenses ''PushToken

libs/wire-api/src/Wire/API/Routes/Public/Brig.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -101,7 +101,7 @@ instance AsUnion DeleteSelfResponses (Maybe Timeout) where
101101
toUnion Nothing = Z (I ())
102102
fromUnion (Z (I ())) = Nothing
103103
fromUnion (S (Z (I (DeletionCodeTimeout t)))) = Just t
104-
fromUnion (S (S x)) = case x of {}
104+
fromUnion (S (S x)) = case x of
105105

106106
type ConnectionUpdateResponses = UpdateResponses "Connection unchanged" "Connection updated" UserConnection
107107

Lines changed: 85 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,85 @@
1+
-- This file is part of the Wire Server implementation.
2+
--
3+
-- Copyright (C) 2022 Wire Swiss GmbH <[email protected]>
4+
--
5+
-- This program is free software: you can redistribute it and/or modify it under
6+
-- the terms of the GNU Affero General Public License as published by the Free
7+
-- Software Foundation, either version 3 of the License, or (at your option) any
8+
-- later version.
9+
--
10+
-- This program is distributed in the hope that it will be useful, but WITHOUT
11+
-- ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
12+
-- FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more
13+
-- details.
14+
--
15+
-- You should have received a copy of the GNU Affero General Public License along
16+
-- with this program. If not, see <https://www.gnu.org/licenses/>.
17+
18+
module Wire.API.Routes.Public.Gundeck where
19+
20+
import Control.Lens ((^.))
21+
import Data.SOP
22+
import qualified Data.Swagger as Swagger
23+
import qualified Generics.SOP as GSOP
24+
import Imports
25+
import Servant
26+
import Servant.Swagger
27+
import Wire.API.Error
28+
import qualified Wire.API.Error.Gundeck as E
29+
import Wire.API.Push.V2.Token
30+
import Wire.API.Routes.MultiVerb
31+
import Wire.API.Routes.Named
32+
import Wire.API.Routes.Public
33+
34+
data AddTokenError
35+
= AddTokenErrorNoBudget
36+
| AddTokenErrorNotFound
37+
| AddTokenErrorInvalid
38+
| AddTokenErrorTooLong
39+
| AddTokenErrorMetadataTooLong
40+
deriving (Show, Generic)
41+
deriving (AsUnion AddTokenErrorResponses) via GenericAsUnion AddTokenErrorResponses AddTokenError
42+
43+
type AddTokenErrorResponses =
44+
'[ ErrorResponse 'E.AddTokenErrorNoBudget,
45+
ErrorResponse 'E.AddTokenErrorNotFound,
46+
ErrorResponse 'E.AddTokenErrorInvalid,
47+
ErrorResponse 'E.AddTokenErrorTooLong,
48+
ErrorResponse 'E.AddTokenErrorMetadataTooLong
49+
]
50+
51+
instance GSOP.Generic AddTokenError
52+
53+
data AddTokenSuccess = AddTokenSuccess PushToken
54+
55+
type AddTokenSuccessResponses =
56+
WithHeaders
57+
'[ Header "Location" Text
58+
]
59+
AddTokenSuccess
60+
(Respond 201 "Push token registered" PushToken)
61+
62+
type AddTokenResponses = AddTokenErrorResponses .++ '[AddTokenSuccessResponses]
63+
64+
type GundeckAPI =
65+
Named
66+
"register-push-token"
67+
( Summary "Register a native push token"
68+
:> ZUser
69+
:> ZConn
70+
:> "push"
71+
:> "tokens"
72+
:> ReqBody '[JSON] PushToken
73+
:> MultiVerb 'POST '[JSON] AddTokenResponses (Either AddTokenError AddTokenSuccess)
74+
)
75+
76+
instance AsHeaders '[Text] PushToken AddTokenSuccess where
77+
fromHeaders (I _ :* Nil, t) = AddTokenSuccess t
78+
toHeaders (AddTokenSuccess t) = (I (tokenText $ t ^. token) :* Nil, t)
79+
80+
instance (res ~ AddTokenResponses) => AsUnion res (Either AddTokenError AddTokenSuccess) where
81+
toUnion = eitherToUnion (toUnion @AddTokenErrorResponses) (Z . I)
82+
fromUnion = eitherFromUnion (fromUnion @AddTokenErrorResponses) (unI . unZ)
83+
84+
swaggerDoc :: Swagger.Swagger
85+
swaggerDoc = toSwagger (Proxy @GundeckAPI)

libs/wire-api/test/golden/Test/Wire/API/Golden/Manual.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,7 @@ import Test.Wire.API.Golden.Manual.GroupId
3333
import Test.Wire.API.Golden.Manual.ListConversations
3434
import Test.Wire.API.Golden.Manual.QualifiedUserClientPrekeyMap
3535
import Test.Wire.API.Golden.Manual.SearchResultContact
36+
import Test.Wire.API.Golden.Manual.Token
3637
import Test.Wire.API.Golden.Manual.UserClientPrekeyMap
3738
import Test.Wire.API.Golden.Manual.UserIdList
3839
import Test.Wire.API.Golden.Runner
@@ -122,5 +123,8 @@ tests =
122123
[(testObject_SearchResultContact_1, "testObject_SearchResultContact_1.json")],
123124
testGroup "GroupId" $
124125
testObjects
125-
[(testObject_GroupId_1, "testObject_GroupId_1.json")]
126+
[(testObject_GroupId_1, "testObject_GroupId_1.json")],
127+
testGroup "PushToken" $
128+
testObjects
129+
[(testObject_Token_1, "testObject_Token_1.json")]
126130
]
Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,29 @@
1+
-- This file is part of the Wire Server implementation.
2+
--
3+
-- Copyright (C) 2022 Wire Swiss GmbH <[email protected]>
4+
--
5+
-- This program is free software: you can redistribute it and/or modify it under
6+
-- the terms of the GNU Affero General Public License as published by the Free
7+
-- Software Foundation, either version 3 of the License, or (at your option) any
8+
-- later version.
9+
--
10+
-- This program is distributed in the hope that it will be useful, but WITHOUT
11+
-- ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
12+
-- FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more
13+
-- details.
14+
--
15+
-- You should have received a copy of the GNU Affero General Public License along
16+
-- with this program. If not, see <https://www.gnu.org/licenses/>.
17+
18+
module Test.Wire.API.Golden.Manual.Token where
19+
20+
import Data.Id
21+
import Wire.API.Push.V2.Token
22+
23+
testObject_Token_1 :: PushToken
24+
testObject_Token_1 =
25+
pushToken
26+
APNSVoIPSandbox
27+
(AppName {appNameText = "j{\110746\SOH_\1084873M"})
28+
(Token {tokenText = "K"})
29+
(ClientId {client = "6"})
Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
{
2+
"app": "j{𛂚\u0001_􈷉M",
3+
"client": "6",
4+
"token": "K",
5+
"transport": "APNS_VOIP_SANDBOX"
6+
}

libs/wire-api/wire-api.cabal

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@ library
3232
Wire.API.Error.Cargohold
3333
Wire.API.Error.Empty
3434
Wire.API.Error.Galley
35+
Wire.API.Error.Gundeck
3536
Wire.API.Event.Conversation
3637
Wire.API.Event.FeatureConfig
3738
Wire.API.Event.Team
@@ -87,6 +88,7 @@ library
8788
Wire.API.Routes.Public.Cannon
8889
Wire.API.Routes.Public.Cargohold
8990
Wire.API.Routes.Public.Galley
91+
Wire.API.Routes.Public.Gundeck
9092
Wire.API.Routes.Public.Spar
9193
Wire.API.Routes.Public.Util
9294
Wire.API.Routes.QualifiedCapture
@@ -508,6 +510,7 @@ test-suite wire-api-golden-tests
508510
Test.Wire.API.Golden.Manual.ListConversations
509511
Test.Wire.API.Golden.Manual.QualifiedUserClientPrekeyMap
510512
Test.Wire.API.Golden.Manual.SearchResultContact
513+
Test.Wire.API.Golden.Manual.Token
511514
Test.Wire.API.Golden.Manual.UserClientPrekeyMap
512515
Test.Wire.API.Golden.Manual.UserIdList
513516
Test.Wire.API.Golden.Protobuf

services/gundeck/gundeck.cabal

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -135,7 +135,12 @@ library
135135
, resourcet >=1.1
136136
, retry >=0.5
137137
, safe-exceptions
138-
, swagger >=0.1
138+
, servant
139+
, servant-server
140+
, servant-swagger
141+
, servant-swagger-ui
142+
, swagger
143+
, swagger2
139144
, text >=1.1
140145
, time >=1.4
141146
, tinylog >=0.10

0 commit comments

Comments
 (0)