amazonka-mq-1.6.0: Amazon MQ 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.MQ.Types

Contents

Description

 

Synopsis

Service Configuration

mq :: Service Source #

API version 2017-11-27 of the Amazon MQ SDK configuration.

Errors

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

Returns information about an error.

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

Returns information about an error.

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

Returns information about an error.

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

Returns information about an error.

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

Returns information about an error.

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

Returns information about an error.

BrokerState

data BrokerState Source #

The status of the broker. Possible values: CREATION_IN_PROGRESS, CREATION_FAILED, DELETION_IN_PROGRESS, RUNNING, REBOOT_IN_PROGRESS

Instances

Bounded BrokerState Source # 
Enum BrokerState Source # 
Eq BrokerState Source # 
Data BrokerState Source # 

Methods

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

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

toConstr :: BrokerState -> Constr #

dataTypeOf :: BrokerState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BrokerState Source # 
Read BrokerState Source # 
Show BrokerState Source # 
Generic BrokerState Source # 

Associated Types

type Rep BrokerState :: * -> * #

Hashable BrokerState Source # 
FromJSON BrokerState Source # 
NFData BrokerState Source # 

Methods

rnf :: BrokerState -> () #

ToHeader BrokerState Source # 
ToQuery BrokerState Source # 
ToByteString BrokerState Source # 
FromText BrokerState Source # 
ToText BrokerState Source # 

Methods

toText :: BrokerState -> Text #

type Rep BrokerState Source # 
type Rep BrokerState = D1 * (MetaData "BrokerState" "Network.AWS.MQ.Types.Sum" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) ((:+:) * ((:+:) * (C1 * (MetaCons "CreationFailed" PrefixI False) (U1 *)) (C1 * (MetaCons "CreationInProgress" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "DeletionInProgress" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "RebootInProgress" PrefixI False) (U1 *)) (C1 * (MetaCons "Running" PrefixI False) (U1 *)))))

ChangeType

data ChangeType Source #

The type of change pending for the ActiveMQ user. Possible values: CREATE, UPDATE, DELETE

Constructors

Create 
Delete 
Update 

Instances

Bounded ChangeType Source # 
Enum ChangeType Source # 
Eq ChangeType Source # 
Data ChangeType Source # 

Methods

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

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

toConstr :: ChangeType -> Constr #

dataTypeOf :: ChangeType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ChangeType Source # 
Read ChangeType Source # 
Show ChangeType Source # 
Generic ChangeType Source # 

Associated Types

type Rep ChangeType :: * -> * #

Hashable ChangeType Source # 
FromJSON ChangeType Source # 
NFData ChangeType Source # 

Methods

rnf :: ChangeType -> () #

ToHeader ChangeType Source # 
ToQuery ChangeType Source # 
ToByteString ChangeType Source # 
FromText ChangeType Source # 
ToText ChangeType Source # 

Methods

toText :: ChangeType -> Text #

type Rep ChangeType Source # 
type Rep ChangeType = D1 * (MetaData "ChangeType" "Network.AWS.MQ.Types.Sum" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) ((:+:) * (C1 * (MetaCons "Create" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Delete" PrefixI False) (U1 *)) (C1 * (MetaCons "Update" PrefixI False) (U1 *))))

DayOfWeek

data DayOfWeek Source #

Instances

Bounded DayOfWeek Source # 
Enum DayOfWeek Source # 
Eq DayOfWeek Source # 
Data DayOfWeek Source # 

Methods

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

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

toConstr :: DayOfWeek -> Constr #

dataTypeOf :: DayOfWeek -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DayOfWeek Source # 
Read DayOfWeek Source # 
Show DayOfWeek Source # 
Generic DayOfWeek Source # 

Associated Types

type Rep DayOfWeek :: * -> * #

Hashable DayOfWeek Source # 
ToJSON DayOfWeek Source # 
FromJSON DayOfWeek Source # 
NFData DayOfWeek Source # 

Methods

rnf :: DayOfWeek -> () #

ToHeader DayOfWeek Source # 
ToQuery DayOfWeek Source # 
ToByteString DayOfWeek Source # 

Methods

toBS :: DayOfWeek -> ByteString #

FromText DayOfWeek Source # 
ToText DayOfWeek Source # 

Methods

toText :: DayOfWeek -> Text #

type Rep DayOfWeek Source # 
type Rep DayOfWeek = D1 * (MetaData "DayOfWeek" "Network.AWS.MQ.Types.Sum" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Friday" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Monday" PrefixI False) (U1 *)) (C1 * (MetaCons "Saturday" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Sunday" PrefixI False) (U1 *)) (C1 * (MetaCons "Thursday" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Tuesday" PrefixI False) (U1 *)) (C1 * (MetaCons "Wednesday" PrefixI False) (U1 *)))))

