{-# 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.S3.ListObjects
    (
    
      listObjects
    , ListObjects
    
    , loPrefix
    , loEncodingType
    , loRequestPayer
    , loMarker
    , loMaxKeys
    , loDelimiter
    , loBucket
    
    , listObjectsResponse
    , ListObjectsResponse
    
    , lorsContents
    , lorsPrefix
    , lorsCommonPrefixes
    , lorsEncodingType
    , lorsName
    , lorsMarker
    , lorsNextMarker
    , lorsMaxKeys
    , lorsIsTruncated
    , lorsDelimiter
    , lorsResponseStatus
    ) where
import Network.AWS.Lens
import Network.AWS.Pager
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
import Network.AWS.S3.Types
import Network.AWS.S3.Types.Product
data ListObjects = ListObjects'
  { _loPrefix       :: !(Maybe Text)
  , _loEncodingType :: !(Maybe EncodingType)
  , _loRequestPayer :: !(Maybe RequestPayer)
  , _loMarker       :: !(Maybe Text)
  , _loMaxKeys      :: !(Maybe Int)
  , _loDelimiter    :: !(Maybe Delimiter)
  , _loBucket       :: !BucketName
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
listObjects
    :: BucketName 
    -> ListObjects
listObjects pBucket_ =
  ListObjects'
    { _loPrefix = Nothing
    , _loEncodingType = Nothing
    , _loRequestPayer = Nothing
    , _loMarker = Nothing
    , _loMaxKeys = Nothing
    , _loDelimiter = Nothing
    , _loBucket = pBucket_
    }
loPrefix :: Lens' ListObjects (Maybe Text)
loPrefix = lens _loPrefix (\ s a -> s{_loPrefix = a})
loEncodingType :: Lens' ListObjects (Maybe EncodingType)
loEncodingType = lens _loEncodingType (\ s a -> s{_loEncodingType = a})
loRequestPayer :: Lens' ListObjects (Maybe RequestPayer)
loRequestPayer = lens _loRequestPayer (\ s a -> s{_loRequestPayer = a})
loMarker :: Lens' ListObjects (Maybe Text)
loMarker = lens _loMarker (\ s a -> s{_loMarker = a})
loMaxKeys :: Lens' ListObjects (Maybe Int)
loMaxKeys = lens _loMaxKeys (\ s a -> s{_loMaxKeys = a})
loDelimiter :: Lens' ListObjects (Maybe Delimiter)
loDelimiter = lens _loDelimiter (\ s a -> s{_loDelimiter = a})
loBucket :: Lens' ListObjects BucketName
loBucket = lens _loBucket (\ s a -> s{_loBucket = a})
instance AWSPager ListObjects where
        page rq rs
          | stop (rs ^. lorsIsTruncated) = Nothing
          | isNothing
              (rs ^.
                 choice (^. lorsNextMarker)
                   (^? (lorsContents . _last . oKey)))
            = Nothing
          | otherwise =
            Just $ rq &
              loMarker .~
                rs ^.
                  choice (^. lorsNextMarker)
                    (^? (lorsContents . _last . oKey))
instance AWSRequest ListObjects where
        type Rs ListObjects = ListObjectsResponse
        request = get s3
        response
          = receiveXML
              (\ s h x ->
                 ListObjectsResponse' <$>
                   (may (parseXMLList "Contents") x) <*>
                     (x .@? "Prefix")
                     <*> (may (parseXMLList "CommonPrefixes") x)
                     <*> (x .@? "EncodingType")
                     <*> (x .@? "Name")
                     <*> (x .@? "Marker")
                     <*> (x .@? "NextMarker")
                     <*> (x .@? "MaxKeys")
                     <*> (x .@? "IsTruncated")
                     <*> (x .@? "Delimiter")
                     <*> (pure (fromEnum s)))
instance Hashable ListObjects where
instance NFData ListObjects where
instance ToHeaders ListObjects where
        toHeaders ListObjects'{..}
          = mconcat ["x-amz-request-payer" =# _loRequestPayer]
instance ToPath ListObjects where
        toPath ListObjects'{..}
          = mconcat ["/", toBS _loBucket]
instance ToQuery ListObjects where
        toQuery ListObjects'{..}
          = mconcat
              ["prefix" =: _loPrefix,
               "encoding-type" =: _loEncodingType,
               "marker" =: _loMarker, "max-keys" =: _loMaxKeys,
               "delimiter" =: _loDelimiter]
data ListObjectsResponse = ListObjectsResponse'
  { _lorsContents       :: !(Maybe [Object])
  , _lorsPrefix         :: !(Maybe Text)
  , _lorsCommonPrefixes :: !(Maybe [CommonPrefix])
  , _lorsEncodingType   :: !(Maybe EncodingType)
  , _lorsName           :: !(Maybe BucketName)
  , _lorsMarker         :: !(Maybe Text)
  , _lorsNextMarker     :: !(Maybe Text)
  , _lorsMaxKeys        :: !(Maybe Int)
  , _lorsIsTruncated    :: !(Maybe Bool)
  , _lorsDelimiter      :: !(Maybe Delimiter)
  , _lorsResponseStatus :: !Int
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
listObjectsResponse
    :: Int 
    -> ListObjectsResponse
listObjectsResponse pResponseStatus_ =
  ListObjectsResponse'
    { _lorsContents = Nothing
    , _lorsPrefix = Nothing
    , _lorsCommonPrefixes = Nothing
    , _lorsEncodingType = Nothing
    , _lorsName = Nothing
    , _lorsMarker = Nothing
    , _lorsNextMarker = Nothing
    , _lorsMaxKeys = Nothing
    , _lorsIsTruncated = Nothing
    , _lorsDelimiter = Nothing
    , _lorsResponseStatus = pResponseStatus_
    }
lorsContents :: Lens' ListObjectsResponse [Object]
lorsContents = lens _lorsContents (\ s a -> s{_lorsContents = a}) . _Default . _Coerce
lorsPrefix :: Lens' ListObjectsResponse (Maybe Text)
lorsPrefix = lens _lorsPrefix (\ s a -> s{_lorsPrefix = a})
lorsCommonPrefixes :: Lens' ListObjectsResponse [CommonPrefix]
lorsCommonPrefixes = lens _lorsCommonPrefixes (\ s a -> s{_lorsCommonPrefixes = a}) . _Default . _Coerce
lorsEncodingType :: Lens' ListObjectsResponse (Maybe EncodingType)
lorsEncodingType = lens _lorsEncodingType (\ s a -> s{_lorsEncodingType = a})
lorsName :: Lens' ListObjectsResponse (Maybe BucketName)
lorsName = lens _lorsName (\ s a -> s{_lorsName = a})
lorsMarker :: Lens' ListObjectsResponse (Maybe Text)
lorsMarker = lens _lorsMarker (\ s a -> s{_lorsMarker = a})
lorsNextMarker :: Lens' ListObjectsResponse (Maybe Text)
lorsNextMarker = lens _lorsNextMarker (\ s a -> s{_lorsNextMarker = a})
lorsMaxKeys :: Lens' ListObjectsResponse (Maybe Int)
lorsMaxKeys = lens _lorsMaxKeys (\ s a -> s{_lorsMaxKeys = a})
lorsIsTruncated :: Lens' ListObjectsResponse (Maybe Bool)
lorsIsTruncated = lens _lorsIsTruncated (\ s a -> s{_lorsIsTruncated = a})
lorsDelimiter :: Lens' ListObjectsResponse (Maybe Delimiter)
lorsDelimiter = lens _lorsDelimiter (\ s a -> s{_lorsDelimiter = a})
lorsResponseStatus :: Lens' ListObjectsResponse Int
lorsResponseStatus = lens _lorsResponseStatus (\ s a -> s{_lorsResponseStatus = a})
instance NFData ListObjectsResponse where