{-# 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.DirectoryService.ListIpRoutes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists the address blocks that you have added to a directory.
--
-- This operation returns paginated results.
module Amazonka.DirectoryService.ListIpRoutes
  ( -- * Creating a Request
    ListIpRoutes (..),
    newListIpRoutes,

    -- * Request Lenses
    listIpRoutes_limit,
    listIpRoutes_nextToken,
    listIpRoutes_directoryId,

    -- * Destructuring the Response
    ListIpRoutesResponse (..),
    newListIpRoutesResponse,

    -- * Response Lenses
    listIpRoutesResponse_ipRoutesInfo,
    listIpRoutesResponse_nextToken,
    listIpRoutesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListIpRoutes' smart constructor.
data ListIpRoutes = ListIpRoutes'
  { -- | Maximum number of items to return. If this value is zero, the maximum
    -- number of items is specified by the limitations of the operation.
    ListIpRoutes -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | The /ListIpRoutes.NextToken/ value from a previous call to ListIpRoutes.
    -- Pass null if this is the first call.
    ListIpRoutes -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Identifier (ID) of the directory for which you want to retrieve the IP
    -- addresses.
    ListIpRoutes -> Text
directoryId :: Prelude.Text
  }
  deriving (ListIpRoutes -> ListIpRoutes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListIpRoutes -> ListIpRoutes -> Bool
$c/= :: ListIpRoutes -> ListIpRoutes -> Bool
== :: ListIpRoutes -> ListIpRoutes -> Bool
$c== :: ListIpRoutes -> ListIpRoutes -> Bool
Prelude.Eq, ReadPrec [ListIpRoutes]
ReadPrec ListIpRoutes
Int -> ReadS ListIpRoutes
ReadS [ListIpRoutes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListIpRoutes]
$creadListPrec :: ReadPrec [ListIpRoutes]
readPrec :: ReadPrec ListIpRoutes
$creadPrec :: ReadPrec ListIpRoutes
readList :: ReadS [ListIpRoutes]
$creadList :: ReadS [ListIpRoutes]
readsPrec :: Int -> ReadS ListIpRoutes
$creadsPrec :: Int -> ReadS ListIpRoutes
Prelude.Read, Int -> ListIpRoutes -> ShowS
[ListIpRoutes] -> ShowS
ListIpRoutes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListIpRoutes] -> ShowS
$cshowList :: [ListIpRoutes] -> ShowS
show :: ListIpRoutes -> String
$cshow :: ListIpRoutes -> String
showsPrec :: Int -> ListIpRoutes -> ShowS
$cshowsPrec :: Int -> ListIpRoutes -> ShowS
Prelude.Show, forall x. Rep ListIpRoutes x -> ListIpRoutes
forall x. ListIpRoutes -> Rep ListIpRoutes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListIpRoutes x -> ListIpRoutes
$cfrom :: forall x. ListIpRoutes -> Rep ListIpRoutes x
Prelude.Generic)

-- |
-- Create a value of 'ListIpRoutes' 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:
--
-- 'limit', 'listIpRoutes_limit' - Maximum number of items to return. If this value is zero, the maximum
-- number of items is specified by the limitations of the operation.
--
-- 'nextToken', 'listIpRoutes_nextToken' - The /ListIpRoutes.NextToken/ value from a previous call to ListIpRoutes.
-- Pass null if this is the first call.
--
-- 'directoryId', 'listIpRoutes_directoryId' - Identifier (ID) of the directory for which you want to retrieve the IP
-- addresses.
newListIpRoutes ::
  -- | 'directoryId'
  Prelude.Text ->
  ListIpRoutes
newListIpRoutes :: Text -> ListIpRoutes
newListIpRoutes Text
pDirectoryId_ =
  ListIpRoutes'
    { $sel:limit:ListIpRoutes' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListIpRoutes' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:directoryId:ListIpRoutes' :: Text
directoryId = Text
pDirectoryId_
    }

-- | Maximum number of items to return. If this value is zero, the maximum
-- number of items is specified by the limitations of the operation.
listIpRoutes_limit :: Lens.Lens' ListIpRoutes (Prelude.Maybe Prelude.Natural)
listIpRoutes_limit :: Lens' ListIpRoutes (Maybe Natural)
listIpRoutes_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIpRoutes' {Maybe Natural
limit :: Maybe Natural
$sel:limit:ListIpRoutes' :: ListIpRoutes -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: ListIpRoutes
s@ListIpRoutes' {} Maybe Natural
a -> ListIpRoutes
s {$sel:limit:ListIpRoutes' :: Maybe Natural
limit = Maybe Natural
a} :: ListIpRoutes)

-- | The /ListIpRoutes.NextToken/ value from a previous call to ListIpRoutes.
-- Pass null if this is the first call.
listIpRoutes_nextToken :: Lens.Lens' ListIpRoutes (Prelude.Maybe Prelude.Text)
listIpRoutes_nextToken :: Lens' ListIpRoutes (Maybe Text)
listIpRoutes_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIpRoutes' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListIpRoutes' :: ListIpRoutes -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListIpRoutes
s@ListIpRoutes' {} Maybe Text
a -> ListIpRoutes
s {$sel:nextToken:ListIpRoutes' :: Maybe Text
nextToken = Maybe Text
a} :: ListIpRoutes)

-- | Identifier (ID) of the directory for which you want to retrieve the IP
-- addresses.
listIpRoutes_directoryId :: Lens.Lens' ListIpRoutes Prelude.Text
listIpRoutes_directoryId :: Lens' ListIpRoutes Text
listIpRoutes_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIpRoutes' {Text
directoryId :: Text
$sel:directoryId:ListIpRoutes' :: ListIpRoutes -> Text
directoryId} -> Text
directoryId) (\s :: ListIpRoutes
s@ListIpRoutes' {} Text
a -> ListIpRoutes
s {$sel:directoryId:ListIpRoutes' :: Text
directoryId = Text
a} :: ListIpRoutes)

instance Core.AWSPager ListIpRoutes where
  page :: ListIpRoutes -> AWSResponse ListIpRoutes -> Maybe ListIpRoutes
page ListIpRoutes
rq AWSResponse ListIpRoutes
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListIpRoutes
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListIpRoutesResponse (Maybe Text)
listIpRoutesResponse_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 ListIpRoutes
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListIpRoutesResponse (Maybe [IpRouteInfo])
listIpRoutesResponse_ipRoutesInfo
            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.$ ListIpRoutes
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListIpRoutes (Maybe Text)
listIpRoutes_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListIpRoutes
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListIpRoutesResponse (Maybe Text)
listIpRoutesResponse_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 ListIpRoutes where
  type AWSResponse ListIpRoutes = ListIpRoutesResponse
  request :: (Service -> Service) -> ListIpRoutes -> Request ListIpRoutes
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 ListIpRoutes
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListIpRoutes)))
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 [IpRouteInfo] -> Maybe Text -> Int -> ListIpRoutesResponse
ListIpRoutesResponse'
            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
"IpRoutesInfo" 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.<*> (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))
      )

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

instance Prelude.NFData ListIpRoutes where
  rnf :: ListIpRoutes -> ()
rnf ListIpRoutes' {Maybe Natural
Maybe Text
Text
directoryId :: Text
nextToken :: Maybe Text
limit :: Maybe Natural
$sel:directoryId:ListIpRoutes' :: ListIpRoutes -> Text
$sel:nextToken:ListIpRoutes' :: ListIpRoutes -> Maybe Text
$sel:limit:ListIpRoutes' :: ListIpRoutes -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
directoryId

instance Data.ToHeaders ListIpRoutes where
  toHeaders :: ListIpRoutes -> 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
"DirectoryService_20150416.ListIpRoutes" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ListIpRoutes where
  toJSON :: ListIpRoutes -> Value
toJSON ListIpRoutes' {Maybe Natural
Maybe Text
Text
directoryId :: Text
nextToken :: Maybe Text
limit :: Maybe Natural
$sel:directoryId:ListIpRoutes' :: ListIpRoutes -> Text
$sel:nextToken:ListIpRoutes' :: ListIpRoutes -> Maybe Text
$sel:limit:ListIpRoutes' :: ListIpRoutes -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Limit" 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
limit,
            (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,
            forall a. a -> Maybe a
Prelude.Just (Key
"DirectoryId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
directoryId)
          ]
      )

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

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

-- | /See:/ 'newListIpRoutesResponse' smart constructor.
data ListIpRoutesResponse = ListIpRoutesResponse'
  { -- | A list of IpRoutes.
    ListIpRoutesResponse -> Maybe [IpRouteInfo]
ipRoutesInfo :: Prelude.Maybe [IpRouteInfo],
    -- | If not null, more results are available. Pass this value for the
    -- /NextToken/ parameter in a subsequent call to ListIpRoutes to retrieve
    -- the next set of items.
    ListIpRoutesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListIpRoutesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListIpRoutesResponse -> ListIpRoutesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListIpRoutesResponse -> ListIpRoutesResponse -> Bool
$c/= :: ListIpRoutesResponse -> ListIpRoutesResponse -> Bool
== :: ListIpRoutesResponse -> ListIpRoutesResponse -> Bool
$c== :: ListIpRoutesResponse -> ListIpRoutesResponse -> Bool
Prelude.Eq, ReadPrec [ListIpRoutesResponse]
ReadPrec ListIpRoutesResponse
Int -> ReadS ListIpRoutesResponse
ReadS [ListIpRoutesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListIpRoutesResponse]
$creadListPrec :: ReadPrec [ListIpRoutesResponse]
readPrec :: ReadPrec ListIpRoutesResponse
$creadPrec :: ReadPrec ListIpRoutesResponse
readList :: ReadS [ListIpRoutesResponse]
$creadList :: ReadS [ListIpRoutesResponse]
readsPrec :: Int -> ReadS ListIpRoutesResponse
$creadsPrec :: Int -> ReadS ListIpRoutesResponse
Prelude.Read, Int -> ListIpRoutesResponse -> ShowS
[ListIpRoutesResponse] -> ShowS
ListIpRoutesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListIpRoutesResponse] -> ShowS
$cshowList :: [ListIpRoutesResponse] -> ShowS
show :: ListIpRoutesResponse -> String
$cshow :: ListIpRoutesResponse -> String
showsPrec :: Int -> ListIpRoutesResponse -> ShowS
$cshowsPrec :: Int -> ListIpRoutesResponse -> ShowS
Prelude.Show, forall x. Rep ListIpRoutesResponse x -> ListIpRoutesResponse
forall x. ListIpRoutesResponse -> Rep ListIpRoutesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListIpRoutesResponse x -> ListIpRoutesResponse
$cfrom :: forall x. ListIpRoutesResponse -> Rep ListIpRoutesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListIpRoutesResponse' 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:
--
-- 'ipRoutesInfo', 'listIpRoutesResponse_ipRoutesInfo' - A list of IpRoutes.
--
-- 'nextToken', 'listIpRoutesResponse_nextToken' - If not null, more results are available. Pass this value for the
-- /NextToken/ parameter in a subsequent call to ListIpRoutes to retrieve
-- the next set of items.
--
-- 'httpStatus', 'listIpRoutesResponse_httpStatus' - The response's http status code.
newListIpRoutesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListIpRoutesResponse
newListIpRoutesResponse :: Int -> ListIpRoutesResponse
newListIpRoutesResponse Int
pHttpStatus_ =
  ListIpRoutesResponse'
    { $sel:ipRoutesInfo:ListIpRoutesResponse' :: Maybe [IpRouteInfo]
ipRoutesInfo =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListIpRoutesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListIpRoutesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of IpRoutes.
listIpRoutesResponse_ipRoutesInfo :: Lens.Lens' ListIpRoutesResponse (Prelude.Maybe [IpRouteInfo])
listIpRoutesResponse_ipRoutesInfo :: Lens' ListIpRoutesResponse (Maybe [IpRouteInfo])
listIpRoutesResponse_ipRoutesInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIpRoutesResponse' {Maybe [IpRouteInfo]
ipRoutesInfo :: Maybe [IpRouteInfo]
$sel:ipRoutesInfo:ListIpRoutesResponse' :: ListIpRoutesResponse -> Maybe [IpRouteInfo]
ipRoutesInfo} -> Maybe [IpRouteInfo]
ipRoutesInfo) (\s :: ListIpRoutesResponse
s@ListIpRoutesResponse' {} Maybe [IpRouteInfo]
a -> ListIpRoutesResponse
s {$sel:ipRoutesInfo:ListIpRoutesResponse' :: Maybe [IpRouteInfo]
ipRoutesInfo = Maybe [IpRouteInfo]
a} :: ListIpRoutesResponse) 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

-- | If not null, more results are available. Pass this value for the
-- /NextToken/ parameter in a subsequent call to ListIpRoutes to retrieve
-- the next set of items.
listIpRoutesResponse_nextToken :: Lens.Lens' ListIpRoutesResponse (Prelude.Maybe Prelude.Text)
listIpRoutesResponse_nextToken :: Lens' ListIpRoutesResponse (Maybe Text)
listIpRoutesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIpRoutesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListIpRoutesResponse' :: ListIpRoutesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListIpRoutesResponse
s@ListIpRoutesResponse' {} Maybe Text
a -> ListIpRoutesResponse
s {$sel:nextToken:ListIpRoutesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListIpRoutesResponse)

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

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