DeploymentMode

data DeploymentMode Source #

The deployment mode of the broker. Possible values: SINGLE_INSTANCE, ACTIVE_STANDBY_MULTI_AZ SINGLE_INSTANCE creates a single-instance broker in a single Availability Zone. ACTIVE_STANDBY_MULTI_AZ creates an active/standby broker for high availability.

Instances

Bounded DeploymentMode Source # 
Enum DeploymentMode Source # 
Eq DeploymentMode Source # 
Data DeploymentMode Source # 

Methods

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

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

toConstr :: DeploymentMode -> Constr #

dataTypeOf :: DeploymentMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DeploymentMode Source # 
Read DeploymentMode Source # 
Show DeploymentMode Source # 
Generic DeploymentMode Source # 

Associated Types

type Rep DeploymentMode :: * -> * #

Hashable DeploymentMode Source # 
ToJSON DeploymentMode Source # 
FromJSON DeploymentMode Source # 
NFData DeploymentMode Source # 

Methods

rnf :: DeploymentMode -> () #

ToHeader DeploymentMode Source # 
ToQuery DeploymentMode Source # 
ToByteString DeploymentMode Source # 
FromText DeploymentMode Source # 
ToText DeploymentMode Source # 
type Rep DeploymentMode Source # 
type Rep DeploymentMode = D1 * (MetaData "DeploymentMode" "Network.AWS.MQ.Types.Sum" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) ((:+:) * (C1 * (MetaCons "ActiveStandbyMultiAz" PrefixI False) (U1 *)) (C1 * (MetaCons "SingleInstance" PrefixI False) (U1 *)))

EngineType

data EngineType Source #

The type of broker engine. Note: Currently, Amazon MQ supports only ActiveMQ.

Constructors

Activemq 

Instances

Bounded EngineType Source # 
Enum EngineType Source # 
Eq EngineType Source # 
Data EngineType Source # 

Methods

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

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

toConstr :: EngineType -> Constr #

dataTypeOf :: EngineType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EngineType Source # 
Read EngineType Source # 
Show EngineType Source # 
Generic EngineType Source # 

Associated Types

type Rep EngineType :: * -> * #

Hashable EngineType Source # 
ToJSON EngineType Source # 
FromJSON EngineType Source # 
NFData EngineType Source # 

Methods

rnf :: EngineType -> () #

ToHeader EngineType Source # 
ToQuery EngineType Source # 
ToByteString EngineType Source # 
FromText EngineType Source # 
ToText EngineType Source # 

Methods

toText :: EngineType -> Text #

type Rep EngineType Source # 
type Rep EngineType = D1 * (MetaData "EngineType" "Network.AWS.MQ.Types.Sum" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) (C1 * (MetaCons "Activemq" PrefixI False) (U1 *))

SanitizationWarningReason

data SanitizationWarningReason Source #

The reason for which the XML elements or attributes were sanitized. Possible values: DISALLOWED_ELEMENT_REMOVED, DISALLOWED_ATTRIBUTE_REMOVED, INVALID_ATTRIBUTE_VALUE_REMOVED DISALLOWED_ELEMENT_REMOVED shows that the provided element isn't allowed and has been removed. DISALLOWED_ATTRIBUTE_REMOVED shows that the provided attribute isn't allowed and has been removed. INVALID_ATTRIBUTE_VALUE_REMOVED shows that the provided value for the attribute isn't allowed and has been removed.

Instances

Bounded SanitizationWarningReason Source # 
Enum SanitizationWarningReason Source # 
Eq SanitizationWarningReason Source # 
Data SanitizationWarningReason Source # 

Methods

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

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

toConstr :: SanitizationWarningReason -> Constr #

dataTypeOf :: SanitizationWarningReason -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SanitizationWarningReason Source # 
Read SanitizationWarningReason Source # 
Show SanitizationWarningReason Source # 
Generic SanitizationWarningReason Source # 
Hashable SanitizationWarningReason Source # 
FromJSON SanitizationWarningReason Source # 
NFData SanitizationWarningReason Source # 
ToHeader SanitizationWarningReason Source # 
ToQuery SanitizationWarningReason Source # 
ToByteString SanitizationWarningReason Source # 
FromText SanitizationWarningReason Source # 
ToText SanitizationWarningReason Source # 
type Rep SanitizationWarningReason Source # 
type Rep SanitizationWarningReason = D1 * (MetaData "SanitizationWarningReason" "Network.AWS.MQ.Types.Sum" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) ((:+:) * (C1 * (MetaCons "DisallowedAttributeRemoved" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "DisallowedElementRemoved" PrefixI False) (U1 *)) (C1 * (MetaCons "InvalidAttributeValueRemoved" PrefixI False) (U1 *))))

BrokerInstance

data BrokerInstance Source #

Returns information about all brokers.

See: brokerInstance smart constructor.

Instances

Eq BrokerInstance Source # 
Data BrokerInstance Source # 

Methods

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

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

toConstr :: BrokerInstance -> Constr #

dataTypeOf :: BrokerInstance -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BrokerInstance Source # 
Show BrokerInstance Source # 
Generic BrokerInstance Source # 

Associated Types

type Rep BrokerInstance :: * -> * #

Hashable BrokerInstance Source # 
FromJSON BrokerInstance Source # 
NFData BrokerInstance Source # 

Methods

rnf :: BrokerInstance -> () #

type Rep BrokerInstance Source # 
type Rep BrokerInstance = D1 * (MetaData "BrokerInstance" "Network.AWS.MQ.Types.Product" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) (C1 * (MetaCons "BrokerInstance'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_biConsoleURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_biEndpoints") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text])))))

brokerInstance :: BrokerInstance Source #

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

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

  • biConsoleURL - The URL of the broker's ActiveMQ Web Console.
  • biEndpoints - The broker's wire-level protocol endpoints.

biConsoleURL :: Lens' BrokerInstance (Maybe Text) Source #

The URL of the broker's ActiveMQ Web Console.

biEndpoints :: Lens' BrokerInstance [Text] Source #

The broker's wire-level protocol endpoints.

BrokerSummary

data BrokerSummary Source #

The Amazon Resource Name (ARN) of the broker.

See: brokerSummary smart constructor.

Instances

Eq BrokerSummary Source # 
Data BrokerSummary Source # 

Methods

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

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

toConstr :: BrokerSummary -> Constr #

dataTypeOf :: BrokerSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BrokerSummary Source # 
Show BrokerSummary Source # 
Generic BrokerSummary Source # 

Associated Types

type Rep BrokerSummary :: * -> * #

Hashable BrokerSummary Source # 
FromJSON BrokerSummary Source # 
NFData BrokerSummary Source # 

Methods

rnf :: BrokerSummary -> () #

type Rep BrokerSummary Source # 
type Rep BrokerSummary = D1 * (MetaData "BrokerSummary" "Network.AWS.MQ.Types.Product" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) (C1 * (MetaCons "BrokerSummary'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_bsBrokerName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bsBrokerState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe BrokerState))) (S1 * (MetaSel (Just Symbol "_bsDeploymentMode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DeploymentMode))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bsBrokerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bsBrokerARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_bsHostInstanceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

brokerSummary :: BrokerSummary Source #

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

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

  • bsBrokerName - The name of the broker. This value must be unique in your AWS account, 1-50 characters long, must contain only letters, numbers, dashes, and underscores, and must not contain whitespaces, brackets, wildcard characters, or special characters.
  • bsBrokerState - The status of the broker. Possible values: CREATION_IN_PROGRESS, CREATION_FAILED, DELETION_IN_PROGRESS, RUNNING, REBOOT_IN_PROGRESS
  • bsDeploymentMode - Required. The deployment mode of the broker. Possible values: SINGLE_INSTANCE, ACTIVE_STANDBY_MULTI_AZ SINGLE_INSTANCE creates a single-instance broker in a single Availability Zone. ACTIVE_STANDBY_MULTI_AZ creates an active/standby broker for high availability.
  • bsBrokerId - The unique ID that Amazon MQ generates for the broker.
  • bsBrokerARN - The Amazon Resource Name (ARN) of the broker.
  • bsHostInstanceType - The broker's instance type. Possible values: mq.t2.micro, mq.m4.large

