1{-# LANGUAGE RecordWildCards #-}
2{-# LANGUAGE OverloadedStrings #-}
3{-# LANGUAGE TupleSections #-}
4
5module Network.Mattermost.Endpoints where
6
7import qualified Data.Aeson as A
8import qualified Data.ByteString.Char8 as B
9import qualified Data.HashMap.Strict as HM
10import           Data.Sequence (Seq, fromList)
11import           Data.Text (Text)
12import qualified Data.Text as T
13import qualified Network.HTTP.Base as HTTP
14import qualified Network.HTTP.Headers as HTTP
15import           Text.Printf (printf)
16
17import Network.Mattermost.Connection
18import Network.Mattermost.Exceptions
19import Network.Mattermost.Types
20import Network.Mattermost.Types.Config
21import Network.Mattermost.Types.Internal
22
23
24mmLogin :: ConnectionData -> Login -> IO (Either LoginFailureException (Session, User))
25mmLogin cd login = do
26  rsp <- doUnauthRequest cd HTTP.POST "/users/login" (jsonBody login)
27  case HTTP.rspCode rsp of
28    (2, _, _) -> do
29      token <- mmGetHeader rsp (HTTP.HdrCustom "Token")
30      value <- mmGetJSONBody "User" rsp
31      return (Right (Session cd (Token token), value))
32    _ ->
33      let eMsg = "Server returned unexpected " ++ show (HTTP.rspCode rsp) ++ " response"
34      in return (Left (LoginFailureException eMsg))
35
36mmInitialUser :: ConnectionData -> UsersCreate -> IO User
37mmInitialUser cd users = do
38  rsp <- doUnauthRequest cd HTTP.POST "/users" (jsonBody users)
39  case HTTP.rspCode rsp of
40    (2, _, _) -> mmGetJSONBody "User" rsp
41    _ -> error ("Server returned unexpected " ++ show (HTTP.rspCode rsp) ++ " response")
42
43-- * Endpoints
44
45-- * Brand
46
47-- -- | Uploads a brand image.
48-- --
49-- --   /Permissions/: Must have @manage_system@ permission.
50-- mmUploadBrandImage :: Session -> IO ()
51-- mmUploadBrandImage =
52--   inPost "/brand/image" noBody jsonResponse
53
54-- -- | Get the previously uploaded brand image. Returns 404 if no brand image
55-- --   has been uploaded.
56-- --
57-- --   /Permissions/: No permission required.
58-- mmGetBrandImage :: Session -> IO Text
59-- mmGetBrandImage =
60--   inGet "/brand/image" noBody jsonResponse
61
62
63
64-- * Channels
65
66-- | Get all channel members on a team for a user.
67--
68--   /Permissions/: Logged in as the user and @view_team@ permission for
69--   the team. Having @manage_system@ permission voids the previous
70--   requirements.
71mmGetChannelMembersForUser :: UserParam -> TeamId -> Session -> IO (Seq ChannelMember)
72mmGetChannelMembersForUser userId teamId =
73  inGet (printf "/users/%s/teams/%s/channels/members" userId teamId) noBody jsonResponse
74
75-- | Get all the channels on a team for a user.
76--
77--   /Permissions/: Logged in as the user, or have @edit_other_users@
78--   permission, and @view_team@ permission for the team.
79mmGetChannelsForUser :: UserParam -> TeamId -> Session -> IO (Seq Channel)
80mmGetChannelsForUser userId teamId =
81  inGet (printf "/users/%s/teams/%s/channels" userId teamId) noBody jsonResponse
82
83-- -- | Get a list of channel members based on the provided user ids.
84-- --
85-- --   /Permissions/: Must have the @read_channel@ permission.
86-- mmGetChannelMembersByIds :: ChannelId -> (Seq Text) -> Session -> IO (Seq ChannelMember)
87-- mmGetChannelMembersByIds channelId body =
88--   inPost (printf "/channels/%s/members/ids" channelId) (jsonBody body) jsonResponse
89
90-- | Perform all the actions involved in viewing a channel. This includes
91--   marking channels as read, clearing push notifications, and updating
92--   the active channel.
93--
94--   /Permissions/: Must be logged in as user or have @edit_other_users@
95--   permission.
96mmViewChannel :: UserParam -> ChannelId -> Maybe ChannelId -> Session -> IO ()
97mmViewChannel userId chanId prevChanIdMb =
98  inPost (printf "/channels/members/%s/view" userId) (jsonBody body) noResponse
99  where body = HM.fromList $
100          ("channel_id" :: T.Text, chanId)
101          : case prevChanIdMb of
102              Just prevChanId -> [ ("prev_channel_id", prevChanId) ]
103              Nothing         -> []
104
105-- | Create a new group message channel to group of users. If the logged in
106--   user's id is not included in the list, it will be appended to the end.
107--
108--   /Permissions/: Must have @create_group_channel@ permission.
109mmCreateGroupMessageChannel :: Seq UserId -> Session -> IO Channel
110mmCreateGroupMessageChannel body =
111  inPost "/channels/group" (jsonBody body) jsonResponse
112
113-- | Get the total unread messages and mentions for a channel for a user.
114--
115--   /Permissions/: Must be logged in as user and have the @read_channel@
116--   permission, or have @edit_other_usrs@ permission.
117mmGetUnreadMessages :: UserParam -> ChannelId -> Session -> IO ChannelUnread
118mmGetUnreadMessages userId channelId =
119  inGet (printf "/users/%s/channels/%s/unread" userId channelId) noBody jsonResponse
120
121-- -- | Gets a channel from the provided team name and channel name strings.
122-- --
123-- --   /Permissions/: @read_channel@ permission for the channel.
124-- mmGetChannelByNameAndTeamName :: Text -> Text -> Session -> IO Channel
125-- mmGetChannelByNameAndTeamName teamName channelName =
126--   inGet (printf "/teams/name/%s/channels/name/%s" teamName channelName) noBody jsonResponse
127
128-- | Get a list of public channels on a team by id.
129--
130--   /Permissions/: @view_team@ for the team the channels are on.
131mmGetListOfChannelsByIds :: TeamId -> Seq ChannelId -> Session -> IO (Seq Channel)
132mmGetListOfChannelsByIds teamId body =
133  inPost (printf "/teams/%s/channels/ids" teamId) (jsonBody body) jsonResponse
134
135-- | Partially update a channel by providing only the fields you want to
136--   update. Omitted fields will not be updated. The fields that can be
137--   updated are defined in the request body, all other provided fields
138--   will be ignored.
139--
140--   /Permissions/: If updating a public channel,
141--   @manage_public_channel_members@ permission is required. If updating a
142--   private channel, @manage_private_channel_members@ permission is
143--   required.
144mmPatchChannel :: ChannelId -> ChannelPatch -> Session -> IO Channel
145mmPatchChannel channelId body =
146  inPut (printf "/channels/%s/patch" channelId) (jsonBody body) jsonResponse
147
148-- | Create a new direct message channel between two users.
149--
150--   /Permissions/: Must be one of the two users and have
151--   @create_direct_channel@ permission. Having the @manage_system@
152--   permission voids the previous requirements.
153mmCreateDirectMessageChannel :: (UserId, UserId) -> Session -> IO Channel
154mmCreateDirectMessageChannel body =
155  inPost "/channels/direct" (jsonBody body) jsonResponse
156
157-- | Get a list of pinned posts for channel.
158mmGetChannelPinnedPosts :: ChannelId -> Session -> IO Posts
159mmGetChannelPinnedPosts channelId =
160  inGet (printf "/channels/%s/pinned" channelId) noBody jsonResponse
161
162-- | Get statistics for a channel.
163--
164--   /Permissions/: Must have the @read_channel@ permission.
165mmGetChannelStatistics :: ChannelId -> Session -> IO ChannelStats
166mmGetChannelStatistics channelId =
167  inGet (printf "/channels/%s/stats" channelId) noBody jsonResponse
168
169-- | Update a user's notification properties for a channel.
170--
171--   /Permissions/: Must be logged in as the user or have
172--   @edit_other_users@ permission.
173mmUpdateChannelNotifications :: ChannelId -> UserId -> ChannelNotifyProps -> Session -> IO ()
174mmUpdateChannelNotifications channelId userId body =
175  inPut (printf "/channels/%s/members/%s/notify_props" channelId userId) (jsonBody body) noResponse
176
177-- | Add a user to the channel.
178mmAddUser :: ChannelId -> MinChannelMember -> Session -> IO ChannelMember
179mmAddUser channelId body =
180  inPost (printf "/channels/%s/members" channelId) (jsonBody body) jsonResponse
181
182-- -- | Get a page of members for a channel.
183-- --
184-- --   /Permissions/: @read_channel@ permission for the channel.
185-- mmGetChannelMembers :: ChannelId -> Maybe Integer -> Maybe Integer -> Session -> IO (Seq ChannelMember)
186-- mmGetChannelMembers channelId page perPage =
187--   inGet (printf "/channels/%s/members?%s" channelId (mkQueryString [ sequence ("page", fmap show page) , sequence ("per_page", fmap show perPage) ])) noBody jsonResponse
188
189-- | Create a new channel.
190--
191--   /Permissions/: If creating a public channel, @create_public_channel@
192--   permission is required. If creating a private channel,
193--   @create_private_channel@ permission is required.
194mmCreateChannel :: MinChannel -> Session -> IO Channel
195mmCreateChannel body =
196  inPost "/channels" (jsonBody body) jsonResponse
197
198-- | Gets channel from the provided team id and channel name strings.
199--
200--   /Permissions/: @read_channel@ permission for the channel.
201mmGetChannelByName :: TeamId -> Text -> Session -> IO Channel
202mmGetChannelByName teamId channelName =
203  inGet (printf "/teams/%s/channels/name/%s" teamId channelName) noBody jsonResponse
204
205-- -- | Update a user's roles for a channel.
206-- --
207-- --   /Permissions/: Must have @manage_channel_roles@ permission for the
208-- --   channel.
209-- mmUpdateChannelRoles :: ChannelId -> UserId -> Text -> Session -> IO ()
210-- mmUpdateChannelRoles channelId userId roles =
211--   inPut (printf "/channels/%s/members/%s/roles" channelId userId) (jsonBody (A.object [ "roles" A..= roles ])) jsonResponse
212
213-- -- | Update a channel. The fields that can be updated are listed as
214-- --   paramters. Omitted fields will be treated as blanks.
215-- --
216-- --   /Permissions/: If updating a public channel,
217-- --   @manage_public_channel_members@ permission is required. If updating a
218-- --   private channel, @manage_private_channel_members@ permission is
219-- --   required.
220-- mmUpdateChannel :: ChannelId -> XX28 -> Session -> IO Channel
221-- mmUpdateChannel channelId body =
222--   inPut (printf "/channels/%s" channelId) (jsonBody body) jsonResponse
223
224-- | Get channel from the provided channel id string.
225--
226--   /Permissions/: @read_channel@ permission for the channel.
227mmGetChannel :: ChannelId -> Session -> IO Channel
228mmGetChannel channelId =
229  inGet (printf "/channels/%s" channelId) noBody jsonResponse
230
231-- | Delete a channel based from provided channel id string.
232--
233--   /Permissions/: @delete_public_channel@ permission if the channel is
234--   public,
235--
236--   @delete_private_channel@ permission if the channel is private,
237--
238--   or have @manage_system@ permission.
239mmDeleteChannel :: ChannelId -> Session -> IO ()
240mmDeleteChannel channelId =
241  inDelete (printf "/channels/%s" channelId) noBody noResponse
242
243-- -- | Restore channel from the provided channel id string.
244-- --
245-- --
246-- --   /Minimum server version/: 3.10
247-- --
248-- --
249-- --   /Permissions/: @manage_team@ permission for the team of channel.
250-- mmRestoreChannel :: ChannelId -> Session -> IO Channel
251-- mmRestoreChannel channelId =
252--   inPost (printf "/channels/%s/restore" channelId) noBody jsonResponse
253
254-- | Get a channel member.
255--
256--   /Permissions/: @read_channel@ permission for the channel.
257mmGetChannelMember :: ChannelId -> UserParam -> Session -> IO ChannelMember
258mmGetChannelMember channelId userId =
259  inGet (printf "/channels/%s/members/%s" channelId userId) noBody jsonResponse
260
261-- | Delete a channel member, effectively removing them from a channel.
262--
263--   /Permissions/: @manage_public_channel_members@ permission if the
264--   channel is public.
265--
266--   @manage_private_channel_members@ permission if the channel is private.
267mmRemoveUserFromChannel :: ChannelId -> UserParam -> Session -> IO ()
268mmRemoveUserFromChannel channelId userId =
269  inDelete (printf "/channels/%s/members/%s" channelId userId) noBody noResponse
270
271
272
273-- * Cluster
274
275-- -- | Get a set of information for each node in the cluster, useful for
276-- --   checking the status and health of each node.
277-- --
278-- --   /Permissions/: Must have @manage_system@ permission.
279-- mmGetClusterStatus :: Session -> IO (Seq ClusterInfo)
280-- mmGetClusterStatus =
281--   inGet "/cluster/status" noBody jsonResponse
282
283
284
285-- * Commands
286
287-- -- | Generate a new token for the command based on command id string.
288-- --
289-- --   /Permissions/: Must have @manage_slash_commands@ permission for the
290-- --   team the command is in.
291-- mmGenerateNewToken :: CommandId -> Session -> IO Text
292-- mmGenerateNewToken commandId =
293--   inPut (printf "/commands/%s/regen_token" commandId) noBody jsonResponse
294
295-- | Execute a command on a team.
296--
297--   /Permissions/: Must have @use_slash_commands@ permission for the team
298--   the command is in.
299mmExecuteCommand :: MinCommand -> Session -> IO CommandResponse
300mmExecuteCommand body =
301  inPost "/commands/execute" (jsonBody body) jsonResponse
302
303-- -- | Update a single command based on command id string and Command struct.
304-- --
305-- --   /Permissions/: Must have @manage_slash_commands@ permission for the
306-- --   team the command is in.
307-- mmUpdateCommand :: CommandId -> Command -> Session -> IO Command
308-- mmUpdateCommand commandId body =
309--   inPut (printf "/commands/%s" commandId) (jsonBody body) jsonResponse
310
311-- -- | Delete a command based on command id string.
312-- --
313-- --   /Permissions/: Must have @manage_slash_commands@ permission for the
314-- --   team the command is in.
315-- mmDeleteCommand :: CommandId -> Session -> IO ()
316-- mmDeleteCommand commandId =
317--   inDelete (printf "/commands/%s" commandId) noBody jsonResponse
318
319-- -- | List autocomplete commands in the team.
320-- --
321-- --   /Permissions/: @view_team@ for the team.
322-- mmListAutocompleteCommands :: TeamId -> Session -> IO (Seq Command)
323-- mmListAutocompleteCommands teamId =
324--   inGet (printf "/teams/%s/commands/autocomplete" teamId) noBody jsonResponse
325
326-- -- | Create a command for a team.
327-- --
328-- --   /Permissions/: @manage_slash_commands@ for the team the command is in.
329-- mmCreateCommand :: XX32 -> Session -> IO Command
330-- mmCreateCommand body =
331--   inPost "/commands" (jsonBody body) jsonResponse
332
333-- -- | List commands for a team.
334-- --
335-- --   /Permissions/: @manage_slash_commands@ if need list custom commands.
336mmListCommandsForTeam :: TeamId -> Bool -> Session -> IO (Seq Command)
337mmListCommandsForTeam teamId customOnly =
338    let pairs = [ Just ("team_id", T.unpack (idString teamId))
339                , Just ("custom_only", if customOnly then "true" else "false")
340                ]
341    in inGet (printf "/commands?%s" (mkQueryString pairs)) noBody jsonResponse
342
343-- * Compliance
344
345-- -- | Get a compliance reports previously created.
346-- --
347-- --   /Permissions/: Must have @manage_system@ permission.
348-- mmGetReport :: ReportId -> Session -> IO Compliance
349-- mmGetReport reportId =
350--   inGet (printf "/compliance/reports/%s" reportId) noBody jsonResponse
351
352-- -- | Create and save a compliance report.
353-- --
354-- --   /Permissions/: Must have @manage_system@ permission.
355-- mmCreateReport :: Session -> IO Compliance
356-- mmCreateReport =
357--   inPost "/compliance/reports" noBody jsonResponse
358
359-- -- | Get a list of compliance reports previously created by page, selected
360-- --   with @page@ and @per_page@ query parameters.
361-- --
362-- --   /Permissions/: Must have @manage_system@ permission.
363-- mmGetReports :: Maybe Integer -> Maybe Integer -> Session -> IO (Seq Compliance)
364-- mmGetReports page perPage =
365--   inGet (printf "/compliance/reports?%s" (mkQueryString [ sequence ("page", fmap show page) , sequence ("per_page", fmap show perPage) ])) noBody jsonResponse
366
367-- -- | Download the full contents of a report as a file.
368-- --
369-- --   /Permissions/: Must have @manage_system@ permission.
370-- mmDownloadReport :: ReportId -> Session -> IO ()
371-- mmDownloadReport reportId =
372--   inGet (printf "/compliance/reports/%s/download" reportId) noBody jsonResponse
373
374
375
376-- * Elasticsearch
377
378-- -- | Deletes all Elasticsearch indexes and their contents. After calling
379-- --   this endpoint, it is
380-- --
381-- --   necessary to schedule a new Elasticsearch indexing job to repopulate
382-- --   the indexes.
383-- --
384-- --   /Minimum server version/: 4.1
385-- --
386-- --   /Permissions/: Must have @manage_system@ permission.
387-- mmPurgeAllElasticsearchIndexes :: Session -> IO ()
388-- mmPurgeAllElasticsearchIndexes =
389--   inPost "/elasticsearch/purge_indexes" noBody jsonResponse
390
391-- -- | Test the current Elasticsearch configuration to see if the
392-- --   Elasticsearch server can be contacted successfully.
393-- --
394-- --   Optionally provide a configuration in the request body to test. If no
395-- --   valid configuration is present in the
396-- --
397-- --   request body the current server configuration will be tested.
398-- --
399-- --
400-- --   /Minimum server version/: 4.1
401-- --
402-- --   /Permissions/: Must have @manage_system@ permission.
403-- mmTestElasticsearchConfiguration :: Session -> IO ()
404-- mmTestElasticsearchConfiguration =
405--   inPost "/elasticsearch/test" noBody jsonResponse
406
407
408
409-- * Emoji
410
411-- -- | Create a custom emoji for the team.
412-- --
413-- --   /Permissions/: Must be authenticated.
414-- mmCreateCustomEmoji :: Session -> IO Emoji
415-- mmCreateCustomEmoji =
416--   inPost "/emoji" noBody jsonResponse
417
418-- | Search custom emoji using an infix match. (Does not support the
419-- prefix_only option).
420--
421--   /Permissions/: Must be authenticated.
422mmSearchCustomEmoji :: T.Text -> Session -> IO [Emoji]
423mmSearchCustomEmoji searchString =
424  let body = A.object [ "term" A..= searchString
425                      ]
426  in inPost (printf "/emoji/search") (jsonBody body) jsonResponse
427
428-- | Get a page of metadata for custom emoji on the system.
429--
430--   /Permissions/: Must be authenticated.
431mmGetListOfCustomEmoji :: Maybe Integer -> Maybe Integer -> Session -> IO [Emoji]
432mmGetListOfCustomEmoji page perPage =
433    let qs = mkQueryString [ sequence ("page", fmap show page)
434                           , sequence ("per_page", fmap show perPage)
435                           ]
436    in inGet (printf "/emoji?%s" qs) noBody jsonResponse
437
438-- -- | Get some metadata for a custom emoji.
439-- --
440-- --   /Permissions/: Must be authenticated.
441-- mmGetCustomEmoji :: EmojiId -> Session -> IO Emoji
442-- mmGetCustomEmoji emojiId =
443--   inGet (printf "/emoji/%s" emojiId) noBody jsonResponse
444
445-- -- | Delete a custom emoji.
446-- --
447-- --   /Permissions/: Must have the @manage_team@ or @manage_system@
448-- --   permissions or be the user who created the emoji.
449-- mmDeleteCustomEmoji :: EmojiId -> Session -> IO Emoji
450-- mmDeleteCustomEmoji emojiId =
451--   inDelete (printf "/emoji/%s" emojiId) noBody jsonResponse
452
453-- -- | Get the image for a custom emoji.
454-- --
455-- --   /Permissions/: Must be authenticated.
456-- mmGetCustomEmojiImage :: EmojiId -> Session -> IO ()
457-- mmGetCustomEmojiImage emojiId =
458--   inGet (printf "/emoji/%s/image" emojiId) noBody jsonResponse
459
460
461
462-- * Files
463
464-- -- | Gets a public link for a file that can be accessed without logging
465-- mmGetPublicFileLink :: FileId -> Session -> IO Text
466-- mmGetPublicFileLink fileId =
467--   inGet (printf "/files/%s/link" fileId) noBody jsonResponse
468
469-- | Gets a file that has been uploaded previously.
470--
471--   /Permissions/: Must have @read_channel@ permission or be uploader of
472--   the file.
473mmGetFile :: FileId -> Session -> IO B.ByteString
474mmGetFile fileId =
475  inGet (printf "/files/%s" fileId) noBody bytestringResponse
476
477-- | Uploads a file that can later be attached to a post.
478--
479--   /Permissions/: Must have @upload_file@ permission.
480mmUploadFile :: ChannelId -> String -> B.ByteString -> Session -> IO UploadResponse
481mmUploadFile cId filename bytes =
482    let qs = mkQueryString
483                 [ Just ("channel_id", T.unpack $ idString cId)
484                 , Just ("filename", filename)
485                 ]
486    in inPost (printf "/files?%s" qs) bytes jsonResponse
487
488-- | Gets a file's info.
489--
490--   /Permissions/: Must have @read_channel@ permission or be uploader of
491--   the file.
492mmGetMetadataForFile :: FileId -> Session -> IO FileInfo
493mmGetMetadataForFile fileId =
494  inGet (printf "/files/%s/info" fileId) noBody jsonResponse
495
496-- -- | Gets a file's thumbnail.
497-- --
498-- --   /Permissions/: Must have @read_channel@ permission or be uploader of
499-- --   the file.
500-- mmGetFilesThumbnail :: FileId -> Session -> IO ()
501-- mmGetFilesThumbnail fileId =
502--   inGet (printf "/files/%s/thumbnail" fileId) noBody jsonResponse
503
504-- -- | Gets a file's preview.
505-- --
506-- --   /Permissions/: Must have @read_channel@ permission or be uploader of
507-- --   the file.
508-- mmGetFilesPreview :: FileId -> Session -> IO ()
509-- mmGetFilesPreview fileId =
510--   inGet (printf "/files/%s/preview" fileId) noBody jsonResponse
511
512
513
514-- * Jobs
515
516-- -- | Create a new job.
517-- --
518-- --   /Minimum server version: 4.1/
519-- --
520-- --   /Permissions/: Must have @manage_jobs@ permission.
521-- mmCreateNewJob :: XX20 -> Session -> IO Job
522-- mmCreateNewJob body =
523--   inPost "/jobs" (jsonBody body) jsonResponse
524
525-- -- | Get a page of jobs. Use the query parameters to modify the behaviour
526-- --   of this endpoint.
527-- --
528-- --   /Minimum server version: 4.1/
529-- --
530-- --   /Permissions/: Must have @manage_jobs@ permission.
531-- mmGetJobs :: Maybe Integer -> Maybe Integer -> Session -> IO (Seq Job)
532-- mmGetJobs page perPage =
533--   inGet (printf "/jobs?%s" (mkQueryString [ sequence ("page", fmap show page) , sequence ("per_page", fmap show perPage) ])) noBody jsonResponse
534
535-- -- | Cancel a job.
536-- --
537-- --   /Minimum server version: 4.1/
538-- --
539-- --   /Permissions/: Must have @manage_jobs@ permission.
540-- mmCancelJob :: JobId -> Session -> IO ()
541-- mmCancelJob jobId =
542--   inPost (printf "/jobs/%s/cancel" jobId) noBody jsonResponse
543
544-- -- | Gets a single job.
545-- --
546-- --   /Minimum server version: 4.1/
547-- --
548-- --   /Permissions/: Must have @manage_jobs@ permission.
549-- mmGetJob :: JobId -> Session -> IO Job
550-- mmGetJob jobId =
551--   inGet (printf "/jobs/%s" jobId) noBody jsonResponse
552
553-- -- | Get a page of jobs of the given type. Use the query parameters to
554-- --   modify the behaviour of this endpoint.
555-- --
556-- --   /Minimum server version: 4.1/
557-- --
558-- --   /Permissions/: Must have @manage_jobs@ permission.
559-- mmGetJobsOfGivenType :: Text -> Maybe Integer -> Maybe Integer -> Session -> IO (Seq Job)
560-- mmGetJobsOfGivenType type_ page perPage =
561--   inGet (printf "/jobs/type/%s?%s" type_ (mkQueryString [ sequence ("page", fmap show page) , sequence ("per_page", fmap show perPage) ])) noBody jsonResponse
562
563
564
565-- * LDAP
566
567-- -- | Test the current AD\/LDAP configuration to see if the AD\/LDAP server
568-- --   can be contacted successfully.
569-- --
570-- --   /Permissions/: Must have @manage_system@ permission.
571-- mmTestLdapConfiguration :: Session -> IO ()
572-- mmTestLdapConfiguration =
573--   inPost "/ldap/test" noBody jsonResponse
574
575-- -- | Synchronize any user attribute changes in the configured AD\/LDAP
576-- --   server with Mattermost.
577-- --
578-- --   /Permissions/: Must have @manage_system@ permission.
579-- mmSyncWithLdap :: Session -> IO ()
580-- mmSyncWithLdap =
581--   inPost "/ldap/sync" noBody jsonResponse
582
583
584
585-- * OAuth
586
587-- -- | Register an OAuth 2.0 client application with Mattermost as the
588-- --   service provider.
589-- --
590-- --   /Permissions/: Must have @manage_oauth@ permission.
591-- mmRegisterOauthApp :: XX13 -> Session -> IO OAuthApp
592-- mmRegisterOauthApp body =
593--   inPost "/oauth/apps" (jsonBody body) jsonResponse
594
595-- -- | Get a page of OAuth 2.0 client applications registered with
596-- --   Mattermost.
597-- --
598-- --   /Permissions/: With @manage_oauth@ permission, the apps registered by
599-- --   the logged in user are returned. With @manage_system_wide_oauth@
600-- --   permission, all apps regardless of creator are returned.
601-- mmGetOauthApps :: Maybe Integer -> Maybe Integer -> Session -> IO (Seq OAuthApp)
602-- mmGetOauthApps page perPage =
603--   inGet (printf "/oauth/apps?%s" (mkQueryString [ sequence ("page", fmap show page) , sequence ("per_page", fmap show perPage) ])) noBody jsonResponse
604
605-- -- | Get an OAuth 2.0 client application registered with Mattermost.
606-- --
607-- --   /Permissions/: If app creator, must have @mange_oauth@ permission
608-- --   otherwise @manage_system_wide_oauth@ permission is required.
609-- mmGetAnOauthApp :: AppId -> Session -> IO OAuthApp
610-- mmGetAnOauthApp appId =
611--   inGet (printf "/oauth/apps/%s" appId) noBody jsonResponse
612
613-- -- | Delete and unregister an OAuth 2.0 client application
614-- --
615-- --   /Permissions/: If app creator, must have @mange_oauth@ permission
616-- --   otherwise @manage_system_wide_oauth@ permission is required.
617-- mmDeleteAnOauthApp :: AppId -> Session -> IO ()
618-- mmDeleteAnOauthApp appId =
619--   inDelete (printf "/oauth/apps/%s" appId) noBody jsonResponse
620
621-- -- | Get public information about an OAuth 2.0 client application
622-- --   registered with Mattermost. The application's client secret will be
623-- --   blanked out.
624-- --
625-- --   /Permissions/: Must be authenticated.
626-- mmGetInfoOnAnOauthApp :: AppId -> Session -> IO OAuthApp
627-- mmGetInfoOnAnOauthApp appId =
628--   inGet (printf "/oauth/apps/%s/info" appId) noBody jsonResponse
629
630-- -- | Get a page of OAuth 2.0 client applications authorized to access a
631-- --   user's account.
632-- --
633-- --   /Permissions/: Must be authenticated as the user or have
634-- --   @edit_other_users@ permission.
635-- mmGetAuthorizedOauthApps :: UserId -> Maybe Integer -> Maybe Integer -> Session -> IO (Seq OAuthApp)
636-- mmGetAuthorizedOauthApps userId page perPage =
637--   inGet (printf "/users/%s/oauth/apps/authorized?%s" userId (mkQueryString [ sequence ("page", fmap show page) , sequence ("per_page", fmap show perPage) ])) noBody jsonResponse
638
639-- -- | Regenerate the client secret for an OAuth 2.0 client application
640-- --   registered with Mattermost.
641-- --
642-- --   /Permissions/: If app creator, must have @mange_oauth@ permission
643-- --   otherwise @manage_system_wide_oauth@ permission is required.
644-- mmRegenerateOauthAppSecret :: AppId -> Session -> IO OAuthApp
645-- mmRegenerateOauthAppSecret appId =
646--   inPost (printf "/oauth/apps/%s/regen_secret" appId) noBody jsonResponse
647
648
649
650-- * Posts
651
652-- | Create a new post in a channel. To create the post as a comment on
653--   another post, provide @root_id@.
654--
655--   /Permissions/: Must have @create_post@ permission for the channel the
656--   post is being created in.
657mmCreatePost :: RawPost -> Session -> IO Post
658mmCreatePost body =
659  inPost "/posts" (jsonBody body) jsonResponse
660
661-- | Search posts in the team and from the provided terms string.
662--
663--   /Permissions/: Must be authenticated and have the @view_team@
664--   permission.
665mmSearchForTeamPosts :: TeamId -> SearchPosts -> Session -> IO Posts
666mmSearchForTeamPosts teamId body =
667  inPost (printf "/teams/%s/posts/search" teamId) (jsonBody body) jsonResponse
668
669-- | Pin a post to a channel it is in based from the provided post id
670--   string.
671--
672--   /Permissions/: Must be authenticated and have the @read_channel@
673--   permission to the channel the post is in.
674mmPinPostToChannel :: PostId -> Session -> IO StatusOK
675mmPinPostToChannel postId =
676  inPost (printf "/posts/%s/pin" postId) noBody jsonResponse
677
678-- | Get a post and the rest of the posts in the same thread.
679--
680--   /Permissions/: Must have @read_channel@ permission for the channel the
681--   post is in or if the channel is public, have the
682--   @read_public_channels@ permission for the team.
683mmGetThread :: PostId -> Session -> IO Posts
684mmGetThread postId =
685  inGet (printf "/posts/%s/thread" postId) noBody jsonResponse
686
687-- | Update a post. Only the fields listed below are updatable, omitted
688--   fields will be treated as blank.
689--
690--   /Permissions/: Must have @edit_post@ permission for the channel the
691--   post is in.
692mmUpdatePost :: PostId -> PostUpdate -> Session -> IO Post
693mmUpdatePost postId body =
694  inPut (printf "/posts/%s" postId) (jsonBody body) jsonResponse
695
696-- | Get a single post.
697--
698--   /Permissions/: Must have @read_channel@ permission for the channel the
699--   post is in or if the channel is public, have the
700--   @read_public_channels@ permission for the team.
701mmGetPost :: PostId -> Session -> IO Post
702mmGetPost postId =
703  inGet (printf "/posts/%s" postId) noBody jsonResponse
704
705-- | Soft deletes a post, by marking the post as deleted in the database.
706--   Soft deleted posts will not be returned in post queries.
707--
708--   /Permissions/: Must be logged in as the user or have
709--   @delete_others_posts@ permission.
710mmDeletePost :: PostId -> Session -> IO ()
711mmDeletePost postId =
712  inDelete (printf "/posts/%s" postId) noBody noResponse
713
714data FlaggedPostsQuery = FlaggedPostsQuery
715  { flaggedPostsQueryPage      :: Maybe Int
716  , flaggedPostsQueryPerPage   :: Maybe Int
717  , flaggedPostsQueryTeamId    :: Maybe TeamId
718  , flaggedPostsQueryChannelId :: Maybe ChannelId
719  }
720
721defaultFlaggedPostsQuery :: FlaggedPostsQuery
722defaultFlaggedPostsQuery = FlaggedPostsQuery
723  { flaggedPostsQueryPage      = Nothing
724  , flaggedPostsQueryPerPage   = Nothing
725  , flaggedPostsQueryTeamId    = Nothing
726  , flaggedPostsQueryChannelId = Nothing
727  }
728
729
730-- | Get a page of flagged posts of a user provided user id string. Selects
731--   from a channel, team or all flagged posts by a user.
732--
733--   /Permissions/: Must be user or have @manage_system@ permission.
734mmGetListOfFlaggedPosts :: UserParam -> FlaggedPostsQuery -> Session -> IO Posts
735mmGetListOfFlaggedPosts userId FlaggedPostsQuery { .. } =
736  inGet (printf "/users/%s/posts/flagged?%s" userId query) noBody jsonResponse
737    where query = mkQueryString
738            [ sequence ("team_id", fmap (T.unpack . idString) flaggedPostsQueryTeamId)
739            , sequence ("channel_id", fmap (T.unpack . idString) flaggedPostsQueryChannelId)
740            , sequence ("page", fmap show flaggedPostsQueryPage)
741            , sequence ("per_page", fmap show flaggedPostsQueryPerPage)
742            ]
743
744-- | Unpin a post to a channel it is in based from the provided post id
745--   string.
746--
747--   /Permissions/: Must be authenticated and have the @read_channel@
748--   permission to the channel the post is in.
749mmUnpinPostToChannel :: PostId -> Session -> IO StatusOK
750mmUnpinPostToChannel postId =
751  inPost (printf "/posts/%s/unpin" postId) noBody jsonResponse
752
753-- | Partially update a post by providing only the fields you want to
754--   update. Omitted fields will not be updated. The fields that can be
755--   updated are defined in the request body, all other provided fields
756--   will be ignored.
757--
758--   /Permissions/: Must have the @edit_post@ permission.
759mmPatchPost :: PostId -> PostUpdate -> Session -> IO Post
760mmPatchPost postId body =
761  inPut (printf "/posts/%s/patch" postId) (jsonBody body) jsonResponse
762
763data PostQuery = PostQuery
764  { postQueryPage    :: Maybe Int
765  , postQueryPerPage :: Maybe Int
766  , postQuerySince   :: Maybe ServerTime
767  , postQueryBefore  :: Maybe PostId
768  , postQueryAfter   :: Maybe PostId
769  }
770
771defaultPostQuery :: PostQuery
772defaultPostQuery = PostQuery
773  { postQueryPage    = Nothing
774  , postQueryPerPage = Nothing
775  , postQuerySince   = Nothing
776  , postQueryBefore  = Nothing
777  , postQueryAfter   = Nothing
778  }
779
780postQueryToQueryString :: PostQuery -> String
781postQueryToQueryString PostQuery { .. } =
782  mkQueryString
783    [ sequence ("page", fmap show postQueryPage)
784    , sequence ("per_page", fmap show postQueryPerPage)
785    , sequence ("since", fmap (show . timeToServer) postQuerySince)
786    , sequence ("before", fmap (T.unpack . idString) postQueryBefore)
787    , sequence ("after", fmap (T.unpack . idString) postQueryAfter)
788    ]
789
790-- | Get a page of posts in a channel. Use the query parameters to modify
791--   the behaviour of this endpoint. The parameters @since@, @before@ and
792--   @after@ must not be used together.
793--
794--   /Permissions/: Must have @read_channel@ permission for the channel.
795mmGetPostsForChannel :: ChannelId -> PostQuery -> Session -> IO Posts
796mmGetPostsForChannel channelId postQuery =
797  inGet (printf "/channels/%s/posts?%s" channelId (postQueryToQueryString postQuery)) noBody jsonResponse
798
799-- -- | Gets a list of file information objects for the files attached to a
800-- --   post.
801-- --
802-- --   /Permissions/: Must have @read_channel@ permission for the channel the
803-- --   post is in.
804-- mmGetFileInfoForPost :: PostId -> Session -> IO (Seq FileInfo)
805-- mmGetFileInfoForPost postId =
806--   inGet (printf "/posts/%s/files/info" postId) noBody jsonResponse
807
808
809
810-- * Preferences
811
812-- | Gets a single preference for the current user with the given category
813--   and name.
814--
815--   /Permissions/: Must be logged in as the user being updated or have the
816--   @edit_other_users@ permission.
817mmGetSpecificUserPreference :: UserParam -> Text -> Text -> Session -> IO Preference
818mmGetSpecificUserPreference userId category preferenceName =
819  inGet (printf "/users/%s/preferences/%s/name/%s" userId category preferenceName) noBody jsonResponse
820
821-- | Save a list of the user's preferences.
822--
823--   /Permissions/: Must be logged in as the user being updated or have the
824--   @edit_other_users@ permission.
825mmSaveUsersPreferences :: UserParam -> (Seq Preference) -> Session -> IO ()
826mmSaveUsersPreferences userId body =
827  inPut (printf "/users/%s/preferences" userId) (jsonBody body) noResponse
828
829-- | Get a list of the user's preferences.
830--
831--   /Permissions/: Must be logged in as the user being updated or have the
832--   @edit_other_users@ permission.
833mmGetUsersPreferences :: UserParam -> Session -> IO (Seq Preference)
834mmGetUsersPreferences userId =
835  inGet (printf "/users/%s/preferences" userId) noBody jsonResponse
836
837-- | Delete a list of the user's preferences.
838--
839--   /Permissions/: Must be logged in as the user being updated or have the
840--   @edit_other_users@ permission.
841mmDeleteUsersPreferences :: UserParam -> (Seq Preference) -> Session -> IO ()
842mmDeleteUsersPreferences userId body =
843  inPost (printf "/users/%s/preferences/delete" userId) (jsonBody body) noResponse
844
845-- | Lists the current user's stored preferences in the given category.
846--
847--   /Permissions/: Must be logged in as the user being updated or have the
848--   @edit_other_users@ permission.
849mmListUsersPreferencesByCategory :: UserParam -> Text -> Session -> IO (Seq Preference)
850mmListUsersPreferencesByCategory userId category =
851  inGet (printf "/users/%s/preferences/%s" userId category) noBody jsonResponse
852
853
854-- * Reactions
855
856mmGetReactionsForPost :: PostId -> Session -> IO (Seq Reaction)
857mmGetReactionsForPost postId =
858  inGet (printf "/posts/%s/reactions" postId) noBody jsonResponse
859
860mmPostReaction :: PostId -> UserId -> T.Text -> Session -> IO ()
861mmPostReaction postId userId reac =
862    let body = A.object [ "user_id" A..= userId
863                        , "post_id" A..= postId
864                        , "emoji_name" A..= reac
865                        ]
866    in inPost (printf "/reactions") (jsonBody body) noResponse
867
868mmDeleteReaction :: PostId -> UserId -> T.Text -> Session -> IO ()
869mmDeleteReaction postId userId reac =
870    inDelete (printf "/users/%s/posts/%s/reactions/%s" userId postId reac) noBody noResponse
871
872-- * SAML
873
874-- -- | Upload the private key to be used for encryption with your SAML
875-- --   configuration. This will also set the filename for the PrivateKeyFile
876-- --   setting in your @config.json@.
877-- --
878-- --   /Permissions/: Must have @manage_system@ permission.
879-- mmUploadPrivateKey :: Session -> IO ()
880-- mmUploadPrivateKey =
881--   inPost "/saml/certificate/private" noBody noResponse
882
883-- -- | Delete the current private key being used with your SAML
884-- --   configuration. This will also disable encryption for SAML on your
885-- --   system as this key is required for that.
886-- --
887-- --   /Permissions/: Must have @manage_system@ permission.
888-- mmRemovePrivateKey :: Session -> IO ()
889-- mmRemovePrivateKey =
890--   inDelete "/saml/certificate/private" noBody jsonResponse
891
892-- -- | Upload the public certificate to be used for encryption with your SAML
893-- --   configuration. This will also set the filename for the
894-- --   PublicCertificateFile setting in your @config.json@.
895-- --
896-- --   /Permissions/: Must have @manage_system@ permission.
897-- mmUploadPublicCertificate :: Session -> IO ()
898-- mmUploadPublicCertificate =
899--   inPost "/saml/certificate/public" noBody jsonResponse
900
901-- -- | Delete the current public certificate being used with your SAML
902-- --   configuration. This will also disable encryption for SAML on your
903-- --   system as this certificate is required for that.
904-- --
905-- --   /Permissions/: Must have @manage_system@ permission.
906-- mmRemovePublicCertificate :: Session -> IO ()
907-- mmRemovePublicCertificate =
908--   inDelete "/saml/certificate/public" noBody jsonResponse
909
910-- -- | Upload the IDP certificate to be used with your SAML configuration.
911-- --   This will also set the filename for the IdpCertificateFile setting in
912-- --   your @config.json@.
913-- --
914-- --   /Permissions/: Must have @manage_system@ permission.
915-- mmUploadIdpCertificate :: Session -> IO ()
916-- mmUploadIdpCertificate =
917--   inPost "/saml/certificate/idp" noBody jsonResponse
918
919-- -- | Delete the current IDP certificate being used with your SAML
920-- --   configuration. This will also disable SAML on your system as this
921-- --   certificate is required for SAML.
922-- --
923-- --   /Permissions/: Must have @manage_system@ permission.
924-- mmRemoveIdpCertificate :: Session -> IO ()
925-- mmRemoveIdpCertificate =
926--   inDelete "/saml/certificate/idp" noBody jsonResponse
927
928-- -- | Get the status of the uploaded certificates and keys in use by your
929-- --   SAML configuration.
930-- --
931-- --   /Permissions/: Must have @manage_system@ permission.
932-- mmGetCertificateStatus :: Session -> IO SamlCertificateStatus
933-- mmGetCertificateStatus =
934--   inGet "/saml/certificate/status" noBody jsonResponse
935
936-- -- | Get SAML metadata from the server. SAML must be configured properly.
937-- --
938-- --   /Permissions/: No permission required.
939-- mmGetMetadata :: Session -> IO Text
940-- mmGetMetadata =
941--   inGet "/saml/metadata" noBody jsonResponse
942
943
944-- * Statuses
945
946mmGetUserStatusByIds :: Seq UserId -> Session -> IO (Seq Status)
947mmGetUserStatusByIds body =
948  inPost "/users/status/ids" (jsonBody body) jsonResponse
949
950
951-- * System
952
953-- -- | Get a page of audits for all users on the system, selected with @page@
954-- --   and @per_page@ query parameters.
955-- --
956-- --   /Permissions/: Must have @manage_system@ permission.
957-- mmGetAudits :: Maybe Integer -> Maybe Integer -> Session -> IO (Seq Audit)
958-- mmGetAudits page perPage =
959--   inGet (printf "/audits?%s" (mkQueryString [ sequence ("page", fmap show page) , sequence ("per_page", fmap show perPage) ])) noBody jsonResponse
960
961-- -- | Get a subset of the server license needed by the client.
962-- --
963-- --   /Permissions/: No permission required but having the @manage_system@
964-- --   permission returns more information.
965-- mmGetClientLicense :: Text -> Session -> IO ()
966-- mmGetClientLicense format =
967--   inGet (printf "/license/client?%s" (mkQueryString [ Just ("format", T.unpack format) ])) noBody jsonResponse
968
969-- -- | Upload a license to enable enterprise features.
970-- --
971-- --   /Minimum server version/: 4.0
972-- --
973-- --   /Permissions/: Must have @manage_system@ permission.
974-- mmUploadLicenseFile :: Session -> IO ()
975-- mmUploadLicenseFile =
976--   inPost "/license" noBody jsonResponse
977
978-- -- | Remove the license file from the server. This will disable all
979-- --   enterprise features.
980-- --
981-- --   /Minimum server version/: 4.0
982-- --
983-- --   /Permissions/: Must have @manage_system@ permission.
984-- mmRemoveLicenseFile :: Session -> IO ()
985-- mmRemoveLicenseFile =
986--   inDelete "/license" noBody jsonResponse
987
988-- -- | Get a valid WebRTC token, STUN and TURN server URLs along with TURN
989-- --   credentials to use with the Mattermost WebRTC service. See
990-- --   https:\/\/docs.mattermost.com\/administration\/config-settings.html
991-- --   #webrtc-beta for WebRTC configutation settings. The token returned is
992-- --   for the current user's session.
993-- --
994-- --   /Permissions/: Must be authenticated.
995-- mmGetWebrtcToken :: Session -> IO XX8
996-- mmGetWebrtcToken =
997--   inGet "/webrtc/token" noBody jsonResponse
998
999-- | Get a subset of the server configuration needed by the client.
1000--
1001--   /Permissions/: No permission required.
1002mmGetClientConfiguration :: Maybe Text -> Session -> IO ClientConfig
1003mmGetClientConfiguration format =
1004  inGet (printf "/config/client?%s" (mkQueryString [ sequence ("format", fmap T.unpack format) ])) noBody jsonResponse
1005
1006-- | Limited version of 'mmGetClientConfiguration' that doesn't need a session ID.
1007mmGetLimitedClientConfiguration :: ConnectionData -> IO LimitedClientConfig
1008mmGetLimitedClientConfiguration cd =
1009  doUnauthRequest cd HTTP.GET url noBody >>= jsonResponse
1010  where
1011    url = printf "/config/client?%s" (mkQueryString [sequence ("format", Just "old")])
1012
1013-- -- | Reload the configuration file to pick up on any changes made to it.
1014-- --
1015-- --   /Permissions/: Must have @manage_system@ permission.
1016-- mmReloadConfiguration :: Session -> IO ()
1017-- mmReloadConfiguration =
1018--   inPost "/config/reload" noBody jsonResponse
1019
1020-- -- | Purge all the in-memory caches for the Mattermost server. This can
1021-- --   have a temporary negative effect on performance while the caches are
1022-- --   re-populated.
1023-- --
1024-- --   /Permissions/: Must have @manage_system@ permission.
1025-- mmInvalidateAllCaches :: Session -> IO ()
1026-- mmInvalidateAllCaches =
1027--   inPost "/caches/invalidate" noBody jsonResponse
1028
1029-- -- | Recycle database connections by closing and reconnecting all
1030-- --   connections to master and read replica databases.
1031-- --
1032-- --   /Permissions/: Must have @manage_system@ permission.
1033-- mmRecycleDatabaseConnections :: Session -> IO ()
1034-- mmRecycleDatabaseConnections =
1035--   inPost "/database/recycle" noBody jsonResponse
1036
1037-- -- | Add log messages to the server logs.
1038-- --
1039-- --   /Permissions/: Must have @manage_system@ permission or if
1040-- --   @ServiceSettings.EnableDeveloper@ in the
1041-- --
1042-- --   config file is set to @true@ then any user can use this endpoint.
1043-- mmAddLogMessage :: XX26 -> Session -> IO UnknownType
1044-- mmAddLogMessage body =
1045--   inPost "/logs" (jsonBody body) jsonResponse
1046
1047-- -- | Get a page of server logs, selected with @page@ and @per_page@ query
1048-- --   parameters.
1049-- --
1050-- --   /Permissions/: Must have @manage_system@ permission.
1051-- mmGetLogs :: Maybe Integer -> Maybe Integer -> Session -> IO (Seq Text)
1052-- mmGetLogs page perPage =
1053--   inGet (printf "/logs?%s" (mkQueryString [ sequence ("page", fmap show page) , sequence ("per_page", fmap show perPage) ])) noBody jsonResponse
1054
1055-- -- | Send a test email to make sure you have your email settings configured
1056-- --   correctly. Optionally provide a configuration in the request body to
1057-- --   test. If no valid configuration is present in the request body the
1058-- --   current server configuration will be tested.
1059-- --
1060-- --   /Permissions/: Must have @manage_system@ permission.
1061-- mmSendTestEmail :: Session -> IO ()
1062-- mmSendTestEmail =
1063--   inPost "/email/test" noBody jsonResponse
1064
1065-- -- | Check if the server is up and healthy based on the configuration
1066-- --   setting @GoRoutineHealthThreshold@. If @GoRoutineHealthThreshold@ and
1067-- --   the number of goroutines on the server exceeds that threshold the
1068-- --   server is considered unhealthy. If @GoRoutineHealthThreshold@ is not
1069-- --   set or the number of goroutines is below the threshold the server is
1070-- --   considered healthy.
1071-- --
1072-- --   /Minimum server version/: 3.10
1073-- --
1074-- --   /Permissions/: Must be logged in.
1075-- mmCheckSystemHealth :: Session -> IO UnknownType
1076-- mmCheckSystemHealth =
1077--   inGet "/system/ping" noBody jsonResponse
1078
1079-- -- | Get some analytics data about the system. This endpoint uses the old
1080-- --   format, the @\/analytics@ route is reserved for the new format when it
1081-- --   gets implemented.
1082-- --
1083-- --
1084-- --   The returned JSON changes based on the @name@ query parameter but is
1085-- --   always key\/value pairs.
1086-- --
1087-- --
1088-- --   /Minimum server version/: 4.0
1089-- --
1090-- --
1091-- --   /Permissions/: Must have @manage_system@ permission.
1092-- mmGetAnalytics :: Maybe Text -> TeamId -> Session -> IO ()
1093-- mmGetAnalytics name teamId =
1094--   inGet (printf "/analytics/old?%s" (mkQueryString [ sequence ("name", fmap T.unpack name) , Just ("team_id", T.unpack (idString teamId)) ])) noBody jsonResponse
1095
1096-- | Submit a new configuration for the server to use.
1097--
1098--   /Permissions/: Must have @manage_system@ permission.
1099mmUpdateConfiguration :: ServerConfig -> Session -> IO ServerConfig
1100mmUpdateConfiguration body =
1101  inPut "/config" (jsonBody body) jsonResponse
1102
1103-- | Retrieve the current server configuration
1104--
1105--   /Permissions/: Must have @manage_system@ permission.
1106mmGetConfiguration :: Session -> IO ServerConfig
1107mmGetConfiguration =
1108  inGet "/config" noBody jsonResponse
1109
1110
1111
1112-- * Teams
1113
1114-- | Get a team member on the system.
1115--
1116--   /Permissions/: Must be authenticated and have the @view_team@
1117--   permission.
1118mmGetTeamMember :: TeamId -> UserParam -> Session -> IO TeamMember
1119mmGetTeamMember teamId userId =
1120  inGet (printf "/teams/%s/members/%s" teamId userId) noBody jsonResponse
1121
1122-- | Delete the team member object for a user, effectively removing them
1123--   from a team.
1124--
1125--   /Permissions/: Must be logged in as the user or have the
1126--   @remove_user_from_team@ permission.
1127mmRemoveUserFromTeam :: TeamId -> UserParam -> Session -> IO ()
1128mmRemoveUserFromTeam teamId userId =
1129  inDelete (printf "/teams/%s/members/%s" teamId userId) noBody jsonResponse
1130
1131-- -- | Get a page of deleted channels on a team based on query string
1132-- --   parameters - team_id, page and per_page.
1133-- --
1134-- --
1135-- --   /Minimum server version/: 3.10
1136-- --
1137-- --
1138-- --   /Permissions/: Must be authenticated and have the @manage_team@
1139-- --   permission.
1140-- mmGetDeletedChannels :: TeamId -> Maybe Integer -> Maybe Integer -> Session -> IO (Seq Channel)
1141-- mmGetDeletedChannels teamId page perPage =
1142--   inGet (printf "/teams/%s/channels/deleted?%s" teamId (mkQueryString [ sequence ("page", fmap show page) , sequence ("per_page", fmap show perPage) ])) noBody jsonResponse
1143
1144-- -- | Update a team member roles. Valid team roles are "team_user",
1145-- --   "team_admin" or both of them. Overwrites any previously assigned team
1146-- --   roles.
1147-- --
1148-- --   /Permissions/: Must be authenticated and have the @manage_team_roles@
1149-- --   permission.
1150-- mmUpdateTeamMemberRoles :: TeamId -> UserId -> Text -> Session -> IO ()
1151-- mmUpdateTeamMemberRoles teamId userId roles =
1152--   inPut (printf "/teams/%s/members/%s/roles" teamId userId) (jsonBody (A.object [ "roles" A..= roles ])) jsonResponse
1153
1154-- | Get a page of public channels on a team based on query string
1155--   parameters - page and per_page.
1156--
1157--   /Permissions/: Must be authenticated and have the @list_team_channels@
1158--   permission.
1159mmGetPublicChannels :: TeamId -> Maybe Int -> Maybe Int -> Session -> IO (Seq Channel)
1160mmGetPublicChannels teamId page perPage =
1161  inGet (printf "/teams/%s/channels?%s" teamId (mkQueryString [ sequence ("page", fmap show page)
1162                                                              , sequence ("per_page", fmap show perPage)
1163                                                              ])) noBody jsonResponse
1164
1165-- -- | Check if the team exists based on a team name.
1166-- mmCheckIfTeamExists :: Text -> Session -> IO TeamExists
1167-- mmCheckIfTeamExists name =
1168--   inGet (printf "/teams/name/%s/exists" name) noBody jsonResponse
1169
1170-- | Create a new team on the system.
1171--
1172--   /Permissions/: Must be authenticated and have the @create_team@
1173--   permission.
1174mmCreateTeam :: TeamsCreate -> Session -> IO Team
1175mmCreateTeam body =
1176  inPost "/teams" (jsonBody body) jsonResponse
1177
1178-- | For regular users only returns open teams. Users with the
1179--   "manage_system" permission will return teams regardless of type. The
1180--   result is based on query string parameters - page and per_page.
1181--
1182--   /Permissions/: Must be authenticated. "manage_system" permission is
1183--   required to show all teams.
1184mmGetTeams :: Maybe Integer -> Maybe Integer -> Session -> IO (Seq Team)
1185mmGetTeams page perPage =
1186  inGet (printf "/teams?%s"
1187          (mkQueryString [ sequence ("page", fmap show page)
1188                         , sequence ("per_page", fmap show perPage)
1189                         ])) noBody jsonResponse
1190
1191-- | Search teams based on search term provided in the request body.
1192--
1193--   /Permissions/: Logged in user only shows open teams
1194--
1195--   Logged in user with "manage_system" permission shows all teams
1196mmSearchTeams :: Text -> Session -> IO (Seq Team)
1197mmSearchTeams term =
1198  inPost "/teams/search" (jsonBody (A.object [ "term" A..= term ])) jsonResponse
1199
1200-- -- | Invite users to the existing team usign the user's email.
1201-- --
1202-- --   /Permissions/: Must have @invite_to_team@ permission for the team.
1203-- mmInviteUsersToTeamByEmail :: TeamId -> (Seq Text) -> Session -> IO ()
1204-- mmInviteUsersToTeamByEmail teamId body =
1205--   inPost (printf "/teams/%s/invite/email" teamId) (jsonBody body) jsonResponse
1206
1207-- | Search public channels on a team based on the search term provided in
1208--   the request body.
1209--
1210--   /Permissions/: Must have the @list_team_channels@ permission.
1211mmSearchChannels :: TeamId -> Text -> Session -> IO (Seq Channel)
1212mmSearchChannels teamId term =
1213  inPost (printf "/teams/%s/channels/search" teamId) (jsonBody (A.object [ "term" A..= term ])) jsonResponse
1214
1215-- -- | Get the count for unread messages and mentions in the teams the user
1216-- --   is a member of.
1217-- --
1218-- --   /Permissions/: Must be logged in.
1219-- mmGetTeamUnreadsForUser :: UserId -> Text -> Session -> IO (Seq TeamUnread)
1220-- mmGetTeamUnreadsForUser userId excludeTeam =
1221--   inGet (printf "/users/%s/teams/unread?%s" userId (mkQueryString [ Just ("exclude_team", T.unpack excludeTeam) ])) noBody jsonResponse
1222
1223-- | Get a list of teams that a user is on.
1224--
1225--   /Permissions/: Must be authenticated as the user or have the
1226--   @manage_system@ permission.
1227mmGetUsersTeams :: UserParam -> Session -> IO (Seq Team)
1228mmGetUsersTeams userId =
1229  inGet (printf "/users/%s/teams" userId) noBody jsonResponse
1230
1231-- -- | Using either an invite id or hash\/data pair from an email invite
1232-- --   link, add a user to a team.
1233-- --
1234-- --   /Permissions/: Must be authenticated.
1235-- mmAddUserToTeamFromInvite :: Text -> Text -> InviteId -> Session -> IO TeamMember
1236-- mmAddUserToTeamFromInvite hash data_ inviteId =
1237--   inPost (printf "/teams/members/invite?%s" (mkQueryString [ Just ("hash", T.unpack hash) , Just ("data", T.unpack data_) , Just ("invite_id", T.unpack (idString inviteId)) ])) noBody jsonResponse
1238
1239-- -- | Get a team stats on the system.
1240-- --
1241-- --   /Permissions/: Must be authenticated and have the @view_team@
1242-- --   permission.
1243-- mmGetTeamStats :: TeamId -> Session -> IO TeamStats
1244-- mmGetTeamStats teamId =
1245--   inGet (printf "/teams/%s/stats" teamId) noBody jsonResponse
1246
1247-- | Get a list of team members based on a provided array of user ids.
1248--
1249--   /Permissions/: Must have @view_team@ permission for the team.
1250mmGetTeamMembersByIds :: TeamId -> Seq UserId -> Session -> IO (Seq TeamMember)
1251mmGetTeamMembersByIds teamId body =
1252  inPost (printf "/teams/%s/members/ids" teamId) (jsonBody body) jsonResponse
1253
1254-- -- | Partially update a team by providing only the fields you want to
1255-- --   update. Omitted fields will not be updated. The fields that can be
1256-- --   updated are defined in the request body, all other provided fields
1257-- --   will be ignored.
1258-- --
1259-- --   /Permissions/: Must have the @manage_team@ permission.
1260-- mmPatchTeam :: TeamId -> XX23 -> Session -> IO Team
1261-- mmPatchTeam teamId body =
1262--   inPut (printf "/teams/%s/patch" teamId) (jsonBody body) jsonResponse
1263
1264-- | Get a list of team members for a user. Useful for getting the ids of
1265--   teams the user is on and the roles they have in those teams.
1266--
1267--   /Permissions/: Must be logged in as the user or have the
1268--   @edit_other_users@ permission.
1269mmGetTeamMembersForUser :: UserParam -> Session -> IO (Seq TeamMember)
1270mmGetTeamMembersForUser userId =
1271  inGet (printf "/users/%s/teams/members" userId) noBody jsonResponse
1272
1273-- | Add user to the team by user_id.
1274--
1275--   /Permissions/: Must be authenticated and team be open to add self. For
1276--   adding another user, authenticated user must have the
1277--   @add_user_to_team@ permission.
1278mmAddUserToTeam :: TeamId -> TeamMember -> Session -> IO TeamMember
1279mmAddUserToTeam teamId body =
1280  inPost (printf "/teams/%s/members" teamId) (jsonBody body) jsonResponse
1281
1282-- -- | Get a page team members list based on query string parameters - team
1283-- --   id, page and per page.
1284-- --
1285-- --   /Permissions/: Must be authenticated and have the @view_team@
1286-- --   permission.
1287-- mmGetTeamMembers :: TeamId -> Maybe Integer -> Maybe Integer -> Session -> IO (Seq TeamMember)
1288-- mmGetTeamMembers teamId page perPage =
1289--   inGet (printf "/teams/%s/members?%s" teamId (mkQueryString [ sequence ("page", fmap show page) , sequence ("per_page", fmap show perPage) ])) noBody jsonResponse
1290
1291-- -- | Import a team into a existing team. Import users, channels, posts,
1292-- --   hooks.
1293-- --
1294-- --   /Permissions/: Must have @permission_import_team@ permission.
1295-- mmImportTeamFromOtherApplication :: TeamId -> Session -> IO Text
1296-- mmImportTeamFromOtherApplication teamId =
1297--   inPost (printf "/teams/%s/import" teamId) noBody jsonResponse
1298
1299-- -- | Add a number of users to the team by user_id.
1300-- --
1301-- --   /Permissions/: Must be authenticated. Authenticated user must have the
1302-- --   @add_user_to_team@ permission.
1303-- mmAddMultipleUsersToTeam :: TeamId -> (Seq TeamMember) -> Session -> IO (Seq TeamMember)
1304-- mmAddMultipleUsersToTeam teamId body =
1305--   inPost (printf "/teams/%s/members/batch" teamId) (jsonBody body) jsonResponse
1306
1307-- -- | Get the unread mention and message counts for a team for the specified
1308-- --   user.
1309-- --
1310-- --   /Permissions/: Must be the user or have @edit_other_users@ permission
1311-- --   and have @view_team@ permission for the team.
1312-- mmGetUnreadsForTeam :: UserId -> TeamId -> Session -> IO TeamUnread
1313-- mmGetUnreadsForTeam userId teamId =
1314--   inGet (printf "/users/%s/teams/%s/unread" userId teamId) noBody jsonResponse
1315
1316-- -- | Get the @name@, @display_name@, @description@ and @id@ for a team from
1317-- --   the invite id.
1318-- --
1319-- --
1320-- --   /Minimum server version/: 4.0
1321-- --
1322-- --
1323-- --   /Permissions/: No authentication required.
1324-- mmGetInviteInfoForTeam :: InviteId -> Session -> IO XX34
1325-- mmGetInviteInfoForTeam inviteId =
1326--   inGet (printf "/teams/invite/%s" inviteId) noBody jsonResponse
1327
1328-- | Get a team based on provided name string
1329--
1330--   /Permissions/: Must be authenticated, team type is open and have the
1331--   @view_team@ permission.
1332mmGetTeamByName :: Text -> Session -> IO Team
1333mmGetTeamByName name =
1334  inGet (printf "/teams/name/%s" name) noBody jsonResponse
1335
1336-- -- | Update a team by providing the team object. The fields that can be
1337-- --   updated are defined in the request body, all other provided fields
1338-- --   will be ignored.
1339-- --
1340-- --   /Permissions/: Must have the @manage_team@ permission.
1341-- mmUpdateTeam :: TeamId -> XX36 -> Session -> IO Team
1342-- mmUpdateTeam teamId body =
1343--   inPut (printf "/teams/%s" teamId) (jsonBody body) jsonResponse
1344
1345-- | Get a team on the system.
1346--
1347--   /Permissions/: Must be authenticated and have the @view_team@
1348--   permission.
1349mmGetTeam :: TeamId -> Session -> IO Team
1350mmGetTeam teamId =
1351  inGet (printf "/teams/%s" teamId) noBody jsonResponse
1352
1353-- -- | Delete a team softly and put in archived only.
1354-- --
1355-- --   /Permissions/: Must have the @manage_team@ permission.
1356-- mmDeleteTeam :: TeamId -> Bool -> Session -> IO ()
1357-- mmDeleteTeam teamId permanent =
1358--   inDelete (printf "/teams/%s?%s" teamId (mkQueryString [ Just ("permanent", if permanent then "true" else "false") ])) noBody jsonResponse
1359
1360
1361
1362-- * Users
1363
1364-- | Get a list of users based on search criteria provided in the request
1365--   body. Searches are typically done against username, full name,
1366--   nickname and email unless otherwise configured by the server.
1367--
1368--   /Permissions/: Requires an active session and @read_channel@ and\/or
1369--   @view_team@ permissions for any channels or teams specified in the
1370--   request body.
1371mmSearchUsers :: UserSearch -> Session -> IO (Seq User)
1372mmSearchUsers body =
1373  inPost "/users/search" (jsonBody body) jsonResponse
1374
1375-- | Get a list of users based on a provided list of usernames. The
1376-- input usernames must be usernames without sigils (@).
1377--
1378--   /Permissions/: Requires an active session but no other permissions.
1379mmGetUsersByUsernames :: (Seq Text) -> Session -> IO (Seq User)
1380mmGetUsersByUsernames body =
1381  inPost "/users/usernames" (jsonBody body) jsonResponse
1382
1383-- -- | Revokes a user session from the provided user id and session id
1384-- --   strings.
1385-- --
1386-- --   /Permissions/: Must be logged in as the user being updated or have the
1387-- --   @edit_other_users@ permission.
1388-- mmRevokeUserSession :: UserId -> Text -> Session -> IO ()
1389-- mmRevokeUserSession userId sessionId =
1390--   inPost (printf "/users/%s/sessions/revoke" userId) (jsonBody (A.object [ "session_id" A..= sessionId ])) jsonResponse
1391
1392-- | Update a user's system-level roles. Valid user roles are
1393--   "system_user", "system_admin" or both of them. Overwrites any
1394--   previously assigned system-level roles.
1395--
1396--   /Permissions/: Must have the @manage_roles@ permission.
1397mmUpdateUsersRoles :: UserId -> Text -> Session -> IO ()
1398mmUpdateUsersRoles userId roles =
1399  inPut (printf "/users/%s/roles" userId) (jsonBody (A.object [ "roles" A..= roles ])) noResponse
1400
1401-- -- | Send an email with a verification link to a user that has an email
1402-- --   matching the one in the request body. This endpoint will return
1403-- --   success even if the email does not match any users on the system.
1404-- --
1405-- --   /Permissions/: No permissions required.
1406-- mmSendVerificationEmail :: Text -> Session -> IO ()
1407-- mmSendVerificationEmail email =
1408--   inPost "/users/email/verify/send" (jsonBody (A.object [ "email" A..= email ])) jsonResponse
1409
1410-- -- | Get a list of sessions by providing the user GUID. Sensitive
1411-- --   information will be sanitized out.
1412-- --
1413-- --   /Permissions/: Must be logged in as the user being updated or have the
1414-- --   @edit_other_users@ permission.
1415-- -- mmGetUsersSessions :: UserId -> Session -> IO (Seq Session)
1416-- -- mmGetUsersSessions userId =
1417-- --   inGet (printf "/users/%s/sessions" userId) noBody jsonResponse
1418
1419-- -- | Check if a user has multi-factor authentication active on their
1420-- --   account by providing a login id. Used to check whether an MFA code
1421-- --   needs to be provided when logging in.
1422-- --
1423-- --   /Permissions/: No permission required.
1424-- mmCheckMfa :: Text -> Session -> IO Bool
1425-- mmCheckMfa loginId =
1426--   inPost "/users/mfa" (jsonBody (A.object [ "login_id" A..= loginId ])) jsonResponse
1427
1428-- -- | Generate a user access token that can be used to authenticate with the
1429-- --   Mattermost REST API.
1430-- --
1431-- --
1432-- --   /Minimum server version/: 4.1
1433-- --
1434-- --
1435-- --   /Permissions/: Must have @create_user_access_token@ permission. For
1436-- --   non-self requests, must also have the @edit_other_users@ permission.
1437-- mmCreateUserAccessToken :: UserId -> Text -> Session -> IO UserAccessToken
1438-- mmCreateUserAccessToken userId description =
1439--   inPost (printf "/users/%s/tokens" userId) (jsonBody (A.object [ "description" A..= description ])) jsonResponse
1440
1441-- -- | Get a list of user access tokens for a user. Does not include the
1442-- --   actual authentication tokens. Use query paremeters for paging.
1443-- --
1444-- --
1445-- --   /Minimum server version/: 4.1
1446-- --
1447-- --
1448-- --   /Permissions/: Must have @read_user_access_token@ permission. For non-
1449-- --   self requests, must also have the @edit_other_users@ permission.
1450-- mmGetUserAccessTokens :: UserId -> Maybe Integer -> Maybe Integer -> Session -> IO (Seq UserAccessTokenSanitized)
1451-- mmGetUserAccessTokens userId page perPage =
1452--   inGet (printf "/users/%s/tokens?%s" userId (mkQueryString [ sequence ("page", fmap show page) , sequence ("per_page", fmap show perPage) ])) noBody jsonResponse
1453
1454-- -- | Revoke a user access token and delete any sessions using the token.
1455-- --
1456-- --
1457-- --   /Minimum server version/: 4.1
1458-- --
1459-- --
1460-- --   /Permissions/: Must have @revoke_user_access_token@ permission. For
1461-- --   non-self requests, must also have the @edit_other_users@ permission.
1462-- mmRevokeUserAccessToken :: Text -> Session -> IO ()
1463-- mmRevokeUserAccessToken token =
1464--   inPost "/users/tokens/revoke" (jsonBody (A.object [ "token" A..= token ])) jsonResponse
1465
1466-- -- | Get a user access token. Does not include the actual authentication
1467-- --   token.
1468-- --
1469-- --
1470-- --   /Minimum server version/: 4.1
1471-- --
1472-- --
1473-- --   /Permissions/: Must have @read_user_access_token@ permission. For non-
1474-- --   self requests, must also have the @edit_other_users@ permission.
1475-- mmGetUserAccessToken :: TokenId -> Session -> IO UserAccessTokenSanitized
1476-- mmGetUserAccessToken tokenId =
1477--   inGet (printf "/users/tokens/%s" tokenId) noBody jsonResponse
1478
1479-- -- | Update user active or inactive status
1480-- --
1481-- --   /Permissions/: User can deactivate itself.
1482-- --
1483-- --   User with @manage_system@ permission can activate or deactivate a
1484-- --   user.
1485-- mmUpdateUserActiveStatus :: UserId -> Bool -> Session -> IO ()
1486-- mmUpdateUserActiveStatus userId active =
1487--   inPut (printf "/users/%s/active" userId) (jsonBody (A.object [ "active" A..= active ])) jsonResponse
1488
1489-- -- | Get a user object by providing a username. Sensitive information will
1490-- --   be sanitized out.
1491-- --
1492-- --   /Permissions/: Requires an active session but no other permissions.
1493-- mmGetUserByUsername :: Text -> Session -> IO User
1494-- mmGetUserByUsername username =
1495--   inGet (printf "/users/username/%s" username) noBody jsonResponse
1496
1497-- | Get a list of users based on a provided list of user ids.
1498--
1499--   /Permissions/: Requires an active session but no other permissions.
1500mmGetUsersByIds :: Seq UserId -> Session -> IO (Seq User)
1501mmGetUsersByIds body =
1502  inPost "/users/ids" (jsonBody body) jsonResponse
1503
1504-- -- | Attach a mobile device id to the currently logged in session. This
1505-- --   will enable push notiofications for a user, if configured by the
1506-- --   server.
1507-- --
1508-- --   /Permissions/: Must be authenticated.
1509-- mmAttachMobileDevice :: Text -> Session -> IO ()
1510-- mmAttachMobileDevice deviceId =
1511--   inPut "/users/sessions/device" (jsonBody (A.object [ "device_id" A..= deviceId ])) jsonResponse
1512
1513-- -- | Send an email containing a link for resetting the user's password. The
1514-- --   link will contain a one-use, timed recovery code tied to the user's
1515-- --   account. Only works for non-SSO users.
1516-- --
1517-- --   /Permissions/: No permissions required.
1518-- mmSendPasswordResetEmail :: Text -> Session -> IO ()
1519-- mmSendPasswordResetEmail email =
1520--   inPost "/users/password/reset/send" (jsonBody (A.object [ "email" A..= email ])) jsonResponse
1521
1522-- -- | Get a user object by providing a user email. Sensitive information
1523-- --   will be sanitized out.
1524-- --
1525-- --   /Permissions/: Requires an active session but no other permissions.
1526-- mmGetUserByEmail :: Text -> Session -> IO User
1527-- mmGetUserByEmail email =
1528--   inGet (printf "/users/email/%s" email) noBody jsonResponse
1529
1530-- -- | Switch a user's login method from using email to OAuth2\/SAML\/LDAP or
1531-- --   back to email. When switching to OAuth2\/SAML, account switching is
1532-- --   not complete until the user follows the returned link and completes
1533-- --   any steps on the OAuth2\/SAML service provider.
1534-- --
1535-- --
1536-- --   To switch from email to OAuth2\/SAML, specify @current_service@,
1537-- --   @new_service@, @email@ and @password@.
1538-- --
1539-- --
1540-- --   To switch from OAuth2\/SAML to email, specify @current_service@,
1541-- --   @new_service@, @email@ and @new_password@.
1542-- --
1543-- --
1544-- --   To switch from email to LDAP\/AD, specify @current_service@,
1545-- --   @new_service@, @email@, @password@, @ldap_ip@ and @new_password@ (this
1546-- --   is the user's LDAP password).
1547-- --
1548-- --
1549-- --   To switch from LDAP\/AD to email, specify @current_service@,
1550-- --   @new_service@, @ldap_ip@, @password@ (this is the user's LDAP
1551-- --   password), @email@  and @new_password@.
1552-- --
1553-- --
1554-- --   Additionally, specify @mfa_code@ when trying to switch an account on
1555-- --   LDAP\/AD or email that has MFA activated.
1556-- --
1557-- --
1558-- --   /Permissions/: No current authentication required except when
1559-- --   switching from OAuth2\/SAML to email.
1560-- mmSwitchLoginMethod :: XX19 -> Session -> IO Text
1561-- mmSwitchLoginMethod body =
1562--   inPost "/users/login/switch" (jsonBody body) jsonResponse
1563
1564-- -- | Set a user's profile image based on user_id string parameter.
1565-- --
1566-- --   /Permissions/: Must be logged in as the user being updated or have the
1567-- --   @edit_other_users@ permission.
1568-- mmSetUsersProfileImage :: UserId -> Session -> IO ()
1569-- mmSetUsersProfileImage userId =
1570--   inPost (printf "/users/%s/image" userId) noBody jsonResponse
1571
1572-- -- | Get a user's profile image based on user_id string parameter.
1573-- --
1574-- --   /Permissions/: Must be logged in.
1575-- mmGetUsersProfileImage :: UserId -> Session -> IO ()
1576-- mmGetUsersProfileImage userId =
1577--   inGet (printf "/users/%s/image" userId) noBody jsonResponse
1578
1579-- -- | Activates multi-factor authentication for the user if @activate@ is
1580-- --   true and a valid @code@ is provided. If activate is false, then @code@
1581-- --   is not required and multi-factor authentication is disabled for the
1582-- --   user.
1583-- --
1584-- --   /Permissions/: Must be logged in as the user being updated or have the
1585-- --   @edit_other_users@ permission.
1586-- mmUpdateUsersMfa :: UserId -> XX22 -> Session -> IO ()
1587-- mmUpdateUsersMfa userId body =
1588--   inPut (printf "/users/%s/mfa" userId) (jsonBody body) jsonResponse
1589
1590-- -- | Verify the email used by a user to sign-up their account with.
1591-- --
1592-- --   /Permissions/: No permissions required.
1593-- mmVerifyUserEmail :: Text -> Session -> IO ()
1594-- mmVerifyUserEmail token =
1595--   inPost "/users/email/verify" (jsonBody (A.object [ "token" A..= token ])) jsonResponse
1596
1597-- -- | Update the password for a user using a one-use, timed recovery code
1598-- --   tied to the user's account. Only works for non-SSO users.
1599-- --
1600-- --   /Permissions/: No permissions required.
1601-- mmResetPassword :: XX24 -> Session -> IO ()
1602-- mmResetPassword body =
1603--   inPost "/users/password/reset" (jsonBody body) jsonResponse
1604
1605-- -- | Get a list of audit by providing the user GUID.
1606-- --
1607-- --   /Permissions/: Must be logged in as the user or have the
1608-- --   @edit_other_users@ permission.
1609-- mmGetUsersAudits :: UserId -> Session -> IO (Seq Audit)
1610-- mmGetUsersAudits userId =
1611--   inGet (printf "/users/%s/audits" userId) noBody jsonResponse
1612
1613-- -- | Update a user's password. New password must meet password policy set
1614-- --   by server configuration.
1615-- --
1616-- --   /Permissions/: Must be logged in as the user the password is being
1617-- --   changed for or have @manage_system@ permission.
1618-- mmUpdateUsersPassword :: UserId -> XX29 -> Session -> IO ()
1619-- mmUpdateUsersPassword userId body =
1620--   inPut (printf "/users/%s/password" userId) (jsonBody body) jsonResponse
1621
1622-- -- | Update a user by providing the user object. The fields that can be
1623-- --   updated are defined in the request body, all other provided fields
1624-- --   will be ignored.
1625-- --
1626-- --   /Permissions/: Must be logged in as the user being updated or have the
1627-- --   @edit_other_users@ permission.
1628-- mmUpdateUser :: UserId -> XX30 -> Session -> IO User
1629-- mmUpdateUser userId body =
1630--   inPut (printf "/users/%s" userId) (jsonBody body) jsonResponse
1631
1632-- | Get a user a object. Sensitive information will be sanitized out.
1633--
1634--   /Permissions/: Requires an active session but no other permissions.
1635mmGetUser :: UserParam -> Session -> IO User
1636mmGetUser userId =
1637  inGet (printf "/users/%s" userId) noBody jsonResponse
1638
1639-- | Deactivates the user by archiving its user object.
1640--
1641--   /Permissions/: Must be logged in as the user being deactivated or have
1642--   the @edit_other_users@ permission.
1643mmDeactivateUserAccount :: UserParam -> Session -> IO ()
1644mmDeactivateUserAccount userId =
1645  inDelete (printf "/users/%s" userId) noBody jsonResponse
1646
1647-- | Create a new user on the system.
1648--
1649--   /Permissions/: No permission required but user creation can be
1650--   controlled by server configuration.
1651mmCreateUser :: UsersCreate -> Session -> IO User
1652mmCreateUser body =
1653  inPost "/users" (jsonBody body) jsonResponse
1654  -- UsersCreate was XX31
1655
1656data UserQuery = UserQuery
1657  { userQueryPage         :: Maybe Int
1658  , userQueryPerPage      :: Maybe Int
1659  , userQueryInTeam       :: Maybe TeamId
1660  , userQueryNotInTeam    :: Maybe TeamId
1661  , userQueryInChannel    :: Maybe ChannelId
1662  , userQueryNotInChannel :: Maybe ChannelId
1663  , userQueryWithoutTeam  :: Maybe Bool
1664  , userQuerySort         :: Maybe UserQuerySort
1665  }
1666
1667defaultUserQuery :: UserQuery
1668defaultUserQuery = UserQuery
1669  { userQueryPage         = Nothing
1670  , userQueryPerPage      = Nothing
1671  , userQueryInTeam       = Nothing
1672  , userQueryNotInTeam    = Nothing
1673  , userQueryInChannel    = Nothing
1674  , userQueryNotInChannel = Nothing
1675  , userQueryWithoutTeam  = Nothing
1676  , userQuerySort         = Nothing
1677  }
1678
1679data UserQuerySort
1680  = UserQuerySortByLastActivity
1681  | UserQuerySortByCreation
1682
1683userQueryToQueryString :: UserQuery -> String
1684userQueryToQueryString UserQuery { .. } =
1685  mkQueryString [ sequence ("page", fmap show userQueryPage)
1686                , sequence ("per_page", fmap show userQueryPerPage)
1687                , sequence ("in_team", fmap (T.unpack . idString) userQueryInTeam)
1688                , sequence ("not_in_team", fmap (T.unpack . idString) userQueryNotInTeam)
1689                , sequence ("in_channel", fmap (T.unpack . idString) userQueryInChannel)
1690                , sequence ("not_in_channel", fmap (T.unpack . idString) userQueryNotInChannel)
1691                , sequence ( "without_team"
1692                           , case userQueryWithoutTeam of
1693                             Nothing -> Nothing
1694                             Just True -> Just "true"
1695                             Just False -> Just "false"
1696                           )
1697                , sequence ( "sort"
1698                           , case userQuerySort of
1699                               Nothing -> Nothing
1700                               Just UserQuerySortByLastActivity -> Just "last_activity_at"
1701                               Just UserQuerySortByCreation -> Just "create_at"
1702                           )
1703                ]
1704
1705-- | Get a page of a list of users. Based on query string parameters,
1706--   select users from a team, channel, or select users not in a specific
1707--   channel.
1708--
1709--
1710--   Since server version 4.0, some basic sorting is available using the
1711--   @sort@ query parameter. Sorting is currently only supported when
1712--   selecting users on a team.
1713--
1714--   /Permissions/: Requires an active session and (if specified)
1715--   membership to the channel or team being selected from.
1716mmGetUsers
1717  :: UserQuery
1718  -> Session
1719  -> IO (Seq User)
1720mmGetUsers userQuery =
1721  inGet (printf "/users?%s" (userQueryToQueryString userQuery)) noBody jsonResponse
1722
1723-- -- | Generates an multi-factor authentication secret for a user and returns
1724-- --   it as a string and as base64 encoded QR code image.
1725-- --
1726-- --   /Permissions/: Must be logged in as the user or have the
1727-- --   @edit_other_users@ permission.
1728-- mmGenerateMfaSecret :: UserId -> Session -> IO XX37
1729-- mmGenerateMfaSecret userId =
1730--   inPost (printf "/users/%s/mfa/generate" userId) noBody jsonResponse
1731
1732-- -- | Partially update a user by providing only the fields you want to
1733-- --   update. Omitted fields will not be updated. The fields that can be
1734-- --   updated are defined in the request body, all other provided fields
1735-- --   will be ignored.
1736-- --
1737-- --   /Permissions/: Must be logged in as the user being updated or have the
1738-- --   @edit_other_users@ permission.
1739-- mmPatchUser :: UserId -> XX38 -> Session -> IO User
1740-- mmPatchUser userId body =
1741--   inPut (printf "/users/%s/patch" userId) (jsonBody body) jsonResponse
1742
1743-- | Get a list of users for the purpose of autocompleting based on the
1744--   provided search term. Specify a combination of @team_id@ and
1745--   @channel_id@ to filter results further.
1746--
1747--   /Permissions/: Requires an active session and @view_team@ and
1748--   @read_channel@ on any teams or channels used to filter the results
1749--   further.
1750mmAutocompleteUsers :: Maybe TeamId
1751                    -> Maybe ChannelId
1752                    -> Text -> Session -> IO UserAutocomplete
1753mmAutocompleteUsers mTeamId mChannelId name =
1754    let queryString = mkQueryString args
1755        args = [ (("in_team",) . T.unpack . idString) <$> mTeamId
1756               , (("in_channel",) . T.unpack . idString) <$> mChannelId
1757               , Just ("name", T.unpack name)
1758               ]
1759    in inGet (printf "/users/autocomplete?%s" queryString) noBody jsonResponse
1760
1761-- | Get a list of channels for the purpose of autocompleting based on
1762--   the provided search term.
1763mmAutocompleteChannels :: TeamId -> Text -> Session -> IO (Seq Channel)
1764mmAutocompleteChannels teamId name =
1765    let queryString = mkQueryString args
1766        args = [ Just ("name", T.unpack name)
1767               ]
1768    in inGet (printf "/teams/%s/channels/autocomplete?%s" teamId queryString)
1769             noBody jsonResponse
1770
1771-- * Webhooks
1772
1773-- -- | Update an outgoing webhook given the hook id.
1774-- --
1775-- --   /Permissions/: @manage_webhooks@ for system or @manage_webhooks@ for
1776-- --   the specific team or @manage_webhooks@ for the channel.
1777-- mmUpdateAnOutgoingWebhook :: HookId -> XX12 -> Session -> IO OutgoingWebhook
1778-- mmUpdateAnOutgoingWebhook hookId body =
1779--   inPut (printf "/hooks/outgoing/%s" hookId) (jsonBody body) jsonResponse
1780
1781-- -- | Get an outgoing webhook given the hook id.
1782-- --
1783-- --   /Permissions/: @manage_webhooks@ for system or @manage_webhooks@ for
1784-- --   the specific team or @manage_webhooks@ for the channel.
1785-- mmGetAnOutgoingWebhook :: HookId -> Session -> IO OutgoingWebhook
1786-- mmGetAnOutgoingWebhook hookId =
1787--   inGet (printf "/hooks/outgoing/%s" hookId) noBody jsonResponse
1788
1789-- -- | Delete an outgoing webhook given the hook id.
1790-- --
1791-- --   /Permissions/: @manage_webhooks@ for system or @manage_webhooks@ for
1792-- --   the specific team or @manage_webhooks@ for the channel.
1793-- mmDeleteAnOutgoingWebhook :: HookId -> Session -> IO ()
1794-- mmDeleteAnOutgoingWebhook hookId =
1795--   inDelete (printf "/hooks/outgoing/%s" hookId) noBody jsonResponse
1796
1797-- -- | Regenerate the token for the outgoing webhook.
1798-- --
1799-- --   /Permissions/: @manage_webhooks@ for system or @manage_webhooks@ for
1800-- --   the specific team or @manage_webhooks@ for the channel.
1801-- mmRegenerateTokenForOutgoingWebhook :: HookId -> Session -> IO ()
1802-- mmRegenerateTokenForOutgoingWebhook hookId =
1803--   inPost (printf "/hooks/outgoing/%s/regen_token" hookId) noBody jsonResponse
1804
1805-- -- | Create an incoming webhook for a channel.
1806-- --
1807-- --   /Permissions/: @manage_webhooks@ for the channel the webhook is in.
1808-- mmCreateAnIncomingWebhook :: XX25 -> Session -> IO IncomingWebhook
1809-- mmCreateAnIncomingWebhook body =
1810--   inPost "/hooks/incoming" (jsonBody body) jsonResponse
1811
1812-- -- | Get a page of a list of incoming webhooks. Optionally filter for a
1813-- --   specific team using query parameters.
1814-- --
1815-- --   /Permissions/: @manage_webhooks@ for the system or @manage_webhooks@
1816-- --   for the specific team.
1817-- mmListIncomingWebhooks :: Maybe Integer -> Maybe Integer -> TeamId -> Session -> IO (Seq IncomingWebhook)
1818-- mmListIncomingWebhooks page perPage teamId =
1819--   inGet (printf "/hooks/incoming?%s" (mkQueryString [ sequence ("page", fmap show page) , sequence ("per_page", fmap show perPage) , Just ("team_id", T.unpack (idString teamId)) ])) noBody jsonResponse
1820
1821-- -- | Create an outgoing webhook for a team.
1822-- --
1823-- --   /Permissions/: @manage_webhooks@ for the team the webhook is in.
1824-- mmCreateAnOutgoingWebhook :: XX33 -> Session -> IO OutgoingWebhook
1825-- mmCreateAnOutgoingWebhook body =
1826--   inPost "/hooks/outgoing" (jsonBody body) jsonResponse
1827
1828-- -- | Get a page of a list of outgoing webhooks. Optionally filter for a
1829-- --   specific team or channel using query parameters.
1830-- --
1831-- --   /Permissions/: @manage_webhooks@ for the system or @manage_webhooks@
1832-- --   for the specific team\/channel.
1833-- mmListOutgoingWebhooks :: Maybe Integer -> Maybe Integer -> TeamId -> ChannelId -> Session -> IO (Seq OutgoingWebhook)
1834-- mmListOutgoingWebhooks page perPage teamId channelId =
1835--   inGet (printf "/hooks/outgoing?%s" (mkQueryString [ sequence ("page", fmap show page) , sequence ("per_page", fmap show perPage) , Just ("team_id", T.unpack (idString teamId)) , Just ("channel_id", T.unpack (idString channelId)) ])) noBody jsonResponse
1836
1837-- -- | Update an incoming webhook given the hook id.
1838-- --
1839-- --   /Permissions/: @manage_webhooks@ for system or @manage_webhooks@ for
1840-- --   the specific team or @manage_webhooks@ for the channel.
1841-- mmUpdateAnIncomingWebhook :: HookId -> XX35 -> Session -> IO IncomingWebhook
1842-- mmUpdateAnIncomingWebhook hookId body =
1843--   inPut (printf "/hooks/incoming/%s" hookId) (jsonBody body) jsonResponse
1844
1845-- -- | Get an incoming webhook given the hook id.
1846-- --
1847-- --   /Permissions/: @manage_webhooks@ for system or @manage_webhooks@ for
1848-- --   the specific team or @manage_webhooks@ for the channel.
1849-- mmGetAnIncomingWebhook :: HookId -> Session -> IO IncomingWebhook
1850-- mmGetAnIncomingWebhook hookId =
1851--   inGet (printf "/hooks/incoming/%s" hookId) noBody jsonResponse
1852
1853-- data AppError = AppError
1854--   { appErrorStatusCode :: Integer
1855--   , appErrorMessage :: Text
1856--   , appErrorId :: Text
1857--   , appErrorRequestId :: Text
1858--   } deriving (Read, Show, Eq)
1859
1860-- instance A.FromJSON AppError where
1861--   parseJSON = A.withObject "appError" $ \v -> do
1862--     appErrorStatusCode <- v A..: "status_code"
1863--     appErrorMessage <- v A..: "message"
1864--     appErrorId <- v A..: "id"
1865--     appErrorRequestId <- v A..: "request_id"
1866--     return AppError { .. }
1867
1868-- instance A.ToJSON AppError where
1869--   toJSON AppError { .. } = A.object
1870--     [ "status_code" A..= appErrorStatusCode
1871--     , "message" A..= appErrorMessage
1872--     , "id" A..= appErrorId
1873--     , "request_id" A..= appErrorRequestId
1874--     ]
1875
1876-- ** User Statuses
1877
1878mmGetUserStatus :: UserParam -> Session -> IO T.Text
1879mmGetUserStatus userId =
1880  inGet (printf "/users/%s/status" userId) noBody jsonResponse
1881
1882getUserStatusesByIds :: Seq UserId -> Session -> IO (HM.HashMap UserId T.Text)
1883getUserStatusesByIds body =
1884  inPost (printf "/users/%s/status/ids") (jsonBody body) jsonResponse
1885
1886-- updateUserStatus :: UserParam -> Session -> IO ()
1887-- updateUserStatus =
1888--   inPut
1889
1890-- --
1891
1892-- data Article = Article
1893--   { articlePublishedTime :: Text
1894--   , articleTags :: (Seq Text)
1895--   , articleSection :: Text
1896--   , articleAuthors :: (Seq XX4)
1897--   , articleExpirationTime :: Text
1898--   , articleModifiedTime :: Text
1899--   } deriving (Read, Show, Eq)
1900
1901-- instance A.FromJSON Article where
1902--   parseJSON = A.withObject "article" $ \v -> do
1903--     articlePublishedTime <- v A..: "published_time"
1904--     articleTags <- v A..: "tags"
1905--     articleSection <- v A..: "section"
1906--     articleAuthors <- v A..: "authors"
1907--     articleExpirationTime <- v A..: "expiration_time"
1908--     articleModifiedTime <- v A..: "modified_time"
1909--     return Article { .. }
1910
1911-- instance A.ToJSON Article where
1912--   toJSON Article { .. } = A.object
1913--     [ "published_time" A..= articlePublishedTime
1914--     , "tags" A..= articleTags
1915--     , "section" A..= articleSection
1916--     , "authors" A..= articleAuthors
1917--     , "expiration_time" A..= articleExpirationTime
1918--     , "modified_time" A..= articleModifiedTime
1919--     ]
1920
1921-- --
1922
1923-- data Audit = Audit
1924--   { auditUserId :: Text
1925--   , auditAction :: Text
1926--   , auditExtraInfo :: Text
1927--   , auditIpAddress :: Text
1928--   , auditCreateAt :: UnknownType
1929--   , auditSessionId :: Text
1930--   , auditId :: Text
1931--   } deriving (Read, Show, Eq)
1932
1933-- instance A.FromJSON Audit where
1934--   parseJSON = A.withObject "audit" $ \v -> do
1935--     auditUserId <- v A..: "user_id"
1936--     auditAction <- v A..: "action"
1937--     auditExtraInfo <- v A..: "extra_info"
1938--     auditIpAddress <- v A..: "ip_address"
1939--     auditCreateAt <- v A..: "create_at"
1940--     auditSessionId <- v A..: "session_id"
1941--     auditId <- v A..: "id"
1942--     return Audit { .. }
1943
1944-- instance A.ToJSON Audit where
1945--   toJSON Audit { .. } = A.object
1946--     [ "user_id" A..= auditUserId
1947--     , "action" A..= auditAction
1948--     , "extra_info" A..= auditExtraInfo
1949--     , "ip_address" A..= auditIpAddress
1950--     , "create_at" A..= auditCreateAt
1951--     , "session_id" A..= auditSessionId
1952--     , "id" A..= auditId
1953--     ]
1954
1955-- --
1956
1957-- data Book = Book
1958--   { bookReleaseDate :: Text
1959--   , bookTags :: (Seq Text)
1960--   , bookIsbn :: Text
1961--   , bookAuthors :: (Seq XX2)
1962--   } deriving (Read, Show, Eq)
1963
1964-- instance A.FromJSON Book where
1965--   parseJSON = A.withObject "book" $ \v -> do
1966--     bookReleaseDate <- v A..: "release_date"
1967--     bookTags <- v A..: "tags"
1968--     bookIsbn <- v A..: "isbn"
1969--     bookAuthors <- v A..: "authors"
1970--     return Book { .. }
1971
1972-- instance A.ToJSON Book where
1973--   toJSON Book { .. } = A.object
1974--     [ "release_date" A..= bookReleaseDate
1975--     , "tags" A..= bookTags
1976--     , "isbn" A..= bookIsbn
1977--     , "authors" A..= bookAuthors
1978--     ]
1979
1980-- --
1981
1982-- --
1983
1984-- data ClusterInfo = ClusterInfo
1985--   { clusterInfoLastPing :: Integer
1986--   , clusterInfoVersion :: Text
1987--     -- ^ The server version the node is on
1988--   , clusterInfoInternodeUrl :: Text
1989--     -- ^ The URL used to communicate with those node from other nodes
1990--   , clusterInfoConfigHash :: Text
1991--     -- ^ The hash of the configuartion file the node is using
1992--   , clusterInfoHostname :: Text
1993--     -- ^ The hostname for this node
1994--   , clusterInfoIsAlive :: UnknownType
1995--     -- ^ Whether or not the node is alive and well
1996--   , clusterInfoId :: Text
1997--     -- ^ The unique ID for the node
1998--   } deriving (Read, Show, Eq)
1999
2000-- instance A.FromJSON ClusterInfo where
2001--   parseJSON = A.withObject "clusterInfo" $ \v -> do
2002--     clusterInfoLastPing <- v A..: "last_ping"
2003--     clusterInfoVersion <- v A..: "version"
2004--     clusterInfoInternodeUrl <- v A..: "internode_url"
2005--     clusterInfoConfigHash <- v A..: "config_hash"
2006--     clusterInfoHostname <- v A..: "hostname"
2007--     clusterInfoIsAlive <- v A..: "is_alive"
2008--     clusterInfoId <- v A..: "id"
2009--     return ClusterInfo { .. }
2010
2011-- instance A.ToJSON ClusterInfo where
2012--   toJSON ClusterInfo { .. } = A.object
2013--     [ "last_ping" A..= clusterInfoLastPing
2014--     , "version" A..= clusterInfoVersion
2015--     , "internode_url" A..= clusterInfoInternodeUrl
2016--     , "config_hash" A..= clusterInfoConfigHash
2017--     , "hostname" A..= clusterInfoHostname
2018--     , "is_alive" A..= clusterInfoIsAlive
2019--     , "id" A..= clusterInfoId
2020--     ]
2021
2022-- --
2023
2024-- data ClusterSettings = ClusterSettings
2025--   { clusterSettingsInternodeurls :: (Seq Text)
2026--   , clusterSettingsEnable :: UnknownType
2027--   , clusterSettingsInternodelistenaddress :: Text
2028--   } deriving (Read, Show, Eq)
2029
2030-- instance A.FromJSON ClusterSettings where
2031--   parseJSON = A.withObject "clusterSettings" $ \v -> do
2032--     clusterSettingsInternodeurls <- v A..: "InterNodeUrls"
2033--     clusterSettingsEnable <- v A..: "Enable"
2034--     clusterSettingsInternodelistenaddress <- v A..: "InterNodeListenAddress"
2035--     return ClusterSettings { .. }
2036
2037-- instance A.ToJSON ClusterSettings where
2038--   toJSON ClusterSettings { .. } = A.object
2039--     [ "InterNodeUrls" A..= clusterSettingsInternodeurls
2040--     , "Enable" A..= clusterSettingsEnable
2041--     , "InterNodeListenAddress" A..= clusterSettingsInternodelistenaddress
2042--     ]
2043
2044-- --
2045
2046-- data Compliance = Compliance
2047--   { complianceStatus :: Text
2048--   , complianceCount :: UnknownType
2049--   , complianceUserId :: Text
2050--   , complianceId :: Text
2051--   , complianceCreateAt :: UnknownType
2052--   , complianceEndAt :: UnknownType
2053--   , complianceKeywords :: Text
2054--   , complianceStartAt :: UnknownType
2055--   , complianceType :: Text
2056--   , complianceEmails :: Text
2057--   , complianceDesc :: Text
2058--   } deriving (Read, Show, Eq)
2059
2060-- instance A.FromJSON Compliance where
2061--   parseJSON = A.withObject "compliance" $ \v -> do
2062--     complianceStatus <- v A..: "status"
2063--     complianceCount <- v A..: "count"
2064--     complianceUserId <- v A..: "user_id"
2065--     complianceId <- v A..: "id"
2066--     complianceCreateAt <- v A..: "create_at"
2067--     complianceEndAt <- v A..: "end_at"
2068--     complianceKeywords <- v A..: "keywords"
2069--     complianceStartAt <- v A..: "start_at"
2070--     complianceType <- v A..: "type"
2071--     complianceEmails <- v A..: "emails"
2072--     complianceDesc <- v A..: "desc"
2073--     return Compliance { .. }
2074
2075-- instance A.ToJSON Compliance where
2076--   toJSON Compliance { .. } = A.object
2077--     [ "status" A..= complianceStatus
2078--     , "count" A..= complianceCount
2079--     , "user_id" A..= complianceUserId
2080--     , "id" A..= complianceId
2081--     , "create_at" A..= complianceCreateAt
2082--     , "end_at" A..= complianceEndAt
2083--     , "keywords" A..= complianceKeywords
2084--     , "start_at" A..= complianceStartAt
2085--     , "type" A..= complianceType
2086--     , "emails" A..= complianceEmails
2087--     , "desc" A..= complianceDesc
2088--     ]
2089
2090data Emoji = Emoji
2091  { emojiCreatorId :: Text
2092  , emojiName :: Text
2093    -- ^ The name of the emoji
2094  , emojiDeleteAt :: Integer
2095    -- ^ The time at which the emoji was deleted.
2096  , emojiUpdateAt :: Integer
2097    -- ^ The time at which the emoji was updated.
2098  , emojiCreateAt :: Integer
2099    -- ^ The time at which the emoji was made
2100  , emojiId :: Text
2101    -- ^ The ID of the emoji
2102  } deriving (Read, Show, Eq)
2103
2104instance A.FromJSON Emoji where
2105  parseJSON = A.withObject "emoji" $ \v -> do
2106    emojiCreatorId <- v A..: "creator_id"
2107    emojiName <- v A..: "name"
2108    emojiDeleteAt <- v A..: "delete_at"
2109    emojiUpdateAt <- v A..: "update_at"
2110    emojiCreateAt <- v A..: "create_at"
2111    emojiId <- v A..: "id"
2112    return Emoji { .. }
2113
2114instance A.ToJSON Emoji where
2115  toJSON Emoji { .. } = A.object
2116    [ "creator_id" A..= emojiCreatorId
2117    , "name" A..= emojiName
2118    , "delete_at" A..= emojiDeleteAt
2119    , "update_at" A..= emojiUpdateAt
2120    , "create_at" A..= emojiCreateAt
2121    , "id" A..= emojiId
2122    ]
2123
2124-- data FileSettings = FileSettings
2125--   { fileSettingsInitialfont :: Text
2126--   , fileSettingsThumbnailwidth :: UnknownType
2127--   , fileSettingsAmazons3accesskeyid :: Text
2128--   , fileSettingsAmazons3region :: Text
2129--   , fileSettingsPreviewwidth :: UnknownType
2130--   , fileSettingsAmazons3endpoint :: Text
2131--   , fileSettingsDirectory :: Text
2132--   , fileSettingsThumbnailheight :: UnknownType
2133--   , fileSettingsAmazons3bucket :: Text
2134--   , fileSettingsAmazons3secretaccesskey :: Text
2135--   , fileSettingsAmazons3ssl :: UnknownType
2136--   , fileSettingsPreviewheight :: UnknownType
2137--   , fileSettingsEnablepubliclink :: UnknownType
2138--   , fileSettingsMaxfilesize :: UnknownType
2139--   , fileSettingsProfilewidth :: UnknownType
2140--   , fileSettingsProfileheight :: UnknownType
2141--   , fileSettingsPubliclinksalt :: Text
2142--   , fileSettingsDrivername :: Text
2143--   } deriving (Read, Show, Eq)
2144
2145-- instance A.FromJSON FileSettings where
2146--   parseJSON = A.withObject "fileSettings" $ \v -> do
2147--     fileSettingsInitialfont <- v A..: "InitialFont"
2148--     fileSettingsThumbnailwidth <- v A..: "ThumbnailWidth"
2149--     fileSettingsAmazons3accesskeyid <- v A..: "AmazonS3AccessKeyId"
2150--     fileSettingsAmazons3region <- v A..: "AmazonS3Region"
2151--     fileSettingsPreviewwidth <- v A..: "PreviewWidth"
2152--     fileSettingsAmazons3endpoint <- v A..: "AmazonS3Endpoint"
2153--     fileSettingsDirectory <- v A..: "Directory"
2154--     fileSettingsThumbnailheight <- v A..: "ThumbnailHeight"
2155--     fileSettingsAmazons3bucket <- v A..: "AmazonS3Bucket"
2156--     fileSettingsAmazons3secretaccesskey <- v A..: "AmazonS3SecretAccessKey"
2157--     fileSettingsAmazons3ssl <- v A..: "AmazonS3SSL"
2158--     fileSettingsPreviewheight <- v A..: "PreviewHeight"
2159--     fileSettingsEnablepubliclink <- v A..: "EnablePublicLink"
2160--     fileSettingsMaxfilesize <- v A..: "MaxFileSize"
2161--     fileSettingsProfilewidth <- v A..: "ProfileWidth"
2162--     fileSettingsProfileheight <- v A..: "ProfileHeight"
2163--     fileSettingsPubliclinksalt <- v A..: "PublicLinkSalt"
2164--     fileSettingsDrivername <- v A..: "DriverName"
2165--     return FileSettings { .. }
2166
2167-- instance A.ToJSON FileSettings where
2168--   toJSON FileSettings { .. } = A.object
2169--     [ "InitialFont" A..= fileSettingsInitialfont
2170--     , "ThumbnailWidth" A..= fileSettingsThumbnailwidth
2171--     , "AmazonS3AccessKeyId" A..= fileSettingsAmazons3accesskeyid
2172--     , "AmazonS3Region" A..= fileSettingsAmazons3region
2173--     , "PreviewWidth" A..= fileSettingsPreviewwidth
2174--     , "AmazonS3Endpoint" A..= fileSettingsAmazons3endpoint
2175--     , "Directory" A..= fileSettingsDirectory
2176--     , "ThumbnailHeight" A..= fileSettingsThumbnailheight
2177--     , "AmazonS3Bucket" A..= fileSettingsAmazons3bucket
2178--     , "AmazonS3SecretAccessKey" A..= fileSettingsAmazons3secretaccesskey
2179--     , "AmazonS3SSL" A..= fileSettingsAmazons3ssl
2180--     , "PreviewHeight" A..= fileSettingsPreviewheight
2181--     , "EnablePublicLink" A..= fileSettingsEnablepubliclink
2182--     , "MaxFileSize" A..= fileSettingsMaxfilesize
2183--     , "ProfileWidth" A..= fileSettingsProfilewidth
2184--     , "ProfileHeight" A..= fileSettingsProfileheight
2185--     , "PublicLinkSalt" A..= fileSettingsPubliclinksalt
2186--     , "DriverName" A..= fileSettingsDrivername
2187--     ]
2188
2189-- --
2190
2191-- data GitLabSettings = GitLabSettings
2192--   { gitLabSettingsSecret :: Text
2193--   , gitLabSettingsEnable :: UnknownType
2194--   , gitLabSettingsScope :: Text
2195--   , gitLabSettingsUserapiendpoint :: Text
2196--   , gitLabSettingsTokenendpoint :: Text
2197--   , gitLabSettingsAuthendpoint :: Text
2198--   , gitLabSettingsId :: Text
2199--   } deriving (Read, Show, Eq)
2200
2201-- instance A.FromJSON GitLabSettings where
2202--   parseJSON = A.withObject "gitLabSettings" $ \v -> do
2203--     gitLabSettingsSecret <- v A..: "Secret"
2204--     gitLabSettingsEnable <- v A..: "Enable"
2205--     gitLabSettingsScope <- v A..: "Scope"
2206--     gitLabSettingsUserapiendpoint <- v A..: "UserApiEndpoint"
2207--     gitLabSettingsTokenendpoint <- v A..: "TokenEndpoint"
2208--     gitLabSettingsAuthendpoint <- v A..: "AuthEndpoint"
2209--     gitLabSettingsId <- v A..: "Id"
2210--     return GitLabSettings { .. }
2211
2212-- instance A.ToJSON GitLabSettings where
2213--   toJSON GitLabSettings { .. } = A.object
2214--     [ "Secret" A..= gitLabSettingsSecret
2215--     , "Enable" A..= gitLabSettingsEnable
2216--     , "Scope" A..= gitLabSettingsScope
2217--     , "UserApiEndpoint" A..= gitLabSettingsUserapiendpoint
2218--     , "TokenEndpoint" A..= gitLabSettingsTokenendpoint
2219--     , "AuthEndpoint" A..= gitLabSettingsAuthendpoint
2220--     , "Id" A..= gitLabSettingsId
2221--     ]
2222
2223-- --
2224
2225-- data GoogleSettings = GoogleSettings
2226--   { googleSettingsSecret :: Text
2227--   , googleSettingsEnable :: UnknownType
2228--   , googleSettingsScope :: Text
2229--   , googleSettingsUserapiendpoint :: Text
2230--   , googleSettingsTokenendpoint :: Text
2231--   , googleSettingsAuthendpoint :: Text
2232--   , googleSettingsId :: Text
2233--   } deriving (Read, Show, Eq)
2234
2235-- instance A.FromJSON GoogleSettings where
2236--   parseJSON = A.withObject "googleSettings" $ \v -> do
2237--     googleSettingsSecret <- v A..: "Secret"
2238--     googleSettingsEnable <- v A..: "Enable"
2239--     googleSettingsScope <- v A..: "Scope"
2240--     googleSettingsUserapiendpoint <- v A..: "UserApiEndpoint"
2241--     googleSettingsTokenendpoint <- v A..: "TokenEndpoint"
2242--     googleSettingsAuthendpoint <- v A..: "AuthEndpoint"
2243--     googleSettingsId <- v A..: "Id"
2244--     return GoogleSettings { .. }
2245
2246-- instance A.ToJSON GoogleSettings where
2247--   toJSON GoogleSettings { .. } = A.object
2248--     [ "Secret" A..= googleSettingsSecret
2249--     , "Enable" A..= googleSettingsEnable
2250--     , "Scope" A..= googleSettingsScope
2251--     , "UserApiEndpoint" A..= googleSettingsUserapiendpoint
2252--     , "TokenEndpoint" A..= googleSettingsTokenendpoint
2253--     , "AuthEndpoint" A..= googleSettingsAuthendpoint
2254--     , "Id" A..= googleSettingsId
2255--     ]
2256
2257-- --
2258
2259-- data IncomingWebhook = IncomingWebhook
2260--   { incomingWebhookChannelId :: Text
2261--   , incomingWebhookDisplayName :: Text
2262--     -- ^ The display name for this incoming webhook
2263--   , incomingWebhookDescription :: Text
2264--     -- ^ The description for this incoming webhook
2265--   , incomingWebhookDeleteAt :: UnknownType
2266--   , incomingWebhookUpdateAt :: UnknownType
2267--   , incomingWebhookCreateAt :: UnknownType
2268--   , incomingWebhookId :: Text
2269--     -- ^ The unique identifier for this incoming webhook
2270--   } deriving (Read, Show, Eq)
2271
2272-- instance A.FromJSON IncomingWebhook where
2273--   parseJSON = A.withObject "incomingWebhook" $ \v -> do
2274--     incomingWebhookChannelId <- v A..: "channel_id"
2275--     incomingWebhookDisplayName <- v A..: "display_name"
2276--     incomingWebhookDescription <- v A..: "description"
2277--     incomingWebhookDeleteAt <- v A..: "delete_at"
2278--     incomingWebhookUpdateAt <- v A..: "update_at"
2279--     incomingWebhookCreateAt <- v A..: "create_at"
2280--     incomingWebhookId <- v A..: "id"
2281--     return IncomingWebhook { .. }
2282
2283-- instance A.ToJSON IncomingWebhook where
2284--   toJSON IncomingWebhook { .. } = A.object
2285--     [ "channel_id" A..= incomingWebhookChannelId
2286--     , "display_name" A..= incomingWebhookDisplayName
2287--     , "description" A..= incomingWebhookDescription
2288--     , "delete_at" A..= incomingWebhookDeleteAt
2289--     , "update_at" A..= incomingWebhookUpdateAt
2290--     , "create_at" A..= incomingWebhookCreateAt
2291--     , "id" A..= incomingWebhookId
2292--     ]
2293
2294-- --
2295
2296-- data Job = Job
2297--   { jobStatus :: Text
2298--   , jobStartAt :: UnknownType
2299--     -- ^ The time at which the job was started
2300--   , jobType :: Text
2301--     -- ^ The type of job
2302--   , jobCreateAt :: UnknownType
2303--     -- ^ The time at which the job was created
2304--   , jobId :: Text
2305--     -- ^ The unique id of the job
2306--   , jobProgress :: UnknownType
2307--     -- ^ The progress (as a percentage) of the job
2308--   , jobData :: UnknownType
2309--     -- ^ A freeform data field containing additional information about the job
2310--   , jobLastActivityAt :: UnknownType
2311--     -- ^ The last time at which the job had activity
2312--   } deriving (Read, Show, Eq)
2313
2314-- instance A.FromJSON Job where
2315--   parseJSON = A.withObject "job" $ \v -> do
2316--     jobStatus <- v A..: "status"
2317--     jobStartAt <- v A..: "start_at"
2318--     jobType <- v A..: "type"
2319--     jobCreateAt <- v A..: "create_at"
2320--     jobId <- v A..: "id"
2321--     jobProgress <- v A..: "progress"
2322--     jobData <- v A..: "data"
2323--     jobLastActivityAt <- v A..: "last_activity_at"
2324--     return Job { .. }
2325
2326-- instance A.ToJSON Job where
2327--   toJSON Job { .. } = A.object
2328--     [ "status" A..= jobStatus
2329--     , "start_at" A..= jobStartAt
2330--     , "type" A..= jobType
2331--     , "create_at" A..= jobCreateAt
2332--     , "id" A..= jobId
2333--     , "progress" A..= jobProgress
2334--     , "data" A..= jobData
2335--     , "last_activity_at" A..= jobLastActivityAt
2336--     ]
2337
2338-- --
2339
2340-- data LdapSettings = LdapSettings
2341--   { ldapSettingsLastnameattribute :: Text
2342--   , ldapSettingsIdattribute :: Text
2343--   , ldapSettingsSyncintervalminutes :: UnknownType
2344--   , ldapSettingsLoginfieldname :: Text
2345--   , ldapSettingsLdapserver :: Text
2346--   , ldapSettingsLdapport :: UnknownType
2347--   , ldapSettingsUsernameattribute :: Text
2348--   , ldapSettingsMaxpagesize :: UnknownType
2349--   , ldapSettingsEnable :: UnknownType
2350--   , ldapSettingsUserfilter :: Text
2351--   , ldapSettingsBindpassword :: Text
2352--   , ldapSettingsSkipcertificateverification :: UnknownType
2353--   , ldapSettingsQuerytimeout :: UnknownType
2354--   , ldapSettingsBasedn :: Text
2355--   , ldapSettingsPositionattribute :: Text
2356--   , ldapSettingsEmailattribute :: Text
2357--   , ldapSettingsConnectionsecurity :: Text
2358--   , ldapSettingsBindusername :: Text
2359--   , ldapSettingsFirstnameattribute :: Text
2360--   , ldapSettingsNicknameattribute :: Text
2361--   } deriving (Read, Show, Eq)
2362
2363-- instance A.FromJSON LdapSettings where
2364--   parseJSON = A.withObject "ldapSettings" $ \v -> do
2365--     ldapSettingsLastnameattribute <- v A..: "LastNameAttribute"
2366--     ldapSettingsIdattribute <- v A..: "IdAttribute"
2367--     ldapSettingsSyncintervalminutes <- v A..: "SyncIntervalMinutes"
2368--     ldapSettingsLoginfieldname <- v A..: "LoginFieldName"
2369--     ldapSettingsLdapserver <- v A..: "LdapServer"
2370--     ldapSettingsLdapport <- v A..: "LdapPort"
2371--     ldapSettingsUsernameattribute <- v A..: "UsernameAttribute"
2372--     ldapSettingsMaxpagesize <- v A..: "MaxPageSize"
2373--     ldapSettingsEnable <- v A..: "Enable"
2374--     ldapSettingsUserfilter <- v A..: "UserFilter"
2375--     ldapSettingsBindpassword <- v A..: "BindPassword"
2376--     ldapSettingsSkipcertificateverification <- v A..: "SkipCertificateVerification"
2377--     ldapSettingsQuerytimeout <- v A..: "QueryTimeout"
2378--     ldapSettingsBasedn <- v A..: "BaseDN"
2379--     ldapSettingsPositionattribute <- v A..: "PositionAttribute"
2380--     ldapSettingsEmailattribute <- v A..: "EmailAttribute"
2381--     ldapSettingsConnectionsecurity <- v A..: "ConnectionSecurity"
2382--     ldapSettingsBindusername <- v A..: "BindUsername"
2383--     ldapSettingsFirstnameattribute <- v A..: "FirstNameAttribute"
2384--     ldapSettingsNicknameattribute <- v A..: "NicknameAttribute"
2385--     return LdapSettings { .. }
2386
2387-- instance A.ToJSON LdapSettings where
2388--   toJSON LdapSettings { .. } = A.object
2389--     [ "LastNameAttribute" A..= ldapSettingsLastnameattribute
2390--     , "IdAttribute" A..= ldapSettingsIdattribute
2391--     , "SyncIntervalMinutes" A..= ldapSettingsSyncintervalminutes
2392--     , "LoginFieldName" A..= ldapSettingsLoginfieldname
2393--     , "LdapServer" A..= ldapSettingsLdapserver
2394--     , "LdapPort" A..= ldapSettingsLdapport
2395--     , "UsernameAttribute" A..= ldapSettingsUsernameattribute
2396--     , "MaxPageSize" A..= ldapSettingsMaxpagesize
2397--     , "Enable" A..= ldapSettingsEnable
2398--     , "UserFilter" A..= ldapSettingsUserfilter
2399--     , "BindPassword" A..= ldapSettingsBindpassword
2400--     , "SkipCertificateVerification" A..= ldapSettingsSkipcertificateverification
2401--     , "QueryTimeout" A..= ldapSettingsQuerytimeout
2402--     , "BaseDN" A..= ldapSettingsBasedn
2403--     , "PositionAttribute" A..= ldapSettingsPositionattribute
2404--     , "EmailAttribute" A..= ldapSettingsEmailattribute
2405--     , "ConnectionSecurity" A..= ldapSettingsConnectionsecurity
2406--     , "BindUsername" A..= ldapSettingsBindusername
2407--     , "FirstNameAttribute" A..= ldapSettingsFirstnameattribute
2408--     , "NicknameAttribute" A..= ldapSettingsNicknameattribute
2409--     ]
2410
2411-- --
2412
2413-- data LocalizationSettings = LocalizationSettings
2414--   { localizationSettingsDefaultclientlocale :: Text
2415--   , localizationSettingsAvailablelocales :: Text
2416--   , localizationSettingsDefaultserverlocale :: Text
2417--   } deriving (Read, Show, Eq)
2418
2419-- instance A.FromJSON LocalizationSettings where
2420--   parseJSON = A.withObject "localizationSettings" $ \v -> do
2421--     localizationSettingsDefaultclientlocale <- v A..: "DefaultClientLocale"
2422--     localizationSettingsAvailablelocales <- v A..: "AvailableLocales"
2423--     localizationSettingsDefaultserverlocale <- v A..: "DefaultServerLocale"
2424--     return LocalizationSettings { .. }
2425
2426-- instance A.ToJSON LocalizationSettings where
2427--   toJSON LocalizationSettings { .. } = A.object
2428--     [ "DefaultClientLocale" A..= localizationSettingsDefaultclientlocale
2429--     , "AvailableLocales" A..= localizationSettingsAvailablelocales
2430--     , "DefaultServerLocale" A..= localizationSettingsDefaultserverlocale
2431--     ]
2432
2433-- --
2434
2435-- --
2436
2437-- --
2438
2439-- data OAuthApp = OAuthApp
2440--   { oAuthAppDescription :: Text
2441--   , oAuthAppIconUrl :: Text
2442--     -- ^ A URL to an icon to display with the application
2443--   , oAuthAppUpdateAt :: UnknownType
2444--     -- ^ The last time of update for the application
2445--   , oAuthAppCreateAt :: UnknownType
2446--     -- ^ The time of registration for the application
2447--   , oAuthAppIsTrusted :: UnknownType
2448--     -- ^ Set this to `true` to skip asking users for permission
2449--   , oAuthAppClientSecret :: Text
2450--     -- ^ The client secret of the application
2451--   , oAuthAppCallbackUrls :: (Seq Text)
2452--     -- ^ A list of callback URLs for the appliation
2453--   , oAuthAppHomepage :: Text
2454--     -- ^ A link to the website of the application
2455--   , oAuthAppId :: Text
2456--     -- ^ The client id of the application
2457--   , oAuthAppName :: Text
2458--     -- ^ The name of the client application
2459--   } deriving (Read, Show, Eq)
2460
2461-- instance A.FromJSON OAuthApp where
2462--   parseJSON = A.withObject "oAuthApp" $ \v -> do
2463--     oAuthAppDescription <- v A..: "description"
2464--     oAuthAppIconUrl <- v A..: "icon_url"
2465--     oAuthAppUpdateAt <- v A..: "update_at"
2466--     oAuthAppCreateAt <- v A..: "create_at"
2467--     oAuthAppIsTrusted <- v A..: "is_trusted"
2468--     oAuthAppClientSecret <- v A..: "client_secret"
2469--     oAuthAppCallbackUrls <- v A..: "callback_urls"
2470--     oAuthAppHomepage <- v A..: "homepage"
2471--     oAuthAppId <- v A..: "id"
2472--     oAuthAppName <- v A..: "name"
2473--     return OAuthApp { .. }
2474
2475-- instance A.ToJSON OAuthApp where
2476--   toJSON OAuthApp { .. } = A.object
2477--     [ "description" A..= oAuthAppDescription
2478--     , "icon_url" A..= oAuthAppIconUrl
2479--     , "update_at" A..= oAuthAppUpdateAt
2480--     , "create_at" A..= oAuthAppCreateAt
2481--     , "is_trusted" A..= oAuthAppIsTrusted
2482--     , "client_secret" A..= oAuthAppClientSecret
2483--     , "callback_urls" A..= oAuthAppCallbackUrls
2484--     , "homepage" A..= oAuthAppHomepage
2485--     , "id" A..= oAuthAppId
2486--     , "name" A..= oAuthAppName
2487--     ]
2488
2489-- --
2490
2491-- data Office365Settings = Office365Settings
2492--   { office365SettingsSecret :: Text
2493--   , office365SettingsEnable :: UnknownType
2494--   , office365SettingsScope :: Text
2495--   , office365SettingsUserapiendpoint :: Text
2496--   , office365SettingsTokenendpoint :: Text
2497--   , office365SettingsAuthendpoint :: Text
2498--   , office365SettingsId :: Text
2499--   } deriving (Read, Show, Eq)
2500
2501-- instance A.FromJSON Office365Settings where
2502--   parseJSON = A.withObject "office365Settings" $ \v -> do
2503--     office365SettingsSecret <- v A..: "Secret"
2504--     office365SettingsEnable <- v A..: "Enable"
2505--     office365SettingsScope <- v A..: "Scope"
2506--     office365SettingsUserapiendpoint <- v A..: "UserApiEndpoint"
2507--     office365SettingsTokenendpoint <- v A..: "TokenEndpoint"
2508--     office365SettingsAuthendpoint <- v A..: "AuthEndpoint"
2509--     office365SettingsId <- v A..: "Id"
2510--     return Office365Settings { .. }
2511
2512-- instance A.ToJSON Office365Settings where
2513--   toJSON Office365Settings { .. } = A.object
2514--     [ "Secret" A..= office365SettingsSecret
2515--     , "Enable" A..= office365SettingsEnable
2516--     , "Scope" A..= office365SettingsScope
2517--     , "UserApiEndpoint" A..= office365SettingsUserapiendpoint
2518--     , "TokenEndpoint" A..= office365SettingsTokenendpoint
2519--     , "AuthEndpoint" A..= office365SettingsAuthendpoint
2520--     , "Id" A..= office365SettingsId
2521--     ]
2522
2523-- --
2524
2525-- data OpenGraph = OpenGraph
2526--   { openGraphProfile :: UnknownObject
2527--   , openGraphSiteName :: Text
2528--   , openGraphDescription :: Text
2529--   , openGraphVideos :: (Seq XX1)
2530--   , openGraphTitle :: Text
2531--   , openGraphUrl :: Text
2532--   , openGraphLocalesAlternate :: (Seq Text)
2533--   , openGraphLocale :: Text
2534--   , openGraphBook :: Book
2535--     -- ^ Book object used in OpenGraph metadata of a webpage, if type is book
2536--   , openGraphImages :: (Seq XX3)
2537--   , openGraphArticle :: Article
2538--     -- ^ Article object used in OpenGraph metadata of a webpage, if type is article
2539--   , openGraphAudios :: (Seq XX5)
2540--   , openGraphType :: Text
2541--   , openGraphDeterminer :: Text
2542--   } deriving (Read, Show, Eq)
2543
2544-- instance A.FromJSON OpenGraph where
2545--   parseJSON = A.withObject "openGraph" $ \v -> do
2546--     openGraphProfile <- v A..: "profile"
2547--     openGraphSiteName <- v A..: "site_name"
2548--     openGraphDescription <- v A..: "description"
2549--     openGraphVideos <- v A..: "videos"
2550--     openGraphTitle <- v A..: "title"
2551--     openGraphUrl <- v A..: "url"
2552--     openGraphLocalesAlternate <- v A..: "locales_alternate"
2553--     openGraphLocale <- v A..: "locale"
2554--     openGraphBook <- v A..: "book"
2555--     openGraphImages <- v A..: "images"
2556--     openGraphArticle <- v A..: "article"
2557--     openGraphAudios <- v A..: "audios"
2558--     openGraphType <- v A..: "type"
2559--     openGraphDeterminer <- v A..: "determiner"
2560--     return OpenGraph { .. }
2561
2562-- instance A.ToJSON OpenGraph where
2563--   toJSON OpenGraph { .. } = A.object
2564--     [ "profile" A..= openGraphProfile
2565--     , "site_name" A..= openGraphSiteName
2566--     , "description" A..= openGraphDescription
2567--     , "videos" A..= openGraphVideos
2568--     , "title" A..= openGraphTitle
2569--     , "url" A..= openGraphUrl
2570--     , "locales_alternate" A..= openGraphLocalesAlternate
2571--     , "locale" A..= openGraphLocale
2572--     , "book" A..= openGraphBook
2573--     , "images" A..= openGraphImages
2574--     , "article" A..= openGraphArticle
2575--     , "audios" A..= openGraphAudios
2576--     , "type" A..= openGraphType
2577--     , "determiner" A..= openGraphDeterminer
2578--     ]
2579
2580-- --
2581
2582-- data OutgoingWebhook = OutgoingWebhook
2583--   { outgoingWebhookTriggerWhen :: Integer
2584--   , outgoingWebhookDisplayName :: Text
2585--     -- ^ The display name for this outgoing webhook
2586--   , outgoingWebhookDescription :: Text
2587--     -- ^ The description for this outgoing webhook
2588--   , outgoingWebhookDeleteAt :: UnknownType
2589--   , outgoingWebhookUpdateAt :: UnknownType
2590--   , outgoingWebhookCreateAt :: UnknownType
2591--   , outgoingWebhookChannelId :: Text
2592--     -- ^ The ID of a public channel that the webhook watchs
2593--   , outgoingWebhookCreatorId :: Text
2594--     -- ^ The Id of the user who created the webhook
2595--   , outgoingWebhookContentType :: Text
2596--     -- ^ The format to POST the data in, either `application/json` or `application/x-www-form-urlencoded`
2597--   , outgoingWebhookTriggerWords :: (Seq Text)
2598--     -- ^ List of words for the webhook to trigger on
2599--   , outgoingWebhookTeamId :: Text
2600--     -- ^ The ID of the team that the webhook watchs
2601--   , outgoingWebhookCallbackUrls :: (Seq Text)
2602--     -- ^ The URLs to POST the payloads to when the webhook is triggered
2603--   , outgoingWebhookId :: Text
2604--     -- ^ The unique identifier for this outgoing webhook
2605--   } deriving (Read, Show, Eq)
2606
2607-- instance A.FromJSON OutgoingWebhook where
2608--   parseJSON = A.withObject "outgoingWebhook" $ \v -> do
2609--     outgoingWebhookTriggerWhen <- v A..: "trigger_when"
2610--     outgoingWebhookDisplayName <- v A..: "display_name"
2611--     outgoingWebhookDescription <- v A..: "description"
2612--     outgoingWebhookDeleteAt <- v A..: "delete_at"
2613--     outgoingWebhookUpdateAt <- v A..: "update_at"
2614--     outgoingWebhookCreateAt <- v A..: "create_at"
2615--     outgoingWebhookChannelId <- v A..: "channel_id"
2616--     outgoingWebhookCreatorId <- v A..: "creator_id"
2617--     outgoingWebhookContentType <- v A..: "content_type"
2618--     outgoingWebhookTriggerWords <- v A..: "trigger_words"
2619--     outgoingWebhookTeamId <- v A..: "team_id"
2620--     outgoingWebhookCallbackUrls <- v A..: "callback_urls"
2621--     outgoingWebhookId <- v A..: "id"
2622--     return OutgoingWebhook { .. }
2623
2624-- instance A.ToJSON OutgoingWebhook where
2625--   toJSON OutgoingWebhook { .. } = A.object
2626--     [ "trigger_when" A..= outgoingWebhookTriggerWhen
2627--     , "display_name" A..= outgoingWebhookDisplayName
2628--     , "description" A..= outgoingWebhookDescription
2629--     , "delete_at" A..= outgoingWebhookDeleteAt
2630--     , "update_at" A..= outgoingWebhookUpdateAt
2631--     , "create_at" A..= outgoingWebhookCreateAt
2632--     , "channel_id" A..= outgoingWebhookChannelId
2633--     , "creator_id" A..= outgoingWebhookCreatorId
2634--     , "content_type" A..= outgoingWebhookContentType
2635--     , "trigger_words" A..= outgoingWebhookTriggerWords
2636--     , "team_id" A..= outgoingWebhookTeamId
2637--     , "callback_urls" A..= outgoingWebhookCallbackUrls
2638--     , "id" A..= outgoingWebhookId
2639--     ]
2640
2641-- --
2642
2643-- --
2644
2645-- data SamlCertificateStatus = SamlCertificateStatus
2646--   { samlCertificateStatusIdpCertificateFile :: Bool
2647--   , samlCertificateStatusPrivateKeyFile :: UnknownType
2648--     -- ^ Status is good when `true`
2649--   , samlCertificateStatusPublicCertificateFile :: UnknownType
2650--     -- ^ Status is good when `true`
2651--   } deriving (Read, Show, Eq)
2652
2653-- instance A.FromJSON SamlCertificateStatus where
2654--   parseJSON = A.withObject "samlCertificateStatus" $ \v -> do
2655--     samlCertificateStatusIdpCertificateFile <- v A..: "idp_certificate_file"
2656--     samlCertificateStatusPrivateKeyFile <- v A..: "private_key_file"
2657--     samlCertificateStatusPublicCertificateFile <- v A..: "public_certificate_file"
2658--     return SamlCertificateStatus { .. }
2659
2660-- instance A.ToJSON SamlCertificateStatus where
2661--   toJSON SamlCertificateStatus { .. } = A.object
2662--     [ "idp_certificate_file" A..= samlCertificateStatusIdpCertificateFile
2663--     , "private_key_file" A..= samlCertificateStatusPrivateKeyFile
2664--     , "public_certificate_file" A..= samlCertificateStatusPublicCertificateFile
2665--     ]
2666
2667-- --
2668
2669-- data SamlSettings = SamlSettings
2670--   { samlSettingsLoginbuttontext :: Text
2671--   , samlSettingsLastnameattribute :: Text
2672--   , samlSettingsEncrypt :: UnknownType
2673--   , samlSettingsIdpurl :: Text
2674--   , samlSettingsVerify :: UnknownType
2675--   , samlSettingsAssertionconsumerserviceurl :: Text
2676--   , samlSettingsUsernameattribute :: Text
2677--   , samlSettingsLocaleattribute :: Text
2678--   , samlSettingsFirstnameattribute :: Text
2679--   , samlSettingsEnable :: UnknownType
2680--   , samlSettingsNicknameattribute :: Text
2681--   , samlSettingsPositionattribute :: Text
2682--   , samlSettingsIdpdescriptorurl :: Text
2683--   , samlSettingsPrivatekeyfile :: Text
2684--   , samlSettingsIdpcertificatefile :: Text
2685--   , samlSettingsEmailattribute :: Text
2686--   , samlSettingsPubliccertificatefile :: Text
2687--   } deriving (Read, Show, Eq)
2688
2689-- instance A.FromJSON SamlSettings where
2690--   parseJSON = A.withObject "samlSettings" $ \v -> do
2691--     samlSettingsLoginbuttontext <- v A..: "LoginButtonText"
2692--     samlSettingsLastnameattribute <- v A..: "LastNameAttribute"
2693--     samlSettingsEncrypt <- v A..: "Encrypt"
2694--     samlSettingsIdpurl <- v A..: "IdpUrl"
2695--     samlSettingsVerify <- v A..: "Verify"
2696--     samlSettingsAssertionconsumerserviceurl <- v A..: "AssertionConsumerServiceURL"
2697--     samlSettingsUsernameattribute <- v A..: "UsernameAttribute"
2698--     samlSettingsLocaleattribute <- v A..: "LocaleAttribute"
2699--     samlSettingsFirstnameattribute <- v A..: "FirstNameAttribute"
2700--     samlSettingsEnable <- v A..: "Enable"
2701--     samlSettingsNicknameattribute <- v A..: "NicknameAttribute"
2702--     samlSettingsPositionattribute <- v A..: "PositionAttribute"
2703--     samlSettingsIdpdescriptorurl <- v A..: "IdpDescriptorUrl"
2704--     samlSettingsPrivatekeyfile <- v A..: "PrivateKeyFile"
2705--     samlSettingsIdpcertificatefile <- v A..: "IdpCertificateFile"
2706--     samlSettingsEmailattribute <- v A..: "EmailAttribute"
2707--     samlSettingsPubliccertificatefile <- v A..: "PublicCertificateFile"
2708--     return SamlSettings { .. }
2709
2710-- instance A.ToJSON SamlSettings where
2711--   toJSON SamlSettings { .. } = A.object
2712--     [ "LoginButtonText" A..= samlSettingsLoginbuttontext
2713--     , "LastNameAttribute" A..= samlSettingsLastnameattribute
2714--     , "Encrypt" A..= samlSettingsEncrypt
2715--     , "IdpUrl" A..= samlSettingsIdpurl
2716--     , "Verify" A..= samlSettingsVerify
2717--     , "AssertionConsumerServiceURL" A..= samlSettingsAssertionconsumerserviceurl
2718--     , "UsernameAttribute" A..= samlSettingsUsernameattribute
2719--     , "LocaleAttribute" A..= samlSettingsLocaleattribute
2720--     , "FirstNameAttribute" A..= samlSettingsFirstnameattribute
2721--     , "Enable" A..= samlSettingsEnable
2722--     , "NicknameAttribute" A..= samlSettingsNicknameattribute
2723--     , "PositionAttribute" A..= samlSettingsPositionattribute
2724--     , "IdpDescriptorUrl" A..= samlSettingsIdpdescriptorurl
2725--     , "PrivateKeyFile" A..= samlSettingsPrivatekeyfile
2726--     , "IdpCertificateFile" A..= samlSettingsIdpcertificatefile
2727--     , "EmailAttribute" A..= samlSettingsEmailattribute
2728--     , "PublicCertificateFile" A..= samlSettingsPubliccertificatefile
2729--     ]
2730
2731-- --
2732
2733-- data ServiceSettings = ServiceSettings
2734--   { serviceSettingsEnableposticonoverride :: Bool
2735--   , serviceSettingsSegmentdeveloperkey :: Text
2736--   , serviceSettingsEnablepostusernameoverride :: UnknownType
2737--   , serviceSettingsForward80to443 :: UnknownType
2738--   , serviceSettingsEnableincomingwebhooks :: UnknownType
2739--   , serviceSettingsSessionlengthmobileindays :: UnknownType
2740--   , serviceSettingsUseletsencrypt :: UnknownType
2741--   , serviceSettingsRestrictcustomemojicreation :: Text
2742--   , serviceSettingsReadtimeout :: UnknownType
2743--   , serviceSettingsEnableoutgoingwebhooks :: UnknownType
2744--   , serviceSettingsTlscertfile :: Text
2745--   , serviceSettingsEnableonlyadminintegrations :: UnknownType
2746--   , serviceSettingsEnableinsecureoutgoingconnections :: UnknownType
2747--   , serviceSettingsEnableoauthserviceprovider :: UnknownType
2748--   , serviceSettingsEnablecustomemoji :: UnknownType
2749--   , serviceSettingsEnabletesting :: UnknownType
2750--   , serviceSettingsSessioncacheinminutes :: UnknownType
2751--   , serviceSettingsSessionlengthwebindays :: UnknownType
2752--   , serviceSettingsWebservermode :: Text
2753--   , serviceSettingsEnablesecurityfixalert :: UnknownType
2754--   , serviceSettingsEnablemultifactorauthentication :: UnknownType
2755--   , serviceSettingsEnabledeveloper :: UnknownType
2756--   , serviceSettingsSiteurl :: Text
2757--   , serviceSettingsTlskeyfile :: Text
2758--   , serviceSettingsListenaddress :: Text
2759--   , serviceSettingsGoogledeveloperkey :: Text
2760--   , serviceSettingsEnforcemultifactorauthentication :: UnknownType
2761--   , serviceSettingsLetsencryptcertificatecachefile :: Text
2762--   , serviceSettingsWebsocketport :: UnknownType
2763--   , serviceSettingsWebsocketsecureport :: UnknownType
2764--   , serviceSettingsAllowcorsfrom :: Text
2765--   , serviceSettingsSessionlengthssoindays :: UnknownType
2766--   , serviceSettingsEnablecommands :: UnknownType
2767--   , serviceSettingsConnectionsecurity :: Text
2768--   , serviceSettingsWritetimeout :: UnknownType
2769--   , serviceSettingsMaximumloginattempts :: UnknownType
2770--   } deriving (Read, Show, Eq)
2771
2772-- instance A.FromJSON ServiceSettings where
2773--   parseJSON = A.withObject "serviceSettings" $ \v -> do
2774--     serviceSettingsEnableposticonoverride <- v A..: "EnablePostIconOverride"
2775--     serviceSettingsSegmentdeveloperkey <- v A..: "SegmentDeveloperKey"
2776--     serviceSettingsEnablepostusernameoverride <- v A..: "EnablePostUsernameOverride"
2777--     serviceSettingsForward80to443 <- v A..: "Forward80To443"
2778--     serviceSettingsEnableincomingwebhooks <- v A..: "EnableIncomingWebhooks"
2779--     serviceSettingsSessionlengthmobileindays <- v A..: "SessionLengthMobileInDays"
2780--     serviceSettingsUseletsencrypt <- v A..: "UseLetsEncrypt"
2781--     serviceSettingsRestrictcustomemojicreation <- v A..: "RestrictCustomEmojiCreation"
2782--     serviceSettingsReadtimeout <- v A..: "ReadTimeout"
2783--     serviceSettingsEnableoutgoingwebhooks <- v A..: "EnableOutgoingWebhooks"
2784--     serviceSettingsTlscertfile <- v A..: "TLSCertFile"
2785--     serviceSettingsEnableonlyadminintegrations <- v A..: "EnableOnlyAdminIntegrations"
2786--     serviceSettingsEnableinsecureoutgoingconnections <- v A..: "EnableInsecureOutgoingConnections"
2787--     serviceSettingsEnableoauthserviceprovider <- v A..: "EnableOAuthServiceProvider"
2788--     serviceSettingsEnablecustomemoji <- v A..: "EnableCustomEmoji"
2789--     serviceSettingsEnabletesting <- v A..: "EnableTesting"
2790--     serviceSettingsSessioncacheinminutes <- v A..: "SessionCacheInMinutes"
2791--     serviceSettingsSessionlengthwebindays <- v A..: "SessionLengthWebInDays"
2792--     serviceSettingsWebservermode <- v A..: "WebserverMode"
2793--     serviceSettingsEnablesecurityfixalert <- v A..: "EnableSecurityFixAlert"
2794--     serviceSettingsEnablemultifactorauthentication <- v A..: "EnableMultifactorAuthentication"
2795--     serviceSettingsEnabledeveloper <- v A..: "EnableDeveloper"
2796--     serviceSettingsSiteurl <- v A..: "SiteURL"
2797--     serviceSettingsTlskeyfile <- v A..: "TLSKeyFile"
2798--     serviceSettingsListenaddress <- v A..: "ListenAddress"
2799--     serviceSettingsGoogledeveloperkey <- v A..: "GoogleDeveloperKey"
2800--     serviceSettingsEnforcemultifactorauthentication <- v A..: "EnforceMultifactorAuthentication"
2801--     serviceSettingsLetsencryptcertificatecachefile <- v A..: "LetsEncryptCertificateCacheFile"
2802--     serviceSettingsWebsocketport <- v A..: "WebsocketPort"
2803--     serviceSettingsWebsocketsecureport <- v A..: "WebsocketSecurePort"
2804--     serviceSettingsAllowcorsfrom <- v A..: "AllowCorsFrom"
2805--     serviceSettingsSessionlengthssoindays <- v A..: "SessionLengthSSOInDays"
2806--     serviceSettingsEnablecommands <- v A..: "EnableCommands"
2807--     serviceSettingsConnectionsecurity <- v A..: "ConnectionSecurity"
2808--     serviceSettingsWritetimeout <- v A..: "WriteTimeout"
2809--     serviceSettingsMaximumloginattempts <- v A..: "MaximumLoginAttempts"
2810--     return ServiceSettings { .. }
2811
2812-- instance A.ToJSON ServiceSettings where
2813--   toJSON ServiceSettings { .. } = A.object
2814--     [ "EnablePostIconOverride" A..= serviceSettingsEnableposticonoverride
2815--     , "SegmentDeveloperKey" A..= serviceSettingsSegmentdeveloperkey
2816--     , "EnablePostUsernameOverride" A..= serviceSettingsEnablepostusernameoverride
2817--     , "Forward80To443" A..= serviceSettingsForward80to443
2818--     , "EnableIncomingWebhooks" A..= serviceSettingsEnableincomingwebhooks
2819--     , "SessionLengthMobileInDays" A..= serviceSettingsSessionlengthmobileindays
2820--     , "UseLetsEncrypt" A..= serviceSettingsUseletsencrypt
2821--     , "RestrictCustomEmojiCreation" A..= serviceSettingsRestrictcustomemojicreation
2822--     , "ReadTimeout" A..= serviceSettingsReadtimeout
2823--     , "EnableOutgoingWebhooks" A..= serviceSettingsEnableoutgoingwebhooks
2824--     , "TLSCertFile" A..= serviceSettingsTlscertfile
2825--     , "EnableOnlyAdminIntegrations" A..= serviceSettingsEnableonlyadminintegrations
2826--     , "EnableInsecureOutgoingConnections" A..= serviceSettingsEnableinsecureoutgoingconnections
2827--     , "EnableOAuthServiceProvider" A..= serviceSettingsEnableoauthserviceprovider
2828--     , "EnableCustomEmoji" A..= serviceSettingsEnablecustomemoji
2829--     , "EnableTesting" A..= serviceSettingsEnabletesting
2830--     , "SessionCacheInMinutes" A..= serviceSettingsSessioncacheinminutes
2831--     , "SessionLengthWebInDays" A..= serviceSettingsSessionlengthwebindays
2832--     , "WebserverMode" A..= serviceSettingsWebservermode
2833--     , "EnableSecurityFixAlert" A..= serviceSettingsEnablesecurityfixalert
2834--     , "EnableMultifactorAuthentication" A..= serviceSettingsEnablemultifactorauthentication
2835--     , "EnableDeveloper" A..= serviceSettingsEnabledeveloper
2836--     , "SiteURL" A..= serviceSettingsSiteurl
2837--     , "TLSKeyFile" A..= serviceSettingsTlskeyfile
2838--     , "ListenAddress" A..= serviceSettingsListenaddress
2839--     , "GoogleDeveloperKey" A..= serviceSettingsGoogledeveloperkey
2840--     , "EnforceMultifactorAuthentication" A..= serviceSettingsEnforcemultifactorauthentication
2841--     , "LetsEncryptCertificateCacheFile" A..= serviceSettingsLetsencryptcertificatecachefile
2842--     , "WebsocketPort" A..= serviceSettingsWebsocketport
2843--     , "WebsocketSecurePort" A..= serviceSettingsWebsocketsecureport
2844--     , "AllowCorsFrom" A..= serviceSettingsAllowcorsfrom
2845--     , "SessionLengthSSOInDays" A..= serviceSettingsSessionlengthssoindays
2846--     , "EnableCommands" A..= serviceSettingsEnablecommands
2847--     , "ConnectionSecurity" A..= serviceSettingsConnectionsecurity
2848--     , "WriteTimeout" A..= serviceSettingsWritetimeout
2849--     , "MaximumLoginAttempts" A..= serviceSettingsMaximumloginattempts
2850--     ]
2851
2852-- --
2853
2854-- data SlackAttachment = SlackAttachment
2855--   { slackAttachmentTitlelink :: Text
2856--   , slackAttachmentFooter :: Text
2857--   , slackAttachmentFields :: (Seq SlackAttachmentField)
2858--   , slackAttachmentImageurl :: Text
2859--   , slackAttachmentAuthorname :: Text
2860--   , slackAttachmentThumburl :: Text
2861--   , slackAttachmentTitle :: Text
2862--   , slackAttachmentFallback :: Text
2863--   , slackAttachmentColor :: Text
2864--   , slackAttachmentText :: Text
2865--   , slackAttachmentAuthorlink :: Text
2866--   , slackAttachmentAuthoricon :: Text
2867--   , slackAttachmentTimestamp :: Text
2868--     -- ^ The timestamp of the slack attahment, either type of string or integer
2869--   , slackAttachmentPretext :: Text
2870--   , slackAttachmentId :: Text
2871--   , slackAttachmentFootericon :: Text
2872--   } deriving (Read, Show, Eq)
2873
2874-- instance A.FromJSON SlackAttachment where
2875--   parseJSON = A.withObject "slackAttachment" $ \v -> do
2876--     slackAttachmentTitlelink <- v A..: "TitleLink"
2877--     slackAttachmentFooter <- v A..: "Footer"
2878--     slackAttachmentFields <- v A..: "Fields"
2879--     slackAttachmentImageurl <- v A..: "ImageURL"
2880--     slackAttachmentAuthorname <- v A..: "AuthorName"
2881--     slackAttachmentThumburl <- v A..: "ThumbURL"
2882--     slackAttachmentTitle <- v A..: "Title"
2883--     slackAttachmentFallback <- v A..: "Fallback"
2884--     slackAttachmentColor <- v A..: "Color"
2885--     slackAttachmentText <- v A..: "Text"
2886--     slackAttachmentAuthorlink <- v A..: "AuthorLink"
2887--     slackAttachmentAuthoricon <- v A..: "AuthorIcon"
2888--     slackAttachmentTimestamp <- v A..: "Timestamp"
2889--     slackAttachmentPretext <- v A..: "Pretext"
2890--     slackAttachmentId <- v A..: "Id"
2891--     slackAttachmentFootericon <- v A..: "FooterIcon"
2892--     return SlackAttachment { .. }
2893
2894-- instance A.ToJSON SlackAttachment where
2895--   toJSON SlackAttachment { .. } = A.object
2896--     [ "TitleLink" A..= slackAttachmentTitlelink
2897--     , "Footer" A..= slackAttachmentFooter
2898--     , "Fields" A..= slackAttachmentFields
2899--     , "ImageURL" A..= slackAttachmentImageurl
2900--     , "AuthorName" A..= slackAttachmentAuthorname
2901--     , "ThumbURL" A..= slackAttachmentThumburl
2902--     , "Title" A..= slackAttachmentTitle
2903--     , "Fallback" A..= slackAttachmentFallback
2904--     , "Color" A..= slackAttachmentColor
2905--     , "Text" A..= slackAttachmentText
2906--     , "AuthorLink" A..= slackAttachmentAuthorlink
2907--     , "AuthorIcon" A..= slackAttachmentAuthoricon
2908--     , "Timestamp" A..= slackAttachmentTimestamp
2909--     , "Pretext" A..= slackAttachmentPretext
2910--     , "Id" A..= slackAttachmentId
2911--     , "FooterIcon" A..= slackAttachmentFootericon
2912--     ]
2913
2914-- --
2915
2916-- data SlackAttachmentField = SlackAttachmentField
2917--   { slackAttachmentFieldShort :: Bool
2918--   , slackAttachmentFieldValue :: Text
2919--     -- ^ The value of the attachment, set as string but capable with golang interface
2920--   , slackAttachmentFieldTitle :: Text
2921--   } deriving (Read, Show, Eq)
2922
2923-- instance A.FromJSON SlackAttachmentField where
2924--   parseJSON = A.withObject "slackAttachmentField" $ \v -> do
2925--     slackAttachmentFieldShort <- v A..: "Short"
2926--     slackAttachmentFieldValue <- v A..: "Value"
2927--     slackAttachmentFieldTitle <- v A..: "Title"
2928--     return SlackAttachmentField { .. }
2929
2930-- instance A.ToJSON SlackAttachmentField where
2931--   toJSON SlackAttachmentField { .. } = A.object
2932--     [ "Short" A..= slackAttachmentFieldShort
2933--     , "Value" A..= slackAttachmentFieldValue
2934--     , "Title" A..= slackAttachmentFieldTitle
2935--     ]
2936
2937-- --
2938
2939-- data Status = Status
2940--   { statusStatus :: Text
2941--   , statusActiveChannel :: Text
2942--   , statusManual :: UnknownType
2943--   , statusLastActivityAt :: UnknownType
2944--   , statusUserId :: Text
2945--   } deriving (Read, Show, Eq)
2946
2947-- instance A.FromJSON Status where
2948--   parseJSON = A.withObject "status" $ \v -> do
2949--     statusStatus <- v A..: "status"
2950--     statusActiveChannel <- v A..: "active_channel"
2951--     statusManual <- v A..: "manual"
2952--     statusLastActivityAt <- v A..: "last_activity_at"
2953--     statusUserId <- v A..: "user_id"
2954--     return Status { .. }
2955
2956-- instance A.ToJSON Status where
2957--   toJSON Status { .. } = A.object
2958--     [ "status" A..= statusStatus
2959--     , "active_channel" A..= statusActiveChannel
2960--     , "manual" A..= statusManual
2961--     , "last_activity_at" A..= statusLastActivityAt
2962--     , "user_id" A..= statusUserId
2963--     ]
2964
2965-- --
2966
2967newtype StatusOK = StatusOK
2968  { statusOKStatus :: Text
2969  } deriving (Read, Show, Eq)
2970
2971instance A.FromJSON StatusOK where
2972  parseJSON = A.withObject "statusOK" $ \v -> do
2973    statusOKStatus <- v A..: "status"
2974    return StatusOK { .. }
2975
2976instance A.ToJSON StatusOK where
2977  toJSON StatusOK { .. } = A.object
2978    [ "status" A..= statusOKStatus
2979    ]
2980
2981-- --
2982
2983-- --
2984
2985-- newtype TeamExists = TeamExists
2986--   { teamExistsExists :: Bool
2987--   } deriving (Read, Show, Eq)
2988
2989-- instance A.FromJSON TeamExists where
2990--   parseJSON = A.withObject "teamExists" $ \v -> do
2991--     teamExistsExists <- v A..: "exists"
2992--     return TeamExists { .. }
2993
2994-- instance A.ToJSON TeamExists where
2995--   toJSON TeamExists { .. } = A.object
2996--     [ "exists" A..= teamExistsExists
2997--     ]
2998
2999-- --
3000
3001-- newtype TeamMap = TeamMap
3002--   { teamMapTeamId :: Team
3003--   } deriving (Read, Show, Eq)
3004
3005-- instance A.FromJSON TeamMap where
3006--   parseJSON = A.withObject "teamMap" $ \v -> do
3007--     teamMapTeamId <- v A..: "team_id"
3008--     return TeamMap { .. }
3009
3010-- instance A.ToJSON TeamMap where
3011--   toJSON TeamMap { .. } = A.object
3012--     [ "team_id" A..= teamMapTeamId
3013--     ]
3014
3015-- --
3016
3017-- --
3018
3019-- data TeamStats = TeamStats
3020--   { teamStatsTeamId :: Text
3021--   , teamStatsActiveMemberCount :: UnknownType
3022--   , teamStatsTotalMemberCount :: UnknownType
3023--   } deriving (Read, Show, Eq)
3024
3025-- instance A.FromJSON TeamStats where
3026--   parseJSON = A.withObject "teamStats" $ \v -> do
3027--     teamStatsTeamId <- v A..: "team_id"
3028--     teamStatsActiveMemberCount <- v A..: "active_member_count"
3029--     teamStatsTotalMemberCount <- v A..: "total_member_count"
3030--     return TeamStats { .. }
3031
3032-- instance A.ToJSON TeamStats where
3033--   toJSON TeamStats { .. } = A.object
3034--     [ "team_id" A..= teamStatsTeamId
3035--     , "active_member_count" A..= teamStatsActiveMemberCount
3036--     , "total_member_count" A..= teamStatsTotalMemberCount
3037--     ]
3038
3039-- --
3040
3041-- data TeamUnread = TeamUnread
3042--   { teamUnreadTeamId :: Text
3043--   , teamUnreadMsgCount :: UnknownType
3044--   , teamUnreadMentionCount :: UnknownType
3045--   } deriving (Read, Show, Eq)
3046
3047-- instance A.FromJSON TeamUnread where
3048--   parseJSON = A.withObject "teamUnread" $ \v -> do
3049--     teamUnreadTeamId <- v A..: "team_id"
3050--     teamUnreadMsgCount <- v A..: "msg_count"
3051--     teamUnreadMentionCount <- v A..: "mention_count"
3052--     return TeamUnread { .. }
3053
3054-- instance A.ToJSON TeamUnread where
3055--   toJSON TeamUnread { .. } = A.object
3056--     [ "team_id" A..= teamUnreadTeamId
3057--     , "msg_count" A..= teamUnreadMsgCount
3058--     , "mention_count" A..= teamUnreadMentionCount
3059--     ]
3060
3061-- --
3062
3063-- data UserAccessToken = UserAccessToken
3064--   { userAccessTokenToken :: Text
3065--   , userAccessTokenUserId :: Text
3066--     -- ^ The user the token authenticates for
3067--   , userAccessTokenId :: Text
3068--     -- ^ Unique identifier for the token
3069--   , userAccessTokenDescription :: Text
3070--     -- ^ A description of the token usage
3071--   } deriving (Read, Show, Eq)
3072
3073-- instance A.FromJSON UserAccessToken where
3074--   parseJSON = A.withObject "userAccessToken" $ \v -> do
3075--     userAccessTokenToken <- v A..: "token"
3076--     userAccessTokenUserId <- v A..: "user_id"
3077--     userAccessTokenId <- v A..: "id"
3078--     userAccessTokenDescription <- v A..: "description"
3079--     return UserAccessToken { .. }
3080
3081-- instance A.ToJSON UserAccessToken where
3082--   toJSON UserAccessToken { .. } = A.object
3083--     [ "token" A..= userAccessTokenToken
3084--     , "user_id" A..= userAccessTokenUserId
3085--     , "id" A..= userAccessTokenId
3086--     , "description" A..= userAccessTokenDescription
3087--     ]
3088
3089-- --
3090
3091-- data UserAccessTokenSanitized = UserAccessTokenSanitized
3092--   { userAccessTokenSanitizedUserId :: Text
3093--   , userAccessTokenSanitizedId :: Text
3094--     -- ^ Unique identifier for the token
3095--   , userAccessTokenSanitizedDescription :: Text
3096--     -- ^ A description of the token usage
3097--   } deriving (Read, Show, Eq)
3098
3099-- instance A.FromJSON UserAccessTokenSanitized where
3100--   parseJSON = A.withObject "userAccessTokenSanitized" $ \v -> do
3101--     userAccessTokenSanitizedUserId <- v A..: "user_id"
3102--     userAccessTokenSanitizedId <- v A..: "id"
3103--     userAccessTokenSanitizedDescription <- v A..: "description"
3104--     return UserAccessTokenSanitized { .. }
3105
3106-- instance A.ToJSON UserAccessTokenSanitized where
3107--   toJSON UserAccessTokenSanitized { .. } = A.object
3108--     [ "user_id" A..= userAccessTokenSanitizedUserId
3109--     , "id" A..= userAccessTokenSanitizedId
3110--     , "description" A..= userAccessTokenSanitizedDescription
3111--     ]
3112
3113-- --
3114
3115data UserAutocomplete = UserAutocomplete
3116  { userAutocompleteUsers :: Seq User
3117  , userAutocompleteOutOfChannel :: Maybe (Seq User)
3118    -- ^ A special case list of users returned when autocompleting in a
3119    -- specific channel. Omitted when empty or not relevant
3120  } deriving (Read, Show, Eq)
3121
3122instance A.FromJSON UserAutocomplete where
3123  parseJSON = A.withObject "userAutocomplete" $ \v -> do
3124    userAutocompleteUsers <- v A..: "users"
3125    userAutocompleteOutOfChannel <- v A..:? "out_of_channel"
3126    return UserAutocomplete { .. }
3127
3128instance A.ToJSON UserAutocomplete where
3129  toJSON UserAutocomplete { .. } = A.object
3130    [ "users" A..= userAutocompleteUsers
3131    , "out_of_channel" A..= userAutocompleteOutOfChannel
3132    ]
3133
3134-- --
3135
3136-- data UserAutocompleteInChannel = UserAutocompleteInChannel
3137--   { userAutocompleteInChannelInChannel :: (Seq User)
3138--   , userAutocompleteInChannelOutOfChannel :: (Seq User)
3139--     -- ^ A list of user objects not in the channel
3140--   } deriving (Read, Show, Eq)
3141
3142-- instance A.FromJSON UserAutocompleteInChannel where
3143--   parseJSON = A.withObject "userAutocompleteInChannel" $ \v -> do
3144--     userAutocompleteInChannelInChannel <- v A..: "in_channel"
3145--     userAutocompleteInChannelOutOfChannel <- v A..: "out_of_channel"
3146--     return UserAutocompleteInChannel { .. }
3147
3148-- instance A.ToJSON UserAutocompleteInChannel where
3149--   toJSON UserAutocompleteInChannel { .. } = A.object
3150--     [ "in_channel" A..= userAutocompleteInChannelInChannel
3151--     , "out_of_channel" A..= userAutocompleteInChannelOutOfChannel
3152--     ]
3153
3154-- --
3155
3156-- newtype UserAutocompleteInTeam = UserAutocompleteInTeam
3157--   { userAutocompleteInTeamInTeam :: (Seq User)
3158--   } deriving (Read, Show, Eq)
3159
3160-- instance A.FromJSON UserAutocompleteInTeam where
3161--   parseJSON = A.withObject "userAutocompleteInTeam" $ \v -> do
3162--     userAutocompleteInTeamInTeam <- v A..: "in_team"
3163--     return UserAutocompleteInTeam { .. }
3164
3165-- instance A.ToJSON UserAutocompleteInTeam where
3166--   toJSON UserAutocompleteInTeam { .. } = A.object
3167--     [ "in_team" A..= userAutocompleteInTeamInTeam
3168--     ]
3169
3170-- --
3171
3172-- --
3173
3174-- data XX1 = XX1
3175--   { xx1Url :: Text
3176--   , xx1Width :: UnknownType
3177--   , xx1SecureUrl :: Text
3178--   , xx1Type :: Text
3179--   , xx1Height :: UnknownType
3180--   } deriving (Read, Show, Eq)
3181
3182-- instance A.FromJSON XX1 where
3183--   parseJSON = A.withObject "xx1" $ \v -> do
3184--     xx1Url <- v A..: "url"
3185--     xx1Width <- v A..: "width"
3186--     xx1SecureUrl <- v A..: "secure_url"
3187--     xx1Type <- v A..: "type"
3188--     xx1Height <- v A..: "height"
3189--     return XX1 { .. }
3190
3191-- instance A.ToJSON XX1 where
3192--   toJSON XX1 { .. } = A.object
3193--     [ "url" A..= xx1Url
3194--     , "width" A..= xx1Width
3195--     , "secure_url" A..= xx1SecureUrl
3196--     , "type" A..= xx1Type
3197--     , "height" A..= xx1Height
3198--     ]
3199
3200-- --
3201
3202-- data XX10 = XX10
3203--   { xx10IsOrSearch :: Bool
3204--   , xx10Terms :: Text
3205--     -- ^ The search terms as inputed by the user.
3206--   } deriving (Read, Show, Eq)
3207
3208-- instance A.FromJSON XX10 where
3209--   parseJSON = A.withObject "xx10" $ \v -> do
3210--     xx10IsOrSearch <- v A..: "is_or_search"
3211--     xx10Terms <- v A..: "terms"
3212--     return XX10 { .. }
3213
3214-- instance A.ToJSON XX10 where
3215--   toJSON XX10 { .. } = A.object
3216--     [ "is_or_search" A..= xx10IsOrSearch
3217--     , "terms" A..= xx10Terms
3218--     ]
3219
3220-- --
3221
3222-- --
3223
3224-- data XX12 = XX12
3225--   { xx12HookId :: Text
3226--   , xx12ChannelId :: Text
3227--     -- ^ The ID of a public channel or private group that receives the webhook payloads.
3228--   , xx12DisplayName :: Text
3229--     -- ^ The display name for this incoming webhook
3230--   , xx12Description :: Text
3231--     -- ^ The description for this incoming webhook
3232--   } deriving (Read, Show, Eq)
3233
3234-- instance A.FromJSON XX12 where
3235--   parseJSON = A.withObject "xx12" $ \v -> do
3236--     xx12HookId <- v A..: "hook_id"
3237--     xx12ChannelId <- v A..: "channel_id"
3238--     xx12DisplayName <- v A..: "display_name"
3239--     xx12Description <- v A..: "description"
3240--     return XX12 { .. }
3241
3242-- instance A.ToJSON XX12 where
3243--   toJSON XX12 { .. } = A.object
3244--     [ "hook_id" A..= xx12HookId
3245--     , "channel_id" A..= xx12ChannelId
3246--     , "display_name" A..= xx12DisplayName
3247--     , "description" A..= xx12Description
3248--     ]
3249
3250-- --
3251
3252-- data XX13 = XX13
3253--   { xx13Name :: Text
3254--   , xx13IconUrl :: Text
3255--     -- ^ A URL to an icon to display with the application
3256--   , xx13CallbackUrls :: (Seq Text)
3257--     -- ^ A list of callback URLs for the appliation
3258--   , xx13Homepage :: Text
3259--     -- ^ A link to the website of the application
3260--   , xx13IsTrusted :: UnknownType
3261--     -- ^ Set this to `true` to skip asking users for permission
3262--   , xx13Description :: Text
3263--     -- ^ A short description of the application
3264--   } deriving (Read, Show, Eq)
3265
3266-- instance A.FromJSON XX13 where
3267--   parseJSON = A.withObject "xx13" $ \v -> do
3268--     xx13Name <- v A..: "name"
3269--     xx13IconUrl <- v A..: "icon_url"
3270--     xx13CallbackUrls <- v A..: "callback_urls"
3271--     xx13Homepage <- v A..: "homepage"
3272--     xx13IsTrusted <- v A..: "is_trusted"
3273--     xx13Description <- v A..: "description"
3274--     return XX13 { .. }
3275
3276-- instance A.ToJSON XX13 where
3277--   toJSON XX13 { .. } = A.object
3278--     [ "name" A..= xx13Name
3279--     , "icon_url" A..= xx13IconUrl
3280--     , "callback_urls" A..= xx13CallbackUrls
3281--     , "homepage" A..= xx13Homepage
3282--     , "is_trusted" A..= xx13IsTrusted
3283--     , "description" A..= xx13Description
3284--     ]
3285
3286-- --
3287
3288-- --
3289
3290data UploadResponse = UploadResponse
3291  { uploadResponseClientIds :: (Seq Text) -- might be null
3292  , uploadResponseFileInfos :: (Seq FileInfo)
3293    -- ^ A list of file metadata that has been stored in the database
3294  } deriving (Read, Show, Eq)
3295
3296instance A.FromJSON UploadResponse where
3297  parseJSON = A.withObject "UploadResponse" $ \v -> do
3298    uploadResponseClientIds <- v A..:? "client_ids" A..!= fromList []
3299    uploadResponseFileInfos <- v A..: "file_infos"
3300    return UploadResponse { .. }
3301
3302instance A.ToJSON UploadResponse where
3303  toJSON UploadResponse { .. } = A.object
3304    [ "client_ids" A..= uploadResponseClientIds
3305    , "file_infos" A..= uploadResponseFileInfos
3306    ]
3307
3308-- --
3309
3310-- --
3311
3312-- data XX19 = XX19
3313--   { xx19LdapId :: Text
3314--   , xx19CurrentService :: Text
3315--     -- ^ The service the user currently uses to login
3316--   , xx19NewService :: Text
3317--     -- ^ The service the user will use to login
3318--   , xx19Password :: Text
3319--     -- ^ The password used with the current service
3320--   , xx19Email :: Text
3321--     -- ^ The email of the user
3322--   , xx19MfaCode :: Text
3323--     -- ^ The MFA code of the current service
3324--   } deriving (Read, Show, Eq)
3325
3326-- instance A.FromJSON XX19 where
3327--   parseJSON = A.withObject "xx19" $ \v -> do
3328--     xx19LdapId <- v A..: "ldap_id"
3329--     xx19CurrentService <- v A..: "current_service"
3330--     xx19NewService <- v A..: "new_service"
3331--     xx19Password <- v A..: "password"
3332--     xx19Email <- v A..: "email"
3333--     xx19MfaCode <- v A..: "mfa_code"
3334--     return XX19 { .. }
3335
3336-- instance A.ToJSON XX19 where
3337--   toJSON XX19 { .. } = A.object
3338--     [ "ldap_id" A..= xx19LdapId
3339--     , "current_service" A..= xx19CurrentService
3340--     , "new_service" A..= xx19NewService
3341--     , "password" A..= xx19Password
3342--     , "email" A..= xx19Email
3343--     , "mfa_code" A..= xx19MfaCode
3344--     ]
3345
3346-- --
3347
3348-- data XX2 = XX2
3349--   { xx2Username :: Text
3350--   , xx2Gender :: Text
3351--   , xx2FirstName :: Text
3352--   , xx2LastName :: Text
3353--   } deriving (Read, Show, Eq)
3354
3355-- instance A.FromJSON XX2 where
3356--   parseJSON = A.withObject "xx2" $ \v -> do
3357--     xx2Username <- v A..: "username"
3358--     xx2Gender <- v A..: "gender"
3359--     xx2FirstName <- v A..: "first_name"
3360--     xx2LastName <- v A..: "last_name"
3361--     return XX2 { .. }
3362
3363-- instance A.ToJSON XX2 where
3364--   toJSON XX2 { .. } = A.object
3365--     [ "username" A..= xx2Username
3366--     , "gender" A..= xx2Gender
3367--     , "first_name" A..= xx2FirstName
3368--     , "last_name" A..= xx2LastName
3369--     ]
3370
3371-- --
3372
3373-- data XX20 = XX20
3374--   { xx20Type :: Text
3375--   , xx20Data :: UnknownType
3376--     -- ^ An object containing any additional data required for this job type
3377--   } deriving (Read, Show, Eq)
3378
3379-- instance A.FromJSON XX20 where
3380--   parseJSON = A.withObject "xx20" $ \v -> do
3381--     xx20Type <- v A..: "type"
3382--     xx20Data <- v A..: "data"
3383--     return XX20 { .. }
3384
3385-- instance A.ToJSON XX20 where
3386--   toJSON XX20 { .. } = A.object
3387--     [ "type" A..= xx20Type
3388--     , "data" A..= xx20Data
3389--     ]
3390
3391--
3392
3393-- --
3394
3395-- data XX22 = XX22
3396--   { xx22Code :: Text
3397--   , xx22Activate :: UnknownType
3398--     -- ^ Use `true` to activate, `false` to deactivate
3399--   } deriving (Read, Show, Eq)
3400
3401-- instance A.FromJSON XX22 where
3402--   parseJSON = A.withObject "xx22" $ \v -> do
3403--     xx22Code <- v A..: "code"
3404--     xx22Activate <- v A..: "activate"
3405--     return XX22 { .. }
3406
3407-- instance A.ToJSON XX22 where
3408--   toJSON XX22 { .. } = A.object
3409--     [ "code" A..= xx22Code
3410--     , "activate" A..= xx22Activate
3411--     ]
3412
3413-- --
3414
3415-- data XX23 = XX23
3416--   { xx23DisplayName :: Text
3417--   , xx23CompanyName :: Text
3418--   , xx23InviteId :: Text
3419--   , xx23Description :: Text
3420--   , xx23AllowOpenInvite :: UnknownType
3421--   } deriving (Read, Show, Eq)
3422
3423-- instance A.FromJSON XX23 where
3424--   parseJSON = A.withObject "xx23" $ \v -> do
3425--     xx23DisplayName <- v A..: "display_name"
3426--     xx23CompanyName <- v A..: "company_name"
3427--     xx23InviteId <- v A..: "invite_id"
3428--     xx23Description <- v A..: "description"
3429--     xx23AllowOpenInvite <- v A..: "allow_open_invite"
3430--     return XX23 { .. }
3431
3432-- instance A.ToJSON XX23 where
3433--   toJSON XX23 { .. } = A.object
3434--     [ "display_name" A..= xx23DisplayName
3435--     , "company_name" A..= xx23CompanyName
3436--     , "invite_id" A..= xx23InviteId
3437--     , "description" A..= xx23Description
3438--     , "allow_open_invite" A..= xx23AllowOpenInvite
3439--     ]
3440
3441-- --
3442
3443-- data XX24 = XX24
3444--   { xx24NewPassword :: Text
3445--   , xx24Code :: Text
3446--     -- ^ The recovery code
3447--   } deriving (Read, Show, Eq)
3448
3449-- instance A.FromJSON XX24 where
3450--   parseJSON = A.withObject "xx24" $ \v -> do
3451--     xx24NewPassword <- v A..: "new_password"
3452--     xx24Code <- v A..: "code"
3453--     return XX24 { .. }
3454
3455-- instance A.ToJSON XX24 where
3456--   toJSON XX24 { .. } = A.object
3457--     [ "new_password" A..= xx24NewPassword
3458--     , "code" A..= xx24Code
3459--     ]
3460
3461-- --
3462
3463-- data XX25 = XX25
3464--   { xx25ChannelId :: Text
3465--   , xx25DisplayName :: Text
3466--     -- ^ The display name for this incoming webhook
3467--   , xx25Description :: Text
3468--     -- ^ The description for this incoming webhook
3469--   } deriving (Read, Show, Eq)
3470
3471-- instance A.FromJSON XX25 where
3472--   parseJSON = A.withObject "xx25" $ \v -> do
3473--     xx25ChannelId <- v A..: "channel_id"
3474--     xx25DisplayName <- v A..: "display_name"
3475--     xx25Description <- v A..: "description"
3476--     return XX25 { .. }
3477
3478-- instance A.ToJSON XX25 where
3479--   toJSON XX25 { .. } = A.object
3480--     [ "channel_id" A..= xx25ChannelId
3481--     , "display_name" A..= xx25DisplayName
3482--     , "description" A..= xx25Description
3483--     ]
3484
3485-- --
3486
3487-- data XX26 = XX26
3488--   { xx26Message :: Text
3489--   , xx26Level :: Text
3490--     -- ^ The error level, e.g. ERROR or INFO
3491--   } deriving (Read, Show, Eq)
3492
3493-- instance A.FromJSON XX26 where
3494--   parseJSON = A.withObject "xx26" $ \v -> do
3495--     xx26Message <- v A..: "message"
3496--     xx26Level <- v A..: "level"
3497--     return XX26 { .. }
3498
3499-- instance A.ToJSON XX26 where
3500--   toJSON XX26 { .. } = A.object
3501--     [ "message" A..= xx26Message
3502--     , "level" A..= xx26Level
3503--     ]
3504
3505-- --
3506
3507-- data XX28 = XX28
3508--   { xx28Header :: Text
3509--   , xx28DisplayName :: Text
3510--     -- ^ The non-unique UI name for the channel
3511--   , xx28Name :: Text
3512--     -- ^ The unique handle for the channel, will be present in the channel URL
3513--   , xx28Type :: Text
3514--     -- ^ 'O' for a public channel, 'P' for a private channel
3515--   , xx28Id :: Text
3516--     -- ^ The channel's id, not updatable
3517--   , xx28Purpose :: Text
3518--     -- ^ A short description of the purpose of the channel
3519--   } deriving (Read, Show, Eq)
3520
3521-- instance A.FromJSON XX28 where
3522--   parseJSON = A.withObject "xx28" $ \v -> do
3523--     xx28Header <- v A..: "header"
3524--     xx28DisplayName <- v A..: "display_name"
3525--     xx28Name <- v A..: "name"
3526--     xx28Type <- v A..: "type"
3527--     xx28Id <- v A..: "id"
3528--     xx28Purpose <- v A..: "purpose"
3529--     return XX28 { .. }
3530
3531-- instance A.ToJSON XX28 where
3532--   toJSON XX28 { .. } = A.object
3533--     [ "header" A..= xx28Header
3534--     , "display_name" A..= xx28DisplayName
3535--     , "name" A..= xx28Name
3536--     , "type" A..= xx28Type
3537--     , "id" A..= xx28Id
3538--     , "purpose" A..= xx28Purpose
3539--     ]
3540
3541-- --
3542
3543-- data XX29 = XX29
3544--   { xx29CurrentPassword :: Text
3545--   , xx29NewPassword :: Text
3546--     -- ^ The new password for the user
3547--   } deriving (Read, Show, Eq)
3548
3549-- instance A.FromJSON XX29 where
3550--   parseJSON = A.withObject "xx29" $ \v -> do
3551--     xx29CurrentPassword <- v A..: "current_password"
3552--     xx29NewPassword <- v A..: "new_password"
3553--     return XX29 { .. }
3554
3555-- instance A.ToJSON XX29 where
3556--   toJSON XX29 { .. } = A.object
3557--     [ "current_password" A..= xx29CurrentPassword
3558--     , "new_password" A..= xx29NewPassword
3559--     ]
3560
3561-- --
3562
3563-- data XX3 = XX3
3564--   { xx3Url :: Text
3565--   , xx3Width :: UnknownType
3566--   , xx3SecureUrl :: Text
3567--   , xx3Type :: Text
3568--   , xx3Height :: UnknownType
3569--   } deriving (Read, Show, Eq)
3570
3571-- instance A.FromJSON XX3 where
3572--   parseJSON = A.withObject "xx3" $ \v -> do
3573--     xx3Url <- v A..: "url"
3574--     xx3Width <- v A..: "width"
3575--     xx3SecureUrl <- v A..: "secure_url"
3576--     xx3Type <- v A..: "type"
3577--     xx3Height <- v A..: "height"
3578--     return XX3 { .. }
3579
3580-- instance A.ToJSON XX3 where
3581--   toJSON XX3 { .. } = A.object
3582--     [ "url" A..= xx3Url
3583--     , "width" A..= xx3Width
3584--     , "secure_url" A..= xx3SecureUrl
3585--     , "type" A..= xx3Type
3586--     , "height" A..= xx3Height
3587--     ]
3588
3589-- --
3590
3591-- data XX30 = XX30
3592--   { xx30Username :: Text
3593--   , xx30FirstName :: Text
3594--   , xx30LastName :: Text
3595--   , xx30NotifyProps :: UnknownType
3596--   , xx30Locale :: Text
3597--   , xx30Id :: Text
3598--   , xx30Props :: UnknownType
3599--   , xx30Position :: Text
3600--   , xx30Nickname :: Text
3601--   , xx30Email :: Text
3602--   } deriving (Read, Show, Eq)
3603
3604-- instance A.FromJSON XX30 where
3605--   parseJSON = A.withObject "xx30" $ \v -> do
3606--     xx30Username <- v A..: "username"
3607--     xx30FirstName <- v A..: "first_name"
3608--     xx30LastName <- v A..: "last_name"
3609--     xx30NotifyProps <- v A..: "notify_props"
3610--     xx30Locale <- v A..: "locale"
3611--     xx30Id <- v A..: "id"
3612--     xx30Props <- v A..: "props"
3613--     xx30Position <- v A..: "position"
3614--     xx30Nickname <- v A..: "nickname"
3615--     xx30Email <- v A..: "email"
3616--     return XX30 { .. }
3617
3618-- instance A.ToJSON XX30 where
3619--   toJSON XX30 { .. } = A.object
3620--     [ "username" A..= xx30Username
3621--     , "first_name" A..= xx30FirstName
3622--     , "last_name" A..= xx30LastName
3623--     , "notify_props" A..= xx30NotifyProps
3624--     , "locale" A..= xx30Locale
3625--     , "id" A..= xx30Id
3626--     , "props" A..= xx30Props
3627--     , "position" A..= xx30Position
3628--     , "nickname" A..= xx30Nickname
3629--     , "email" A..= xx30Email
3630--     ]
3631
3632-- --
3633
3634-- data XX31 = XX31
3635--   { xx31Username :: Text
3636--   , xx31FirstName :: Text
3637--   , xx31LastName :: Text
3638--   , xx31Locale :: Text
3639--   , xx31Props :: UnknownType
3640--   , xx31Password :: Text
3641--   , xx31Nickname :: Text
3642--   , xx31Email :: Text
3643--   } deriving (Read, Show, Eq)
3644
3645-- instance A.FromJSON XX31 where
3646--   parseJSON = A.withObject "xx31" $ \v -> do
3647--     xx31Username <- v A..: "username"
3648--     xx31FirstName <- v A..: "first_name"
3649--     xx31LastName <- v A..: "last_name"
3650--     xx31Locale <- v A..: "locale"
3651--     xx31Props <- v A..: "props"
3652--     xx31Password <- v A..: "password"
3653--     xx31Nickname <- v A..: "nickname"
3654--     xx31Email <- v A..: "email"
3655--     return XX31 { .. }
3656
3657-- instance A.ToJSON XX31 where
3658--   toJSON XX31 { .. } = A.object
3659--     [ "username" A..= xx31Username
3660--     , "first_name" A..= xx31FirstName
3661--     , "last_name" A..= xx31LastName
3662--     , "locale" A..= xx31Locale
3663--     , "props" A..= xx31Props
3664--     , "password" A..= xx31Password
3665--     , "nickname" A..= xx31Nickname
3666--     , "email" A..= xx31Email
3667--     ]
3668
3669-- --
3670
3671-- data XX32 = XX32
3672--   { xx32Url :: Text
3673--   , xx32TeamId :: Text
3674--     -- ^ Team ID to where the command should be created
3675--   , xx32Trigger :: Text
3676--     -- ^ Activation word to trigger the command
3677--   , xx32Method :: Text
3678--     -- ^ `'P'` for post request, `'G'` for get request
3679--   } deriving (Read, Show, Eq)
3680
3681-- instance A.FromJSON XX32 where
3682--   parseJSON = A.withObject "xx32" $ \v -> do
3683--     xx32Url <- v A..: "url"
3684--     xx32TeamId <- v A..: "team_id"
3685--     xx32Trigger <- v A..: "trigger"
3686--     xx32Method <- v A..: "method"
3687--     return XX32 { .. }
3688
3689-- instance A.ToJSON XX32 where
3690--   toJSON XX32 { .. } = A.object
3691--     [ "url" A..= xx32Url
3692--     , "team_id" A..= xx32TeamId
3693--     , "trigger" A..= xx32Trigger
3694--     , "method" A..= xx32Method
3695--     ]
3696
3697-- --
3698
3699-- data XX33 = XX33
3700--   { xx33TriggerWhen :: Integer
3701--   , xx33DisplayName :: Text
3702--     -- ^ The display name for this outgoing webhook
3703--   , xx33Description :: Text
3704--     -- ^ The description for this outgoing webhook
3705--   , xx33ChannelId :: Text
3706--     -- ^ The ID of a public channel that the webhook watchs
3707--   , xx33TeamId :: Text
3708--     -- ^ The ID of the team that the webhook watchs
3709--   , xx33ContentType :: Text
3710--     -- ^ The format to POST the data in, either `application/json` or `application/x-www-form-urlencoded`
3711--   , xx33TriggerWords :: (Seq Text)
3712--     -- ^ List of words for the webhook to trigger on
3713--   , xx33CallbackUrls :: (Seq Text)
3714--     -- ^ The URLs to POST the payloads to when the webhook is triggered
3715--   } deriving (Read, Show, Eq)
3716
3717-- instance A.FromJSON XX33 where
3718--   parseJSON = A.withObject "xx33" $ \v -> do
3719--     xx33TriggerWhen <- v A..: "trigger_when"
3720--     xx33DisplayName <- v A..: "display_name"
3721--     xx33Description <- v A..: "description"
3722--     xx33ChannelId <- v A..: "channel_id"
3723--     xx33TeamId <- v A..: "team_id"
3724--     xx33ContentType <- v A..: "content_type"
3725--     xx33TriggerWords <- v A..: "trigger_words"
3726--     xx33CallbackUrls <- v A..: "callback_urls"
3727--     return XX33 { .. }
3728
3729-- instance A.ToJSON XX33 where
3730--   toJSON XX33 { .. } = A.object
3731--     [ "trigger_when" A..= xx33TriggerWhen
3732--     , "display_name" A..= xx33DisplayName
3733--     , "description" A..= xx33Description
3734--     , "channel_id" A..= xx33ChannelId
3735--     , "team_id" A..= xx33TeamId
3736--     , "content_type" A..= xx33ContentType
3737--     , "trigger_words" A..= xx33TriggerWords
3738--     , "callback_urls" A..= xx33CallbackUrls
3739--     ]
3740
3741-- --
3742
3743-- data XX34 = XX34
3744--   { xx34DisplayName :: Text
3745--   , xx34Description :: Text
3746--   , xx34Name :: Text
3747--   , xx34Id :: Text
3748--   } deriving (Read, Show, Eq)
3749
3750-- instance A.FromJSON XX34 where
3751--   parseJSON = A.withObject "xx34" $ \v -> do
3752--     xx34DisplayName <- v A..: "display_name"
3753--     xx34Description <- v A..: "description"
3754--     xx34Name <- v A..: "name"
3755--     xx34Id <- v A..: "id"
3756--     return XX34 { .. }
3757
3758-- instance A.ToJSON XX34 where
3759--   toJSON XX34 { .. } = A.object
3760--     [ "display_name" A..= xx34DisplayName
3761--     , "description" A..= xx34Description
3762--     , "name" A..= xx34Name
3763--     , "id" A..= xx34Id
3764--     ]
3765
3766-- --
3767
3768-- data XX35 = XX35
3769--   { xx35HookId :: Text
3770--   , xx35ChannelId :: Text
3771--     -- ^ The ID of a public channel or private group that receives the webhook payloads.
3772--   , xx35DisplayName :: Text
3773--     -- ^ The display name for this incoming webhook
3774--   , xx35Description :: Text
3775--     -- ^ The description for this incoming webhook
3776--   } deriving (Read, Show, Eq)
3777
3778-- instance A.FromJSON XX35 where
3779--   parseJSON = A.withObject "xx35" $ \v -> do
3780--     xx35HookId <- v A..: "hook_id"
3781--     xx35ChannelId <- v A..: "channel_id"
3782--     xx35DisplayName <- v A..: "display_name"
3783--     xx35Description <- v A..: "description"
3784--     return XX35 { .. }
3785
3786-- instance A.ToJSON XX35 where
3787--   toJSON XX35 { .. } = A.object
3788--     [ "hook_id" A..= xx35HookId
3789--     , "channel_id" A..= xx35ChannelId
3790--     , "display_name" A..= xx35DisplayName
3791--     , "description" A..= xx35Description
3792--     ]
3793
3794-- --
3795
3796-- data XX36 = XX36
3797--   { xx36DisplayName :: Text
3798--   , xx36AllowedDomains :: Text
3799--   , xx36CompanyName :: Text
3800--   , xx36AllowOpenInvite :: Text
3801--   , xx36InviteId :: Text
3802--   , xx36Description :: Text
3803--   } deriving (Read, Show, Eq)
3804
3805-- instance A.FromJSON XX36 where
3806--   parseJSON = A.withObject "xx36" $ \v -> do
3807--     xx36DisplayName <- v A..: "display_name"
3808--     xx36AllowedDomains <- v A..: "allowed_domains"
3809--     xx36CompanyName <- v A..: "company_name"
3810--     xx36AllowOpenInvite <- v A..: "allow_open_invite"
3811--     xx36InviteId <- v A..: "invite_id"
3812--     xx36Description <- v A..: "description"
3813--     return XX36 { .. }
3814
3815-- instance A.ToJSON XX36 where
3816--   toJSON XX36 { .. } = A.object
3817--     [ "display_name" A..= xx36DisplayName
3818--     , "allowed_domains" A..= xx36AllowedDomains
3819--     , "company_name" A..= xx36CompanyName
3820--     , "allow_open_invite" A..= xx36AllowOpenInvite
3821--     , "invite_id" A..= xx36InviteId
3822--     , "description" A..= xx36Description
3823--     ]
3824
3825-- --
3826
3827-- data XX37 = XX37
3828--   { xx37Secret :: Text
3829--   , xx37QrCode :: Text
3830--     -- ^ A base64 encoded QR code image
3831--   } deriving (Read, Show, Eq)
3832
3833-- instance A.FromJSON XX37 where
3834--   parseJSON = A.withObject "xx37" $ \v -> do
3835--     xx37Secret <- v A..: "secret"
3836--     xx37QrCode <- v A..: "qr_code"
3837--     return XX37 { .. }
3838
3839-- instance A.ToJSON XX37 where
3840--   toJSON XX37 { .. } = A.object
3841--     [ "secret" A..= xx37Secret
3842--     , "qr_code" A..= xx37QrCode
3843--     ]
3844
3845-- --
3846
3847-- data XX38 = XX38
3848--   { xx38Username :: Text
3849--   , xx38FirstName :: Text
3850--   , xx38LastName :: Text
3851--   , xx38NotifyProps :: UnknownType
3852--   , xx38Locale :: Text
3853--   , xx38Props :: UnknownType
3854--   , xx38Position :: Text
3855--   , xx38Nickname :: Text
3856--   , xx38Email :: Text
3857--   } deriving (Read, Show, Eq)
3858
3859-- instance A.FromJSON XX38 where
3860--   parseJSON = A.withObject "xx38" $ \v -> do
3861--     xx38Username <- v A..: "username"
3862--     xx38FirstName <- v A..: "first_name"
3863--     xx38LastName <- v A..: "last_name"
3864--     xx38NotifyProps <- v A..: "notify_props"
3865--     xx38Locale <- v A..: "locale"
3866--     xx38Props <- v A..: "props"
3867--     xx38Position <- v A..: "position"
3868--     xx38Nickname <- v A..: "nickname"
3869--     xx38Email <- v A..: "email"
3870--     return XX38 { .. }
3871
3872-- instance A.ToJSON XX38 where
3873--   toJSON XX38 { .. } = A.object
3874--     [ "username" A..= xx38Username
3875--     , "first_name" A..= xx38FirstName
3876--     , "last_name" A..= xx38LastName
3877--     , "notify_props" A..= xx38NotifyProps
3878--     , "locale" A..= xx38Locale
3879--     , "props" A..= xx38Props
3880--     , "position" A..= xx38Position
3881--     , "nickname" A..= xx38Nickname
3882--     , "email" A..= xx38Email
3883--     ]
3884
3885-- --
3886
3887-- data XX4 = XX4
3888--   { xx4Username :: Text
3889--   , xx4Gender :: Text
3890--   , xx4FirstName :: Text
3891--   , xx4LastName :: Text
3892--   } deriving (Read, Show, Eq)
3893
3894-- instance A.FromJSON XX4 where
3895--   parseJSON = A.withObject "xx4" $ \v -> do
3896--     xx4Username <- v A..: "username"
3897--     xx4Gender <- v A..: "gender"
3898--     xx4FirstName <- v A..: "first_name"
3899--     xx4LastName <- v A..: "last_name"
3900--     return XX4 { .. }
3901
3902-- instance A.ToJSON XX4 where
3903--   toJSON XX4 { .. } = A.object
3904--     [ "username" A..= xx4Username
3905--     , "gender" A..= xx4Gender
3906--     , "first_name" A..= xx4FirstName
3907--     , "last_name" A..= xx4LastName
3908--     ]
3909
3910-- --
3911
3912-- data XX5 = XX5
3913--   { xx5Url :: Text
3914--   , xx5SecureUrl :: Text
3915--   , xx5Type :: Text
3916--   } deriving (Read, Show, Eq)
3917
3918-- instance A.FromJSON XX5 where
3919--   parseJSON = A.withObject "xx5" $ \v -> do
3920--     xx5Url <- v A..: "url"
3921--     xx5SecureUrl <- v A..: "secure_url"
3922--     xx5Type <- v A..: "type"
3923--     return XX5 { .. }
3924
3925-- instance A.ToJSON XX5 where
3926--   toJSON XX5 { .. } = A.object
3927--     [ "url" A..= xx5Url
3928--     , "secure_url" A..= xx5SecureUrl
3929--     , "type" A..= xx5Type
3930--     ]
3931
3932-- --
3933
3934-- --
3935
3936-- data XX8 = XX8
3937--   { xx8Token :: Text
3938--   , xx8TurnUsername :: Text
3939--     -- ^ The username to use with the TURN server
3940--   , xx8TurnUri :: Text
3941--     -- ^ The URI to the TURN server
3942--   , xx8StunUri :: Text
3943--     -- ^ The URI to the STUN server
3944--   , xx8GatewayUrl :: Text
3945--     -- ^ The URL to the gateway server
3946--   , xx8TurnPassword :: Text
3947--     -- ^ The password to use with the TURN server
3948--   } deriving (Read, Show, Eq)
3949
3950-- instance A.FromJSON XX8 where
3951--   parseJSON = A.withObject "xx8" $ \v -> do
3952--     xx8Token <- v A..: "token"
3953--     xx8TurnUsername <- v A..: "turn_username"
3954--     xx8TurnUri <- v A..: "turn_uri"
3955--     xx8StunUri <- v A..: "stun_uri"
3956--     xx8GatewayUrl <- v A..: "gateway_url"
3957--     xx8TurnPassword <- v A..: "turn_password"
3958--     return XX8 { .. }
3959
3960-- instance A.ToJSON XX8 where
3961--   toJSON XX8 { .. } = A.object
3962--     [ "token" A..= xx8Token
3963--     , "turn_username" A..= xx8TurnUsername
3964--     , "turn_uri" A..= xx8TurnUri
3965--     , "stun_uri" A..= xx8StunUri
3966--     , "gateway_url" A..= xx8GatewayUrl
3967--     , "turn_password" A..= xx8TurnPassword
3968--     ]
3969
3970
3971-- * Helpers
3972
3973-- | Add a post to a user's flagged post list. This is a convenience
3974-- wrapper for the 'mmSaveUsersPreferences' function.
3975--
3976--   /Permissions/: Must be logged in as the user being updated or have the
3977--   @edit_other_users@ permission.
3978mmFlagPost :: UserId -> PostId -> Session -> IO ()
3979mmFlagPost uId pId =
3980  let body = FlaggedPost
3981        { flaggedPostUserId = uId
3982        , flaggedPostId     = pId
3983        , flaggedPostStatus = True
3984        }
3985  in inPut (printf "/users/%s/preferences" uId) (jsonBody [body]) noResponse
3986
3987-- | Remove a post from a user's flagged post list. This is a convenience
3988-- wrapper for the 'mmSaveUsersPreferences' function.
3989--
3990--   /Permissions/: Must be logged in as the user being updated or have the
3991--   @edit_other_users@ permission.
3992mmUnflagPost :: UserId -> PostId -> Session -> IO ()
3993mmUnflagPost uId pId =
3994  let body = FlaggedPost
3995        { flaggedPostUserId = uId
3996        , flaggedPostId     = pId
3997        , flaggedPostStatus = False
3998        }
3999  in inPost (printf "/users/%s/preferences/delete" uId) (jsonBody [body]) noResponse
4000