{-# 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 #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.CloudFront.ListDistributionsByWebACLId
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- List the distributions that are associated with a specified WAF web ACL.
module Amazonka.CloudFront.ListDistributionsByWebACLId
  ( -- * Creating a Request
    ListDistributionsByWebACLId (..),
    newListDistributionsByWebACLId,

    -- * Request Lenses
    listDistributionsByWebACLId_marker,
    listDistributionsByWebACLId_maxItems,
    listDistributionsByWebACLId_webACLId,

    -- * Destructuring the Response
    ListDistributionsByWebACLIdResponse (..),
    newListDistributionsByWebACLIdResponse,

    -- * Response Lenses
    listDistributionsByWebACLIdResponse_distributionList,
    listDistributionsByWebACLIdResponse_httpStatus,
  )
where

import Amazonka.CloudFront.Types
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

-- | The request to list distributions that are associated with a specified
-- WAF web ACL.
--
-- /See:/ 'newListDistributionsByWebACLId' smart constructor.
data ListDistributionsByWebACLId = ListDistributionsByWebACLId'
  { -- | Use @Marker@ and @MaxItems@ to control pagination of results. If you
    -- have more than @MaxItems@ distributions that satisfy the request, the
    -- response includes a @NextMarker@ element. To get the next page of
    -- results, submit another request. For the value of @Marker@, specify the
    -- value of @NextMarker@ from the last response. (For the first request,
    -- omit @Marker@.)
    ListDistributionsByWebACLId -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of distributions that you want CloudFront to return
    -- in the response body. The maximum and default values are both 100.
    ListDistributionsByWebACLId -> Maybe Text
maxItems :: Prelude.Maybe Prelude.Text,
    -- | The ID of the WAF web ACL that you want to list the associated
    -- distributions. If you specify \"null\" for the ID, the request returns a
    -- list of the distributions that aren\'t associated with a web ACL.
    ListDistributionsByWebACLId -> Text
webACLId :: Prelude.Text
  }
  deriving (ListDistributionsByWebACLId -> ListDistributionsByWebACLId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListDistributionsByWebACLId -> ListDistributionsByWebACLId -> Bool
$c/= :: ListDistributionsByWebACLId -> ListDistributionsByWebACLId -> Bool
== :: ListDistributionsByWebACLId -> ListDistributionsByWebACLId -> Bool
$c== :: ListDistributionsByWebACLId -> ListDistributionsByWebACLId -> Bool
Prelude.Eq, ReadPrec [ListDistributionsByWebACLId]
ReadPrec ListDistributionsByWebACLId
Int -> ReadS ListDistributionsByWebACLId
ReadS [ListDistributionsByWebACLId]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListDistributionsByWebACLId]
$creadListPrec :: ReadPrec [ListDistributionsByWebACLId]
readPrec :: ReadPrec ListDistributionsByWebACLId
$creadPrec :: ReadPrec ListDistributionsByWebACLId
readList :: ReadS [ListDistributionsByWebACLId]
$creadList :: ReadS [ListDistributionsByWebACLId]
readsPrec :: Int -> ReadS ListDistributionsByWebACLId
$creadsPrec :: Int -> ReadS ListDistributionsByWebACLId
Prelude.Read, Int -> ListDistributionsByWebACLId -> ShowS
[ListDistributionsByWebACLId] -> ShowS
ListDistributionsByWebACLId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListDistributionsByWebACLId] -> ShowS
$cshowList :: [ListDistributionsByWebACLId] -> ShowS
show :: ListDistributionsByWebACLId -> String
$cshow :: ListDistributionsByWebACLId -> String
showsPrec :: Int -> ListDistributionsByWebACLId -> ShowS
$cshowsPrec :: Int -> ListDistributionsByWebACLId -> ShowS
Prelude.Show, forall x.
Rep ListDistributionsByWebACLId x -> ListDistributionsByWebACLId
forall x.
ListDistributionsByWebACLId -> Rep ListDistributionsByWebACLId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListDistributionsByWebACLId x -> ListDistributionsByWebACLId
$cfrom :: forall x.
ListDistributionsByWebACLId -> Rep ListDistributionsByWebACLId x
Prelude.Generic)