bsBrokerName :: Lens' BrokerSummary (Maybe Text) Source #

The name of the broker. This value must be unique in your AWS account, 1-50 characters long, must contain only letters, numbers, dashes, and underscores, and must not contain whitespaces, brackets, wildcard characters, or special characters.

bsBrokerState :: Lens' BrokerSummary (Maybe BrokerState) Source #

The status of the broker. Possible values: CREATION_IN_PROGRESS, CREATION_FAILED, DELETION_IN_PROGRESS, RUNNING, REBOOT_IN_PROGRESS

bsDeploymentMode :: Lens' BrokerSummary (Maybe DeploymentMode) Source #

Required. The deployment mode of the broker. Possible values: SINGLE_INSTANCE, ACTIVE_STANDBY_MULTI_AZ SINGLE_INSTANCE creates a single-instance broker in a single Availability Zone. ACTIVE_STANDBY_MULTI_AZ creates an active/standby broker for high availability.

bsBrokerId :: Lens' BrokerSummary (Maybe Text) Source #

The unique ID that Amazon MQ generates for the broker.

bsBrokerARN :: Lens' BrokerSummary (Maybe Text) Source #

The Amazon Resource Name (ARN) of the broker.

bsHostInstanceType :: Lens' BrokerSummary (Maybe Text) Source #

The broker's instance type. Possible values: mq.t2.micro, mq.m4.large

Configuration

data Configuration Source #

Returns information about all configurations.

See: configuration smart constructor.

Instances

Eq Configuration Source # 
Data Configuration Source # 

Methods

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

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

toConstr :: Configuration -> Constr #

dataTypeOf :: Configuration -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Configuration Source # 
Show Configuration Source # 
Generic Configuration Source # 

Associated Types

type Rep Configuration :: * -> * #

Hashable Configuration Source # 
FromJSON Configuration Source # 
NFData Configuration Source # 

Methods

rnf :: Configuration -> () #

type Rep Configuration Source # 

configuration :: Configuration Source #

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

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

  • cEngineVersion - Required. The version of the broker engine.
  • cARN - Required. The ARN of the configuration.
  • cLatestRevision - Required. The latest revision of the configuration.
  • cName - Required. The name of the configuration. This value can contain only alphanumeric characters, dashes, periods, underscores, and tildes (- . _ ~). This value must be 1-150 characters long.
  • cId - Required. The unique ID that Amazon MQ generates for the configuration.
  • cDescription - Required. The description of the configuration.
  • cEngineType - Required. The type of broker engine. Note: Currently, Amazon MQ supports only ACTIVEMQ.

cEngineVersion :: Lens' Configuration (Maybe Text) Source #

Required. The version of the broker engine.

cARN :: Lens' Configuration (Maybe Text) Source #

Required. The ARN of the configuration.

cLatestRevision :: Lens' Configuration (Maybe ConfigurationRevision) Source #

Required. The latest revision of the configuration.

cName :: Lens' Configuration (Maybe Text) Source #

Required. The name of the configuration. This value can contain only alphanumeric characters, dashes, periods, underscores, and tildes (- . _ ~). This value must be 1-150 characters long.

cId :: Lens' Configuration (Maybe Text) Source #

Required. The unique ID that Amazon MQ generates for the configuration.

cDescription :: Lens' Configuration (Maybe Text) Source #

Required. The description of the configuration.

cEngineType :: Lens' Configuration (Maybe EngineType) Source #

Required. The type of broker engine. Note: Currently, Amazon MQ supports only ACTIVEMQ.

ConfigurationId

data ConfigurationId Source #

A list of information about the configuration.

See: configurationId smart constructor.

Instances

Eq ConfigurationId Source # 
Data ConfigurationId Source # 

Methods

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

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

toConstr :: ConfigurationId -> Constr #

dataTypeOf :: ConfigurationId -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ConfigurationId -> () #

