cisco-spark-api-0.1.0.2: A Haskell bindings for Cisco Spark API

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

Network.CiscoSpark.Types

Description

This module defines most of types and records used in cisco-spark-api package. Records used for REST communications are designed to be converted from / to JSON using Aeson package. Those records are also 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 doesn't pre-generate those lenses for you because it is so easy. Please create them by yourself as needed.

Synopsis

Documentation

peoplePath :: ByteString Source #

URL path for people API.

roomsPath :: ByteString Source #

URL path for rooms API.

membershipsPath :: ByteString Source #

URL path for memberships API.

messagesPath :: ByteString Source #

URL path for messages API.

teamsPath :: ByteString Source #

URL path for teams API.

teamMembershipsPath :: ByteString Source #

URL path for team memberships API.

organizationsPath :: ByteString Source #

URL path for organizations API.

licensesPath :: ByteString Source #

URL path for licenes API.

rolesPath :: ByteString Source #

URL path for roles API.

webhooksPath :: ByteString Source #

URL path for webhooks API.

class FromJSON (ToList i) => SparkListItem i where Source #

SparkListItem 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.

SparkListItem 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

Associated Types

type ToList i :: * Source #

Associate item type to wrapping list type.

Methods

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

Get bare list from wrapped type which can be parsed directly from JSON.

Instances

SparkListItem Person Source #

PersonList wraps Person.

Associated Types

type ToList Person :: * Source #

SparkListItem Team Source #

TeamList wraps Team

Associated Types

type ToList Team :: * Source #

Methods

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

SparkListItem TeamMembership Source #

TeamMembershipList wraps TeamMembership

SparkListItem Room Source #

RoomList wraps Room

Associated Types

type ToList Room :: * Source #

Methods

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

SparkListItem Membership Source #

MembershipList wraps Membership

Associated Types

type ToList Membership :: * Source #

SparkListItem Message Source #

MessageList wraps Message

Associated Types

type ToList Message :: * Source #

SparkListItem Organization Source #

OrganizationList wraps Organization

Associated Types

type ToList Organization :: * Source #

SparkListItem License Source #

LicenseList wraps License

Associated Types

type ToList License :: * Source #

SparkListItem Role Source #

RoleList wraps Role

Associated Types

type ToList Role :: * Source #

Methods

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

SparkListItem Webhook Source #

WebhookList wraps Webhook

Associated Types

type ToList Webhook :: * Source #

class SparkApiPath a where Source #

Type class for getting URL path of API category from given type of value.

Minimal complete definition

apiPath

Methods

apiPath :: a -> ByteString Source #

Instances

SparkApiPath LicenseId Source #

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

SparkApiPath RoleId Source #

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

SparkApiPath OrganizationId Source #

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

SparkApiPath PersonId Source #

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

SparkApiPath CreatePerson Source #

Create person API uses CreatePerson and path "people".

SparkApiPath PersonFilter Source #

List people API uses PersonFilter and path "people".

SparkApiPath UpdatePerson Source #

Update person API uses UpdatePerson and path "people".

SparkApiPath TeamId Source #

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

SparkApiPath CreateTeam Source #

Create team API uses CreateTeam and path "teams".

SparkApiPath UpdateTeam Source #

Update team API uses UpdateTeam and path "teams".

SparkApiPath TeamMembershipId Source #

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

SparkApiPath CreateTeamMembership Source #

Create teamMembership API uses CreateTeamMembership and path "team/memberships".

SparkApiPath TeamMembershipFilter Source #

List team memberships API uses TeamMembershipFilter and path "team/memberships".

SparkApiPath UpdateTeamMembership Source #

Update teamMembership API uses UpdateTeamMembership and path "team/memberships".

SparkApiPath RoomId Source #

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

SparkApiPath CreateRoom Source #

Create room API uses CreateRoom and path "rooms".

SparkApiPath RoomFilter Source #

List rooms API uses RoomFilter and path "rooms".

SparkApiPath UpdateRoom Source #

Update room API uses UpdateRoom and path "rooms".

SparkApiPath MembershipId Source #

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

SparkApiPath CreateMembership Source #

Create membership API uses CreateMembership and path "memberships".

SparkApiPath MembershipFilter Source #

List memberships API uses MembershipFilter and path "memberships".

SparkApiPath UpdateMembership Source #

Update membership API uses UpdateMembership and path "memberships".

SparkApiPath MessageId Source #

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

SparkApiPath CreateMessage Source #

Create message API uses CreateMessage and path "messages".

SparkApiPath MessageFilter Source #

List messages API uses MessageFilter and path "messages".

SparkApiPath LicenseFilter Source #

List licenses API uses LicenseFilter and path "licenses".

SparkApiPath WebhookId Source #

Get detail for webhook API uses WebhookId and path "webhooks".

SparkApiPath CreateWebhook Source #

Create webhook API uses CreateWebhook and path "webhooks".

SparkApiPath UpdateWebhook Source #

Update webhook API uses UpdateWebhook and path "webhooks".

SparkApiPath WebhookRoomFilter Source #

Create webhook API accepts WebhookRoomFilter and uses path "webhooks".

SparkApiPath WebhookMessageFilter Source #

Create webhook API accepts WebhookMessageFilter and uses path "webhooks".

SparkApiPath WebhookMembershipFilter Source #

Create webhook API accepts WebhookMembershipFilter and uses path "webhooks".

class FromJSON (ToResponse a) => SparkResponse a Source #

Type family to associate a type appears in an argument to response type.

Associated Types

type ToResponse a :: * Source #

Instances

SparkResponse LicenseId Source #

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

Associated Types

type ToResponse LicenseId :: * Source #

SparkResponse RoleId Source #

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

Associated Types

type ToResponse RoleId :: * Source #

SparkResponse OrganizationId Source #

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

Associated Types

type ToResponse OrganizationId :: * Source #

SparkResponse PersonId Source #

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

Associated Types

type ToResponse PersonId :: * Source #

SparkResponse CreatePerson Source #

Create person API uses "CreatePerson' and responses Person.

Associated Types

type ToResponse CreatePerson :: * Source #

SparkResponse PersonFilter Source #

List people API uses PersonFilter and responses Person.

Associated Types

type ToResponse PersonFilter :: * Source #

SparkResponse UpdatePerson Source #

Update person API uses "UpdatePerson' and responses Person.

Associated Types

type ToResponse UpdatePerson :: * Source #

SparkResponse TeamId Source #

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

Associated Types

type ToResponse TeamId :: * Source #

SparkResponse CreateTeam Source #

Create team API uses "CreateTeam' and responses Team.

Associated Types

type ToResponse CreateTeam :: * Source #

SparkResponse UpdateTeam Source #

Update team API uses "UpdateTeam' and responses Team.

Associated Types

type ToResponse UpdateTeam :: * Source #

SparkResponse TeamMembershipId Source #

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

Associated Types

type ToResponse TeamMembershipId :: * Source #

SparkResponse CreateTeamMembership Source #

Create teamMembership API uses "CreateTeamMembership' and responses TeamMembership.

Associated Types

type ToResponse CreateTeamMembership :: * Source #

SparkResponse TeamMembershipFilter Source #

List team memberships API uses TeamMembershipFilter and responses TeamMembership.

Associated Types

type ToResponse TeamMembershipFilter :: * Source #

SparkResponse UpdateTeamMembership Source #

Update teamMembership API uses "UpdateTeamMembership' and responses TeamMembership.

Associated Types

type ToResponse UpdateTeamMembership :: * Source #

SparkResponse RoomId Source #

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

Associated Types

type ToResponse RoomId :: * Source #

SparkResponse CreateRoom Source #

Create room API uses "CreateRoom' and responses Room.

Associated Types

type ToResponse CreateRoom :: * Source #

SparkResponse RoomFilter Source #

List rooms API uses RoomFilter and responses Room.

Associated Types

type ToResponse RoomFilter :: * Source #

SparkResponse UpdateRoom Source #

Update room API uses "UpdateRoom' and responses Room.

Associated Types

type ToResponse UpdateRoom :: * Source #

SparkResponse MembershipId Source #

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

Associated Types

type ToResponse MembershipId :: * Source #

SparkResponse CreateMembership Source #

Create membership API uses "CreateMembership' and responses Membership.

Associated Types

type ToResponse CreateMembership :: * Source #

SparkResponse MembershipFilter Source #

List memberships API uses MembershipFilter and responses Membership.

Associated Types

type ToResponse MembershipFilter :: * Source #

SparkResponse UpdateMembership Source #

Update membership API uses "UpdateMembership' and responses Membership.

Associated Types

type ToResponse UpdateMembership :: * Source #

SparkResponse MessageId Source #

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

Associated Types

type ToResponse MessageId :: * Source #

SparkResponse CreateMessage Source #

Create message API uses "CreateMessage' and responses Message.

Associated Types

type ToResponse CreateMessage :: * Source #

SparkResponse MessageFilter Source #

List messages API uses MessageFilter and responses Message.

Associated Types

type ToResponse MessageFilter :: * Source #

SparkResponse LicenseFilter Source #

List licenses API uses LicenseFilter and responses License.

Associated Types

type ToResponse LicenseFilter :: * Source #

SparkResponse WebhookId Source #

Get detail for a webhook API uses "WebhookId' and responses Webhook.

Associated Types

type ToResponse WebhookId :: * Source #

SparkResponse CreateWebhook Source #

Create webhook API uses "CreateWebhook' and responses Webhook.

Associated Types

type ToResponse CreateWebhook :: * Source #

SparkResponse UpdateWebhook Source #

Update webhook API uses "UpdateWebhook' and responses Webhook.

Associated Types

type ToResponse UpdateWebhook :: * Source #

SparkResponse WebhookRoomFilter Source #

List team memberships API accepts WebhookRoomFilter and responses Webhook.

Associated Types

type ToResponse WebhookRoomFilter :: * Source #

SparkResponse WebhookMessageFilter Source #

List team memberships API accepts WebhookMessageFilter and responses Webhook.

Associated Types

type ToResponse WebhookMessageFilter :: * Source #

SparkResponse WebhookMembershipFilter Source #

List team memberships API accepts WebhookMembershipFilter and responses Webhook.

Associated Types

type ToResponse WebhookMembershipFilter :: * Source #

class (SparkApiPath a, SparkResponse a) => SparkDetail a where Source #

Extract containing entity ID string from given type of value.

Minimal complete definition

toIdStr

Methods

toIdStr :: a -> Text Source #

Instances

SparkDetail LicenseId Source #

User can get detail of a license.

SparkDetail RoleId Source #

User can get detail of a role.

Methods

toIdStr :: RoleId -> Text Source #

SparkDetail OrganizationId Source #

User can get detail of a organization.

SparkDetail PersonId Source #

User can get detail of a person.

SparkDetail TeamId Source #

User can get detail of a team.

Methods

toIdStr :: TeamId -> Text Source #

SparkDetail TeamMembershipId Source #

User can get detail of a team membership.

SparkDetail RoomId Source #

User can get detail of a room.

Methods

toIdStr :: RoomId -> Text Source #

SparkDetail MembershipId Source #

User can get detail of a membership.

SparkDetail MessageId Source #

User can get detail of a message.

SparkDetail WebhookId Source #

User can get detail of a webhook.

class (SparkApiPath a, SparkResponse a) => SparkFilter a where Source #

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

Minimal complete definition

toFilterList

Instances

SparkFilter PersonFilter Source #

User can list people with filter parameter.

SparkFilter TeamMembershipFilter Source #

User can list team membership with filter parameter.

SparkFilter RoomFilter Source #

User can list rooms with filter parameter.

SparkFilter MembershipFilter Source #

User can list memberships with filter parameter.

SparkFilter MessageFilter Source #

User can list messages with filter parameter.

SparkFilter LicenseFilter Source #

User can list licenses with filter parameter.

SparkFilter WebhookRoomFilter Source #

User can filter Webhook events from room.

SparkFilter WebhookMessageFilter Source #

User can filter Webhook events from message.

SparkFilter WebhookMembershipFilter Source #

User can filter Webhook events from membership.

class (SparkApiPath a, SparkResponse a, ToJSON a) => SparkCreate a Source #

Type class for parameter type for create entity API.

Instances

SparkCreate CreatePerson Source #

User can create a person.

SparkCreate CreateTeam Source #

User can create a team.

SparkCreate CreateTeamMembership Source #

User can create a teamMembership.

SparkCreate CreateRoom Source #

User can create a room.

SparkCreate CreateMembership Source #

User can create a membership.

SparkCreate CreateMessage Source #

User can create a message.

SparkCreate CreateWebhook Source #

User can create a webhook.

class (SparkApiPath a, SparkResponse a, ToJSON a) => SparkUpdate a Source #

Type class for parameter type for update entity API.

Instances

SparkUpdate UpdatePerson Source #

User can update a person.

SparkUpdate UpdateTeam Source #

User can update a team.

SparkUpdate UpdateTeamMembership Source #

User can update a teamMembership.

SparkUpdate UpdateRoom Source #

User can update a room.

SparkUpdate UpdateMembership Source #

User can update a membership.

SparkUpdate UpdateWebhook Source #

User can update a webhook.

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.

newtype PersonId Source #

Identifying Person describing detail of Cisco Spark 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 # 
SparkDetail PersonId Source #

User can get detail of a person.

SparkResponse PersonId Source #

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

Associated Types

type ToResponse PersonId :: * Source #

SparkApiPath PersonId Source #

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

type Rep PersonId Source # 
type Rep PersonId = D1 * (MetaData "PersonId" "Network.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" 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.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" 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 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 # 
SparkDetail OrganizationId Source #

User can get detail of a organization.

SparkResponse OrganizationId Source #

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

Associated Types

type ToResponse OrganizationId :: * Source #

SparkApiPath OrganizationId Source #

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

type Rep OrganizationId Source # 
type Rep OrganizationId = D1 * (MetaData "OrganizationId" "Network.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" True) (C1 * (MetaCons "OrganizationId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse OrganizationId 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 # 
SparkDetail RoleId Source #

User can get detail of a role.

Methods

toIdStr :: RoleId -> Text Source #

SparkResponse RoleId Source #

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

Associated Types

type ToResponse RoleId :: * Source #

SparkApiPath RoleId Source #

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

type Rep RoleId Source # 
type Rep RoleId = D1 * (MetaData "RoleId" "Network.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" True) (C1 * (MetaCons "RoleId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse RoleId Source # 

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 # 
SparkDetail LicenseId Source #

User can get detail of a license.

SparkResponse LicenseId Source #

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

Associated Types

type ToResponse LicenseId :: * Source #

SparkApiPath LicenseId Source #

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

type Rep LicenseId Source # 
type Rep LicenseId = D1 * (MetaData "LicenseId" "Network.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" True) (C1 * (MetaCons "LicenseId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse LicenseId Source # 

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.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" 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".

data Person Source #

Person is detail description of Cisco Spark 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.

SparkListItem Person Source #

PersonList wraps Person.

Associated Types

type ToList Person :: * Source #

type ToList Person Source # 

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 #

SparkFilter PersonFilter Source #

User can list people with filter parameter.

SparkResponse PersonFilter Source #

List people API uses PersonFilter and responses Person.

Associated Types

type ToResponse PersonFilter :: * Source #

SparkApiPath PersonFilter Source #

List people API uses PersonFilter and path "people".

type Rep PersonFilter Source # 
type Rep PersonFilter = D1 * (MetaData "PersonFilter" "Network.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" 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

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 # 
SparkDetail TeamId Source #

User can get detail of a team.

Methods

toIdStr :: TeamId -> Text Source #

SparkResponse TeamId Source #

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

Associated Types

type ToResponse TeamId :: * Source #

SparkApiPath TeamId Source #

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

type Rep TeamId Source # 
type Rep TeamId = D1 * (MetaData "TeamId" "Network.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" True) (C1 * (MetaCons "TeamId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse TeamId Source # 

newtype TeamName Source #

Name of Team

Constructors

TeamName Text 

Instances

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.

SparkListItem 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.

SparkCreate CreateTeam Source #

User can create a team.

SparkResponse CreateTeam Source #

Create team API uses "CreateTeam' and responses Team.

Associated Types

type ToResponse CreateTeam :: * Source #

SparkApiPath 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.

SparkUpdate UpdateTeam Source #

User can update a team.

SparkResponse UpdateTeam Source #

Update team API uses "UpdateTeam' and responses Team.

Associated Types

type ToResponse UpdateTeam :: * Source #

SparkApiPath UpdateTeam Source #

Update team API uses UpdateTeam and path "teams".

type ToResponse UpdateTeam Source # 

newtype TeamMembershipId Source #

Identifying TeamMembership.

Constructors

TeamMembershipId Text 

Instances

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

User can get detail of a team membership.

SparkResponse TeamMembershipId Source #

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

Associated Types

type ToResponse TeamMembershipId :: * Source #

SparkApiPath 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.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" True) (C1 * (MetaCons "TeamMembershipId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse TeamMembershipId Source # 

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

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.

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.

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 # 
SparkDetail RoomId Source #

User can get detail of a room.

Methods

toIdStr :: RoomId -> Text Source #

SparkResponse RoomId Source #

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

Associated Types

type ToResponse RoomId :: * Source #

SparkApiPath RoomId Source #

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

type Rep RoomId Source # 
type Rep RoomId = D1 * (MetaData "RoomId" "Network.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" 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 

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.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" True) (C1 * (MetaCons "SipAddr" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * 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

data Room Source #

Room is communication space in Cisco Spark 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 Spark. 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.

SparkListItem Room Source #

RoomList wraps Room

Associated Types

type ToList Room :: * Source #

Methods

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

type ToList Room Source # 

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 #

SparkFilter RoomFilter Source #

User can list rooms with filter parameter.

SparkResponse RoomFilter Source #

List rooms API uses RoomFilter and responses Room.

Associated Types

type ToResponse RoomFilter :: * Source #

SparkApiPath RoomFilter Source #

List rooms API uses RoomFilter and path "rooms".

type Rep RoomFilter Source # 
type Rep RoomFilter = D1 * (MetaData "RoomFilter" "Network.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" 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 # 

roomTypeToFilterString :: RoomType -> ByteString Source #

Sum type to ByteString converter for RoomType.

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.

SparkCreate CreateRoom Source #

User can create a room.

SparkResponse CreateRoom Source #

Create room API uses "CreateRoom' and responses Room.

Associated Types

type ToResponse CreateRoom :: * Source #

SparkApiPath 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.

SparkUpdate UpdateRoom Source #

User can update a room.

SparkResponse UpdateRoom Source #

Update room API uses "UpdateRoom' and responses Room.

Associated Types

type ToResponse UpdateRoom :: * Source #

SparkApiPath UpdateRoom Source #

Update room API uses UpdateRoom and path "rooms".

type ToResponse UpdateRoom Source # 

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 # 
SparkDetail MembershipId Source #

User can get detail of a membership.

SparkResponse MembershipId Source #

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

Associated Types

type ToResponse MembershipId :: * Source #

SparkApiPath MembershipId Source #

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

type Rep MembershipId Source # 
type Rep MembershipId = D1 * (MetaData "MembershipId" "Network.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" True) (C1 * (MetaCons "MembershipId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse MembershipId Source # 

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

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 # 
SparkFilter MembershipFilter Source #

User can list memberships with filter parameter.

SparkResponse MembershipFilter Source #

List memberships API uses MembershipFilter and responses Membership.

Associated Types

type ToResponse MembershipFilter :: * Source #

SparkApiPath MembershipFilter Source #

List memberships API uses MembershipFilter and path "memberships".

type Rep MembershipFilter Source # 
type Rep MembershipFilter = D1 * (MetaData "MembershipFilter" "Network.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" 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

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 # 
SparkDetail MessageId Source #

User can get detail of a message.

SparkResponse MessageId Source #

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

Associated Types

type ToResponse MessageId :: * Source #

SparkApiPath MessageId Source #

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

type Rep MessageId Source # 
type Rep MessageId = D1 * (MetaData "MessageId" "Network.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" 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.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" True) (C1 * (MetaCons "FileUrl" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

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

Instances

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

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.

mentionedPeopleToFilterString :: MentionedPeople -> ByteString Source #

Sum type to ByteString converter for mentionedPeople query string.

data CreateMessage Source #

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

Constructors

CreateMessage 

Fields

newtype OrganizationDisplayName Source #

Display name of Organization

data Organization Source #

Organization is an administrative group of Cisco Spark 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 LicenseUnit Source #

Counting number of granted or consumed License

Constructors

LicenseUnit Integer 

data License Source #

License is allowance for features and services of Cisco Spark 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

Instances

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 #

SparkFilter LicenseFilter Source #

User can list licenses with filter parameter.

SparkResponse LicenseFilter Source #

List licenses API uses LicenseFilter and responses License.

Associated Types

type ToResponse LicenseFilter :: * Source #

SparkApiPath LicenseFilter Source #

List licenses API uses LicenseFilter and path "licenses".

type Rep LicenseFilter Source # 
type Rep LicenseFilter = D1 * (MetaData "LicenseFilter" "Network.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" True) (C1 * (MetaCons "LicenseFilter" PrefixI True) (S1 * (MetaSel (Just Symbol "licenseFilterOrgId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe OrganizationId))))
type ToResponse LicenseFilter Source # 

newtype RoleName Source #

Name of Role.

Constructors

RoleName Text 

Instances

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.

SparkListItem Role Source #

RoleList wraps Role

Associated Types

type ToList Role :: * Source #

Methods

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

type ToList Role Source # 

newtype RoleList Source #

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

Constructors

RoleList 

Fields

Instances

newtype WebhookId Source #

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

Constructors

WebhookId Text 

Instances

Eq WebhookId Source # 
Show WebhookId Source # 
Generic WebhookId Source # 

Associated Types

type Rep WebhookId :: * -> * #

ToJSON WebhookId Source # 
FromJSON WebhookId Source # 
SparkDetail WebhookId Source #

User can get detail of a webhook.

SparkResponse WebhookId Source #

Get detail for a webhook API uses "WebhookId' and responses Webhook.

Associated Types

type ToResponse WebhookId :: * Source #

SparkApiPath WebhookId Source #

Get detail for webhook API uses WebhookId and path "webhooks".

type Rep WebhookId Source # 
type Rep WebhookId = D1 * (MetaData "WebhookId" "Network.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" True) (C1 * (MetaCons "WebhookId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))
type ToResponse WebhookId Source # 

newtype WebhookUrl Source #

URL pointing to webhook target.

Constructors

WebhookUrl Text 

newtype WebhookSecret Source #

Shared secret supplied by user to authenticate Spark Cloud by webhook receiver.

Constructors

WebhookSecret Text 

data Webhook Source #

Webhook allow your app to be notified via HTTP when a specific event occurs on Spark. For example, your app can register a webhook to be notified when a new message is posted into a specific room.

Constructors

Webhook 

Fields

Instances

newtype WebhookList Source #

WebhookList is decoded from response JSON of List Webhook REST call. It is list of Webhook.

Constructors

WebhookList 

data CreateWebhook Source #

CreateWebhook is encoded to request body JSON of Create a Webhook REST call.

Constructors

CreateWebhook 

Fields

data UpdateWebhook Source #

UpdateWebhook is encoded to request body JSON of Update a Webhook REST call.

Constructors

UpdateWebhook 

Fields

data WebhookMembershipFilter Source #

Optional query strings for membership event.

Constructors

WebhookMembershipFilter 

Fields

data WebhookMessageFilter Source #

Optional query strings for message event.

Constructors

WebhookMessageFilter 

Fields

data WebhookRoomFilter Source #

Optional query strings for room event.

Constructors

WebhookRoomFilter 

Fields

newtype AppId Source #

Identifier of app.

Constructors

AppId Text 

Instances

Eq AppId Source # 

Methods

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

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

Show AppId Source # 

Methods

showsPrec :: Int -> AppId -> ShowS #

show :: AppId -> String #

showList :: [AppId] -> ShowS #

Generic AppId Source # 

Associated Types

type Rep AppId :: * -> * #

Methods

from :: AppId -> Rep AppId x #

to :: Rep AppId x -> AppId #

ToJSON AppId Source # 
FromJSON AppId Source # 
type Rep AppId Source # 
type Rep AppId = D1 * (MetaData "AppId" "Network.CiscoSpark.Types" "cisco-spark-api-0.1.0.2-4uci0XnKBqiELiRI38tANM" True) (C1 * (MetaCons "AppId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))