amazonka-servicecatalog-1.6.1: Amazon Service Catalog 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.ServiceCatalog.Types

Contents

Description

 
Synopsis

Service Configuration

serviceCatalog :: Service Source #

API version 2015-12-10 of the Amazon Service Catalog SDK configuration.

Errors

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

One or more parameters provided to the operation are not valid.

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

The specified resource is a duplicate.

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

An operation requiring TagOptions failed because the TagOptions migration process has not been performed for this account. Please use the AWS console to perform the migration process before retrying the operation.

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

The specified resource was not found.

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

An attempt was made to modify a resource that is in a state that is not valid. Check your resources to ensure that they are in valid states before retrying the operation.

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

The current limits of the service would have been exceeded by this operation. Decrease your resource use or increase your service limits and retry the operation.

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

A resource that is currently in use. Ensure that the resource is not in use and retry the operation.

AccessLevelFilterKey

data AccessLevelFilterKey Source #

Constructors

Account 
Role 
User 
Instances
Bounded AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: AccessLevelFilterKey -> Constr #

dataTypeOf :: AccessLevelFilterKey -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep AccessLevelFilterKey :: Type -> Type #

Hashable AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToJSON AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

NFData AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: AccessLevelFilterKey -> () #

type Rep AccessLevelFilterKey Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep AccessLevelFilterKey = D1 (MetaData "AccessLevelFilterKey" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "Account" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Role" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "User" PrefixI False) (U1 :: Type -> Type)))

ChangeAction

data ChangeAction Source #

Constructors

Add 
Modify 
Remove 
Instances
Bounded ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: ChangeAction -> Constr #

dataTypeOf :: ChangeAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep ChangeAction :: Type -> Type #

Hashable ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromJSON ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

toText :: ChangeAction -> Text #

NFData ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: ChangeAction -> () #

type Rep ChangeAction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ChangeAction = D1 (MetaData "ChangeAction" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "Add" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Modify" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Remove" PrefixI False) (U1 :: Type -> Type)))

CopyOption

data CopyOption Source #

Constructors

CopyTags 
Instances
Bounded CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: CopyOption -> Constr #

dataTypeOf :: CopyOption -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep CopyOption :: Type -> Type #

Hashable CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToJSON CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

toText :: CopyOption -> Text #

NFData CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: CopyOption -> () #

type Rep CopyOption Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep CopyOption = D1 (MetaData "CopyOption" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "CopyTags" PrefixI False) (U1 :: Type -> Type))

CopyProductStatus

data CopyProductStatus Source #

Instances
Bounded CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: CopyProductStatus -> Constr #

dataTypeOf :: CopyProductStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep CopyProductStatus :: Type -> Type #

Hashable CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromJSON CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

NFData CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: CopyProductStatus -> () #

type Rep CopyProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep CopyProductStatus = D1 (MetaData "CopyProductStatus" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "CPSFailed" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CPSInProgress" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CPSSucceeded" PrefixI False) (U1 :: Type -> Type)))

EvaluationType

data EvaluationType Source #

Constructors

Dynamic 
Static 
Instances
Bounded EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: EvaluationType -> Constr #

dataTypeOf :: EvaluationType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep EvaluationType :: Type -> Type #

Hashable EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromJSON EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

NFData EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: EvaluationType -> () #

type Rep EvaluationType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep EvaluationType = D1 (MetaData "EvaluationType" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "Dynamic" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Static" PrefixI False) (U1 :: Type -> Type))

PrincipalType

data PrincipalType Source #

Constructors

IAM 
Instances
Bounded PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: PrincipalType -> Constr #

dataTypeOf :: PrincipalType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep PrincipalType :: Type -> Type #

Hashable PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToJSON PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromJSON PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

toText :: PrincipalType -> Text #

NFData PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: PrincipalType -> () #

type Rep PrincipalType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep PrincipalType = D1 (MetaData "PrincipalType" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "IAM" PrefixI False) (U1 :: Type -> Type))

ProductSource

data ProductSource Source #

Constructors

PSAccount 
Instances
Bounded ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: ProductSource -> Constr #

dataTypeOf :: ProductSource -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep ProductSource :: Type -> Type #

Hashable ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToJSON ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

toText :: ProductSource -> Text #

NFData ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: ProductSource -> () #

type Rep ProductSource Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProductSource = D1 (MetaData "ProductSource" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "PSAccount" PrefixI False) (U1 :: Type -> Type))

ProductType

data ProductType Source #

Instances
Bounded ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: ProductType -> Constr #

dataTypeOf :: ProductType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep ProductType :: Type -> Type #

Hashable ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToJSON ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromJSON ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

toText :: ProductType -> Text #

NFData ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: ProductType -> () #

type Rep ProductType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProductType = D1 (MetaData "ProductType" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "CloudFormationTemplate" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Marketplace" PrefixI False) (U1 :: Type -> Type))

ProductViewFilterBy

data ProductViewFilterBy Source #

Instances
Bounded ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: ProductViewFilterBy -> Constr #

dataTypeOf :: ProductViewFilterBy -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep ProductViewFilterBy :: Type -> Type #

Hashable ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToJSON ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

NFData ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: ProductViewFilterBy -> () #

type Rep ProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProductViewFilterBy = D1 (MetaData "ProductViewFilterBy" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) ((C1 (MetaCons "FullTextSearch" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Owner" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ProductType" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SourceProductId" PrefixI False) (U1 :: Type -> Type)))

ProductViewSortBy

data ProductViewSortBy Source #

Instances
Bounded ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: ProductViewSortBy -> Constr #

dataTypeOf :: ProductViewSortBy -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep ProductViewSortBy :: Type -> Type #

Hashable ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToJSON ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

NFData ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: ProductViewSortBy -> () #

type Rep ProductViewSortBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProductViewSortBy = D1 (MetaData "ProductViewSortBy" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "CreationDate" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Title" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VersionCount" PrefixI False) (U1 :: Type -> Type)))

ProvisionedProductPlanStatus

data ProvisionedProductPlanStatus Source #

Instances
Bounded ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: ProvisionedProductPlanStatus -> Constr #

dataTypeOf :: ProvisionedProductPlanStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep ProvisionedProductPlanStatus :: Type -> Type #

Hashable ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromJSON ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

NFData ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProvisionedProductPlanStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProvisionedProductPlanStatus = D1 (MetaData "ProvisionedProductPlanStatus" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) ((C1 (MetaCons "CreateFailed" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CreateInProgress" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CreateSuccess" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "ExecuteFailed" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ExecuteInProgress" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ExecuteSuccess" PrefixI False) (U1 :: Type -> Type))))

ProvisionedProductPlanType

data ProvisionedProductPlanType Source #

Constructors

Cloudformation 
Instances
Bounded ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: ProvisionedProductPlanType -> Constr #

dataTypeOf :: ProvisionedProductPlanType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep ProvisionedProductPlanType :: Type -> Type #

Hashable ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToJSON ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromJSON ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

NFData ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProvisionedProductPlanType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProvisionedProductPlanType = D1 (MetaData "ProvisionedProductPlanType" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "Cloudformation" PrefixI False) (U1 :: Type -> Type))

ProvisionedProductStatus

data ProvisionedProductStatus Source #

Instances
Bounded ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: ProvisionedProductStatus -> Constr #

dataTypeOf :: ProvisionedProductStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep ProvisionedProductStatus :: Type -> Type #

Hashable ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromJSON ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

NFData ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProvisionedProductStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProvisionedProductStatus = D1 (MetaData "ProvisionedProductStatus" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) ((C1 (MetaCons "PPSAvailable" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PPSError'" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "PPSPlanInProgress" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "PPSTainted" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PPSUnderChange" PrefixI False) (U1 :: Type -> Type))))

ProvisionedProductViewFilterBy

data ProvisionedProductViewFilterBy Source #

Constructors

SearchQuery 
Instances
Bounded ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: ProvisionedProductViewFilterBy -> Constr #

dataTypeOf :: ProvisionedProductViewFilterBy -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep ProvisionedProductViewFilterBy :: Type -> Type #

Hashable ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToJSON ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

NFData ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProvisionedProductViewFilterBy Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProvisionedProductViewFilterBy = D1 (MetaData "ProvisionedProductViewFilterBy" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "SearchQuery" PrefixI False) (U1 :: Type -> Type))

ProvisioningArtifactPropertyName

data ProvisioningArtifactPropertyName Source #

Constructors

Id 
Instances
Bounded ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: ProvisioningArtifactPropertyName -> Constr #

dataTypeOf :: ProvisioningArtifactPropertyName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep ProvisioningArtifactPropertyName :: Type -> Type #

Hashable ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToJSON ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

NFData ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProvisioningArtifactPropertyName Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProvisioningArtifactPropertyName = D1 (MetaData "ProvisioningArtifactPropertyName" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "Id" PrefixI False) (U1 :: Type -> Type))

ProvisioningArtifactType

data ProvisioningArtifactType Source #

Instances
Bounded ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: ProvisioningArtifactType -> Constr #

dataTypeOf :: ProvisioningArtifactType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep ProvisioningArtifactType :: Type -> Type #

Hashable ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToJSON ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromJSON ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

NFData ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProvisioningArtifactType Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ProvisioningArtifactType = D1 (MetaData "ProvisioningArtifactType" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "PATCloudFormationTemplate" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "PATMarketplaceAMI" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PATMarketplaceCar" PrefixI False) (U1 :: Type -> Type)))

RecordStatus

data RecordStatus Source #

Instances
Bounded RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: RecordStatus -> Constr #

dataTypeOf :: RecordStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep RecordStatus :: Type -> Type #

Hashable RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromJSON RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

toText :: RecordStatus -> Text #

NFData RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: RecordStatus -> () #

type Rep RecordStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep RecordStatus = D1 (MetaData "RecordStatus" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) ((C1 (MetaCons "RSCreated" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RSFailed" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "RSInProgress" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "RSInProgressInError" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RSSucceeded" PrefixI False) (U1 :: Type -> Type))))

Replacement

data Replacement Source #

Constructors

Conditional 
False' 
True' 
Instances
Bounded Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: Replacement -> Constr #

dataTypeOf :: Replacement -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep Replacement :: Type -> Type #

Hashable Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromJSON Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

toText :: Replacement -> Text #

NFData Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: Replacement -> () #

type Rep Replacement Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep Replacement = D1 (MetaData "Replacement" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "Conditional" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "False'" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "True'" PrefixI False) (U1 :: Type -> Type)))