type Rep ConfigurationId Source # 
type Rep ConfigurationId = D1 * (MetaData "ConfigurationId" "Network.AWS.MQ.Types.Product" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) (C1 * (MetaCons "ConfigurationId'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ciId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_ciRevision") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))))

configurationId :: ConfigurationId Source #

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

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

  • ciId - Required. The unique ID that Amazon MQ generates for the configuration.
  • ciRevision - The Universally Unique Identifier (UUID) of the request.

ciId :: Lens' ConfigurationId (Maybe Text) Source #

Required. The unique ID that Amazon MQ generates for the configuration.

ciRevision :: Lens' ConfigurationId (Maybe Int) Source #

The Universally Unique Identifier (UUID) of the request.

ConfigurationRevision

data ConfigurationRevision Source #

Returns information about the specified configuration revision.

See: configurationRevision smart constructor.

Instances

Eq ConfigurationRevision Source # 
Data ConfigurationRevision Source # 

Methods

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

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

toConstr :: ConfigurationRevision -> Constr #

dataTypeOf :: ConfigurationRevision -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ConfigurationRevision -> () #

type Rep ConfigurationRevision Source # 
type Rep ConfigurationRevision = D1 * (MetaData "ConfigurationRevision" "Network.AWS.MQ.Types.Product" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) (C1 * (MetaCons "ConfigurationRevision'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_crRevision") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_crDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

configurationRevision :: ConfigurationRevision Source #

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

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

  • crRevision - Required. The revision of the configuration.
  • crDescription - The description of the configuration revision.

crRevision :: Lens' ConfigurationRevision (Maybe Int) Source #

Required. The revision of the configuration.

crDescription :: Lens' ConfigurationRevision (Maybe Text) Source #

The description of the configuration revision.

Configurations

data Configurations Source #

Broker configuration information

See: configurations smart constructor.

Instances

Eq Configurations Source # 
Data Configurations Source # 

Methods

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

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

toConstr :: Configurations -> Constr #

dataTypeOf :: Configurations -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Configurations Source # 
Show Configurations Source # 
Generic Configurations Source # 

Associated Types

type Rep Configurations :: * -> * #

Hashable Configurations Source # 
FromJSON Configurations Source # 
NFData Configurations Source # 

Methods

rnf :: Configurations -> () #

type Rep Configurations Source # 
type Rep Configurations = D1 * (MetaData "Configurations" "Network.AWS.MQ.Types.Product" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) (C1 * (MetaCons "Configurations'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cPending") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ConfigurationId))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cHistory") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [ConfigurationId]))) (S1 * (MetaSel (Just Symbol "_cCurrent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ConfigurationId))))))

configurations :: Configurations Source #

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

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

  • cPending - The pending configuration of the broker.
  • cHistory - The history of configurations applied to the broker.
  • cCurrent - The current configuration of the broker.

cPending :: Lens' Configurations (Maybe ConfigurationId) Source #

The pending configuration of the broker.

cHistory :: Lens' Configurations [ConfigurationId] Source #

The history of configurations applied to the broker.

cCurrent :: Lens' Configurations (Maybe ConfigurationId) Source #

The current configuration of the broker.

SanitizationWarning

data SanitizationWarning Source #

Returns information about the XML element or attribute that was sanitized in the configuration.

See: sanitizationWarning smart constructor.

Instances

Eq SanitizationWarning Source # 
Data SanitizationWarning Source # 

Methods

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

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

toConstr :: SanitizationWarning -> Constr #

dataTypeOf :: SanitizationWarning -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: SanitizationWarning -> () #

