{-# 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.ListChildren
-- 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 all of the organizational units (OUs) or accounts that are
-- contained in the specified parent OU or root. This operation, along with
-- ListParents 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.
--
-- This operation returns paginated results.
module Amazonka.Organizations.ListChildren
  ( -- * Creating a Request
    ListChildren (..),
    newListChildren,

    -- * Request Lenses
    listChildren_maxResults,
    listChildren_nextToken,
    listChildren_parentId,
    listChildren_childType,

    -- * Destructuring the Response
    ListChildrenResponse (..),
    newListChildrenResponse,

    -- * Response Lenses
    listChildrenResponse_children,
    listChildrenResponse_nextToken,
    listChildrenResponse_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:/ 'newListChildren' smart constructor.
data ListChildren = ListChildren'
  { -- | 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.
    ListChildren -> 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.
    ListChildren -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier (ID) for the parent root or OU whose children you
    -- want to list.
    --
    -- The <http://wikipedia.org/wiki/regex regex pattern> for a parent ID
    -- string requires one of the following:
    --
    -- -   __Root__ - A string that begins with \"r-\" followed by from 4 to 32
    --     lowercase letters or 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 the OU is in). This string is followed by a second \"-\"
    --     dash and from 8 to 32 additional lowercase letters or digits.
    ListChildren -> Text
parentId :: Prelude.Text,
    -- | Filters the output to include only the specified child type.
    ListChildren -> ChildType
childType :: ChildType
  }
  deriving (ListChildren -> ListChildren -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListChildren -> ListChildren -> Bool
$c/= :: ListChildren -> ListChildren -> Bool
== :: ListChildren -> ListChildren -> Bool
$c== :: ListChildren -> ListChildren -> Bool
Prelude.Eq, ReadPrec [ListChildren]
ReadPrec ListChildren
Int -> ReadS ListChildren
ReadS [ListChildren]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListChildren]
$creadListPrec :: ReadPrec [ListChildren]
readPrec :: ReadPrec ListChildren
$creadPrec :: ReadPrec ListChildren
readList :: ReadS [ListChildren]
$creadList :: ReadS [ListChildren]
readsPrec :: Int -> ReadS ListChildren
$creadsPrec :: Int -> ReadS ListChildren
Prelude.Read, Int -> ListChildren -> ShowS
[ListChildren] -> ShowS
ListChildren -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListChildren] -> ShowS
$cshowList :: [ListChildren] -> ShowS
show :: ListChildren -> String
$cshow :: ListChildren -> String
showsPrec :: Int -> ListChildren -> ShowS
$cshowsPrec :: Int -> ListChildren -> ShowS
Prelude.Show, forall x. Rep ListChildren x -> ListChildren
forall x. ListChildren -> Rep ListChildren x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListChildren x -> ListChildren
$cfrom :: forall x. ListChildren -> Rep ListChildren x
Prelude.Generic)

-- |
-- Create a value of 'ListChildren' 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', 'listChildren_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', 'listChildren_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.
--
-- 'parentId', 'listChildren_parentId' - The unique identifier (ID) for the parent root or OU whose children you
-- want to list.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> for a parent ID
-- string requires one of the following:
--
-- -   __Root__ - A string that begins with \"r-\" followed by from 4 to 32
--     lowercase letters or 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 the OU is in). This string is followed by a second \"-\"
--     dash and from 8 to 32 additional lowercase letters or digits.
--
-- 'childType', 'listChildren_childType' - Filters the output to include only the specified child type.
newListChildren ::
  -- | 'parentId'
  Prelude.Text ->
  -- | 'childType'
  ChildType ->
  ListChildren
newListChildren :: Text -> ChildType -> ListChildren
newListChildren Text
pParentId_ ChildType
pChildType_ =
  ListChildren'
    { $sel:maxResults:ListChildren' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListChildren' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:parentId:ListChildren' :: Text
parentId = Text
pParentId_,
      $sel:childType:ListChildren' :: ChildType
childType = ChildType
pChildType_
    }

-- | 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.
listChildren_maxResults :: Lens.Lens' ListChildren (Prelude.Maybe Prelude.Natural)
listChildren_maxResults :: Lens' ListChildren (Maybe Natural)
listChildren_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChildren' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListChildren' :: ListChildren -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListChildren
s@ListChildren' {} Maybe Natural
a -> ListChildren
s {$sel:maxResults:ListChildren' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListChildren)

-- | 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.
listChildren_nextToken :: Lens.Lens' ListChildren (Prelude.Maybe Prelude.Text)
listChildren_nextToken :: Lens' ListChildren (Maybe Text)
listChildren_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChildren' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListChildren' :: ListChildren -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListChildren
s@ListChildren' {} Maybe Text
a -> ListChildren
s {$sel:nextToken:ListChildren' :: Maybe Text
nextToken = Maybe Text
a} :: ListChildren)

-- | The unique identifier (ID) for the parent root or OU whose children you
-- want to list.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> for a parent ID
-- string requires one of the following:
--
-- -   __Root__ - A string that begins with \"r-\" followed by from 4 to 32
--     lowercase letters or 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 the OU is in). This string is followed by a second \"-\"
--     dash and from 8 to 32 additional lowercase letters or digits.
listChildren_parentId :: Lens.Lens' ListChildren Prelude.Text
listChildren_parentId :: Lens' ListChildren Text
listChildren_parentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChildren' {Text
parentId :: Text
$sel:parentId:ListChildren' :: ListChildren -> Text
parentId} -> Text
parentId) (\s :: ListChildren
s@ListChildren' {} Text
a -> ListChildren
s {$sel:parentId:ListChildren' :: Text
parentId = Text
a} :: ListChildren)

-- | Filters the output to include only the specified child type.
listChildren_childType :: Lens.Lens' ListChildren ChildType
listChildren_childType :: Lens' ListChildren ChildType
listChildren_childType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChildren' {ChildType
childType :: ChildType
$sel:childType:ListChildren' :: ListChildren -> ChildType
childType} -> ChildType
childType) (\s :: ListChildren
s@ListChildren' {} ChildType
a -> ListChildren
s {$sel:childType:ListChildren' :: ChildType
childType = ChildType
a} :: ListChildren)

instance Core.AWSPager ListChildren where
  page :: ListChildren -> AWSResponse ListChildren -> Maybe ListChildren
page ListChildren
rq AWSResponse ListChildren
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListChildren
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListChildrenResponse (Maybe Text)
listChildrenResponse_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 ListChildren
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListChildrenResponse (Maybe [Child])
listChildrenResponse_children
            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.$ ListChildren
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListChildren (Maybe Text)
listChildren_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListChildren
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListChildrenResponse (Maybe Text)
listChildrenResponse_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 ListChildren where
  type AWSResponse ListChildren = ListChildrenResponse
  request :: (Service -> Service) -> ListChildren -> Request ListChildren
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 ListChildren
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListChildren)))
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 [Child] -> Maybe Text -> Int -> ListChildrenResponse
ListChildrenResponse'
            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
"Children" 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 ListChildren where
  hashWithSalt :: Int -> ListChildren -> Int
hashWithSalt Int
_salt ListChildren' {Maybe Natural
Maybe Text
Text
ChildType
childType :: ChildType
parentId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:childType:ListChildren' :: ListChildren -> ChildType
$sel:parentId:ListChildren' :: ListChildren -> Text
$sel:nextToken:ListChildren' :: ListChildren -> Maybe Text
$sel:maxResults:ListChildren' :: ListChildren -> 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
parentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ChildType
childType

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

instance Data.ToHeaders ListChildren where
  toHeaders :: ListChildren -> 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.ListChildren" ::
                          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 ListChildren where
  toJSON :: ListChildren -> Value
toJSON ListChildren' {Maybe Natural
Maybe Text
Text
ChildType
childType :: ChildType
parentId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:childType:ListChildren' :: ListChildren -> ChildType
$sel:parentId:ListChildren' :: ListChildren -> Text
$sel:nextToken:ListChildren' :: ListChildren -> Maybe Text
$sel:maxResults:ListChildren' :: ListChildren -> 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
"ParentId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
parentId),
            forall a. a -> Maybe a
Prelude.Just (Key
"ChildType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ChildType
childType)
          ]
      )

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

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

-- | /See:/ 'newListChildrenResponse' smart constructor.
data ListChildrenResponse = ListChildrenResponse'
  { -- | The list of children of the specified parent container.
    ListChildrenResponse -> Maybe [Child]
children :: Prelude.Maybe [Child],
    -- | 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@.
    ListChildrenResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListChildrenResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListChildrenResponse -> ListChildrenResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListChildrenResponse -> ListChildrenResponse -> Bool
$c/= :: ListChildrenResponse -> ListChildrenResponse -> Bool
== :: ListChildrenResponse -> ListChildrenResponse -> Bool
$c== :: ListChildrenResponse -> ListChildrenResponse -> Bool
Prelude.Eq, ReadPrec [ListChildrenResponse]
ReadPrec ListChildrenResponse
Int -> ReadS ListChildrenResponse
ReadS [ListChildrenResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListChildrenResponse]
$creadListPrec :: ReadPrec [ListChildrenResponse]
readPrec :: ReadPrec ListChildrenResponse
$creadPrec :: ReadPrec ListChildrenResponse
readList :: ReadS [ListChildrenResponse]
$creadList :: ReadS [ListChildrenResponse]
readsPrec :: Int -> ReadS ListChildrenResponse
$creadsPrec :: Int -> ReadS ListChildrenResponse
Prelude.Read, Int -> ListChildrenResponse -> ShowS
[ListChildrenResponse] -> ShowS
ListChildrenResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListChildrenResponse] -> ShowS
$cshowList :: [ListChildrenResponse] -> ShowS
show :: ListChildrenResponse -> String
$cshow :: ListChildrenResponse -> String
showsPrec :: Int -> ListChildrenResponse -> ShowS
$cshowsPrec :: Int -> ListChildrenResponse -> ShowS
Prelude.Show, forall x. Rep ListChildrenResponse x -> ListChildrenResponse
forall x. ListChildrenResponse -> Rep ListChildrenResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListChildrenResponse x -> ListChildrenResponse
$cfrom :: forall x. ListChildrenResponse -> Rep ListChildrenResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListChildrenResponse' 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:
--
-- 'children', 'listChildrenResponse_children' - The list of children of the specified parent container.
--
-- 'nextToken', 'listChildrenResponse_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@.
--
-- 'httpStatus', 'listChildrenResponse_httpStatus' - The response's http status code.
newListChildrenResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListChildrenResponse
newListChildrenResponse :: Int -> ListChildrenResponse
newListChildrenResponse Int
pHttpStatus_ =
  ListChildrenResponse'
    { $sel:children:ListChildrenResponse' :: Maybe [Child]
children = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListChildrenResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListChildrenResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of children of the specified parent container.
listChildrenResponse_children :: Lens.Lens' ListChildrenResponse (Prelude.Maybe [Child])
listChildrenResponse_children :: Lens' ListChildrenResponse (Maybe [Child])
listChildrenResponse_children = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChildrenResponse' {Maybe [Child]
children :: Maybe [Child]
$sel:children:ListChildrenResponse' :: ListChildrenResponse -> Maybe [Child]
children} -> Maybe [Child]
children) (\s :: ListChildrenResponse
s@ListChildrenResponse' {} Maybe [Child]
a -> ListChildrenResponse
s {$sel:children:ListChildrenResponse' :: Maybe [Child]
children = Maybe [Child]
a} :: ListChildrenResponse) 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 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@.
listChildrenResponse_nextToken :: Lens.Lens' ListChildrenResponse (Prelude.Maybe Prelude.Text)
listChildrenResponse_nextToken :: Lens' ListChildrenResponse (Maybe Text)
listChildrenResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChildrenResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListChildrenResponse' :: ListChildrenResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListChildrenResponse
s@ListChildrenResponse' {} Maybe Text
a -> ListChildrenResponse
s {$sel:nextToken:ListChildrenResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListChildrenResponse)

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

instance Prelude.NFData ListChildrenResponse where
  rnf :: ListChildrenResponse -> ()
rnf ListChildrenResponse' {Int
Maybe [Child]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
children :: Maybe [Child]
$sel:httpStatus:ListChildrenResponse' :: ListChildrenResponse -> Int
$sel:nextToken:ListChildrenResponse' :: ListChildrenResponse -> Maybe Text
$sel:children:ListChildrenResponse' :: ListChildrenResponse -> Maybe [Child]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Child]
children
      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