{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Network.AWS.Lambda.PublishVersion
(
publishVersion
, PublishVersion
, pvCodeSha256
, pvDescription
, pvFunctionName
, functionConfiguration
, FunctionConfiguration
, fcMemorySize
, fcRuntime
, fcFunctionARN
, fcRole
, fcVPCConfig
, fcVersion
, fcFunctionName
, fcCodeSize
, fcHandler
, fcTimeout
, fcLastModified
, fcCodeSha256
, fcDescription
) where
import Network.AWS.Lambda.Types
import Network.AWS.Lambda.Types.Product
import Network.AWS.Lens
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
data PublishVersion = PublishVersion'
{ _pvCodeSha256 :: !(Maybe Text)
, _pvDescription :: !(Maybe Text)
, _pvFunctionName :: !Text
} deriving (Eq,Read,Show,Data,Typeable,Generic)
publishVersion
:: Text
-> PublishVersion
publishVersion pFunctionName_ =
PublishVersion'
{ _pvCodeSha256 = Nothing
, _pvDescription = Nothing
, _pvFunctionName = pFunctionName_
}
pvCodeSha256 :: Lens' PublishVersion (Maybe Text)
pvCodeSha256 = lens _pvCodeSha256 (\ s a -> s{_pvCodeSha256 = a});
pvDescription :: Lens' PublishVersion (Maybe Text)
pvDescription = lens _pvDescription (\ s a -> s{_pvDescription = a});
pvFunctionName :: Lens' PublishVersion Text
pvFunctionName = lens _pvFunctionName (\ s a -> s{_pvFunctionName = a});
instance AWSRequest PublishVersion where
type Rs PublishVersion = FunctionConfiguration
request = postJSON lambda
response = receiveJSON (\ s h x -> eitherParseJSON x)
instance Hashable PublishVersion
instance NFData PublishVersion
instance ToHeaders PublishVersion where
toHeaders = const mempty
instance ToJSON PublishVersion where
toJSON PublishVersion'{..}
= object
(catMaybes
[("CodeSha256" .=) <$> _pvCodeSha256,
("Description" .=) <$> _pvDescription])
instance ToPath PublishVersion where
toPath PublishVersion'{..}
= mconcat
["/2015-03-31/functions/", toBS _pvFunctionName,
"/versions"]
instance ToQuery PublishVersion where
toQuery = const mempty