amazonka-workmail-1.6.0: Amazon WorkMail 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.WorkMail.Types

Contents

Description

 

Synopsis

Service Configuration

workMail :: Service Source #

API version 2017-10-01 of the Amazon WorkMail SDK configuration.

Errors

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

The directory that you are trying to perform operations on isn't available.

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

One or more of the input parameters don't match the service's restrictions.

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

You can't perform a write operation against a read-only directory.

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

The Directory Service doesn't recognize the credentials supplied by the Amazon WorkMail service.

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

The organization must have a valid state (Active or Synchronizing) to perform certain operations on the organization or its entities.

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

You are performing an operation on an entity that isn't in the expected state, such as trying to update a deleted user.

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

The configuration for a resource isn't valid. A resource must either be able to auto-respond to requests or have at least one delegate associated that can do it on its behalf.

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

After a domain has been added to the organization, it must be verified. The domain is not yet verified.

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

This entity name is not allowed in Amazon WorkMail.

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

An operation received a valid organization identifier that either doesn't belong or exist in the system.

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

The identifier supplied for the entity is valid, but it does not exist in your organization.

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

The user, group, or resource that you're trying to register is already registered.

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

For an email or alias to be created in Amazon WorkMail, the included domain must be defined in the organization.

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

The email address that you're trying to assign is already created for a different user, group, or resource.

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

The entity (user, group, or user) name isn't unique in Amazon WorkMail.

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

The supplied password doesn't match the minimum security constraints, such as length or use of special characters.

EntityState

data EntityState Source #

Constructors

Deleted 
Disabled 
Enabled 

Instances

Bounded EntityState Source # 
Enum EntityState Source # 
Eq EntityState Source # 
Data EntityState Source # 

Methods

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

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

toConstr :: EntityState -> Constr #

dataTypeOf :: EntityState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EntityState Source # 
Read EntityState Source # 
Show EntityState Source # 
Generic EntityState Source # 

Associated Types

type Rep EntityState :: * -> * #

Hashable EntityState Source # 
FromJSON EntityState Source # 
NFData EntityState Source # 

Methods

rnf :: EntityState -> () #

ToHeader EntityState Source # 
ToQuery EntityState Source # 
ToByteString EntityState Source # 
FromText EntityState Source # 
ToText EntityState Source # 

Methods

toText :: EntityState -> Text #

