{-# 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.Route53RecoveryCluster.ListRoutingControls
-- 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 routing control names and Amazon Resource Names (ARNs), as well as
-- the routing control state for each routing control, along with the
-- control panel name and control panel ARN for the routing controls. If
-- you specify a control panel ARN, this call lists the routing controls in
-- the control panel. Otherwise, it lists all the routing controls in the
-- cluster.
--
-- A routing control is a simple on\/off switch in Route 53 ARC that you
-- can use to route traffic to cells. When a routing control state is On,
-- traffic flows to a cell. When the state is Off, traffic does not flow.
--
-- Before you can create a routing control, you must first create a
-- cluster, and then host the control in a control panel on the cluster.
-- For more information, see
-- <https://docs.aws.amazon.com/r53recovery/latest/dg/routing-control.create.html Create routing control structures>
-- in the Amazon Route 53 Application Recovery Controller Developer Guide.
-- You access one of the endpoints for the cluster to get or update the
-- routing control state to redirect traffic for your application.
--
-- /You must specify Regional endpoints when you work with API cluster
-- operations to use this API operation to list routing controls in Route
-- 53 ARC./
--
-- Learn more about working with routing controls in the following topics
-- in the Amazon Route 53 Application Recovery Controller Developer Guide:
--
-- -   <https://docs.aws.amazon.com/r53recovery/latest/dg/routing-control.update.html Viewing and updating routing control states>
--
-- -   <https://docs.aws.amazon.com/r53recovery/latest/dg/routing-control.html Working with routing controls in Route 53 ARC>
--
-- This operation returns paginated results.
module Amazonka.Route53RecoveryCluster.ListRoutingControls
  ( -- * Creating a Request
    ListRoutingControls (..),
    newListRoutingControls,

    -- * Request Lenses
    listRoutingControls_controlPanelArn,
    listRoutingControls_maxResults,
    listRoutingControls_nextToken,

    -- * Destructuring the Response
    ListRoutingControlsResponse (..),
    newListRoutingControlsResponse,

    -- * Response Lenses
    listRoutingControlsResponse_nextToken,
    listRoutingControlsResponse_httpStatus,
    listRoutingControlsResponse_routingControls,
  )
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.Route53RecoveryCluster.Types

-- | /See:/ 'newListRoutingControls' smart constructor.
data ListRoutingControls = ListRoutingControls'
  { -- | The Amazon Resource Name (ARN) of the control panel of the routing
    -- controls to list.
    ListRoutingControls -> Maybe Text
controlPanelArn :: Prelude.Maybe Prelude.Text,
    -- | The number of routing controls objects that you want to return with this
    -- call. The default value is 500.
    ListRoutingControls -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token for the next set of results. You receive this token from a
    -- previous call.
    ListRoutingControls -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListRoutingControls -> ListRoutingControls -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListRoutingControls -> ListRoutingControls -> Bool
$c/= :: ListRoutingControls -> ListRoutingControls -> Bool
== :: ListRoutingControls -> ListRoutingControls -> Bool
$c== :: ListRoutingControls -> ListRoutingControls -> Bool
Prelude.Eq, ReadPrec [ListRoutingControls]
ReadPrec ListRoutingControls
Int -> ReadS ListRoutingControls
ReadS [ListRoutingControls]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListRoutingControls]
$creadListPrec :: ReadPrec [ListRoutingControls]
readPrec :: ReadPrec ListRoutingControls
$creadPrec :: ReadPrec ListRoutingControls
readList :: ReadS [ListRoutingControls]
$creadList :: ReadS [ListRoutingControls]
readsPrec :: Int -> ReadS ListRoutingControls
$creadsPrec :: Int -> ReadS ListRoutingControls
Prelude.Read, Int -> ListRoutingControls -> ShowS
[ListRoutingControls] -> ShowS
ListRoutingControls -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListRoutingControls] -> ShowS
$cshowList :: [ListRoutingControls] -> ShowS
show :: ListRoutingControls -> String
$cshow :: ListRoutingControls -> String
showsPrec :: Int -> ListRoutingControls -> ShowS
$cshowsPrec :: Int -> ListRoutingControls -> ShowS
Prelude.Show, forall x. Rep ListRoutingControls x -> ListRoutingControls
forall x. ListRoutingControls -> Rep ListRoutingControls x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListRoutingControls x -> ListRoutingControls
$cfrom :: forall x. ListRoutingControls -> Rep ListRoutingControls x
Prelude.Generic)

