webex-teams-api-0.2.0.0: A Haskell bindings for Webex Teams API

Copyright(c) Naoto Shimazaki 20172018
LicenseMIT (see the file LICENSE)
Maintainerhttps://github.com/nshimaza
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Network.WebexTeams

Contents

Description

This module provides types and functions for accessing Cisco Webex Teams REST API.

The module is designed to improve type safety over the API. Each entity is separately typed. JSON messages contained in REST responses are decoded into appropriate type of Haskell record. JSON messages sent in REST requests are encoded only from correct type of record.

Some Webex Teams REST API return list of objects. Those APIs require HTTP Link Header based pagination. Haskell functions for those APIs automatically request subsequent pages as needed.

Examples

    -- Sending a message to a room.
    let auth        = Authorization "your authorization token"
        roomId      = RoomId "Room ID your message to be sent"
        messageText = MessageText "your message"
        message     = CreateMessage (Just roomId) Nothing Nothing (Just messageText) Nothing Nothing
    createEntity auth def createMessage >>= print . getResponseBody

    -- Obtaining detail of a user.
    let personId    = PersonId "your person ID"
    getDetail auth def personId >>= print . getResponseBody

    -- Obtaining membership of a room as stream of object representing each membership relation.
    let filter = MembershipFilter yourRoomId Nothing Nothing
    runConduit $ streamListWithFilter auth def filter .| takeC 200 .| mapM_C print

    -- Create a room.
    let createRoom  = CreateRoom "Title of the new room" Nothing
    createEntity auth def createRoom >>= print . getResponseBody

    -- Delete a room.
    deleteRoom auth def roomId >>= print . getResponseBody

List and steaming

The WebexTeams module doesn't provide streaming API for REST response returning list of entities. It is because the author of the package wants to keep it streaming library agnostic. Instead, it provides ListReader IO action to read list responses with automatic pagenation. Streaming APIs can be found in separate packages like webex-teams-pipes or webex-teams-conduit.

Support for Lens

This package provides many of records representing objects communicated via Webex Teams REST API. Those records are designed to allow create lenses by Control.Lens.TH.makeFields.

Following example creates overloaded accessors for Person, Room and Team.

makeFields ''Person
makeFields ''Room
makeFields ''Team

You can access personId, roomId and teamId via overloaded accessor function id like this.

    let yourPersonId = yourPerson ^. id
        yourRoomId = yourRoom ^. id
        yourTeamId = yourTeam ^. id

This package does not provide pre-generated lenses for you because not everyone need it but you can make it by yourself so easily as described.

Synopsis

Types

Class and Type Families

class (WebexTeamsApiPath a, WebexTeamsResponse a) => WebexTeamsFilter a Source #

Convert given filter condition parameter in a concrete type to HTTP query strings.

Minimal complete definition

toFilterList

Instances

WebexTeamsFilter PersonFilter Source #

User can list people with filter parameter.

WebexTeamsFilter TeamMembershipFilter Source #

User can list team membership with filter parameter.

WebexTeamsFilter RoomFilter Source #

User can list rooms with filter parameter.

WebexTeamsFilter MembershipFilter Source #

User can list memberships with filter parameter.

WebexTeamsFilter MessageFilter Source #

User can list messages with filter parameter.

WebexTeamsFilter LicenseFilter Source #

User can list licenses with filter parameter.

WebexTeamsFilter WebhookRoomFilter Source #

User can filter Webhook events from room.

WebexTeamsFilter WebhookMessageFilter Source #

User can filter Webhook events from message.

WebexTeamsFilter WebhookMembershipFilter Source #

User can filter Webhook events from membership.

class FromJSON (ToList i) => WebexTeamsListItem i Source #

WebexTeamsListItem is a type class grouping types with following common usage.

  • It is used for return value of get-detail APIs.
  • It is used for element of return value of list APIs.

WebexTeamsListItem also associates the above type to wrapping list type (e.g. associates Person to PersonList). Wrapping type (PersonList in this case) is necessary for parsing JSON from REST API but what we are interested in is bare list such like [Person]. Type family association defined in this class is used for type translation from type of items to type of wrapper.

Minimal complete definition

unwrap

Instances

WebexTeamsListItem Person Source #

PersonList wraps Person.

Associated Types

type ToList Person :: * Source #

WebexTeamsListItem Team Source #

TeamList wraps Team

Associated Types

type ToList Team :: * Source #

Methods

unwrap :: ToList Team -> [Team] Source #

WebexTeamsListItem TeamMembership Source #

TeamMembershipList wraps TeamMembership

WebexTeamsListItem Room Source #

RoomList wraps Room

Associated Types

type ToList Room :: * Source #

Methods

unwrap :: ToList Room -> [Room] Source #

WebexTeamsListItem Membership Source #

MembershipList wraps Membership

Associated Types

type ToList Membership :: * Source #

WebexTeamsListItem Message Source #

MessageList wraps Message

Associated Types

type ToList Message :: * Source #

WebexTeamsListItem Organization Source #

OrganizationList wraps Organization

Associated Types

type ToList Organization :: * Source #

WebexTeamsListItem License Source #

LicenseList wraps License

Associated Types

type ToList License :: * Source #

WebexTeamsListItem Role Source #

RoleList wraps Role

Associated Types

