amazonka-cloudhsm-1.6.1: Amazon CloudHSM 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.CloudHSM

Contents

Description

AWS CloudHSM Service

This is documentation for AWS CloudHSM Classic . For more information, see AWS CloudHSM Classic FAQs , the AWS CloudHSM Classic User Guide , and the AWS CloudHSM Classic API Reference .

For information about the current version of AWS CloudHSM , see AWS CloudHSM , the AWS CloudHSM User Guide , and the AWS CloudHSM API Reference .

Synopsis

Service Configuration

cloudHSM :: Service Source #

API version 2014-05-30 of the Amazon CloudHSM SDK configuration.

Errors

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

InvalidRequestException

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

Indicates that one or more of the request parameters are not valid.

CloudHSMServiceException

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

Indicates that an exception occurred in the AWS CloudHSM service.

CloudHSMInternalException

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

Indicates that an internal error occurred.

Waiters

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

Operations

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

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

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

DeleteHAPG

ListHAPGs

ModifyLunaClient

ListHSMs

DescribeLunaClient

ListTagsForResource

CreateHAPG

CreateHSM

RemoveTagsFromResource

DescribeHAPG

CreateLunaClient

ListLunaClients

AddTagsToResource

GetConfig

DeleteHSM

DescribeHSM

ModifyHAPG

DeleteLunaClient

ModifyHSM

ListAvailableZones

Types

ClientVersion

data ClientVersion Source #

Constructors

VD5_1 
VD5_3 
Instances
Bounded ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Enum ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Eq ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Data ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Methods

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

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

toConstr :: ClientVersion -> Constr #

dataTypeOf :: ClientVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Read ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Show ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Generic ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Associated Types

type Rep ClientVersion :: Type -> Type #

Hashable ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToJSON ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToHeader ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToQuery ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToByteString ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

FromText ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToText ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Methods

toText :: ClientVersion -> Text #

NFData ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Methods

rnf :: ClientVersion -> () #

type Rep ClientVersion Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

type Rep ClientVersion = D1 (MetaData "ClientVersion" "Network.AWS.CloudHSM.Types.Sum" "amazonka-cloudhsm-1.6.1-4znIKUA0fUEDSYNWkcPcz3" False) (C1 (MetaCons "VD5_1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VD5_3" PrefixI False) (U1 :: Type -> Type))

CloudHSMObjectState

data CloudHSMObjectState Source #

Constructors

Degraded 
Ready 
Updating 
Instances
Bounded CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Enum CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Eq CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Data CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Methods

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

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

toConstr :: CloudHSMObjectState -> Constr #

dataTypeOf :: CloudHSMObjectState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Read CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Show CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Generic CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Associated Types

type Rep CloudHSMObjectState :: Type -> Type #

Hashable CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

FromJSON CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToHeader CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToQuery CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToByteString CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

FromText CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToText CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

NFData CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Methods

rnf :: CloudHSMObjectState -> () #

type Rep CloudHSMObjectState Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

type Rep CloudHSMObjectState = D1 (MetaData "CloudHSMObjectState" "Network.AWS.CloudHSM.Types.Sum" "amazonka-cloudhsm-1.6.1-4znIKUA0fUEDSYNWkcPcz3" False) (C1 (MetaCons "Degraded" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Ready" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Updating" PrefixI False) (U1 :: Type -> Type)))

HSMStatus

data HSMStatus Source #

Instances
Bounded HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Enum HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Eq HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Data HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Methods

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

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

toConstr :: HSMStatus -> Constr #

dataTypeOf :: HSMStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Read HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Show HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Generic HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Associated Types

type Rep HSMStatus :: Type -> Type #

Hashable HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

FromJSON HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToHeader HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToQuery HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToByteString HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Methods

toBS :: HSMStatus -> ByteString #

FromText HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToText HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Methods

toText :: HSMStatus -> Text #

NFData HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Methods

rnf :: HSMStatus -> () #

type Rep HSMStatus Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

type Rep HSMStatus = D1 (MetaData "HSMStatus" "Network.AWS.CloudHSM.Types.Sum" "amazonka-cloudhsm-1.6.1-4znIKUA0fUEDSYNWkcPcz3" False) ((C1 (MetaCons "HSDegraded" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HSPending" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HSRunning" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "HSSuspended" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HSTerminated" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "HSTerminating" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HSUpdating" PrefixI False) (U1 :: Type -> Type))))

SubscriptionType

data SubscriptionType Source #

Specifies the type of subscription for the HSM.

  • PRODUCTION - The HSM is being used in a production environment.
  • TRIAL - The HSM is being used in a product trial.

Constructors

Production 
Instances
Bounded SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Enum SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Eq SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Data SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Methods

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

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

toConstr :: SubscriptionType -> Constr #

dataTypeOf :: SubscriptionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Read SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Show SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Generic SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Associated Types

type Rep SubscriptionType :: Type -> Type #

Hashable SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToJSON SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

FromJSON SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToHeader SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToQuery SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToByteString SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

FromText SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

ToText SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

NFData SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

Methods

rnf :: SubscriptionType -> () #

type Rep SubscriptionType Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Sum

type Rep SubscriptionType = D1 (MetaData "SubscriptionType" "Network.AWS.CloudHSM.Types.Sum" "amazonka-cloudhsm-1.6.1-4znIKUA0fUEDSYNWkcPcz3" False) (C1 (MetaCons "Production" PrefixI False) (U1 :: Type -> Type))

Tag

data Tag Source #

A key-value pair that identifies or specifies metadata about an AWS CloudHSM resource.

See: tag smart constructor.

Instances
Eq Tag Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Product

Methods

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

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

Data Tag Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Product

Methods

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

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

toConstr :: Tag -> Constr #

dataTypeOf :: Tag -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Tag Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Product

Show Tag Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Product

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Product

Associated Types

type Rep Tag :: Type -> Type #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Hashable Tag Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Product

Methods

hashWithSalt :: Int -> Tag -> Int #

hash :: Tag -> Int #

ToJSON Tag Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Product

FromJSON Tag Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Product

NFData Tag Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Product

Methods

rnf :: Tag -> () #

type Rep Tag Source # 
Instance details

Defined in Network.AWS.CloudHSM.Types.Product

type Rep Tag = D1 (MetaData "Tag" "Network.AWS.CloudHSM.Types.Product" "amazonka-cloudhsm-1.6.1-4znIKUA0fUEDSYNWkcPcz3" False) (C1 (MetaCons "Tag'" PrefixI True) (S1 (MetaSel (Just "_tagKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_tagValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

tag Source #

Arguments

:: Text

tagKey

-> Text

tagValue

-> Tag 

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

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

tagKey :: Lens' Tag Text Source #

The key of the tag.

tagValue :: Lens' Tag Text Source #

The value of the tag.