{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.Route53Domains.ListDomains
(
ListDomains (..),
newListDomains,
listDomains_filterConditions,
listDomains_marker,
listDomains_maxItems,
listDomains_sortCondition,
ListDomainsResponse (..),
newListDomainsResponse,
listDomainsResponse_domains,
listDomainsResponse_nextPageMarker,
listDomainsResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.Route53Domains.Types
data ListDomains = ListDomains'
{
ListDomains -> Maybe [FilterCondition]
filterConditions :: Prelude.Maybe [FilterCondition],
ListDomains -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
ListDomains -> Maybe Int
maxItems :: Prelude.Maybe Prelude.Int,
ListDomains -> Maybe SortCondition
sortCondition :: Prelude.Maybe SortCondition
}
deriving (ListDomains -> ListDomains -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListDomains -> ListDomains -> Bool
$c/= :: ListDomains -> ListDomains -> Bool
== :: ListDomains -> ListDomains -> Bool
$c== :: ListDomains -> ListDomains -> Bool
Prelude.Eq, ReadPrec [ListDomains]
ReadPrec ListDomains
Int -> ReadS ListDomains
ReadS [ListDomains]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListDomains]
$creadListPrec :: ReadPrec [ListDomains]
readPrec :: ReadPrec ListDomains
$creadPrec :: ReadPrec ListDomains
readList :: ReadS [ListDomains]
$creadList :: ReadS [ListDomains]
readsPrec :: Int -> ReadS ListDomains
$creadsPrec :: Int -> ReadS ListDomains
Prelude.Read, Int -> ListDomains -> ShowS
[ListDomains] -> ShowS
ListDomains -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListDomains] -> ShowS
$cshowList :: [ListDomains] -> ShowS
show :: ListDomains -> String
$cshow :: ListDomains -> String
showsPrec :: Int -> ListDomains -> ShowS
$cshowsPrec :: Int -> ListDomains -> ShowS
Prelude.Show, forall x. Rep ListDomains x -> ListDomains
forall x. ListDomains -> Rep ListDomains x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListDomains x -> ListDomains
$cfrom :: forall x. ListDomains -> Rep ListDomains x
Prelude.Generic)
newListDomains ::
ListDomains
newListDomains :: ListDomains
newListDomains =
ListDomains'
{ $sel:filterConditions:ListDomains' :: Maybe [FilterCondition]
filterConditions = forall a. Maybe a
Prelude.Nothing,
$sel:marker:ListDomains' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
$sel:maxItems:ListDomains' :: Maybe Int
maxItems = forall a. Maybe a
Prelude.Nothing,
$sel:sortCondition:ListDomains' :: Maybe SortCondition
sortCondition = forall a. Maybe a
Prelude.Nothing
}
listDomains_filterConditions :: Lens.Lens' ListDomains (Prelude.Maybe [FilterCondition])
listDomains_filterConditions :: Lens' ListDomains (Maybe [FilterCondition])
listDomains_filterConditions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDomains' {Maybe [FilterCondition]
filterConditions :: Maybe [FilterCondition]
$sel:filterConditions:ListDomains' :: ListDomains -> Maybe [FilterCondition]
filterConditions} -> Maybe [FilterCondition]
filterConditions) (\s :: ListDomains
s@ListDomains' {} Maybe [FilterCondition]
a -> ListDomains
s {$sel:filterConditions:ListDomains' :: Maybe [FilterCondition]
filterConditions = Maybe [FilterCondition]
a} :: ListDomains) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
listDomains_marker :: Lens.Lens' ListDomains (Prelude.Maybe Prelude.Text)
listDomains_marker :: Lens' ListDomains (Maybe Text)
listDomains_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDomains' {Maybe Text
marker :: Maybe Text
$sel:marker:ListDomains' :: ListDomains -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListDomains
s@ListDomains' {} Maybe Text
a -> ListDomains
s {$sel:marker:ListDomains' :: Maybe Text
marker = Maybe Text
a} :: ListDomains)
listDomains_maxItems :: Lens.Lens' ListDomains (Prelude.Maybe Prelude.Int)
listDomains_maxItems :: Lens' ListDomains (Maybe Int)
listDomains_maxItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDomains' {Maybe Int
maxItems :: Maybe Int
$sel:maxItems:ListDomains' :: ListDomains -> Maybe Int
maxItems} -> Maybe Int
maxItems) (\s :: ListDomains
s@ListDomains' {} Maybe Int
a -> ListDomains
s {$sel:maxItems:ListDomains' :: Maybe Int
maxItems = Maybe Int
a} :: ListDomains)
listDomains_sortCondition :: Lens.Lens' ListDomains (Prelude.Maybe SortCondition)
listDomains_sortCondition :: Lens' ListDomains (Maybe SortCondition)
listDomains_sortCondition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDomains' {Maybe SortCondition
sortCondition :: Maybe SortCondition
$sel:sortCondition:ListDomains' :: ListDomains -> Maybe SortCondition
sortCondition} -> Maybe SortCondition
sortCondition) (\s :: ListDomains
s@ListDomains' {} Maybe SortCondition
a -> ListDomains
s {$sel:sortCondition:ListDomains' :: Maybe SortCondition
sortCondition = Maybe SortCondition
a} :: ListDomains)
instance Core.AWSPager ListDomains where
page :: ListDomains -> AWSResponse ListDomains -> Maybe ListDomains
page ListDomains
rq AWSResponse ListDomains
rs
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse ListDomains
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListDomainsResponse (Maybe Text)
listDomainsResponse_nextPageMarker
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
) =
forall a. Maybe a
Prelude.Nothing
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse ListDomains
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListDomainsResponse (Maybe [DomainSummary])
listDomainsResponse_domains
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
) =
forall a. Maybe a
Prelude.Nothing
| Bool
Prelude.otherwise =
forall a. a -> Maybe a
Prelude.Just
forall a b. (a -> b) -> a -> b
Prelude.$ ListDomains
rq
forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListDomains (Maybe Text)
listDomains_marker
forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListDomains
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListDomainsResponse (Maybe Text)
listDomainsResponse_nextPageMarker
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
instance Core.AWSRequest ListDomains where
type AWSResponse ListDomains = ListDomainsResponse
request :: (Service -> Service) -> ListDomains -> Request ListDomains
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListDomains
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListDomains)))
response =
forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
( \Int
s ResponseHeaders
h Object
x ->
Maybe [DomainSummary] -> Maybe Text -> Int -> ListDomainsResponse
ListDomainsResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Domains" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NextPageMarker")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
)
instance Prelude.Hashable ListDomains where
hashWithSalt :: Int -> ListDomains -> Int
hashWithSalt Int
_salt ListDomains' {Maybe Int
Maybe [FilterCondition]
Maybe Text
Maybe SortCondition
sortCondition :: Maybe SortCondition
maxItems :: Maybe Int
marker :: Maybe Text
filterConditions :: Maybe [FilterCondition]
$sel:sortCondition:ListDomains' :: ListDomains -> Maybe SortCondition
$sel:maxItems:ListDomains' :: ListDomains -> Maybe Int
$sel:marker:ListDomains' :: ListDomains -> Maybe Text
$sel:filterConditions:ListDomains' :: ListDomains -> Maybe [FilterCondition]
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [FilterCondition]
filterConditions
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxItems
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortCondition
sortCondition
instance Prelude.NFData ListDomains where
rnf :: ListDomains -> ()
rnf ListDomains' {Maybe Int
Maybe [FilterCondition]
Maybe Text
Maybe SortCondition
sortCondition :: Maybe SortCondition
maxItems :: Maybe Int
marker :: Maybe Text
filterConditions :: Maybe [FilterCondition]
$sel:sortCondition:ListDomains' :: ListDomains -> Maybe SortCondition
$sel:maxItems:ListDomains' :: ListDomains -> Maybe Int
$sel:marker:ListDomains' :: ListDomains -> Maybe Text
$sel:filterConditions:ListDomains' :: ListDomains -> Maybe [FilterCondition]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [FilterCondition]
filterConditions
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxItems
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SortCondition
sortCondition
instance Data.ToHeaders ListDomains where
toHeaders :: ListDomains -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"X-Amz-Target"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"Route53Domains_v20140515.ListDomains" ::
Prelude.ByteString
),
HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON ListDomains where
toJSON :: ListDomains -> Value
toJSON ListDomains' {Maybe Int
Maybe [FilterCondition]
Maybe Text
Maybe SortCondition
sortCondition :: Maybe SortCondition
maxItems :: Maybe Int
marker :: Maybe Text
filterConditions :: Maybe [FilterCondition]
$sel:sortCondition:ListDomains' :: ListDomains -> Maybe SortCondition
$sel:maxItems:ListDomains' :: ListDomains -> Maybe Int
$sel:marker:ListDomains' :: ListDomains -> Maybe Text
$sel:filterConditions:ListDomains' :: ListDomains -> Maybe [FilterCondition]
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"FilterConditions" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [FilterCondition]
filterConditions,
(Key
"Marker" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
marker,
(Key
"MaxItems" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Int
maxItems,
(Key
"SortCondition" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SortCondition
sortCondition
]
)
instance Data.ToPath ListDomains where
toPath :: ListDomains -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery ListDomains where
toQuery :: ListDomains -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data ListDomainsResponse = ListDomainsResponse'
{
ListDomainsResponse -> Maybe [DomainSummary]
domains :: Prelude.Maybe [DomainSummary],
ListDomainsResponse -> Maybe Text
nextPageMarker :: Prelude.Maybe Prelude.Text,
ListDomainsResponse -> Int
httpStatus :: Prelude.Int
}
deriving (ListDomainsResponse -> ListDomainsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListDomainsResponse -> ListDomainsResponse -> Bool
$c/= :: ListDomainsResponse -> ListDomainsResponse -> Bool
== :: ListDomainsResponse -> ListDomainsResponse -> Bool
$c== :: ListDomainsResponse -> ListDomainsResponse -> Bool
Prelude.Eq, ReadPrec [ListDomainsResponse]
ReadPrec ListDomainsResponse
Int -> ReadS ListDomainsResponse
ReadS [ListDomainsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListDomainsResponse]
$creadListPrec :: ReadPrec [ListDomainsResponse]
readPrec :: ReadPrec ListDomainsResponse
$creadPrec :: ReadPrec ListDomainsResponse
readList :: ReadS [ListDomainsResponse]
$creadList :: ReadS [ListDomainsResponse]
readsPrec :: Int -> ReadS ListDomainsResponse
$creadsPrec :: Int -> ReadS ListDomainsResponse
Prelude.Read, Int -> ListDomainsResponse -> ShowS
[ListDomainsResponse] -> ShowS
ListDomainsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListDomainsResponse] -> ShowS
$cshowList :: [ListDomainsResponse] -> ShowS
show :: ListDomainsResponse -> String
$cshow :: ListDomainsResponse -> String
showsPrec :: Int -> ListDomainsResponse -> ShowS
$cshowsPrec :: Int -> ListDomainsResponse -> ShowS
Prelude.Show, forall x. Rep ListDomainsResponse x -> ListDomainsResponse
forall x. ListDomainsResponse -> Rep ListDomainsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListDomainsResponse x -> ListDomainsResponse
$cfrom :: forall x. ListDomainsResponse -> Rep ListDomainsResponse x
Prelude.Generic)
newListDomainsResponse ::
Prelude.Int ->
ListDomainsResponse
newListDomainsResponse :: Int -> ListDomainsResponse
newListDomainsResponse Int
pHttpStatus_ =
ListDomainsResponse'
{ $sel:domains:ListDomainsResponse' :: Maybe [DomainSummary]
domains = forall a. Maybe a
Prelude.Nothing,
$sel:nextPageMarker:ListDomainsResponse' :: Maybe Text
nextPageMarker = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:ListDomainsResponse' :: Int
httpStatus = Int
pHttpStatus_
}
listDomainsResponse_domains :: Lens.Lens' ListDomainsResponse (Prelude.Maybe [DomainSummary])
listDomainsResponse_domains :: Lens' ListDomainsResponse (Maybe [DomainSummary])
listDomainsResponse_domains = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDomainsResponse' {Maybe [DomainSummary]
domains :: Maybe [DomainSummary]
$sel:domains:ListDomainsResponse' :: ListDomainsResponse -> Maybe [DomainSummary]
domains} -> Maybe [DomainSummary]
domains) (\s :: ListDomainsResponse
s@ListDomainsResponse' {} Maybe [DomainSummary]
a -> ListDomainsResponse
s {$sel:domains:ListDomainsResponse' :: Maybe [DomainSummary]
domains = Maybe [DomainSummary]
a} :: ListDomainsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
listDomainsResponse_nextPageMarker :: Lens.Lens' ListDomainsResponse (Prelude.Maybe Prelude.Text)
listDomainsResponse_nextPageMarker :: Lens' ListDomainsResponse (Maybe Text)
listDomainsResponse_nextPageMarker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDomainsResponse' {Maybe Text
nextPageMarker :: Maybe Text
$sel:nextPageMarker:ListDomainsResponse' :: ListDomainsResponse -> Maybe Text
nextPageMarker} -> Maybe Text
nextPageMarker) (\s :: ListDomainsResponse
s@ListDomainsResponse' {} Maybe Text
a -> ListDomainsResponse
s {$sel:nextPageMarker:ListDomainsResponse' :: Maybe Text
nextPageMarker = Maybe Text
a} :: ListDomainsResponse)
listDomainsResponse_httpStatus :: Lens.Lens' ListDomainsResponse Prelude.Int
listDomainsResponse_httpStatus :: Lens' ListDomainsResponse Int
listDomainsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDomainsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListDomainsResponse' :: ListDomainsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListDomainsResponse
s@ListDomainsResponse' {} Int
a -> ListDomainsResponse
s {$sel:httpStatus:ListDomainsResponse' :: Int
httpStatus = Int
a} :: ListDomainsResponse)
instance Prelude.NFData ListDomainsResponse where
rnf :: ListDomainsResponse -> ()
rnf ListDomainsResponse' {Int
Maybe [DomainSummary]
Maybe Text
httpStatus :: Int
nextPageMarker :: Maybe Text
domains :: Maybe [DomainSummary]
$sel:httpStatus:ListDomainsResponse' :: ListDomainsResponse -> Int
$sel:nextPageMarker:ListDomainsResponse' :: ListDomainsResponse -> Maybe Text
$sel:domains:ListDomainsResponse' :: ListDomainsResponse -> Maybe [DomainSummary]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [DomainSummary]
domains
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextPageMarker
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus