module Network.AWS.S3.GetObject
    (
    
      GetObject
    
    , getObject
    
    , goBucket
    , goIfMatch
    , goIfModifiedSince
    , goIfNoneMatch
    , goIfUnmodifiedSince
    , goKey
    , goRange
    , goResponseCacheControl
    , goResponseContentDisposition
    , goResponseContentEncoding
    , goResponseContentLanguage
    , goResponseContentType
    , goResponseExpires
    , goSSECustomerAlgorithm
    , goSSECustomerKey
    , goSSECustomerKeyMD5
    , goSSEKMSKeyId
    , goVersionId
    
    , GetObjectResponse
    
    , getObjectResponse
    
    , gorAcceptRanges
    , gorBody
    , gorCacheControl
    , gorContentDisposition
    , gorContentEncoding
    , gorContentLanguage
    , gorContentLength
    , gorContentType
    , gorDeleteMarker
    , gorETag
    , gorExpiration
    , gorExpires
    , gorLastModified
    , gorMetadata
    , gorMissingMeta
    , gorRestore
    , gorSSECustomerAlgorithm
    , gorSSECustomerKeyMD5
    , gorSSEKMSKeyId
    , gorServerSideEncryption
    , gorVersionId
    , gorWebsiteRedirectLocation
    ) where
import Network.AWS.Prelude
import Network.AWS.Request.S3
import Network.AWS.S3.Types
import qualified GHC.Exts
data GetObject = GetObject
    { _goBucket                     :: Text
    , _goIfMatch                    :: Maybe Text
    , _goIfModifiedSince            :: Maybe RFC822
    , _goIfNoneMatch                :: Maybe Text
    , _goIfUnmodifiedSince          :: Maybe RFC822
    , _goKey                        :: Text
    , _goRange                      :: Maybe Text
    , _goResponseCacheControl       :: Maybe Text
    , _goResponseContentDisposition :: Maybe Text
    , _goResponseContentEncoding    :: Maybe Text
    , _goResponseContentLanguage    :: Maybe Text
    , _goResponseContentType        :: Maybe Text
    , _goResponseExpires            :: Maybe RFC822
    , _goSSECustomerAlgorithm       :: Maybe Text
    , _goSSECustomerKey             :: Maybe (Sensitive Text)
    , _goSSECustomerKeyMD5          :: Maybe Text
    , _goSSEKMSKeyId                :: Maybe (Sensitive Text)
    , _goVersionId                  :: Maybe Text
    } deriving (Eq, Ord, Show)
getObject :: Text 
          -> Text 
          -> GetObject
getObject p1 p2 = GetObject
    { _goBucket                     = p1
    , _goKey                        = p2
    , _goIfMatch                    = Nothing
    , _goIfModifiedSince            = Nothing
    , _goIfNoneMatch                = Nothing
    , _goIfUnmodifiedSince          = Nothing
    , _goRange                      = Nothing
    , _goResponseCacheControl       = Nothing
    , _goResponseContentDisposition = Nothing
    , _goResponseContentEncoding    = Nothing
    , _goResponseContentLanguage    = Nothing
    , _goResponseContentType        = Nothing
    , _goResponseExpires            = Nothing
    , _goVersionId                  = Nothing
    , _goSSECustomerAlgorithm       = Nothing
    , _goSSECustomerKey             = Nothing
    , _goSSECustomerKeyMD5          = Nothing
    , _goSSEKMSKeyId                = Nothing
    }
goBucket :: Lens' GetObject Text
goBucket = lens _goBucket (\s a -> s { _goBucket = a })
goIfMatch :: Lens' GetObject (Maybe Text)
goIfMatch = lens _goIfMatch (\s a -> s { _goIfMatch = a })
goIfModifiedSince :: Lens' GetObject (Maybe UTCTime)
goIfModifiedSince =
    lens _goIfModifiedSince (\s a -> s { _goIfModifiedSince = a })
        . mapping _Time
goIfNoneMatch :: Lens' GetObject (Maybe Text)
goIfNoneMatch = lens _goIfNoneMatch (\s a -> s { _goIfNoneMatch = a })
goIfUnmodifiedSince :: Lens' GetObject (Maybe UTCTime)
goIfUnmodifiedSince =
    lens _goIfUnmodifiedSince (\s a -> s { _goIfUnmodifiedSince = a })
        . mapping _Time
goKey :: Lens' GetObject Text
goKey = lens _goKey (\s a -> s { _goKey = a })
goRange :: Lens' GetObject (Maybe Text)
goRange = lens _goRange (\s a -> s { _goRange = a })
goResponseCacheControl :: Lens' GetObject (Maybe Text)
goResponseCacheControl =
    lens _goResponseCacheControl (\s a -> s { _goResponseCacheControl = a })
goResponseContentDisposition :: Lens' GetObject (Maybe Text)
goResponseContentDisposition =
    lens _goResponseContentDisposition
        (\s a -> s { _goResponseContentDisposition = a })
goResponseContentEncoding :: Lens' GetObject (Maybe Text)
goResponseContentEncoding =
    lens _goResponseContentEncoding
        (\s a -> s { _goResponseContentEncoding = a })
goResponseContentLanguage :: Lens' GetObject (Maybe Text)
goResponseContentLanguage =
    lens _goResponseContentLanguage
        (\s a -> s { _goResponseContentLanguage = a })
goResponseContentType :: Lens' GetObject (Maybe Text)
goResponseContentType =
    lens _goResponseContentType (\s a -> s { _goResponseContentType = a })
goResponseExpires :: Lens' GetObject (Maybe UTCTime)
goResponseExpires =
    lens _goResponseExpires (\s a -> s { _goResponseExpires = a })
        . mapping _Time
goSSECustomerAlgorithm :: Lens' GetObject (Maybe Text)
goSSECustomerAlgorithm =
    lens _goSSECustomerAlgorithm (\s a -> s { _goSSECustomerAlgorithm = a })
goSSECustomerKey :: Lens' GetObject (Maybe Text)
goSSECustomerKey = lens _goSSECustomerKey (\s a -> s { _goSSECustomerKey = a }) . mapping _Sensitive
goSSECustomerKeyMD5 :: Lens' GetObject (Maybe Text)
goSSECustomerKeyMD5 =
    lens _goSSECustomerKeyMD5 (\s a -> s { _goSSECustomerKeyMD5 = a })
goSSEKMSKeyId :: Lens' GetObject (Maybe Text)
goSSEKMSKeyId = lens _goSSEKMSKeyId (\s a -> s { _goSSEKMSKeyId = a }) . mapping _Sensitive
goVersionId :: Lens' GetObject (Maybe Text)
goVersionId = lens _goVersionId (\s a -> s { _goVersionId = a })
data GetObjectResponse = GetObjectResponse
    { _gorAcceptRanges            :: Maybe Text
    , _gorBody                    :: RsBody
    , _gorCacheControl            :: Maybe Text
    , _gorContentDisposition      :: Maybe Text
    , _gorContentEncoding         :: Maybe Text
    , _gorContentLanguage         :: Maybe Text
    , _gorContentLength           :: Maybe Int
    , _gorContentType             :: Maybe Text
    , _gorDeleteMarker            :: Maybe Bool
    , _gorETag                    :: Maybe Text
    , _gorExpiration              :: Maybe RFC822
    , _gorExpires                 :: Maybe RFC822
    , _gorLastModified            :: Maybe RFC822
    , _gorMetadata                :: Map (CI Text) Text
    , _gorMissingMeta             :: Maybe Int
    , _gorRestore                 :: Maybe Text
    , _gorSSECustomerAlgorithm    :: Maybe Text
    , _gorSSECustomerKeyMD5       :: Maybe Text
    , _gorSSEKMSKeyId             :: Maybe (Sensitive Text)
    , _gorServerSideEncryption    :: Maybe ServerSideEncryption
    , _gorVersionId               :: Maybe Text
    , _gorWebsiteRedirectLocation :: Maybe Text
    } deriving (Show)
getObjectResponse :: RsBody 
                  -> GetObjectResponse
getObjectResponse p1 = GetObjectResponse
    { _gorBody                    = p1
    , _gorDeleteMarker            = Nothing
    , _gorAcceptRanges            = Nothing
    , _gorExpiration              = Nothing
    , _gorRestore                 = Nothing
    , _gorLastModified            = Nothing
    , _gorContentLength           = Nothing
    , _gorETag                    = Nothing
    , _gorMissingMeta             = Nothing
    , _gorVersionId               = Nothing
    , _gorCacheControl            = Nothing
    , _gorContentDisposition      = Nothing
    , _gorContentEncoding         = Nothing
    , _gorContentLanguage         = Nothing
    , _gorContentType             = Nothing
    , _gorExpires                 = Nothing
    , _gorWebsiteRedirectLocation = Nothing
    , _gorServerSideEncryption    = Nothing
    , _gorMetadata                = mempty
    , _gorSSECustomerAlgorithm    = Nothing
    , _gorSSECustomerKeyMD5       = Nothing
    , _gorSSEKMSKeyId             = Nothing
    }
gorAcceptRanges :: Lens' GetObjectResponse (Maybe Text)
gorAcceptRanges = lens _gorAcceptRanges (\s a -> s { _gorAcceptRanges = a })
gorBody :: Lens' GetObjectResponse RsBody
gorBody = lens _gorBody (\s a -> s { _gorBody = a })
gorCacheControl :: Lens' GetObjectResponse (Maybe Text)
gorCacheControl = lens _gorCacheControl (\s a -> s { _gorCacheControl = a })
gorContentDisposition :: Lens' GetObjectResponse (Maybe Text)
gorContentDisposition =
    lens _gorContentDisposition (\s a -> s { _gorContentDisposition = a })
gorContentEncoding :: Lens' GetObjectResponse (Maybe Text)
gorContentEncoding =
    lens _gorContentEncoding (\s a -> s { _gorContentEncoding = a })
gorContentLanguage :: Lens' GetObjectResponse (Maybe Text)
gorContentLanguage =
    lens _gorContentLanguage (\s a -> s { _gorContentLanguage = a })
gorContentLength :: Lens' GetObjectResponse (Maybe Int)
gorContentLength = lens _gorContentLength (\s a -> s { _gorContentLength = a })
gorContentType :: Lens' GetObjectResponse (Maybe Text)
gorContentType = lens _gorContentType (\s a -> s { _gorContentType = a })
gorDeleteMarker :: Lens' GetObjectResponse (Maybe Bool)
gorDeleteMarker = lens _gorDeleteMarker (\s a -> s { _gorDeleteMarker = a })
gorETag :: Lens' GetObjectResponse (Maybe Text)
gorETag = lens _gorETag (\s a -> s { _gorETag = a })
gorExpiration :: Lens' GetObjectResponse (Maybe UTCTime)
gorExpiration = lens _gorExpiration (\s a -> s { _gorExpiration = a }) . mapping _Time
gorExpires :: Lens' GetObjectResponse (Maybe UTCTime)
gorExpires = lens _gorExpires (\s a -> s { _gorExpires = a }) . mapping _Time
gorLastModified :: Lens' GetObjectResponse (Maybe UTCTime)
gorLastModified = lens _gorLastModified (\s a -> s { _gorLastModified = a }) . mapping _Time
gorMetadata :: Lens' GetObjectResponse (HashMap (CI Text) Text)
gorMetadata = lens _gorMetadata (\s a -> s { _gorMetadata = a }) . _Map
gorMissingMeta :: Lens' GetObjectResponse (Maybe Int)
gorMissingMeta = lens _gorMissingMeta (\s a -> s { _gorMissingMeta = a })
gorRestore :: Lens' GetObjectResponse (Maybe Text)
gorRestore = lens _gorRestore (\s a -> s { _gorRestore = a })
gorSSECustomerAlgorithm :: Lens' GetObjectResponse (Maybe Text)
gorSSECustomerAlgorithm =
    lens _gorSSECustomerAlgorithm (\s a -> s { _gorSSECustomerAlgorithm = a })
