amazonka-greengrass-1.6.0: Amazon Greengrass 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.Greengrass.Types

Contents

Description

 

Synopsis

Service Configuration

greengrass :: Service Source #

API version 2017-06-07 of the Amazon Greengrass SDK configuration.

Errors

DeploymentType

data DeploymentType Source #

Instances

Bounded DeploymentType Source # 
Enum DeploymentType Source # 
Eq DeploymentType Source # 
Data DeploymentType Source # 

Methods

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

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

toConstr :: DeploymentType -> Constr #

dataTypeOf :: DeploymentType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DeploymentType Source # 
Read DeploymentType Source # 
Show DeploymentType Source # 
Generic DeploymentType Source # 

Associated Types

type Rep DeploymentType :: * -> * #

Hashable DeploymentType Source # 
ToJSON DeploymentType Source # 
FromJSON DeploymentType Source # 
NFData DeploymentType Source # 

Methods

rnf :: DeploymentType -> () #

ToHeader DeploymentType Source # 
ToQuery DeploymentType Source # 
ToByteString DeploymentType Source # 
FromText DeploymentType Source # 
ToText DeploymentType Source # 
type Rep DeploymentType Source # 
type Rep DeploymentType = D1 * (MetaData "DeploymentType" "Network.AWS.Greengrass.Types.Sum" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ForceResetDeployment" PrefixI False) (U1 *)) (C1 * (MetaCons "NewDeployment" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Redeployment" PrefixI False) (U1 *)) (C1 * (MetaCons "ResetDeployment" PrefixI False) (U1 *))))

EncodingType

data EncodingType Source #

Constructors

Binary 
JSON 

Instances

Bounded EncodingType Source # 
Enum EncodingType Source # 
Eq EncodingType Source # 
Data EncodingType Source # 

Methods

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

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

toConstr :: EncodingType -> Constr #

dataTypeOf :: EncodingType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EncodingType Source # 
Read EncodingType Source # 
Show EncodingType Source # 
Generic EncodingType Source # 

Associated Types

type Rep EncodingType :: * -> * #

Hashable EncodingType Source # 
ToJSON EncodingType Source # 
FromJSON EncodingType Source # 
NFData EncodingType Source # 

Methods

rnf :: EncodingType -> () #

ToHeader EncodingType Source # 
ToQuery EncodingType Source # 
ToByteString EncodingType Source # 
FromText EncodingType Source # 
ToText EncodingType Source # 

Methods

toText :: EncodingType -> Text #

type Rep EncodingType Source # 
type Rep EncodingType = D1 * (MetaData "EncodingType" "Network.AWS.Greengrass.Types.Sum" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) ((:+:) * (C1 * (MetaCons "Binary" PrefixI False) (U1 *)) (C1 * (MetaCons "JSON" PrefixI False) (U1 *)))

LoggerComponent

data LoggerComponent Source #

Constructors

GreengrassSystem 
Lambda 

Instances

Bounded LoggerComponent Source # 
Enum LoggerComponent Source # 
Eq LoggerComponent Source # 
Data LoggerComponent Source # 

Methods

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

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

toConstr :: LoggerComponent -> Constr #

dataTypeOf :: LoggerComponent -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LoggerComponent Source # 
Read LoggerComponent Source # 
Show LoggerComponent Source # 
Generic LoggerComponent Source # 
Hashable LoggerComponent Source # 
ToJSON LoggerComponent Source # 
FromJSON LoggerComponent Source # 
NFData LoggerComponent Source # 

Methods

rnf :: LoggerComponent -> () #

ToHeader LoggerComponent Source # 
ToQuery LoggerComponent Source # 
ToByteString LoggerComponent Source # 
FromText LoggerComponent Source # 
ToText LoggerComponent Source # 
type Rep LoggerComponent Source # 
type Rep LoggerComponent = D1 * (MetaData "LoggerComponent" "Network.AWS.Greengrass.Types.Sum" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) ((:+:) * (C1 * (MetaCons "GreengrassSystem" PrefixI False) (U1 *)) (C1 * (MetaCons "Lambda" PrefixI False) (U1 *)))

LoggerLevel

data LoggerLevel Source #

Constructors

Debug 
Error' 
Fatal 
Info 
Warn 

Instances

Bounded LoggerLevel Source # 
Enum LoggerLevel Source # 
Eq LoggerLevel Source # 
Data LoggerLevel Source # 

Methods

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

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

toConstr :: LoggerLevel -> Constr #

dataTypeOf :: LoggerLevel -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LoggerLevel Source # 
Read LoggerLevel Source # 
Show LoggerLevel Source # 
Generic LoggerLevel Source # 

Associated Types

type Rep LoggerLevel :: * -> * #

Hashable LoggerLevel Source # 
ToJSON LoggerLevel Source # 
FromJSON LoggerLevel Source # 
NFData LoggerLevel Source # 

Methods

rnf :: LoggerLevel -> () #

ToHeader LoggerLevel Source # 
ToQuery LoggerLevel Source # 
ToByteString LoggerLevel Source # 
FromText LoggerLevel Source # 
ToText LoggerLevel Source # 

Methods

toText :: LoggerLevel -> Text #

