{-# 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.MediaPackage.ListOriginEndpoints
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a collection of OriginEndpoint records.
--
-- This operation returns paginated results.
module Amazonka.MediaPackage.ListOriginEndpoints
  ( -- * Creating a Request
    ListOriginEndpoints (..),
    newListOriginEndpoints,

    -- * Request Lenses
    listOriginEndpoints_channelId,
    listOriginEndpoints_maxResults,
    listOriginEndpoints_nextToken,

    -- * Destructuring the Response
    ListOriginEndpointsResponse (..),
    newListOriginEndpointsResponse,

    -- * Response Lenses
    listOriginEndpointsResponse_nextToken,
    listOriginEndpointsResponse_originEndpoints,
    listOriginEndpointsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MediaPackage.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListOriginEndpoints' smart constructor.
data ListOriginEndpoints = ListOriginEndpoints'
  { -- | When specified, the request will return only OriginEndpoints associated
    -- with the given Channel ID.
    ListOriginEndpoints -> Maybe Text
channelId :: Prelude.Maybe Prelude.Text,
    -- | The upper bound on the number of records to return.
    ListOriginEndpoints -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A token used to resume pagination from the end of a previous request.
    ListOriginEndpoints -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListOriginEndpoints -> ListOriginEndpoints -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListOriginEndpoints -> ListOriginEndpoints -> Bool
$c/= :: ListOriginEndpoints -> ListOriginEndpoints -> Bool
== :: ListOriginEndpoints -> ListOriginEndpoints -> Bool
$c== :: ListOriginEndpoints -> ListOriginEndpoints -> Bool
Prelude.Eq, ReadPrec [ListOriginEndpoints]
ReadPrec ListOriginEndpoints
Int -> ReadS ListOriginEndpoints
ReadS [ListOriginEndpoints]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListOriginEndpoints]
$creadListPrec :: ReadPrec [ListOriginEndpoints]
readPrec :: ReadPrec ListOriginEndpoints
$creadPrec :: ReadPrec ListOriginEndpoints
readList :: ReadS [ListOriginEndpoints]
$creadList :: ReadS [ListOriginEndpoints]
readsPrec :: Int -> ReadS ListOriginEndpoints
$creadsPrec :: Int -> ReadS ListOriginEndpoints
Prelude.Read, Int -> ListOriginEndpoints -> ShowS
[ListOriginEndpoints] -> ShowS
ListOriginEndpoints -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListOriginEndpoints] -> ShowS
$cshowList :: [ListOriginEndpoints] -> ShowS
show :: ListOriginEndpoints -> String
$cshow :: ListOriginEndpoints -> String
showsPrec :: Int -> ListOriginEndpoints -> ShowS
$cshowsPrec :: Int -> ListOriginEndpoints -> ShowS
Prelude.Show, forall x. Rep ListOriginEndpoints x -> ListOriginEndpoints
forall x. ListOriginEndpoints -> Rep ListOriginEndpoints x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListOriginEndpoints x -> ListOriginEndpoints
$cfrom :: forall x. ListOriginEndpoints -> Rep ListOriginEndpoints x
Prelude.Generic)

-- |
-- Create a value of 'ListOriginEndpoints' 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:
--
-- 'channelId', 'listOriginEndpoints_channelId' - When specified, the request will return only OriginEndpoints associated
-- with the given Channel ID.
--
-- 'maxResults', 'listOriginEndpoints_maxResults' - The upper bound on the number of records to return.
--
-- 'nextToken', 'listOriginEndpoints_nextToken' - A token used to resume pagination from the end of a previous request.
newListOriginEndpoints ::
  ListOriginEndpoints
newListOriginEndpoints :: ListOriginEndpoints
newListOriginEndpoints =
  ListOriginEndpoints'
    { $sel:channelId:ListOriginEndpoints' :: Maybe Text
channelId = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListOriginEndpoints' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListOriginEndpoints' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | When specified, the request will return only OriginEndpoints associated
-- with the given Channel ID.
listOriginEndpoints_channelId :: Lens.Lens' ListOriginEndpoints (Prelude.Maybe Prelude.Text)
listOriginEndpoints_channelId :: Lens' ListOriginEndpoints (Maybe Text)
listOriginEndpoints_channelId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListOriginEndpoints' {Maybe Text
channelId :: Maybe Text
$sel:channelId:ListOriginEndpoints' :: ListOriginEndpoints -> Maybe Text
channelId} -> Maybe Text
channelId) (\s :: ListOriginEndpoints
s@ListOriginEndpoints' {} Maybe Text
a -> ListOriginEndpoints
s {$sel:channelId:ListOriginEndpoints' :: Maybe Text
channelId = Maybe Text
a} :: ListOriginEndpoints)

-- | The upper bound on the number of records to return.
listOriginEndpoints_maxResults :: Lens.Lens' ListOriginEndpoints (Prelude.Maybe Prelude.Natural)
listOriginEndpoints_maxResults :: Lens' ListOriginEndpoints (Maybe Natural)
listOriginEndpoints_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListOriginEndpoints' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListOriginEndpoints' :: ListOriginEndpoints -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListOriginEndpoints
s@ListOriginEndpoints' {} Maybe Natural
a -> ListOriginEndpoints
s {$sel:maxResults:ListOriginEndpoints' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListOriginEndpoints)

-- | A token used to resume pagination from the end of a previous request.
listOriginEndpoints_nextToken :: Lens.Lens' ListOriginEndpoints (Prelude.Maybe Prelude.Text)
listOriginEndpoints_nextToken :: Lens' ListOriginEndpoints (Maybe Text)
listOriginEndpoints_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListOriginEndpoints' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListOriginEndpoints' :: ListOriginEndpoints -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListOriginEndpoints
s@ListOriginEndpoints' {} Maybe Text
a -> ListOriginEndpoints
s {$sel:nextToken:ListOriginEndpoints' :: Maybe Text
nextToken = Maybe Text
a} :: ListOriginEndpoints)

instance Core.AWSPager ListOriginEndpoints where
  page :: ListOriginEndpoints
-> AWSResponse ListOriginEndpoints -> Maybe ListOriginEndpoints
page ListOriginEndpoints
rq AWSResponse ListOriginEndpoints
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListOriginEndpoints
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListOriginEndpointsResponse (Maybe Text)
listOriginEndpointsResponse_nextToken
            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 ListOriginEndpoints
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListOriginEndpointsResponse (Maybe [OriginEndpoint])
listOriginEndpointsResponse_originEndpoints
            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.$ ListOriginEndpoints
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListOriginEndpoints (Maybe Text)
listOriginEndpoints_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListOriginEndpoints
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListOriginEndpointsResponse (Maybe Text)
listOriginEndpointsResponse_nextToken
          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 ListOriginEndpoints where
  type
    AWSResponse ListOriginEndpoints =
      ListOriginEndpointsResponse
  request :: (Service -> Service)
-> ListOriginEndpoints -> Request ListOriginEndpoints
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 ListOriginEndpoints
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListOriginEndpoints)))
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 Text
-> Maybe [OriginEndpoint] -> Int -> ListOriginEndpointsResponse
ListOriginEndpointsResponse'
            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
"nextToken")
            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
"originEndpoints"
                            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListOriginEndpoints where
  hashWithSalt :: Int -> ListOriginEndpoints -> Int
hashWithSalt Int
_salt ListOriginEndpoints' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
channelId :: Maybe Text
$sel:nextToken:ListOriginEndpoints' :: ListOriginEndpoints -> Maybe Text
$sel:maxResults:ListOriginEndpoints' :: ListOriginEndpoints -> Maybe Natural
$sel:channelId:ListOriginEndpoints' :: ListOriginEndpoints -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
channelId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListOriginEndpoints where
  rnf :: ListOriginEndpoints -> ()
rnf ListOriginEndpoints' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
channelId :: Maybe Text
$sel:nextToken:ListOriginEndpoints' :: ListOriginEndpoints -> Maybe Text
$sel:maxResults:ListOriginEndpoints' :: ListOriginEndpoints -> Maybe Natural
$sel:channelId:ListOriginEndpoints' :: ListOriginEndpoints -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
channelId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

instance Data.ToHeaders ListOriginEndpoints where
  toHeaders :: ListOriginEndpoints -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath ListOriginEndpoints where
  toPath :: ListOriginEndpoints -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/origin_endpoints"

instance Data.ToQuery ListOriginEndpoints where
  toQuery :: ListOriginEndpoints -> QueryString
toQuery ListOriginEndpoints' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
channelId :: Maybe Text
$sel:nextToken:ListOriginEndpoints' :: ListOriginEndpoints -> Maybe Text
$sel:maxResults:ListOriginEndpoints' :: ListOriginEndpoints -> Maybe Natural
$sel:channelId:ListOriginEndpoints' :: ListOriginEndpoints -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"channelId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
channelId,
        ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newListOriginEndpointsResponse' smart constructor.
data ListOriginEndpointsResponse = ListOriginEndpointsResponse'
  { -- | A token that can be used to resume pagination from the end of the
    -- collection.
    ListOriginEndpointsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of OriginEndpoint records.
    ListOriginEndpointsResponse -> Maybe [OriginEndpoint]
originEndpoints :: Prelude.Maybe [OriginEndpoint],
    -- | The response's http status code.
    ListOriginEndpointsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListOriginEndpointsResponse -> ListOriginEndpointsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListOriginEndpointsResponse -> ListOriginEndpointsResponse -> Bool
$c/= :: ListOriginEndpointsResponse -> ListOriginEndpointsResponse -> Bool
== :: ListOriginEndpointsResponse -> ListOriginEndpointsResponse -> Bool
$c== :: ListOriginEndpointsResponse -> ListOriginEndpointsResponse -> Bool
Prelude.Eq, ReadPrec [ListOriginEndpointsResponse]
ReadPrec ListOriginEndpointsResponse
Int -> ReadS ListOriginEndpointsResponse
ReadS [ListOriginEndpointsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListOriginEndpointsResponse]
$creadListPrec :: ReadPrec [ListOriginEndpointsResponse]
readPrec :: ReadPrec ListOriginEndpointsResponse
$creadPrec :: ReadPrec ListOriginEndpointsResponse
readList :: ReadS [ListOriginEndpointsResponse]
$creadList :: ReadS [ListOriginEndpointsResponse]
readsPrec :: Int -> ReadS ListOriginEndpointsResponse
$creadsPrec :: Int -> ReadS ListOriginEndpointsResponse
Prelude.Read, Int -> ListOriginEndpointsResponse -> ShowS
[ListOriginEndpointsResponse] -> ShowS
ListOriginEndpointsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListOriginEndpointsResponse] -> ShowS
$cshowList :: [ListOriginEndpointsResponse] -> ShowS
show :: ListOriginEndpointsResponse -> String
$cshow :: ListOriginEndpointsResponse -> String
showsPrec :: Int -> ListOriginEndpointsResponse -> ShowS
$cshowsPrec :: Int -> ListOriginEndpointsResponse -> ShowS
Prelude.Show, forall x.
Rep ListOriginEndpointsResponse x -> ListOriginEndpointsResponse
forall x.
ListOriginEndpointsResponse -> Rep ListOriginEndpointsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListOriginEndpointsResponse x -> ListOriginEndpointsResponse
$cfrom :: forall x.
ListOriginEndpointsResponse -> Rep ListOriginEndpointsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListOriginEndpointsResponse' 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:
--
-- 'nextToken', 'listOriginEndpointsResponse_nextToken' - A token that can be used to resume pagination from the end of the
-- collection.
--
-- 'originEndpoints', 'listOriginEndpointsResponse_originEndpoints' - A list of OriginEndpoint records.
--
-- 'httpStatus', 'listOriginEndpointsResponse_httpStatus' - The response's http status code.
newListOriginEndpointsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListOriginEndpointsResponse
newListOriginEndpointsResponse :: Int -> ListOriginEndpointsResponse
newListOriginEndpointsResponse Int
pHttpStatus_ =
  ListOriginEndpointsResponse'
    { $sel:nextToken:ListOriginEndpointsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:originEndpoints:ListOriginEndpointsResponse' :: Maybe [OriginEndpoint]
originEndpoints = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListOriginEndpointsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A token that can be used to resume pagination from the end of the
-- collection.
listOriginEndpointsResponse_nextToken :: Lens.Lens' ListOriginEndpointsResponse (Prelude.Maybe Prelude.Text)
listOriginEndpointsResponse_nextToken :: Lens' ListOriginEndpointsResponse (Maybe Text)
listOriginEndpointsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListOriginEndpointsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListOriginEndpointsResponse' :: ListOriginEndpointsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListOriginEndpointsResponse
s@ListOriginEndpointsResponse' {} Maybe Text
a -> ListOriginEndpointsResponse
s {$sel:nextToken:ListOriginEndpointsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListOriginEndpointsResponse)

-- | A list of OriginEndpoint records.
listOriginEndpointsResponse_originEndpoints :: Lens.Lens' ListOriginEndpointsResponse (Prelude.Maybe [OriginEndpoint])
listOriginEndpointsResponse_originEndpoints :: Lens' ListOriginEndpointsResponse (Maybe [OriginEndpoint])
listOriginEndpointsResponse_originEndpoints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListOriginEndpointsResponse' {Maybe [OriginEndpoint]
originEndpoints :: Maybe [OriginEndpoint]
$sel:originEndpoints:ListOriginEndpointsResponse' :: ListOriginEndpointsResponse -> Maybe [OriginEndpoint]
originEndpoints} -> Maybe [OriginEndpoint]
originEndpoints) (\s :: ListOriginEndpointsResponse
s@ListOriginEndpointsResponse' {} Maybe [OriginEndpoint]
a -> ListOriginEndpointsResponse
s {$sel:originEndpoints:ListOriginEndpointsResponse' :: Maybe [OriginEndpoint]
originEndpoints = Maybe [OriginEndpoint]
a} :: ListOriginEndpointsResponse) 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

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

instance Prelude.NFData ListOriginEndpointsResponse where
  rnf :: ListOriginEndpointsResponse -> ()
rnf ListOriginEndpointsResponse' {Int
Maybe [OriginEndpoint]
Maybe Text
httpStatus :: Int
originEndpoints :: Maybe [OriginEndpoint]
nextToken :: Maybe Text
$sel:httpStatus:ListOriginEndpointsResponse' :: ListOriginEndpointsResponse -> Int
$sel:originEndpoints:ListOriginEndpointsResponse' :: ListOriginEndpointsResponse -> Maybe [OriginEndpoint]
$sel:nextToken:ListOriginEndpointsResponse' :: ListOriginEndpointsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [OriginEndpoint]
originEndpoints
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus