module Network.AWS.S3.HeadObject
    (
    
      HeadObject
    
    , headObject
    
    , hoBucket
    , hoIfMatch
    , hoIfModifiedSince
    , hoIfNoneMatch
    , hoIfUnmodifiedSince
    , hoKey
    , hoRange
    , hoSSECustomerAlgorithm
    , hoSSECustomerKey
    , hoSSECustomerKeyMD5
    , hoSSEKMSKeyId
    , hoVersionId
    
    , HeadObjectResponse
    
    , headObjectResponse
    
    , horAcceptRanges
    , horCacheControl
    , horContentDisposition
    , horContentEncoding
    , horContentLanguage
    , horContentLength
    , horContentType
    , horDeleteMarker
    , horETag
    , horExpiration
    , horExpires
    , horLastModified
    , horMetadata
    , horMissingMeta
    , horRestore
    , horSSECustomerAlgorithm
    , horSSECustomerKeyMD5
    , horSSEKMSKeyId
    , horServerSideEncryption
    , horVersionId
    , horWebsiteRedirectLocation
    ) where
import Network.AWS.Prelude
import Network.AWS.Request.S3
import Network.AWS.S3.Types
import qualified GHC.Exts
data HeadObject = HeadObject
    { _hoBucket               :: Text
    , _hoIfMatch              :: Maybe Text
    , _hoIfModifiedSince      :: Maybe RFC822
    , _hoIfNoneMatch          :: Maybe Text
    , _hoIfUnmodifiedSince    :: Maybe RFC822
    , _hoKey                  :: Text
    , _hoRange                :: Maybe Text
    , _hoSSECustomerAlgorithm :: Maybe Text
    , _hoSSECustomerKey       :: Maybe (Sensitive Text)
    , _hoSSECustomerKeyMD5    :: Maybe Text
    , _hoSSEKMSKeyId          :: Maybe (Sensitive Text)
    , _hoVersionId            :: Maybe Text
    } deriving (Eq, Ord, Show)
headObject :: Text 
           -> Text 
           -> HeadObject
headObject p1 p2 = HeadObject
    { _hoBucket               = p1
    , _hoKey                  = p2
    , _hoIfMatch              = Nothing
    , _hoIfModifiedSince      = Nothing
    , _hoIfNoneMatch          = Nothing
    , _hoIfUnmodifiedSince    = Nothing
    , _hoRange                = Nothing
    , _hoVersionId            = Nothing
    , _hoSSECustomerAlgorithm = Nothing
    , _hoSSECustomerKey       = Nothing
    , _hoSSECustomerKeyMD5    = Nothing
    , _hoSSEKMSKeyId          = Nothing
    }
hoBucket :: Lens' HeadObject Text
hoBucket = lens _hoBucket (\s a -> s { _hoBucket = a })
hoIfMatch :: Lens' HeadObject (Maybe Text)
hoIfMatch = lens _hoIfMatch (\s a -> s { _hoIfMatch = a })
hoIfModifiedSince :: Lens' HeadObject (Maybe UTCTime)
hoIfModifiedSince =
    lens _hoIfModifiedSince (\s a -> s { _hoIfModifiedSince = a })
        . mapping _Time
hoIfNoneMatch :: Lens' HeadObject (Maybe Text)
hoIfNoneMatch = lens _hoIfNoneMatch (\s a -> s { _hoIfNoneMatch = a })
hoIfUnmodifiedSince :: Lens' HeadObject (Maybe UTCTime)
hoIfUnmodifiedSince =
    lens _hoIfUnmodifiedSince (\s a -> s { _hoIfUnmodifiedSince = a })
        . mapping _Time
hoKey :: Lens' HeadObject Text
hoKey = lens _hoKey (\s a -> s { _hoKey = a })
hoRange :: Lens' HeadObject (Maybe Text)
hoRange = lens _hoRange (\s a -> s { _hoRange = a })
hoSSECustomerAlgorithm :: Lens' HeadObject (Maybe Text)
hoSSECustomerAlgorithm =
    lens _hoSSECustomerAlgorithm (\s a -> s { _hoSSECustomerAlgorithm = a })