-- |
-- Create a value of 'ListDistributionsByWebACLId' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'marker', 'listDistributionsByWebACLId_marker' - Use @Marker@ and @MaxItems@ to control pagination of results. If you
-- have more than @MaxItems@ distributions that satisfy the request, the
-- response includes a @NextMarker@ element. To get the next page of
-- results, submit another request. For the value of @Marker@, specify the
-- value of @NextMarker@ from the last response. (For the first request,
-- omit @Marker@.)
--
-- 'maxItems', 'listDistributionsByWebACLId_maxItems' - The maximum number of distributions that you want CloudFront to return
-- in the response body. The maximum and default values are both 100.
--
-- 'webACLId', 'listDistributionsByWebACLId_webACLId' - The ID of the WAF web ACL that you want to list the associated
-- distributions. If you specify \"null\" for the ID, the request returns a
-- list of the distributions that aren\'t associated with a web ACL.
newListDistributionsByWebACLId ::
  -- | 'webACLId'
  Prelude.Text ->
  ListDistributionsByWebACLId
newListDistributionsByWebACLId :: Text -> ListDistributionsByWebACLId
newListDistributionsByWebACLId Text
pWebACLId_ =
  ListDistributionsByWebACLId'
    { $sel:marker:ListDistributionsByWebACLId' :: Maybe Text
marker =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxItems:ListDistributionsByWebACLId' :: Maybe Text
maxItems = forall a. Maybe a
Prelude.Nothing,
      $sel:webACLId:ListDistributionsByWebACLId' :: Text
webACLId = Text
pWebACLId_
    }

-- | Use @Marker@ and @MaxItems@ to control pagination of results. If you
-- have more than @MaxItems@ distributions that satisfy the request, the
-- response includes a @NextMarker@ element. To get the next page of
-- results, submit another request. For the value of @Marker@, specify the
-- value of @NextMarker@ from the last response. (For the first request,
-- omit @Marker@.)
listDistributionsByWebACLId_marker :: Lens.Lens' ListDistributionsByWebACLId (Prelude.Maybe Prelude.Text)
listDistributionsByWebACLId_marker :: Lens' ListDistributionsByWebACLId (Maybe Text)
listDistributionsByWebACLId_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDistributionsByWebACLId' {Maybe Text
marker :: Maybe Text
$sel:marker:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListDistributionsByWebACLId
s@ListDistributionsByWebACLId' {} Maybe Text
a -> ListDistributionsByWebACLId
s {$sel:marker:ListDistributionsByWebACLId' :: Maybe Text
marker = Maybe Text
a} :: ListDistributionsByWebACLId)

-- | The maximum number of distributions that you want CloudFront to return
-- in the response body. The maximum and default values are both 100.
listDistributionsByWebACLId_maxItems :: Lens.Lens' ListDistributionsByWebACLId (Prelude.Maybe Prelude.Text)
listDistributionsByWebACLId_maxItems :: Lens' ListDistributionsByWebACLId (Maybe Text)
listDistributionsByWebACLId_maxItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDistributionsByWebACLId' {Maybe Text
maxItems :: Maybe Text
$sel:maxItems:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Maybe Text
maxItems} -> Maybe Text
maxItems) (\s :: ListDistributionsByWebACLId
s@ListDistributionsByWebACLId' {} Maybe Text
a -> ListDistributionsByWebACLId
s {$sel:maxItems:ListDistributionsByWebACLId' :: Maybe Text
maxItems = Maybe Text
a} :: ListDistributionsByWebACLId)

-- | The ID of the WAF web ACL that you want to list the associated
-- distributions. If you specify \"null\" for the ID, the request returns a
-- list of the distributions that aren\'t associated with a web ACL.
listDistributionsByWebACLId_webACLId :: Lens.Lens' ListDistributionsByWebACLId Prelude.Text
listDistributionsByWebACLId_webACLId :: Lens' ListDistributionsByWebACLId Text
listDistributionsByWebACLId_webACLId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDistributionsByWebACLId' {Text
webACLId :: Text
$sel:webACLId:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Text
webACLId} -> Text
webACLId) (\s :: ListDistributionsByWebACLId
s@ListDistributionsByWebACLId' {} Text
a -> ListDistributionsByWebACLId
s {$sel:webACLId:ListDistributionsByWebACLId' :: Text
webACLId = Text
a} :: ListDistributionsByWebACLId)

