{-# 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.SES.VerifyDomainIdentity
    (
    
      verifyDomainIdentity
    , VerifyDomainIdentity
    
    , vdiDomain
    
    , verifyDomainIdentityResponse
    , VerifyDomainIdentityResponse
    
    , vdirsResponseStatus
    , vdirsVerificationToken
    ) where
import           Network.AWS.Lens
import           Network.AWS.Prelude
import           Network.AWS.Request
import           Network.AWS.Response
import           Network.AWS.SES.Types
import           Network.AWS.SES.Types.Product
newtype VerifyDomainIdentity = VerifyDomainIdentity'
    { _vdiDomain :: Text
    } deriving (Eq,Read,Show,Data,Typeable,Generic)
verifyDomainIdentity
    :: Text 
    -> VerifyDomainIdentity
verifyDomainIdentity pDomain_ =
    VerifyDomainIdentity'
    { _vdiDomain = pDomain_
    }
vdiDomain :: Lens' VerifyDomainIdentity Text
vdiDomain = lens _vdiDomain (\ s a -> s{_vdiDomain = a});
instance AWSRequest VerifyDomainIdentity where
        type Rs VerifyDomainIdentity =
             VerifyDomainIdentityResponse
        request = postQuery ses
        response
          = receiveXMLWrapper "VerifyDomainIdentityResult"
              (\ s h x ->
                 VerifyDomainIdentityResponse' <$>
                   (pure (fromEnum s)) <*> (x .@ "VerificationToken"))
instance Hashable VerifyDomainIdentity
instance NFData VerifyDomainIdentity
instance ToHeaders VerifyDomainIdentity where
        toHeaders = const mempty
instance ToPath VerifyDomainIdentity where
        toPath = const "/"
instance ToQuery VerifyDomainIdentity where
        toQuery VerifyDomainIdentity'{..}
          = mconcat
              ["Action" =: ("VerifyDomainIdentity" :: ByteString),
               "Version" =: ("2010-12-01" :: ByteString),
               "Domain" =: _vdiDomain]
data VerifyDomainIdentityResponse = VerifyDomainIdentityResponse'
    { _vdirsResponseStatus    :: !Int
    , _vdirsVerificationToken :: !Text
    } deriving (Eq,Read,Show,Data,Typeable,Generic)
verifyDomainIdentityResponse
    :: Int 
    -> Text 
    -> VerifyDomainIdentityResponse
verifyDomainIdentityResponse pResponseStatus_ pVerificationToken_ =
    VerifyDomainIdentityResponse'
    { _vdirsResponseStatus = pResponseStatus_
    , _vdirsVerificationToken = pVerificationToken_
    }
vdirsResponseStatus :: Lens' VerifyDomainIdentityResponse Int
vdirsResponseStatus = lens _vdirsResponseStatus (\ s a -> s{_vdirsResponseStatus = a});
vdirsVerificationToken :: Lens' VerifyDomainIdentityResponse Text
vdirsVerificationToken = lens _vdirsVerificationToken (\ s a -> s{_vdirsVerificationToken = a});
instance NFData VerifyDomainIdentityResponse