amazonka-iot-analytics-1.6.1: Amazon IoT Analytics 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.IoTAnalytics.Types

Contents

Description

 
Synopsis

Service Configuration

ioTAnalytics :: Service Source #

API version 2017-11-27 of the Amazon IoT Analytics SDK configuration.

Errors

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

A resource with the same name already exists.

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

The request was denied due to request throttling.

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

The service is temporarily unavailable.

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

A resource with the specified name could not be found.

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

The command caused an internal limit to be exceeded.

ChannelStatus

data ChannelStatus Source #

Instances
Bounded ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Enum ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Eq ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Data ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

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

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

toConstr :: ChannelStatus -> Constr #

dataTypeOf :: ChannelStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Read ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Show ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Generic ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Associated Types

type Rep ChannelStatus :: Type -> Type #

Hashable ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

FromJSON ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToHeader ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToQuery ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToByteString ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

FromText ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToText ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

toText :: ChannelStatus -> Text #

NFData ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

rnf :: ChannelStatus -> () #

type Rep ChannelStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

type Rep ChannelStatus = D1 (MetaData "ChannelStatus" "Network.AWS.IoTAnalytics.Types.Sum" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "CSActive" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CSCreating" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSDeleting" PrefixI False) (U1 :: Type -> Type)))

DatasetContentState

data DatasetContentState Source #

Instances
Bounded DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Enum DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Eq DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Data DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

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

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

toConstr :: DatasetContentState -> Constr #

dataTypeOf :: DatasetContentState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Read DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Show DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Generic DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Associated Types

type Rep DatasetContentState :: Type -> Type #

Hashable DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

FromJSON DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToHeader DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToQuery DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToByteString DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

FromText DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToText DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

NFData DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

rnf :: DatasetContentState -> () #

type Rep DatasetContentState Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

type Rep DatasetContentState = D1 (MetaData "DatasetContentState" "Network.AWS.IoTAnalytics.Types.Sum" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "DCSCreating" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "DCSFailed" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DCSSucceeded" PrefixI False) (U1 :: Type -> Type)))

DatasetStatus

data DatasetStatus Source #

Constructors

Active 
Creating 
Deleting 
Instances
Bounded DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Enum DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Eq DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Data DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

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

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

toConstr :: DatasetStatus -> Constr #

dataTypeOf :: DatasetStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Read DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Show DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Generic DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Associated Types

type Rep DatasetStatus :: Type -> Type #

Hashable DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

FromJSON DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToHeader DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToQuery DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToByteString DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

FromText DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToText DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

toText :: DatasetStatus -> Text #

NFData DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

rnf :: DatasetStatus -> () #

type Rep DatasetStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

type Rep DatasetStatus = D1 (MetaData "DatasetStatus" "Network.AWS.IoTAnalytics.Types.Sum" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "Active" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Creating" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Deleting" PrefixI False) (U1 :: Type -> Type)))

DatastoreStatus

data DatastoreStatus Source #

Instances
Bounded DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Enum DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Eq DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Data DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

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

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

toConstr :: DatastoreStatus -> Constr #

dataTypeOf :: DatastoreStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Read DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Show DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Generic DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Associated Types

type Rep DatastoreStatus :: Type -> Type #

Hashable DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

FromJSON DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToHeader DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToQuery DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToByteString DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

FromText DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToText DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

NFData DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

rnf :: DatastoreStatus -> () #

type Rep DatastoreStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

type Rep DatastoreStatus = D1 (MetaData "DatastoreStatus" "Network.AWS.IoTAnalytics.Types.Sum" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "DSActive" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "DSCreating" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DSDeleting" PrefixI False) (U1 :: Type -> Type)))

LoggingLevel

data LoggingLevel Source #

Constructors

Error' 
Instances
Bounded LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Enum LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Eq LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Data LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

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

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

toConstr :: LoggingLevel -> Constr #

dataTypeOf :: LoggingLevel -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Read LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Show LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Generic LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Associated Types

type Rep LoggingLevel :: Type -> Type #

Hashable LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToJSON LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

FromJSON LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToHeader LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToQuery LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToByteString LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

FromText LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToText LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

toText :: LoggingLevel -> Text #

NFData LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

rnf :: LoggingLevel -> () #

type Rep LoggingLevel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

type Rep LoggingLevel = D1 (MetaData "LoggingLevel" "Network.AWS.IoTAnalytics.Types.Sum" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "Error'" PrefixI False) (U1 :: Type -> Type))

ReprocessingStatus

data ReprocessingStatus Source #

Instances
Bounded ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Enum ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Eq ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Data ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

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

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

toConstr :: ReprocessingStatus -> Constr #

dataTypeOf :: ReprocessingStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Read ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Show ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Generic ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Associated Types

type Rep ReprocessingStatus :: Type -> Type #

Hashable ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

FromJSON ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToHeader ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToQuery ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToByteString ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

FromText ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

ToText ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

NFData ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

Methods

rnf :: ReprocessingStatus -> () #

type Rep ReprocessingStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Sum