type Rep EntityState Source # 
type Rep EntityState = D1 * (MetaData "EntityState" "Network.AWS.WorkMail.Types.Sum" "amazonka-workmail-1.6.0-8HAZCS55pFIAg9ZAclEI0R" False) ((:+:) * (C1 * (MetaCons "Deleted" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Disabled" PrefixI False) (U1 *)) (C1 * (MetaCons "Enabled" PrefixI False) (U1 *))))

MemberType

data MemberType Source #

Constructors

Group 
User 

Instances

Bounded MemberType Source # 
Enum MemberType Source # 
Eq MemberType Source # 
Data MemberType Source # 

Methods

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

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

toConstr :: MemberType -> Constr #

dataTypeOf :: MemberType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MemberType Source # 
Read MemberType Source # 
Show MemberType Source # 
Generic MemberType Source # 

Associated Types

type Rep MemberType :: * -> * #

Hashable MemberType Source # 
FromJSON MemberType Source # 
NFData MemberType Source # 

Methods

rnf :: MemberType -> () #

ToHeader MemberType Source # 
ToQuery MemberType Source # 
ToByteString MemberType Source # 
FromText MemberType Source # 
ToText MemberType Source # 

Methods

toText :: MemberType -> Text #

type Rep MemberType Source # 
type Rep MemberType = D1 * (MetaData "MemberType" "Network.AWS.WorkMail.Types.Sum" "amazonka-workmail-1.6.0-8HAZCS55pFIAg9ZAclEI0R" False) ((:+:) * (C1 * (MetaCons "Group" PrefixI False) (U1 *)) (C1 * (MetaCons "User" PrefixI False) (U1 *)))

PermissionType

data PermissionType Source #

Instances

Bounded PermissionType Source # 
Enum PermissionType Source # 
Eq PermissionType Source # 
Data PermissionType Source # 

Methods

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

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

toConstr :: PermissionType -> Constr #

dataTypeOf :: PermissionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PermissionType Source # 
Read PermissionType Source # 
Show PermissionType Source # 
Generic PermissionType Source # 

Associated Types

type Rep PermissionType :: * -> * #

Hashable PermissionType Source # 
ToJSON PermissionType Source # 
FromJSON PermissionType Source # 
NFData PermissionType Source # 

Methods

rnf :: PermissionType -> () #

ToHeader PermissionType Source # 
ToQuery PermissionType Source # 
ToByteString PermissionType Source # 
FromText PermissionType Source # 
ToText PermissionType Source # 
type Rep PermissionType Source # 
type Rep PermissionType = D1 * (MetaData "PermissionType" "Network.AWS.WorkMail.Types.Sum" "amazonka-workmail-1.6.0-8HAZCS55pFIAg9ZAclEI0R" False) ((:+:) * (C1 * (MetaCons "FullAccess" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SendAs" PrefixI False) (U1 *)) (C1 * (MetaCons "SendOnBehalf" PrefixI False) (U1 *))))

ResourceType

data ResourceType Source #

Constructors

Equipment 
Room 

Instances

Bounded ResourceType Source # 
Enum ResourceType Source # 
Eq ResourceType Source # 
Data ResourceType Source # 

Methods

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

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

toConstr :: ResourceType -> Constr #

dataTypeOf :: ResourceType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ResourceType Source # 
Read ResourceType Source # 
Show ResourceType Source # 
Generic ResourceType Source # 

Associated Types

type Rep ResourceType :: * -> * #

Hashable ResourceType Source # 
ToJSON ResourceType Source # 
FromJSON ResourceType Source # 
NFData ResourceType Source # 

Methods

rnf :: ResourceType -> () #

ToHeader ResourceType Source # 
ToQuery ResourceType Source # 
ToByteString ResourceType Source # 
FromText ResourceType Source # 
ToText ResourceType Source # 

Methods

toText :: ResourceType -> Text #

type Rep ResourceType Source # 
type Rep ResourceType = D1 * (MetaData "ResourceType" "Network.AWS.WorkMail.Types.Sum" "amazonka-workmail-1.6.0-8HAZCS55pFIAg9ZAclEI0R" False) ((:+:) * (C1 * (MetaCons "Equipment" PrefixI False) (U1 *)) (C1 * (MetaCons "Room" PrefixI False) (U1 *)))

UserRole

data UserRole Source #

Instances

Bounded UserRole Source # 
Enum UserRole Source # 
Eq UserRole Source # 
Data UserRole Source # 

Methods

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

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

toConstr :: UserRole -> Constr #

dataTypeOf :: UserRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UserRole Source # 
Read UserRole Source # 
Show UserRole Source # 
Generic UserRole Source # 

Associated Types

type Rep UserRole :: * -> * #

Methods

from :: UserRole -> Rep UserRole x #

to :: Rep UserRole x -> UserRole #

Hashable UserRole Source # 

Methods

hashWithSalt :: Int -> UserRole -> Int #

hash :: UserRole -> Int #

FromJSON UserRole Source # 
NFData UserRole Source # 

Methods

rnf :: UserRole -> () #

ToHeader UserRole Source # 

Methods

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

ToQuery UserRole Source # 
ToByteString UserRole Source # 

Methods

toBS :: UserRole -> ByteString #

FromText UserRole Source # 
ToText UserRole Source # 

Methods

toText :: UserRole -> Text #

type Rep UserRole Source # 
type Rep UserRole = D1 * (MetaData "UserRole" "Network.AWS.WorkMail.Types.Sum" "amazonka-workmail-1.6.0-8HAZCS55pFIAg9ZAclEI0R" False) ((:+:) * (C1 * (MetaCons "URResource" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "URSystemUser" PrefixI False) (U1 *)) (C1 * (MetaCons "URUser" PrefixI False) (U1 *))))

BookingOptions

data BookingOptions Source #

At least one delegate must be associated to the resource to disable automatic replies from the resource.

See: bookingOptions smart constructor.

Instances

Eq BookingOptions Source # 
Data BookingOptions Source # 

Methods

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

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

toConstr :: BookingOptions -> Constr #

dataTypeOf :: BookingOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BookingOptions Source # 
Show BookingOptions Source # 
Generic BookingOptions Source # 

Associated Types

type Rep BookingOptions :: * -> * #

Hashable BookingOptions Source # 
ToJSON BookingOptions Source # 
FromJSON BookingOptions Source # 
NFData BookingOptions Source # 

Methods

rnf :: BookingOptions -> () #

type Rep BookingOptions Source # 
type Rep BookingOptions = D1 * (MetaData "BookingOptions" "Network.AWS.WorkMail.Types.Product" "amazonka-workmail-1.6.0-8HAZCS55pFIAg9ZAclEI0R" False) (C1 * (MetaCons "BookingOptions'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_boAutoDeclineConflictingRequests") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_boAutoDeclineRecurringRequests") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_boAutoAcceptRequests") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))))))