type Rep SanitizationWarning Source # 
type Rep SanitizationWarning = D1 * (MetaData "SanitizationWarning" "Network.AWS.MQ.Types.Product" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) (C1 * (MetaCons "SanitizationWarning'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_swReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SanitizationWarningReason))) ((:*:) * (S1 * (MetaSel (Just Symbol "_swAttributeName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_swElementName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

sanitizationWarning :: SanitizationWarning Source #

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

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

  • swReason - Required. The reason for which the XML elements or attributes were sanitized. Possible values: DISALLOWED_ELEMENT_REMOVED, DISALLOWED_ATTRIBUTE_REMOVED, INVALID_ATTRIBUTE_VALUE_REMOVED DISALLOWED_ELEMENT_REMOVED shows that the provided element isn't allowed and has been removed. DISALLOWED_ATTRIBUTE_REMOVED shows that the provided attribute isn't allowed and has been removed. INVALID_ATTRIBUTE_VALUE_REMOVED shows that the provided value for the attribute isn't allowed and has been removed.
  • swAttributeName - The name of the XML attribute that has been sanitized.
  • swElementName - The name of the XML element that has been sanitized.

swReason :: Lens' SanitizationWarning (Maybe SanitizationWarningReason) Source #

Required. The reason for which the XML elements or attributes were sanitized. Possible values: DISALLOWED_ELEMENT_REMOVED, DISALLOWED_ATTRIBUTE_REMOVED, INVALID_ATTRIBUTE_VALUE_REMOVED DISALLOWED_ELEMENT_REMOVED shows that the provided element isn't allowed and has been removed. DISALLOWED_ATTRIBUTE_REMOVED shows that the provided attribute isn't allowed and has been removed. INVALID_ATTRIBUTE_VALUE_REMOVED shows that the provided value for the attribute isn't allowed and has been removed.

swAttributeName :: Lens' SanitizationWarning (Maybe Text) Source #

The name of the XML attribute that has been sanitized.

swElementName :: Lens' SanitizationWarning (Maybe Text) Source #

The name of the XML element that has been sanitized.

User

data User Source #

An ActiveMQ user associated with the broker.

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 #

ToJSON User Source # 
NFData User Source # 

Methods

rnf :: User -> () #

type Rep User Source # 
type Rep User = D1 * (MetaData "User" "Network.AWS.MQ.Types.Product" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) (C1 * (MetaCons "User'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_uGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) (S1 * (MetaSel (Just Symbol "_uConsoleAccess") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_uUsername") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_uPassword") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

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:

  • uGroups - The list of groups (20 maximum) to which the ActiveMQ user belongs. This value can contain only alphanumeric characters, dashes, periods, underscores, and tildes (- . _ ~). This value must be 2-100 characters long.
  • uConsoleAccess - Enables access to the the ActiveMQ Web Console for the ActiveMQ user.
  • uUsername - Required. The username of the ActiveMQ user. This value can contain only alphanumeric characters, dashes, periods, underscores, and tildes (- . _ ~). This value must be 2-100 characters long.
  • uPassword - Required. The password of the ActiveMQ user. This value must be at least 12 characters long, must contain at least 4 unique characters, and must not contain commas.

uGroups :: Lens' User [Text] Source #

The list of groups (20 maximum) to which the ActiveMQ user belongs. This value can contain only alphanumeric characters, dashes, periods, underscores, and tildes (- . _ ~). This value must be 2-100 characters long.

uConsoleAccess :: Lens' User (Maybe Bool) Source #

Enables access to the the ActiveMQ Web Console for the ActiveMQ user.

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

Required. The username of the ActiveMQ user. This value can contain only alphanumeric characters, dashes, periods, underscores, and tildes (- . _ ~). This value must be 2-100 characters long.

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

Required. The password of the ActiveMQ user. This value must be at least 12 characters long, must contain at least 4 unique characters, and must not contain commas.

UserPendingChanges

data UserPendingChanges Source #

Returns information about the status of the changes pending for the ActiveMQ user.

See: userPendingChanges smart constructor.

Instances

Eq UserPendingChanges Source # 
Data UserPendingChanges Source # 

Methods

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

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

toConstr :: UserPendingChanges -> Constr #

dataTypeOf :: UserPendingChanges -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: UserPendingChanges -> () #

type Rep UserPendingChanges Source # 
type Rep UserPendingChanges = D1 * (MetaData "UserPendingChanges" "Network.AWS.MQ.Types.Product" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) (C1 * (MetaCons "UserPendingChanges'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_upcGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Text]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_upcConsoleAccess") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_upcPendingChange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ChangeType))))))

userPendingChanges :: UserPendingChanges Source #

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

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

  • upcGroups - The list of groups (20 maximum) to which the ActiveMQ user belongs. This value can contain only alphanumeric characters, dashes, periods, underscores, and tildes (- . _ ~). This value must be 2-100 characters long.
  • upcConsoleAccess - Enables access to the the ActiveMQ Web Console for the ActiveMQ user.
  • upcPendingChange - Required. The type of change pending for the ActiveMQ user. Possible values: CREATE, UPDATE, DELETE

