amazonka-alexa-business-1.6.0: Amazon Alexa For Business SDK.

Copyright(c) 2013-2018 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay+amazonka@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.AWS.AlexaBusiness

Contents

Description

Alexa for Business makes it easy for you to use Alexa in your organization. Alexa for Business gives you the tools you need for managing Alexa devices, enroll your users, and assign skills, at scale. You can build your own context-aware voice skills using the Alexa Skills Kit and the Alexa for Business API operations. You can make also these available as private skills for your organization. Alexa for Business makes it easy to voice-enable your products and services, providing context-aware voice experiences for your customers.

Synopsis

Service Configuration

alexaBusiness :: Service Source #

API version 2017-11-09 of the Amazon Alexa For Business SDK configuration.

Errors

Error matchers are designed for use with the functions provided by Control.Exception.Lens. This allows catching (and rethrowing) service specific errors returned by AlexaBusiness.

InvalidUserStatusException

_InvalidUserStatusException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The attempt to update a user is invalid due to the user's current status. HTTP Status Code: 400

NotFoundException

_NotFoundException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The resource is not found. HTTP Status Code: 400

NameInUseException

_NameInUseException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The name sent in the request is already in use. HTTP Status Code: 400

AlreadyExistsException

_AlreadyExistsException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The resource being created already exists. HTTP Status Code: 400

LimitExceededException

_LimitExceededException :: AsError a => Getting (First ServiceError) a ServiceError Source #

You are performing an action that would put you beyond your account's limits. HTTP Status Code: 400

ResourceInUseException

_ResourceInUseException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The resource in the request is already in use. HTTP Status Code: 400

Waiters

Waiters poll by repeatedly sending a request until some remote success condition configured by the Wait specification is fulfilled. The Wait specification determines how many attempts should be made, in addition to delay and retry strategies.

Operations

Some AWS operations return results that are incomplete and require subsequent requests in order to obtain the entire result set. The process of sending subsequent requests to continue where a previous request left off is called pagination. For example, the ListObjects operation of Amazon S3 returns up to 1000 objects at a time, and you must send subsequent requests with the appropriate Marker in order to retrieve the next page of results.

Operations that have an AWSPager instance can transparently perform subsequent requests, correctly setting Markers and other request facets to iterate through the entire result set of a truncated API operation. Operations which support this have an additional note in the documentation.

Many operations have the ability to filter results on the server side. See the individual operation parameters for details.

SearchUsers (Paginated)

AssociateSkillGroupWithRoom

DeleteProfile

UpdateProfile

SearchRooms (Paginated)

DisassociateContactFromAddressBook

CreateAddressBook

DeleteAddressBook

UpdateAddressBook

UpdateRoom

DeleteRoom

GetDevice

GetContact

AssociateDeviceWithRoom

GetRoomSkillParameter

DeleteContact

UpdateContact

GetAddressBook

CreateContact

CreateProfile

DeleteSkillGroup

UpdateSkillGroup

StartDeviceSync

SearchAddressBooks

CreateSkillGroup

GetProfile

DisassociateSkillGroupFromRoom

SendInvitation

ListDeviceEvents

CreateUser

SearchDevices (Paginated)

SearchContacts

DeleteUser

GetSkillGroup

ListSkills (Paginated)

TagResource

DisassociateDeviceFromRoom

SearchSkillGroups (Paginated)

ListTags (Paginated)

UntagResource

ResolveRoom

CreateRoom

DeleteRoomSkillParameter

PutRoomSkillParameter

SearchProfiles (Paginated)

RevokeInvitation

UpdateDevice

GetRoom

AssociateContactWithAddressBook

Types

ConnectionStatus

data ConnectionStatus Source #

Constructors

Offline 
Online 

Instances

Bounded ConnectionStatus Source # 
Enum ConnectionStatus Source # 
Eq ConnectionStatus Source # 
Data ConnectionStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConnectionStatus -> c ConnectionStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConnectionStatus #

toConstr :: ConnectionStatus -> Constr #

dataTypeOf :: ConnectionStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConnectionStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConnectionStatus) #

gmapT :: (forall b. Data b => b -> b) -> ConnectionStatus -> ConnectionStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConnectionStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConnectionStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConnectionStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConnectionStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConnectionStatus -> m ConnectionStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConnectionStatus -> m ConnectionStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConnectionStatus -> m ConnectionStatus #

Ord ConnectionStatus Source # 
Read ConnectionStatus Source # 
Show ConnectionStatus Source # 
Generic ConnectionStatus Source # 
Hashable ConnectionStatus Source # 
FromJSON ConnectionStatus Source # 
NFData ConnectionStatus Source # 

Methods

rnf :: ConnectionStatus -> () #

ToHeader ConnectionStatus Source # 
ToQuery ConnectionStatus Source # 
ToByteString ConnectionStatus Source # 
FromText ConnectionStatus Source # 
ToText ConnectionStatus Source # 
type Rep ConnectionStatus Source # 
type Rep ConnectionStatus = D1 * (MetaData "ConnectionStatus" "Network.AWS.AlexaBusiness.Types.Sum" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) ((:+:) * (C1 * (MetaCons "Offline" PrefixI False) (U1 *)) (C1 * (MetaCons "Online" PrefixI False) (U1 *)))

DeviceEventType

data DeviceEventType Source #

Instances

Bounded DeviceEventType Source # 
Enum DeviceEventType Source # 
Eq DeviceEventType Source # 
Data DeviceEventType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeviceEventType -> c DeviceEventType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeviceEventType #

toConstr :: DeviceEventType -> Constr #

dataTypeOf :: DeviceEventType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeviceEventType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeviceEventType) #

gmapT :: (forall b. Data b => b -> b) -> DeviceEventType -> DeviceEventType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeviceEventType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeviceEventType -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeviceEventType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeviceEventType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeviceEventType -> m DeviceEventType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeviceEventType -> m DeviceEventType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeviceEventType -> m DeviceEventType #

Ord DeviceEventType Source # 
Read DeviceEventType Source # 
Show DeviceEventType Source # 
Generic DeviceEventType Source # 
Hashable DeviceEventType Source # 
ToJSON DeviceEventType Source # 
FromJSON DeviceEventType Source # 
NFData DeviceEventType Source # 

Methods

rnf :: DeviceEventType -> () #

ToHeader DeviceEventType Source # 
ToQuery DeviceEventType Source # 
ToByteString DeviceEventType Source # 
FromText DeviceEventType Source # 
ToText DeviceEventType Source # 
type Rep DeviceEventType Source # 
type Rep DeviceEventType = D1 * (MetaData "DeviceEventType" "Network.AWS.AlexaBusiness.Types.Sum" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) ((:+:) * (C1 * (MetaCons "ConnectionStatus" PrefixI False) (U1 *)) (C1 * (MetaCons "DeviceStatus" PrefixI False) (U1 *)))

DeviceStatus

data DeviceStatus Source #

Instances

Bounded DeviceStatus Source # 
Enum DeviceStatus Source # 
Eq DeviceStatus Source # 
Data DeviceStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeviceStatus -> c DeviceStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeviceStatus #

toConstr :: DeviceStatus -> Constr #

dataTypeOf :: DeviceStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeviceStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeviceStatus) #

gmapT :: (forall b. Data b => b -> b) -> DeviceStatus -> DeviceStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeviceStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeviceStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeviceStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeviceStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeviceStatus -> m DeviceStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeviceStatus -> m DeviceStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeviceStatus -> m DeviceStatus #

Ord DeviceStatus Source # 
Read DeviceStatus Source # 
Show DeviceStatus Source # 
Generic DeviceStatus Source # 

Associated Types

type Rep DeviceStatus :: * -> * #

Hashable DeviceStatus Source # 
FromJSON DeviceStatus Source # 
NFData DeviceStatus Source # 

Methods

rnf :: DeviceStatus -> () #

ToHeader DeviceStatus Source # 
ToQuery DeviceStatus Source # 
ToByteString DeviceStatus Source # 
FromText DeviceStatus Source # 
ToText DeviceStatus Source # 

Methods

toText :: DeviceStatus -> Text #

type Rep DeviceStatus Source # 
type Rep DeviceStatus = D1 * (MetaData "DeviceStatus" "Network.AWS.AlexaBusiness.Types.Sum" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Deregistered" PrefixI False) (U1 *)) (C1 * (MetaCons "Pending" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Ready" PrefixI False) (U1 *)) (C1 * (MetaCons "WasOffline" PrefixI False) (U1 *))))

DeviceStatusDetailCode

data DeviceStatusDetailCode Source #

Instances

Bounded DeviceStatusDetailCode Source # 
Enum DeviceStatusDetailCode Source # 
Eq DeviceStatusDetailCode Source # 
Data DeviceStatusDetailCode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeviceStatusDetailCode -> c DeviceStatusDetailCode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeviceStatusDetailCode #

toConstr :: DeviceStatusDetailCode -> Constr #

dataTypeOf :: DeviceStatusDetailCode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeviceStatusDetailCode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeviceStatusDetailCode) #

gmapT :: (forall b. Data b => b -> b) -> DeviceStatusDetailCode -> DeviceStatusDetailCode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeviceStatusDetailCode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeviceStatusDetailCode -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeviceStatusDetailCode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeviceStatusDetailCode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeviceStatusDetailCode -> m DeviceStatusDetailCode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeviceStatusDetailCode -> m DeviceStatusDetailCode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeviceStatusDetailCode -> m DeviceStatusDetailCode #

Ord DeviceStatusDetailCode Source # 
Read DeviceStatusDetailCode Source # 
Show DeviceStatusDetailCode Source # 
Generic DeviceStatusDetailCode Source # 
Hashable DeviceStatusDetailCode Source # 
FromJSON DeviceStatusDetailCode Source # 
NFData DeviceStatusDetailCode Source # 

Methods

rnf :: DeviceStatusDetailCode -> () #

ToHeader DeviceStatusDetailCode Source # 
ToQuery DeviceStatusDetailCode Source # 
ToByteString DeviceStatusDetailCode Source # 
FromText DeviceStatusDetailCode Source # 
ToText DeviceStatusDetailCode Source # 
type Rep DeviceStatusDetailCode Source # 
type Rep DeviceStatusDetailCode = D1 * (MetaData "DeviceStatusDetailCode" "Network.AWS.AlexaBusiness.Types.Sum" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) ((:+:) * (C1 * (MetaCons "DeviceSoftwareUpdateNeeded" PrefixI False) (U1 *)) (C1 * (MetaCons "DeviceWasOffline" PrefixI False) (U1 *)))

DistanceUnit

data DistanceUnit Source #

Constructors

Imperial 
Metric 

Instances

Bounded DistanceUnit Source # 
Enum DistanceUnit Source # 
Eq DistanceUnit Source # 
Data DistanceUnit Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DistanceUnit -> c DistanceUnit #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DistanceUnit #

toConstr :: DistanceUnit -> Constr #

dataTypeOf :: DistanceUnit -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DistanceUnit) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DistanceUnit) #

gmapT :: (forall b. Data b => b -> b) -> DistanceUnit -> DistanceUnit #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DistanceUnit -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DistanceUnit -> r #

gmapQ :: (forall d. Data d => d -> u) -> DistanceUnit -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DistanceUnit -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DistanceUnit -> m DistanceUnit #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DistanceUnit -> m DistanceUnit #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DistanceUnit -> m DistanceUnit #

Ord DistanceUnit Source # 
Read DistanceUnit Source # 
Show DistanceUnit Source # 
Generic DistanceUnit Source # 

Associated Types

type Rep DistanceUnit :: * -> * #

Hashable DistanceUnit Source # 
ToJSON DistanceUnit Source # 
FromJSON DistanceUnit Source # 
NFData DistanceUnit Source # 

Methods

rnf :: DistanceUnit -> () #

ToHeader DistanceUnit Source # 
ToQuery DistanceUnit Source # 
ToByteString DistanceUnit Source # 
FromText DistanceUnit Source # 
ToText DistanceUnit Source # 

Methods

toText :: DistanceUnit -> Text #

type Rep DistanceUnit Source # 
type Rep DistanceUnit = D1 * (MetaData "DistanceUnit" "Network.AWS.AlexaBusiness.Types.Sum" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) ((:+:) * (C1 * (MetaCons "Imperial" PrefixI False) (U1 *)) (C1 * (MetaCons "Metric" PrefixI False) (U1 *)))

EnrollmentStatus

data EnrollmentStatus Source #

Instances

Bounded EnrollmentStatus Source # 
Enum EnrollmentStatus Source # 
Eq EnrollmentStatus Source # 
Data EnrollmentStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EnrollmentStatus -> c EnrollmentStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EnrollmentStatus #

toConstr :: EnrollmentStatus -> Constr #

dataTypeOf :: EnrollmentStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EnrollmentStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EnrollmentStatus) #

gmapT :: (forall b. Data b => b -> b) -> EnrollmentStatus -> EnrollmentStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EnrollmentStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EnrollmentStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> EnrollmentStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EnrollmentStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EnrollmentStatus -> m EnrollmentStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EnrollmentStatus -> m EnrollmentStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EnrollmentStatus -> m EnrollmentStatus #

Ord EnrollmentStatus Source # 
Read EnrollmentStatus Source # 
Show EnrollmentStatus Source # 
Generic EnrollmentStatus Source # 
Hashable EnrollmentStatus Source # 
FromJSON EnrollmentStatus Source # 
NFData EnrollmentStatus Source # 

Methods

rnf :: EnrollmentStatus -> () #

ToHeader EnrollmentStatus Source # 
ToQuery EnrollmentStatus Source # 
ToByteString EnrollmentStatus Source # 
FromText EnrollmentStatus Source # 
ToText EnrollmentStatus Source # 
type Rep EnrollmentStatus Source # 
type Rep EnrollmentStatus = D1 * (MetaData "EnrollmentStatus" "Network.AWS.AlexaBusiness.Types.Sum" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ESDeregistering" PrefixI False) (U1 *)) (C1 * (MetaCons "ESDisassociating" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ESInitialized" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ESPending" PrefixI False) (U1 *)) (C1 * (MetaCons "ESRegistered" PrefixI False) (U1 *)))))

Feature

data Feature Source #

Instances

Bounded Feature Source # 
Enum Feature Source # 
Eq Feature Source # 

Methods

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

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

Data Feature Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Feature -> c Feature #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Feature #

toConstr :: Feature -> Constr #

dataTypeOf :: Feature -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Feature) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Feature) #

gmapT :: (forall b. Data b => b -> b) -> Feature -> Feature #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Feature -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Feature -> r #

gmapQ :: (forall d. Data d => d -> u) -> Feature -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Feature -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Feature -> m Feature #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Feature -> m Feature #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Feature -> m Feature #

Ord Feature Source # 
Read Feature Source # 
Show Feature Source # 
Generic Feature Source # 

Associated Types

type Rep Feature :: * -> * #

Methods

from :: Feature -> Rep Feature x #

to :: Rep Feature x -> Feature #

Hashable Feature Source # 

Methods

hashWithSalt :: Int -> Feature -> Int #

hash :: Feature -> Int #

ToJSON Feature Source # 
NFData Feature Source # 

Methods

rnf :: Feature -> () #

ToHeader Feature Source # 

Methods

toHeader :: HeaderName -> Feature -> [Header] #

ToQuery Feature Source # 
ToByteString Feature Source # 

Methods

toBS :: Feature -> ByteString #

FromText Feature Source # 
ToText Feature Source # 

Methods

toText :: Feature -> Text #

type Rep Feature Source # 
type Rep Feature = D1 * (MetaData "Feature" "Network.AWS.AlexaBusiness.Types.Sum" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) ((:+:) * ((:+:) * (C1 * (MetaCons "All" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Bluetooth" PrefixI False) (U1 *)) (C1 * (MetaCons "Lists" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "Notifications" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Skills" PrefixI False) (U1 *)) (C1 * (MetaCons "Volume" PrefixI False) (U1 *)))))

SortValue

data SortValue Source #

Constructors

Asc 
Desc 

Instances

Bounded SortValue Source # 
Enum SortValue Source # 
Eq SortValue Source # 
Data SortValue Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SortValue -> c SortValue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SortValue #

toConstr :: SortValue -> Constr #

dataTypeOf :: SortValue -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SortValue) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortValue) #

gmapT :: (forall b. Data b => b -> b) -> SortValue -> SortValue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SortValue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SortValue -> r #

gmapQ :: (forall d. Data d => d -> u) -> SortValue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SortValue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SortValue -> m SortValue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SortValue -> m SortValue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SortValue -> m SortValue #

Ord SortValue Source # 
Read SortValue Source # 
Show SortValue Source # 
Generic SortValue Source # 

Associated Types

type Rep SortValue :: * -> * #

Hashable SortValue Source # 
ToJSON SortValue Source # 
NFData SortValue Source # 

Methods

rnf :: SortValue -> () #

ToHeader SortValue Source # 
ToQuery SortValue Source # 
ToByteString SortValue Source # 

Methods

toBS :: SortValue -> ByteString #

FromText SortValue Source # 
ToText SortValue Source # 

Methods

toText :: SortValue -> Text #

type Rep SortValue Source # 
type Rep SortValue = D1 * (MetaData "SortValue" "Network.AWS.AlexaBusiness.Types.Sum" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) ((:+:) * (C1 * (MetaCons "Asc" PrefixI False) (U1 *)) (C1 * (MetaCons "Desc" PrefixI False) (U1 *)))

TemperatureUnit

data TemperatureUnit Source #

Constructors

Celsius 
Fahrenheit 

Instances

Bounded TemperatureUnit Source # 
Enum TemperatureUnit Source # 
Eq TemperatureUnit Source # 
Data TemperatureUnit Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TemperatureUnit -> c TemperatureUnit #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TemperatureUnit #

toConstr :: TemperatureUnit -> Constr #

dataTypeOf :: TemperatureUnit -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TemperatureUnit) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TemperatureUnit) #

gmapT :: (forall b. Data b => b -> b) -> TemperatureUnit -> TemperatureUnit #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TemperatureUnit -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TemperatureUnit -> r #

gmapQ :: (forall d. Data d => d -> u) -> TemperatureUnit -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TemperatureUnit -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TemperatureUnit -> m TemperatureUnit #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TemperatureUnit -> m TemperatureUnit #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TemperatureUnit -> m TemperatureUnit #

Ord TemperatureUnit Source # 
Read TemperatureUnit Source # 
Show TemperatureUnit Source # 
Generic TemperatureUnit Source # 
Hashable TemperatureUnit Source # 
ToJSON TemperatureUnit Source # 
FromJSON TemperatureUnit Source # 
NFData TemperatureUnit Source # 

Methods

rnf :: TemperatureUnit -> () #

ToHeader TemperatureUnit Source # 
ToQuery TemperatureUnit Source # 
ToByteString TemperatureUnit Source # 
FromText TemperatureUnit Source # 
ToText TemperatureUnit Source # 
type Rep TemperatureUnit Source # 
type Rep TemperatureUnit = D1 * (MetaData "TemperatureUnit" "Network.AWS.AlexaBusiness.Types.Sum" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) ((:+:) * (C1 * (MetaCons "Celsius" PrefixI False) (U1 *)) (C1 * (MetaCons "Fahrenheit" PrefixI False) (U1 *)))

WakeWord

data WakeWord Source #

Constructors

Alexa 
Amazon 
Computer 
Echo 

Instances

Bounded WakeWord Source # 
Enum WakeWord Source # 
Eq WakeWord Source # 
Data WakeWord Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WakeWord -> c WakeWord #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WakeWord #

toConstr :: WakeWord -> Constr #

dataTypeOf :: WakeWord -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c WakeWord) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WakeWord) #

gmapT :: (forall b. Data b => b -> b) -> WakeWord -> WakeWord #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WakeWord -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WakeWord -> r #

gmapQ :: (forall d. Data d => d -> u) -> WakeWord -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WakeWord -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WakeWord -> m WakeWord #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WakeWord -> m WakeWord #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WakeWord -> m WakeWord #

Ord WakeWord Source # 
Read WakeWord Source # 
Show WakeWord Source # 
Generic WakeWord Source # 

Associated Types

type Rep WakeWord :: * -> * #

Methods

from :: WakeWord -> Rep WakeWord x #

to :: Rep WakeWord x -> WakeWord #

Hashable WakeWord Source # 

Methods

hashWithSalt :: Int -> WakeWord -> Int #

hash :: WakeWord -> Int #

ToJSON WakeWord Source # 
FromJSON WakeWord Source # 
NFData WakeWord Source # 

Methods

rnf :: WakeWord -> () #

ToHeader WakeWord Source # 

Methods

toHeader :: HeaderName -> WakeWord -> [Header] #

ToQuery WakeWord Source # 
ToByteString WakeWord Source # 

Methods

toBS :: WakeWord -> ByteString #

FromText WakeWord Source # 
ToText WakeWord Source # 

Methods

toText :: WakeWord -> Text #

type Rep WakeWord Source # 
type Rep WakeWord = D1 * (MetaData "WakeWord" "Network.AWS.AlexaBusiness.Types.Sum" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Alexa" PrefixI False) (U1 *)) (C1 * (MetaCons "Amazon" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Computer" PrefixI False) (U1 *)) (C1 * (MetaCons "Echo" PrefixI False) (U1 *))))

AddressBook

data AddressBook Source #

An address book with attributes.

See: addressBook smart constructor.

Instances

Eq AddressBook Source # 
Data AddressBook Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddressBook -> c AddressBook #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddressBook #

toConstr :: AddressBook -> Constr #

dataTypeOf :: AddressBook -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddressBook) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddressBook) #

gmapT :: (forall b. Data b => b -> b) -> AddressBook -> AddressBook #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddressBook -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddressBook -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddressBook -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddressBook -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddressBook -> m AddressBook #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddressBook -> m AddressBook #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddressBook -> m AddressBook #

Read AddressBook Source # 
Show AddressBook Source # 
Generic AddressBook Source # 

Associated Types

type Rep AddressBook :: * -> * #

Hashable AddressBook Source # 
FromJSON AddressBook Source # 
NFData AddressBook Source # 

Methods

rnf :: AddressBook -> () #

type Rep AddressBook Source # 
type Rep AddressBook = D1 * (MetaData "AddressBook" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "AddressBook'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_abAddressBookARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_abName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_abDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

addressBook :: AddressBook Source #

Creates a value of AddressBook with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

abAddressBookARN :: Lens' AddressBook (Maybe Text) Source #

The ARN of the address book.

abName :: Lens' AddressBook (Maybe Text) Source #

The name of the address book.

abDescription :: Lens' AddressBook (Maybe Text) Source #

The description of the address book.

AddressBookData

data AddressBookData Source #

Information related to an address book.

See: addressBookData smart constructor.

Instances

Eq AddressBookData Source # 
Data AddressBookData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddressBookData -> c AddressBookData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddressBookData #

toConstr :: AddressBookData -> Constr #

dataTypeOf :: AddressBookData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddressBookData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddressBookData) #

gmapT :: (forall b. Data b => b -> b) -> AddressBookData -> AddressBookData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddressBookData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddressBookData -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddressBookData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddressBookData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddressBookData -> m AddressBookData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddressBookData -> m AddressBookData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddressBookData -> m AddressBookData #

Read AddressBookData Source # 
Show AddressBookData Source # 
Generic AddressBookData Source # 
Hashable AddressBookData Source # 
FromJSON AddressBookData Source # 
NFData AddressBookData Source # 

Methods

rnf :: AddressBookData -> () #

type Rep AddressBookData Source # 
type Rep AddressBookData = D1 * (MetaData "AddressBookData" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "AddressBookData'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_abdAddressBookARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_abdName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_abdDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

addressBookData :: AddressBookData Source #

Creates a value of AddressBookData with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

abdAddressBookARN :: Lens' AddressBookData (Maybe Text) Source #

The ARN of the address book.

abdName :: Lens' AddressBookData (Maybe Text) Source #

The name of the address book.

abdDescription :: Lens' AddressBookData (Maybe Text) Source #

The description of the address book.

Contact

data Contact Source #

A contact with attributes.

See: contact smart constructor.

Instances

Eq Contact Source # 

Methods

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

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

Data Contact Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Contact -> c Contact #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Contact #

toConstr :: Contact -> Constr #

dataTypeOf :: Contact -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Contact) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Contact) #

gmapT :: (forall b. Data b => b -> b) -> Contact -> Contact #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Contact -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Contact -> r #

gmapQ :: (forall d. Data d => d -> u) -> Contact -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Contact -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Contact -> m Contact #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Contact -> m Contact #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Contact -> m Contact #

Read Contact Source # 
Show Contact Source # 
Generic Contact Source # 

Associated Types

type Rep Contact :: * -> * #

Methods

from :: Contact -> Rep Contact x #

to :: Rep Contact x -> Contact #

Hashable Contact Source # 

Methods

hashWithSalt :: Int -> Contact -> Int #

hash :: Contact -> Int #

FromJSON Contact Source # 
NFData Contact Source # 

Methods

rnf :: Contact -> () #

type Rep Contact Source # 
type Rep Contact = D1 * (MetaData "Contact" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "Contact'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cLastName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cContactARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cPhoneNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cFirstName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cDisplayName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

contact :: Contact Source #

Creates a value of Contact with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • cLastName - The last name of the contact, used to call the contact on the device.
  • cContactARN - The ARN of the contact.
  • cPhoneNumber - The phone number of the contact.
  • cFirstName - The first name of the contact, used to call the contact on the device.
  • cDisplayName - The name of the contact to display on the console.

cLastName :: Lens' Contact (Maybe Text) Source #

The last name of the contact, used to call the contact on the device.

cContactARN :: Lens' Contact (Maybe Text) Source #

The ARN of the contact.

cPhoneNumber :: Lens' Contact (Maybe Text) Source #

The phone number of the contact.

cFirstName :: Lens' Contact (Maybe Text) Source #

The first name of the contact, used to call the contact on the device.

cDisplayName :: Lens' Contact (Maybe Text) Source #

The name of the contact to display on the console.

ContactData

data ContactData Source #

Information related to a contact.

See: contactData smart constructor.

Instances

Eq ContactData Source # 
Data ContactData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ContactData -> c ContactData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ContactData #

toConstr :: ContactData -> Constr #

dataTypeOf :: ContactData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ContactData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ContactData) #

gmapT :: (forall b. Data b => b -> b) -> ContactData -> ContactData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ContactData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ContactData -> r #

gmapQ :: (forall d. Data d => d -> u) -> ContactData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ContactData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ContactData -> m ContactData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ContactData -> m ContactData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ContactData -> m ContactData #

Read ContactData Source # 
Show ContactData Source # 
Generic ContactData Source # 

Associated Types

type Rep ContactData :: * -> * #

Hashable ContactData Source # 
FromJSON ContactData Source # 
NFData ContactData Source # 

Methods

rnf :: ContactData -> () #

type Rep ContactData Source # 
type Rep ContactData = D1 * (MetaData "ContactData" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "ContactData'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cdLastName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cdContactARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cdPhoneNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cdFirstName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cdDisplayName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

contactData :: ContactData Source #

Creates a value of ContactData with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • cdLastName - The last name of the contact, used to call the contact on the device.
  • cdContactARN - The ARN of the contact.
  • cdPhoneNumber - The phone number of the contact.
  • cdFirstName - The first name of the contact, used to call the contact on the device.
  • cdDisplayName - The name of the contact to display on the console.

cdLastName :: Lens' ContactData (Maybe Text) Source #

The last name of the contact, used to call the contact on the device.

cdContactARN :: Lens' ContactData (Maybe Text) Source #

The ARN of the contact.

cdPhoneNumber :: Lens' ContactData (Maybe Text) Source #

The phone number of the contact.

cdFirstName :: Lens' ContactData (Maybe Text) Source #

The first name of the contact, used to call the contact on the device.

cdDisplayName :: Lens' ContactData (Maybe Text) Source #

The name of the contact to display on the console.

Device

data Device Source #

A device with attributes.

See: device smart constructor.

Instances

Eq Device Source # 

Methods

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

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

Data Device Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Device -> c Device #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Device #

toConstr :: Device -> Constr #

dataTypeOf :: Device -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Device) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Device) #

gmapT :: (forall b. Data b => b -> b) -> Device -> Device #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Device -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Device -> r #

gmapQ :: (forall d. Data d => d -> u) -> Device -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Device -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Device -> m Device #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Device -> m Device #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Device -> m Device #

Read Device Source # 
Show Device Source # 
Generic Device Source # 

Associated Types

type Rep Device :: * -> * #

Methods

from :: Device -> Rep Device x #

to :: Rep Device x -> Device #

Hashable Device Source # 

Methods

hashWithSalt :: Int -> Device -> Int #

hash :: Device -> Int #

FromJSON Device Source # 
NFData Device Source # 

Methods

rnf :: Device -> () #

type Rep Device Source # 

device :: Device Source #

Creates a value of Device with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dDeviceStatus :: Lens' Device (Maybe DeviceStatus) Source #

The status of a device. If the status is not READY, check the DeviceStatusInfo value for details.

dDeviceStatusInfo :: Lens' Device (Maybe DeviceStatusInfo) Source #

Detailed information about a device's status.

dDeviceARN :: Lens' Device (Maybe Text) Source #

The ARN of a device.

dMACAddress :: Lens' Device (Maybe Text) Source #

The MAC address of a device.

dDeviceName :: Lens' Device (Maybe Text) Source #

The name of a device.

dRoomARN :: Lens' Device (Maybe Text) Source #

The room ARN of a device.

dSoftwareVersion :: Lens' Device (Maybe Text) Source #

The software version of a device.

dDeviceType :: Lens' Device (Maybe Text) Source #

The type of a device.

dDeviceSerialNumber :: Lens' Device (Maybe Text) Source #

The serial number of a device.

DeviceData

data DeviceData Source #

Device attributes.

See: deviceData smart constructor.

Instances

Eq DeviceData Source # 
Data DeviceData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeviceData -> c DeviceData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeviceData #

toConstr :: DeviceData -> Constr #

dataTypeOf :: DeviceData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeviceData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeviceData) #

gmapT :: (forall b. Data b => b -> b) -> DeviceData -> DeviceData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeviceData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeviceData -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeviceData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeviceData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeviceData -> m DeviceData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeviceData -> m DeviceData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeviceData -> m DeviceData #

Read DeviceData Source # 
Show DeviceData Source # 
Generic DeviceData Source # 

Associated Types

type Rep DeviceData :: * -> * #

Hashable DeviceData Source # 
FromJSON DeviceData Source # 
NFData DeviceData Source # 

Methods

rnf :: DeviceData -> () #

type Rep DeviceData Source # 

deviceData :: DeviceData Source #

Creates a value of DeviceData with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ddDeviceStatusInfo :: Lens' DeviceData (Maybe DeviceStatusInfo) Source #

Detailed information about a device's status.

ddDeviceARN :: Lens' DeviceData (Maybe Text) Source #

The ARN of a device.

ddMACAddress :: Lens' DeviceData (Maybe Text) Source #

The MAC address of a device.

ddDeviceName :: Lens' DeviceData (Maybe Text) Source #

The name of a device.

ddRoomARN :: Lens' DeviceData (Maybe Text) Source #

The room ARN associated with a device.

ddSoftwareVersion :: Lens' DeviceData (Maybe Text) Source #

The software version of a device.

ddDeviceType :: Lens' DeviceData (Maybe Text) Source #

The type of a device.

ddRoomName :: Lens' DeviceData (Maybe Text) Source #

The name of the room associated with a device.

ddDeviceSerialNumber :: Lens' DeviceData (Maybe Text) Source #

The serial number of a device.

DeviceEvent

data DeviceEvent Source #

The list of device events.

See: deviceEvent smart constructor.

Instances

Eq DeviceEvent Source # 
Data DeviceEvent Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeviceEvent -> c DeviceEvent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeviceEvent #

toConstr :: DeviceEvent -> Constr #

dataTypeOf :: DeviceEvent -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeviceEvent) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeviceEvent) #

gmapT :: (forall b. Data b => b -> b) -> DeviceEvent -> DeviceEvent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeviceEvent -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeviceEvent -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeviceEvent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeviceEvent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeviceEvent -> m DeviceEvent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeviceEvent -> m DeviceEvent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeviceEvent -> m DeviceEvent #

Read DeviceEvent Source # 
Show DeviceEvent Source # 
Generic DeviceEvent Source # 

Associated Types

type Rep DeviceEvent :: * -> * #

Hashable DeviceEvent Source # 
FromJSON DeviceEvent Source # 
NFData DeviceEvent Source # 

Methods

rnf :: DeviceEvent -> () #

type Rep DeviceEvent Source # 
type Rep DeviceEvent = D1 * (MetaData "DeviceEvent" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "DeviceEvent'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_deValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_deType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DeviceEventType))) (S1 * (MetaSel (Just Symbol "_deTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))))))

deviceEvent :: DeviceEvent Source #

Creates a value of DeviceEvent with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • deValue - The value of the event.
  • deType - The type of device event.
  • deTimestamp - The time (in epoch) when the event occurred.

deValue :: Lens' DeviceEvent (Maybe Text) Source #

The value of the event.

deType :: Lens' DeviceEvent (Maybe DeviceEventType) Source #

The type of device event.

deTimestamp :: Lens' DeviceEvent (Maybe UTCTime) Source #

The time (in epoch) when the event occurred.

DeviceStatusDetail

data DeviceStatusDetail Source #

Details of a device’s status.

See: deviceStatusDetail smart constructor.

Instances

Eq DeviceStatusDetail Source # 
Data DeviceStatusDetail Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeviceStatusDetail -> c DeviceStatusDetail #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeviceStatusDetail #

toConstr :: DeviceStatusDetail -> Constr #

dataTypeOf :: DeviceStatusDetail -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeviceStatusDetail) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeviceStatusDetail) #

gmapT :: (forall b. Data b => b -> b) -> DeviceStatusDetail -> DeviceStatusDetail #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeviceStatusDetail -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeviceStatusDetail -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeviceStatusDetail -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeviceStatusDetail -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeviceStatusDetail -> m DeviceStatusDetail #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeviceStatusDetail -> m DeviceStatusDetail #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeviceStatusDetail -> m DeviceStatusDetail #

Read DeviceStatusDetail Source # 
Show DeviceStatusDetail Source # 
Generic DeviceStatusDetail Source # 
Hashable DeviceStatusDetail Source # 
FromJSON DeviceStatusDetail Source # 
NFData DeviceStatusDetail Source # 

Methods

rnf :: DeviceStatusDetail -> () #

type Rep DeviceStatusDetail Source # 
type Rep DeviceStatusDetail = D1 * (MetaData "DeviceStatusDetail" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" True) (C1 * (MetaCons "DeviceStatusDetail'" PrefixI True) (S1 * (MetaSel (Just Symbol "_dsdCode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe DeviceStatusDetailCode))))

deviceStatusDetail :: DeviceStatusDetail Source #

Creates a value of DeviceStatusDetail with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • dsdCode - The device status detail code.

DeviceStatusInfo

data DeviceStatusInfo Source #

Detailed information about a device's status.

See: deviceStatusInfo smart constructor.

Instances

Eq DeviceStatusInfo Source # 
Data DeviceStatusInfo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeviceStatusInfo -> c DeviceStatusInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeviceStatusInfo #

toConstr :: DeviceStatusInfo -> Constr #

dataTypeOf :: DeviceStatusInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeviceStatusInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeviceStatusInfo) #

gmapT :: (forall b. Data b => b -> b) -> DeviceStatusInfo -> DeviceStatusInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeviceStatusInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeviceStatusInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeviceStatusInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeviceStatusInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeviceStatusInfo -> m DeviceStatusInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeviceStatusInfo -> m DeviceStatusInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeviceStatusInfo -> m DeviceStatusInfo #

