{-# 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.Organizations.ListParents
-- 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 root or organizational units (OUs) that serve as the immediate
-- parent of the specified child OU or account. This operation, along with
-- ListChildren enables you to traverse the tree structure that makes up
-- this root.
--
-- Always check the @NextToken@ response parameter for a @null@ value when
-- calling a @List*@ operation. These operations can occasionally return an
-- empty set of results even when there are more results available. The
-- @NextToken@ response parameter value is @null@ /only/ when there are no
-- more results to display.
--
-- This operation can be called only from the organization\'s management
-- account or by a member account that is a delegated administrator for an
-- Amazon Web Services service.
--
-- In the current release, a child can have only a single parent.
--
-- This operation returns paginated results.
module Amazonka.Organizations.ListParents
  ( -- * Creating a Request
    ListParents (..),
    newListParents,

    -- * Request Lenses
    listParents_maxResults,
    listParents_nextToken,
    listParents_childId,

    -- * Destructuring the Response
    ListParentsResponse (..),
    newListParentsResponse,

    -- * Response Lenses
    listParentsResponse_nextToken,
    listParentsResponse_parents,
    listParentsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListParents' smart constructor.
data ListParents = ListParents'
  { -- | The total number of results that you want included on each page of the
    -- response. If you do not include this parameter, it defaults to a value
    -- that is specific to the operation. If additional items exist beyond the
    -- maximum you specify, the @NextToken@ response element is present and has
    -- a value (is not null). Include that value as the @NextToken@ request
    -- parameter in the next call to the operation to get the next part of the
    -- results. Note that Organizations might return fewer results than the
    -- maximum even when there are more results available. You should check
    -- @NextToken@ after every operation to ensure that you receive all of the
    -- results.
    ListParents -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The parameter for receiving additional results if you receive a
    -- @NextToken@ response in a previous request. A @NextToken@ response
    -- indicates that more output is available. Set this parameter to the value
    -- of the previous call\'s @NextToken@ response to indicate where the
    -- output should continue from.
    ListParents -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier (ID) of the OU or account whose parent containers
    -- you want to list. Don\'t specify a root.
    --
    -- The <http://wikipedia.org/wiki/regex regex pattern> for a child ID
    -- string requires one of the following:
    --
    -- -   __Account__ - A string that consists of exactly 12 digits.
    --
    -- -   __Organizational unit (OU)__ - A string that begins with \"ou-\"
    --     followed by from 4 to 32 lowercase letters or digits (the ID of the
    --     root that contains the OU). This string is followed by a second
    --     \"-\" dash and from 8 to 32 additional lowercase letters or digits.
    ListParents -> Text
childId :: Prelude.Text
  }
  deriving (ListParents -> ListParents -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListParents -> ListParents -> Bool
$c/= :: ListParents -> ListParents -> Bool
== :: ListParents -> ListParents -> Bool
$c== :: ListParents -> ListParents -> Bool
Prelude.Eq, ReadPrec [ListParents]
ReadPrec ListParents
Int -> ReadS ListParents
ReadS [ListParents]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListParents]
$creadListPrec :: ReadPrec [ListParents]
readPrec :: ReadPrec ListParents
$creadPrec :: ReadPrec ListParents
readList :: ReadS [ListParents]
$creadList :: ReadS [ListParents]
readsPrec :: Int -> ReadS ListParents
$creadsPrec :: Int -> ReadS ListParents
Prelude.Read, Int -> ListParents -> ShowS
[ListParents] -> ShowS
ListParents -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListParents] -> ShowS
$cshowList :: [ListParents] -> ShowS
show :: ListParents -> String
$cshow :: ListParents -> String
showsPrec :: Int -> ListParents -> ShowS
$cshowsPrec :: Int -> ListParents -> ShowS
Prelude.Show, forall x. Rep ListParents x -> ListParents
forall x. ListParents -> Rep ListParents x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListParents x -> ListParents
$cfrom :: forall x. ListParents -> Rep ListParents x
Prelude.Generic)

-- |
-- Create a value of 'ListParents' 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:
--
-- 'maxResults', 'listParents_maxResults' - The total number of results that you want included on each page of the
-- response. If you do not include this parameter, it defaults to a value
-- that is specific to the operation. If additional items exist beyond the
-- maximum you specify, the @NextToken@ response element is present and has
-- a value (is not null). Include that value as the @NextToken@ request
-- parameter in the next call to the operation to get the next part of the
-- results. Note that Organizations might return fewer results than the
-- maximum even when there are more results available. You should check
-- @NextToken@ after every operation to ensure that you receive all of the
-- results.
--
-- 'nextToken', 'listParents_nextToken' - The parameter for receiving additional results if you receive a
-- @NextToken@ response in a previous request. A @NextToken@ response
-- indicates that more output is available. Set this parameter to the value
-- of the previous call\'s @NextToken@ response to indicate where the
-- output should continue from.
--
-- 'childId', 'listParents_childId' - The unique identifier (ID) of the OU or account whose parent containers
-- you want to list. Don\'t specify a root.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> for a child ID
-- string requires one of the following:
--
-- -   __Account__ - A string that consists of exactly 12 digits.
--
-- -   __Organizational unit (OU)__ - A string that begins with \"ou-\"
--     followed by from 4 to 32 lowercase letters or digits (the ID of the
--     root that contains the OU). This string is followed by a second
--     \"-\" dash and from 8 to 32 additional lowercase letters or digits.
newListParents ::
  -- | 'childId'
  Prelude.Text ->
  ListParents