gorSSECustomerKeyMD5 :: Lens' GetObjectResponse (Maybe Text)
gorSSECustomerKeyMD5 =
    lens _gorSSECustomerKeyMD5 (\s a -> s { _gorSSECustomerKeyMD5 = a })
gorSSEKMSKeyId :: Lens' GetObjectResponse (Maybe Text)
gorSSEKMSKeyId = lens _gorSSEKMSKeyId (\s a -> s { _gorSSEKMSKeyId = a }) . mapping _Sensitive
gorServerSideEncryption :: Lens' GetObjectResponse (Maybe ServerSideEncryption)
gorServerSideEncryption =
    lens _gorServerSideEncryption (\s a -> s { _gorServerSideEncryption = a })
gorVersionId :: Lens' GetObjectResponse (Maybe Text)
gorVersionId = lens _gorVersionId (\s a -> s { _gorVersionId = a })
gorWebsiteRedirectLocation :: Lens' GetObjectResponse (Maybe Text)
gorWebsiteRedirectLocation =
    lens _gorWebsiteRedirectLocation
        (\s a -> s { _gorWebsiteRedirectLocation = a })
instance ToPath GetObject where
    toPath GetObject{..} = mconcat
        [ "/"
        , toText _goBucket
        , "/"
        , toText _goKey
        ]
instance ToQuery GetObject where
    toQuery GetObject{..} = mconcat
        [ "response-cache-control"       =? _goResponseCacheControl
        , "response-content-disposition" =? _goResponseContentDisposition
        , "response-content-encoding"    =? _goResponseContentEncoding
        , "response-content-language"    =? _goResponseContentLanguage
        , "response-content-type"        =? _goResponseContentType
        , "response-expires"             =? _goResponseExpires
        , "versionId"                    =? _goVersionId
        ]
instance ToHeaders GetObject where
    toHeaders GetObject{..} = mconcat
        [ "If-Match"                                        =: _goIfMatch
        , "If-Modified-Since"                               =: _goIfModifiedSince
        , "If-None-Match"                                   =: _goIfNoneMatch
        , "If-Unmodified-Since"                             =: _goIfUnmodifiedSince
        , "Range"                                           =: _goRange
        , "x-amz-server-side-encryption-customer-algorithm" =: _goSSECustomerAlgorithm
        , "x-amz-server-side-encryption-customer-key"       =: _goSSECustomerKey
        , "x-amz-server-side-encryption-customer-key-MD5"   =: _goSSECustomerKeyMD5
        , "x-amz-server-side-encryption-aws-kms-key-id"     =: _goSSEKMSKeyId
        ]
instance ToXMLRoot GetObject where
    toXMLRoot = const (namespaced ns "GetObject" [])
instance ToXML GetObject
instance AWSRequest GetObject where
    type Sv GetObject = S3
    type Rs GetObject = GetObjectResponse
    request  = get
    response = bodyResponse $ \h b -> GetObjectResponse
        <$> h ~:? "accept-ranges"
        <*> pure (RsBody b)
        <*> h ~:? "Cache-Control"
        <*> h ~:? "Content-Disposition"
        <*> h ~:? "Content-Encoding"
        <*> h ~:? "Content-Language"
        <*> h ~:? "Content-Length"
        <*> h ~:? "Content-Type"
        <*> h ~:? "x-amz-delete-marker"
        <*> h ~:? "ETag"
        <*> h ~:? "x-amz-expiration"
        <*> h ~:? "Expires"
        <*> h ~:? "Last-Modified"
        <*> h ~:: "x-amz-meta-"
        <*> h ~:? "x-amz-missing-meta"
        <*> h ~:? "x-amz-restore"
        <*> h ~:? "x-amz-server-side-encryption-customer-algorithm"
        <*> h ~:? "x-amz-server-side-encryption-customer-key-MD5"
        <*> h ~:? "x-amz-server-side-encryption-aws-kms-key-id"
        <*> h ~:? "x-amz-server-side-encryption"
        <*> h ~:? "x-amz-version-id"
        <*> h ~:? "x-amz-website-redirect-location"