Read DeviceStatusInfo Source # 
Show DeviceStatusInfo Source # 
Generic DeviceStatusInfo Source # 
Hashable DeviceStatusInfo Source # 
FromJSON DeviceStatusInfo Source # 
NFData DeviceStatusInfo Source # 

Methods

rnf :: DeviceStatusInfo -> () #

type Rep DeviceStatusInfo Source # 
type Rep DeviceStatusInfo = D1 * (MetaData "DeviceStatusInfo" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "DeviceStatusInfo'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_dsiDeviceStatusDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [DeviceStatusDetail]))) (S1 * (MetaSel (Just Symbol "_dsiConnectionStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ConnectionStatus)))))

deviceStatusInfo :: DeviceStatusInfo Source #

Creates a value of DeviceStatusInfo with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dsiDeviceStatusDetails :: Lens' DeviceStatusInfo [DeviceStatusDetail] Source #

One or more device status detail descriptions.

dsiConnectionStatus :: Lens' DeviceStatusInfo (Maybe ConnectionStatus) Source #

The latest available information about the connection status of a device.

Filter

data Filter Source #

A filter name and value pair that is used to return a more specific list of results. Filters can be used to match a set of resources by various criteria.

See: filter' smart constructor.

Instances

Eq Filter Source # 

Methods

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

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

Data Filter Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Filter -> c Filter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Filter #

toConstr :: Filter -> Constr #

dataTypeOf :: Filter -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Filter) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Filter) #

gmapT :: (forall b. Data b => b -> b) -> Filter -> Filter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Filter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Filter -> r #

gmapQ :: (forall d. Data d => d -> u) -> Filter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Filter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Filter -> m Filter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Filter -> m Filter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Filter -> m Filter #

Read Filter Source # 
Show Filter Source # 
Generic Filter Source # 

Associated Types

type Rep Filter :: * -> * #

Methods

from :: Filter -> Rep Filter x #

to :: Rep Filter x -> Filter #

Hashable Filter Source # 

Methods

hashWithSalt :: Int -> Filter -> Int #

hash :: Filter -> Int #

ToJSON Filter Source # 
NFData Filter Source # 

Methods

rnf :: Filter -> () #

type Rep Filter Source # 
type Rep Filter = D1 * (MetaData "Filter" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "Filter'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_fKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_fValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Text]))))

filter' Source #

Arguments

:: Text

fKey

-> Filter 

Creates a value of Filter with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • fKey - The key of a filter.
  • fValues - The values of a filter.

fKey :: Lens' Filter Text Source #

The key of a filter.

fValues :: Lens' Filter [Text] Source #

The values of a filter.

Profile

data Profile Source #

A room profile with attributes.

See: profile smart constructor.

Instances

Eq Profile Source # 

Methods

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

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

Data Profile Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Profile -> c Profile #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Profile #

toConstr :: Profile -> Constr #

dataTypeOf :: Profile -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Profile) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Profile) #

gmapT :: (forall b. Data b => b -> b) -> Profile -> Profile #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Profile -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Profile -> r #

gmapQ :: (forall d. Data d => d -> u) -> Profile -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Profile -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Profile -> m Profile #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Profile -> m Profile #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Profile -> m Profile #

Read Profile Source # 
Show Profile Source # 
Generic Profile Source # 

Associated Types

type Rep Profile :: * -> * #

Methods

from :: Profile -> Rep Profile x #

to :: Rep Profile x -> Profile #

Hashable Profile Source # 

Methods

hashWithSalt :: Int -> Profile -> Int #

hash :: Profile -> Int #

FromJSON Profile Source # 
NFData Profile Source # 

Methods

rnf :: Profile -> () #

type Rep Profile Source # 

profile :: Profile Source #

Creates a value of Profile with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pSetupModeDisabled :: Lens' Profile (Maybe Bool) Source #

The setup mode of a room profile.

pPSTNEnabled :: Lens' Profile (Maybe Bool) Source #

The PSTN setting of a room profile.

pDistanceUnit :: Lens' Profile (Maybe DistanceUnit) Source #

The distance unit of a room profile.

pAddress :: Lens' Profile (Maybe Text) Source #

The address of a room profile.

pProfileARN :: Lens' Profile (Maybe Text) Source #

The ARN of a room profile.

pWakeWord :: Lens' Profile (Maybe WakeWord) Source #

The wake word of a room profile.

pProfileName :: Lens' Profile (Maybe Text) Source #

The name of a room profile.

pTemperatureUnit :: Lens' Profile (Maybe TemperatureUnit) Source #

The temperature unit of a room profile.

pTimezone :: Lens' Profile (Maybe Text) Source #

The time zone of a room profile.

pMaxVolumeLimit :: Lens' Profile (Maybe Int) Source #

The max volume limit of a room profile.

ProfileData

data ProfileData Source #

The data of a room profile.

See: profileData smart constructor.

Instances

Eq ProfileData Source # 
Data ProfileData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProfileData -> c ProfileData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProfileData #

toConstr :: ProfileData -> Constr #

dataTypeOf :: ProfileData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ProfileData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProfileData) #

gmapT :: (forall b. Data b => b -> b) -> ProfileData -> ProfileData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProfileData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProfileData -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProfileData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProfileData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProfileData -> m ProfileData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProfileData -> m ProfileData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProfileData -> m ProfileData #

Read ProfileData Source # 
Show ProfileData Source # 
Generic ProfileData Source # 

Associated Types

type Rep ProfileData :: * -> * #

Hashable ProfileData Source # 
FromJSON ProfileData Source # 
NFData ProfileData Source # 

Methods

rnf :: ProfileData -> () #

type Rep ProfileData Source # 

profileData :: ProfileData Source #

Creates a value of ProfileData with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pdDistanceUnit :: Lens' ProfileData (Maybe DistanceUnit) Source #

The distance unit of a room profile.

pdAddress :: Lens' ProfileData (Maybe Text) Source #

The address of a room profile.

pdProfileARN :: Lens' ProfileData (Maybe Text) Source #

The ARN of a room profile.

pdWakeWord :: Lens' ProfileData (Maybe WakeWord) Source #

The wake word of a room profile.

pdProfileName :: Lens' ProfileData (Maybe Text) Source #

The name of a room profile.

pdTemperatureUnit :: Lens' ProfileData (Maybe TemperatureUnit) Source #

The temperature unit of a room profile.

pdTimezone :: Lens' ProfileData (Maybe Text) Source #

The timezone of a room profile.

Room

data Room Source #

A room with attributes.

See: room smart constructor.

Instances

Eq Room Source # 

Methods

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

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

Data Room Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Room -> c Room #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Room #

toConstr :: Room -> Constr #

dataTypeOf :: Room -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Room) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Room) #

gmapT :: (forall b. Data b => b -> b) -> Room -> Room #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Room -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Room -> r #

gmapQ :: (forall d. Data d => d -> u) -> Room -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Room -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Room -> m Room #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Room -> m Room #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Room -> m Room #

Read Room Source # 
Show Room Source # 

Methods

showsPrec :: Int -> Room -> ShowS #

show :: Room -> String #

showList :: [Room] -> ShowS #

Generic Room Source # 

Associated Types

type Rep Room :: * -> * #

Methods

from :: Room -> Rep Room x #

to :: Rep Room x -> Room #

Hashable Room Source # 

Methods

