{-# 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.ListFunctions
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets a list of all CloudFront functions in your Amazon Web Services
-- account.
--
-- You can optionally apply a filter to return only the functions that are
-- in the specified stage, either @DEVELOPMENT@ or @LIVE@.
--
-- You can optionally specify the maximum number of items to receive in the
-- response. If the total number of items in the list exceeds the maximum
-- that you specify, or the default maximum, the response is paginated. To
-- get the next page of items, send a subsequent request that specifies the
-- @NextMarker@ value from the current response as the @Marker@ value in
-- the subsequent request.
module Amazonka.CloudFront.ListFunctions
  ( -- * Creating a Request
    ListFunctions (..),
    newListFunctions,

    -- * Request Lenses
    listFunctions_marker,
    listFunctions_maxItems,
    listFunctions_stage,

    -- * Destructuring the Response
    ListFunctionsResponse (..),
    newListFunctionsResponse,

    -- * Response Lenses
    listFunctionsResponse_functionList,
    listFunctionsResponse_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:/ 'newListFunctions' smart constructor.
data ListFunctions = ListFunctions'
  { -- | Use this field when paginating results to indicate where to begin in
    -- your list of functions. The response includes functions in the list that
    -- occur after the marker. To get the next page of the list, set this
    -- field\'s value to the value of @NextMarker@ from the current page\'s
    -- response.
    ListFunctions -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of functions that you want in the response.
    ListFunctions -> Maybe Text
maxItems :: Prelude.Maybe Prelude.Text,
    -- | An optional filter to return only the functions that are in the
    -- specified stage, either @DEVELOPMENT@ or @LIVE@.
    ListFunctions -> Maybe FunctionStage
stage :: Prelude.Maybe FunctionStage
  }
  deriving (ListFunctions -> ListFunctions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFunctions -> ListFunctions -> Bool
$c/= :: ListFunctions -> ListFunctions -> Bool
== :: ListFunctions -> ListFunctions -> Bool
$c== :: ListFunctions -> ListFunctions -> Bool
Prelude.Eq, ReadPrec [ListFunctions]
ReadPrec ListFunctions
Int -> ReadS ListFunctions
ReadS [ListFunctions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFunctions]
$creadListPrec :: ReadPrec [ListFunctions]
readPrec :: ReadPrec ListFunctions
$creadPrec :: ReadPrec ListFunctions
readList :: ReadS [ListFunctions]
$creadList :: ReadS [ListFunctions]
readsPrec :: Int -> ReadS ListFunctions
$creadsPrec :: Int -> ReadS ListFunctions
Prelude.Read, Int -> ListFunctions -> ShowS
[ListFunctions] -> ShowS
ListFunctions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFunctions] -> ShowS
$cshowList :: [ListFunctions] -> ShowS
show :: ListFunctions -> String
$cshow :: ListFunctions -> String
showsPrec :: Int -> ListFunctions -> ShowS
$cshowsPrec :: Int -> ListFunctions -> ShowS
Prelude.Show, forall x. Rep ListFunctions x -> ListFunctions
forall x. ListFunctions -> Rep ListFunctions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListFunctions x -> ListFunctions
$cfrom :: forall x. ListFunctions -> Rep ListFunctions x
Prelude.Generic)

-- |
-- Create a value of 'ListFunctions' 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', 'listFunctions_marker' - Use this field when paginating results to indicate where to begin in
-- your list of functions. The response includes functions in the list that
-- occur after the marker. To get the next page of the list, set this
-- field\'s value to the value of @NextMarker@ from the current page\'s
-- response.
--
-- 'maxItems', 'listFunctions_maxItems' - The maximum number of functions that you want in the response.
--
-- 'stage', 'listFunctions_stage' - An optional filter to return only the functions that are in the
-- specified stage, either @DEVELOPMENT@ or @LIVE@.
newListFunctions ::
  ListFunctions
newListFunctions :: ListFunctions
newListFunctions =
  ListFunctions'
    { $sel:marker:ListFunctions' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:maxItems:ListFunctions' :: Maybe Text
maxItems = forall a. Maybe a
Prelude.Nothing,
      $sel:stage:ListFunctions' :: Maybe FunctionStage
stage = forall a. Maybe a
Prelude.Nothing
    }

-- | Use this field when paginating results to indicate where to begin in
-- your list of functions. The response includes functions in the list that
-- occur after the marker. To get the next page of the list, set this
-- field\'s value to the value of @NextMarker@ from the current page\'s
-- response.
listFunctions_marker :: Lens.Lens' ListFunctions (Prelude.Maybe Prelude.Text)
listFunctions_marker :: Lens' ListFunctions (Maybe Text)
listFunctions_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFunctions' {Maybe Text
marker :: Maybe Text
$sel:marker:ListFunctions' :: ListFunctions -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListFunctions
s@ListFunctions' {} Maybe Text
a -> ListFunctions
s {$sel:marker:ListFunctions' :: Maybe Text
marker = Maybe Text
a} :: ListFunctions)

-- | The maximum number of functions that you want in the response.
listFunctions_maxItems :: Lens.Lens' ListFunctions (Prelude.Maybe Prelude.Text)
listFunctions_maxItems :: Lens' ListFunctions (Maybe Text)
listFunctions_maxItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFunctions' {Maybe Text
maxItems :: Maybe Text
$sel:maxItems:ListFunctions' :: ListFunctions -> Maybe Text
maxItems} -> Maybe Text
maxItems) (\s :: ListFunctions
s@ListFunctions' {} Maybe Text
a -> ListFunctions
s {$sel:maxItems:ListFunctions' :: Maybe Text
maxItems = Maybe Text
a} :: ListFunctions)

