{-# 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.ListFieldLevelEncryptionConfigs
-- 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 all field-level encryption configurations that have been created in
-- CloudFront for this account.
module Amazonka.CloudFront.ListFieldLevelEncryptionConfigs
  ( -- * Creating a Request
    ListFieldLevelEncryptionConfigs (..),
    newListFieldLevelEncryptionConfigs,

    -- * Request Lenses
    listFieldLevelEncryptionConfigs_marker,
    listFieldLevelEncryptionConfigs_maxItems,

    -- * Destructuring the Response
    ListFieldLevelEncryptionConfigsResponse (..),
    newListFieldLevelEncryptionConfigsResponse,

    -- * Response Lenses
    listFieldLevelEncryptionConfigsResponse_fieldLevelEncryptionList,
    listFieldLevelEncryptionConfigsResponse_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

-- | /See:/ 'newListFieldLevelEncryptionConfigs' smart constructor.
data ListFieldLevelEncryptionConfigs = ListFieldLevelEncryptionConfigs'
  { -- | Use this when paginating results to indicate where to begin in your list
    -- of configurations. The results include configurations in the list that
    -- occur after the marker. To get the next page of results, set the
    -- @Marker@ to the value of the @NextMarker@ from the current page\'s
    -- response (which is also the ID of the last configuration on that page).
    ListFieldLevelEncryptionConfigs -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of field-level encryption configurations you want in
    -- the response body.
    ListFieldLevelEncryptionConfigs -> Maybe Text
maxItems :: Prelude.Maybe Prelude.Text
  }
  deriving (ListFieldLevelEncryptionConfigs
-> ListFieldLevelEncryptionConfigs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFieldLevelEncryptionConfigs
-> ListFieldLevelEncryptionConfigs -> Bool
$c/= :: ListFieldLevelEncryptionConfigs
-> ListFieldLevelEncryptionConfigs -> Bool
== :: ListFieldLevelEncryptionConfigs
-> ListFieldLevelEncryptionConfigs -> Bool
$c== :: ListFieldLevelEncryptionConfigs
-> ListFieldLevelEncryptionConfigs -> Bool
Prelude.Eq, ReadPrec [ListFieldLevelEncryptionConfigs]
ReadPrec ListFieldLevelEncryptionConfigs
Int -> ReadS ListFieldLevelEncryptionConfigs
ReadS [ListFieldLevelEncryptionConfigs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFieldLevelEncryptionConfigs]
$creadListPrec :: ReadPrec [ListFieldLevelEncryptionConfigs]
readPrec :: ReadPrec ListFieldLevelEncryptionConfigs
$creadPrec :: ReadPrec ListFieldLevelEncryptionConfigs
readList :: ReadS [ListFieldLevelEncryptionConfigs]
$creadList :: ReadS [ListFieldLevelEncryptionConfigs]
readsPrec :: Int -> ReadS ListFieldLevelEncryptionConfigs
$creadsPrec :: Int -> ReadS ListFieldLevelEncryptionConfigs
Prelude.Read, Int -> ListFieldLevelEncryptionConfigs -> ShowS
[ListFieldLevelEncryptionConfigs] -> ShowS
ListFieldLevelEncryptionConfigs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFieldLevelEncryptionConfigs] -> ShowS
$cshowList :: [ListFieldLevelEncryptionConfigs] -> ShowS
show :: ListFieldLevelEncryptionConfigs -> String
$cshow :: ListFieldLevelEncryptionConfigs -> String
showsPrec :: Int -> ListFieldLevelEncryptionConfigs -> ShowS
$cshowsPrec :: Int -> ListFieldLevelEncryptionConfigs -> ShowS
Prelude.Show, forall x.
Rep ListFieldLevelEncryptionConfigs x
-> ListFieldLevelEncryptionConfigs
forall x.
ListFieldLevelEncryptionConfigs
-> Rep ListFieldLevelEncryptionConfigs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListFieldLevelEncryptionConfigs x
-> ListFieldLevelEncryptionConfigs
$cfrom :: forall x.
ListFieldLevelEncryptionConfigs
-> Rep ListFieldLevelEncryptionConfigs x
Prelude.Generic)

-- |
-- Create a value of 'ListFieldLevelEncryptionConfigs' 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', 'listFieldLevelEncryptionConfigs_marker' - Use this when paginating results to indicate where to begin in your list
-- of configurations. The results include configurations in the list that
-- occur after the marker. To get the next page of results, set the
-- @Marker@ to the value of the @NextMarker@ from the current page\'s
-- response (which is also the ID of the last configuration on that page).
--
-- 'maxItems', 'listFieldLevelEncryptionConfigs_maxItems' - The maximum number of field-level encryption configurations you want in
-- the response body.
newListFieldLevelEncryptionConfigs ::
  ListFieldLevelEncryptionConfigs
newListFieldLevelEncryptionConfigs :: ListFieldLevelEncryptionConfigs
newListFieldLevelEncryptionConfigs =
  ListFieldLevelEncryptionConfigs'
    { $sel:marker:ListFieldLevelEncryptionConfigs' :: Maybe Text
marker =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxItems:ListFieldLevelEncryptionConfigs' :: Maybe Text
maxItems = forall a. Maybe a
Prelude.Nothing
    }

-- | Use this when paginating results to indicate where to begin in your list
-- of configurations. The results include configurations in the list that
-- occur after the marker. To get the next page of results, set the
-- @Marker@ to the value of the @NextMarker@ from the current page\'s
-- response (which is also the ID of the last configuration on that page).
listFieldLevelEncryptionConfigs_marker :: Lens.Lens' ListFieldLevelEncryptionConfigs (Prelude.Maybe Prelude.Text)
listFieldLevelEncryptionConfigs_marker :: Lens' ListFieldLevelEncryptionConfigs (Maybe Text)
listFieldLevelEncryptionConfigs_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFieldLevelEncryptionConfigs' {Maybe Text
marker :: Maybe Text
$sel:marker:ListFieldLevelEncryptionConfigs' :: ListFieldLevelEncryptionConfigs -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListFieldLevelEncryptionConfigs
s@ListFieldLevelEncryptionConfigs' {} Maybe Text
a -> ListFieldLevelEncryptionConfigs
s {$sel:marker:ListFieldLevelEncryptionConfigs' :: Maybe Text
marker = Maybe Text
a} :: ListFieldLevelEncryptionConfigs)

-- | The maximum number of field-level encryption configurations you want in
-- the response body.
listFieldLevelEncryptionConfigs_maxItems :: Lens.Lens' ListFieldLevelEncryptionConfigs (Prelude.Maybe Prelude.Text)
listFieldLevelEncryptionConfigs_maxItems :: Lens' ListFieldLevelEncryptionConfigs (Maybe Text)
listFieldLevelEncryptionConfigs_maxItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFieldLevelEncryptionConfigs' {Maybe Text
maxItems :: Maybe Text
$sel:maxItems:ListFieldLevelEncryptionConfigs' :: ListFieldLevelEncryptionConfigs -> Maybe Text
maxItems} -> Maybe Text
maxItems) (\s :: ListFieldLevelEncryptionConfigs
s@ListFieldLevelEncryptionConfigs' {} Maybe Text
a -> ListFieldLevelEncryptionConfigs
s {$sel:maxItems:ListFieldLevelEncryptionConfigs' :: Maybe Text
maxItems = Maybe Text
a} :: ListFieldLevelEncryptionConfigs)

instance
  Core.AWSRequest
    ListFieldLevelEncryptionConfigs
  where
  type
    AWSResponse ListFieldLevelEncryptionConfigs =
      ListFieldLevelEncryptionConfigsResponse
  request :: (Service -> Service)
-> ListFieldLevelEncryptionConfigs
-> Request ListFieldLevelEncryptionConfigs
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 ListFieldLevelEncryptionConfigs
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse ListFieldLevelEncryptionConfigs)))
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 FieldLevelEncryptionList
-> Int -> ListFieldLevelEncryptionConfigsResponse
ListFieldLevelEncryptionConfigsResponse'
            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
    ListFieldLevelEncryptionConfigs
  where
  hashWithSalt :: Int -> ListFieldLevelEncryptionConfigs -> Int
hashWithSalt
    Int
_salt
    ListFieldLevelEncryptionConfigs' {Maybe Text
maxItems :: Maybe Text
marker :: Maybe Text
$sel:maxItems:ListFieldLevelEncryptionConfigs' :: ListFieldLevelEncryptionConfigs -> Maybe Text
$sel:marker:ListFieldLevelEncryptionConfigs' :: ListFieldLevelEncryptionConfigs -> 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

instance
  Prelude.NFData
    ListFieldLevelEncryptionConfigs
  where
  rnf :: ListFieldLevelEncryptionConfigs -> ()
rnf ListFieldLevelEncryptionConfigs' {Maybe Text
maxItems :: Maybe Text
marker :: Maybe Text
$sel:maxItems:ListFieldLevelEncryptionConfigs' :: ListFieldLevelEncryptionConfigs -> Maybe Text
$sel:marker:ListFieldLevelEncryptionConfigs' :: ListFieldLevelEncryptionConfigs -> 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

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

instance Data.ToPath ListFieldLevelEncryptionConfigs where
  toPath :: ListFieldLevelEncryptionConfigs -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/2020-05-31/field-level-encryption"

instance Data.ToQuery ListFieldLevelEncryptionConfigs where
  toQuery :: ListFieldLevelEncryptionConfigs -> QueryString
toQuery ListFieldLevelEncryptionConfigs' {Maybe Text
maxItems :: Maybe Text
marker :: Maybe Text
$sel:maxItems:ListFieldLevelEncryptionConfigs' :: ListFieldLevelEncryptionConfigs -> Maybe Text
$sel:marker:ListFieldLevelEncryptionConfigs' :: ListFieldLevelEncryptionConfigs -> 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
      ]

-- | /See:/ 'newListFieldLevelEncryptionConfigsResponse' smart constructor.
data ListFieldLevelEncryptionConfigsResponse = ListFieldLevelEncryptionConfigsResponse'
  { -- | Returns a list of all field-level encryption configurations that have
    -- been created in CloudFront for this account.
    ListFieldLevelEncryptionConfigsResponse
-> Maybe FieldLevelEncryptionList
fieldLevelEncryptionList :: Prelude.Maybe FieldLevelEncryptionList,
    -- | The response's http status code.
    ListFieldLevelEncryptionConfigsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListFieldLevelEncryptionConfigsResponse
-> ListFieldLevelEncryptionConfigsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFieldLevelEncryptionConfigsResponse
-> ListFieldLevelEncryptionConfigsResponse -> Bool
$c/= :: ListFieldLevelEncryptionConfigsResponse
-> ListFieldLevelEncryptionConfigsResponse -> Bool
== :: ListFieldLevelEncryptionConfigsResponse
-> ListFieldLevelEncryptionConfigsResponse -> Bool
$c== :: ListFieldLevelEncryptionConfigsResponse
-> ListFieldLevelEncryptionConfigsResponse -> Bool
Prelude.Eq, ReadPrec [ListFieldLevelEncryptionConfigsResponse]
ReadPrec ListFieldLevelEncryptionConfigsResponse
Int -> ReadS ListFieldLevelEncryptionConfigsResponse
ReadS [ListFieldLevelEncryptionConfigsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFieldLevelEncryptionConfigsResponse]
$creadListPrec :: ReadPrec [ListFieldLevelEncryptionConfigsResponse]
readPrec :: ReadPrec ListFieldLevelEncryptionConfigsResponse
$creadPrec :: ReadPrec ListFieldLevelEncryptionConfigsResponse
readList :: ReadS [ListFieldLevelEncryptionConfigsResponse]
$creadList :: ReadS [ListFieldLevelEncryptionConfigsResponse]
readsPrec :: Int -> ReadS ListFieldLevelEncryptionConfigsResponse
$creadsPrec :: Int -> ReadS ListFieldLevelEncryptionConfigsResponse
Prelude.Read, Int -> ListFieldLevelEncryptionConfigsResponse -> ShowS
[ListFieldLevelEncryptionConfigsResponse] -> ShowS
ListFieldLevelEncryptionConfigsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFieldLevelEncryptionConfigsResponse] -> ShowS
$cshowList :: [ListFieldLevelEncryptionConfigsResponse] -> ShowS
show :: ListFieldLevelEncryptionConfigsResponse -> String
$cshow :: ListFieldLevelEncryptionConfigsResponse -> String
showsPrec :: Int -> ListFieldLevelEncryptionConfigsResponse -> ShowS
$cshowsPrec :: Int -> ListFieldLevelEncryptionConfigsResponse -> ShowS
Prelude.Show, forall x.
Rep ListFieldLevelEncryptionConfigsResponse x
-> ListFieldLevelEncryptionConfigsResponse
forall x.
ListFieldLevelEncryptionConfigsResponse
-> Rep ListFieldLevelEncryptionConfigsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListFieldLevelEncryptionConfigsResponse x
-> ListFieldLevelEncryptionConfigsResponse
$cfrom :: forall x.
ListFieldLevelEncryptionConfigsResponse
-> Rep ListFieldLevelEncryptionConfigsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListFieldLevelEncryptionConfigsResponse' 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:
--
-- 'fieldLevelEncryptionList', 'listFieldLevelEncryptionConfigsResponse_fieldLevelEncryptionList' - Returns a list of all field-level encryption configurations that have
-- been created in CloudFront for this account.
--
-- 'httpStatus', 'listFieldLevelEncryptionConfigsResponse_httpStatus' - The response's http status code.
newListFieldLevelEncryptionConfigsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListFieldLevelEncryptionConfigsResponse
newListFieldLevelEncryptionConfigsResponse :: Int -> ListFieldLevelEncryptionConfigsResponse
newListFieldLevelEncryptionConfigsResponse
  Int
pHttpStatus_ =
    ListFieldLevelEncryptionConfigsResponse'
      { $sel:fieldLevelEncryptionList:ListFieldLevelEncryptionConfigsResponse' :: Maybe FieldLevelEncryptionList
fieldLevelEncryptionList =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ListFieldLevelEncryptionConfigsResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Returns a list of all field-level encryption configurations that have
-- been created in CloudFront for this account.
listFieldLevelEncryptionConfigsResponse_fieldLevelEncryptionList :: Lens.Lens' ListFieldLevelEncryptionConfigsResponse (Prelude.Maybe FieldLevelEncryptionList)
listFieldLevelEncryptionConfigsResponse_fieldLevelEncryptionList :: Lens'
  ListFieldLevelEncryptionConfigsResponse
  (Maybe FieldLevelEncryptionList)
listFieldLevelEncryptionConfigsResponse_fieldLevelEncryptionList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFieldLevelEncryptionConfigsResponse' {Maybe FieldLevelEncryptionList
fieldLevelEncryptionList :: Maybe FieldLevelEncryptionList
$sel:fieldLevelEncryptionList:ListFieldLevelEncryptionConfigsResponse' :: ListFieldLevelEncryptionConfigsResponse
-> Maybe FieldLevelEncryptionList
fieldLevelEncryptionList} -> Maybe FieldLevelEncryptionList
fieldLevelEncryptionList) (\s :: ListFieldLevelEncryptionConfigsResponse
s@ListFieldLevelEncryptionConfigsResponse' {} Maybe FieldLevelEncryptionList
a -> ListFieldLevelEncryptionConfigsResponse
s {$sel:fieldLevelEncryptionList:ListFieldLevelEncryptionConfigsResponse' :: Maybe FieldLevelEncryptionList
fieldLevelEncryptionList = Maybe FieldLevelEncryptionList
a} :: ListFieldLevelEncryptionConfigsResponse)

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

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