RequestStatus

data RequestStatus Source #

Constructors

Available 
Creating 
Failed 
Instances
Bounded RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: RequestStatus -> Constr #

dataTypeOf :: RequestStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep RequestStatus :: Type -> Type #

Hashable RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromJSON RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

toText :: RequestStatus -> Text #

NFData RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: RequestStatus -> () #

type Rep RequestStatus Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep RequestStatus = D1 (MetaData "RequestStatus" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "Available" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Creating" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Failed" PrefixI False) (U1 :: Type -> Type)))

RequiresRecreation

data RequiresRecreation Source #

Constructors

Always 
Conditionally 
Never 
Instances
Bounded RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: RequiresRecreation -> Constr #

dataTypeOf :: RequiresRecreation -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep RequiresRecreation :: Type -> Type #

Hashable RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromJSON RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

NFData RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: RequiresRecreation -> () #

type Rep RequiresRecreation Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep RequiresRecreation = D1 (MetaData "RequiresRecreation" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "Always" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Conditionally" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Never" PrefixI False) (U1 :: Type -> Type)))

ResourceAttribute

data ResourceAttribute Source #

Instances
Bounded ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: ResourceAttribute -> Constr #

dataTypeOf :: ResourceAttribute -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep ResourceAttribute :: Type -> Type #

Hashable ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromJSON ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

FromText ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

NFData ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: ResourceAttribute -> () #

