module Network.AWS.CloudFront.GetDistributionConfig
    (
    
      GetDistributionConfig
    
    , getDistributionConfig
    
    , gdcId
    
    , GetDistributionConfigResponse
    
    , getDistributionConfigResponse
    
    , gdcrDistributionConfig
    , gdcrETag
    ) where
import Network.AWS.Prelude
import Network.AWS.Request.RestXML
import Network.AWS.CloudFront.Types
import qualified GHC.Exts
newtype GetDistributionConfig = GetDistributionConfig
    { _gdcId :: Text
    } deriving (Eq, Ord, Read, Show, Monoid, IsString)
getDistributionConfig :: Text 
                      -> GetDistributionConfig
getDistributionConfig p1 = GetDistributionConfig
    { _gdcId = p1
    }
gdcId :: Lens' GetDistributionConfig Text
gdcId = lens _gdcId (\s a -> s { _gdcId = a })
data GetDistributionConfigResponse = GetDistributionConfigResponse
    { _gdcrDistributionConfig :: Maybe DistributionConfig
    , _gdcrETag               :: Maybe Text
    } deriving (Eq, Read, Show)
getDistributionConfigResponse :: GetDistributionConfigResponse
getDistributionConfigResponse = GetDistributionConfigResponse
    { _gdcrDistributionConfig = Nothing
    , _gdcrETag               = Nothing
    }
gdcrDistributionConfig :: Lens' GetDistributionConfigResponse (Maybe DistributionConfig)
gdcrDistributionConfig =
    lens _gdcrDistributionConfig (\s a -> s { _gdcrDistributionConfig = a })
gdcrETag :: Lens' GetDistributionConfigResponse (Maybe Text)
gdcrETag = lens _gdcrETag (\s a -> s { _gdcrETag = a })
instance ToPath GetDistributionConfig where
    toPath GetDistributionConfig{..} = mconcat
        [ "/2014-11-06/distribution/"
        , toText _gdcId
        , "/config"
        ]
instance ToQuery GetDistributionConfig where
    toQuery = const mempty
instance ToHeaders GetDistributionConfig
instance ToXMLRoot GetDistributionConfig where
    toXMLRoot = const (namespaced ns "GetDistributionConfig" [])
instance ToXML GetDistributionConfig
instance AWSRequest GetDistributionConfig where
    type Sv GetDistributionConfig = CloudFront
    type Rs GetDistributionConfig = GetDistributionConfigResponse
    request  = get
    response = xmlHeaderResponse $ \h x -> GetDistributionConfigResponse
        <$> x .@? "DistributionConfig"
        <*> h ~:? "ETag"