bookingOptions :: BookingOptions Source #

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

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

boAutoDeclineConflictingRequests :: Lens' BookingOptions (Maybe Bool) Source #

The resource's ability to automatically decline any conflicting requests.

boAutoDeclineRecurringRequests :: Lens' BookingOptions (Maybe Bool) Source #

The resource's ability to automatically decline any recurring requests.

boAutoAcceptRequests :: Lens' BookingOptions (Maybe Bool) Source #

The resource's ability to automatically reply to requests. If disabled, delegates must be associated to the resource.

Delegate

data Delegate Source #

The name of the attribute, which is one of the values defined in the UserAttribute enumeration.

See: delegate smart constructor.

Instances

Eq Delegate Source # 
Data Delegate Source # 

Methods

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

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

toConstr :: Delegate -> Constr #

dataTypeOf :: Delegate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Delegate Source # 
Show Delegate Source # 
Generic Delegate Source # 

Associated Types

type Rep Delegate :: * -> * #

Methods

from :: Delegate -> Rep Delegate x #

to :: Rep Delegate x -> Delegate #

Hashable Delegate Source # 

Methods

hashWithSalt :: Int -> Delegate -> Int #

hash :: Delegate -> Int #

FromJSON Delegate Source # 
NFData Delegate Source # 

Methods

rnf :: Delegate -> () #

