amazonka-importexport-1.5.0: Amazon Import/Export SDK.

Copyright(c) 2013-2017 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.ImportExport

Contents

Description

AWS Import/Export Service

Synopsis

Service Configuration

importExport :: Service Source #

API version 2010-06-01 of the Amazon Import/Export 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 ImportExport.

InvalidJobIdException

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

The JOBID was missing, not found, or not associated with the AWS account.

InvalidParameterException

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

One or more parameters had an invalid value.

ExpiredJobIdException

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

Indicates that the specified job has expired out of the system.

InvalidFileSystemException

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

File system specified in export manifest is invalid.

InvalidAccessKeyIdException

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

The AWS Access Key ID specified in the request did not match the manifest's accessKeyId value. The manifest and the request authentication must use the same AWS Access Key ID.

UnableToUpdateJobIdException

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

AWS Import/Export cannot update the job

UnableToCancelJobIdException

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

AWS Import/Export cannot cancel the job

MultipleRegionsException

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

Your manifest file contained buckets from multiple regions. A job is restricted to buckets from one region. Please correct and resubmit.

InvalidVersionException

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

The client tool version is invalid.

MalformedManifestException

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

Your manifest is not well-formed.

MissingParameterException

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

One or more required parameters was missing from the request.

CanceledJobIdException

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

The specified job ID has been canceled and is no longer valid.

BucketPermissionException

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

The account specified does not have the appropriate bucket permissions.

NoSuchBucketException

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

The specified bucket does not exist. Create the specified bucket or change the manifest's bucket, exportBucket, or logBucket field to a bucket that the account, as specified by the manifest's Access Key ID, has write permissions to.

InvalidAddressException

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

The address specified in the manifest is invalid.

MissingCustomsException

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

One or more required customs parameters was missing from the manifest.

InvalidManifestFieldException

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

One or more manifest fields was invalid. Please correct and resubmit.

InvalidCustomsException

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

One or more customs parameters was invalid. Please correct and resubmit.

MissingManifestFieldException

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

One or more required fields were missing from the manifest file. Please correct and resubmit.

CreateJobQuotaExceededException

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

Each account can create only a certain number of jobs per day. If you need to create more than this, please contact awsimportexport@amazon.com to explain your particular use case.

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.

GetShippingLabel

CreateJob

ListJobs (Paginated)

UpdateJob

GetStatus

CancelJob

Types

JobType

data JobType Source #

Specifies whether the job to initiate is an import or export job.

Constructors

Export 
Import 

Instances

Bounded JobType Source # 
Enum JobType Source # 
Eq JobType Source # 

Methods

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

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

Data JobType Source # 

Methods

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

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

toConstr :: JobType -> Constr #

dataTypeOf :: JobType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord JobType Source # 
Read JobType Source # 
Show JobType Source # 
Generic JobType Source # 

Associated Types

type Rep JobType :: * -> * #

Methods

from :: JobType -> Rep JobType x #

to :: Rep JobType x -> JobType #

Hashable JobType Source # 

Methods

hashWithSalt :: Int -> JobType -> Int #

hash :: JobType -> Int #

NFData JobType Source # 

Methods

rnf :: JobType -> () #

FromXML JobType Source # 
ToQuery JobType Source # 
ToHeader JobType Source # 

Methods

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

ToByteString JobType Source # 

Methods

toBS :: JobType -> ByteString #

FromText JobType Source # 
ToText JobType Source # 

Methods

toText :: JobType -> Text #

type Rep JobType Source # 
type Rep JobType = D1 (MetaData "JobType" "Network.AWS.ImportExport.Types.Sum" "amazonka-importexport-1.5.0-Cw4Z8XONDIx1zxYwsDV1d3" False) ((:+:) (C1 (MetaCons "Export" PrefixI False) U1) (C1 (MetaCons "Import" PrefixI False) U1))

Artifact

data Artifact Source #

A discrete item that contains the description and URL of an artifact (such as a PDF).

See: artifact smart constructor.

Instances

Eq Artifact Source # 
Data Artifact Source # 

Methods

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

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

toConstr :: Artifact -> Constr #

dataTypeOf :: Artifact -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Artifact Source # 
Show Artifact Source # 
Generic Artifact Source # 

Associated Types

type Rep Artifact :: * -> * #

Methods

from :: Artifact -> Rep Artifact x #

to :: Rep Artifact x -> Artifact #

Hashable Artifact Source # 

Methods

hashWithSalt :: Int -> Artifact -> Int #

hash :: Artifact -> Int #

NFData Artifact Source # 

Methods

rnf :: Artifact -> () #

FromXML Artifact Source # 
type Rep Artifact Source # 
type Rep Artifact = D1 (MetaData "Artifact" "Network.AWS.ImportExport.Types.Product" "amazonka-importexport-1.5.0-Cw4Z8XONDIx1zxYwsDV1d3" False) (C1 (MetaCons "Artifact'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_aURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_aDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

artifact :: Artifact Source #

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

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

aURL :: Lens' Artifact (Maybe Text) Source #

Undocumented member.

aDescription :: Lens' Artifact (Maybe Text) Source #

Undocumented member.

Job

data Job Source #

Representation of a job returned by the ListJobs operation.

See: job smart constructor.

Instances

Eq Job Source # 

Methods

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

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

Data Job Source # 

Methods

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

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

toConstr :: Job -> Constr #

dataTypeOf :: Job -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Job Source # 
Show Job Source # 

Methods

showsPrec :: Int -> Job -> ShowS #

show :: Job -> String #

showList :: [Job] -> ShowS #

Generic Job Source # 

Associated Types

type Rep Job :: * -> * #

Methods

from :: Job -> Rep Job x #

to :: Rep Job x -> Job #

Hashable Job Source # 

Methods

hashWithSalt :: Int -> Job -> Int #

hash :: Job -> Int #

NFData Job Source # 

Methods

rnf :: Job -> () #

FromXML Job Source # 

Methods

parseXML :: [Node] -> Either String Job #

type Rep Job Source # 
type Rep Job = D1 (MetaData "Job" "Network.AWS.ImportExport.Types.Product" "amazonka-importexport-1.5.0-Cw4Z8XONDIx1zxYwsDV1d3" False) (C1 (MetaCons "Job'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_jobJobType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 JobType)) (S1 (MetaSel (Just Symbol "_jobJobId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_jobIsCanceled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "_jobCreationDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ISO8601)))))

job Source #

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

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

jobJobType :: Lens' Job JobType Source #

Undocumented member.

jobJobId :: Lens' Job Text Source #

Undocumented member.

jobIsCanceled :: Lens' Job Bool Source #

Undocumented member.

jobCreationDate :: Lens' Job UTCTime Source #

Undocumented member.