amazonka-storagegateway-1.4.4: Amazon Storage Gateway SDK.

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

Network.AWS.StorageGateway.Types

Contents

Description

 

Synopsis

Service Configuration

storageGateway :: Service Source #

API version '2013-06-30' of the Amazon Storage Gateway SDK configuration.

Errors

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

An exception occurred because an invalid gateway request was issued to the service. For more information, see the error and message fields.

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

An internal server error has occurred during the request. For more information, see the error and message fields.

CachediSCSIVolume

data CachediSCSIVolume Source #

See: cachediSCSIVolume smart constructor.

Instances

Eq CachediSCSIVolume Source # 
Data CachediSCSIVolume Source # 

Methods

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

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

toConstr :: CachediSCSIVolume -> Constr #

dataTypeOf :: CachediSCSIVolume -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CachediSCSIVolume Source # 
Show CachediSCSIVolume Source # 
Generic CachediSCSIVolume Source # 
Hashable CachediSCSIVolume Source # 
NFData CachediSCSIVolume Source # 

Methods

rnf :: CachediSCSIVolume -> () #

FromJSON CachediSCSIVolume Source # 

Methods

parseJSON :: Value -> Parser CachediSCSIVolume #

type Rep CachediSCSIVolume Source # 
type Rep CachediSCSIVolume = D1 (MetaData "CachediSCSIVolume" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "CachediSCSIVolume'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cscsivVolumeiSCSIAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe VolumeiSCSIAttributes))) (S1 (MetaSel (Just Symbol "_cscsivVolumeStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cscsivSourceSnapshotId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cscsivVolumeARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cscsivVolumeProgress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double))) (S1 (MetaSel (Just Symbol "_cscsivVolumeSizeInBytes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)))) ((:*:) (S1 (MetaSel (Just Symbol "_cscsivVolumeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cscsivVolumeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

cachediSCSIVolume :: CachediSCSIVolume Source #

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

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

ChapInfo

data ChapInfo Source #

Describes Challenge-Handshake Authentication Protocol (CHAP) information that supports authentication between your gateway and iSCSI initiators.

See: chapInfo smart constructor.

Instances

Eq ChapInfo Source # 
Data ChapInfo Source # 

Methods

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

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

toConstr :: ChapInfo -> Constr #

dataTypeOf :: ChapInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ChapInfo Source # 
Show ChapInfo Source # 
Generic ChapInfo Source # 

Associated Types

type Rep ChapInfo :: * -> * #

Methods

from :: ChapInfo -> Rep ChapInfo x #

to :: Rep ChapInfo x -> ChapInfo #

Hashable ChapInfo Source # 

Methods

hashWithSalt :: Int -> ChapInfo -> Int #

hash :: ChapInfo -> Int #

NFData ChapInfo Source # 

Methods

rnf :: ChapInfo -> () #

FromJSON ChapInfo Source # 

Methods

parseJSON :: Value -> Parser ChapInfo #

type Rep ChapInfo Source # 
type Rep ChapInfo = D1 (MetaData "ChapInfo" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "ChapInfo'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ciTargetARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ciSecretToAuthenticateInitiator") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_ciInitiatorName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ciSecretToAuthenticateTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

chapInfo :: ChapInfo Source #

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

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

ciTargetARN :: Lens' ChapInfo (Maybe Text) Source #

The Amazon Resource Name (ARN) of the volume.

Valid Values: 50 to 500 lowercase letters, numbers, periods (.), and hyphens (-).

ciSecretToAuthenticateInitiator :: Lens' ChapInfo (Maybe Text) Source #

The secret key that the initiator (for example, the Windows client) must provide to participate in mutual CHAP with the target.

ciInitiatorName :: Lens' ChapInfo (Maybe Text) Source #

The iSCSI initiator that connects to the target.

ciSecretToAuthenticateTarget :: Lens' ChapInfo (Maybe Text) Source #

The secret key that the target must provide to participate in mutual CHAP with the initiator (e.g. Windows client).

DeviceiSCSIAttributes

data DeviceiSCSIAttributes Source #

Lists iSCSI information about a VTL device.

See: deviceiSCSIAttributes smart constructor.

Instances

Eq DeviceiSCSIAttributes Source # 
Data DeviceiSCSIAttributes Source # 

Methods

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

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

toConstr :: DeviceiSCSIAttributes -> Constr #

dataTypeOf :: DeviceiSCSIAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DeviceiSCSIAttributes Source # 
Show DeviceiSCSIAttributes Source # 
Generic DeviceiSCSIAttributes Source # 
Hashable DeviceiSCSIAttributes Source # 
NFData DeviceiSCSIAttributes Source # 

Methods

rnf :: DeviceiSCSIAttributes -> () #

FromJSON DeviceiSCSIAttributes Source # 
type Rep DeviceiSCSIAttributes Source # 
type Rep DeviceiSCSIAttributes = D1 (MetaData "DeviceiSCSIAttributes" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "DeviceiSCSIAttributes'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dscsiaTargetARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dscsiaChapEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_dscsiaNetworkInterfaceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dscsiaNetworkInterfacePort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))))

deviceiSCSIAttributes :: DeviceiSCSIAttributes Source #

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

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

dscsiaTargetARN :: Lens' DeviceiSCSIAttributes (Maybe Text) Source #

Specifies the unique Amazon Resource Name(ARN) that encodes the iSCSI qualified name(iqn) of a tape drive or media changer target.

dscsiaChapEnabled :: Lens' DeviceiSCSIAttributes (Maybe Bool) Source #

Indicates whether mutual CHAP is enabled for the iSCSI target.

dscsiaNetworkInterfaceId :: Lens' DeviceiSCSIAttributes (Maybe Text) Source #

The network interface identifier of the VTL device.

dscsiaNetworkInterfacePort :: Lens' DeviceiSCSIAttributes (Maybe Int) Source #

The port used to communicate with iSCSI VTL device targets.

Disk

data Disk Source #

See: disk smart constructor.

Instances

Eq Disk Source # 

Methods

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

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

Data Disk Source # 

Methods

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

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

toConstr :: Disk -> Constr #

dataTypeOf :: Disk -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Disk Source # 
Show Disk Source # 

Methods

showsPrec :: Int -> Disk -> ShowS #

show :: Disk -> String #

showList :: [Disk] -> ShowS #

Generic Disk Source # 

Associated Types

type Rep Disk :: * -> * #

Methods

from :: Disk -> Rep Disk x #

to :: Rep Disk x -> Disk #

Hashable Disk Source # 

Methods

hashWithSalt :: Int -> Disk -> Int #

hash :: Disk -> Int #

NFData Disk Source # 

Methods

rnf :: Disk -> () #

FromJSON Disk Source # 

Methods

parseJSON :: Value -> Parser Disk #

type Rep Disk Source # 
type Rep Disk = D1 (MetaData "Disk" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "Disk'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dDiskAllocationResource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_dDiskAllocationType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dDiskNode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dDiskPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dDiskSizeInBytes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)))) ((:*:) (S1 (MetaSel (Just Symbol "_dDiskStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dDiskId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

disk :: Disk Source #

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

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

dDiskAllocationType :: Lens' Disk (Maybe Text) Source #

Undocumented member.

dDiskNode :: Lens' Disk (Maybe Text) Source #

Undocumented member.

dDiskPath :: Lens' Disk (Maybe Text) Source #

Undocumented member.

dDiskSizeInBytes :: Lens' Disk (Maybe Integer) Source #

Undocumented member.

dDiskStatus :: Lens' Disk (Maybe Text) Source #

Undocumented member.

dDiskId :: Lens' Disk (Maybe Text) Source #

Undocumented member.

GatewayInfo

data GatewayInfo Source #

Describes a gateway object.

See: gatewayInfo smart constructor.

Instances

Eq GatewayInfo Source # 
Data GatewayInfo Source # 

Methods

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

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

toConstr :: GatewayInfo -> Constr #

dataTypeOf :: GatewayInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read GatewayInfo Source # 
Show GatewayInfo Source # 
Generic GatewayInfo Source # 

Associated Types

type Rep GatewayInfo :: * -> * #

Hashable GatewayInfo Source # 
NFData GatewayInfo Source # 

Methods

rnf :: GatewayInfo -> () #

FromJSON GatewayInfo Source # 

Methods

parseJSON :: Value -> Parser GatewayInfo #

type Rep GatewayInfo Source # 
type Rep GatewayInfo = D1 (MetaData "GatewayInfo" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "GatewayInfo'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_giGatewayARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_giGatewayOperationalState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_giGatewayName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_giGatewayId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_giGatewayType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

gatewayInfo :: GatewayInfo Source #

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

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

giGatewayARN :: Lens' GatewayInfo (Maybe Text) Source #

The Amazon Resource Name (ARN) of the gateway. Use the ListGateways operation to return a list of gateways for your account and region.

giGatewayOperationalState :: Lens' GatewayInfo (Maybe Text) Source #

The state of the gateway.

Valid Values: DISABLED or ACTIVE

giGatewayName :: Lens' GatewayInfo (Maybe Text) Source #

The name of the gateway.

giGatewayId :: Lens' GatewayInfo (Maybe Text) Source #

The unique identifier assigned to your gateway during activation. This ID becomes part of the gateway Amazon Resource Name (ARN), which you use as input for other operations.

giGatewayType :: Lens' GatewayInfo (Maybe Text) Source #

The type of the gateway.

NetworkInterface

data NetworkInterface Source #

Describes a gateway's network interface.

See: networkInterface smart constructor.

Instances

Eq NetworkInterface Source # 
Data NetworkInterface Source # 

Methods

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

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

toConstr :: NetworkInterface -> Constr #

dataTypeOf :: NetworkInterface -> DataType #

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

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

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

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

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

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

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

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

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

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

Read NetworkInterface Source # 
Show NetworkInterface Source # 
Generic NetworkInterface Source # 
Hashable NetworkInterface Source # 
NFData NetworkInterface Source # 

Methods

rnf :: NetworkInterface -> () #

FromJSON NetworkInterface Source # 

Methods

parseJSON :: Value -> Parser NetworkInterface #

type Rep NetworkInterface Source # 
type Rep NetworkInterface = D1 (MetaData "NetworkInterface" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "NetworkInterface'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_niIPv6Address") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_niMACAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_niIPv4Address") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

networkInterface :: NetworkInterface Source #

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

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

niIPv6Address :: Lens' NetworkInterface (Maybe Text) Source #

The Internet Protocol version 6 (IPv6) address of the interface. Currently not supported.

niMACAddress :: Lens' NetworkInterface (Maybe Text) Source #

The Media Access Control (MAC) address of the interface.

This is currently unsupported and will not be returned in output.

niIPv4Address :: Lens' NetworkInterface (Maybe Text) Source #

The Internet Protocol version 4 (IPv4) address of the interface.

StorediSCSIVolume

data StorediSCSIVolume Source #

See: storediSCSIVolume smart constructor.

Instances

Eq StorediSCSIVolume Source # 
Data StorediSCSIVolume Source # 

Methods

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

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

toConstr :: StorediSCSIVolume -> Constr #

dataTypeOf :: StorediSCSIVolume -> DataType #

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

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

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

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

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

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

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

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

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

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

Read StorediSCSIVolume Source # 
Show StorediSCSIVolume Source # 
Generic StorediSCSIVolume Source # 
Hashable StorediSCSIVolume Source # 
NFData StorediSCSIVolume Source # 

Methods

rnf :: StorediSCSIVolume -> () #

FromJSON StorediSCSIVolume Source # 

Methods

parseJSON :: Value -> Parser StorediSCSIVolume #

type Rep StorediSCSIVolume Source # 
type Rep StorediSCSIVolume = D1 (MetaData "StorediSCSIVolume" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "StorediSCSIVolume'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sscsivVolumeiSCSIAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe VolumeiSCSIAttributes))) (S1 (MetaSel (Just Symbol "_sscsivVolumeStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_sscsivSourceSnapshotId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sscsivPreservedExistingData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_sscsivVolumeARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sscsivVolumeProgress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double))) (S1 (MetaSel (Just Symbol "_sscsivVolumeSizeInBytes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)))) ((:*:) (S1 (MetaSel (Just Symbol "_sscsivVolumeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sscsivVolumeDiskId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_sscsivVolumeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

Tag

data Tag Source #

See: tag smart constructor.

Instances

Eq Tag Source # 

Methods

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

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

Data Tag Source # 

Methods

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

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

toConstr :: Tag -> Constr #

dataTypeOf :: Tag -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Tag Source # 
Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 

Associated Types

type Rep Tag :: * -> * #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Hashable Tag Source # 

Methods

hashWithSalt :: Int -> Tag -> Int #

hash :: Tag -> Int #

NFData Tag Source # 

Methods

rnf :: Tag -> () #

FromJSON Tag Source # 

Methods

parseJSON :: Value -> Parser Tag #

ToJSON Tag Source # 

Methods

toJSON :: Tag -> Value #

toEncoding :: Tag -> Encoding #

type Rep Tag Source # 
type Rep Tag = D1 (MetaData "Tag" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "Tag'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tagKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_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 #

Undocumented member.

tagValue :: Lens' Tag Text Source #

Undocumented member.

Tape

data Tape Source #

Describes a virtual tape object.

See: tape smart constructor.

Instances

Eq Tape Source # 

Methods

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

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

Data Tape Source # 

Methods

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

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

toConstr :: Tape -> Constr #

dataTypeOf :: Tape -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Tape Source # 
Show Tape Source # 

Methods

showsPrec :: Int -> Tape -> ShowS #

show :: Tape -> String #

showList :: [Tape] -> ShowS #

Generic Tape Source # 

Associated Types

type Rep Tape :: * -> * #

Methods

from :: Tape -> Rep Tape x #

to :: Rep Tape x -> Tape #

Hashable Tape Source # 

Methods

hashWithSalt :: Int -> Tape -> Int #

hash :: Tape -> Int #

NFData Tape Source # 

Methods

rnf :: Tape -> () #

FromJSON Tape Source # 

Methods

parseJSON :: Value -> Parser Tape #

type Rep Tape Source # 
type Rep Tape = D1 (MetaData "Tape" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "Tape'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_tTapeBarcode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_tTapeStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tTapeARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_tProgress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double))) ((:*:) (S1 (MetaSel (Just Symbol "_tTapeSizeInBytes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer))) (S1 (MetaSel (Just Symbol "_tVTLDevice") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

tape :: Tape Source #

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

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

tTapeBarcode :: Lens' Tape (Maybe Text) Source #

The barcode that identifies a specific virtual tape.

tTapeStatus :: Lens' Tape (Maybe Text) Source #

The current state of the virtual tape.

tTapeARN :: Lens' Tape (Maybe Text) Source #

The Amazon Resource Name (ARN) of the virtual tape.

tProgress :: Lens' Tape (Maybe Double) Source #

For archiving virtual tapes, indicates how much data remains to be uploaded before archiving is complete.

Range: 0 (not started) to 100 (complete).

tTapeSizeInBytes :: Lens' Tape (Maybe Integer) Source #

The size, in bytes, of the virtual tape.

tVTLDevice :: Lens' Tape (Maybe Text) Source #

The virtual tape library (VTL) device that the virtual tape is associated with.

TapeArchive

data TapeArchive Source #

Represents a virtual tape that is archived in the virtual tape shelf (VTS).

See: tapeArchive smart constructor.

Instances

Eq TapeArchive Source # 
Data TapeArchive Source # 

Methods

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

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

toConstr :: TapeArchive -> Constr #

dataTypeOf :: TapeArchive -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TapeArchive Source # 
Show TapeArchive Source # 
Generic TapeArchive Source # 

Associated Types

type Rep TapeArchive :: * -> * #

Hashable TapeArchive Source # 
NFData TapeArchive Source # 

Methods

rnf :: TapeArchive -> () #

FromJSON TapeArchive Source # 

Methods

parseJSON :: Value -> Parser TapeArchive #

type Rep TapeArchive Source # 
type Rep TapeArchive = D1 (MetaData "TapeArchive" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "TapeArchive'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_taTapeBarcode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_taTapeStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_taTapeARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_taTapeSizeInBytes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer))) ((:*:) (S1 (MetaSel (Just Symbol "_taCompletionTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))) (S1 (MetaSel (Just Symbol "_taRetrievedTo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

tapeArchive :: TapeArchive Source #

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

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

taTapeBarcode :: Lens' TapeArchive (Maybe Text) Source #

The barcode that identifies the archived virtual tape.

taTapeStatus :: Lens' TapeArchive (Maybe Text) Source #

The current state of the archived virtual tape.

taTapeARN :: Lens' TapeArchive (Maybe Text) Source #

The Amazon Resource Name (ARN) of an archived virtual tape.

taTapeSizeInBytes :: Lens' TapeArchive (Maybe Integer) Source #

The size, in bytes, of the archived virtual tape.

taCompletionTime :: Lens' TapeArchive (Maybe UTCTime) Source #

The time that the archiving of the virtual tape was completed.

The string format of the completion time is in the ISO8601 extended YYYY-MM-DD'T'HH:MM:SS'Z' format.

taRetrievedTo :: Lens' TapeArchive (Maybe Text) Source #

The Amazon Resource Name (ARN) of the gateway-VTL that the virtual tape is being retrieved to.

The virtual tape is retrieved from the virtual tape shelf (VTS).

TapeInfo

data TapeInfo Source #

Describes a virtual tape.

See: tapeInfo smart constructor.

Instances

Eq TapeInfo Source # 
Data TapeInfo Source # 

Methods

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

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

toConstr :: TapeInfo -> Constr #

dataTypeOf :: TapeInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TapeInfo Source # 
Show TapeInfo Source # 
Generic TapeInfo Source # 

Associated Types

type Rep TapeInfo :: * -> * #

Methods

from :: TapeInfo -> Rep TapeInfo x #

to :: Rep TapeInfo x -> TapeInfo #

Hashable TapeInfo Source # 

Methods

hashWithSalt :: Int -> TapeInfo -> Int #

hash :: TapeInfo -> Int #

NFData TapeInfo Source # 

Methods

rnf :: TapeInfo -> () #

FromJSON TapeInfo Source # 

Methods

parseJSON :: Value -> Parser TapeInfo #

type Rep TapeInfo Source # 
type Rep TapeInfo = D1 (MetaData "TapeInfo" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "TapeInfo'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_tiTapeBarcode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tiTapeStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_tiTapeARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_tiGatewayARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tiTapeSizeInBytes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)))))))

tapeInfo :: TapeInfo Source #

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

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

tiTapeBarcode :: Lens' TapeInfo (Maybe Text) Source #

The barcode that identifies a specific virtual tape.

tiTapeStatus :: Lens' TapeInfo (Maybe Text) Source #

The status of the tape.

tiTapeARN :: Lens' TapeInfo (Maybe Text) Source #

The Amazon Resource Name (ARN) of a virtual tape.

tiGatewayARN :: Lens' TapeInfo (Maybe Text) Source #

The Amazon Resource Name (ARN) of the gateway. Use the ListGateways operation to return a list of gateways for your account and region.

tiTapeSizeInBytes :: Lens' TapeInfo (Maybe Integer) Source #

The size, in bytes, of a virtual tape.

TapeRecoveryPointInfo

data TapeRecoveryPointInfo Source #

Describes a recovery point.

See: tapeRecoveryPointInfo smart constructor.

Instances

Eq TapeRecoveryPointInfo Source # 
Data TapeRecoveryPointInfo Source # 

Methods

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

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

toConstr :: TapeRecoveryPointInfo -> Constr #

dataTypeOf :: TapeRecoveryPointInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TapeRecoveryPointInfo Source # 
Show TapeRecoveryPointInfo Source # 
Generic TapeRecoveryPointInfo Source # 
Hashable TapeRecoveryPointInfo Source # 
NFData TapeRecoveryPointInfo Source # 

Methods

rnf :: TapeRecoveryPointInfo -> () #

FromJSON TapeRecoveryPointInfo Source # 
type Rep TapeRecoveryPointInfo Source # 
type Rep TapeRecoveryPointInfo = D1 (MetaData "TapeRecoveryPointInfo" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "TapeRecoveryPointInfo'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_trpiTapeStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_trpiTapeRecoveryPointTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)))) ((:*:) (S1 (MetaSel (Just Symbol "_trpiTapeARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_trpiTapeSizeInBytes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer))))))

tapeRecoveryPointInfo :: TapeRecoveryPointInfo Source #

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

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

trpiTapeRecoveryPointTime :: Lens' TapeRecoveryPointInfo (Maybe UTCTime) Source #

The time when the point-in-time view of the virtual tape was replicated for later recovery.

The string format of the tape recovery point time is in the ISO8601 extended YYYY-MM-DD'T'HH:MM:SS'Z' format.

trpiTapeARN :: Lens' TapeRecoveryPointInfo (Maybe Text) Source #

The Amazon Resource Name (ARN) of the virtual tape.

trpiTapeSizeInBytes :: Lens' TapeRecoveryPointInfo (Maybe Integer) Source #

The size, in bytes, of the virtual tapes to recover.

VTLDevice

data VTLDevice Source #

Represents a device object associated with a gateway-VTL.

See: vTLDevice smart constructor.

Instances

Eq VTLDevice Source # 
Data VTLDevice Source # 

Methods

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

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

toConstr :: VTLDevice -> Constr #

dataTypeOf :: VTLDevice -> DataType #

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

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

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

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

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

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

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

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

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

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

Read VTLDevice Source # 
Show VTLDevice Source # 
Generic VTLDevice Source # 

Associated Types

type Rep VTLDevice :: * -> * #

Hashable VTLDevice Source # 
NFData VTLDevice Source # 

Methods

rnf :: VTLDevice -> () #

FromJSON VTLDevice Source # 

Methods

parseJSON :: Value -> Parser VTLDevice #

type Rep VTLDevice Source # 
type Rep VTLDevice = D1 (MetaData "VTLDevice" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "VTLDevice'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_vtldDeviceiSCSIAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeviceiSCSIAttributes))) (S1 (MetaSel (Just Symbol "_vtldVTLDeviceVendor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_vtldVTLDeviceARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_vtldVTLDeviceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_vtldVTLDeviceProductIdentifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

vTLDevice :: VTLDevice Source #

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

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

vtldDeviceiSCSIAttributes :: Lens' VTLDevice (Maybe DeviceiSCSIAttributes) Source #

A list of iSCSI information about a VTL device.

vtldVTLDeviceARN :: Lens' VTLDevice (Maybe Text) Source #

Specifies the unique Amazon Resource Name (ARN) of the device (tape drive or media changer).

VolumeInfo

data VolumeInfo Source #

Describes a storage volume object.

See: volumeInfo smart constructor.

Instances

Eq VolumeInfo Source # 
Data VolumeInfo Source # 

Methods

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

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

toConstr :: VolumeInfo -> Constr #

dataTypeOf :: VolumeInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read VolumeInfo Source # 
Show VolumeInfo Source # 
Generic VolumeInfo Source # 

Associated Types

type Rep VolumeInfo :: * -> * #

Hashable VolumeInfo Source # 
NFData VolumeInfo Source # 

Methods

rnf :: VolumeInfo -> () #

FromJSON VolumeInfo Source # 

Methods

parseJSON :: Value -> Parser VolumeInfo #

type Rep VolumeInfo Source # 
type Rep VolumeInfo = D1 (MetaData "VolumeInfo" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "VolumeInfo'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_viGatewayARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_viVolumeARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_viVolumeSizeInBytes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer))))) ((:*:) (S1 (MetaSel (Just Symbol "_viVolumeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_viGatewayId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_viVolumeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

volumeInfo :: VolumeInfo Source #

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

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

viGatewayARN :: Lens' VolumeInfo (Maybe Text) Source #

Undocumented member.

viVolumeARN :: Lens' VolumeInfo (Maybe Text) Source #

The Amazon Resource Name (ARN) for the storage volume. For example, the following is a valid ARN:

'arn:aws:storagegateway:us-east-1:111122223333:gateway\/sgw-12A3456B\/volume\/vol-1122AABB'

Valid Values: 50 to 500 lowercase letters, numbers, periods (.), and hyphens (-).

viVolumeSizeInBytes :: Lens' VolumeInfo (Maybe Integer) Source #

The size, in bytes, of the volume.

Valid Values: 50 to 500 lowercase letters, numbers, periods (.), and hyphens (-).

viVolumeId :: Lens' VolumeInfo (Maybe Text) Source #

The unique identifier assigned to the volume. This ID becomes part of the volume Amazon Resource Name (ARN), which you use as input for other operations.

Valid Values: 50 to 500 lowercase letters, numbers, periods (.), and hyphens (-).

viGatewayId :: Lens' VolumeInfo (Maybe Text) Source #

The unique identifier assigned to your gateway during activation. This ID becomes part of the gateway Amazon Resource Name (ARN), which you use as input for other operations.

Valid Values: 50 to 500 lowercase letters, numbers, periods (.), and hyphens (-).

viVolumeType :: Lens' VolumeInfo (Maybe Text) Source #

Undocumented member.

VolumeRecoveryPointInfo

data VolumeRecoveryPointInfo Source #

See: volumeRecoveryPointInfo smart constructor.

Instances

Eq VolumeRecoveryPointInfo Source # 
Data VolumeRecoveryPointInfo Source # 

Methods

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

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

toConstr :: VolumeRecoveryPointInfo -> Constr #

dataTypeOf :: VolumeRecoveryPointInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read VolumeRecoveryPointInfo Source # 
Show VolumeRecoveryPointInfo Source # 
Generic VolumeRecoveryPointInfo Source # 
Hashable VolumeRecoveryPointInfo Source # 
NFData VolumeRecoveryPointInfo Source # 

Methods

rnf :: VolumeRecoveryPointInfo -> () #

FromJSON VolumeRecoveryPointInfo Source # 
type Rep VolumeRecoveryPointInfo Source # 
type Rep VolumeRecoveryPointInfo = D1 (MetaData "VolumeRecoveryPointInfo" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "VolumeRecoveryPointInfo'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_vrpiVolumeRecoveryPointTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_vrpiVolumeARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_vrpiVolumeSizeInBytes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer))) (S1 (MetaSel (Just Symbol "_vrpiVolumeUsageInBytes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer))))))

volumeRecoveryPointInfo :: VolumeRecoveryPointInfo Source #

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

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

VolumeiSCSIAttributes

data VolumeiSCSIAttributes Source #

Lists iSCSI information about a volume.

See: volumeiSCSIAttributes smart constructor.

Instances

Eq VolumeiSCSIAttributes Source # 
Data VolumeiSCSIAttributes Source # 

Methods

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

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

toConstr :: VolumeiSCSIAttributes -> Constr #

dataTypeOf :: VolumeiSCSIAttributes -> DataType #

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

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

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

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

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

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

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

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

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

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

Read VolumeiSCSIAttributes Source # 
Show VolumeiSCSIAttributes Source # 
Generic VolumeiSCSIAttributes Source # 
Hashable VolumeiSCSIAttributes Source # 
NFData VolumeiSCSIAttributes Source # 

Methods

rnf :: VolumeiSCSIAttributes -> () #

FromJSON VolumeiSCSIAttributes Source # 
type Rep VolumeiSCSIAttributes Source # 
type Rep VolumeiSCSIAttributes = D1 (MetaData "VolumeiSCSIAttributes" "Network.AWS.StorageGateway.Types.Product" "amazonka-storagegateway-1.4.4-HOInns2Rr9V9xD6G5ZVbNW" False) (C1 (MetaCons "VolumeiSCSIAttributes'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_vscsiaLunNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) (S1 (MetaSel (Just Symbol "_vscsiaTargetARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_vscsiaChapEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_vscsiaNetworkInterfaceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_vscsiaNetworkInterfacePort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int)))))))

volumeiSCSIAttributes :: VolumeiSCSIAttributes Source #

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

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

vscsiaTargetARN :: Lens' VolumeiSCSIAttributes (Maybe Text) Source #

The Amazon Resource Name (ARN) of the volume target.

vscsiaChapEnabled :: Lens' VolumeiSCSIAttributes (Maybe Bool) Source #

Indicates whether mutual CHAP is enabled for the iSCSI target.

vscsiaNetworkInterfaceId :: Lens' VolumeiSCSIAttributes (Maybe Text) Source #

The network interface identifier.

vscsiaNetworkInterfacePort :: Lens' VolumeiSCSIAttributes (Maybe Int) Source #

The port used to communicate with iSCSI targets.