type Rep Delegate Source # 
type Rep Delegate = D1 * (MetaData "Delegate" "Network.AWS.WorkMail.Types.Product" "amazonka-workmail-1.6.0-8HAZCS55pFIAg9ZAclEI0R" False) (C1 * (MetaCons "Delegate'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_dId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_dType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MemberType))))

delegate Source #

Arguments

:: Text

dId

-> MemberType

dType

-> Delegate 

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

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

  • dId - The identifier for the user or group is associated as the resource's delegate.
  • dType - The type of the delegate: user or group.

dId :: Lens' Delegate Text Source #

The identifier for the user or group is associated as the resource's delegate.

dType :: Lens' Delegate MemberType Source #

The type of the delegate: user or group.

Group

data Group Source #

The representation of an Amazon WorkMail group.

See: group' smart constructor.

Instances

Eq Group Source # 

Methods

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

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

Data Group Source # 

Methods

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

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

toConstr :: Group -> Constr #

dataTypeOf :: Group -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Group Source # 
Show Group Source # 

Methods

showsPrec :: Int -> Group -> ShowS #

show :: Group -> String #

showList :: [Group] -> ShowS #

Generic Group Source # 

Associated Types

type Rep Group :: * -> * #

Methods

from :: Group -> Rep Group x #

to :: Rep Group x -> Group #

Hashable Group Source # 

Methods

hashWithSalt :: Int -> Group -> Int #

hash :: Group -> Int #

FromJSON Group Source # 
NFData Group Source # 

Methods

rnf :: Group -> () #

type Rep Group Source # 

group' :: Group Source #

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

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

  • gEmail - The email of the group.
  • gState - The state of the group, which can be ENABLED, DISABLED, or DELETED.
  • gDisabledDate - The date indicating when the group was disabled from Amazon WorkMail use.
  • gName - The name of the group.
  • gId - The identifier of the group.
  • gEnabledDate - The date indicating when the group was enabled for Amazon WorkMail use.

gEmail :: Lens' Group (Maybe Text) Source #

The email of the group.

gState :: Lens' Group (Maybe EntityState) Source #

The state of the group, which can be ENABLED, DISABLED, or DELETED.

gDisabledDate :: Lens' Group (Maybe UTCTime) Source #

The date indicating when the group was disabled from Amazon WorkMail use.

gName :: Lens' Group (Maybe Text) Source #

The name of the group.

gId :: Lens' Group (Maybe Text) Source #

The identifier of the group.

gEnabledDate :: Lens' Group (Maybe UTCTime) Source #

The date indicating when the group was enabled for Amazon WorkMail use.

Member

data Member Source #

The representation of a group member (user or group).

See: member smart constructor.

Instances

Eq Member Source # 

Methods

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

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

Data Member Source # 

Methods

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

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

toConstr :: Member -> Constr #

dataTypeOf :: Member -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Member Source # 
Show Member Source # 
Generic Member Source # 

Associated Types

type Rep Member :: * -> * #

Methods

from :: Member -> Rep Member x #

to :: Rep Member x -> Member #

Hashable Member Source # 

Methods

hashWithSalt :: Int -> Member -> Int #

hash :: Member -> Int #

FromJSON Member Source # 
NFData Member Source # 

Methods

rnf :: Member -> () #

type Rep Member Source # 

member :: Member Source #

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

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

  • mState - The state of the member, which can be ENABLED, DISABLED, or DELETED.
  • mDisabledDate - The date indicating when the member was disabled from Amazon WorkMail use.
  • mName - The name of the member.
  • mId - The identifier of the member.
  • mType - A member can be a user or group.
  • mEnabledDate - The date indicating when the member was enabled for Amazon WorkMail use.

mState :: Lens' Member (Maybe EntityState) Source #

The state of the member, which can be ENABLED, DISABLED, or DELETED.

mDisabledDate :: Lens' Member (Maybe UTCTime) Source #

The date indicating when the member was disabled from Amazon WorkMail use.

mName :: Lens' Member (Maybe Text) Source #

The name of the member.

mId :: Lens' Member (Maybe Text) Source #

The identifier of the member.

mType :: Lens' Member (Maybe MemberType) Source #

A member can be a user or group.

mEnabledDate :: Lens' Member (Maybe UTCTime) Source #

The date indicating when the member was enabled for Amazon WorkMail use.

OrganizationSummary

data OrganizationSummary Source #

The brief overview associated with an organization.

See: organizationSummary smart constructor.

Instances

Eq OrganizationSummary Source # 
Data OrganizationSummary Source # 

Methods

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

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

toConstr :: OrganizationSummary -> Constr #

dataTypeOf :: OrganizationSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: OrganizationSummary -> () #

type Rep OrganizationSummary Source # 
type Rep OrganizationSummary = D1 * (MetaData "OrganizationSummary" "Network.AWS.WorkMail.Types.Product" "amazonka-workmail-1.6.0-8HAZCS55pFIAg9ZAclEI0R" False) (C1 * (MetaCons "OrganizationSummary'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_osState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_osAlias") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_osErrorMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_osOrganizationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

organizationSummary :: OrganizationSummary Source #

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

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

  • osState - The state associated with the organization.
  • osAlias - The alias associated with the organization.
  • osErrorMessage - The error message associated with the organization. It is only present if unexpected behavior has occurred with regards to the organization. It provides insight or solutions regarding unexpected behavior.
  • osOrganizationId - The identifier associated with the organization.

osState :: Lens' OrganizationSummary (Maybe Text) Source #

The state associated with the organization.

osAlias :: Lens' OrganizationSummary (Maybe Text) Source #

The alias associated with the organization.

osErrorMessage :: Lens' OrganizationSummary (Maybe Text) Source #

The error message associated with the organization. It is only present if unexpected behavior has occurred with regards to the organization. It provides insight or solutions regarding unexpected behavior.

osOrganizationId :: Lens' OrganizationSummary (Maybe Text) Source #

The identifier associated with the organization.

Permission

data Permission Source #

Permission granted to an entity (user, group) to access a certain aspect of another entity's mailbox.

See: permission smart constructor.

Instances

Eq Permission Source # 
Data Permission Source # 

Methods

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

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

toConstr :: Permission -> Constr #

dataTypeOf :: Permission -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Permission Source # 
Show Permission Source # 
Generic Permission Source # 

Associated Types

type Rep Permission :: * -> * #

Hashable Permission Source # 
FromJSON Permission Source # 
NFData Permission Source # 

Methods

rnf :: Permission -> () #

type Rep Permission Source # 
type Rep Permission = D1 * (MetaData "Permission" "Network.AWS.WorkMail.Types.Product" "amazonka-workmail-1.6.0-8HAZCS55pFIAg9ZAclEI0R" False) (C1 * (MetaCons "Permission'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_pGranteeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "_pGranteeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MemberType)) (S1 * (MetaSel (Just Symbol "_pPermissionValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [PermissionType])))))

permission Source #

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

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

  • pGranteeId - The identifier of the entity (user or group) to which the permissions are granted.
  • pGranteeType - The type of entity (user, group) of the entity referred to in GranteeId.
  • pPermissionValues - The permissions granted to the grantee. SEND_AS allows the grantee to send email as the owner of the mailbox (the grantee is not mentioned on these emails). SEND_ON_BEHALF allows the grantee to send email on behalf of the owner of the mailbox (the grantee is not mentioned as the physical sender of these emails). FULL_ACCESS allows the grantee full access to the mailbox, irrespective of other folder-level permissions set on the mailbox.

pGranteeId :: Lens' Permission Text Source #

The identifier of the entity (user or group) to which the permissions are granted.

pGranteeType :: Lens' Permission MemberType Source #

The type of entity (user, group) of the entity referred to in GranteeId.

pPermissionValues :: Lens' Permission [PermissionType] Source #

The permissions granted to the grantee. SEND_AS allows the grantee to send email as the owner of the mailbox (the grantee is not mentioned on these emails). SEND_ON_BEHALF allows the grantee to send email on behalf of the owner of the mailbox (the grantee is not mentioned as the physical sender of these emails). FULL_ACCESS allows the grantee full access to the mailbox, irrespective of other folder-level permissions set on the mailbox.

Resource

data Resource Source #

The overview for a resource containing relevant data regarding it.

See: resource smart constructor.

Instances

Eq Resource Source # 
Data Resource Source # 

Methods

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

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

toConstr :: Resource -> Constr #

dataTypeOf :: Resource -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Resource Source # 
Show Resource Source # 
Generic Resource Source # 

Associated Types

type Rep Resource :: * -> * #

Methods

from :: Resource -> Rep Resource x #

to :: Rep Resource x -> Resource #

Hashable Resource Source # 

Methods

hashWithSalt :: Int -> Resource -> Int #

hash :: Resource -> Int #

FromJSON Resource Source # 
NFData Resource Source # 

Methods

rnf :: Resource -> () #

type Rep Resource Source # 

resource :: Resource Source #

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

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

  • rEmail - The email of the resource.
  • rState - The state of the resource, which can be ENABLED, DISABLED, or DELETED.
  • rDisabledDate - The date indicating when the resource was disabled from Amazon WorkMail use.
  • rName - The name of the resource.
  • rId - The identifier of the resource.
  • rType - The type of the resource: equipment or room.
  • rEnabledDate - The date indicating when the resource was enabled for Amazon WorkMail use.

rEmail :: Lens' Resource (Maybe Text) Source #

The email of the resource.

rState :: Lens' Resource (Maybe EntityState) Source #

The state of the resource, which can be ENABLED, DISABLED, or DELETED.

rDisabledDate :: Lens' Resource (Maybe UTCTime) Source #

The date indicating when the resource was disabled from Amazon WorkMail use.

rName :: Lens' Resource (Maybe Text) Source #

The name of the resource.

rId :: Lens' Resource (Maybe Text) Source #

The identifier of the resource.

rType :: Lens' Resource (Maybe ResourceType) Source #

The type of the resource: equipment or room.

rEnabledDate :: Lens' Resource (Maybe UTCTime) Source #

The date indicating when the resource was enabled for Amazon WorkMail use.

User

data User Source #

The representation of an Amazon WorkMail user.

See: user smart constructor.

Instances

Eq User Source # 

Methods

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

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

Data User Source # 

Methods

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

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

toConstr :: User -> Constr #

dataTypeOf :: User -> DataType #

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

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

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

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

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

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

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

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

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

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

Read User Source # 
Show User Source # 

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

Generic User Source # 

Associated Types

type Rep User :: * -> * #

Methods

from :: User -> Rep User x #

to :: Rep User x -> User #

Hashable User Source # 

Methods

hashWithSalt :: Int -> User -> Int #

hash :: User -> Int #

FromJSON User Source # 
NFData User Source # 

Methods

rnf :: User -> () #

type Rep User Source # 

user :: User Source #

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

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

  • uEmail - The email of the user.
  • uState - The state of the user, which can be ENABLED, DISABLED, or DELETED.
  • uDisabledDate - The date indicating when the user was disabled from Amazon WorkMail use.
  • uName - The name of the user.
  • uId - The identifier of the user.
  • uDisplayName - The display name of the user.
  • uUserRole - The role of the user.
  • uEnabledDate - The date indicating when the user was enabled for Amazon WorkMail use.

uEmail :: Lens' User (Maybe Text) Source #

The email of the user.

uState :: Lens' User (Maybe EntityState) Source #

The state of the user, which can be ENABLED, DISABLED, or DELETED.

uDisabledDate :: Lens' User (Maybe UTCTime) Source #

The date indicating when the user was disabled from Amazon WorkMail use.

uName :: Lens' User (Maybe Text) Source #

The name of the user.

uId :: Lens' User (Maybe Text) Source #

The identifier of the user.

uDisplayName :: Lens' User (Maybe Text) Source #

The display name of the user.

uUserRole :: Lens' User (Maybe UserRole) Source #

The role of the user.

uEnabledDate :: Lens' User (Maybe UTCTime) Source #

The date indicating when the user was enabled for Amazon WorkMail use.