hashWithSalt :: Int -> Room -> Int #

hash :: Room -> Int #

FromJSON Room Source # 
NFData Room Source # 

Methods

rnf :: Room -> () #

type Rep Room Source # 
type Rep Room = D1 * (MetaData "Room" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "Room'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_rProfileARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_rProviderCalendarId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rRoomARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rRoomName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_rDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

room :: Room Source #

Creates a value of Room with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rProfileARN :: Lens' Room (Maybe Text) Source #

The profile ARN of a room.

rProviderCalendarId :: Lens' Room (Maybe Text) Source #

The provider calendar ARN of a room.

rRoomARN :: Lens' Room (Maybe Text) Source #

The ARN of a room.

rRoomName :: Lens' Room (Maybe Text) Source #

The name of a room.

rDescription :: Lens' Room (Maybe Text) Source #

The description of a room.

RoomData

data RoomData Source #

The data of a room.

See: roomData smart constructor.

Instances

Eq RoomData Source # 
Data RoomData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RoomData -> c RoomData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RoomData #

toConstr :: RoomData -> Constr #

dataTypeOf :: RoomData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RoomData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RoomData) #

gmapT :: (forall b. Data b => b -> b) -> RoomData -> RoomData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoomData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoomData -> r #

gmapQ :: (forall d. Data d => d -> u) -> RoomData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RoomData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoomData -> m RoomData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoomData -> m RoomData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoomData -> m RoomData #

Read RoomData Source # 
Show RoomData Source # 
Generic RoomData Source # 

Associated Types

type Rep RoomData :: * -> * #

Methods

from :: RoomData -> Rep RoomData x #

to :: Rep RoomData x -> RoomData #

Hashable RoomData Source # 

Methods

hashWithSalt :: Int -> RoomData -> Int #

hash :: RoomData -> Int #

FromJSON RoomData Source # 
NFData RoomData Source # 

Methods

rnf :: RoomData -> () #

type Rep RoomData Source # 
type Rep RoomData = D1 * (MetaData "RoomData" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "RoomData'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_rdProfileARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rdProviderCalendarId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_rdProfileName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rdRoomARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rdRoomName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_rdDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

roomData :: RoomData Source #

Creates a value of RoomData with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rdProfileARN :: Lens' RoomData (Maybe Text) Source #

The profile ARN of a room.

rdProviderCalendarId :: Lens' RoomData (Maybe Text) Source #

The provider calendar ARN of a room.

rdProfileName :: Lens' RoomData (Maybe Text) Source #

The profile name of a room.

rdRoomARN :: Lens' RoomData (Maybe Text) Source #

The ARN of a room.

rdRoomName :: Lens' RoomData (Maybe Text) Source #

The name of a room.

rdDescription :: Lens' RoomData (Maybe Text) Source #

The description of a room.

RoomSkillParameter

data RoomSkillParameter Source #

A skill parameter associated with a room.

See: roomSkillParameter smart constructor.

Instances

Eq RoomSkillParameter Source # 
Data RoomSkillParameter Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RoomSkillParameter -> c RoomSkillParameter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RoomSkillParameter #

toConstr :: RoomSkillParameter -> Constr #

dataTypeOf :: RoomSkillParameter -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RoomSkillParameter) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RoomSkillParameter) #

gmapT :: (forall b. Data b => b -> b) -> RoomSkillParameter -> RoomSkillParameter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoomSkillParameter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoomSkillParameter -> r #

gmapQ :: (forall d. Data d => d -> u) -> RoomSkillParameter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RoomSkillParameter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoomSkillParameter -> m RoomSkillParameter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoomSkillParameter -> m RoomSkillParameter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoomSkillParameter -> m RoomSkillParameter #

Read RoomSkillParameter Source # 
Show RoomSkillParameter Source # 
Generic RoomSkillParameter Source # 
Hashable RoomSkillParameter Source # 
ToJSON RoomSkillParameter Source # 
FromJSON RoomSkillParameter Source # 
NFData RoomSkillParameter Source # 

Methods

rnf :: RoomSkillParameter -> () #

type Rep RoomSkillParameter Source # 
type Rep RoomSkillParameter = D1 * (MetaData "RoomSkillParameter" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "RoomSkillParameter'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_rspParameterKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_rspParameterValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

roomSkillParameter Source #

Creates a value of RoomSkillParameter with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rspParameterKey - The parameter key of a room skill parameter. ParameterKey is an enumerated type that only takes “DEFAULT” or “SCOPE” as valid values.
  • rspParameterValue - The parameter value of a room skill parameter.

rspParameterKey :: Lens' RoomSkillParameter Text Source #

The parameter key of a room skill parameter. ParameterKey is an enumerated type that only takes “DEFAULT” or “SCOPE” as valid values.

rspParameterValue :: Lens' RoomSkillParameter Text Source #

The parameter value of a room skill parameter.

SkillGroup

data SkillGroup Source #

A skill group with attributes.

See: skillGroup smart constructor.

Instances

Eq SkillGroup Source # 
Data SkillGroup Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SkillGroup -> c SkillGroup #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SkillGroup #

toConstr :: SkillGroup -> Constr #

dataTypeOf :: SkillGroup -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SkillGroup) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SkillGroup) #

gmapT :: (forall b. Data b => b -> b) -> SkillGroup -> SkillGroup #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SkillGroup -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SkillGroup -> r #

gmapQ :: (forall d. Data d => d -> u) -> SkillGroup -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SkillGroup -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SkillGroup -> m SkillGroup #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SkillGroup -> m SkillGroup #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SkillGroup -> m SkillGroup #

Read SkillGroup Source # 
Show SkillGroup Source # 
Generic SkillGroup Source # 

Associated Types

type Rep SkillGroup :: * -> * #

Hashable SkillGroup Source # 
FromJSON SkillGroup Source # 
NFData SkillGroup Source # 

Methods

rnf :: SkillGroup -> () #

type Rep SkillGroup Source # 
type Rep SkillGroup = D1 * (MetaData "SkillGroup" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "SkillGroup'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_sgSkillGroupARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_sgDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_sgSkillGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

skillGroup :: SkillGroup Source #

Creates a value of SkillGroup with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sgSkillGroupARN :: Lens' SkillGroup (Maybe Text) Source #

The ARN of a skill group.

sgDescription :: Lens' SkillGroup (Maybe Text) Source #

The description of a skill group.

sgSkillGroupName :: Lens' SkillGroup (Maybe Text) Source #

The name of a skill group.

SkillGroupData

data SkillGroupData Source #

The attributes of a skill group.

See: skillGroupData smart constructor.

Instances

Eq SkillGroupData Source # 
Data SkillGroupData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SkillGroupData -> c SkillGroupData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SkillGroupData #

toConstr :: SkillGroupData -> Constr #

dataTypeOf :: SkillGroupData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SkillGroupData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SkillGroupData) #

gmapT :: (forall b. Data b => b -> b) -> SkillGroupData -> SkillGroupData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SkillGroupData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SkillGroupData -> r #

gmapQ :: (forall d. Data d => d -> u) -> SkillGroupData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SkillGroupData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SkillGroupData -> m SkillGroupData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SkillGroupData -> m SkillGroupData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SkillGroupData -> m SkillGroupData #

Read SkillGroupData Source # 
Show SkillGroupData Source # 
Generic SkillGroupData Source # 

Associated Types

type Rep SkillGroupData :: * -> * #

Hashable SkillGroupData Source # 
FromJSON SkillGroupData Source # 
NFData SkillGroupData Source # 

Methods

rnf :: SkillGroupData -> () #

type Rep SkillGroupData Source # 
type Rep SkillGroupData = D1 * (MetaData "SkillGroupData" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "SkillGroupData'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_sgdSkillGroupARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_sgdDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_sgdSkillGroupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

skillGroupData :: SkillGroupData Source #

Creates a value of SkillGroupData with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sgdSkillGroupARN :: Lens' SkillGroupData (Maybe Text) Source #

The skill group ARN of a skill group.

sgdDescription :: Lens' SkillGroupData (Maybe Text) Source #

The description of a skill group.

sgdSkillGroupName :: Lens' SkillGroupData (Maybe Text) Source #

The skill group name of a skill group.

SkillSummary

data SkillSummary Source #

The summary of skills.

See: skillSummary smart constructor.

Instances

Eq SkillSummary Source # 
Data SkillSummary Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SkillSummary -> c SkillSummary #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SkillSummary #

toConstr :: SkillSummary -> Constr #

dataTypeOf :: SkillSummary -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SkillSummary) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SkillSummary) #

gmapT :: (forall b. Data b => b -> b) -> SkillSummary -> SkillSummary #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SkillSummary -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SkillSummary -> r #

gmapQ :: (forall d. Data d => d -> u) -> SkillSummary -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SkillSummary -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SkillSummary -> m SkillSummary #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SkillSummary -> m SkillSummary #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SkillSummary -> m SkillSummary #

Read SkillSummary Source # 
Show SkillSummary Source # 
Generic SkillSummary Source # 

Associated Types

type Rep SkillSummary :: * -> * #

Hashable SkillSummary Source # 
FromJSON SkillSummary Source # 
NFData SkillSummary Source # 

Methods

rnf :: SkillSummary -> () #

type Rep SkillSummary Source # 
type Rep SkillSummary = D1 * (MetaData "SkillSummary" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "SkillSummary'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ssSkillId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ssSupportsLinking") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_ssSkillName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

skillSummary :: SkillSummary Source #

Creates a value of SkillSummary with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ssSkillId :: Lens' SkillSummary (Maybe Text) Source #

The ARN of the skill summary.

ssSupportsLinking :: Lens' SkillSummary (Maybe Bool) Source #

Linking support for a skill.

ssSkillName :: Lens' SkillSummary (Maybe Text) Source #

The name of the skill.

Sort

data Sort Source #

An object representing a sort criteria.

See: sort smart constructor.

Instances

Eq Sort Source # 

Methods

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

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

Data Sort Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sort -> c Sort #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Sort #

toConstr :: Sort -> Constr #

dataTypeOf :: Sort -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Sort) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sort) #

gmapT :: (forall b. Data b => b -> b) -> Sort -> Sort #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sort -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sort -> r #

gmapQ :: (forall d. Data d => d -> u) -> Sort -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Sort -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sort -> m Sort #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sort -> m Sort #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sort -> m Sort #

Read Sort Source # 
Show Sort Source # 

Methods

showsPrec :: Int -> Sort -> ShowS #

show :: Sort -> String #

showList :: [Sort] -> ShowS #

Generic Sort Source # 

Associated Types

type Rep Sort :: * -> * #

Methods

from :: Sort -> Rep Sort x #

to :: Rep Sort x -> Sort #

Hashable Sort Source # 

Methods

hashWithSalt :: Int -> Sort -> Int #

hash :: Sort -> Int #

ToJSON Sort Source # 
NFData Sort Source # 

Methods

rnf :: Sort -> () #

type Rep Sort Source # 
type Rep Sort = D1 * (MetaData "Sort" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "Sort'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_sKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_sValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SortValue))))

sort Source #

Arguments

:: Text

sKey

-> SortValue

sValue

-> Sort 

Creates a value of Sort with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • sKey - The sort key of a sort object.
  • sValue - The sort value of a sort object.

sKey :: Lens' Sort Text Source #

The sort key of a sort object.

sValue :: Lens' Sort SortValue Source #

The sort value of a sort object.

Tag

data Tag Source #

A key-value pair that can be associated with a resource.

See: tag smart constructor.

Instances

Eq Tag Source # 

Methods

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

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

Data Tag Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tag -> c Tag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tag #

toConstr :: Tag -> Constr #

dataTypeOf :: Tag -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Tag) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag) #

gmapT :: (forall b. Data b => b -> b) -> Tag -> Tag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

Read Tag Source # 
Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 

Associated Types

type Rep Tag :: * -> * #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Hashable Tag Source # 

Methods

hashWithSalt :: Int -> Tag -> Int #

hash :: Tag -> Int #

ToJSON Tag Source # 
FromJSON Tag Source # 
NFData Tag Source # 

Methods

rnf :: Tag -> () #

type Rep Tag Source # 
type Rep Tag = D1 * (MetaData "Tag" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "Tag'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_tagValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tagKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

tag :: Tag Source #

Creates a value of Tag with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • tagValue - The value of a tag. Tag values are case-sensitive and can be null.
  • tagKey - The key of a tag. Tag keys are case-sensitive.

tagValue :: Lens' Tag (Maybe Text) Source #

The value of a tag. Tag values are case-sensitive and can be null.

tagKey :: Lens' Tag (Maybe Text) Source #

The key of a tag. Tag keys are case-sensitive.

UserData

data UserData Source #

Information related to a user.

See: userData smart constructor.

Instances

Eq UserData Source # 
Data UserData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserData -> c UserData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserData #

toConstr :: UserData -> Constr #

dataTypeOf :: UserData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserData) #

gmapT :: (forall b. Data b => b -> b) -> UserData -> UserData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserData -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserData -> m UserData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserData -> m UserData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserData -> m UserData #

Read UserData Source # 
Show UserData Source # 
Generic UserData Source # 

Associated Types

type Rep UserData :: * -> * #

Methods

from :: UserData -> Rep UserData x #

to :: Rep UserData x -> UserData #

Hashable UserData Source # 

Methods

hashWithSalt :: Int -> UserData -> Int #

hash :: UserData -> Int #

FromJSON UserData Source # 
NFData UserData Source # 

Methods

rnf :: UserData -> () #

type Rep UserData Source # 
type Rep UserData = D1 * (MetaData "UserData" "Network.AWS.AlexaBusiness.Types.Product" "amazonka-alexa-business-1.6.0-DI5T43QkJWfD1hlGpmjsnd" False) (C1 * (MetaCons "UserData'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_udEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_udLastName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_udEnrollmentId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_udUserARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_udFirstName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_udEnrollmentStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe EnrollmentStatus)))))))

userData :: UserData Source #

Creates a value of UserData with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

udEmail :: Lens' UserData (Maybe Text) Source #

The email of a user.

udLastName :: Lens' UserData (Maybe Text) Source #

The last name of a user.

udEnrollmentId :: Lens' UserData (Maybe Text) Source #

The enrollment ARN of a user.

udUserARN :: Lens' UserData (Maybe Text) Source #

The ARN of a user.

udFirstName :: Lens' UserData (Maybe Text) Source #

The first name of a user.

udEnrollmentStatus :: Lens' UserData (Maybe EnrollmentStatus) Source #

The enrollment status of a user.