upcGroups :: Lens' UserPendingChanges [Text] Source #

The list of groups (20 maximum) to which the ActiveMQ user belongs. This value can contain only alphanumeric characters, dashes, periods, underscores, and tildes (- . _ ~). This value must be 2-100 characters long.

upcConsoleAccess :: Lens' UserPendingChanges (Maybe Bool) Source #

Enables access to the the ActiveMQ Web Console for the ActiveMQ user.

upcPendingChange :: Lens' UserPendingChanges (Maybe ChangeType) Source #

Required. The type of change pending for the ActiveMQ user. Possible values: CREATE, UPDATE, DELETE

UserSummary

data UserSummary Source #

Returns a list of all ActiveMQ users.

See: userSummary smart constructor.

Instances

Eq UserSummary Source # 
Data UserSummary Source # 

Methods

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

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

toConstr :: UserSummary -> Constr #

dataTypeOf :: UserSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read UserSummary Source # 
Show UserSummary Source # 
Generic UserSummary Source # 

Associated Types

type Rep UserSummary :: * -> * #

Hashable UserSummary Source # 
FromJSON UserSummary Source # 
NFData UserSummary Source # 

Methods

rnf :: UserSummary -> () #

type Rep UserSummary Source # 
type Rep UserSummary = D1 * (MetaData "UserSummary" "Network.AWS.MQ.Types.Product" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) (C1 * (MetaCons "UserSummary'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_usUsername") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_usPendingChange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ChangeType)))))

userSummary :: UserSummary Source #

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

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

  • usUsername - Required. The username of the ActiveMQ user. This value can contain only alphanumeric characters, dashes, periods, underscores, and tildes (- . _ ~). This value must be 2-100 characters long.
  • usPendingChange - The type of change pending for the ActiveMQ user. Possible values: CREATE, UPDATE, DELETE

usUsername :: Lens' UserSummary (Maybe Text) Source #

Required. The username of the ActiveMQ user. This value can contain only alphanumeric characters, dashes, periods, underscores, and tildes (- . _ ~). This value must be 2-100 characters long.

usPendingChange :: Lens' UserSummary (Maybe ChangeType) Source #

The type of change pending for the ActiveMQ user. Possible values: CREATE, UPDATE, DELETE

WeeklyStartTime

data WeeklyStartTime Source #

The scheduled time period relative to UTC during which Amazon MQ begins to apply pending updates or patches to the broker.

See: weeklyStartTime smart constructor.

Instances

Eq WeeklyStartTime Source # 
Data WeeklyStartTime Source # 

Methods

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

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

toConstr :: WeeklyStartTime -> Constr #

dataTypeOf :: WeeklyStartTime -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: WeeklyStartTime -> () #

type Rep WeeklyStartTime Source # 
type Rep WeeklyStartTime = D1 * (MetaData "WeeklyStartTime" "Network.AWS.MQ.Types.Product" "amazonka-mq-1.6.0-2p1A05IoaUzMnRutMRqns" False) (C1 * (MetaCons "WeeklyStartTime'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_wstTimeOfDay") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_wstTimeZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_wstDayOfWeek") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DayOfWeek))))))

weeklyStartTime :: WeeklyStartTime Source #

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

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

  • wstTimeOfDay - Required. The time, in 24-hour format.
  • wstTimeZone - The time zone, UTC by default, in either the Country/City format, or the UTC offset format.
  • wstDayOfWeek - Required. The day of the week. Possible values: MONDAY, TUESDAY, WEDNESDAY, THURSDAY, FRIDAY, SATURDAY, SUNDAY

wstTimeOfDay :: Lens' WeeklyStartTime (Maybe Text) Source #

Required. The time, in 24-hour format.

wstTimeZone :: Lens' WeeklyStartTime (Maybe Text) Source #

The time zone, UTC by default, in either the Country/City format, or the UTC offset format.

wstDayOfWeek :: Lens' WeeklyStartTime (Maybe DayOfWeek) Source #

Required. The day of the week. Possible values: MONDAY, TUESDAY, WEDNESDAY, THURSDAY, FRIDAY, SATURDAY, SUNDAY