-- |
-- Create a value of 'ListRoutingControls' 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:
--
-- 'controlPanelArn', 'listRoutingControls_controlPanelArn' - The Amazon Resource Name (ARN) of the control panel of the routing
-- controls to list.
--
-- 'maxResults', 'listRoutingControls_maxResults' - The number of routing controls objects that you want to return with this
-- call. The default value is 500.
--
-- 'nextToken', 'listRoutingControls_nextToken' - The token for the next set of results. You receive this token from a
-- previous call.
newListRoutingControls ::
  ListRoutingControls
newListRoutingControls :: ListRoutingControls
newListRoutingControls =
  ListRoutingControls'
    { $sel:controlPanelArn:ListRoutingControls' :: Maybe Text
controlPanelArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListRoutingControls' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListRoutingControls' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the control panel of the routing
-- controls to list.
listRoutingControls_controlPanelArn :: Lens.Lens' ListRoutingControls (Prelude.Maybe Prelude.Text)
listRoutingControls_controlPanelArn :: Lens' ListRoutingControls (Maybe Text)
listRoutingControls_controlPanelArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRoutingControls' {Maybe Text
controlPanelArn :: Maybe Text
$sel:controlPanelArn:ListRoutingControls' :: ListRoutingControls -> Maybe Text
controlPanelArn} -> Maybe Text
controlPanelArn) (\s :: ListRoutingControls
s@ListRoutingControls' {} Maybe Text
a -> ListRoutingControls
s {$sel:controlPanelArn:ListRoutingControls' :: Maybe Text
controlPanelArn = Maybe Text
a} :: ListRoutingControls)

-- | The number of routing controls objects that you want to return with this
-- call. The default value is 500.
listRoutingControls_maxResults :: Lens.Lens' ListRoutingControls (Prelude.Maybe Prelude.Natural)
listRoutingControls_maxResults :: Lens' ListRoutingControls (Maybe Natural)
listRoutingControls_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRoutingControls' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListRoutingControls' :: ListRoutingControls -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListRoutingControls
s@ListRoutingControls' {} Maybe Natural
a -> ListRoutingControls
s {$sel:maxResults:ListRoutingControls' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListRoutingControls)

-- | The token for the next set of results. You receive this token from a
-- previous call.
listRoutingControls_nextToken :: Lens.Lens' ListRoutingControls (Prelude.Maybe Prelude.Text)
listRoutingControls_nextToken :: Lens' ListRoutingControls (Maybe Text)
listRoutingControls_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRoutingControls' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListRoutingControls' :: ListRoutingControls -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListRoutingControls
s@ListRoutingControls' {} Maybe Text
a -> ListRoutingControls
s {$sel:nextToken:ListRoutingControls' :: Maybe Text
nextToken = Maybe Text
a} :: ListRoutingControls)

instance Core.AWSPager ListRoutingControls where
  page :: ListRoutingControls
-> AWSResponse ListRoutingControls -> Maybe ListRoutingControls
page ListRoutingControls
rq AWSResponse ListRoutingControls
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListRoutingControls
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListRoutingControlsResponse (Maybe Text)
listRoutingControlsResponse_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 ListRoutingControls
rs
            forall s a. s -> Getting a s a -> a
Lens.^. Lens' ListRoutingControlsResponse [RoutingControl]
listRoutingControlsResponse_routingControls
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListRoutingControls
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListRoutingControls (Maybe Text)
listRoutingControls_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListRoutingControls
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListRoutingControlsResponse (Maybe Text)
listRoutingControlsResponse_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 ListRoutingControls where
  type
    AWSResponse ListRoutingControls =
      ListRoutingControlsResponse
  request :: (Service -> Service)
-> ListRoutingControls -> Request ListRoutingControls
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 ListRoutingControls
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListRoutingControls)))
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
-> Int -> [RoutingControl] -> ListRoutingControlsResponse
ListRoutingControlsResponse'
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            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
"RoutingControls"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable ListRoutingControls where
  hashWithSalt :: Int -> ListRoutingControls -> Int
hashWithSalt Int
_salt ListRoutingControls' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
controlPanelArn :: Maybe Text
$sel:nextToken:ListRoutingControls' :: ListRoutingControls -> Maybe Text
$sel:maxResults:ListRoutingControls' :: ListRoutingControls -> Maybe Natural
$sel:controlPanelArn:ListRoutingControls' :: ListRoutingControls -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
controlPanelArn
      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 ListRoutingControls where
  rnf :: ListRoutingControls -> ()
rnf ListRoutingControls' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
controlPanelArn :: Maybe Text
$sel:nextToken:ListRoutingControls' :: ListRoutingControls -> Maybe Text
$sel:maxResults:ListRoutingControls' :: ListRoutingControls -> Maybe Natural
$sel:controlPanelArn:ListRoutingControls' :: ListRoutingControls -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
controlPanelArn
      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 ListRoutingControls where
  toHeaders :: ListRoutingControls -> 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
"ToggleCustomerAPI.ListRoutingControls" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ListRoutingControls where
  toJSON :: ListRoutingControls -> Value
toJSON ListRoutingControls' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
controlPanelArn :: Maybe Text
$sel:nextToken:ListRoutingControls' :: ListRoutingControls -> Maybe Text
$sel:maxResults:ListRoutingControls' :: ListRoutingControls -> Maybe Natural
$sel:controlPanelArn:ListRoutingControls' :: ListRoutingControls -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ControlPanelArn" 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
controlPanelArn,
            (Key
"MaxResults" 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 Natural
maxResults,
            (Key
"NextToken" 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
nextToken
          ]
      )

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

instance Data.ToQuery ListRoutingControls where
  toQuery :: ListRoutingControls -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newListRoutingControlsResponse' smart constructor.
data ListRoutingControlsResponse = ListRoutingControlsResponse'
  { -- | The token for the next set of results. You receive this token from a
    -- previous call.
    ListRoutingControlsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListRoutingControlsResponse -> Int
httpStatus :: Prelude.Int,
    -- | The list of routing controls.
    ListRoutingControlsResponse -> [RoutingControl]
routingControls :: [RoutingControl]
  }
  deriving (ListRoutingControlsResponse -> ListRoutingControlsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListRoutingControlsResponse -> ListRoutingControlsResponse -> Bool
$c/= :: ListRoutingControlsResponse -> ListRoutingControlsResponse -> Bool
== :: ListRoutingControlsResponse -> ListRoutingControlsResponse -> Bool
$c== :: ListRoutingControlsResponse -> ListRoutingControlsResponse -> Bool
Prelude.Eq, ReadPrec [ListRoutingControlsResponse]
ReadPrec ListRoutingControlsResponse
Int -> ReadS ListRoutingControlsResponse
ReadS [ListRoutingControlsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListRoutingControlsResponse]
$creadListPrec :: ReadPrec [ListRoutingControlsResponse]
readPrec :: ReadPrec ListRoutingControlsResponse
$creadPrec :: ReadPrec ListRoutingControlsResponse
readList :: ReadS [ListRoutingControlsResponse]
$creadList :: ReadS [ListRoutingControlsResponse]
readsPrec :: Int -> ReadS ListRoutingControlsResponse
$creadsPrec :: Int -> ReadS ListRoutingControlsResponse
Prelude.Read, Int -> ListRoutingControlsResponse -> ShowS
[ListRoutingControlsResponse] -> ShowS
ListRoutingControlsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListRoutingControlsResponse] -> ShowS
$cshowList :: [ListRoutingControlsResponse] -> ShowS
show :: ListRoutingControlsResponse -> String
$cshow :: ListRoutingControlsResponse -> String
showsPrec :: Int -> ListRoutingControlsResponse -> ShowS
$cshowsPrec :: Int -> ListRoutingControlsResponse -> ShowS
Prelude.Show, forall x.
Rep ListRoutingControlsResponse x -> ListRoutingControlsResponse
forall x.
ListRoutingControlsResponse -> Rep ListRoutingControlsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListRoutingControlsResponse x -> ListRoutingControlsResponse
$cfrom :: forall x.
ListRoutingControlsResponse -> Rep ListRoutingControlsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListRoutingControlsResponse' 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', 'listRoutingControlsResponse_nextToken' - The token for the next set of results. You receive this token from a
-- previous call.
--
-- 'httpStatus', 'listRoutingControlsResponse_httpStatus' - The response's http status code.
--
-- 'routingControls', 'listRoutingControlsResponse_routingControls' - The list of routing controls.
newListRoutingControlsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListRoutingControlsResponse
newListRoutingControlsResponse :: Int -> ListRoutingControlsResponse
newListRoutingControlsResponse Int
pHttpStatus_ =
  ListRoutingControlsResponse'
    { $sel:nextToken:ListRoutingControlsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListRoutingControlsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:routingControls:ListRoutingControlsResponse' :: [RoutingControl]
routingControls = forall a. Monoid a => a
Prelude.mempty
    }

-- | The token for the next set of results. You receive this token from a
-- previous call.
listRoutingControlsResponse_nextToken :: Lens.Lens' ListRoutingControlsResponse (Prelude.Maybe Prelude.Text)
listRoutingControlsResponse_nextToken :: Lens' ListRoutingControlsResponse (Maybe Text)
listRoutingControlsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRoutingControlsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListRoutingControlsResponse' :: ListRoutingControlsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListRoutingControlsResponse
s@ListRoutingControlsResponse' {} Maybe Text
a -> ListRoutingControlsResponse
s {$sel:nextToken:ListRoutingControlsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListRoutingControlsResponse)

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

-- | The list of routing controls.
listRoutingControlsResponse_routingControls :: Lens.Lens' ListRoutingControlsResponse [RoutingControl]
listRoutingControlsResponse_routingControls :: Lens' ListRoutingControlsResponse [RoutingControl]
listRoutingControlsResponse_routingControls = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRoutingControlsResponse' {[RoutingControl]
routingControls :: [RoutingControl]
$sel:routingControls:ListRoutingControlsResponse' :: ListRoutingControlsResponse -> [RoutingControl]
routingControls} -> [RoutingControl]
routingControls) (\s :: ListRoutingControlsResponse
s@ListRoutingControlsResponse' {} [RoutingControl]
a -> ListRoutingControlsResponse
s {$sel:routingControls:ListRoutingControlsResponse' :: [RoutingControl]
routingControls = [RoutingControl]
a} :: ListRoutingControlsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Prelude.NFData ListRoutingControlsResponse where
  rnf :: ListRoutingControlsResponse -> ()
rnf ListRoutingControlsResponse' {Int
[RoutingControl]
Maybe Text
routingControls :: [RoutingControl]
httpStatus :: Int
nextToken :: Maybe Text
$sel:routingControls:ListRoutingControlsResponse' :: ListRoutingControlsResponse -> [RoutingControl]
$sel:httpStatus:ListRoutingControlsResponse' :: ListRoutingControlsResponse -> Int
$sel:nextToken:ListRoutingControlsResponse' :: ListRoutingControlsResponse -> 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 Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [RoutingControl]
routingControls