type Rep LoggerLevel Source # 
type Rep LoggerLevel = D1 * (MetaData "LoggerLevel" "Network.AWS.Greengrass.Types.Sum" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Debug" PrefixI False) (U1 *)) (C1 * (MetaCons "Error'" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Fatal" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Info" PrefixI False) (U1 *)) (C1 * (MetaCons "Warn" PrefixI False) (U1 *)))))

LoggerType

data LoggerType Source #

Constructors

AWSCloudWatch 
FileSystem 

Instances

Bounded LoggerType Source # 
Enum LoggerType Source # 
Eq LoggerType Source # 
Data LoggerType Source # 

Methods

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

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

toConstr :: LoggerType -> Constr #

dataTypeOf :: LoggerType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LoggerType Source # 
Read LoggerType Source # 
Show LoggerType Source # 
Generic LoggerType Source # 

Associated Types

type Rep LoggerType :: * -> * #

Hashable LoggerType Source # 
ToJSON LoggerType Source # 
FromJSON LoggerType Source # 
NFData LoggerType Source # 

Methods

rnf :: LoggerType -> () #

ToHeader LoggerType Source # 
ToQuery LoggerType Source # 
ToByteString LoggerType Source # 
FromText LoggerType Source # 
ToText LoggerType Source # 

Methods

toText :: LoggerType -> Text #

type Rep LoggerType Source # 
type Rep LoggerType = D1 * (MetaData "LoggerType" "Network.AWS.Greengrass.Types.Sum" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) ((:+:) * (C1 * (MetaCons "AWSCloudWatch" PrefixI False) (U1 *)) (C1 * (MetaCons "FileSystem" PrefixI False) (U1 *)))

Permission

data Permission Source #

The type of permission a function has to access a resource.

Constructors

RO 
RW 

Instances

Bounded Permission Source # 
Enum Permission Source # 
Eq Permission Source # 
Data Permission Source # 

Methods

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

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

toConstr :: Permission -> Constr #

dataTypeOf :: Permission -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Permission Source # 
Read Permission Source # 
Show Permission Source # 
Generic Permission Source # 

Associated Types

type Rep Permission :: * -> * #

Hashable Permission Source # 
ToJSON Permission Source # 
FromJSON Permission Source # 
NFData Permission Source # 

Methods

rnf :: Permission -> () #

ToHeader Permission Source # 
ToQuery Permission Source # 
ToByteString Permission Source # 
FromText Permission Source # 
ToText Permission Source # 

Methods

toText :: Permission -> Text #

type Rep Permission Source # 
type Rep Permission = D1 * (MetaData "Permission" "Network.AWS.Greengrass.Types.Sum" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) ((:+:) * (C1 * (MetaCons "RO" PrefixI False) (U1 *)) (C1 * (MetaCons "RW" PrefixI False) (U1 *)))

SoftwareToUpdate

data SoftwareToUpdate Source #

The piece of software on the Greengrass core that will be updated.

Constructors

Core 
OtaAgent 

Instances

Bounded SoftwareToUpdate Source # 
Enum SoftwareToUpdate Source # 
Eq SoftwareToUpdate Source # 
Data SoftwareToUpdate Source # 

Methods

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

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

toConstr :: SoftwareToUpdate -> Constr #

dataTypeOf :: SoftwareToUpdate -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SoftwareToUpdate Source # 
Read SoftwareToUpdate Source # 
Show SoftwareToUpdate Source # 
Generic SoftwareToUpdate Source # 
Hashable SoftwareToUpdate Source # 
ToJSON SoftwareToUpdate Source # 
NFData SoftwareToUpdate Source # 

Methods

rnf :: SoftwareToUpdate -> () #

ToHeader SoftwareToUpdate Source # 
ToQuery SoftwareToUpdate Source # 
ToByteString SoftwareToUpdate Source # 
FromText SoftwareToUpdate Source # 
ToText SoftwareToUpdate Source # 
type Rep SoftwareToUpdate Source # 
type Rep SoftwareToUpdate = D1 * (MetaData "SoftwareToUpdate" "Network.AWS.Greengrass.Types.Sum" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) ((:+:) * (C1 * (MetaCons "Core" PrefixI False) (U1 *)) (C1 * (MetaCons "OtaAgent" PrefixI False) (U1 *)))

UpdateAgentLogLevel

data UpdateAgentLogLevel Source #

The minimum level of log statements that should be logged by the OTA Agent during an update.

Instances

Bounded UpdateAgentLogLevel Source # 
Enum UpdateAgentLogLevel Source # 
Eq UpdateAgentLogLevel Source # 
Data UpdateAgentLogLevel Source # 

Methods

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

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

toConstr :: UpdateAgentLogLevel -> Constr #

dataTypeOf :: UpdateAgentLogLevel -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UpdateAgentLogLevel Source # 
Read UpdateAgentLogLevel Source # 
Show UpdateAgentLogLevel Source # 
Generic UpdateAgentLogLevel Source # 
Hashable UpdateAgentLogLevel Source # 
ToJSON UpdateAgentLogLevel Source # 
NFData UpdateAgentLogLevel Source # 

Methods

rnf :: UpdateAgentLogLevel -> () #

ToHeader UpdateAgentLogLevel Source # 
ToQuery UpdateAgentLogLevel Source # 
ToByteString UpdateAgentLogLevel Source # 
FromText UpdateAgentLogLevel Source # 
ToText UpdateAgentLogLevel Source # 
type Rep UpdateAgentLogLevel Source # 
type Rep UpdateAgentLogLevel = D1 * (MetaData "UpdateAgentLogLevel" "Network.AWS.Greengrass.Types.Sum" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "UALLDebug" PrefixI False) (U1 *)) (C1 * (MetaCons "UALLError'" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "UALLFatal" PrefixI False) (U1 *)) (C1 * (MetaCons "UALLInfo" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "UALLNone" PrefixI False) (U1 *)) (C1 * (MetaCons "UALLTrace" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "UALLVerbose" PrefixI False) (U1 *)) (C1 * (MetaCons "UALLWarn" PrefixI False) (U1 *)))))

UpdateTargetsArchitecture

data UpdateTargetsArchitecture Source #

The architecture of the cores which are the targets of an update.

Constructors

AARCH64 
Armv7l 
X86_64 

Instances

Bounded UpdateTargetsArchitecture Source # 
Enum UpdateTargetsArchitecture Source # 
Eq UpdateTargetsArchitecture Source # 
Data UpdateTargetsArchitecture Source # 

Methods

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

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

toConstr :: UpdateTargetsArchitecture -> Constr #

dataTypeOf :: UpdateTargetsArchitecture -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UpdateTargetsArchitecture Source # 
Read UpdateTargetsArchitecture Source # 
Show UpdateTargetsArchitecture Source # 
Generic UpdateTargetsArchitecture Source # 
Hashable UpdateTargetsArchitecture Source # 
ToJSON UpdateTargetsArchitecture Source # 
NFData UpdateTargetsArchitecture Source # 
ToHeader UpdateTargetsArchitecture Source # 
ToQuery UpdateTargetsArchitecture Source # 
ToByteString UpdateTargetsArchitecture Source # 
FromText UpdateTargetsArchitecture Source # 
ToText UpdateTargetsArchitecture Source # 
type Rep UpdateTargetsArchitecture Source # 
type Rep UpdateTargetsArchitecture = D1 * (MetaData "UpdateTargetsArchitecture" "Network.AWS.Greengrass.Types.Sum" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) ((:+:) * (C1 * (MetaCons "AARCH64" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Armv7l" PrefixI False) (U1 *)) (C1 * (MetaCons "X86_64" PrefixI False) (U1 *))))

UpdateTargetsOperatingSystem

data UpdateTargetsOperatingSystem Source #

The operating system of the cores which are the targets of an update.

Constructors

AmazonLinux 
Raspbian 
Ubuntu 

Instances

Bounded UpdateTargetsOperatingSystem Source # 
Enum UpdateTargetsOperatingSystem Source # 
Eq UpdateTargetsOperatingSystem Source # 
Data UpdateTargetsOperatingSystem Source # 

Methods

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

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

toConstr :: UpdateTargetsOperatingSystem -> Constr #

dataTypeOf :: UpdateTargetsOperatingSystem -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UpdateTargetsOperatingSystem Source # 
Read UpdateTargetsOperatingSystem Source # 
Show UpdateTargetsOperatingSystem Source # 
Generic UpdateTargetsOperatingSystem Source # 
Hashable UpdateTargetsOperatingSystem Source # 
ToJSON UpdateTargetsOperatingSystem Source # 
NFData UpdateTargetsOperatingSystem Source # 
ToHeader UpdateTargetsOperatingSystem Source # 
ToQuery UpdateTargetsOperatingSystem Source # 
ToByteString UpdateTargetsOperatingSystem Source # 
FromText UpdateTargetsOperatingSystem Source # 
ToText UpdateTargetsOperatingSystem Source # 
type Rep UpdateTargetsOperatingSystem Source # 
type Rep UpdateTargetsOperatingSystem = D1 * (MetaData "UpdateTargetsOperatingSystem" "Network.AWS.Greengrass.Types.Sum" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) ((:+:) * (C1 * (MetaCons "AmazonLinux" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Raspbian" PrefixI False) (U1 *)) (C1 * (MetaCons "Ubuntu" PrefixI False) (U1 *))))

ConnectivityInfo

data ConnectivityInfo Source #

Information about a Greengrass core's connectivity.

See: connectivityInfo smart constructor.

Instances

Eq ConnectivityInfo Source # 
Data ConnectivityInfo Source # 

Methods

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

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

toConstr :: ConnectivityInfo -> Constr #

dataTypeOf :: ConnectivityInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ConnectivityInfo -> () #

type Rep ConnectivityInfo Source # 
type Rep ConnectivityInfo = D1 * (MetaData "ConnectivityInfo" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "ConnectivityInfo'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ciPortNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_ciId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ciMetadata") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_ciHostAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

connectivityInfo :: ConnectivityInfo Source #

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

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

  • ciPortNumber - The port of the Greengrass core. Usually 8883.
  • ciId - The ID of the connectivity information.
  • ciMetadata - Metadata for this endpoint.
  • ciHostAddress - The endpoint for the Greengrass core. Can be an IP address or DNS.

ciPortNumber :: Lens' ConnectivityInfo (Maybe Int) Source #

The port of the Greengrass core. Usually 8883.

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

The ID of the connectivity information.

ciMetadata :: Lens' ConnectivityInfo (Maybe Text) Source #

Metadata for this endpoint.

ciHostAddress :: Lens' ConnectivityInfo (Maybe Text) Source #

The endpoint for the Greengrass core. Can be an IP address or DNS.

Core

data Core Source #

Information about a core.

See: core smart constructor.

Instances

Eq Core Source # 

Methods

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

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

Data Core Source # 

Methods

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

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

toConstr :: Core -> Constr #

dataTypeOf :: Core -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Core Source # 
Show Core Source # 

Methods

showsPrec :: Int -> Core -> ShowS #

show :: Core -> String #

showList :: [Core] -> ShowS #

Generic Core Source # 

Associated Types

type Rep Core :: * -> * #

Methods

from :: Core -> Rep Core x #

to :: Rep Core x -> Core #

Hashable Core Source # 

Methods

hashWithSalt :: Int -> Core -> Int #

hash :: Core -> Int #

ToJSON Core Source # 
FromJSON Core Source # 
NFData Core Source # 

Methods

rnf :: Core -> () #

type Rep Core Source # 
type Rep Core = D1 * (MetaData "Core" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "Core'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cCertificateARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_cThingARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cSyncShadow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_cId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

core :: Core Source #

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

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

  • cCertificateARN - The ARN of the certificate associated with the core.
  • cThingARN - The ARN of the thing which is the core.
  • cSyncShadow - If true, the core's local shadow is automatically synced with the cloud.
  • cId - The ID of the core.

cCertificateARN :: Lens' Core (Maybe Text) Source #

The ARN of the certificate associated with the core.

cThingARN :: Lens' Core (Maybe Text) Source #

The ARN of the thing which is the core.

cSyncShadow :: Lens' Core (Maybe Bool) Source #

If true, the core's local shadow is automatically synced with the cloud.

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

The ID of the core.

CoreDefinitionVersion

data CoreDefinitionVersion Source #

Information about a core definition version.

See: coreDefinitionVersion smart constructor.

Instances

Eq CoreDefinitionVersion Source # 
Data CoreDefinitionVersion Source # 

Methods

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

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

toConstr :: CoreDefinitionVersion -> Constr #

dataTypeOf :: CoreDefinitionVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: CoreDefinitionVersion -> () #

type Rep CoreDefinitionVersion Source # 
type Rep CoreDefinitionVersion = D1 * (MetaData "CoreDefinitionVersion" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" True) (C1 * (MetaCons "CoreDefinitionVersion'" PrefixI True) (S1 * (MetaSel (Just Symbol "_cdvCores") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe [Core]))))

coreDefinitionVersion :: CoreDefinitionVersion Source #

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

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

  • cdvCores - A list of cores in the core definition version.

cdvCores :: Lens' CoreDefinitionVersion [Core] Source #

A list of cores in the core definition version.

DefinitionInformation

data DefinitionInformation Source #

Information about a definition.

See: definitionInformation smart constructor.

Instances

Eq DefinitionInformation Source # 
Data DefinitionInformation Source # 

Methods

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

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

toConstr :: DefinitionInformation -> Constr #

dataTypeOf :: DefinitionInformation -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: DefinitionInformation -> () #

type Rep DefinitionInformation Source # 
type Rep DefinitionInformation = D1 * (MetaData "DefinitionInformation" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "DefinitionInformation'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_diLatestVersionARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_diARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_diName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_diCreationTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_diId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_diLatestVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_diLastUpdatedTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

definitionInformation :: DefinitionInformation Source #

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

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

diLatestVersionARN :: Lens' DefinitionInformation (Maybe Text) Source #

The ARN of the latest version of the definition.

diARN :: Lens' DefinitionInformation (Maybe Text) Source #

The ARN of the definition.

diName :: Lens' DefinitionInformation (Maybe Text) Source #

The name of the definition.

diCreationTimestamp :: Lens' DefinitionInformation (Maybe Text) Source #

The time, in milliseconds since the epoch, when the definition was created.

diId :: Lens' DefinitionInformation (Maybe Text) Source #

The ID of the definition.

diLatestVersion :: Lens' DefinitionInformation (Maybe Text) Source #

The latest version of the definition.

diLastUpdatedTimestamp :: Lens' DefinitionInformation (Maybe Text) Source #

The time, in milliseconds since the epoch, when the definition was last updated.

Deployment

data Deployment Source #

Information about a deployment.

See: deployment smart constructor.

Instances

Eq Deployment Source # 
Data Deployment Source # 

Methods

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

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

toConstr :: Deployment -> Constr #

dataTypeOf :: Deployment -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Deployment Source # 
Show Deployment Source # 
Generic Deployment Source # 

Associated Types

type Rep Deployment :: * -> * #

Hashable Deployment Source # 
FromJSON Deployment Source # 
NFData Deployment Source # 

Methods

rnf :: Deployment -> () #

type Rep Deployment Source # 
type Rep Deployment = D1 * (MetaData "Deployment" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "Deployment'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dDeploymentId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dDeploymentARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dDeploymentType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DeploymentType))) (S1 * (MetaSel (Just Symbol "_dGroupARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

deployment :: Deployment Source #

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

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

dDeploymentId :: Lens' Deployment (Maybe Text) Source #

The ID of the deployment.

dDeploymentARN :: Lens' Deployment (Maybe Text) Source #

The ARN of the deployment.

dCreatedAt :: Lens' Deployment (Maybe Text) Source #

The time, in milliseconds since the epoch, when the deployment was created.

dDeploymentType :: Lens' Deployment (Maybe DeploymentType) Source #

The type of the deployment.

dGroupARN :: Lens' Deployment (Maybe Text) Source #

The ARN of the group for this deployment.

Device

data Device Source #

Information about a device.

See: device smart constructor.

Instances

Eq Device Source # 

Methods

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

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

Data Device Source # 

Methods

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

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

toConstr :: Device -> Constr #

dataTypeOf :: Device -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Device Source # 
Show Device Source # 
Generic Device Source # 

Associated Types

type Rep Device :: * -> * #

Methods

from :: Device -> Rep Device x #

to :: Rep Device x -> Device #

Hashable Device Source # 

Methods

hashWithSalt :: Int -> Device -> Int #

hash :: Device -> Int #

ToJSON Device Source # 
FromJSON Device Source # 
NFData Device Source # 

Methods

rnf :: Device -> () #

type Rep Device Source # 
type Rep Device = D1 * (MetaData "Device" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "Device'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dCertificateARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_dThingARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dSyncShadow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_dId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

device :: Device Source #

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

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

  • dCertificateARN - The ARN of the certificate associated with the device.
  • dThingARN - The thing ARN of the device.
  • dSyncShadow - If true, the device's local shadow will be automatically synced with the cloud.
  • dId - The ID of the device.

dCertificateARN :: Lens' Device (Maybe Text) Source #

The ARN of the certificate associated with the device.

dThingARN :: Lens' Device (Maybe Text) Source #

The thing ARN of the device.

dSyncShadow :: Lens' Device (Maybe Bool) Source #

If true, the device's local shadow will be automatically synced with the cloud.

dId :: Lens' Device (Maybe Text) Source #

The ID of the device.

DeviceDefinitionVersion

data DeviceDefinitionVersion Source #

Information about a device definition version.

See: deviceDefinitionVersion smart constructor.

Instances

Eq DeviceDefinitionVersion Source # 
Data DeviceDefinitionVersion Source # 

Methods

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

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

toConstr :: DeviceDefinitionVersion -> Constr #

dataTypeOf :: DeviceDefinitionVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: DeviceDefinitionVersion -> () #

type Rep DeviceDefinitionVersion Source # 
type Rep DeviceDefinitionVersion = D1 * (MetaData "DeviceDefinitionVersion" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" True) (C1 * (MetaCons "DeviceDefinitionVersion'" PrefixI True) (S1 * (MetaSel (Just Symbol "_ddvDevices") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe [Device]))))

deviceDefinitionVersion :: DeviceDefinitionVersion Source #

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

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

  • ddvDevices - A list of devices in the definition version.

ddvDevices :: Lens' DeviceDefinitionVersion [Device] Source #

A list of devices in the definition version.

ErrorDetail

data ErrorDetail Source #

Details about the error.

See: errorDetail smart constructor.

Instances

Eq ErrorDetail Source # 
Data ErrorDetail Source # 

Methods

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

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

toConstr :: ErrorDetail -> Constr #

dataTypeOf :: ErrorDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ErrorDetail Source # 
Show ErrorDetail Source # 
Generic ErrorDetail Source # 

Associated Types

type Rep ErrorDetail :: * -> * #

Hashable ErrorDetail Source # 
FromJSON ErrorDetail Source # 
NFData ErrorDetail Source # 

Methods

rnf :: ErrorDetail -> () #

type Rep ErrorDetail Source # 
type Rep ErrorDetail = D1 * (MetaData "ErrorDetail" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "ErrorDetail'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_edDetailedErrorCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_edDetailedErrorMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

errorDetail :: ErrorDetail Source #

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

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

edDetailedErrorMessage :: Lens' ErrorDetail (Maybe Text) Source #

A detailed error message.

Function

data Function Source #

Information about a Lambda function.

See: function smart constructor.

Instances

Eq Function Source # 
Data Function Source # 

Methods

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

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

toConstr :: Function -> Constr #

dataTypeOf :: Function -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Function Source # 
Show Function Source # 
Generic Function Source # 

Associated Types

type Rep Function :: * -> * #

Methods

from :: Function -> Rep Function x #

to :: Rep Function x -> Function #

Hashable Function Source # 

Methods

hashWithSalt :: Int -> Function -> Int #

hash :: Function -> Int #

ToJSON Function Source # 
FromJSON Function Source # 
NFData Function Source # 

Methods

rnf :: Function -> () #

type Rep Function Source # 
type Rep Function = D1 * (MetaData "Function" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "Function'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_fFunctionARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_fFunctionConfiguration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe FunctionConfiguration))) (S1 * (MetaSel (Just Symbol "_fId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

function :: Function Source #

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

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

fFunctionARN :: Lens' Function (Maybe Text) Source #

The ARN of the Lambda function.

fFunctionConfiguration :: Lens' Function (Maybe FunctionConfiguration) Source #

The configuration of the Lambda function.

fId :: Lens' Function (Maybe Text) Source #

The ID of the Lambda function.

FunctionConfiguration

data FunctionConfiguration Source #

The configuration of the Lambda function.

See: functionConfiguration smart constructor.

Instances

Eq FunctionConfiguration Source # 
Data FunctionConfiguration Source # 

Methods

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

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

toConstr :: FunctionConfiguration -> Constr #

dataTypeOf :: FunctionConfiguration -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: FunctionConfiguration -> () #

type Rep FunctionConfiguration Source # 

functionConfiguration :: FunctionConfiguration Source #

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

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

  • fcMemorySize - The memory size, in KB, which the function requires.
  • fcExecArgs - The execution arguments.
  • fcEnvironment - The environment configuration of the function.
  • fcExecutable - The name of the function executable.
  • fcPinned - True if the function is pinned. Pinned means the function is long-lived and starts when the core starts.
  • fcEncodingType - The expected encoding type of the input payload for the function. The default is 'json'.
  • fcTimeout - The allowed function execution time, after which Lambda should terminate the function. This timeout still applies to pinned lambdas for each request.

fcMemorySize :: Lens' FunctionConfiguration (Maybe Int) Source #

The memory size, in KB, which the function requires.

fcExecArgs :: Lens' FunctionConfiguration (Maybe Text) Source #

The execution arguments.

fcEnvironment :: Lens' FunctionConfiguration (Maybe FunctionConfigurationEnvironment) Source #

The environment configuration of the function.

fcExecutable :: Lens' FunctionConfiguration (Maybe Text) Source #

The name of the function executable.

fcPinned :: Lens' FunctionConfiguration (Maybe Bool) Source #

True if the function is pinned. Pinned means the function is long-lived and starts when the core starts.

fcEncodingType :: Lens' FunctionConfiguration (Maybe EncodingType) Source #

The expected encoding type of the input payload for the function. The default is 'json'.

fcTimeout :: Lens' FunctionConfiguration (Maybe Int) Source #

The allowed function execution time, after which Lambda should terminate the function. This timeout still applies to pinned lambdas for each request.

FunctionConfigurationEnvironment

data FunctionConfigurationEnvironment Source #

The environment configuration of the function.

See: functionConfigurationEnvironment smart constructor.

Instances

Eq FunctionConfigurationEnvironment Source # 
Data FunctionConfigurationEnvironment Source # 

Methods

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

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

toConstr :: FunctionConfigurationEnvironment -> Constr #

dataTypeOf :: FunctionConfigurationEnvironment -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FunctionConfigurationEnvironment Source # 
Show FunctionConfigurationEnvironment Source # 
Generic FunctionConfigurationEnvironment Source # 
Hashable FunctionConfigurationEnvironment Source # 
ToJSON FunctionConfigurationEnvironment Source # 
FromJSON FunctionConfigurationEnvironment Source # 
NFData FunctionConfigurationEnvironment Source # 
type Rep FunctionConfigurationEnvironment Source # 
type Rep FunctionConfigurationEnvironment = D1 * (MetaData "FunctionConfigurationEnvironment" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "FunctionConfigurationEnvironment'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_fceVariables") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_fceResourceAccessPolicies") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [ResourceAccessPolicy]))) (S1 * (MetaSel (Just Symbol "_fceAccessSysfs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))))))

functionConfigurationEnvironment :: FunctionConfigurationEnvironment Source #

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

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

  • fceVariables - Environment variables for the Lambda function's configuration.
  • fceResourceAccessPolicies - A list of the resources, with their permissions, to which the Lambda function will be granted access. A Lambda function can have at most 10 resources.
  • fceAccessSysfs - If true, the Lambda function is allowed to access the host's sys folder. Use this when the Lambda function needs to read device information from sys.

fceVariables :: Lens' FunctionConfigurationEnvironment (HashMap Text Text) Source #

Environment variables for the Lambda function's configuration.

fceResourceAccessPolicies :: Lens' FunctionConfigurationEnvironment [ResourceAccessPolicy] Source #

A list of the resources, with their permissions, to which the Lambda function will be granted access. A Lambda function can have at most 10 resources.

fceAccessSysfs :: Lens' FunctionConfigurationEnvironment (Maybe Bool) Source #

If true, the Lambda function is allowed to access the host's sys folder. Use this when the Lambda function needs to read device information from sys.

FunctionDefinitionVersion

data FunctionDefinitionVersion Source #

Information about a function definition version.

See: functionDefinitionVersion smart constructor.

Instances

Eq FunctionDefinitionVersion Source # 
Data FunctionDefinitionVersion Source # 

Methods

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

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

toConstr :: FunctionDefinitionVersion -> Constr #

dataTypeOf :: FunctionDefinitionVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FunctionDefinitionVersion Source # 
Show FunctionDefinitionVersion Source # 
Generic FunctionDefinitionVersion Source # 
Hashable FunctionDefinitionVersion Source # 
ToJSON FunctionDefinitionVersion Source # 
FromJSON FunctionDefinitionVersion Source # 
NFData FunctionDefinitionVersion Source # 
type Rep FunctionDefinitionVersion Source # 
type Rep FunctionDefinitionVersion = D1 * (MetaData "FunctionDefinitionVersion" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" True) (C1 * (MetaCons "FunctionDefinitionVersion'" PrefixI True) (S1 * (MetaSel (Just Symbol "_fdvFunctions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe [Function]))))

functionDefinitionVersion :: FunctionDefinitionVersion Source #

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

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

  • fdvFunctions - A list of Lambda functions in this function definition version.

fdvFunctions :: Lens' FunctionDefinitionVersion [Function] Source #

A list of Lambda functions in this function definition version.

GreengrassLogger

data GreengrassLogger Source #

Information about a logger

See: greengrassLogger smart constructor.

Instances

Eq GreengrassLogger Source # 
Data GreengrassLogger Source # 

Methods

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

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

toConstr :: GreengrassLogger -> Constr #

dataTypeOf :: GreengrassLogger -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: GreengrassLogger -> () #

type Rep GreengrassLogger Source # 

greengrassLogger :: GreengrassLogger Source #

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

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

  • glSpace - The amount of file space, in KB, to use if the local file system is used for logging purposes.
  • glComponent - The component that will be subject to logging.
  • glId - The id of the logger.
  • glType - The type of log output which will be used.
  • glLevel - The level of the logs.

glSpace :: Lens' GreengrassLogger (Maybe Int) Source #

The amount of file space, in KB, to use if the local file system is used for logging purposes.

glComponent :: Lens' GreengrassLogger (Maybe LoggerComponent) Source #

The component that will be subject to logging.

glId :: Lens' GreengrassLogger (Maybe Text) Source #

The id of the logger.

glType :: Lens' GreengrassLogger (Maybe LoggerType) Source #

The type of log output which will be used.

GroupCertificateAuthorityProperties

data GroupCertificateAuthorityProperties Source #

Information about a certificate authority for a group.

See: groupCertificateAuthorityProperties smart constructor.

Instances

Eq GroupCertificateAuthorityProperties Source # 
Data GroupCertificateAuthorityProperties Source # 

Methods

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

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

toConstr :: GroupCertificateAuthorityProperties -> Constr #

dataTypeOf :: GroupCertificateAuthorityProperties -> DataType #

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

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

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

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

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

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

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

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

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

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

Read GroupCertificateAuthorityProperties Source # 
Show GroupCertificateAuthorityProperties Source # 
Generic GroupCertificateAuthorityProperties Source # 
Hashable GroupCertificateAuthorityProperties Source # 
FromJSON GroupCertificateAuthorityProperties Source # 
NFData GroupCertificateAuthorityProperties Source # 
type Rep GroupCertificateAuthorityProperties Source # 
type Rep GroupCertificateAuthorityProperties = D1 * (MetaData "GroupCertificateAuthorityProperties" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "GroupCertificateAuthorityProperties'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_gcapGroupCertificateAuthorityARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_gcapGroupCertificateAuthorityId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

groupCertificateAuthorityProperties :: GroupCertificateAuthorityProperties Source #

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

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

gcapGroupCertificateAuthorityARN :: Lens' GroupCertificateAuthorityProperties (Maybe Text) Source #

The ARN of the certificate authority for the group.

gcapGroupCertificateAuthorityId :: Lens' GroupCertificateAuthorityProperties (Maybe Text) Source #

The ID of the certificate authority for the group.

GroupInformation

data GroupInformation Source #

Information about a group.

See: groupInformation smart constructor.

Instances

Eq GroupInformation Source # 
Data GroupInformation Source # 

Methods

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

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

toConstr :: GroupInformation -> Constr #

dataTypeOf :: GroupInformation -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: GroupInformation -> () #

type Rep GroupInformation Source # 
type Rep GroupInformation = D1 * (MetaData "GroupInformation" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "GroupInformation'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_giLatestVersionARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_giARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_giName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_giCreationTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_giId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_giLatestVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_giLastUpdatedTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

groupInformation :: GroupInformation Source #

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

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

giLatestVersionARN :: Lens' GroupInformation (Maybe Text) Source #

The ARN of the latest version of the group.

giARN :: Lens' GroupInformation (Maybe Text) Source #

The ARN of the group.

giName :: Lens' GroupInformation (Maybe Text) Source #

The name of the group.

giCreationTimestamp :: Lens' GroupInformation (Maybe Text) Source #

The time, in milliseconds since the epoch, when the group was created.

giId :: Lens' GroupInformation (Maybe Text) Source #

The ID of the group.

giLatestVersion :: Lens' GroupInformation (Maybe Text) Source #

The latest version of the group.

giLastUpdatedTimestamp :: Lens' GroupInformation (Maybe Text) Source #

The time, in milliseconds since the epoch, when the group was last updated.

GroupOwnerSetting

data GroupOwnerSetting Source #

Group owner related settings for local resources.

See: groupOwnerSetting smart constructor.

Instances

Eq GroupOwnerSetting Source # 
Data GroupOwnerSetting Source # 

Methods

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

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

toConstr :: GroupOwnerSetting -> Constr #

dataTypeOf :: GroupOwnerSetting -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: GroupOwnerSetting -> () #

type Rep GroupOwnerSetting Source # 
type Rep GroupOwnerSetting = D1 * (MetaData "GroupOwnerSetting" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "GroupOwnerSetting'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_gosAutoAddGroupOwner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_gosGroupOwner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

groupOwnerSetting :: GroupOwnerSetting Source #

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

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

  • gosAutoAddGroupOwner - If true, GreenGrass automatically adds the specified Linux OS group owner of the resource to the Lambda process privileges. Thus the Lambda process will have the file access permissions of the added Linux group.
  • gosGroupOwner - The name of the Linux OS group whose privileges will be added to the Lambda process. This field is optional.

gosAutoAddGroupOwner :: Lens' GroupOwnerSetting (Maybe Bool) Source #

If true, GreenGrass automatically adds the specified Linux OS group owner of the resource to the Lambda process privileges. Thus the Lambda process will have the file access permissions of the added Linux group.

gosGroupOwner :: Lens' GroupOwnerSetting (Maybe Text) Source #

The name of the Linux OS group whose privileges will be added to the Lambda process. This field is optional.

GroupVersion

data GroupVersion Source #

Information about a group version.

See: groupVersion smart constructor.

Instances

Eq GroupVersion Source # 
Data GroupVersion Source # 

Methods

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

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

toConstr :: GroupVersion -> Constr #

dataTypeOf :: GroupVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Read GroupVersion Source # 
Show GroupVersion Source # 
Generic GroupVersion Source # 

Associated Types

type Rep GroupVersion :: * -> * #

Hashable GroupVersion Source # 
ToJSON GroupVersion Source # 
FromJSON GroupVersion Source # 
NFData GroupVersion Source # 

Methods

rnf :: GroupVersion -> () #

type Rep GroupVersion Source # 
type Rep GroupVersion = D1 * (MetaData "GroupVersion" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "GroupVersion'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_gvResourceDefinitionVersionARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_gvSubscriptionDefinitionVersionARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_gvCoreDefinitionVersionARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_gvDeviceDefinitionVersionARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_gvFunctionDefinitionVersionARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_gvLoggerDefinitionVersionARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

groupVersion :: GroupVersion Source #

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

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

gvResourceDefinitionVersionARN :: Lens' GroupVersion (Maybe Text) Source #

The resource definition version ARN for this group.

gvSubscriptionDefinitionVersionARN :: Lens' GroupVersion (Maybe Text) Source #

The ARN of the subscription definition version for this group.

gvCoreDefinitionVersionARN :: Lens' GroupVersion (Maybe Text) Source #

The ARN of the core definition version for this group.

gvDeviceDefinitionVersionARN :: Lens' GroupVersion (Maybe Text) Source #

The ARN of the device definition version for this group.

gvFunctionDefinitionVersionARN :: Lens' GroupVersion (Maybe Text) Source #

The ARN of the function definition version for this group.

gvLoggerDefinitionVersionARN :: Lens' GroupVersion (Maybe Text) Source #

The ARN of the logger definition version for this group.

LocalDeviceResourceData

data LocalDeviceResourceData Source #

Attributes that define a local device resource.

See: localDeviceResourceData smart constructor.

Instances

Eq LocalDeviceResourceData Source # 
Data LocalDeviceResourceData Source # 

Methods

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

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

toConstr :: LocalDeviceResourceData -> Constr #

dataTypeOf :: LocalDeviceResourceData -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: LocalDeviceResourceData -> () #

type Rep LocalDeviceResourceData Source # 
type Rep LocalDeviceResourceData = D1 * (MetaData "LocalDeviceResourceData" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "LocalDeviceResourceData'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ldrdGroupOwnerSetting") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe GroupOwnerSetting))) (S1 * (MetaSel (Just Symbol "_ldrdSourcePath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

localDeviceResourceData :: LocalDeviceResourceData Source #

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

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

  • ldrdGroupOwnerSetting - Group/owner related settings for local resources.
  • ldrdSourcePath - The local absolute path of the device resource. The source path for a device resource can refer only to a character device or block device under ''/dev''.

ldrdGroupOwnerSetting :: Lens' LocalDeviceResourceData (Maybe GroupOwnerSetting) Source #

Group/owner related settings for local resources.

ldrdSourcePath :: Lens' LocalDeviceResourceData (Maybe Text) Source #

The local absolute path of the device resource. The source path for a device resource can refer only to a character device or block device under ''/dev''.

LocalVolumeResourceData

data LocalVolumeResourceData Source #

Attributes that define a local volume resource.

See: localVolumeResourceData smart constructor.

Instances

Eq LocalVolumeResourceData Source # 
Data LocalVolumeResourceData Source # 

Methods

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

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

toConstr :: LocalVolumeResourceData -> Constr #

dataTypeOf :: LocalVolumeResourceData -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: LocalVolumeResourceData -> () #

type Rep LocalVolumeResourceData Source # 
type Rep LocalVolumeResourceData = D1 * (MetaData "LocalVolumeResourceData" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "LocalVolumeResourceData'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_lvrdGroupOwnerSetting") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe GroupOwnerSetting))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lvrdDestinationPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lvrdSourcePath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

localVolumeResourceData :: LocalVolumeResourceData Source #

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

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

  • lvrdGroupOwnerSetting - Allows you to configure additional group privileges for the Lambda process. This field is optional.
  • lvrdDestinationPath - The absolute local path of the resource inside the lambda environment.
  • lvrdSourcePath - The local absolute path of the volume resource on the host. The source path for a volume resource type cannot start with ''/proc'' or ''/sys''.

lvrdGroupOwnerSetting :: Lens' LocalVolumeResourceData (Maybe GroupOwnerSetting) Source #

Allows you to configure additional group privileges for the Lambda process. This field is optional.

lvrdDestinationPath :: Lens' LocalVolumeResourceData (Maybe Text) Source #

The absolute local path of the resource inside the lambda environment.

lvrdSourcePath :: Lens' LocalVolumeResourceData (Maybe Text) Source #

The local absolute path of the volume resource on the host. The source path for a volume resource type cannot start with ''/proc'' or ''/sys''.

LoggerDefinitionVersion

data LoggerDefinitionVersion Source #

Information about a logger definition version.

See: loggerDefinitionVersion smart constructor.

Instances

Eq LoggerDefinitionVersion Source # 
Data LoggerDefinitionVersion Source # 

Methods

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

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

toConstr :: LoggerDefinitionVersion -> Constr #

dataTypeOf :: LoggerDefinitionVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: LoggerDefinitionVersion -> () #

type Rep LoggerDefinitionVersion Source # 
type Rep LoggerDefinitionVersion = D1 * (MetaData "LoggerDefinitionVersion" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" True) (C1 * (MetaCons "LoggerDefinitionVersion'" PrefixI True) (S1 * (MetaSel (Just Symbol "_ldvLoggers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe [GreengrassLogger]))))

loggerDefinitionVersion :: LoggerDefinitionVersion Source #

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

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

Resource

data Resource Source #

Information about a resource.

See: resource smart constructor.

Instances

Eq Resource Source # 
Data Resource Source # 

Methods

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

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

toConstr :: Resource -> Constr #

dataTypeOf :: Resource -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Resource Source # 
Show Resource Source # 
Generic Resource Source # 

Associated Types

type Rep Resource :: * -> * #

Methods

from :: Resource -> Rep Resource x #

to :: Rep Resource x -> Resource #

Hashable Resource Source # 

Methods

hashWithSalt :: Int -> Resource -> Int #

hash :: Resource -> Int #

ToJSON Resource Source # 
FromJSON Resource Source # 
NFData Resource Source # 

Methods

rnf :: Resource -> () #

type Rep Resource Source # 
type Rep Resource = D1 * (MetaData "Resource" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "Resource'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_rResourceDataContainer") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ResourceDataContainer))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_rId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

resource :: Resource Source #

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

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

  • rResourceDataContainer - A container of data for all resource types.
  • rName - The descriptive resource name, which is displayed on the Greengrass console. Max length 128 characters with pattern ''[a-zA-Z0-9:_-]+''. This must be unique within a Greengrass group.
  • rId - The resource ID, used to refer to a resource in the Lambda function configuration. Max length is 128 characters with pattern ''[a-zA-Z0-9:_-]+''. This must be unique within a Greengrass group.

rResourceDataContainer :: Lens' Resource (Maybe ResourceDataContainer) Source #

A container of data for all resource types.

rName :: Lens' Resource (Maybe Text) Source #

The descriptive resource name, which is displayed on the Greengrass console. Max length 128 characters with pattern ''[a-zA-Z0-9:_-]+''. This must be unique within a Greengrass group.

rId :: Lens' Resource (Maybe Text) Source #

The resource ID, used to refer to a resource in the Lambda function configuration. Max length is 128 characters with pattern ''[a-zA-Z0-9:_-]+''. This must be unique within a Greengrass group.

ResourceAccessPolicy

data ResourceAccessPolicy Source #

A policy used by the function to access a resource.

See: resourceAccessPolicy smart constructor.

Instances

Eq ResourceAccessPolicy Source # 
Data ResourceAccessPolicy Source # 

Methods

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

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

toConstr :: ResourceAccessPolicy -> Constr #

dataTypeOf :: ResourceAccessPolicy -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ResourceAccessPolicy -> () #

type Rep ResourceAccessPolicy Source # 
type Rep ResourceAccessPolicy = D1 * (MetaData "ResourceAccessPolicy" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "ResourceAccessPolicy'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_rapResourceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_rapPermission") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Permission)))))

resourceAccessPolicy :: ResourceAccessPolicy Source #

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

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

  • rapResourceId - The ID of the resource. (This ID is assigned to the resource when you create the resource definiton.)
  • rapPermission - The permissions that the Lambda function has to the resource. Can be one of 'rw' (read/write) or 'ro' (read-only).

rapResourceId :: Lens' ResourceAccessPolicy (Maybe Text) Source #

The ID of the resource. (This ID is assigned to the resource when you create the resource definiton.)

rapPermission :: Lens' ResourceAccessPolicy (Maybe Permission) Source #

The permissions that the Lambda function has to the resource. Can be one of 'rw' (read/write) or 'ro' (read-only).

ResourceDataContainer

data ResourceDataContainer Source #

A container for resource data. The container takes only one of the following supported resource data types: 'LocalDeviceResourceData', 'LocalVolumeResourceData', 'SageMakerMachineLearningModelResourceData', 'S3MachineLearningModelResourceData'.

See: resourceDataContainer smart constructor.

Instances

Eq ResourceDataContainer Source # 
Data ResourceDataContainer Source # 

Methods

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

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

toConstr :: ResourceDataContainer -> Constr #

dataTypeOf :: ResourceDataContainer -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ResourceDataContainer -> () #

type Rep ResourceDataContainer Source # 
type Rep ResourceDataContainer = D1 * (MetaData "ResourceDataContainer" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "ResourceDataContainer'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_rdcS3MachineLearningModelResourceData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe S3MachineLearningModelResourceData))) (S1 * (MetaSel (Just Symbol "_rdcSageMakerMachineLearningModelResourceData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SageMakerMachineLearningModelResourceData)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rdcLocalVolumeResourceData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LocalVolumeResourceData))) (S1 * (MetaSel (Just Symbol "_rdcLocalDeviceResourceData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe LocalDeviceResourceData))))))

resourceDataContainer :: ResourceDataContainer Source #

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

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

rdcLocalVolumeResourceData :: Lens' ResourceDataContainer (Maybe LocalVolumeResourceData) Source #

Attributes that define the local volume resource.

rdcLocalDeviceResourceData :: Lens' ResourceDataContainer (Maybe LocalDeviceResourceData) Source #

Attributes that define the local device resource.

ResourceDefinitionVersion

data ResourceDefinitionVersion Source #

Information about a resource definition version.

See: resourceDefinitionVersion smart constructor.

Instances

Eq ResourceDefinitionVersion Source # 
Data ResourceDefinitionVersion Source # 

Methods

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

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

toConstr :: ResourceDefinitionVersion -> Constr #

dataTypeOf :: ResourceDefinitionVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ResourceDefinitionVersion Source # 
Show ResourceDefinitionVersion Source # 
Generic ResourceDefinitionVersion Source # 
Hashable ResourceDefinitionVersion Source # 
ToJSON ResourceDefinitionVersion Source # 
FromJSON ResourceDefinitionVersion Source # 
NFData ResourceDefinitionVersion Source # 
type Rep ResourceDefinitionVersion Source # 
type Rep ResourceDefinitionVersion = D1 * (MetaData "ResourceDefinitionVersion" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" True) (C1 * (MetaCons "ResourceDefinitionVersion'" PrefixI True) (S1 * (MetaSel (Just Symbol "_rdvResources") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe [Resource]))))

resourceDefinitionVersion :: ResourceDefinitionVersion Source #

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

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

S3MachineLearningModelResourceData

data S3MachineLearningModelResourceData Source #

Attributes that define an S3 machine learning resource.

See: s3MachineLearningModelResourceData smart constructor.

Instances

Eq S3MachineLearningModelResourceData Source # 
Data S3MachineLearningModelResourceData Source # 

Methods

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

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

toConstr :: S3MachineLearningModelResourceData -> Constr #

dataTypeOf :: S3MachineLearningModelResourceData -> DataType #

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

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

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

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

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

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

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

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

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

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

Read S3MachineLearningModelResourceData Source # 
Show S3MachineLearningModelResourceData Source # 
Generic S3MachineLearningModelResourceData Source # 
Hashable S3MachineLearningModelResourceData Source # 
ToJSON S3MachineLearningModelResourceData Source # 
FromJSON S3MachineLearningModelResourceData Source # 
NFData S3MachineLearningModelResourceData Source # 
type Rep S3MachineLearningModelResourceData Source # 
type Rep S3MachineLearningModelResourceData = D1 * (MetaData "S3MachineLearningModelResourceData" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "S3MachineLearningModelResourceData'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_smlmrdDestinationPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_smlmrdS3URI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

s3MachineLearningModelResourceData :: S3MachineLearningModelResourceData Source #

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

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

  • smlmrdDestinationPath - The absolute local path of the resource inside the Lambda environment.
  • smlmrdS3URI - The URI of the source model in an S3 bucket. The model package must be in tar.gz or .zip format.

smlmrdDestinationPath :: Lens' S3MachineLearningModelResourceData (Maybe Text) Source #

The absolute local path of the resource inside the Lambda environment.

smlmrdS3URI :: Lens' S3MachineLearningModelResourceData (Maybe Text) Source #

The URI of the source model in an S3 bucket. The model package must be in tar.gz or .zip format.

SageMakerMachineLearningModelResourceData

data SageMakerMachineLearningModelResourceData Source #

Attributes that define an SageMaker machine learning resource.

See: sageMakerMachineLearningModelResourceData smart constructor.

Instances

Eq SageMakerMachineLearningModelResourceData Source # 
Data SageMakerMachineLearningModelResourceData Source # 

Methods

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

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

toConstr :: SageMakerMachineLearningModelResourceData -> Constr #

dataTypeOf :: SageMakerMachineLearningModelResourceData -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SageMakerMachineLearningModelResourceData Source # 
Show SageMakerMachineLearningModelResourceData Source # 
Generic SageMakerMachineLearningModelResourceData Source # 
Hashable SageMakerMachineLearningModelResourceData Source # 
ToJSON SageMakerMachineLearningModelResourceData Source # 
FromJSON SageMakerMachineLearningModelResourceData Source # 
NFData SageMakerMachineLearningModelResourceData Source # 
type Rep SageMakerMachineLearningModelResourceData Source # 
type Rep SageMakerMachineLearningModelResourceData = D1 * (MetaData "SageMakerMachineLearningModelResourceData" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "SageMakerMachineLearningModelResourceData'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_smmlmrdSageMakerJobARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_smmlmrdDestinationPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

sageMakerMachineLearningModelResourceData :: SageMakerMachineLearningModelResourceData Source #

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

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

smmlmrdSageMakerJobARN :: Lens' SageMakerMachineLearningModelResourceData (Maybe Text) Source #

The ARN of the SageMaker training job that represents the source model.

smmlmrdDestinationPath :: Lens' SageMakerMachineLearningModelResourceData (Maybe Text) Source #

The absolute local path of the resource inside the Lambda environment.

Subscription

data Subscription Source #

Information about a subscription.

See: subscription smart constructor.

Instances

Eq Subscription Source # 
Data Subscription Source # 

Methods

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

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

toConstr :: Subscription -> Constr #

dataTypeOf :: Subscription -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Subscription Source # 
Show Subscription Source # 
Generic Subscription Source # 

Associated Types

type Rep Subscription :: * -> * #

Hashable Subscription Source # 
ToJSON Subscription Source # 
FromJSON Subscription Source # 
NFData Subscription Source # 

Methods

rnf :: Subscription -> () #

type Rep Subscription Source # 
type Rep Subscription = D1 * (MetaData "Subscription" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "Subscription'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_sSubject") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_sSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_sId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_sTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

subscription :: Subscription Source #

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

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

  • sSubject - The subject of the message.
  • sSource - The source of the subscription. Can be a thing ARN, a Lambda function ARN, cloud (which represents the IoT cloud), or GGShadowService.
  • sId - The id of the subscription.
  • sTarget - Where the message is sent to. Can be a thing ARN, a Lambda function ARN, cloud (which represents the IoT cloud), or GGShadowService.

sSubject :: Lens' Subscription (Maybe Text) Source #

The subject of the message.

sSource :: Lens' Subscription (Maybe Text) Source #

The source of the subscription. Can be a thing ARN, a Lambda function ARN, cloud (which represents the IoT cloud), or GGShadowService.

sId :: Lens' Subscription (Maybe Text) Source #

The id of the subscription.

sTarget :: Lens' Subscription (Maybe Text) Source #

Where the message is sent to. Can be a thing ARN, a Lambda function ARN, cloud (which represents the IoT cloud), or GGShadowService.

SubscriptionDefinitionVersion

data SubscriptionDefinitionVersion Source #

Information about a subscription definition version.

See: subscriptionDefinitionVersion smart constructor.

Instances

Eq SubscriptionDefinitionVersion Source # 
Data SubscriptionDefinitionVersion Source # 

Methods

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

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

toConstr :: SubscriptionDefinitionVersion -> Constr #

dataTypeOf :: SubscriptionDefinitionVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SubscriptionDefinitionVersion Source # 
Show SubscriptionDefinitionVersion Source # 
Generic SubscriptionDefinitionVersion Source # 
Hashable SubscriptionDefinitionVersion Source # 
ToJSON SubscriptionDefinitionVersion Source # 
FromJSON SubscriptionDefinitionVersion Source # 
NFData SubscriptionDefinitionVersion Source # 
type Rep SubscriptionDefinitionVersion Source # 
type Rep SubscriptionDefinitionVersion = D1 * (MetaData "SubscriptionDefinitionVersion" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" True) (C1 * (MetaCons "SubscriptionDefinitionVersion'" PrefixI True) (S1 * (MetaSel (Just Symbol "_sdvSubscriptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe [Subscription]))))

subscriptionDefinitionVersion :: SubscriptionDefinitionVersion Source #

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

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

VersionInformation

data VersionInformation Source #

Information about a version.

See: versionInformation smart constructor.

Instances

Eq VersionInformation Source # 
Data VersionInformation Source # 

Methods

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

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

toConstr :: VersionInformation -> Constr #

dataTypeOf :: VersionInformation -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: VersionInformation -> () #

type Rep VersionInformation Source # 
type Rep VersionInformation = D1 * (MetaData "VersionInformation" "Network.AWS.Greengrass.Types.Product" "amazonka-greengrass-1.6.0-UQvTNoJiEcHgaWALQEura" False) (C1 * (MetaCons "VersionInformation'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_viARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_viCreationTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_viVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_viId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

versionInformation :: VersionInformation Source #

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

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

  • viARN - The ARN of the version.
  • viCreationTimestamp - The time, in milliseconds since the epoch, when the version was created.
  • viVersion - The unique ID of the version.
  • viId - The ID of the version.

viARN :: Lens' VersionInformation (Maybe Text) Source #

The ARN of the version.

viCreationTimestamp :: Lens' VersionInformation (Maybe Text) Source #

The time, in milliseconds since the epoch, when the version was created.

viVersion :: Lens' VersionInformation (Maybe Text) Source #

The unique ID of the version.

viId :: Lens' VersionInformation (Maybe Text) Source #

The ID of the version.