{-# 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.Mobile.ExportBundle
(
exportBundle
, ExportBundle
, ebPlatform
, ebProjectId
, ebBundleId
, exportBundleResponse
, ExportBundleResponse
, ebrsDownloadURL
, ebrsResponseStatus
) where
import Network.AWS.Lens
import Network.AWS.Mobile.Types
import Network.AWS.Mobile.Types.Product
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
data ExportBundle = ExportBundle'
{ _ebPlatform :: !(Maybe Platform)
, _ebProjectId :: !(Maybe Text)
, _ebBundleId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
exportBundle
:: Text
-> ExportBundle
exportBundle pBundleId_ =
ExportBundle'
{_ebPlatform = Nothing, _ebProjectId = Nothing, _ebBundleId = pBundleId_}
ebPlatform :: Lens' ExportBundle (Maybe Platform)
ebPlatform = lens _ebPlatform (\ s a -> s{_ebPlatform = a})
ebProjectId :: Lens' ExportBundle (Maybe Text)
ebProjectId = lens _ebProjectId (\ s a -> s{_ebProjectId = a})
ebBundleId :: Lens' ExportBundle Text
ebBundleId = lens _ebBundleId (\ s a -> s{_ebBundleId = a})
instance AWSRequest ExportBundle where
type Rs ExportBundle = ExportBundleResponse
request = postJSON mobile
response
= receiveJSON
(\ s h x ->
ExportBundleResponse' <$>
(x .?> "downloadUrl") <*> (pure (fromEnum s)))
instance Hashable ExportBundle where
instance NFData ExportBundle where
instance ToHeaders ExportBundle where
toHeaders
= const
(mconcat
["Content-Type" =#
("application/x-amz-json-1.1" :: ByteString)])
instance ToJSON ExportBundle where
toJSON = const (Object mempty)
instance ToPath ExportBundle where
toPath ExportBundle'{..}
= mconcat ["/bundles/", toBS _ebBundleId]
instance ToQuery ExportBundle where
toQuery ExportBundle'{..}
= mconcat
["platform" =: _ebPlatform,
"projectId" =: _ebProjectId]
data ExportBundleResponse = ExportBundleResponse'
{ _ebrsDownloadURL :: !(Maybe Text)
, _ebrsResponseStatus :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
exportBundleResponse
:: Int
-> ExportBundleResponse
exportBundleResponse pResponseStatus_ =
ExportBundleResponse'
{_ebrsDownloadURL = Nothing, _ebrsResponseStatus = pResponseStatus_}
ebrsDownloadURL :: Lens' ExportBundleResponse (Maybe Text)
ebrsDownloadURL = lens _ebrsDownloadURL (\ s a -> s{_ebrsDownloadURL = a})
ebrsResponseStatus :: Lens' ExportBundleResponse Int
ebrsResponseStatus = lens _ebrsResponseStatus (\ s a -> s{_ebrsResponseStatus = a})
instance NFData ExportBundleResponse where