type ToList Role :: * Source #

Methods

unwrap :: ToList Role -> [Role] Source #

WebexTeamsListItem Webhook Source #

WebhookList wraps Webhook

Associated Types

type ToList Webhook :: * Source #

Common Types

newtype Authorization Source #

Authorization string against Webex Teams API to be contained in HTTP Authorization header of every request.

type CiscoSparkRequest = WebexTeamsRequest Source #

Type synonym for backward compatibility.

data WebexTeamsRequest Source #

Wrapping Request in order to provide easy default value specifically for Webex Teams public API.

Constructors

WebexTeamsRequest 

Fields

Instances

Show WebexTeamsRequest Source # 
Default WebexTeamsRequest Source #

Default parameters for HTTP request to Webex Teams REST API.

newtype Timestamp Source #

Type representing timestamp. For now, it is just copied from API response JSON.

Constructors

Timestamp Text 

newtype ErrorCode Source #

Error code for element level error potentially contained in List API responses.

Constructors

ErrorCode Text 

data ErrorTitle Source #

ErrorTitle represent concrete error code and reason. It appears in Errors.

Constructors

ErrorTitle 

Fields

newtype Errors Source #

Errors is used for element level error in List API. When list API failed to retrieve an element, it returns this object for the element and response API status as successful instead of failing entire API request.

Refer to API Document for more detail.

Constructors

Errors 

Instances

Eq Errors Source # 

Methods

(==) :: Errors -> Errors -> Bool #

(/=) :: Errors -> Errors -> Bool #

Show Errors Source # 
ToJSON Errors Source # 
FromJSON Errors Source #

Errors derives ToJSON and FromJSON via deriveJSON template haskell function.

People related types

data Person Source #

Person is detail description of Webex Teams user or bot. Person is decoded from response JSON of Get Person Details REST call. It is also element type of response of List People call.

Constructors

Person 

Fields

Instances

Eq Person Source # 

Methods

(==) :: Person -> Person -> Bool #

(/=) :: Person -> Person -> Bool #

Show Person Source # 
ToJSON Person Source # 
FromJSON Person Source #

Person derives ToJSON and FromJSON via deriveJSON template haskell function.

WebexTeamsListItem Person Source #

PersonList wraps Person.

Associated Types

type ToList Person :: * Source #

type ToList Person Source # 

newtype PersonId Source #

Identifying Person describing detail of Webex Teams user or bot.

Constructors

PersonId Text 

Instances

Eq PersonId Source # 
Show PersonId Source # 
Generic PersonId Source # 

Associated Types

type Rep PersonId :: * -> * #

Methods

from :: PersonId -> Rep PersonId x #

to :: Rep PersonId x -> PersonId #

ToJSON PersonId Source # 
FromJSON PersonId Source # 
WebexTeamsDetail PersonId Source #

User can get detail of a person.

WebexTeamsResponse PersonId Source #

Get detail for a person API uses "PersonId' and responses Person.

Associated Types

type ToResponse PersonId :: * Source #

WebexTeamsApiPath PersonId Source #

Get detail for a person API uses PersonId and path "people".

type Rep PersonId Source # 
type Rep PersonId = D1 * (MetaData "PersonId" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" True) (C1 * (MetaCons "PersonId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse PersonId Source # 

newtype Email Source #

Email address of user.

Constructors

Email Text 

Instances

Eq Email Source # 

Methods

(==) :: Email -> Email -> Bool #

(/=) :: Email -> Email -> Bool #

Show Email Source # 

Methods

showsPrec :: Int -> Email -> ShowS #

show :: Email -> String #

showList :: [Email] -> ShowS #

Generic Email Source # 

Associated Types

type Rep Email :: * -> * #

Methods

from :: Email -> Rep Email x #

to :: Rep Email x -> Email #

ToJSON Email Source # 
FromJSON Email Source # 
type Rep Email Source # 
type Rep Email = D1 * (MetaData "Email" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" True) (C1 * (MetaCons "Email" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

newtype NickName Source #

Nickname of user.

Constructors

NickName Text 

Instances

newtype FirstName Source #

First name of user.

Constructors

FirstName Text 

newtype LastName Source #

Last name of user.

Constructors

LastName Text 

Instances

newtype AvatarUrl Source #

URL pointing to image file of Avatar.

Constructors

AvatarUrl Text 

newtype Timezone Source #

Timezone in timezone name.

Constructors

Timezone Text 

Instances

data PersonStatus Source #

Current status of Person. It can be updated automatically by recent activity or explicitly updated by user's operation or propagated from vacation setting on email system.

Constructors

PersonStatusActive

The Person is currently active. Decoded from "active".

PersonStatusInactive

The Person is currently not active. Decoded from "inactive".

PersonStatusOutOfOffice

Email system of the Person currently sets vacation. Decoded from "OutOfOffice".

PersonStatusDoNotDisturb

The Person is explicitly indicated do-not-disturb. Decoded from "DoNotDisturb".

PersonStatusUnknown

The status of the Person is unknown. Decoded from "unknown".

Instances

Eq PersonStatus Source # 
Show PersonStatus Source # 
Generic PersonStatus Source # 

Associated Types

type Rep PersonStatus :: * -> * #

ToJSON PersonStatus Source #

PersonStatus implements toEncoding to encode each constructor into JSON enum value.

FromJSON PersonStatus Source #

PersonStatus implements parseJSON to decode JSON enum value to a constructor.

type Rep PersonStatus Source # 
type Rep PersonStatus = D1 * (MetaData "PersonStatus" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" False) ((:+:) * ((:+:) * (C1 * (MetaCons "PersonStatusActive" PrefixI False) (U1 *)) (C1 * (MetaCons "PersonStatusInactive" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "PersonStatusOutOfOffice" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PersonStatusDoNotDisturb" PrefixI False) (U1 *)) (C1 * (MetaCons "PersonStatusUnknown" PrefixI False) (U1 *)))))