-- | An optional filter to return only the functions that are in the
-- specified stage, either @DEVELOPMENT@ or @LIVE@.
listFunctions_stage :: Lens.Lens' ListFunctions (Prelude.Maybe FunctionStage)
listFunctions_stage :: Lens' ListFunctions (Maybe FunctionStage)
listFunctions_stage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFunctions' {Maybe FunctionStage
stage :: Maybe FunctionStage
$sel:stage:ListFunctions' :: ListFunctions -> Maybe FunctionStage
stage} -> Maybe FunctionStage
stage) (\s :: ListFunctions
s@ListFunctions' {} Maybe FunctionStage
a -> ListFunctions
s {$sel:stage:ListFunctions' :: Maybe FunctionStage
stage = Maybe FunctionStage
a} :: ListFunctions)

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

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

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

instance Data.ToPath ListFunctions where
  toPath :: ListFunctions -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/2020-05-31/function"

instance Data.ToQuery ListFunctions where
  toQuery :: ListFunctions -> QueryString
toQuery ListFunctions' {Maybe Text
Maybe FunctionStage
stage :: Maybe FunctionStage
maxItems :: Maybe Text
marker :: Maybe Text
$sel:stage:ListFunctions' :: ListFunctions -> Maybe FunctionStage
$sel:maxItems:ListFunctions' :: ListFunctions -> Maybe Text
$sel:marker:ListFunctions' :: ListFunctions -> 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,
        ByteString
"Stage" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe FunctionStage
stage
      ]

-- | /See:/ 'newListFunctionsResponse' smart constructor.
data ListFunctionsResponse = ListFunctionsResponse'
  { -- | A list of CloudFront functions.
    ListFunctionsResponse -> Maybe FunctionList
functionList :: Prelude.Maybe FunctionList,
    -- | The response's http status code.
    ListFunctionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListFunctionsResponse -> ListFunctionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFunctionsResponse -> ListFunctionsResponse -> Bool
$c/= :: ListFunctionsResponse -> ListFunctionsResponse -> Bool
== :: ListFunctionsResponse -> ListFunctionsResponse -> Bool
$c== :: ListFunctionsResponse -> ListFunctionsResponse -> Bool
Prelude.Eq, ReadPrec [ListFunctionsResponse]
ReadPrec ListFunctionsResponse
Int -> ReadS ListFunctionsResponse
ReadS [ListFunctionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFunctionsResponse]
$creadListPrec :: ReadPrec [ListFunctionsResponse]
readPrec :: ReadPrec ListFunctionsResponse
$creadPrec :: ReadPrec ListFunctionsResponse
readList :: ReadS [ListFunctionsResponse]
$creadList :: ReadS [ListFunctionsResponse]
readsPrec :: Int -> ReadS ListFunctionsResponse
$creadsPrec :: Int -> ReadS ListFunctionsResponse
Prelude.Read, Int -> ListFunctionsResponse -> ShowS
[ListFunctionsResponse] -> ShowS
ListFunctionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFunctionsResponse] -> ShowS
$cshowList :: [ListFunctionsResponse] -> ShowS
show :: ListFunctionsResponse -> String
$cshow :: ListFunctionsResponse -> String
showsPrec :: Int -> ListFunctionsResponse -> ShowS
$cshowsPrec :: Int -> ListFunctionsResponse -> ShowS
Prelude.Show, forall x. Rep ListFunctionsResponse x -> ListFunctionsResponse
forall x. ListFunctionsResponse -> Rep ListFunctionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListFunctionsResponse x -> ListFunctionsResponse
$cfrom :: forall x. ListFunctionsResponse -> Rep ListFunctionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListFunctionsResponse' 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:
--
-- 'functionList', 'listFunctionsResponse_functionList' - A list of CloudFront functions.
--
-- 'httpStatus', 'listFunctionsResponse_httpStatus' - The response's http status code.
newListFunctionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListFunctionsResponse
newListFunctionsResponse :: Int -> ListFunctionsResponse
newListFunctionsResponse Int
pHttpStatus_ =
  ListFunctionsResponse'
    { $sel:functionList:ListFunctionsResponse' :: Maybe FunctionList
functionList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListFunctionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of CloudFront functions.
listFunctionsResponse_functionList :: Lens.Lens' ListFunctionsResponse (Prelude.Maybe FunctionList)
listFunctionsResponse_functionList :: Lens' ListFunctionsResponse (Maybe FunctionList)
listFunctionsResponse_functionList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFunctionsResponse' {Maybe FunctionList
functionList :: Maybe FunctionList
$sel:functionList:ListFunctionsResponse' :: ListFunctionsResponse -> Maybe FunctionList
functionList} -> Maybe FunctionList
functionList) (\s :: ListFunctionsResponse
s@ListFunctionsResponse' {} Maybe FunctionList
a -> ListFunctionsResponse
s {$sel:functionList:ListFunctionsResponse' :: Maybe FunctionList
functionList = Maybe FunctionList
a} :: ListFunctionsResponse)

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

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