{-# 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.Route53Domains.ViewBilling
(
viewBilling
, ViewBilling
, vbStart
, vbEnd
, vbMarker
, vbMaxItems
, viewBillingResponse
, ViewBillingResponse
, vbrsNextPageMarker
, vbrsBillingRecords
, vbrsResponseStatus
) where
import Network.AWS.Lens
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
import Network.AWS.Route53Domains.Types
import Network.AWS.Route53Domains.Types.Product
data ViewBilling = ViewBilling'
{ _vbStart :: !(Maybe POSIX)
, _vbEnd :: !(Maybe POSIX)
, _vbMarker :: !(Maybe Text)
, _vbMaxItems :: !(Maybe Int)
} deriving (Eq,Read,Show,Data,Typeable,Generic)
viewBilling
:: ViewBilling
viewBilling =
ViewBilling'
{ _vbStart = Nothing
, _vbEnd = Nothing
, _vbMarker = Nothing
, _vbMaxItems = Nothing
}
vbStart :: Lens' ViewBilling (Maybe UTCTime)
vbStart = lens _vbStart (\ s a -> s{_vbStart = a}) . mapping _Time;
vbEnd :: Lens' ViewBilling (Maybe UTCTime)
vbEnd = lens _vbEnd (\ s a -> s{_vbEnd = a}) . mapping _Time;
vbMarker :: Lens' ViewBilling (Maybe Text)
vbMarker = lens _vbMarker (\ s a -> s{_vbMarker = a});
vbMaxItems :: Lens' ViewBilling (Maybe Int)
vbMaxItems = lens _vbMaxItems (\ s a -> s{_vbMaxItems = a});
instance AWSRequest ViewBilling where
type Rs ViewBilling = ViewBillingResponse
request = postJSON route53Domains
response
= receiveJSON
(\ s h x ->
ViewBillingResponse' <$>
(x .?> "NextPageMarker") <*>
(x .?> "BillingRecords" .!@ mempty)
<*> (pure (fromEnum s)))
instance Hashable ViewBilling
instance NFData ViewBilling
instance ToHeaders ViewBilling where
toHeaders
= const
(mconcat
["X-Amz-Target" =#
("Route53Domains_v20140515.ViewBilling" ::
ByteString),
"Content-Type" =#
("application/x-amz-json-1.1" :: ByteString)])
instance ToJSON ViewBilling where
toJSON ViewBilling'{..}
= object
(catMaybes
[("Start" .=) <$> _vbStart, ("End" .=) <$> _vbEnd,
("Marker" .=) <$> _vbMarker,
("MaxItems" .=) <$> _vbMaxItems])
instance ToPath ViewBilling where
toPath = const "/"
instance ToQuery ViewBilling where
toQuery = const mempty
data ViewBillingResponse = ViewBillingResponse'
{ _vbrsNextPageMarker :: !(Maybe Text)
, _vbrsBillingRecords :: !(Maybe [BillingRecord])
, _vbrsResponseStatus :: !Int
} deriving (Eq,Read,Show,Data,Typeable,Generic)
viewBillingResponse
:: Int
-> ViewBillingResponse
viewBillingResponse pResponseStatus_ =
ViewBillingResponse'
{ _vbrsNextPageMarker = Nothing
, _vbrsBillingRecords = Nothing
, _vbrsResponseStatus = pResponseStatus_
}
vbrsNextPageMarker :: Lens' ViewBillingResponse (Maybe Text)
vbrsNextPageMarker = lens _vbrsNextPageMarker (\ s a -> s{_vbrsNextPageMarker = a});
vbrsBillingRecords :: Lens' ViewBillingResponse [BillingRecord]
vbrsBillingRecords = lens _vbrsBillingRecords (\ s a -> s{_vbrsBillingRecords = a}) . _Default . _Coerce;
vbrsResponseStatus :: Lens' ViewBillingResponse Int
vbrsResponseStatus = lens _vbrsResponseStatus (\ s a -> s{_vbrsResponseStatus = a});
instance NFData ViewBillingResponse