data PersonType Source #

PersonType indicates whether the Person is real human or bot.

Constructors

PersonTypePerson

The Person is a real human. Decoded from "person".

PersonTypeBot

The Person is a bot. Decoded from "bot".

newtype PersonList Source #

PersonList is decoded from response JSON of List People REST call. It is list of Person.

Constructors

PersonList 

Fields

data PersonFilter Source #

Optional query strings for people list API.

Constructors

PersonFilter 

Fields

Instances

Eq PersonFilter Source # 
Show PersonFilter Source # 
Generic PersonFilter Source # 

Associated Types

type Rep PersonFilter :: * -> * #

Default PersonFilter Source # 

Methods

def :: PersonFilter #

WebexTeamsFilter PersonFilter Source #

User can list people with filter parameter.

WebexTeamsResponse PersonFilter Source #

List people API uses PersonFilter and responses Person.

Associated Types

type ToResponse PersonFilter :: * Source #

WebexTeamsApiPath PersonFilter Source #

List people API uses PersonFilter and path "people".

type Rep PersonFilter Source # 
type Rep PersonFilter = D1 * (MetaData "PersonFilter" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" False) (C1 * (MetaCons "PersonFilter" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "personFilterEmail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Email))) ((:*:) * (S1 * (MetaSel (Just Symbol "personFilterDisplayName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe DisplayName))) (S1 * (MetaSel (Just Symbol "personFilterOrgId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe OrganizationId))))))
type ToResponse PersonFilter Source # 

data CreatePerson Source #

CreatePerson is encoded to request body JSON of Create a Person REST call.

Constructors

CreatePerson 

Fields

data UpdatePerson Source #

UpdatePerson is encoded to request body JSON of Update a Person REST call.

Constructors

UpdatePerson 

Fields

Room related types

data Room Source #

Room is communication space in Webex Teams and called "Space" on UI. Historically it was called Room on UI too but UI has been changed to "Space" in order to avoid confusion with the concept "Room" associated to hardware facility of video conferencing on Webex Teams. The name of Room is kept unchanged for backward compatibility.

Room is decoded from response JSON of Get Room Details REST call. It is also element type of response of List Rooms call.

Constructors

Room 

Fields

Instances

Eq Room Source # 

Methods

(==) :: Room -> Room -> Bool #

(/=) :: Room -> Room -> Bool #

Show Room Source # 

Methods

showsPrec :: Int -> Room -> ShowS #

show :: Room -> String #

showList :: [Room] -> ShowS #

ToJSON Room Source # 
FromJSON Room Source #

Room derives ToJSON and FromJSON via deriveJSON template haskell function.

WebexTeamsListItem Room Source #

RoomList wraps Room

Associated Types

type ToList Room :: * Source #

Methods

unwrap :: ToList Room -> [Room] Source #

type ToList Room Source # 

newtype RoomId Source #

Identifying Room.

Constructors

RoomId Text 

Instances

Eq RoomId Source # 

Methods

(==) :: RoomId -> RoomId -> Bool #

(/=) :: RoomId -> RoomId -> Bool #

Show RoomId Source # 
Generic RoomId Source # 

Associated Types

type Rep RoomId :: * -> * #

Methods

from :: RoomId -> Rep RoomId x #

to :: Rep RoomId x -> RoomId #

ToJSON RoomId Source # 
FromJSON RoomId Source # 
WebexTeamsDetail RoomId Source #

User can get detail of a room.

Methods

toIdStr :: RoomId -> Text Source #

WebexTeamsResponse RoomId Source #

Get detail for a room API uses "RoomId' and responses Room.

Associated Types

type ToResponse RoomId :: * Source #

WebexTeamsApiPath RoomId Source #

Get detail for a room API uses RoomId and path "rooms".

