module Network.AWS.Lambda.Types.Product where
import Network.AWS.Lambda.Types.Sum
import Network.AWS.Prelude
data EventSourceMappingConfiguration = EventSourceMappingConfiguration'
{ _esmcEventSourceARN :: !(Maybe Text)
, _esmcFunctionARN :: !(Maybe Text)
, _esmcState :: !(Maybe Text)
, _esmcUUId :: !(Maybe Text)
, _esmcLastProcessingResult :: !(Maybe Text)
, _esmcBatchSize :: !(Maybe Nat)
, _esmcStateTransitionReason :: !(Maybe Text)
, _esmcLastModified :: !(Maybe POSIX)
} deriving (Eq,Read,Show,Data,Typeable,Generic)
eventSourceMappingConfiguration
:: EventSourceMappingConfiguration
eventSourceMappingConfiguration =
EventSourceMappingConfiguration'
{ _esmcEventSourceARN = Nothing
, _esmcFunctionARN = Nothing
, _esmcState = Nothing
, _esmcUUId = Nothing
, _esmcLastProcessingResult = Nothing
, _esmcBatchSize = Nothing
, _esmcStateTransitionReason = Nothing
, _esmcLastModified = Nothing
}
esmcEventSourceARN :: Lens' EventSourceMappingConfiguration (Maybe Text)
esmcEventSourceARN = lens _esmcEventSourceARN (\ s a -> s{_esmcEventSourceARN = a});
esmcFunctionARN :: Lens' EventSourceMappingConfiguration (Maybe Text)
esmcFunctionARN = lens _esmcFunctionARN (\ s a -> s{_esmcFunctionARN = a});
esmcState :: Lens' EventSourceMappingConfiguration (Maybe Text)
esmcState = lens _esmcState (\ s a -> s{_esmcState = a});
esmcUUId :: Lens' EventSourceMappingConfiguration (Maybe Text)
esmcUUId = lens _esmcUUId (\ s a -> s{_esmcUUId = a});
esmcLastProcessingResult :: Lens' EventSourceMappingConfiguration (Maybe Text)
esmcLastProcessingResult = lens _esmcLastProcessingResult (\ s a -> s{_esmcLastProcessingResult = a});
esmcBatchSize :: Lens' EventSourceMappingConfiguration (Maybe Natural)
esmcBatchSize = lens _esmcBatchSize (\ s a -> s{_esmcBatchSize = a}) . mapping _Nat;
esmcStateTransitionReason :: Lens' EventSourceMappingConfiguration (Maybe Text)
esmcStateTransitionReason = lens _esmcStateTransitionReason (\ s a -> s{_esmcStateTransitionReason = a});
esmcLastModified :: Lens' EventSourceMappingConfiguration (Maybe UTCTime)
esmcLastModified = lens _esmcLastModified (\ s a -> s{_esmcLastModified = a}) . mapping _Time;
instance FromJSON EventSourceMappingConfiguration
where
parseJSON
= withObject "EventSourceMappingConfiguration"
(\ x ->
EventSourceMappingConfiguration' <$>
(x .:? "EventSourceArn") <*> (x .:? "FunctionArn")
<*> (x .:? "State")
<*> (x .:? "UUID")
<*> (x .:? "LastProcessingResult")
<*> (x .:? "BatchSize")
<*> (x .:? "StateTransitionReason")
<*> (x .:? "LastModified"))
data FunctionCode = FunctionCode'
{ _fcS3ObjectVersion :: !(Maybe Text)
, _fcS3Key :: !(Maybe Text)
, _fcZipFile :: !(Maybe Base64)
, _fcS3Bucket :: !(Maybe Text)
} deriving (Eq,Read,Show,Data,Typeable,Generic)
functionCode
:: FunctionCode
functionCode =
FunctionCode'
{ _fcS3ObjectVersion = Nothing
, _fcS3Key = Nothing
, _fcZipFile = Nothing
, _fcS3Bucket = Nothing
}
fcS3ObjectVersion :: Lens' FunctionCode (Maybe Text)
fcS3ObjectVersion = lens _fcS3ObjectVersion (\ s a -> s{_fcS3ObjectVersion = a});
fcS3Key :: Lens' FunctionCode (Maybe Text)
fcS3Key = lens _fcS3Key (\ s a -> s{_fcS3Key = a});
fcZipFile :: Lens' FunctionCode (Maybe ByteString)
fcZipFile = lens _fcZipFile (\ s a -> s{_fcZipFile = a}) . mapping _Base64;
fcS3Bucket :: Lens' FunctionCode (Maybe Text)
fcS3Bucket = lens _fcS3Bucket (\ s a -> s{_fcS3Bucket = a});
instance ToJSON FunctionCode where
toJSON FunctionCode'{..}
= object
["S3ObjectVersion" .= _fcS3ObjectVersion,
"S3Key" .= _fcS3Key, "ZipFile" .= _fcZipFile,
"S3Bucket" .= _fcS3Bucket]
data FunctionCodeLocation = FunctionCodeLocation'
{ _fclLocation :: !(Maybe Text)
, _fclRepositoryType :: !(Maybe Text)
} deriving (Eq,Read,Show,Data,Typeable,Generic)
functionCodeLocation
:: FunctionCodeLocation
functionCodeLocation =
FunctionCodeLocation'
{ _fclLocation = Nothing
, _fclRepositoryType = Nothing
}
fclLocation :: Lens' FunctionCodeLocation (Maybe Text)
fclLocation = lens _fclLocation (\ s a -> s{_fclLocation = a});
fclRepositoryType :: Lens' FunctionCodeLocation (Maybe Text)
fclRepositoryType = lens _fclRepositoryType (\ s a -> s{_fclRepositoryType = a});
instance FromJSON FunctionCodeLocation where
parseJSON
= withObject "FunctionCodeLocation"
(\ x ->
FunctionCodeLocation' <$>
(x .:? "Location") <*> (x .:? "RepositoryType"))
data FunctionConfiguration = FunctionConfiguration'
{ _fcRuntime :: !(Maybe Runtime)
, _fcMemorySize :: !(Maybe Nat)
, _fcFunctionARN :: !(Maybe Text)
, _fcRole :: !(Maybe Text)
, _fcFunctionName :: !(Maybe Text)
, _fcCodeSize :: !(Maybe Integer)
, _fcHandler :: !(Maybe Text)
, _fcTimeout :: !(Maybe Nat)
, _fcLastModified :: !(Maybe Text)
, _fcDescription :: !(Maybe Text)
} deriving (Eq,Read,Show,Data,Typeable,Generic)
functionConfiguration
:: FunctionConfiguration
functionConfiguration =
FunctionConfiguration'
{ _fcRuntime = Nothing
, _fcMemorySize = Nothing
, _fcFunctionARN = Nothing
, _fcRole = Nothing
, _fcFunctionName = Nothing
, _fcCodeSize = Nothing
, _fcHandler = Nothing
, _fcTimeout = Nothing
, _fcLastModified = Nothing
, _fcDescription = Nothing
}
fcRuntime :: Lens' FunctionConfiguration (Maybe Runtime)
fcRuntime = lens _fcRuntime (\ s a -> s{_fcRuntime = a});
fcMemorySize :: Lens' FunctionConfiguration (Maybe Natural)
fcMemorySize = lens _fcMemorySize (\ s a -> s{_fcMemorySize = a}) . mapping _Nat;
fcFunctionARN :: Lens' FunctionConfiguration (Maybe Text)
fcFunctionARN = lens _fcFunctionARN (\ s a -> s{_fcFunctionARN = a});
fcRole :: Lens' FunctionConfiguration (Maybe Text)
fcRole = lens _fcRole (\ s a -> s{_fcRole = a});
fcFunctionName :: Lens' FunctionConfiguration (Maybe Text)
fcFunctionName = lens _fcFunctionName (\ s a -> s{_fcFunctionName = a});
fcCodeSize :: Lens' FunctionConfiguration (Maybe Integer)
fcCodeSize = lens _fcCodeSize (\ s a -> s{_fcCodeSize = a});
fcHandler :: Lens' FunctionConfiguration (Maybe Text)
fcHandler = lens _fcHandler (\ s a -> s{_fcHandler = a});
fcTimeout :: Lens' FunctionConfiguration (Maybe Natural)
fcTimeout = lens _fcTimeout (\ s a -> s{_fcTimeout = a}) . mapping _Nat;
fcLastModified :: Lens' FunctionConfiguration (Maybe Text)
fcLastModified = lens _fcLastModified (\ s a -> s{_fcLastModified = a});
fcDescription :: Lens' FunctionConfiguration (Maybe Text)
fcDescription = lens _fcDescription (\ s a -> s{_fcDescription = a});
instance FromJSON FunctionConfiguration where
parseJSON
= withObject "FunctionConfiguration"
(\ x ->
FunctionConfiguration' <$>
(x .:? "Runtime") <*> (x .:? "MemorySize") <*>
(x .:? "FunctionArn")
<*> (x .:? "Role")
<*> (x .:? "FunctionName")
<*> (x .:? "CodeSize")
<*> (x .:? "Handler")
<*> (x .:? "Timeout")
<*> (x .:? "LastModified")
<*> (x .:? "Description"))