hoSSECustomerKey :: Lens' HeadObject (Maybe Text)
hoSSECustomerKey = lens _hoSSECustomerKey (\s a -> s { _hoSSECustomerKey = a }) . mapping _Sensitive
hoSSECustomerKeyMD5 :: Lens' HeadObject (Maybe Text)
hoSSECustomerKeyMD5 =
    lens _hoSSECustomerKeyMD5 (\s a -> s { _hoSSECustomerKeyMD5 = a })
hoSSEKMSKeyId :: Lens' HeadObject (Maybe Text)
hoSSEKMSKeyId = lens _hoSSEKMSKeyId (\s a -> s { _hoSSEKMSKeyId = a }) . mapping _Sensitive
hoVersionId :: Lens' HeadObject (Maybe Text)
hoVersionId = lens _hoVersionId (\s a -> s { _hoVersionId = a })
data HeadObjectResponse = HeadObjectResponse
    { _horAcceptRanges            :: Maybe Text
    , _horCacheControl            :: Maybe Text
    , _horContentDisposition      :: Maybe Text
    , _horContentEncoding         :: Maybe Text
    , _horContentLanguage         :: Maybe Text
    , _horContentLength           :: Maybe Int
    , _horContentType             :: Maybe Text
    , _horDeleteMarker            :: Maybe Bool
    , _horETag                    :: Maybe Text
    , _horExpiration              :: Maybe RFC822
    , _horExpires                 :: Maybe RFC822
    , _horLastModified            :: Maybe RFC822
    , _horMetadata                :: Map (CI Text) Text
    , _horMissingMeta             :: Maybe Int
    , _horRestore                 :: Maybe Text
    , _horSSECustomerAlgorithm    :: Maybe Text
    , _horSSECustomerKeyMD5       :: Maybe Text
    , _horSSEKMSKeyId             :: Maybe (Sensitive Text)
    , _horServerSideEncryption    :: Maybe ServerSideEncryption
    , _horVersionId               :: Maybe Text
    , _horWebsiteRedirectLocation :: Maybe Text
    } deriving (Eq, Show)
headObjectResponse :: HeadObjectResponse
headObjectResponse = HeadObjectResponse
    { _horDeleteMarker            = Nothing
    , _horAcceptRanges            = Nothing
    , _horExpiration              = Nothing
    , _horRestore                 = Nothing
    , _horLastModified            = Nothing
    , _horContentLength           = Nothing
    , _horETag                    = Nothing
    , _horMissingMeta             = Nothing
    , _horVersionId               = Nothing
    , _horCacheControl            = Nothing
    , _horContentDisposition      = Nothing
    , _horContentEncoding         = Nothing
    , _horContentLanguage         = Nothing
    , _horContentType             = Nothing
    , _horExpires                 = Nothing
    , _horWebsiteRedirectLocation = Nothing
    , _horServerSideEncryption    = Nothing
    , _horMetadata                = mempty
    , _horSSECustomerAlgorithm    = Nothing
    , _horSSECustomerKeyMD5       = Nothing
    , _horSSEKMSKeyId             = Nothing
    }
horAcceptRanges :: Lens' HeadObjectResponse (Maybe Text)
horAcceptRanges = lens _horAcceptRanges (\s a -> s { _horAcceptRanges = a })
horCacheControl :: Lens' HeadObjectResponse (Maybe Text)
horCacheControl = lens _horCacheControl (\s a -> s { _horCacheControl = a })
horContentDisposition :: Lens' HeadObjectResponse (Maybe Text)
horContentDisposition =
    lens _horContentDisposition (\s a -> s { _horContentDisposition = a })
horContentEncoding :: Lens' HeadObjectResponse (Maybe Text)
horContentEncoding =
    lens _horContentEncoding (\s a -> s { _horContentEncoding = a })
horContentLanguage :: Lens' HeadObjectResponse (Maybe Text)
horContentLanguage =
    lens _horContentLanguage (\s a -> s { _horContentLanguage = a })