newListParents :: Text -> ListParents
newListParents Text
pChildId_ =
  ListParents'
    { $sel:maxResults:ListParents' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListParents' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:childId:ListParents' :: Text
childId = Text
pChildId_
    }

-- | The total number of results that you want included on each page of the
-- response. If you do not include this parameter, it defaults to a value
-- that is specific to the operation. If additional items exist beyond the
-- maximum you specify, the @NextToken@ response element is present and has
-- a value (is not null). Include that value as the @NextToken@ request
-- parameter in the next call to the operation to get the next part of the
-- results. Note that Organizations might return fewer results than the
-- maximum even when there are more results available. You should check
-- @NextToken@ after every operation to ensure that you receive all of the
-- results.
listParents_maxResults :: Lens.Lens' ListParents (Prelude.Maybe Prelude.Natural)
listParents_maxResults :: Lens' ListParents (Maybe Natural)
listParents_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListParents' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListParents' :: ListParents -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListParents
s@ListParents' {} Maybe Natural
a -> ListParents
s {$sel:maxResults:ListParents' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListParents)

-- | The parameter for receiving additional results if you receive a
-- @NextToken@ response in a previous request. A @NextToken@ response
-- indicates that more output is available. Set this parameter to the value
-- of the previous call\'s @NextToken@ response to indicate where the
-- output should continue from.
listParents_nextToken :: Lens.Lens' ListParents (Prelude.Maybe Prelude.Text)
listParents_nextToken :: Lens' ListParents (Maybe Text)
listParents_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListParents' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListParents' :: ListParents -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListParents
s@ListParents' {} Maybe Text
a -> ListParents
s {$sel:nextToken:ListParents' :: Maybe Text
nextToken = Maybe Text
a} :: ListParents)

-- | The unique identifier (ID) of the OU or account whose parent containers
-- you want to list. Don\'t specify a root.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> for a child ID
-- string requires one of the following:
--
-- -   __Account__ - A string that consists of exactly 12 digits.
--
-- -   __Organizational unit (OU)__ - A string that begins with \"ou-\"
--     followed by from 4 to 32 lowercase letters or digits (the ID of the
--     root that contains the OU). This string is followed by a second
--     \"-\" dash and from 8 to 32 additional lowercase letters or digits.
listParents_childId :: Lens.Lens' ListParents Prelude.Text
listParents_childId :: Lens' ListParents Text
listParents_childId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListParents' {Text
childId :: Text
$sel:childId:ListParents' :: ListParents -> Text
childId} -> Text
childId) (\s :: ListParents
s@ListParents' {} Text
a -> ListParents
s {$sel:childId:ListParents' :: Text
childId = Text
a} :: ListParents)

instance Core.AWSPager ListParents where
  page :: ListParents -> AWSResponse ListParents -> Maybe ListParents
page ListParents
rq AWSResponse ListParents
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListParents
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListParentsResponse (Maybe Text)
listParentsResponse_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 ListParents
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListParentsResponse (Maybe [Parent])
listParentsResponse_parents
            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.$ ListParents
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListParents (Maybe Text)
listParents_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListParents
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListParentsResponse (Maybe Text)
listParentsResponse_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 ListParents where
  type AWSResponse ListParents = ListParentsResponse
  request :: (Service -> Service) -> ListParents -> Request ListParents
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 ListParents
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListParents)))
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 [Parent] -> Int -> ListParentsResponse
ListParentsResponse'
            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
"Parents" 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 ListParents where
  hashWithSalt :: Int -> ListParents -> Int
hashWithSalt Int
_salt ListParents' {Maybe Natural
Maybe Text
Text
childId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:childId:ListParents' :: ListParents -> Text
$sel:nextToken:ListParents' :: ListParents -> Maybe Text
$sel:maxResults:ListParents' :: ListParents -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
childId

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

instance Data.ToHeaders ListParents where
  toHeaders :: ListParents -> 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
"AWSOrganizationsV20161128.ListParents" ::
                          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 ListParents where
  toJSON :: ListParents -> Value
toJSON ListParents' {Maybe Natural
Maybe Text
Text
childId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:childId:ListParents' :: ListParents -> Text
$sel:nextToken:ListParents' :: ListParents -> Maybe Text
$sel:maxResults:ListParents' :: ListParents -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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,
            forall a. a -> Maybe a
Prelude.Just (Key
"ChildId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
childId)
          ]
      )

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

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

-- | /See:/ 'newListParentsResponse' smart constructor.
data ListParentsResponse = ListParentsResponse'
  { -- | If present, indicates that more output is available than is included in
    -- the current response. Use this value in the @NextToken@ request
    -- parameter in a subsequent call to the operation to get the next part of
    -- the output. You should repeat this until the @NextToken@ response
    -- element comes back as @null@.
    ListParentsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of parents for the specified child account or OU.
    ListParentsResponse -> Maybe [Parent]
parents :: Prelude.Maybe [Parent],
    -- | The response's http status code.
    ListParentsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListParentsResponse -> ListParentsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListParentsResponse -> ListParentsResponse -> Bool
$c/= :: ListParentsResponse -> ListParentsResponse -> Bool
== :: ListParentsResponse -> ListParentsResponse -> Bool
$c== :: ListParentsResponse -> ListParentsResponse -> Bool
Prelude.Eq, ReadPrec [ListParentsResponse]
ReadPrec ListParentsResponse
Int -> ReadS ListParentsResponse
ReadS [ListParentsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListParentsResponse]
$creadListPrec :: ReadPrec [ListParentsResponse]
readPrec :: ReadPrec ListParentsResponse
$creadPrec :: ReadPrec ListParentsResponse
readList :: ReadS [ListParentsResponse]
$creadList :: ReadS [ListParentsResponse]
readsPrec :: Int -> ReadS ListParentsResponse
$creadsPrec :: Int -> ReadS ListParentsResponse
Prelude.Read, Int -> ListParentsResponse -> ShowS
[ListParentsResponse] -> ShowS
ListParentsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListParentsResponse] -> ShowS
$cshowList :: [ListParentsResponse] -> ShowS
show :: ListParentsResponse -> String
$cshow :: ListParentsResponse -> String
showsPrec :: Int -> ListParentsResponse -> ShowS
$cshowsPrec :: Int -> ListParentsResponse -> ShowS
Prelude.Show, forall x. Rep ListParentsResponse x -> ListParentsResponse
forall x. ListParentsResponse -> Rep ListParentsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListParentsResponse x -> ListParentsResponse
$cfrom :: forall x. ListParentsResponse -> Rep ListParentsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListParentsResponse' 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', 'listParentsResponse_nextToken' - If present, indicates that more output is available than is included in
-- the current response. Use this value in the @NextToken@ request
-- parameter in a subsequent call to the operation to get the next part of
-- the output. You should repeat this until the @NextToken@ response
-- element comes back as @null@.
--
-- 'parents', 'listParentsResponse_parents' - A list of parents for the specified child account or OU.
--
-- 'httpStatus', 'listParentsResponse_httpStatus' - The response's http status code.
newListParentsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListParentsResponse
newListParentsResponse :: Int -> ListParentsResponse
newListParentsResponse Int
pHttpStatus_ =
  ListParentsResponse'
    { $sel:nextToken:ListParentsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:parents:ListParentsResponse' :: Maybe [Parent]
parents = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListParentsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If present, indicates that more output is available than is included in
-- the current response. Use this value in the @NextToken@ request
-- parameter in a subsequent call to the operation to get the next part of
-- the output. You should repeat this until the @NextToken@ response
-- element comes back as @null@.
listParentsResponse_nextToken :: Lens.Lens' ListParentsResponse (Prelude.Maybe Prelude.Text)
listParentsResponse_nextToken :: Lens' ListParentsResponse (Maybe Text)
listParentsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListParentsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListParentsResponse' :: ListParentsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListParentsResponse
s@ListParentsResponse' {} Maybe Text
a -> ListParentsResponse
s {$sel:nextToken:ListParentsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListParentsResponse)

-- | A list of parents for the specified child account or OU.
listParentsResponse_parents :: Lens.Lens' ListParentsResponse (Prelude.Maybe [Parent])
listParentsResponse_parents :: Lens' ListParentsResponse (Maybe [Parent])
listParentsResponse_parents = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListParentsResponse' {Maybe [Parent]
parents :: Maybe [Parent]
$sel:parents:ListParentsResponse' :: ListParentsResponse -> Maybe [Parent]
parents} -> Maybe [Parent]
parents) (\s :: ListParentsResponse
s@ListParentsResponse' {} Maybe [Parent]
a -> ListParentsResponse
s {$sel:parents:ListParentsResponse' :: Maybe [Parent]
parents = Maybe [Parent]
a} :: ListParentsResponse) 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.
listParentsResponse_httpStatus :: Lens.Lens' ListParentsResponse Prelude.Int
listParentsResponse_httpStatus :: Lens' ListParentsResponse Int
listParentsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListParentsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListParentsResponse' :: ListParentsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListParentsResponse
s@ListParentsResponse' {} Int
a -> ListParentsResponse
s {$sel:httpStatus:ListParentsResponse' :: Int
httpStatus = Int
a} :: ListParentsResponse)

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