type Rep ResourceAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep ResourceAttribute = D1 (MetaData "ResourceAttribute" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) ((C1 (MetaCons "Creationpolicy" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Deletionpolicy" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Metadata" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Properties" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Tags" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Updatepolicy" PrefixI False) (U1 :: Type -> Type))))

SortOrder

data SortOrder Source #

Constructors

Ascending 
Descending 
Instances
Bounded SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Enum SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Eq SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Data SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

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

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

toConstr :: SortOrder -> Constr #

dataTypeOf :: SortOrder -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Read SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Show SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Generic SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Associated Types

type Rep SortOrder :: Type -> Type #

Hashable SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToJSON SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToHeader SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToQuery SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToByteString SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

toBS :: SortOrder -> ByteString #

FromText SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

ToText SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

toText :: SortOrder -> Text #

NFData SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

Methods

rnf :: SortOrder -> () #

type Rep SortOrder Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Sum

type Rep SortOrder = D1 (MetaData "SortOrder" "Network.AWS.ServiceCatalog.Types.Sum" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "Ascending" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Descending" PrefixI False) (U1 :: Type -> Type))

AccessLevelFilter

data AccessLevelFilter Source #

The access level to use to filter results.

See: accessLevelFilter smart constructor.

Instances
Eq AccessLevelFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data AccessLevelFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: AccessLevelFilter -> Constr #

dataTypeOf :: AccessLevelFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AccessLevelFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show AccessLevelFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic AccessLevelFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep AccessLevelFilter :: Type -> Type #

Hashable AccessLevelFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

ToJSON AccessLevelFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData AccessLevelFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: AccessLevelFilter -> () #

type Rep AccessLevelFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep AccessLevelFilter = D1 (MetaData "AccessLevelFilter" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "AccessLevelFilter'" PrefixI True) (S1 (MetaSel (Just "_alfValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_alfKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AccessLevelFilterKey))))

accessLevelFilter :: AccessLevelFilter Source #

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

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

  • alfValue - The user to which the access level applies. The only supported value is Self .
  • alfKey - The access level. * Account - Filter results based on the account. * Role - Filter results based on the federated role of the specified user. * User - Filter results based on the specified user.

alfValue :: Lens' AccessLevelFilter (Maybe Text) Source #

The user to which the access level applies. The only supported value is Self .

alfKey :: Lens' AccessLevelFilter (Maybe AccessLevelFilterKey) Source #

The access level. * Account - Filter results based on the account. * Role - Filter results based on the federated role of the specified user. * User - Filter results based on the specified user.

CloudWatchDashboard

data CloudWatchDashboard Source #

Information about a CloudWatch dashboard.

See: cloudWatchDashboard smart constructor.

Instances
Eq CloudWatchDashboard Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data CloudWatchDashboard Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: CloudWatchDashboard -> Constr #

dataTypeOf :: CloudWatchDashboard -> DataType #

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

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

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

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

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

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

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

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

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

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

Read CloudWatchDashboard Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show CloudWatchDashboard Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic CloudWatchDashboard Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep CloudWatchDashboard :: Type -> Type #

Hashable CloudWatchDashboard Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON CloudWatchDashboard Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData CloudWatchDashboard Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: CloudWatchDashboard -> () #

type Rep CloudWatchDashboard Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep CloudWatchDashboard = D1 (MetaData "CloudWatchDashboard" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" True) (C1 (MetaCons "CloudWatchDashboard'" PrefixI True) (S1 (MetaSel (Just "_cwdName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

cloudWatchDashboard :: CloudWatchDashboard Source #

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

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

  • cwdName - The name of the CloudWatch dashboard.

cwdName :: Lens' CloudWatchDashboard (Maybe Text) Source #

The name of the CloudWatch dashboard.

ConstraintDetail

data ConstraintDetail Source #

Information about a constraint.

See: constraintDetail smart constructor.

Instances
Eq ConstraintDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ConstraintDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ConstraintDetail -> Constr #

dataTypeOf :: ConstraintDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ConstraintDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ConstraintDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ConstraintDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ConstraintDetail :: Type -> Type #

Hashable ConstraintDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ConstraintDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ConstraintDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: ConstraintDetail -> () #

type Rep ConstraintDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ConstraintDetail = D1 (MetaData "ConstraintDetail" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ConstraintDetail'" PrefixI True) ((S1 (MetaSel (Just "_cdConstraintId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_cdOwner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_cdType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_cdDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

constraintDetail :: ConstraintDetail Source #

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

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

  • cdConstraintId - The identifier of the constraint.
  • cdOwner - The owner of the constraint.
  • cdType - The type of constraint. * LAUNCH * NOTIFICATION * TEMPLATE
  • cdDescription - The description of the constraint.

cdConstraintId :: Lens' ConstraintDetail (Maybe Text) Source #

The identifier of the constraint.

cdOwner :: Lens' ConstraintDetail (Maybe Text) Source #

The owner of the constraint.

cdType :: Lens' ConstraintDetail (Maybe Text) Source #

The type of constraint. * LAUNCH * NOTIFICATION * TEMPLATE

cdDescription :: Lens' ConstraintDetail (Maybe Text) Source #

The description of the constraint.

ConstraintSummary

data ConstraintSummary Source #

Summary information about a constraint.

See: constraintSummary smart constructor.

Instances
Eq ConstraintSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ConstraintSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ConstraintSummary -> Constr #

dataTypeOf :: ConstraintSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ConstraintSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ConstraintSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ConstraintSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ConstraintSummary :: Type -> Type #

Hashable ConstraintSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ConstraintSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ConstraintSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: ConstraintSummary -> () #

type Rep ConstraintSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ConstraintSummary = D1 (MetaData "ConstraintSummary" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ConstraintSummary'" PrefixI True) (S1 (MetaSel (Just "_csType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_csDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

constraintSummary :: ConstraintSummary Source #

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

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

  • csType - The type of constraint. * LAUNCH * NOTIFICATION * TEMPLATE
  • csDescription - The description of the constraint.

csType :: Lens' ConstraintSummary (Maybe Text) Source #

The type of constraint. * LAUNCH * NOTIFICATION * TEMPLATE

csDescription :: Lens' ConstraintSummary (Maybe Text) Source #

The description of the constraint.

LaunchPathSummary

data LaunchPathSummary Source #

Summary information about a product path for a user.

See: launchPathSummary smart constructor.

Instances
Eq LaunchPathSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data LaunchPathSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: LaunchPathSummary -> Constr #

dataTypeOf :: LaunchPathSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LaunchPathSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show LaunchPathSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic LaunchPathSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep LaunchPathSummary :: Type -> Type #

Hashable LaunchPathSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON LaunchPathSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData LaunchPathSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: LaunchPathSummary -> () #

type Rep LaunchPathSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep LaunchPathSummary = D1 (MetaData "LaunchPathSummary" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "LaunchPathSummary'" PrefixI True) ((S1 (MetaSel (Just "_lpsConstraintSummaries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ConstraintSummary])) :*: S1 (MetaSel (Just "_lpsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_lpsId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lpsTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Tag])))))

launchPathSummary :: LaunchPathSummary Source #

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

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

  • lpsConstraintSummaries - The constraints on the portfolio-product relationship.
  • lpsName - The name of the portfolio to which the user was assigned.
  • lpsId - The identifier of the product path.
  • lpsTags - The tags associated with this product path.

lpsConstraintSummaries :: Lens' LaunchPathSummary [ConstraintSummary] Source #

The constraints on the portfolio-product relationship.

lpsName :: Lens' LaunchPathSummary (Maybe Text) Source #

The name of the portfolio to which the user was assigned.

lpsId :: Lens' LaunchPathSummary (Maybe Text) Source #

The identifier of the product path.

lpsTags :: Lens' LaunchPathSummary [Tag] Source #

The tags associated with this product path.

ListRecordHistorySearchFilter

data ListRecordHistorySearchFilter Source #

The search filter to use when listing history records.

See: listRecordHistorySearchFilter smart constructor.

Instances
Eq ListRecordHistorySearchFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ListRecordHistorySearchFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ListRecordHistorySearchFilter -> Constr #

dataTypeOf :: ListRecordHistorySearchFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ListRecordHistorySearchFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ListRecordHistorySearchFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ListRecordHistorySearchFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ListRecordHistorySearchFilter :: Type -> Type #

Hashable ListRecordHistorySearchFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

ToJSON ListRecordHistorySearchFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ListRecordHistorySearchFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ListRecordHistorySearchFilter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ListRecordHistorySearchFilter = D1 (MetaData "ListRecordHistorySearchFilter" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ListRecordHistorySearchFilter'" PrefixI True) (S1 (MetaSel (Just "_lrhsfValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_lrhsfKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

listRecordHistorySearchFilter :: ListRecordHistorySearchFilter Source #

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

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

  • lrhsfValue - The filter value.
  • lrhsfKey - The filter key. * product - Filter results based on the specified product identifier. * provisionedproduct - Filter results based on the provisioned product identifier.

lrhsfKey :: Lens' ListRecordHistorySearchFilter (Maybe Text) Source #

The filter key. * product - Filter results based on the specified product identifier. * provisionedproduct - Filter results based on the provisioned product identifier.

ListTagOptionsFilters

data ListTagOptionsFilters Source #

Filters to use when listing TagOptions.

See: listTagOptionsFilters smart constructor.

Instances
Eq ListTagOptionsFilters Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ListTagOptionsFilters Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ListTagOptionsFilters -> Constr #

dataTypeOf :: ListTagOptionsFilters -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ListTagOptionsFilters Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ListTagOptionsFilters Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ListTagOptionsFilters Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ListTagOptionsFilters :: Type -> Type #

Hashable ListTagOptionsFilters Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

ToJSON ListTagOptionsFilters Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ListTagOptionsFilters Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: ListTagOptionsFilters -> () #

type Rep ListTagOptionsFilters Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ListTagOptionsFilters = D1 (MetaData "ListTagOptionsFilters" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ListTagOptionsFilters'" PrefixI True) (S1 (MetaSel (Just "_ltofValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_ltofActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "_ltofKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

listTagOptionsFilters :: ListTagOptionsFilters Source #

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

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

ParameterConstraints

data ParameterConstraints Source #

The constraints that the administrator has put on the parameter.

See: parameterConstraints smart constructor.

Instances
Eq ParameterConstraints Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ParameterConstraints Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ParameterConstraints -> Constr #

dataTypeOf :: ParameterConstraints -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ParameterConstraints Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ParameterConstraints Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ParameterConstraints Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ParameterConstraints :: Type -> Type #

Hashable ParameterConstraints Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ParameterConstraints Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ParameterConstraints Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: ParameterConstraints -> () #

type Rep ParameterConstraints Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ParameterConstraints = D1 (MetaData "ParameterConstraints" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" True) (C1 (MetaCons "ParameterConstraints'" PrefixI True) (S1 (MetaSel (Just "_pcAllowedValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Text]))))

parameterConstraints :: ParameterConstraints Source #

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

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

  • pcAllowedValues - The values that the administrator has allowed for the parameter.

pcAllowedValues :: Lens' ParameterConstraints [Text] Source #

The values that the administrator has allowed for the parameter.

PortfolioDetail

data PortfolioDetail Source #

Information about a portfolio.

See: portfolioDetail smart constructor.

Instances
Eq PortfolioDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data PortfolioDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: PortfolioDetail -> Constr #

dataTypeOf :: PortfolioDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read PortfolioDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show PortfolioDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic PortfolioDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep PortfolioDetail :: Type -> Type #

Hashable PortfolioDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON PortfolioDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData PortfolioDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: PortfolioDetail -> () #

type Rep PortfolioDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep PortfolioDetail = D1 (MetaData "PortfolioDetail" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "PortfolioDetail'" PrefixI True) ((S1 (MetaSel (Just "_pdARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_pdCreatedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: S1 (MetaSel (Just "_pdId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "_pdDisplayName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_pdDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pdProviderName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

portfolioDetail :: PortfolioDetail Source #

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

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

pdARN :: Lens' PortfolioDetail (Maybe Text) Source #

The ARN assigned to the portfolio.

pdCreatedTime :: Lens' PortfolioDetail (Maybe UTCTime) Source #

The UTC time stamp of the creation time.

pdId :: Lens' PortfolioDetail (Maybe Text) Source #

The portfolio identifier.

pdDisplayName :: Lens' PortfolioDetail (Maybe Text) Source #

The name to use for display purposes.

pdDescription :: Lens' PortfolioDetail (Maybe Text) Source #

The description of the portfolio.

pdProviderName :: Lens' PortfolioDetail (Maybe Text) Source #

The name of the portfolio provider.

Principal

data Principal Source #

Information about a principal.

See: principal smart constructor.

Instances
Eq Principal Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data Principal Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: Principal -> Constr #

dataTypeOf :: Principal -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Principal Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show Principal Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic Principal Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep Principal :: Type -> Type #

Hashable Principal Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON Principal Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData Principal Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: Principal -> () #

type Rep Principal Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep Principal = D1 (MetaData "Principal" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "Principal'" PrefixI True) (S1 (MetaSel (Just "_pPrincipalType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PrincipalType)) :*: S1 (MetaSel (Just "_pPrincipalARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

principal :: Principal Source #

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

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

pPrincipalType :: Lens' Principal (Maybe PrincipalType) Source #

The principal type. The supported value is IAM .

pPrincipalARN :: Lens' Principal (Maybe Text) Source #

The ARN of the principal (IAM user, role, or group).

ProductViewAggregationValue

data ProductViewAggregationValue Source #

A single product view aggregation value/count pair, containing metadata about each product to which the calling user has access.

See: productViewAggregationValue smart constructor.

Instances
Eq ProductViewAggregationValue Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ProductViewAggregationValue Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ProductViewAggregationValue -> Constr #

dataTypeOf :: ProductViewAggregationValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ProductViewAggregationValue Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ProductViewAggregationValue Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ProductViewAggregationValue Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ProductViewAggregationValue :: Type -> Type #

Hashable ProductViewAggregationValue Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ProductViewAggregationValue Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ProductViewAggregationValue Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProductViewAggregationValue Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProductViewAggregationValue = D1 (MetaData "ProductViewAggregationValue" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ProductViewAggregationValue'" PrefixI True) (S1 (MetaSel (Just "_pvavValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pvavApproximateCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))

productViewAggregationValue :: ProductViewAggregationValue Source #

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

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

pvavValue :: Lens' ProductViewAggregationValue (Maybe Text) Source #

The value of the product view aggregation.

pvavApproximateCount :: Lens' ProductViewAggregationValue (Maybe Int) Source #

An approximate count of the products that match the value.

ProductViewDetail

data ProductViewDetail Source #

Information about a product view.

See: productViewDetail smart constructor.

Instances
Eq ProductViewDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ProductViewDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ProductViewDetail -> Constr #

dataTypeOf :: ProductViewDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ProductViewDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ProductViewDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ProductViewDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ProductViewDetail :: Type -> Type #

Hashable ProductViewDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ProductViewDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ProductViewDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: ProductViewDetail -> () #

type Rep ProductViewDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProductViewDetail = D1 (MetaData "ProductViewDetail" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ProductViewDetail'" PrefixI True) ((S1 (MetaSel (Just "_pvdStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RequestStatus)) :*: S1 (MetaSel (Just "_pvdProductViewSummary") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ProductViewSummary))) :*: (S1 (MetaSel (Just "_pvdCreatedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: S1 (MetaSel (Just "_pvdProductARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

productViewDetail :: ProductViewDetail Source #

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

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

  • pvdStatus - The status of the product. * AVAILABLE - The product is ready for use. * CREATING - Product creation has started; the product is not ready for use. * FAILED - An action failed.
  • pvdProductViewSummary - Summary information about the product view.
  • pvdCreatedTime - The UTC time stamp of the creation time.
  • pvdProductARN - The ARN of the product.

pvdStatus :: Lens' ProductViewDetail (Maybe RequestStatus) Source #

The status of the product. * AVAILABLE - The product is ready for use. * CREATING - Product creation has started; the product is not ready for use. * FAILED - An action failed.

pvdProductViewSummary :: Lens' ProductViewDetail (Maybe ProductViewSummary) Source #

Summary information about the product view.

pvdCreatedTime :: Lens' ProductViewDetail (Maybe UTCTime) Source #

The UTC time stamp of the creation time.

pvdProductARN :: Lens' ProductViewDetail (Maybe Text) Source #

The ARN of the product.

ProductViewSummary

data ProductViewSummary Source #

Summary information about a product view.

See: productViewSummary smart constructor.

Instances
Eq ProductViewSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ProductViewSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ProductViewSummary -> Constr #

dataTypeOf :: ProductViewSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ProductViewSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ProductViewSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ProductViewSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ProductViewSummary :: Type -> Type #

Hashable ProductViewSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ProductViewSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ProductViewSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: ProductViewSummary -> () #

type Rep ProductViewSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

productViewSummary :: ProductViewSummary Source #

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

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

  • pvsOwner - The owner of the product. Contact the product administrator for the significance of this value.
  • pvsSupportURL - The URL information to obtain support for this Product.
  • pvsShortDescription - Short description of the product.
  • pvsHasDefaultPath - Indicates whether the product has a default path. If the product does not have a default path, call ListLaunchPaths to disambiguate between paths. Otherwise, ListLaunchPaths is not required, and the output of ProductViewSummary can be used directly with DescribeProvisioningParameters .
  • pvsDistributor - The distributor of the product. Contact the product administrator for the significance of this value.
  • pvsName - The name of the product.
  • pvsId - The product view identifier.
  • pvsType - The product type. Contact the product administrator for the significance of this value. If this value is MARKETPLACE , the product was created by AWS Marketplace.
  • pvsSupportEmail - The email contact information to obtain support for this Product.
  • pvsProductId - The product identifier.
  • pvsSupportDescription - The description of the support for this Product.

pvsOwner :: Lens' ProductViewSummary (Maybe Text) Source #

The owner of the product. Contact the product administrator for the significance of this value.

pvsSupportURL :: Lens' ProductViewSummary (Maybe Text) Source #

The URL information to obtain support for this Product.

pvsShortDescription :: Lens' ProductViewSummary (Maybe Text) Source #

Short description of the product.

pvsHasDefaultPath :: Lens' ProductViewSummary (Maybe Bool) Source #

Indicates whether the product has a default path. If the product does not have a default path, call ListLaunchPaths to disambiguate between paths. Otherwise, ListLaunchPaths is not required, and the output of ProductViewSummary can be used directly with DescribeProvisioningParameters .

pvsDistributor :: Lens' ProductViewSummary (Maybe Text) Source #

The distributor of the product. Contact the product administrator for the significance of this value.

pvsName :: Lens' ProductViewSummary (Maybe Text) Source #

The name of the product.

pvsId :: Lens' ProductViewSummary (Maybe Text) Source #

The product view identifier.

pvsType :: Lens' ProductViewSummary (Maybe ProductType) Source #

The product type. Contact the product administrator for the significance of this value. If this value is MARKETPLACE , the product was created by AWS Marketplace.

pvsSupportEmail :: Lens' ProductViewSummary (Maybe Text) Source #

The email contact information to obtain support for this Product.

pvsProductId :: Lens' ProductViewSummary (Maybe Text) Source #

The product identifier.

pvsSupportDescription :: Lens' ProductViewSummary (Maybe Text) Source #

The description of the support for this Product.

ProvisionedProductAttribute

data ProvisionedProductAttribute Source #

Information about a provisioned product.

See: provisionedProductAttribute smart constructor.

Instances
Eq ProvisionedProductAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ProvisionedProductAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ProvisionedProductAttribute -> Constr #

dataTypeOf :: ProvisionedProductAttribute -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ProvisionedProductAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ProvisionedProductAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ProvisionedProductAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ProvisionedProductAttribute :: Type -> Type #

Hashable ProvisionedProductAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ProvisionedProductAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ProvisionedProductAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisionedProductAttribute Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisionedProductAttribute = D1 (MetaData "ProvisionedProductAttribute" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ProvisionedProductAttribute'" PrefixI True) (((S1 (MetaSel (Just "_ppaIdempotencyToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_ppaStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ProvisionedProductStatus)) :*: S1 (MetaSel (Just "_ppaProvisioningArtifactId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_ppaARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ppaCreatedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))) :*: (S1 (MetaSel (Just "_ppaUserARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ppaStatusMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) :*: (((S1 (MetaSel (Just "_ppaName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ppaLastRecordId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_ppaUserARNSession") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ppaId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_ppaType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ppaPhysicalId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_ppaProductId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ppaTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Tag])))))))

provisionedProductAttribute :: ProvisionedProductAttribute Source #

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

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

  • ppaIdempotencyToken - A unique identifier that you provide to ensure idempotency. If multiple requests differ only by the idempotency token, the same response is returned for each repeated request.
  • ppaStatus - The current status of the provisioned product. * AVAILABLE - Stable state, ready to perform any operation. The most recent operation succeeded and completed. * UNDER_CHANGE - Transitive state, operations performed might not have valid results. Wait for an AVAILABLE status before performing operations. * TAINTED - Stable state, ready to perform any operation. The stack has completed the requested operation but is not exactly what was requested. For example, a request to update to a new version failed and the stack rolled back to the current version. * ERROR - An unexpected error occurred, the provisioned product exists but the stack is not running. For example, CloudFormation received a parameter value that was not valid and could not launch the stack.
  • ppaProvisioningArtifactId - The identifier of the provisioning artifact.
  • ppaARN - The ARN of the provisioned product.
  • ppaCreatedTime - The UTC time stamp of the creation time.
  • ppaUserARN - The Amazon Resource Name (ARN) of the IAM user.
  • ppaStatusMessage - The current status message of the provisioned product.
  • ppaName - The user-friendly name of the provisioned product.
  • ppaLastRecordId - The record identifier of the last request performed on this provisioned product.
  • ppaUserARNSession - The ARN of the IAM user in the session. This ARN might contain a session ID.
  • ppaId - The identifier of the provisioned product.
  • ppaType - The type of provisioned product. The supported value is CFN_STACK .
  • ppaPhysicalId - The assigned identifier for the resource, such as an EC2 instance ID or an S3 bucket name.
  • ppaProductId - The product identifier.
  • ppaTags - One or more tags.

ppaIdempotencyToken :: Lens' ProvisionedProductAttribute (Maybe Text) Source #

A unique identifier that you provide to ensure idempotency. If multiple requests differ only by the idempotency token, the same response is returned for each repeated request.

ppaStatus :: Lens' ProvisionedProductAttribute (Maybe ProvisionedProductStatus) Source #

The current status of the provisioned product. * AVAILABLE - Stable state, ready to perform any operation. The most recent operation succeeded and completed. * UNDER_CHANGE - Transitive state, operations performed might not have valid results. Wait for an AVAILABLE status before performing operations. * TAINTED - Stable state, ready to perform any operation. The stack has completed the requested operation but is not exactly what was requested. For example, a request to update to a new version failed and the stack rolled back to the current version. * ERROR - An unexpected error occurred, the provisioned product exists but the stack is not running. For example, CloudFormation received a parameter value that was not valid and could not launch the stack.

ppaProvisioningArtifactId :: Lens' ProvisionedProductAttribute (Maybe Text) Source #

The identifier of the provisioning artifact.

ppaARN :: Lens' ProvisionedProductAttribute (Maybe Text) Source #

The ARN of the provisioned product.

ppaCreatedTime :: Lens' ProvisionedProductAttribute (Maybe UTCTime) Source #

The UTC time stamp of the creation time.

ppaUserARN :: Lens' ProvisionedProductAttribute (Maybe Text) Source #

The Amazon Resource Name (ARN) of the IAM user.

ppaStatusMessage :: Lens' ProvisionedProductAttribute (Maybe Text) Source #

The current status message of the provisioned product.

ppaName :: Lens' ProvisionedProductAttribute (Maybe Text) Source #

The user-friendly name of the provisioned product.

ppaLastRecordId :: Lens' ProvisionedProductAttribute (Maybe Text) Source #

The record identifier of the last request performed on this provisioned product.

ppaUserARNSession :: Lens' ProvisionedProductAttribute (Maybe Text) Source #

The ARN of the IAM user in the session. This ARN might contain a session ID.

ppaId :: Lens' ProvisionedProductAttribute (Maybe Text) Source #

The identifier of the provisioned product.

ppaType :: Lens' ProvisionedProductAttribute (Maybe Text) Source #

The type of provisioned product. The supported value is CFN_STACK .

ppaPhysicalId :: Lens' ProvisionedProductAttribute (Maybe Text) Source #

The assigned identifier for the resource, such as an EC2 instance ID or an S3 bucket name.

ProvisionedProductDetail

data ProvisionedProductDetail Source #

Information about a provisioned product.

See: provisionedProductDetail smart constructor.

Instances
Eq ProvisionedProductDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ProvisionedProductDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ProvisionedProductDetail -> Constr #

dataTypeOf :: ProvisionedProductDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ProvisionedProductDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ProvisionedProductDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ProvisionedProductDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ProvisionedProductDetail :: Type -> Type #

Hashable ProvisionedProductDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ProvisionedProductDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ProvisionedProductDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisionedProductDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

provisionedProductDetail :: ProvisionedProductDetail Source #

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

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

  • ppdIdempotencyToken - A unique identifier that you provide to ensure idempotency. If multiple requests differ only by the idempotency token, the same response is returned for each repeated request.
  • ppdStatus - The current status of the provisioned product. * AVAILABLE - Stable state, ready to perform any operation. The most recent operation succeeded and completed. * UNDER_CHANGE - Transitive state, operations performed might not have valid results. Wait for an AVAILABLE status before performing operations. * TAINTED - Stable state, ready to perform any operation. The stack has completed the requested operation but is not exactly what was requested. For example, a request to update to a new version failed and the stack rolled back to the current version. * ERROR - An unexpected error occurred, the provisioned product exists but the stack is not running. For example, CloudFormation received a parameter value that was not valid and could not launch the stack.
  • ppdARN - The ARN of the provisioned product.
  • ppdCreatedTime - The UTC time stamp of the creation time.
  • ppdStatusMessage - The current status message of the provisioned product.
  • ppdName - The user-friendly name of the provisioned product.
  • ppdLastRecordId - The record identifier of the last request performed on this provisioned product.
  • ppdId - The identifier of the provisioned product.
  • ppdType - The type of provisioned product. The supported value is CFN_STACK .

ppdIdempotencyToken :: Lens' ProvisionedProductDetail (Maybe Text) Source #

A unique identifier that you provide to ensure idempotency. If multiple requests differ only by the idempotency token, the same response is returned for each repeated request.

ppdStatus :: Lens' ProvisionedProductDetail (Maybe ProvisionedProductStatus) Source #

The current status of the provisioned product. * AVAILABLE - Stable state, ready to perform any operation. The most recent operation succeeded and completed. * UNDER_CHANGE - Transitive state, operations performed might not have valid results. Wait for an AVAILABLE status before performing operations. * TAINTED - Stable state, ready to perform any operation. The stack has completed the requested operation but is not exactly what was requested. For example, a request to update to a new version failed and the stack rolled back to the current version. * ERROR - An unexpected error occurred, the provisioned product exists but the stack is not running. For example, CloudFormation received a parameter value that was not valid and could not launch the stack.

ppdARN :: Lens' ProvisionedProductDetail (Maybe Text) Source #

The ARN of the provisioned product.

ppdCreatedTime :: Lens' ProvisionedProductDetail (Maybe UTCTime) Source #

The UTC time stamp of the creation time.

ppdStatusMessage :: Lens' ProvisionedProductDetail (Maybe Text) Source #

The current status message of the provisioned product.

ppdName :: Lens' ProvisionedProductDetail (Maybe Text) Source #

The user-friendly name of the provisioned product.

ppdLastRecordId :: Lens' ProvisionedProductDetail (Maybe Text) Source #

The record identifier of the last request performed on this provisioned product.

ppdId :: Lens' ProvisionedProductDetail (Maybe Text) Source #

The identifier of the provisioned product.

ppdType :: Lens' ProvisionedProductDetail (Maybe Text) Source #

The type of provisioned product. The supported value is CFN_STACK .

ProvisionedProductPlanDetails

data ProvisionedProductPlanDetails Source #

Information about a plan.

See: provisionedProductPlanDetails smart constructor.

Instances
Eq ProvisionedProductPlanDetails Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ProvisionedProductPlanDetails Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ProvisionedProductPlanDetails -> Constr #

dataTypeOf :: ProvisionedProductPlanDetails -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ProvisionedProductPlanDetails Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ProvisionedProductPlanDetails Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ProvisionedProductPlanDetails Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ProvisionedProductPlanDetails :: Type -> Type #

Hashable ProvisionedProductPlanDetails Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ProvisionedProductPlanDetails Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ProvisionedProductPlanDetails Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisionedProductPlanDetails Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisionedProductPlanDetails = D1 (MetaData "ProvisionedProductPlanDetails" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ProvisionedProductPlanDetails'" PrefixI True) (((S1 (MetaSel (Just "_pppdStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ProvisionedProductPlanStatus)) :*: (S1 (MetaSel (Just "_pppdProvisionProductId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pppdProvisioningArtifactId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_pppdProvisionProductName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pppdCreatedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))) :*: (S1 (MetaSel (Just "_pppdNotificationARNs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 (MetaSel (Just "_pppdPlanId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) :*: (((S1 (MetaSel (Just "_pppdPlanName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pppdStatusMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_pppdUpdatedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: S1 (MetaSel (Just "_pppdPathId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_pppdProvisioningParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [UpdateProvisioningParameter])) :*: S1 (MetaSel (Just "_pppdPlanType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ProvisionedProductPlanType))) :*: (S1 (MetaSel (Just "_pppdProductId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pppdTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Tag])))))))

provisionedProductPlanDetails :: ProvisionedProductPlanDetails Source #

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

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

pppdProvisioningArtifactId :: Lens' ProvisionedProductPlanDetails (Maybe Text) Source #

The identifier of the provisioning artifact.

pppdProvisionProductName :: Lens' ProvisionedProductPlanDetails (Maybe Text) Source #

The user-friendly name of the provisioned product.

pppdCreatedTime :: Lens' ProvisionedProductPlanDetails (Maybe UTCTime) Source #

The UTC time stamp of the creation time.

pppdNotificationARNs :: Lens' ProvisionedProductPlanDetails [Text] Source #

Passed to CloudFormation. The SNS topic ARNs to which to publish stack-related events.

pppdUpdatedTime :: Lens' ProvisionedProductPlanDetails (Maybe UTCTime) Source #

The time when the plan was last updated.

pppdPathId :: Lens' ProvisionedProductPlanDetails (Maybe Text) Source #

The path identifier of the product. This value is optional if the product has a default path, and required if the product has more than one path. To list the paths for a product, use ListLaunchPaths .

pppdProvisioningParameters :: Lens' ProvisionedProductPlanDetails [UpdateProvisioningParameter] Source #

Parameters specified by the administrator that are required for provisioning the product.

ProvisionedProductPlanSummary

data ProvisionedProductPlanSummary Source #

Summary information about a plan.

See: provisionedProductPlanSummary smart constructor.

Instances
Eq ProvisionedProductPlanSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ProvisionedProductPlanSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ProvisionedProductPlanSummary -> Constr #

dataTypeOf :: ProvisionedProductPlanSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ProvisionedProductPlanSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ProvisionedProductPlanSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ProvisionedProductPlanSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ProvisionedProductPlanSummary :: Type -> Type #

Hashable ProvisionedProductPlanSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ProvisionedProductPlanSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ProvisionedProductPlanSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisionedProductPlanSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisionedProductPlanSummary = D1 (MetaData "ProvisionedProductPlanSummary" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ProvisionedProductPlanSummary'" PrefixI True) ((S1 (MetaSel (Just "_pppsProvisionProductId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_pppsProvisioningArtifactId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pppsProvisionProductName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "_pppsPlanId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_pppsPlanName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pppsPlanType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ProvisionedProductPlanType))))))

provisionedProductPlanSummary :: ProvisionedProductPlanSummary Source #

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

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

pppsProvisioningArtifactId :: Lens' ProvisionedProductPlanSummary (Maybe Text) Source #

The identifier of the provisioning artifact.

pppsProvisionProductName :: Lens' ProvisionedProductPlanSummary (Maybe Text) Source #

The user-friendly name of the provisioned product.

ProvisioningArtifact

data ProvisioningArtifact Source #

Information about a provisioning artifact. A provisioning artifact is also known as a product version.

See: provisioningArtifact smart constructor.

Instances
Eq ProvisioningArtifact Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ProvisioningArtifact Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ProvisioningArtifact -> Constr #

dataTypeOf :: ProvisioningArtifact -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ProvisioningArtifact Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ProvisioningArtifact Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ProvisioningArtifact Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ProvisioningArtifact :: Type -> Type #

Hashable ProvisioningArtifact Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ProvisioningArtifact Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ProvisioningArtifact Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: ProvisioningArtifact -> () #

type Rep ProvisioningArtifact Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisioningArtifact = D1 (MetaData "ProvisioningArtifact" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ProvisioningArtifact'" PrefixI True) ((S1 (MetaSel (Just "_paCreatedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: S1 (MetaSel (Just "_paName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_paId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_paDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

provisioningArtifact :: ProvisioningArtifact Source #

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

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

  • paCreatedTime - The UTC time stamp of the creation time.
  • paName - The name of the provisioning artifact.
  • paId - The identifier of the provisioning artifact.
  • paDescription - The description of the provisioning artifact.

paCreatedTime :: Lens' ProvisioningArtifact (Maybe UTCTime) Source #

The UTC time stamp of the creation time.

paName :: Lens' ProvisioningArtifact (Maybe Text) Source #

The name of the provisioning artifact.

paId :: Lens' ProvisioningArtifact (Maybe Text) Source #

The identifier of the provisioning artifact.

paDescription :: Lens' ProvisioningArtifact (Maybe Text) Source #

The description of the provisioning artifact.

ProvisioningArtifactDetail

data ProvisioningArtifactDetail Source #

Information about a provisioning artifact (also known as a version) for a product.

See: provisioningArtifactDetail smart constructor.

Instances
Eq ProvisioningArtifactDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ProvisioningArtifactDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ProvisioningArtifactDetail -> Constr #

dataTypeOf :: ProvisioningArtifactDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ProvisioningArtifactDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ProvisioningArtifactDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ProvisioningArtifactDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ProvisioningArtifactDetail :: Type -> Type #

Hashable ProvisioningArtifactDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ProvisioningArtifactDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ProvisioningArtifactDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisioningArtifactDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisioningArtifactDetail = D1 (MetaData "ProvisioningArtifactDetail" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ProvisioningArtifactDetail'" PrefixI True) ((S1 (MetaSel (Just "_padCreatedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: (S1 (MetaSel (Just "_padActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "_padName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "_padId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_padType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ProvisioningArtifactType)) :*: S1 (MetaSel (Just "_padDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

provisioningArtifactDetail :: ProvisioningArtifactDetail Source #

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

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

  • padCreatedTime - The UTC time stamp of the creation time.
  • padActive - Indicates whether the product version is active.
  • padName - The name of the provisioning artifact.
  • padId - The identifier of the provisioning artifact.
  • padType - The type of provisioning artifact. * CLOUD_FORMATION_TEMPLATE - AWS CloudFormation template * MARKETPLACE_AMI - AWS Marketplace AMI * MARKETPLACE_CAR - AWS Marketplace Clusters and AWS Resources
  • padDescription - The description of the provisioning artifact.

padCreatedTime :: Lens' ProvisioningArtifactDetail (Maybe UTCTime) Source #

The UTC time stamp of the creation time.

padActive :: Lens' ProvisioningArtifactDetail (Maybe Bool) Source #

Indicates whether the product version is active.

padName :: Lens' ProvisioningArtifactDetail (Maybe Text) Source #

The name of the provisioning artifact.

padId :: Lens' ProvisioningArtifactDetail (Maybe Text) Source #

The identifier of the provisioning artifact.

padType :: Lens' ProvisioningArtifactDetail (Maybe ProvisioningArtifactType) Source #

The type of provisioning artifact. * CLOUD_FORMATION_TEMPLATE - AWS CloudFormation template * MARKETPLACE_AMI - AWS Marketplace AMI * MARKETPLACE_CAR - AWS Marketplace Clusters and AWS Resources

padDescription :: Lens' ProvisioningArtifactDetail (Maybe Text) Source #

The description of the provisioning artifact.

ProvisioningArtifactParameter

data ProvisioningArtifactParameter Source #

Information about a parameter used to provision a product.

See: provisioningArtifactParameter smart constructor.

Instances
Eq ProvisioningArtifactParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ProvisioningArtifactParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ProvisioningArtifactParameter -> Constr #

dataTypeOf :: ProvisioningArtifactParameter -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ProvisioningArtifactParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ProvisioningArtifactParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ProvisioningArtifactParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ProvisioningArtifactParameter :: Type -> Type #

Hashable ProvisioningArtifactParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ProvisioningArtifactParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ProvisioningArtifactParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisioningArtifactParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisioningArtifactParameter = D1 (MetaData "ProvisioningArtifactParameter" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ProvisioningArtifactParameter'" PrefixI True) ((S1 (MetaSel (Just "_pIsNoEcho") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 (MetaSel (Just "_pParameterKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pParameterType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "_pParameterConstraints") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ParameterConstraints)) :*: (S1 (MetaSel (Just "_pDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

provisioningArtifactParameter :: ProvisioningArtifactParameter Source #

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

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

pIsNoEcho :: Lens' ProvisioningArtifactParameter (Maybe Bool) Source #

If this value is true, the value for this parameter is obfuscated from view when the parameter is retrieved. This parameter is used to hide sensitive information.

pParameterConstraints :: Lens' ProvisioningArtifactParameter (Maybe ParameterConstraints) Source #

Constraints that the administrator has put on a parameter.

pDescription :: Lens' ProvisioningArtifactParameter (Maybe Text) Source #

The description of the parameter.

ProvisioningArtifactProperties

data ProvisioningArtifactProperties Source #

Information about a provisioning artifact (also known as a version) for a product.

See: provisioningArtifactProperties smart constructor.

Instances
Eq ProvisioningArtifactProperties Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ProvisioningArtifactProperties Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ProvisioningArtifactProperties -> Constr #

dataTypeOf :: ProvisioningArtifactProperties -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ProvisioningArtifactProperties Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ProvisioningArtifactProperties Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ProvisioningArtifactProperties Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ProvisioningArtifactProperties :: Type -> Type #

Hashable ProvisioningArtifactProperties Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

ToJSON ProvisioningArtifactProperties Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ProvisioningArtifactProperties Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisioningArtifactProperties Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisioningArtifactProperties = D1 (MetaData "ProvisioningArtifactProperties" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ProvisioningArtifactProperties'" PrefixI True) ((S1 (MetaSel (Just "_papName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_papType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ProvisioningArtifactType))) :*: (S1 (MetaSel (Just "_papDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_papInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Map Text Text)))))

provisioningArtifactProperties :: ProvisioningArtifactProperties Source #

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

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

  • papName - The name of the provisioning artifact (for example, v1 v2beta). No spaces are allowed.
  • papType - The type of provisioning artifact. * CLOUD_FORMATION_TEMPLATE - AWS CloudFormation template * MARKETPLACE_AMI - AWS Marketplace AMI * MARKETPLACE_CAR - AWS Marketplace Clusters and AWS Resources
  • papDescription - The description of the provisioning artifact, including how it differs from the previous provisioning artifact.
  • papInfo - The URL of the CloudFormation template in Amazon S3. Specify the URL in JSON format as follows: LoadTemplateFromURL: "https://s3.amazonaws.com/cf-templates-ozkq9d3hgiq2-us-east-1/..."

papName :: Lens' ProvisioningArtifactProperties (Maybe Text) Source #

The name of the provisioning artifact (for example, v1 v2beta). No spaces are allowed.

papType :: Lens' ProvisioningArtifactProperties (Maybe ProvisioningArtifactType) Source #

The type of provisioning artifact. * CLOUD_FORMATION_TEMPLATE - AWS CloudFormation template * MARKETPLACE_AMI - AWS Marketplace AMI * MARKETPLACE_CAR - AWS Marketplace Clusters and AWS Resources

papDescription :: Lens' ProvisioningArtifactProperties (Maybe Text) Source #

The description of the provisioning artifact, including how it differs from the previous provisioning artifact.

papInfo :: Lens' ProvisioningArtifactProperties (HashMap Text Text) Source #

The URL of the CloudFormation template in Amazon S3. Specify the URL in JSON format as follows: LoadTemplateFromURL: "https://s3.amazonaws.com/cf-templates-ozkq9d3hgiq2-us-east-1/..."

ProvisioningArtifactSummary

data ProvisioningArtifactSummary Source #

Summary information about a provisioning artifact (also known as a version) for a product.

See: provisioningArtifactSummary smart constructor.

Instances
Eq ProvisioningArtifactSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ProvisioningArtifactSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ProvisioningArtifactSummary -> Constr #

dataTypeOf :: ProvisioningArtifactSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ProvisioningArtifactSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ProvisioningArtifactSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ProvisioningArtifactSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ProvisioningArtifactSummary :: Type -> Type #

Hashable ProvisioningArtifactSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ProvisioningArtifactSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ProvisioningArtifactSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisioningArtifactSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisioningArtifactSummary = D1 (MetaData "ProvisioningArtifactSummary" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ProvisioningArtifactSummary'" PrefixI True) ((S1 (MetaSel (Just "_pasProvisioningArtifactMetadata") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text))) :*: S1 (MetaSel (Just "_pasCreatedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))) :*: (S1 (MetaSel (Just "_pasName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_pasId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pasDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

provisioningArtifactSummary :: ProvisioningArtifactSummary Source #

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

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

pasProvisioningArtifactMetadata :: Lens' ProvisioningArtifactSummary (HashMap Text Text) Source #

The metadata for the provisioning artifact. This is used with AWS Marketplace products.

pasCreatedTime :: Lens' ProvisioningArtifactSummary (Maybe UTCTime) Source #

The UTC time stamp of the creation time.

pasName :: Lens' ProvisioningArtifactSummary (Maybe Text) Source #

The name of the provisioning artifact.

pasId :: Lens' ProvisioningArtifactSummary (Maybe Text) Source #

The identifier of the provisioning artifact.

pasDescription :: Lens' ProvisioningArtifactSummary (Maybe Text) Source #

The description of the provisioning artifact.

ProvisioningParameter

data ProvisioningParameter Source #

Information about a parameter used to provision a product.

See: provisioningParameter smart constructor.

Instances
Eq ProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ProvisioningParameter -> Constr #

dataTypeOf :: ProvisioningParameter -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ProvisioningParameter :: Type -> Type #

Hashable ProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

ToJSON ProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: ProvisioningParameter -> () #

type Rep ProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ProvisioningParameter = D1 (MetaData "ProvisioningParameter" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ProvisioningParameter'" PrefixI True) (S1 (MetaSel (Just "_ppValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ppKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

provisioningParameter :: ProvisioningParameter Source #

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

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

RecordDetail

data RecordDetail Source #

Information about a request operation.

See: recordDetail smart constructor.

Instances
Eq RecordDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data RecordDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: RecordDetail -> Constr #

dataTypeOf :: RecordDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RecordDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show RecordDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic RecordDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep RecordDetail :: Type -> Type #

Hashable RecordDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON RecordDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData RecordDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: RecordDetail -> () #

type Rep RecordDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep RecordDetail = D1 (MetaData "RecordDetail" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "RecordDetail'" PrefixI True) (((S1 (MetaSel (Just "_rdStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RecordStatus)) :*: (S1 (MetaSel (Just "_rdRecordTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [RecordTag])) :*: S1 (MetaSel (Just "_rdProvisionedProductName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "_rdProvisioningArtifactId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rdCreatedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: S1 (MetaSel (Just "_rdRecordType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) :*: ((S1 (MetaSel (Just "_rdRecordId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rdProvisionedProductType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rdUpdatedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)))) :*: ((S1 (MetaSel (Just "_rdPathId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rdProvisionedProductId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_rdRecordErrors") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [RecordError])) :*: S1 (MetaSel (Just "_rdProductId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

recordDetail :: RecordDetail Source #

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

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

  • rdStatus - The status of the provisioned product. * CREATED - The request was created but the operation has not started. * IN_PROGRESS - The requested operation is in progress. * IN_PROGRESS_IN_ERROR - The provisioned product is under change but the requested operation failed and some remediation is occurring. For example, a rollback. * SUCCEEDED - The requested operation has successfully completed. * FAILED - The requested operation has unsuccessfully completed. Investigate using the error messages returned.
  • rdRecordTags - One or more tags.
  • rdProvisionedProductName - The user-friendly name of the provisioned product.
  • rdProvisioningArtifactId - The identifier of the provisioning artifact.
  • rdCreatedTime - The UTC time stamp of the creation time.
  • rdRecordType - The record type. * PROVISION_PRODUCT * UPDATE_PROVISIONED_PRODUCT * TERMINATE_PROVISIONED_PRODUCT
  • rdRecordId - The identifier of the record.
  • rdProvisionedProductType - The type of provisioned product. The supported value is CFN_STACK .
  • rdUpdatedTime - The time when the record was last updated.
  • rdPathId - The path identifier.
  • rdProvisionedProductId - The identifier of the provisioned product.
  • rdRecordErrors - The errors that occurred.
  • rdProductId - The product identifier.

rdStatus :: Lens' RecordDetail (Maybe RecordStatus) Source #

The status of the provisioned product. * CREATED - The request was created but the operation has not started. * IN_PROGRESS - The requested operation is in progress. * IN_PROGRESS_IN_ERROR - The provisioned product is under change but the requested operation failed and some remediation is occurring. For example, a rollback. * SUCCEEDED - The requested operation has successfully completed. * FAILED - The requested operation has unsuccessfully completed. Investigate using the error messages returned.

rdProvisionedProductName :: Lens' RecordDetail (Maybe Text) Source #

The user-friendly name of the provisioned product.

rdProvisioningArtifactId :: Lens' RecordDetail (Maybe Text) Source #

The identifier of the provisioning artifact.

rdCreatedTime :: Lens' RecordDetail (Maybe UTCTime) Source #

The UTC time stamp of the creation time.

rdRecordType :: Lens' RecordDetail (Maybe Text) Source #

The record type. * PROVISION_PRODUCT * UPDATE_PROVISIONED_PRODUCT * TERMINATE_PROVISIONED_PRODUCT

rdRecordId :: Lens' RecordDetail (Maybe Text) Source #

The identifier of the record.

rdProvisionedProductType :: Lens' RecordDetail (Maybe Text) Source #

The type of provisioned product. The supported value is CFN_STACK .

rdUpdatedTime :: Lens' RecordDetail (Maybe UTCTime) Source #

The time when the record was last updated.

rdPathId :: Lens' RecordDetail (Maybe Text) Source #

The path identifier.

rdProvisionedProductId :: Lens' RecordDetail (Maybe Text) Source #

The identifier of the provisioned product.

rdRecordErrors :: Lens' RecordDetail [RecordError] Source #

The errors that occurred.

rdProductId :: Lens' RecordDetail (Maybe Text) Source #

The product identifier.

RecordError

data RecordError Source #

The error code and description resulting from an operation.

See: recordError smart constructor.

Instances
Eq RecordError Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data RecordError Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: RecordError -> Constr #

dataTypeOf :: RecordError -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RecordError Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show RecordError Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic RecordError Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep RecordError :: Type -> Type #

Hashable RecordError Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON RecordError Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData RecordError Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: RecordError -> () #

type Rep RecordError Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep RecordError = D1 (MetaData "RecordError" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "RecordError'" PrefixI True) (S1 (MetaSel (Just "_reCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_reDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

recordError :: RecordError Source #

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

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

reCode :: Lens' RecordError (Maybe Text) Source #

The numeric value of the error.

reDescription :: Lens' RecordError (Maybe Text) Source #

The description of the error.

RecordOutput

data RecordOutput Source #

The output for the product created as the result of a request. For example, the output for a CloudFormation-backed product that creates an S3 bucket would include the S3 bucket URL.

See: recordOutput smart constructor.

Instances
Eq RecordOutput Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data RecordOutput Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: RecordOutput -> Constr #

dataTypeOf :: RecordOutput -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RecordOutput Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show RecordOutput Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic RecordOutput Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep RecordOutput :: Type -> Type #

Hashable RecordOutput Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON RecordOutput Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData RecordOutput Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: RecordOutput -> () #

type Rep RecordOutput Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep RecordOutput = D1 (MetaData "RecordOutput" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "RecordOutput'" PrefixI True) (S1 (MetaSel (Just "_roOutputValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_roOutputKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_roDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

recordOutput :: RecordOutput Source #

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

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

roDescription :: Lens' RecordOutput (Maybe Text) Source #

The description of the output.

RecordTag

data RecordTag Source #

Information about a tag, which is a key-value pair.

See: recordTag smart constructor.

Instances
Eq RecordTag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data RecordTag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: RecordTag -> Constr #

dataTypeOf :: RecordTag -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RecordTag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show RecordTag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic RecordTag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep RecordTag :: Type -> Type #

Hashable RecordTag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON RecordTag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData RecordTag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: RecordTag -> () #

type Rep RecordTag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep RecordTag = D1 (MetaData "RecordTag" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "RecordTag'" PrefixI True) (S1 (MetaSel (Just "_rtValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rtKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

recordTag :: RecordTag Source #

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

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

  • rtValue - The value for this tag.
  • rtKey - The key for this tag.

rtValue :: Lens' RecordTag (Maybe Text) Source #

The value for this tag.

rtKey :: Lens' RecordTag (Maybe Text) Source #

The key for this tag.

ResourceChange

data ResourceChange Source #

Information about a resource change that will occur when a plan is executed.

See: resourceChange smart constructor.

Instances
Eq ResourceChange Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ResourceChange Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ResourceChange -> Constr #

dataTypeOf :: ResourceChange -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ResourceChange Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ResourceChange Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ResourceChange Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ResourceChange :: Type -> Type #

Hashable ResourceChange Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ResourceChange Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ResourceChange Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: ResourceChange -> () #

type Rep ResourceChange Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ResourceChange = D1 (MetaData "ResourceChange" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ResourceChange'" PrefixI True) ((S1 (MetaSel (Just "_rcLogicalResourceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rcPhysicalResourceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rcResourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_rcAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChangeAction)) :*: S1 (MetaSel (Just "_rcScope") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ResourceAttribute]))) :*: (S1 (MetaSel (Just "_rcDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ResourceChangeDetail])) :*: S1 (MetaSel (Just "_rcReplacement") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Replacement))))))

resourceChange :: ResourceChange Source #

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

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

rcLogicalResourceId :: Lens' ResourceChange (Maybe Text) Source #

The ID of the resource, as defined in the CloudFormation template.

rcPhysicalResourceId :: Lens' ResourceChange (Maybe Text) Source #

The ID of the resource, if it was already created.

rcDetails :: Lens' ResourceChange [ResourceChangeDetail] Source #

Information about the resource changes.

rcReplacement :: Lens' ResourceChange (Maybe Replacement) Source #

If the change type is Modify , indicates whether the existing resource is deleted and replaced with a new one.

ResourceChangeDetail

data ResourceChangeDetail Source #

Information about a change to a resource attribute.

See: resourceChangeDetail smart constructor.

Instances
Eq ResourceChangeDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ResourceChangeDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ResourceChangeDetail -> Constr #

dataTypeOf :: ResourceChangeDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ResourceChangeDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ResourceChangeDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ResourceChangeDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ResourceChangeDetail :: Type -> Type #

Hashable ResourceChangeDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ResourceChangeDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ResourceChangeDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: ResourceChangeDetail -> () #

type Rep ResourceChangeDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ResourceChangeDetail = D1 (MetaData "ResourceChangeDetail" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ResourceChangeDetail'" PrefixI True) (S1 (MetaSel (Just "_rcdCausingEntity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rcdEvaluation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EvaluationType)) :*: S1 (MetaSel (Just "_rcdTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ResourceTargetDefinition)))))

resourceChangeDetail :: ResourceChangeDetail Source #

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

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

  • rcdCausingEntity - The ID of the entity that caused the change.
  • rcdEvaluation - For static evaluations, the value of the resource attribute will change and the new value is known. For dynamic evaluations, the value might change, and any new value will be determined when the plan is updated.
  • rcdTarget - Information about the resource attribute to be modified.

rcdCausingEntity :: Lens' ResourceChangeDetail (Maybe Text) Source #

The ID of the entity that caused the change.

rcdEvaluation :: Lens' ResourceChangeDetail (Maybe EvaluationType) Source #

For static evaluations, the value of the resource attribute will change and the new value is known. For dynamic evaluations, the value might change, and any new value will be determined when the plan is updated.

rcdTarget :: Lens' ResourceChangeDetail (Maybe ResourceTargetDefinition) Source #

Information about the resource attribute to be modified.

ResourceDetail

data ResourceDetail Source #

Information about a resource.

See: resourceDetail smart constructor.

Instances
Eq ResourceDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ResourceDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ResourceDetail -> Constr #

dataTypeOf :: ResourceDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ResourceDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ResourceDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ResourceDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ResourceDetail :: Type -> Type #

Hashable ResourceDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ResourceDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ResourceDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: ResourceDetail -> () #

type Rep ResourceDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ResourceDetail = D1 (MetaData "ResourceDetail" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ResourceDetail'" PrefixI True) ((S1 (MetaSel (Just "_rARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rCreatedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))) :*: (S1 (MetaSel (Just "_rName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

resourceDetail :: ResourceDetail Source #

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

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

  • rARN - The ARN of the resource.
  • rCreatedTime - The creation time of the resource.
  • rName - The name of the resource.
  • rId - The identifier of the resource.
  • rDescription - The description of the resource.

rARN :: Lens' ResourceDetail (Maybe Text) Source #

The ARN of the resource.

rCreatedTime :: Lens' ResourceDetail (Maybe UTCTime) Source #

The creation time of the resource.

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

The name of the resource.

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

The identifier of the resource.

rDescription :: Lens' ResourceDetail (Maybe Text) Source #

The description of the resource.

ResourceTargetDefinition

data ResourceTargetDefinition Source #

Information about a change to a resource attribute.

See: resourceTargetDefinition smart constructor.

Instances
Eq ResourceTargetDefinition Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data ResourceTargetDefinition Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: ResourceTargetDefinition -> Constr #

dataTypeOf :: ResourceTargetDefinition -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ResourceTargetDefinition Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show ResourceTargetDefinition Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic ResourceTargetDefinition Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep ResourceTargetDefinition :: Type -> Type #

Hashable ResourceTargetDefinition Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON ResourceTargetDefinition Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData ResourceTargetDefinition Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ResourceTargetDefinition Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep ResourceTargetDefinition = D1 (MetaData "ResourceTargetDefinition" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "ResourceTargetDefinition'" PrefixI True) (S1 (MetaSel (Just "_rtdAttribute") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ResourceAttribute)) :*: (S1 (MetaSel (Just "_rtdRequiresRecreation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RequiresRecreation)) :*: S1 (MetaSel (Just "_rtdName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

resourceTargetDefinition :: ResourceTargetDefinition Source #

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

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

  • rtdAttribute - The attribute to be changed.
  • rtdRequiresRecreation - If the attribute is Properties , indicates whether a change to this property causes the resource to be re-created.
  • rtdName - If the attribute is Properties , the value is the name of the property. Otherwise, the value is null.

rtdRequiresRecreation :: Lens' ResourceTargetDefinition (Maybe RequiresRecreation) Source #

If the attribute is Properties , indicates whether a change to this property causes the resource to be re-created.

rtdName :: Lens' ResourceTargetDefinition (Maybe Text) Source #

If the attribute is Properties , the value is the name of the property. Otherwise, the value is null.

Tag

data Tag Source #

Information about a tag. A tag is a key-value pair. Tags are propagated to the resources created when provisioning a product.

See: tag smart constructor.

Instances
Eq Tag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

Data Tag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.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.ServiceCatalog.Types.Product

Show Tag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.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.ServiceCatalog.Types.Product

Methods

hashWithSalt :: Int -> Tag -> Int #

hash :: Tag -> Int #

ToJSON Tag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON Tag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData Tag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: Tag -> () #

type Rep Tag Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep Tag = D1 (MetaData "Tag" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" 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 tag key.

tagValue :: Lens' Tag Text Source #

The value for this key.

TagOptionDetail

data TagOptionDetail Source #

Information about a TagOption.

See: tagOptionDetail smart constructor.

Instances
Eq TagOptionDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data TagOptionDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: TagOptionDetail -> Constr #

dataTypeOf :: TagOptionDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TagOptionDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show TagOptionDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic TagOptionDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep TagOptionDetail :: Type -> Type #

Hashable TagOptionDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON TagOptionDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData TagOptionDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: TagOptionDetail -> () #

type Rep TagOptionDetail Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep TagOptionDetail = D1 (MetaData "TagOptionDetail" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "TagOptionDetail'" PrefixI True) ((S1 (MetaSel (Just "_todValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_todActive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) :*: (S1 (MetaSel (Just "_todKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_todId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

tagOptionDetail :: TagOptionDetail Source #

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

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

todValue :: Lens' TagOptionDetail (Maybe Text) Source #

The TagOption value.

todActive :: Lens' TagOptionDetail (Maybe Bool) Source #

The TagOption active state.

todKey :: Lens' TagOptionDetail (Maybe Text) Source #

The TagOption key.

todId :: Lens' TagOptionDetail (Maybe Text) Source #

The TagOption identifier.

TagOptionSummary

data TagOptionSummary Source #

Summary information about a TagOption.

See: tagOptionSummary smart constructor.

Instances
Eq TagOptionSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data TagOptionSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: TagOptionSummary -> Constr #

dataTypeOf :: TagOptionSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TagOptionSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show TagOptionSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic TagOptionSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep TagOptionSummary :: Type -> Type #

Hashable TagOptionSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON TagOptionSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData TagOptionSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: TagOptionSummary -> () #

type Rep TagOptionSummary Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep TagOptionSummary = D1 (MetaData "TagOptionSummary" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "TagOptionSummary'" PrefixI True) (S1 (MetaSel (Just "_tosValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 (MetaSel (Just "_tosKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

tagOptionSummary :: TagOptionSummary Source #

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

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

tosValues :: Lens' TagOptionSummary [Text] Source #

The TagOption value.

tosKey :: Lens' TagOptionSummary (Maybe Text) Source #

The TagOption key.

UpdateProvisioningParameter

data UpdateProvisioningParameter Source #

The parameter key-value pair used to update a provisioned product.

See: updateProvisioningParameter smart constructor.

Instances
Eq UpdateProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data UpdateProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: UpdateProvisioningParameter -> Constr #

dataTypeOf :: UpdateProvisioningParameter -> DataType #

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

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

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

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

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

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

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

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

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

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

Read UpdateProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show UpdateProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic UpdateProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep UpdateProvisioningParameter :: Type -> Type #

Hashable UpdateProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

ToJSON UpdateProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON UpdateProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData UpdateProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep UpdateProvisioningParameter Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep UpdateProvisioningParameter = D1 (MetaData "UpdateProvisioningParameter" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "UpdateProvisioningParameter'" PrefixI True) (S1 (MetaSel (Just "_uppValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_uppKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_uppUsePreviousValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))

updateProvisioningParameter :: UpdateProvisioningParameter Source #

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

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

uppUsePreviousValue :: Lens' UpdateProvisioningParameter (Maybe Bool) Source #

If set to true, Value is ignored and the previous parameter value is kept.

UsageInstruction

data UsageInstruction Source #

Additional information provided by the administrator.

See: usageInstruction smart constructor.

Instances
Eq UsageInstruction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Data UsageInstruction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

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

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

toConstr :: UsageInstruction -> Constr #

dataTypeOf :: UsageInstruction -> DataType #

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

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

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

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

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

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

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

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

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

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

Read UsageInstruction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Show UsageInstruction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Generic UsageInstruction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Associated Types

type Rep UsageInstruction :: Type -> Type #

Hashable UsageInstruction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

FromJSON UsageInstruction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

NFData UsageInstruction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

Methods

rnf :: UsageInstruction -> () #

type Rep UsageInstruction Source # 
Instance details

Defined in Network.AWS.ServiceCatalog.Types.Product

type Rep UsageInstruction = D1 (MetaData "UsageInstruction" "Network.AWS.ServiceCatalog.Types.Product" "amazonka-servicecatalog-1.6.1-3x3nXpki5UUGYHxW61f9xy" False) (C1 (MetaCons "UsageInstruction'" PrefixI True) (S1 (MetaSel (Just "_uiValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_uiType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

usageInstruction :: UsageInstruction Source #

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

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

  • uiValue - The usage instruction value for this type.
  • uiType - The usage instruction type for the value.

uiValue :: Lens' UsageInstruction (Maybe Text) Source #

The usage instruction value for this type.

uiType :: Lens' UsageInstruction (Maybe Text) Source #

The usage instruction type for the value.