type Rep RoomId Source # 
type Rep RoomId = D1 * (MetaData "RoomId" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" True) (C1 * (MetaCons "RoomId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse RoomId Source # 

newtype RoomTitle Source #

Title text of Room.

Constructors

RoomTitle Text 

data RoomType Source #

RoomType indicates if the Room is for 1:1 user or group of users.

Constructors

RoomTypeDirect

The Room is for 1:1. Decoded from "direct".

RoomTypeGroup

The Room is for group. Decoded from "group".

Instances

newtype SipAddr Source #

SIP address.

Constructors

SipAddr Text 

Instances

Eq SipAddr Source # 

Methods

(==) :: SipAddr -> SipAddr -> Bool #

(/=) :: SipAddr -> SipAddr -> Bool #

Show SipAddr Source # 
Generic SipAddr Source # 

Associated Types

type Rep SipAddr :: * -> * #

Methods

from :: SipAddr -> Rep SipAddr x #

to :: Rep SipAddr x -> SipAddr #

ToJSON SipAddr Source # 
FromJSON SipAddr Source # 
type Rep SipAddr Source # 
type Rep SipAddr = D1 * (MetaData "SipAddr" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" True) (C1 * (MetaCons "SipAddr" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

newtype RoomList Source #

RoomList is decoded from response JSON of List Rooms REST call. It is list of Room.

Constructors

RoomList 

Fields

Instances

data RoomFilter Source #

Optional query strings for room list API

Constructors

RoomFilter 

Fields

Instances

Eq RoomFilter Source # 
Show RoomFilter Source # 
Generic RoomFilter Source # 

Associated Types

type Rep RoomFilter :: * -> * #

Default RoomFilter Source # 

Methods

def :: RoomFilter #

WebexTeamsFilter RoomFilter Source #

User can list rooms with filter parameter.

WebexTeamsResponse RoomFilter Source #

List rooms API uses RoomFilter and responses Room.

Associated Types

type ToResponse RoomFilter :: * Source #

WebexTeamsApiPath RoomFilter Source #

List rooms API uses RoomFilter and path "rooms".

type Rep RoomFilter Source # 
type Rep RoomFilter = D1 * (MetaData "RoomFilter" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" False) (C1 * (MetaCons "RoomFilter" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "roomFilterTeamId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TeamId))) ((:*:) * (S1 * (MetaSel (Just Symbol "roomFilterRoomType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe RoomType))) (S1 * (MetaSel (Just Symbol "roomFilterSortBy") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe RoomFilterSortBy))))))
type ToResponse RoomFilter Source # 

data CreateRoom Source #

CreateRoom is encoded to request body JSON of Create a Room REST call.

Constructors

CreateRoom 

Fields

Instances

Eq CreateRoom Source # 
Show CreateRoom Source # 
ToJSON CreateRoom Source # 
FromJSON CreateRoom Source #

CreateRoom derives ToJSON and FromJSON via deriveJSON template haskell function.

WebexTeamsCreate CreateRoom Source #

User can create a room.

WebexTeamsResponse CreateRoom Source #

Create room API uses "CreateRoom' and responses Room.

Associated Types

type ToResponse CreateRoom :: * Source #

WebexTeamsApiPath CreateRoom Source #

Create room API uses CreateRoom and path "rooms".

type ToResponse CreateRoom Source # 

newtype UpdateRoom Source #

UpdateRoom is encoded to request body JSON of Update a Room REST call.

Constructors

UpdateRoom 

Instances

Eq UpdateRoom Source # 
Show UpdateRoom Source # 
ToJSON UpdateRoom Source # 
FromJSON UpdateRoom Source #

UpdateRoom derives ToJSON and FromJSON via deriveJSON template haskell function.

WebexTeamsUpdate UpdateRoom Source #

User can update a room.

WebexTeamsResponse UpdateRoom Source #

Update room API uses "UpdateRoom' and responses Room.

Associated Types

type ToResponse UpdateRoom :: * Source #

WebexTeamsApiPath UpdateRoom Source #

Update room API uses UpdateRoom and path "rooms".

type ToResponse UpdateRoom Source # 

Membership related types

data Membership Source #

Membership is association between Room and Person. It can be N:N relation. A Person can belong to multiple Room. Membership is decoded from response JSON of Get Membership Details REST call. It is also element type of response of List Memberships call.

Constructors

Membership 

Fields

newtype MembershipId Source #

Identifying Membership.

Constructors

MembershipId Text 

Instances

Eq MembershipId Source # 
Show MembershipId Source # 
Generic MembershipId Source # 

Associated Types

type Rep MembershipId :: * -> * #

ToJSON MembershipId Source # 
FromJSON MembershipId Source # 
WebexTeamsDetail MembershipId Source #

User can get detail of a membership.

WebexTeamsResponse MembershipId Source #

Get detail for a membership API uses "MembershipId' and responses Membership.

Associated Types

type ToResponse MembershipId :: * Source #

WebexTeamsApiPath MembershipId Source #

Get detail for a membership API uses MembershipId and path "memberships".

type Rep MembershipId Source # 
type Rep MembershipId = D1 * (MetaData "MembershipId" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" True) (C1 * (MetaCons "MembershipId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse MembershipId Source # 

data MembershipFilter Source #

Optional query strings for room membership list API

Constructors

MembershipFilter 

Fields

Instances

Eq MembershipFilter Source # 
Show MembershipFilter Source # 
Generic MembershipFilter Source # 
Default MembershipFilter Source # 
WebexTeamsFilter MembershipFilter Source #

User can list memberships with filter parameter.

WebexTeamsResponse MembershipFilter Source #

List memberships API uses MembershipFilter and responses Membership.

Associated Types

type ToResponse MembershipFilter :: * Source #

WebexTeamsApiPath MembershipFilter Source #

List memberships API uses MembershipFilter and path "memberships".

type Rep MembershipFilter Source # 
type Rep MembershipFilter = D1 * (MetaData "MembershipFilter" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" False) (C1 * (MetaCons "MembershipFilter" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "membershipFilterRoomId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe RoomId))) ((:*:) * (S1 * (MetaSel (Just Symbol "membershipFilterPersonId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PersonId))) (S1 * (MetaSel (Just Symbol "membershipFilterPersonEmail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Email))))))
type ToResponse MembershipFilter Source # 

data CreateMembership Source #

CreateMembership is encoded to request body JSON of Create a Membership REST call.

Constructors

CreateMembership 

Fields

Message related types

data Message Source #

Message is a message posted to a Room by some Person. Room is decoded from response JSON of Get Message Details REST call. It is also element type of response of List Messages call.

Constructors

Message 

Fields

newtype MessageId Source #

Identifying Message.

Constructors

MessageId Text 

Instances

Eq MessageId Source # 
Show MessageId Source # 
Generic MessageId Source # 

Associated Types

type Rep MessageId :: * -> * #

ToJSON MessageId Source # 
FromJSON MessageId Source # 
WebexTeamsDetail MessageId Source #

User can get detail of a message.

WebexTeamsResponse MessageId Source #

Get detail for a message API uses "MessageId' and responses Message.

Associated Types

type ToResponse MessageId :: * Source #

WebexTeamsApiPath MessageId Source #

Get detail for message API uses MessageId and path "messages".

type Rep MessageId Source # 
type Rep MessageId = D1 * (MetaData "MessageId" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" True) (C1 * (MetaCons "MessageId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse MessageId Source # 

newtype FileUrl Source #

URL pointing attached file of message.

Constructors

FileUrl Text 

Instances

Eq FileUrl Source # 

Methods

(==) :: FileUrl -> FileUrl -> Bool #

(/=) :: FileUrl -> FileUrl -> Bool #

Show FileUrl Source # 
Generic FileUrl Source # 

Associated Types

type Rep FileUrl :: * -> * #

Methods

from :: FileUrl -> Rep FileUrl x #

to :: Rep FileUrl x -> FileUrl #

ToJSON FileUrl Source # 
FromJSON FileUrl Source # 
type Rep FileUrl Source # 
type Rep FileUrl = D1 * (MetaData "FileUrl" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" True) (C1 * (MetaCons "FileUrl" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

newtype MessageList Source #

MessageList is decoded from response JSON of List Messages REST call. It is list of Message.

Constructors

MessageList 

data MessageFilter Source #

Optional query strings for message list API

Constructors

MessageFilter 

Fields

data CreateMessage Source #

CreateMessage is encoded to request body JSON of Create a Message REST call.

Constructors

CreateMessage 

Fields

Team related types

newtype TeamName Source #

Name of Team

Constructors

TeamName Text 

Instances

newtype TeamId Source #

Identifying Team.

Constructors

TeamId Text 

Instances

Eq TeamId Source # 

Methods

(==) :: TeamId -> TeamId -> Bool #

(/=) :: TeamId -> TeamId -> Bool #

Show TeamId Source # 
Generic TeamId Source # 

Associated Types

type Rep TeamId :: * -> * #

Methods

from :: TeamId -> Rep TeamId x #

to :: Rep TeamId x -> TeamId #

ToJSON TeamId Source # 
FromJSON TeamId Source # 
WebexTeamsDetail TeamId Source #

User can get detail of a team.

Methods

toIdStr :: TeamId -> Text Source #

WebexTeamsResponse TeamId Source #

Get detail for a team API uses "TeamId' and responses Team.

Associated Types

type ToResponse TeamId :: * Source #

WebexTeamsApiPath TeamId Source #

Get detail for a team API uses TeamId and path "teams".

type Rep TeamId Source # 
type Rep TeamId = D1 * (MetaData "TeamId" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" True) (C1 * (MetaCons "TeamId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse TeamId Source # 

data Team Source #

Team is group of Person and group of Room. A Person can belong to multiple Team but a Room can belong to at most one Team. Team is decoded from response JSON of Get Team Details REST call. It is also element type of response of List Teams call.

Constructors

Team 

Fields

Instances

Eq Team Source # 

Methods

(==) :: Team -> Team -> Bool #

(/=) :: Team -> Team -> Bool #

Show Team Source # 

Methods

showsPrec :: Int -> Team -> ShowS #

show :: Team -> String #

showList :: [Team] -> ShowS #

ToJSON Team Source # 
FromJSON Team Source #

Team derives ToJSON and FromJSON via deriveJSON template haskell function.

WebexTeamsListItem Team Source #

TeamList wraps Team

Associated Types

type ToList Team :: * Source #

Methods

unwrap :: ToList Team -> [Team] Source #

type ToList Team Source # 

newtype TeamList Source #

TeamList is decoded from response JSON of List Teams REST call. It is list of Team.

Constructors

TeamList 

Fields

Instances

newtype CreateTeam Source #

CreateTeam is encoded to request body JSON of Create a Team REST call.

Constructors

CreateTeam 

Instances

Eq CreateTeam Source # 
Show CreateTeam Source # 
ToJSON CreateTeam Source # 
FromJSON CreateTeam Source #

CreateTeam derives ToJSON and FromJSON via deriveJSON template haskell function.

WebexTeamsCreate CreateTeam Source #

User can create a team.

WebexTeamsResponse CreateTeam Source #

Create team API uses "CreateTeam' and responses Team.

Associated Types

type ToResponse CreateTeam :: * Source #

WebexTeamsApiPath CreateTeam Source #

Create team API uses CreateTeam and path "teams".

type ToResponse CreateTeam Source # 

newtype UpdateTeam Source #

UpdateTeam is encoded to request body JSON of Update a Team REST call.

Constructors

UpdateTeam 

Instances

Eq UpdateTeam Source # 
Show UpdateTeam Source # 
ToJSON UpdateTeam Source # 
FromJSON UpdateTeam Source #

UpdateTeam derives ToJSON and FromJSON via deriveJSON template haskell function.

WebexTeamsUpdate UpdateTeam Source #

User can update a team.

WebexTeamsResponse UpdateTeam Source #

Update team API uses "UpdateTeam' and responses Team.

Associated Types

type ToResponse UpdateTeam :: * Source #

WebexTeamsApiPath UpdateTeam Source #

Update team API uses UpdateTeam and path "teams".

type ToResponse UpdateTeam Source # 

Team Membership related types

data TeamMembership Source #

TeamMembership is association between Team and Person. It can be N:N relation. A Person can belong to multiple Team. TeamMembership is decoded from response JSON of Get Team Membership Details REST call. It is also element type of response of List Team Memberships call.

Constructors

TeamMembership 

Fields

newtype TeamMembershipId Source #

Identifying TeamMembership.

Constructors

TeamMembershipId Text 

Instances

Eq TeamMembershipId Source # 
Show TeamMembershipId Source # 
Generic TeamMembershipId Source # 
ToJSON TeamMembershipId Source # 
FromJSON TeamMembershipId Source # 
WebexTeamsDetail TeamMembershipId Source #

User can get detail of a team membership.

WebexTeamsResponse TeamMembershipId Source #

Get detail for a team membership API uses "TeamMembershipId' and responses TeamMembership.

Associated Types

type ToResponse TeamMembershipId :: * Source #

WebexTeamsApiPath TeamMembershipId Source #

Get detail for a team membership API uses TeamMembershipId and path "team/memberships".

type Rep TeamMembershipId Source # 
type Rep TeamMembershipId = D1 * (MetaData "TeamMembershipId" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" True) (C1 * (MetaCons "TeamMembershipId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse TeamMembershipId Source # 

data CreateTeamMembership Source #

CreateTeamMembership is encoded to request body JSON of Create a Team Membership REST call.

Constructors

CreateTeamMembership 

Fields

newtype UpdateTeamMembership Source #

UpdateTeamMembership is encoded to request body JSON of Update a Team Membership REST call.

Organization related types

data Organization Source #

Organization is an administrative group of Webex Teams users. Each Person belongs to one Organization. Organization is decoded from response JSON of Get Organization Details REST call. It is also element type of response of List Organizations call.

Constructors

Organization 

Fields

newtype OrganizationId Source #

Organization identifier which user or team belongs to.

Constructors

OrganizationId Text 

Instances

Eq OrganizationId Source # 
Show OrganizationId Source # 
Generic OrganizationId Source # 

Associated Types

type Rep OrganizationId :: * -> * #

ToJSON OrganizationId Source # 
FromJSON OrganizationId Source # 
WebexTeamsDetail OrganizationId Source #

User can get detail of a organization.

WebexTeamsResponse OrganizationId Source #

Get detail for a organization API uses "OrganizationId' and responses Organization.

Associated Types

type ToResponse OrganizationId :: * Source #

WebexTeamsApiPath OrganizationId Source #

Get detail for organization API uses OrganizationId and path "organizations".

type Rep OrganizationId Source # 
type Rep OrganizationId = D1 * (MetaData "OrganizationId" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" True) (C1 * (MetaCons "OrganizationId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse OrganizationId Source # 

newtype OrganizationDisplayName Source #

Display name of Organization

License related types

data License Source #

License is allowance for features and services of Webex Teams subscription. License is decoded from response JSON of Get License Details REST call. It is also element type of response of List Licenses call.

Constructors

License 

Fields

newtype LicenseId Source #

License identifier which can be enabled on user. See License too.

Constructors

LicenseId Text 

Instances

Eq LicenseId Source # 
Show LicenseId Source # 
Generic LicenseId Source # 

Associated Types

type Rep LicenseId :: * -> * #

ToJSON LicenseId Source # 
FromJSON LicenseId Source # 
WebexTeamsDetail LicenseId Source #

User can get detail of a license.

WebexTeamsResponse LicenseId Source #

Get detail for a license API uses "LicenseId' and responses License.

Associated Types

type ToResponse LicenseId :: * Source #

WebexTeamsApiPath LicenseId Source #

Get detail for license API uses LicenseId and path "licenses".

type Rep LicenseId Source # 
type Rep LicenseId = D1 * (MetaData "LicenseId" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" True) (C1 * (MetaCons "LicenseId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse LicenseId Source # 

newtype LicenseUnit Source #

Counting number of granted or consumed License

Constructors

LicenseUnit Integer 

newtype LicenseList Source #

LicenseList is decoded from response JSON of List Licenses REST call. It is list of License.

Constructors

LicenseList 

newtype LicenseFilter Source #

Optional query strings for license list API

Constructors

LicenseFilter 

Fields

Instances

Eq LicenseFilter Source # 
Show LicenseFilter Source # 
Generic LicenseFilter Source # 

Associated Types

type Rep LicenseFilter :: * -> * #

Default LicenseFilter Source # 

Methods

def :: LicenseFilter #

WebexTeamsFilter LicenseFilter Source #

User can list licenses with filter parameter.

WebexTeamsResponse LicenseFilter Source #

List licenses API uses LicenseFilter and responses License.

Associated Types

type ToResponse LicenseFilter :: * Source #

WebexTeamsApiPath LicenseFilter Source #

List licenses API uses LicenseFilter and path "licenses".

type Rep LicenseFilter Source # 
type Rep LicenseFilter = D1 * (MetaData "LicenseFilter" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" True) (C1 * (MetaCons "LicenseFilter" PrefixI True) (S1 * (MetaSel (Just Symbol "licenseFilterOrgId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe OrganizationId))))
type ToResponse LicenseFilter Source # 

Role related types

data Role Source #

A persona for an authenticated user, corresponding to a set of privileges within an organization. Role is decoded from response JSON of Get Role Details REST call. It is also element type of response of List Roles call.

Constructors

Role 

Fields

Instances

Eq Role Source # 

Methods

(==) :: Role -> Role -> Bool #

(/=) :: Role -> Role -> Bool #

Show Role Source # 

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

ToJSON Role Source # 
FromJSON Role Source #

Role derives ToJSON and FromJSON via deriveJSON template haskell function.

WebexTeamsListItem Role Source #

RoleList wraps Role

Associated Types

type ToList Role :: * Source #

Methods

unwrap :: ToList Role -> [Role] Source #

type ToList Role Source # 

newtype RoleId Source #

Role identifier which can be assigned to user. See Role too.

Constructors

RoleId Text 

Instances

Eq RoleId Source # 

Methods

(==) :: RoleId -> RoleId -> Bool #

(/=) :: RoleId -> RoleId -> Bool #

Show RoleId Source # 
Generic RoleId Source # 

Associated Types

type Rep RoleId :: * -> * #

Methods

from :: RoleId -> Rep RoleId x #

to :: Rep RoleId x -> RoleId #

ToJSON RoleId Source # 
FromJSON RoleId Source # 
WebexTeamsDetail RoleId Source #

User can get detail of a role.

Methods

toIdStr :: RoleId -> Text Source #

WebexTeamsResponse RoleId Source #

Get detail for a role API uses "RoleId' and responses Role.

Associated Types

type ToResponse RoleId :: * Source #

WebexTeamsApiPath RoleId Source #

Get detail for role API uses RoleId and path "roles".

type Rep RoleId Source # 
type Rep RoleId = D1 * (MetaData "RoleId" "Network.WebexTeams.Types" "webex-teams-api-0.2.0.0-7FTz8ity16Y8LjICwKwblT" True) (C1 * (MetaCons "RoleId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse RoleId Source # 

newtype RoleName Source #

Name of Role.

Constructors

RoleName Text 

Instances

newtype RoleList Source #

RoleList is decoded from response JSON of List Role REST call. It is list of Role.

Constructors

RoleList 

Fields

Instances

Functions

Getting detail of an entity

getDetail Source #

Arguments

:: (MonadIO m, WebexTeamsDetail key) 
=> Authorization

Authorization string against Webex Teams API.

-> WebexTeamsRequest

Predefined part of Request commonly used for Webex Teams API.

-> key

One of PersonId, RoomId, MembershipId, MessageId, TeamId, TeamMembershipId, OrganizationId, LicenseId and RoleId.

-> m (Response (ToResponse key)) 

Get details of a Webex Teams entity.

Obtaining detail of an entity identified by key. The key can be a value in one of following types: PersonId, RoomId, MembershipId, MessageId, TeamId, TeamMembershipId, OrganizationId, LicenseId, RoleId. API is automatically selected by type of the key. A JSONException runtime exception will be thrown on an JSON parse errors.

getDetailEither :: (MonadIO m, WebexTeamsDetail key) => Authorization -> WebexTeamsRequest -> key -> m (Response (Either JSONException (ToResponse key))) Source #

Get details of a Webex Teams entity. A Left value will be returned on an JSON parse errors.

Streaming response of List API with auto pagenation

type ListReader a = IO [a] Source #

ListReader is IO action returned by functions for list API (getListWithFilter, getTeamList etc). It is containing URL inside to be accessed. When you call the IO action, it accesses to Webex Teams REST API, parse next page URL if available, then return new IO action. The new IO action contains list of responded items and new URL for next page so you can call the new IO action to get the next page.

Following example demonstrates how you can get all items into single list.

    readAllList :: ListReader i -> IO [i]
    readAllList reader = go []
      where
        go xs = reader >>= chunk -> case chunk of
            [] -> pure xs
            ys -> go (xs <> ys)

Note that this example is only for explaining how ListReader works. Practically you should not do the above because it eagerly creates entire list. You should use streaming APIs instead. Streaming APIs are available via webex-teams-conduit and webex-teams-pipes package.

getListWithFilter :: (MonadIO m, WebexTeamsFilter filter, WebexTeamsListItem (ToResponse filter)) => Authorization -> WebexTeamsRequest -> filter -> m (ListReader (ToResponse filter)) Source #

Get list with query parameter.

streamEntityWithFilter :: (MonadIO m, WebexTeamsFilter filter, WebexTeamsListItem (ToResponse filter)) => Authorization -> WebexTeamsRequest -> filter -> ConduitT () (ToResponse filter) m () Source #

Deprecated: Use getListWithFilter or streamListWithFilter of webex-teams-conduit

Get list of entities with query parameter and stream it into Conduit pipe. It automatically performs pagination.

streamTeamList :: MonadIO m => Authorization -> WebexTeamsRequest -> ConduitT () Team m () Source #

Deprecated: Use getTeamList or streamTeamList of webex-teams-conduit

List of Team and stream it into Conduit pipe. It automatically performs pagination.

streamOrganizationList :: MonadIO m => Authorization -> WebexTeamsRequest -> ConduitT () Organization m () Source #

Deprecated: Use getOrganizationList or streamOrganizationList of webex-teams-conduit

Filter list of Organization and stream it into Conduit pipe. It automatically performs pagination.

streamRoleList :: MonadIO m => Authorization -> WebexTeamsRequest -> ConduitT () Role m () Source #

Deprecated: Use getRoleList or streamRoleList of webex-teams-conduit

List of Role and stream it into Conduit pipe. It automatically performs pagination.

Creating an entity

createEntity Source #

Arguments

:: (MonadIO m, WebexTeamsCreate createParams) 
=> Authorization

Authorization string against Webex Teams API.

-> WebexTeamsRequest

Predefined part of Request commonly used for Webex Teams API.

-> createParams

One of CreatePerson, CreateRoom, CreateMembership, CreateMessage, CreateTeam and CreateTeamMembership.

-> m (Response (ToResponse createParams)) 

Create a Webex Teams entity with given parameters.

Creating a new entity of Webex Teams such as space, team, membership or message. REST API path is automatically selected by type of createParams. A JSONException runtime exception will be thrown on an JSON parse errors.

createEntityEither :: (MonadIO m, WebexTeamsCreate createParams) => Authorization -> WebexTeamsRequest -> createParams -> m (Response (Either JSONException (ToResponse createParams))) Source #

Create a Webex Teams entity with given parameters. A Left value will be returned on an JSON parse errors.

Updating an entity

updateEntity Source #

Arguments

:: (MonadIO m, WebexTeamsUpdate updateParams) 
=> Authorization

Authorization string against Webex Teams API.

-> WebexTeamsRequest

Predefined part of Request commonly used for Webex Teams API.

-> updateParams

One of UpdatePerson, UpdateRoom, UpdateMembership, UpdateTeam and UpdateTeamMembership.

-> m (Response (ToResponse updateParams)) 

Update a Webex Teams entity with given parameters.

Creating a new entity of Webex Teams such as space, team, or membership. REST API path is automatically selected by type of updateParams. A JSONException runtime exception will be thrown on an JSON parse errors.

updateEntityEither :: (MonadIO m, WebexTeamsUpdate updateParams) => Authorization -> WebexTeamsRequest -> updateParams -> m (Response (Either JSONException (ToResponse updateParams))) Source #

Update a Webex Teams entity with given parameters. A Left value will be returned on an JSON parse errors.

Creating default filter spec from mandatory field

defaultMessageFilter :: RoomId -> MessageFilter Source #

Default value of query strings for message list API. Because RoomId is mandatory, user have to supply it in order to get rest of defaults.

defaultTeamMembershipFilter :: TeamId -> TeamMembershipFilter Source #

Default value of query strings for team membership list API. Because TeamId is mandatory, user have to supply it in order to get rest of defaults. As of writing, there is no filter parameter other than TeamId but TeamMembershipFilter is used for providing consistent API like streamEntityWithFilter.

Deleting an entity

deleteRoom Source #

Arguments

:: MonadIO m 
=> Authorization

Authorization string against Webex Teams API.

-> WebexTeamsRequest

Predefined part of Request commonly used for Webex Teams API.

-> RoomId

Identifier of a space to be deleted.

-> m (Response ()) 

Deletes a room, by ID.

deleteMembership Source #

Arguments

:: MonadIO m 
=> Authorization

Authorization string against Webex Teams API.

-> WebexTeamsRequest

Predefined part of Request commonly used for Webex Teams API.

-> MembershipId

Identifier of a space to be deleted.

-> m (Response ()) 

Deletes a membership, by ID.

deleteMessage Source #

Arguments

:: MonadIO m 
=> Authorization

Authorization string against Webex Teams API.

-> WebexTeamsRequest

Predefined part of Request commonly used for Webex Teams API.

-> MessageId

Identifier of a space to be deleted.

-> m (Response ()) 

Deletes a message, by ID.

deleteTeam Source #

Arguments

:: MonadIO m 
=> Authorization

Authorization string against Webex Teams API.

-> WebexTeamsRequest

Predefined part of Request commonly used for Webex Teams API.

-> TeamId

Identifier of a space to be deleted.

-> m (Response ()) 

Deletes a team, by ID.

deleteTeamMembership Source #

Arguments

:: MonadIO m 
=> Authorization

Authorization string against Webex Teams API.

-> WebexTeamsRequest

Predefined part of Request commonly used for Webex Teams API.

-> TeamMembershipId

Identifier of a space to be deleted.

-> m (Response ()) 

Deletes a teamMembership, by ID.