type Rep ReprocessingStatus = D1 (MetaData "ReprocessingStatus" "Network.AWS.IoTAnalytics.Types.Sum" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) ((C1 (MetaCons "Cancelled" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Failed" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Running" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Succeeded" PrefixI False) (U1 :: Type -> Type)))

AddAttributesActivity

data AddAttributesActivity Source #

An activity that adds other attributes based on existing attributes in the message.

See: addAttributesActivity smart constructor.

Instances
Eq AddAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data AddAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: AddAttributesActivity -> Constr #

dataTypeOf :: AddAttributesActivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AddAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show AddAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic AddAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep AddAttributesActivity :: Type -> Type #

Hashable AddAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON AddAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON AddAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData AddAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: AddAttributesActivity -> () #

type Rep AddAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep AddAttributesActivity = D1 (MetaData "AddAttributesActivity" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "AddAttributesActivity'" PrefixI True) (S1 (MetaSel (Just "_aaaNext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_aaaName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_aaaAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Map Text Text)))))

addAttributesActivity Source #

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

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

aaaNext :: Lens' AddAttributesActivity (Maybe Text) Source #

The next activity in the pipeline.

aaaName :: Lens' AddAttributesActivity Text Source #

The name of the addAttributes activity.

aaaAttributes :: Lens' AddAttributesActivity (HashMap Text Text) Source #

A list of 1-50 AttributeNameMapping objects that map an existing attribute to a new attribute.

BatchPutMessageErrorEntry

data BatchPutMessageErrorEntry Source #

Contains informations about errors.

See: batchPutMessageErrorEntry smart constructor.

Instances
Eq BatchPutMessageErrorEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data BatchPutMessageErrorEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: BatchPutMessageErrorEntry -> Constr #

dataTypeOf :: BatchPutMessageErrorEntry -> DataType #

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

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

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

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

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

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

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

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

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

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

Read BatchPutMessageErrorEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show BatchPutMessageErrorEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic BatchPutMessageErrorEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep BatchPutMessageErrorEntry :: Type -> Type #

Hashable BatchPutMessageErrorEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON BatchPutMessageErrorEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData BatchPutMessageErrorEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep BatchPutMessageErrorEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep BatchPutMessageErrorEntry = D1 (MetaData "BatchPutMessageErrorEntry" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "BatchPutMessageErrorEntry'" PrefixI True) (S1 (MetaSel (Just "_bpmeeErrorCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_bpmeeErrorMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_bpmeeMessageId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

batchPutMessageErrorEntry :: BatchPutMessageErrorEntry Source #

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

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

  • bpmeeErrorCode - The code associated with the error.
  • bpmeeErrorMessage - The message associated with the error.
  • bpmeeMessageId - The ID of the message that caused the error. (See the value corresponding to the "messageId" key in the message object.)

bpmeeErrorCode :: Lens' BatchPutMessageErrorEntry (Maybe Text) Source #

The code associated with the error.

bpmeeErrorMessage :: Lens' BatchPutMessageErrorEntry (Maybe Text) Source #

The message associated with the error.

bpmeeMessageId :: Lens' BatchPutMessageErrorEntry (Maybe Text) Source #

The ID of the message that caused the error. (See the value corresponding to the "messageId" key in the message object.)

Channel

data Channel Source #

A collection of data from an MQTT topic. Channels archive the raw, unprocessed messages before publishing the data to a pipeline.

See: channel smart constructor.

Instances
Eq Channel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

Data Channel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: Channel -> Constr #

dataTypeOf :: Channel -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Channel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show Channel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic Channel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep Channel :: Type -> Type #

Methods

from :: Channel -> Rep Channel x #

to :: Rep Channel x -> Channel #

Hashable Channel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

hashWithSalt :: Int -> Channel -> Int #

hash :: Channel -> Int #

FromJSON Channel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData Channel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: Channel -> () #

type Rep Channel Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

channel :: Channel Source #

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

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

cCreationTime :: Lens' Channel (Maybe UTCTime) Source #

When the channel was created.

cStatus :: Lens' Channel (Maybe ChannelStatus) Source #

The status of the channel.

cArn :: Lens' Channel (Maybe Text) Source #

The ARN of the channel.

cRetentionPeriod :: Lens' Channel (Maybe RetentionPeriod) Source #

How long, in days, message data is kept for the channel.

cName :: Lens' Channel (Maybe Text) Source #

The name of the channel.

cLastUpdateTime :: Lens' Channel (Maybe UTCTime) Source #

When the channel was last updated.

ChannelActivity

data ChannelActivity Source #

The activity that determines the source of the messages to be processed.

See: channelActivity smart constructor.

Instances
Eq ChannelActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data ChannelActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: ChannelActivity -> Constr #

dataTypeOf :: ChannelActivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ChannelActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show ChannelActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic ChannelActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep ChannelActivity :: Type -> Type #

Hashable ChannelActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON ChannelActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON ChannelActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData ChannelActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: ChannelActivity -> () #

type Rep ChannelActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep ChannelActivity = D1 (MetaData "ChannelActivity" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "ChannelActivity'" PrefixI True) (S1 (MetaSel (Just "_caNext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_caName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_caChannelName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

channelActivity Source #

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

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

  • caNext - The next activity in the pipeline.
  • caName - The name of the channel activity.
  • caChannelName - The name of the channel from which the messages are processed.

caNext :: Lens' ChannelActivity (Maybe Text) Source #

The next activity in the pipeline.

caName :: Lens' ChannelActivity Text Source #

The name of the channel activity.

caChannelName :: Lens' ChannelActivity Text Source #

The name of the channel from which the messages are processed.

ChannelSummary

data ChannelSummary Source #

A summary of information about a channel.

See: channelSummary smart constructor.

Instances
Eq ChannelSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data ChannelSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: ChannelSummary -> Constr #

dataTypeOf :: ChannelSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ChannelSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show ChannelSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic ChannelSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep ChannelSummary :: Type -> Type #

Hashable ChannelSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON ChannelSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData ChannelSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: ChannelSummary -> () #

type Rep ChannelSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep ChannelSummary = D1 (MetaData "ChannelSummary" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "ChannelSummary'" PrefixI True) ((S1 (MetaSel (Just "_csCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: S1 (MetaSel (Just "_csStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChannelStatus))) :*: (S1 (MetaSel (Just "_csChannelName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_csLastUpdateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)))))

channelSummary :: ChannelSummary Source #

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

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

csCreationTime :: Lens' ChannelSummary (Maybe UTCTime) Source #

When the channel was created.

csStatus :: Lens' ChannelSummary (Maybe ChannelStatus) Source #

The status of the channel.

csChannelName :: Lens' ChannelSummary (Maybe Text) Source #

The name of the channel.

csLastUpdateTime :: Lens' ChannelSummary (Maybe UTCTime) Source #

The last time the channel was updated.

Dataset

data Dataset Source #

Information about a data set.

See: dataset smart constructor.

Instances
Eq Dataset Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

Data Dataset Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: Dataset -> Constr #

dataTypeOf :: Dataset -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Dataset Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show Dataset Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic Dataset Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep Dataset :: Type -> Type #

Methods

from :: Dataset -> Rep Dataset x #

to :: Rep Dataset x -> Dataset #

Hashable Dataset Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

hashWithSalt :: Int -> Dataset -> Int #

hash :: Dataset -> Int #

FromJSON Dataset Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData Dataset Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: Dataset -> () #

type Rep Dataset Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

dataset :: Dataset Source #

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

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

dCreationTime :: Lens' Dataset (Maybe UTCTime) Source #

When the data set was created.

dStatus :: Lens' Dataset (Maybe DatasetStatus) Source #

The status of the data set.

dArn :: Lens' Dataset (Maybe Text) Source #

The ARN of the data set.

dActions :: Lens' Dataset (Maybe (NonEmpty DatasetAction)) Source #

The DatasetAction objects that create the data set.

dTriggers :: Lens' Dataset [DatasetTrigger] Source #

The DatasetTrigger objects that specify when the data set is automatically updated.

dName :: Lens' Dataset (Maybe Text) Source #

The name of the data set.

dLastUpdateTime :: Lens' Dataset (Maybe UTCTime) Source #

The last time the data set was updated.

DatasetAction

data DatasetAction Source #

A DatasetAction object specifying the query that creates the data set content.

See: datasetAction smart constructor.

Instances
Eq DatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data DatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: DatasetAction -> Constr #

dataTypeOf :: DatasetAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show DatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic DatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep DatasetAction :: Type -> Type #

Hashable DatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON DatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON DatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData DatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: DatasetAction -> () #

type Rep DatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep DatasetAction = D1 (MetaData "DatasetAction" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "DatasetAction'" PrefixI True) (S1 (MetaSel (Just "_daQueryAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SqlQueryDatasetAction)) :*: S1 (MetaSel (Just "_daActionName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

datasetAction :: DatasetAction Source #

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

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

daQueryAction :: Lens' DatasetAction (Maybe SqlQueryDatasetAction) Source #

An SqlQueryDatasetAction object that contains the SQL query to modify the message.

daActionName :: Lens' DatasetAction (Maybe Text) Source #

The name of the data set action.

DatasetContentStatus

data DatasetContentStatus Source #

The state of the data set and the reason it is in this state.

See: datasetContentStatus smart constructor.

Instances
Eq DatasetContentStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data DatasetContentStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: DatasetContentStatus -> Constr #

dataTypeOf :: DatasetContentStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DatasetContentStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show DatasetContentStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic DatasetContentStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep DatasetContentStatus :: Type -> Type #

Hashable DatasetContentStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON DatasetContentStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData DatasetContentStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: DatasetContentStatus -> () #

type Rep DatasetContentStatus Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep DatasetContentStatus = D1 (MetaData "DatasetContentStatus" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "DatasetContentStatus'" PrefixI True) (S1 (MetaSel (Just "_dcsState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DatasetContentState)) :*: S1 (MetaSel (Just "_dcsReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

datasetContentStatus :: DatasetContentStatus Source #

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

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

dcsState :: Lens' DatasetContentStatus (Maybe DatasetContentState) Source #

The state of the data set. Can be one of CREATING, SUCCEEDED or FAILED.

dcsReason :: Lens' DatasetContentStatus (Maybe Text) Source #

The reason the data set is in this state.

DatasetEntry

data DatasetEntry Source #

The reference to a data set entry.

See: datasetEntry smart constructor.

Instances
Eq DatasetEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data DatasetEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: DatasetEntry -> Constr #

dataTypeOf :: DatasetEntry -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DatasetEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show DatasetEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic DatasetEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep DatasetEntry :: Type -> Type #

Hashable DatasetEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON DatasetEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData DatasetEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: DatasetEntry -> () #

type Rep DatasetEntry Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep DatasetEntry = D1 (MetaData "DatasetEntry" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "DatasetEntry'" PrefixI True) (S1 (MetaSel (Just "_deEntryName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_deDataURI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

datasetEntry :: DatasetEntry Source #

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

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

deEntryName :: Lens' DatasetEntry (Maybe Text) Source #

The name of the data set item.

deDataURI :: Lens' DatasetEntry (Maybe Text) Source #

The pre-signed URI of the data set item.

DatasetSummary

data DatasetSummary Source #

A summary of information about a data set.

See: datasetSummary smart constructor.

Instances
Eq DatasetSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data DatasetSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: DatasetSummary -> Constr #

dataTypeOf :: DatasetSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DatasetSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show DatasetSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic DatasetSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep DatasetSummary :: Type -> Type #

Hashable DatasetSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON DatasetSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData DatasetSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: DatasetSummary -> () #

type Rep DatasetSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep DatasetSummary = D1 (MetaData "DatasetSummary" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "DatasetSummary'" PrefixI True) ((S1 (MetaSel (Just "_dssCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: S1 (MetaSel (Just "_dssStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DatasetStatus))) :*: (S1 (MetaSel (Just "_dssDatasetName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_dssLastUpdateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)))))

datasetSummary :: DatasetSummary Source #

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

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

dssCreationTime :: Lens' DatasetSummary (Maybe UTCTime) Source #

The time the data set was created.

dssStatus :: Lens' DatasetSummary (Maybe DatasetStatus) Source #

The status of the data set.

dssDatasetName :: Lens' DatasetSummary (Maybe Text) Source #

The name of the data set.

dssLastUpdateTime :: Lens' DatasetSummary (Maybe UTCTime) Source #

The last time the data set was updated.

DatasetTrigger

data DatasetTrigger Source #

The DatasetTrigger that specifies when the data set is automatically updated.

See: datasetTrigger smart constructor.

Instances
Eq DatasetTrigger Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data DatasetTrigger Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: DatasetTrigger -> Constr #

dataTypeOf :: DatasetTrigger -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DatasetTrigger Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show DatasetTrigger Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic DatasetTrigger Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep DatasetTrigger :: Type -> Type #

Hashable DatasetTrigger Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON DatasetTrigger Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON DatasetTrigger Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData DatasetTrigger Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: DatasetTrigger -> () #

type Rep DatasetTrigger Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep DatasetTrigger = D1 (MetaData "DatasetTrigger" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" True) (C1 (MetaCons "DatasetTrigger'" PrefixI True) (S1 (MetaSel (Just "_dtSchedule") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Schedule))))

datasetTrigger :: DatasetTrigger Source #

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

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

dtSchedule :: Lens' DatasetTrigger (Maybe Schedule) Source #

The Schedule when the trigger is initiated.

Datastore

data Datastore Source #

Information about a data store.

See: datastore smart constructor.

Instances
Eq Datastore Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data Datastore Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: Datastore -> Constr #

dataTypeOf :: Datastore -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Datastore Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show Datastore Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic Datastore Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep Datastore :: Type -> Type #

Hashable Datastore Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON Datastore Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData Datastore Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: Datastore -> () #

type Rep Datastore Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep Datastore = D1 (MetaData "Datastore" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "Datastore'" PrefixI True) ((S1 (MetaSel (Just "_datCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: (S1 (MetaSel (Just "_datStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DatastoreStatus)) :*: S1 (MetaSel (Just "_datArn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "_datRetentionPeriod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RetentionPeriod)) :*: (S1 (MetaSel (Just "_datName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_datLastUpdateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))))))

datastore :: Datastore Source #

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

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

  • datCreationTime - When the data store was created.
  • datStatus - The status of a data store: * CREATING * The data store is being created. * ACTIVE * The data store has been created and can be used. * DELETING * The data store is being deleted.
  • datArn - The ARN of the data store.
  • datRetentionPeriod - How long, in days, message data is kept for the data store.
  • datName - The name of the data store.
  • datLastUpdateTime - The last time the data store was updated.

datCreationTime :: Lens' Datastore (Maybe UTCTime) Source #

When the data store was created.

datStatus :: Lens' Datastore (Maybe DatastoreStatus) Source #

The status of a data store: * CREATING * The data store is being created. * ACTIVE * The data store has been created and can be used. * DELETING * The data store is being deleted.

datArn :: Lens' Datastore (Maybe Text) Source #

The ARN of the data store.

datRetentionPeriod :: Lens' Datastore (Maybe RetentionPeriod) Source #

How long, in days, message data is kept for the data store.

datName :: Lens' Datastore (Maybe Text) Source #

The name of the data store.

datLastUpdateTime :: Lens' Datastore (Maybe UTCTime) Source #

The last time the data store was updated.

DatastoreActivity

data DatastoreActivity Source #

The datastore activity that specifies where to store the processed data.

See: datastoreActivity smart constructor.

Instances
Eq DatastoreActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data DatastoreActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: DatastoreActivity -> Constr #

dataTypeOf :: DatastoreActivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DatastoreActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show DatastoreActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic DatastoreActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep DatastoreActivity :: Type -> Type #

Hashable DatastoreActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON DatastoreActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON DatastoreActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData DatastoreActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: DatastoreActivity -> () #

type Rep DatastoreActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep DatastoreActivity = D1 (MetaData "DatastoreActivity" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "DatastoreActivity'" PrefixI True) (S1 (MetaSel (Just "_daName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_daDatastoreName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

datastoreActivity Source #

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

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

daName :: Lens' DatastoreActivity Text Source #

The name of the datastore activity.

daDatastoreName :: Lens' DatastoreActivity Text Source #

The name of the data store where processed messages are stored.

DatastoreSummary

data DatastoreSummary Source #

A summary of information about a data store.

See: datastoreSummary smart constructor.

Instances
Eq DatastoreSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data DatastoreSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: DatastoreSummary -> Constr #

dataTypeOf :: DatastoreSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DatastoreSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show DatastoreSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic DatastoreSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep DatastoreSummary :: Type -> Type #

Hashable DatastoreSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON DatastoreSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData DatastoreSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: DatastoreSummary -> () #

type Rep DatastoreSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep DatastoreSummary = D1 (MetaData "DatastoreSummary" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "DatastoreSummary'" PrefixI True) ((S1 (MetaSel (Just "_dsCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: S1 (MetaSel (Just "_dsStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DatastoreStatus))) :*: (S1 (MetaSel (Just "_dsDatastoreName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_dsLastUpdateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)))))

datastoreSummary :: DatastoreSummary Source #

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

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

dsCreationTime :: Lens' DatastoreSummary (Maybe UTCTime) Source #

When the data store was created.

dsStatus :: Lens' DatastoreSummary (Maybe DatastoreStatus) Source #

The status of the data store.

dsDatastoreName :: Lens' DatastoreSummary (Maybe Text) Source #

The name of the data store.

dsLastUpdateTime :: Lens' DatastoreSummary (Maybe UTCTime) Source #

The last time the data store was updated.

DeviceRegistryEnrichActivity

data DeviceRegistryEnrichActivity Source #

An activity that adds data from the AWS IoT device registry to your message.

See: deviceRegistryEnrichActivity smart constructor.

Instances
Eq DeviceRegistryEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data DeviceRegistryEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: DeviceRegistryEnrichActivity -> Constr #

dataTypeOf :: DeviceRegistryEnrichActivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DeviceRegistryEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show DeviceRegistryEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic DeviceRegistryEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep DeviceRegistryEnrichActivity :: Type -> Type #

Hashable DeviceRegistryEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON DeviceRegistryEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON DeviceRegistryEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData DeviceRegistryEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep DeviceRegistryEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep DeviceRegistryEnrichActivity = D1 (MetaData "DeviceRegistryEnrichActivity" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "DeviceRegistryEnrichActivity'" PrefixI True) ((S1 (MetaSel (Just "_dreaNext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_dreaName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "_dreaAttribute") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "_dreaThingName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_dreaRoleARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

deviceRegistryEnrichActivity Source #

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

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

  • dreaNext - The next activity in the pipeline.
  • dreaName - The name of the deviceRegistryEnrich activity.
  • dreaAttribute - The name of the attribute that is added to the message.
  • dreaThingName - The name of the IoT device whose registry information is added to the message.
  • dreaRoleARN - The ARN of the role that allows access to the device's registry information.

dreaNext :: Lens' DeviceRegistryEnrichActivity (Maybe Text) Source #

The next activity in the pipeline.

dreaName :: Lens' DeviceRegistryEnrichActivity Text Source #

The name of the deviceRegistryEnrich activity.

dreaAttribute :: Lens' DeviceRegistryEnrichActivity Text Source #

The name of the attribute that is added to the message.

dreaThingName :: Lens' DeviceRegistryEnrichActivity Text Source #

The name of the IoT device whose registry information is added to the message.

dreaRoleARN :: Lens' DeviceRegistryEnrichActivity Text Source #

The ARN of the role that allows access to the device's registry information.

DeviceShadowEnrichActivity

data DeviceShadowEnrichActivity Source #

An activity that adds information from the AWS IoT Device Shadows service to a message.

See: deviceShadowEnrichActivity smart constructor.

Instances
Eq DeviceShadowEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data DeviceShadowEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: DeviceShadowEnrichActivity -> Constr #

dataTypeOf :: DeviceShadowEnrichActivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DeviceShadowEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show DeviceShadowEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic DeviceShadowEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep DeviceShadowEnrichActivity :: Type -> Type #

Hashable DeviceShadowEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON DeviceShadowEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON DeviceShadowEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData DeviceShadowEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep DeviceShadowEnrichActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep DeviceShadowEnrichActivity = D1 (MetaData "DeviceShadowEnrichActivity" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "DeviceShadowEnrichActivity'" PrefixI True) ((S1 (MetaSel (Just "_dseaNext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_dseaName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "_dseaAttribute") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "_dseaThingName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_dseaRoleARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

deviceShadowEnrichActivity Source #

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

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

  • dseaNext - The next activity in the pipeline.
  • dseaName - The name of the deviceShadowEnrich activity.
  • dseaAttribute - The name of the attribute that is added to the message.
  • dseaThingName - The name of the IoT device whose shadow information is added to the message.
  • dseaRoleARN - The ARN of the role that allows access to the device's shadow.

dseaNext :: Lens' DeviceShadowEnrichActivity (Maybe Text) Source #

The next activity in the pipeline.

dseaName :: Lens' DeviceShadowEnrichActivity Text Source #

The name of the deviceShadowEnrich activity.

dseaAttribute :: Lens' DeviceShadowEnrichActivity Text Source #

The name of the attribute that is added to the message.

dseaThingName :: Lens' DeviceShadowEnrichActivity Text Source #

The name of the IoT device whose shadow information is added to the message.

dseaRoleARN :: Lens' DeviceShadowEnrichActivity Text Source #

The ARN of the role that allows access to the device's shadow.

FilterActivity

data FilterActivity Source #

An activity that filters a message based on its attributes.

See: filterActivity smart constructor.

Instances
Eq FilterActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data FilterActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: FilterActivity -> Constr #

dataTypeOf :: FilterActivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FilterActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show FilterActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic FilterActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep FilterActivity :: Type -> Type #

Hashable FilterActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON FilterActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON FilterActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData FilterActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: FilterActivity -> () #

type Rep FilterActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep FilterActivity = D1 (MetaData "FilterActivity" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "FilterActivity'" PrefixI True) (S1 (MetaSel (Just "_faNext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_faName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_faFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

filterActivity Source #

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

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

  • faNext - The next activity in the pipeline.
  • faName - The name of the filter activity.
  • faFilter - An expression that looks like an SQL WHERE clause that must return a Boolean value.

faNext :: Lens' FilterActivity (Maybe Text) Source #

The next activity in the pipeline.

faName :: Lens' FilterActivity Text Source #

The name of the filter activity.

faFilter :: Lens' FilterActivity Text Source #

An expression that looks like an SQL WHERE clause that must return a Boolean value.

LambdaActivity

data LambdaActivity Source #

An activity that runs a Lambda function to modify the message.

See: lambdaActivity smart constructor.

Instances
Eq LambdaActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data LambdaActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: LambdaActivity -> Constr #

dataTypeOf :: LambdaActivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LambdaActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show LambdaActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic LambdaActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep LambdaActivity :: Type -> Type #

Hashable LambdaActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON LambdaActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON LambdaActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData LambdaActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: LambdaActivity -> () #

type Rep LambdaActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep LambdaActivity = D1 (MetaData "LambdaActivity" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "LambdaActivity'" PrefixI True) ((S1 (MetaSel (Just "_laNext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_laName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "_laLambdaName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_laBatchSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Nat))))

lambdaActivity Source #

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

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

  • laNext - The next activity in the pipeline.
  • laName - The name of the lambda activity.
  • laLambdaName - The name of the Lambda function that is run on the message.
  • laBatchSize - The number of messages passed to the Lambda function for processing. The AWS Lambda function must be able to process all of these messages within five minutes, which is the maximum timeout duration for Lambda functions.

laNext :: Lens' LambdaActivity (Maybe Text) Source #

The next activity in the pipeline.

laName :: Lens' LambdaActivity Text Source #

The name of the lambda activity.

laLambdaName :: Lens' LambdaActivity Text Source #

The name of the Lambda function that is run on the message.

laBatchSize :: Lens' LambdaActivity Natural Source #

The number of messages passed to the Lambda function for processing. The AWS Lambda function must be able to process all of these messages within five minutes, which is the maximum timeout duration for Lambda functions.

LoggingOptions

data LoggingOptions Source #

Information about logging options.

See: loggingOptions smart constructor.

Instances
Eq LoggingOptions Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data LoggingOptions Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: LoggingOptions -> Constr #

dataTypeOf :: LoggingOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LoggingOptions Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show LoggingOptions Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic LoggingOptions Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep LoggingOptions :: Type -> Type #

Hashable LoggingOptions Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON LoggingOptions Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON LoggingOptions Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData LoggingOptions Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: LoggingOptions -> () #

type Rep LoggingOptions Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep LoggingOptions = D1 (MetaData "LoggingOptions" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "LoggingOptions'" PrefixI True) (S1 (MetaSel (Just "_loRoleARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "_loLevel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 LoggingLevel) :*: S1 (MetaSel (Just "_loEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))))

loggingOptions Source #

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

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

  • loRoleARN - The ARN of the role that grants permission to AWS IoT Analytics to perform logging.
  • loLevel - The logging level. Currently, only ERROR is supported.
  • loEnabled - If true, logging is enabled for AWS IoT Analytics.

loRoleARN :: Lens' LoggingOptions Text Source #

The ARN of the role that grants permission to AWS IoT Analytics to perform logging.

loLevel :: Lens' LoggingOptions LoggingLevel Source #

The logging level. Currently, only ERROR is supported.

loEnabled :: Lens' LoggingOptions Bool Source #

If true, logging is enabled for AWS IoT Analytics.

MathActivity

data MathActivity Source #

An activity that computes an arithmetic expression using the message's attributes.

See: mathActivity smart constructor.

Instances
Eq MathActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data MathActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: MathActivity -> Constr #

dataTypeOf :: MathActivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Read MathActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show MathActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic MathActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep MathActivity :: Type -> Type #

Hashable MathActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON MathActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON MathActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData MathActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: MathActivity -> () #

type Rep MathActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep MathActivity = D1 (MetaData "MathActivity" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "MathActivity'" PrefixI True) ((S1 (MetaSel (Just "_maNext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_maName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "_maAttribute") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_maMath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

mathActivity Source #

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

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

  • maNext - The next activity in the pipeline.
  • maName - The name of the math activity.
  • maAttribute - The name of the attribute that will contain the result of the math operation.
  • maMath - An expression that uses one or more existing attributes and must return an integer value.

maNext :: Lens' MathActivity (Maybe Text) Source #

The next activity in the pipeline.

maName :: Lens' MathActivity Text Source #

The name of the math activity.

maAttribute :: Lens' MathActivity Text Source #

The name of the attribute that will contain the result of the math operation.

maMath :: Lens' MathActivity Text Source #

An expression that uses one or more existing attributes and must return an integer value.

Message

data Message Source #

Information about a message.

See: message smart constructor.

Instances
Eq Message Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

Data Message Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: Message -> Constr #

dataTypeOf :: Message -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Message Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show Message Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic Message Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep Message :: Type -> Type #

Methods

from :: Message -> Rep Message x #

to :: Rep Message x -> Message #

Hashable Message Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

hashWithSalt :: Int -> Message -> Int #

hash :: Message -> Int #

ToJSON Message Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData Message Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: Message -> () #

type Rep Message Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep Message = D1 (MetaData "Message" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "Message'" PrefixI True) (S1 (MetaSel (Just "_mMessageId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_mPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Base64)))

message Source #

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

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

  • mMessageId - The ID you wish to assign to the message.
  • mPayload - The payload of the message.-- Note: This Lens automatically encodes and decodes Base64 data. The underlying isomorphism will encode to Base64 representation during serialisation, and decode from Base64 representation during deserialisation. This Lens accepts and returns only raw unencoded data.

mMessageId :: Lens' Message Text Source #

The ID you wish to assign to the message.

mPayload :: Lens' Message ByteString Source #

The payload of the message.-- Note: This Lens automatically encodes and decodes Base64 data. The underlying isomorphism will encode to Base64 representation during serialisation, and decode from Base64 representation during deserialisation. This Lens accepts and returns only raw unencoded data.

Pipeline

data Pipeline Source #

Contains information about a pipeline.

See: pipeline smart constructor.

Instances
Eq Pipeline Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data Pipeline Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: Pipeline -> Constr #

dataTypeOf :: Pipeline -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Pipeline Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show Pipeline Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic Pipeline Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep Pipeline :: Type -> Type #

Methods

from :: Pipeline -> Rep Pipeline x #

to :: Rep Pipeline x -> Pipeline #

Hashable Pipeline Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

hashWithSalt :: Int -> Pipeline -> Int #

hash :: Pipeline -> Int #

FromJSON Pipeline Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData Pipeline Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: Pipeline -> () #

type Rep Pipeline Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep Pipeline = D1 (MetaData "Pipeline" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "Pipeline'" PrefixI True) ((S1 (MetaSel (Just "_pCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: (S1 (MetaSel (Just "_pArn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pActivities") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (List1 PipelineActivity))))) :*: (S1 (MetaSel (Just "_pName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_pReprocessingSummaries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ReprocessingSummary])) :*: S1 (MetaSel (Just "_pLastUpdateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX))))))

pipeline :: Pipeline Source #

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

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

pCreationTime :: Lens' Pipeline (Maybe UTCTime) Source #

When the pipeline was created.

pArn :: Lens' Pipeline (Maybe Text) Source #

The ARN of the pipeline.

pActivities :: Lens' Pipeline (Maybe (NonEmpty PipelineActivity)) Source #

The activities that perform transformations on the messages.

pName :: Lens' Pipeline (Maybe Text) Source #

The name of the pipeline.

pReprocessingSummaries :: Lens' Pipeline [ReprocessingSummary] Source #

A summary of information about the pipeline reprocessing.

pLastUpdateTime :: Lens' Pipeline (Maybe UTCTime) Source #

The last time the pipeline was updated.

PipelineActivity

data PipelineActivity Source #

An activity that performs a transformation on a message.

See: pipelineActivity smart constructor.

Instances
Eq PipelineActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data PipelineActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: PipelineActivity -> Constr #

dataTypeOf :: PipelineActivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Read PipelineActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show PipelineActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic PipelineActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep PipelineActivity :: Type -> Type #

Hashable PipelineActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON PipelineActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON PipelineActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData PipelineActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: PipelineActivity -> () #

type Rep PipelineActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

pipelineActivity :: PipelineActivity Source #

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

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

  • paSelectAttributes - Creates a new message using only the specified attributes from the original message.
  • paChannel - Determines the source of the messages to be processed.
  • paAddAttributes - Adds other attributes based on existing attributes in the message.
  • paDeviceRegistryEnrich - Adds data from the AWS IoT device registry to your message.
  • paRemoveAttributes - Removes attributes from a message.
  • paLambda - Runs a Lambda function to modify the message.
  • paDatastore - Specifies where to store the processed message data.
  • paDeviceShadowEnrich - Adds information from the AWS IoT Device Shadows service to a message.
  • paFilter - Filters a message based on its attributes.
  • paMath - Computes an arithmetic expression using the message's attributes and adds it to the message.

paSelectAttributes :: Lens' PipelineActivity (Maybe SelectAttributesActivity) Source #

Creates a new message using only the specified attributes from the original message.

paChannel :: Lens' PipelineActivity (Maybe ChannelActivity) Source #

Determines the source of the messages to be processed.

paAddAttributes :: Lens' PipelineActivity (Maybe AddAttributesActivity) Source #

Adds other attributes based on existing attributes in the message.

paDeviceRegistryEnrich :: Lens' PipelineActivity (Maybe DeviceRegistryEnrichActivity) Source #

Adds data from the AWS IoT device registry to your message.

paLambda :: Lens' PipelineActivity (Maybe LambdaActivity) Source #

Runs a Lambda function to modify the message.

paDatastore :: Lens' PipelineActivity (Maybe DatastoreActivity) Source #

Specifies where to store the processed message data.

paDeviceShadowEnrich :: Lens' PipelineActivity (Maybe DeviceShadowEnrichActivity) Source #

Adds information from the AWS IoT Device Shadows service to a message.

paFilter :: Lens' PipelineActivity (Maybe FilterActivity) Source #

Filters a message based on its attributes.

paMath :: Lens' PipelineActivity (Maybe MathActivity) Source #

Computes an arithmetic expression using the message's attributes and adds it to the message.

PipelineSummary

data PipelineSummary Source #

A summary of information about a pipeline.

See: pipelineSummary smart constructor.

Instances
Eq PipelineSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data PipelineSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: PipelineSummary -> Constr #

dataTypeOf :: PipelineSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read PipelineSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show PipelineSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic PipelineSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep PipelineSummary :: Type -> Type #

Hashable PipelineSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON PipelineSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData PipelineSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: PipelineSummary -> () #

type Rep PipelineSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep PipelineSummary = D1 (MetaData "PipelineSummary" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "PipelineSummary'" PrefixI True) ((S1 (MetaSel (Just "_psCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: S1 (MetaSel (Just "_psPipelineName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_psReprocessingSummaries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ReprocessingSummary])) :*: S1 (MetaSel (Just "_psLastUpdateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)))))

pipelineSummary :: PipelineSummary Source #

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

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

psCreationTime :: Lens' PipelineSummary (Maybe UTCTime) Source #

When the pipeline was created.

psPipelineName :: Lens' PipelineSummary (Maybe Text) Source #

The name of the pipeline.

psReprocessingSummaries :: Lens' PipelineSummary [ReprocessingSummary] Source #

A summary of information about the pipeline reprocessing.

psLastUpdateTime :: Lens' PipelineSummary (Maybe UTCTime) Source #

When the pipeline was last updated.

RemoveAttributesActivity

data RemoveAttributesActivity Source #

An activity that removes attributes from a message.

See: removeAttributesActivity smart constructor.

Instances
Eq RemoveAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data RemoveAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: RemoveAttributesActivity -> Constr #

dataTypeOf :: RemoveAttributesActivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RemoveAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show RemoveAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic RemoveAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep RemoveAttributesActivity :: Type -> Type #

Hashable RemoveAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON RemoveAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON RemoveAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData RemoveAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep RemoveAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep RemoveAttributesActivity = D1 (MetaData "RemoveAttributesActivity" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "RemoveAttributesActivity'" PrefixI True) (S1 (MetaSel (Just "_raaNext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_raaName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_raaAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (List1 Text)))))

removeAttributesActivity Source #

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

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

  • raaNext - The next activity in the pipeline.
  • raaName - The name of the removeAttributes activity.
  • raaAttributes - A list of 1-50 attributes to remove from the message.

raaNext :: Lens' RemoveAttributesActivity (Maybe Text) Source #

The next activity in the pipeline.

raaName :: Lens' RemoveAttributesActivity Text Source #

The name of the removeAttributes activity.

raaAttributes :: Lens' RemoveAttributesActivity (NonEmpty Text) Source #

A list of 1-50 attributes to remove from the message.

ReprocessingSummary

data ReprocessingSummary Source #

Information about pipeline reprocessing.

See: reprocessingSummary smart constructor.

Instances
Eq ReprocessingSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data ReprocessingSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: ReprocessingSummary -> Constr #

dataTypeOf :: ReprocessingSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ReprocessingSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show ReprocessingSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic ReprocessingSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep ReprocessingSummary :: Type -> Type #

Hashable ReprocessingSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON ReprocessingSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData ReprocessingSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: ReprocessingSummary -> () #

type Rep ReprocessingSummary Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep ReprocessingSummary = D1 (MetaData "ReprocessingSummary" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "ReprocessingSummary'" PrefixI True) (S1 (MetaSel (Just "_rsCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: (S1 (MetaSel (Just "_rsStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReprocessingStatus)) :*: S1 (MetaSel (Just "_rsId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

reprocessingSummary :: ReprocessingSummary Source #

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

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

rsCreationTime :: Lens' ReprocessingSummary (Maybe UTCTime) Source #

The time the pipeline reprocessing was created.

rsStatus :: Lens' ReprocessingSummary (Maybe ReprocessingStatus) Source #

The status of the pipeline reprocessing.

RetentionPeriod

data RetentionPeriod Source #

How long, in days, message data is kept.

See: retentionPeriod smart constructor.

Instances
Eq RetentionPeriod Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data RetentionPeriod Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: RetentionPeriod -> Constr #

dataTypeOf :: RetentionPeriod -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RetentionPeriod Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show RetentionPeriod Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic RetentionPeriod Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep RetentionPeriod :: Type -> Type #

Hashable RetentionPeriod Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON RetentionPeriod Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON RetentionPeriod Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData RetentionPeriod Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: RetentionPeriod -> () #

type Rep RetentionPeriod Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep RetentionPeriod = D1 (MetaData "RetentionPeriod" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "RetentionPeriod'" PrefixI True) (S1 (MetaSel (Just "_rpUnlimited") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "_rpNumberOfDays") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))))

retentionPeriod :: RetentionPeriod Source #

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

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

  • rpUnlimited - If true, message data is kept indefinitely.
  • rpNumberOfDays - The number of days that message data is kept. The "unlimited" parameter must be false.

rpUnlimited :: Lens' RetentionPeriod (Maybe Bool) Source #

If true, message data is kept indefinitely.

rpNumberOfDays :: Lens' RetentionPeriod (Maybe Natural) Source #

The number of days that message data is kept. The "unlimited" parameter must be false.

Schedule

data Schedule Source #

The schedule for when to trigger an update.

See: schedule smart constructor.

Instances
Eq Schedule Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data Schedule Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: Schedule -> Constr #

dataTypeOf :: Schedule -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Schedule Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show Schedule Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic Schedule Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep Schedule :: Type -> Type #

Methods

from :: Schedule -> Rep Schedule x #

to :: Rep Schedule x -> Schedule #

Hashable Schedule Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

hashWithSalt :: Int -> Schedule -> Int #

hash :: Schedule -> Int #

ToJSON Schedule Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON Schedule Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData Schedule Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: Schedule -> () #

type Rep Schedule Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep Schedule = D1 (MetaData "Schedule" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" True) (C1 (MetaCons "Schedule'" PrefixI True) (S1 (MetaSel (Just "_sExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

schedule :: Schedule Source #

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

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

sExpression :: Lens' Schedule (Maybe Text) Source #

The expression that defines when to trigger an update. For more information, see Schedule Expressions for Rules in the Amazon CloudWatch documentation.

SelectAttributesActivity

data SelectAttributesActivity Source #

Creates a new message using only the specified attributes from the original message.

See: selectAttributesActivity smart constructor.

Instances
Eq SelectAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data SelectAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: SelectAttributesActivity -> Constr #

dataTypeOf :: SelectAttributesActivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SelectAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show SelectAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic SelectAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep SelectAttributesActivity :: Type -> Type #

Hashable SelectAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON SelectAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON SelectAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData SelectAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep SelectAttributesActivity Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep SelectAttributesActivity = D1 (MetaData "SelectAttributesActivity" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" False) (C1 (MetaCons "SelectAttributesActivity'" PrefixI True) (S1 (MetaSel (Just "_saaNext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_saaName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_saaAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (List1 Text)))))

selectAttributesActivity Source #

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

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

  • saaNext - The next activity in the pipeline.
  • saaName - The name of the selectAttributes activity.
  • saaAttributes - A list of the attributes to select from the message.

saaNext :: Lens' SelectAttributesActivity (Maybe Text) Source #

The next activity in the pipeline.

saaName :: Lens' SelectAttributesActivity Text Source #

The name of the selectAttributes activity.

saaAttributes :: Lens' SelectAttributesActivity (NonEmpty Text) Source #

A list of the attributes to select from the message.

SqlQueryDatasetAction

data SqlQueryDatasetAction Source #

The SQL query to modify the message.

See: sqlQueryDatasetAction smart constructor.

Instances
Eq SqlQueryDatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Data SqlQueryDatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

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

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

toConstr :: SqlQueryDatasetAction -> Constr #

dataTypeOf :: SqlQueryDatasetAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SqlQueryDatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Show SqlQueryDatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Generic SqlQueryDatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Associated Types

type Rep SqlQueryDatasetAction :: Type -> Type #

Hashable SqlQueryDatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

ToJSON SqlQueryDatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

FromJSON SqlQueryDatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

NFData SqlQueryDatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

Methods

rnf :: SqlQueryDatasetAction -> () #

type Rep SqlQueryDatasetAction Source # 
Instance details

Defined in Network.AWS.IoTAnalytics.Types.Product

type Rep SqlQueryDatasetAction = D1 (MetaData "SqlQueryDatasetAction" "Network.AWS.IoTAnalytics.Types.Product" "amazonka-iot-analytics-1.6.1-II7URRwPIs5C2HKxTKtgRZ" True) (C1 (MetaCons "SqlQueryDatasetAction'" PrefixI True) (S1 (MetaSel (Just "_sqdaSqlQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

sqlQueryDatasetAction Source #

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

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