horContentLength :: Lens' HeadObjectResponse (Maybe Int)
horContentLength = lens _horContentLength (\s a -> s { _horContentLength = a })
horContentType :: Lens' HeadObjectResponse (Maybe Text)
horContentType = lens _horContentType (\s a -> s { _horContentType = a })
horDeleteMarker :: Lens' HeadObjectResponse (Maybe Bool)
horDeleteMarker = lens _horDeleteMarker (\s a -> s { _horDeleteMarker = a })
horETag :: Lens' HeadObjectResponse (Maybe Text)
horETag = lens _horETag (\s a -> s { _horETag = a })
horExpiration :: Lens' HeadObjectResponse (Maybe UTCTime)
horExpiration = lens _horExpiration (\s a -> s { _horExpiration = a }) . mapping _Time
horExpires :: Lens' HeadObjectResponse (Maybe UTCTime)
horExpires = lens _horExpires (\s a -> s { _horExpires = a }) . mapping _Time
horLastModified :: Lens' HeadObjectResponse (Maybe UTCTime)
horLastModified = lens _horLastModified (\s a -> s { _horLastModified = a }) . mapping _Time
horMetadata :: Lens' HeadObjectResponse (HashMap (CI Text) Text)
horMetadata = lens _horMetadata (\s a -> s { _horMetadata = a }) . _Map
horMissingMeta :: Lens' HeadObjectResponse (Maybe Int)
horMissingMeta = lens _horMissingMeta (\s a -> s { _horMissingMeta = a })
horRestore :: Lens' HeadObjectResponse (Maybe Text)
horRestore = lens _horRestore (\s a -> s { _horRestore = a })
horSSECustomerAlgorithm :: Lens' HeadObjectResponse (Maybe Text)
horSSECustomerAlgorithm =
    lens _horSSECustomerAlgorithm (\s a -> s { _horSSECustomerAlgorithm = a })
horSSECustomerKeyMD5 :: Lens' HeadObjectResponse (Maybe Text)
horSSECustomerKeyMD5 =
    lens _horSSECustomerKeyMD5 (\s a -> s { _horSSECustomerKeyMD5 = a })
horSSEKMSKeyId :: Lens' HeadObjectResponse (Maybe Text)
horSSEKMSKeyId = lens _horSSEKMSKeyId (\s a -> s { _horSSEKMSKeyId = a }) . mapping _Sensitive
horServerSideEncryption :: Lens' HeadObjectResponse (Maybe ServerSideEncryption)
horServerSideEncryption =
    lens _horServerSideEncryption (\s a -> s { _horServerSideEncryption = a })
horVersionId :: Lens' HeadObjectResponse (Maybe Text)
horVersionId = lens _horVersionId (\s a -> s { _horVersionId = a })
horWebsiteRedirectLocation :: Lens' HeadObjectResponse (Maybe Text)
horWebsiteRedirectLocation =
    lens _horWebsiteRedirectLocation
        (\s a -> s { _horWebsiteRedirectLocation = a })
instance ToPath HeadObject where
    toPath HeadObject{..} = mconcat
        [ "/"
        , toText _hoBucket
        , "/"
        , toText _hoKey
        ]
instance ToQuery HeadObject where
    toQuery rq = "versionId" =? _hoVersionId rq
instance ToHeaders HeadObject where
    toHeaders HeadObject{..} = mconcat
        [ "If-Match"                                        =: _hoIfMatch
        , "If-Modified-Since"                               =: _hoIfModifiedSince
        , "If-None-Match"                                   =: _hoIfNoneMatch
        , "If-Unmodified-Since"                             =: _hoIfUnmodifiedSince
        , "Range"                                           =: _hoRange
        , "x-amz-server-side-encryption-customer-algorithm" =: _hoSSECustomerAlgorithm
        , "x-amz-server-side-encryption-customer-key"       =: _hoSSECustomerKey
        , "x-amz-server-side-encryption-customer-key-MD5"   =: _hoSSECustomerKeyMD5
        , "x-amz-server-side-encryption-aws-kms-key-id"     =: _hoSSEKMSKeyId
        ]
instance ToXMLRoot HeadObject where
    toXMLRoot = const (namespaced ns "HeadObject" [])
instance ToXML HeadObject
instance AWSRequest HeadObject where
    type Sv HeadObject = S3
    type Rs HeadObject = HeadObjectResponse
    request  = head
    response = headerResponse $ \h -> HeadObjectResponse
        <$> h ~:? "accept-ranges"
        <*> 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"