instance Core.AWSRequest ListDistributionsByWebACLId where
  type
    AWSResponse ListDistributionsByWebACLId =
      ListDistributionsByWebACLIdResponse
  request :: (Service -> Service)
-> ListDistributionsByWebACLId
-> Request ListDistributionsByWebACLId
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListDistributionsByWebACLId
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListDistributionsByWebACLId)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe DistributionList
-> Int -> ListDistributionsByWebACLIdResponse
ListDistributionsByWebACLIdResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)
            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 ListDistributionsByWebACLId where
  hashWithSalt :: Int -> ListDistributionsByWebACLId -> Int
hashWithSalt Int
_salt ListDistributionsByWebACLId' {Maybe Text
Text
webACLId :: Text
maxItems :: Maybe Text
marker :: Maybe Text
$sel:webACLId:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Text
$sel:maxItems:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Maybe Text
$sel:marker:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
maxItems
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
webACLId

instance Prelude.NFData ListDistributionsByWebACLId where
  rnf :: ListDistributionsByWebACLId -> ()
rnf ListDistributionsByWebACLId' {Maybe Text
Text
webACLId :: Text
maxItems :: Maybe Text
marker :: Maybe Text
$sel:webACLId:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Text
$sel:maxItems:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Maybe Text
$sel:marker:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Maybe Text
..} =
    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 Text
maxItems
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
webACLId

instance Data.ToHeaders ListDistributionsByWebACLId where
  toHeaders :: ListDistributionsByWebACLId -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath ListDistributionsByWebACLId where
  toPath :: ListDistributionsByWebACLId -> ByteString
toPath ListDistributionsByWebACLId' {Maybe Text
Text
webACLId :: Text
maxItems :: Maybe Text
marker :: Maybe Text
$sel:webACLId:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Text
$sel:maxItems:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Maybe Text
$sel:marker:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/2020-05-31/distributionsByWebACLId/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
webACLId
      ]

instance Data.ToQuery ListDistributionsByWebACLId where
  toQuery :: ListDistributionsByWebACLId -> QueryString
toQuery ListDistributionsByWebACLId' {Maybe Text
Text
webACLId :: Text
maxItems :: Maybe Text
marker :: Maybe Text
$sel:webACLId:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Text
$sel:maxItems:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Maybe Text
$sel:marker:ListDistributionsByWebACLId' :: ListDistributionsByWebACLId -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Marker" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
marker,
        ByteString
"MaxItems" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
maxItems
      ]

-- | The response to a request to list the distributions that are associated
-- with a specified WAF web ACL.
--
-- /See:/ 'newListDistributionsByWebACLIdResponse' smart constructor.
data ListDistributionsByWebACLIdResponse = ListDistributionsByWebACLIdResponse'
  { -- | The @DistributionList@ type.
    ListDistributionsByWebACLIdResponse -> Maybe DistributionList
distributionList :: Prelude.Maybe DistributionList,
    -- | The response's http status code.
    ListDistributionsByWebACLIdResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListDistributionsByWebACLIdResponse
-> ListDistributionsByWebACLIdResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListDistributionsByWebACLIdResponse
-> ListDistributionsByWebACLIdResponse -> Bool
$c/= :: ListDistributionsByWebACLIdResponse
-> ListDistributionsByWebACLIdResponse -> Bool
== :: ListDistributionsByWebACLIdResponse
-> ListDistributionsByWebACLIdResponse -> Bool
$c== :: ListDistributionsByWebACLIdResponse
-> ListDistributionsByWebACLIdResponse -> Bool
Prelude.Eq, Int -> ListDistributionsByWebACLIdResponse -> ShowS
[ListDistributionsByWebACLIdResponse] -> ShowS
ListDistributionsByWebACLIdResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListDistributionsByWebACLIdResponse] -> ShowS
$cshowList :: [ListDistributionsByWebACLIdResponse] -> ShowS
show :: ListDistributionsByWebACLIdResponse -> String
$cshow :: ListDistributionsByWebACLIdResponse -> String
showsPrec :: Int -> ListDistributionsByWebACLIdResponse -> ShowS
$cshowsPrec :: Int -> ListDistributionsByWebACLIdResponse -> ShowS
Prelude.Show, forall x.
Rep ListDistributionsByWebACLIdResponse x
-> ListDistributionsByWebACLIdResponse
forall x.
ListDistributionsByWebACLIdResponse
-> Rep ListDistributionsByWebACLIdResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListDistributionsByWebACLIdResponse x
-> ListDistributionsByWebACLIdResponse
$cfrom :: forall x.
ListDistributionsByWebACLIdResponse
-> Rep ListDistributionsByWebACLIdResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListDistributionsByWebACLIdResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'distributionList', 'listDistributionsByWebACLIdResponse_distributionList' - The @DistributionList@ type.
--
-- 'httpStatus', 'listDistributionsByWebACLIdResponse_httpStatus' - The response's http status code.
newListDistributionsByWebACLIdResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListDistributionsByWebACLIdResponse
newListDistributionsByWebACLIdResponse :: Int -> ListDistributionsByWebACLIdResponse
newListDistributionsByWebACLIdResponse Int
pHttpStatus_ =
  ListDistributionsByWebACLIdResponse'
    { $sel:distributionList:ListDistributionsByWebACLIdResponse' :: Maybe DistributionList
distributionList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListDistributionsByWebACLIdResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The @DistributionList@ type.
listDistributionsByWebACLIdResponse_distributionList :: Lens.Lens' ListDistributionsByWebACLIdResponse (Prelude.Maybe DistributionList)
listDistributionsByWebACLIdResponse_distributionList :: Lens' ListDistributionsByWebACLIdResponse (Maybe DistributionList)
listDistributionsByWebACLIdResponse_distributionList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDistributionsByWebACLIdResponse' {Maybe DistributionList
distributionList :: Maybe DistributionList
$sel:distributionList:ListDistributionsByWebACLIdResponse' :: ListDistributionsByWebACLIdResponse -> Maybe DistributionList
distributionList} -> Maybe DistributionList
distributionList) (\s :: ListDistributionsByWebACLIdResponse
s@ListDistributionsByWebACLIdResponse' {} Maybe DistributionList
a -> ListDistributionsByWebACLIdResponse
s {$sel:distributionList:ListDistributionsByWebACLIdResponse' :: Maybe DistributionList
distributionList = Maybe DistributionList
a} :: ListDistributionsByWebACLIdResponse)

-- | The response's http status code.
listDistributionsByWebACLIdResponse_httpStatus :: Lens.Lens' ListDistributionsByWebACLIdResponse Prelude.Int
listDistributionsByWebACLIdResponse_httpStatus :: Lens' ListDistributionsByWebACLIdResponse Int
listDistributionsByWebACLIdResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDistributionsByWebACLIdResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListDistributionsByWebACLIdResponse' :: ListDistributionsByWebACLIdResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListDistributionsByWebACLIdResponse
s@ListDistributionsByWebACLIdResponse' {} Int
a -> ListDistributionsByWebACLIdResponse
s {$sel:httpStatus:ListDistributionsByWebACLIdResponse' :: Int
httpStatus = Int
a} :: ListDistributionsByWebACLIdResponse)

instance
  Prelude.NFData
    ListDistributionsByWebACLIdResponse
  where
  rnf :: ListDistributionsByWebACLIdResponse -> ()
rnf ListDistributionsByWebACLIdResponse' {Int
Maybe DistributionList
httpStatus :: Int
distributionList :: Maybe DistributionList
$sel:httpStatus:ListDistributionsByWebACLIdResponse' :: ListDistributionsByWebACLIdResponse -> Int
$sel:distributionList:ListDistributionsByWebACLIdResponse' :: ListDistributionsByWebACLIdResponse -> Maybe DistributionList
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DistributionList
distributionList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus