{-# 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.DescribeUpdateDirectory
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the updates of a directory for a particular update type.
--
-- This operation returns paginated results.
module Amazonka.DirectoryService.DescribeUpdateDirectory
  ( -- * Creating a Request
    DescribeUpdateDirectory (..),
    newDescribeUpdateDirectory,

    -- * Request Lenses
    describeUpdateDirectory_nextToken,
    describeUpdateDirectory_regionName,
    describeUpdateDirectory_directoryId,
    describeUpdateDirectory_updateType,

    -- * Destructuring the Response
    DescribeUpdateDirectoryResponse (..),
    newDescribeUpdateDirectoryResponse,

    -- * Response Lenses
    describeUpdateDirectoryResponse_nextToken,
    describeUpdateDirectoryResponse_updateActivities,
    describeUpdateDirectoryResponse_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:/ 'newDescribeUpdateDirectory' smart constructor.
data DescribeUpdateDirectory = DescribeUpdateDirectory'
  { -- | The @DescribeUpdateDirectoryResult@. NextToken value from a previous
    -- call to DescribeUpdateDirectory. Pass null if this is the first call.
    DescribeUpdateDirectory -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The name of the Region.
    DescribeUpdateDirectory -> Maybe Text
regionName :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier of the directory.
    DescribeUpdateDirectory -> Text
directoryId :: Prelude.Text,
    -- | The type of updates you want to describe for the directory.
    DescribeUpdateDirectory -> UpdateType
updateType :: UpdateType
  }
  deriving (DescribeUpdateDirectory -> DescribeUpdateDirectory -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeUpdateDirectory -> DescribeUpdateDirectory -> Bool
$c/= :: DescribeUpdateDirectory -> DescribeUpdateDirectory -> Bool
== :: DescribeUpdateDirectory -> DescribeUpdateDirectory -> Bool
$c== :: DescribeUpdateDirectory -> DescribeUpdateDirectory -> Bool
Prelude.Eq, ReadPrec [DescribeUpdateDirectory]
ReadPrec DescribeUpdateDirectory
Int -> ReadS DescribeUpdateDirectory
ReadS [DescribeUpdateDirectory]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeUpdateDirectory]
$creadListPrec :: ReadPrec [DescribeUpdateDirectory]
readPrec :: ReadPrec DescribeUpdateDirectory
$creadPrec :: ReadPrec DescribeUpdateDirectory
readList :: ReadS [DescribeUpdateDirectory]
$creadList :: ReadS [DescribeUpdateDirectory]
readsPrec :: Int -> ReadS DescribeUpdateDirectory
$creadsPrec :: Int -> ReadS DescribeUpdateDirectory
Prelude.Read, Int -> DescribeUpdateDirectory -> ShowS
[DescribeUpdateDirectory] -> ShowS
DescribeUpdateDirectory -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeUpdateDirectory] -> ShowS
$cshowList :: [DescribeUpdateDirectory] -> ShowS
show :: DescribeUpdateDirectory -> String
$cshow :: DescribeUpdateDirectory -> String
showsPrec :: Int -> DescribeUpdateDirectory -> ShowS
$cshowsPrec :: Int -> DescribeUpdateDirectory -> ShowS
Prelude.Show, forall x. Rep DescribeUpdateDirectory x -> DescribeUpdateDirectory
forall x. DescribeUpdateDirectory -> Rep DescribeUpdateDirectory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeUpdateDirectory x -> DescribeUpdateDirectory
$cfrom :: forall x. DescribeUpdateDirectory -> Rep DescribeUpdateDirectory x
Prelude.Generic)

-- |
-- Create a value of 'DescribeUpdateDirectory' 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', 'describeUpdateDirectory_nextToken' - The @DescribeUpdateDirectoryResult@. NextToken value from a previous
-- call to DescribeUpdateDirectory. Pass null if this is the first call.
--
-- 'regionName', 'describeUpdateDirectory_regionName' - The name of the Region.
--
-- 'directoryId', 'describeUpdateDirectory_directoryId' - The unique identifier of the directory.
--
-- 'updateType', 'describeUpdateDirectory_updateType' - The type of updates you want to describe for the directory.
newDescribeUpdateDirectory ::
  -- | 'directoryId'
  Prelude.Text ->
  -- | 'updateType'
  UpdateType ->
  DescribeUpdateDirectory
newDescribeUpdateDirectory :: Text -> UpdateType -> DescribeUpdateDirectory
newDescribeUpdateDirectory Text
pDirectoryId_ UpdateType
pUpdateType_ =
  DescribeUpdateDirectory'
    { $sel:nextToken:DescribeUpdateDirectory' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:regionName:DescribeUpdateDirectory' :: Maybe Text
regionName = forall a. Maybe a
Prelude.Nothing,
      $sel:directoryId:DescribeUpdateDirectory' :: Text
directoryId = Text
pDirectoryId_,
      $sel:updateType:DescribeUpdateDirectory' :: UpdateType
updateType = UpdateType
pUpdateType_
    }

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

-- | The name of the Region.
describeUpdateDirectory_regionName :: Lens.Lens' DescribeUpdateDirectory (Prelude.Maybe Prelude.Text)
describeUpdateDirectory_regionName :: Lens' DescribeUpdateDirectory (Maybe Text)
describeUpdateDirectory_regionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeUpdateDirectory' {Maybe Text
regionName :: Maybe Text
$sel:regionName:DescribeUpdateDirectory' :: DescribeUpdateDirectory -> Maybe Text
regionName} -> Maybe Text
regionName) (\s :: DescribeUpdateDirectory
s@DescribeUpdateDirectory' {} Maybe Text
a -> DescribeUpdateDirectory
s {$sel:regionName:DescribeUpdateDirectory' :: Maybe Text
regionName = Maybe Text
a} :: DescribeUpdateDirectory)

-- | The unique identifier of the directory.
describeUpdateDirectory_directoryId :: Lens.Lens' DescribeUpdateDirectory Prelude.Text
describeUpdateDirectory_directoryId :: Lens' DescribeUpdateDirectory Text
describeUpdateDirectory_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeUpdateDirectory' {Text
directoryId :: Text
$sel:directoryId:DescribeUpdateDirectory' :: DescribeUpdateDirectory -> Text
directoryId} -> Text
directoryId) (\s :: DescribeUpdateDirectory
s@DescribeUpdateDirectory' {} Text
a -> DescribeUpdateDirectory
s {$sel:directoryId:DescribeUpdateDirectory' :: Text
directoryId = Text
a} :: DescribeUpdateDirectory)

-- | The type of updates you want to describe for the directory.
describeUpdateDirectory_updateType :: Lens.Lens' DescribeUpdateDirectory UpdateType
describeUpdateDirectory_updateType :: Lens' DescribeUpdateDirectory UpdateType
describeUpdateDirectory_updateType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeUpdateDirectory' {UpdateType
updateType :: UpdateType
$sel:updateType:DescribeUpdateDirectory' :: DescribeUpdateDirectory -> UpdateType
updateType} -> UpdateType
updateType) (\s :: DescribeUpdateDirectory
s@DescribeUpdateDirectory' {} UpdateType
a -> DescribeUpdateDirectory
s {$sel:updateType:DescribeUpdateDirectory' :: UpdateType
updateType = UpdateType
a} :: DescribeUpdateDirectory)

instance Core.AWSPager DescribeUpdateDirectory where
  page :: DescribeUpdateDirectory
-> AWSResponse DescribeUpdateDirectory
-> Maybe DescribeUpdateDirectory
page DescribeUpdateDirectory
rq AWSResponse DescribeUpdateDirectory
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeUpdateDirectory
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeUpdateDirectoryResponse (Maybe Text)
describeUpdateDirectoryResponse_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 DescribeUpdateDirectory
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeUpdateDirectoryResponse (Maybe [UpdateInfoEntry])
describeUpdateDirectoryResponse_updateActivities
            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.$ DescribeUpdateDirectory
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeUpdateDirectory (Maybe Text)
describeUpdateDirectory_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeUpdateDirectory
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeUpdateDirectoryResponse (Maybe Text)
describeUpdateDirectoryResponse_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 DescribeUpdateDirectory where
  type
    AWSResponse DescribeUpdateDirectory =
      DescribeUpdateDirectoryResponse
  request :: (Service -> Service)
-> DescribeUpdateDirectory -> Request DescribeUpdateDirectory
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 DescribeUpdateDirectory
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeUpdateDirectory)))
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 [UpdateInfoEntry]
-> Int
-> DescribeUpdateDirectoryResponse
DescribeUpdateDirectoryResponse'
            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
"UpdateActivities"
                            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 DescribeUpdateDirectory where
  hashWithSalt :: Int -> DescribeUpdateDirectory -> Int
hashWithSalt Int
_salt DescribeUpdateDirectory' {Maybe Text
Text
UpdateType
updateType :: UpdateType
directoryId :: Text
regionName :: Maybe Text
nextToken :: Maybe Text
$sel:updateType:DescribeUpdateDirectory' :: DescribeUpdateDirectory -> UpdateType
$sel:directoryId:DescribeUpdateDirectory' :: DescribeUpdateDirectory -> Text
$sel:regionName:DescribeUpdateDirectory' :: DescribeUpdateDirectory -> Maybe Text
$sel:nextToken:DescribeUpdateDirectory' :: DescribeUpdateDirectory -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
regionName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
directoryId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` UpdateType
updateType

instance Prelude.NFData DescribeUpdateDirectory where
  rnf :: DescribeUpdateDirectory -> ()
rnf DescribeUpdateDirectory' {Maybe Text
Text
UpdateType
updateType :: UpdateType
directoryId :: Text
regionName :: Maybe Text
nextToken :: Maybe Text
$sel:updateType:DescribeUpdateDirectory' :: DescribeUpdateDirectory -> UpdateType
$sel:directoryId:DescribeUpdateDirectory' :: DescribeUpdateDirectory -> Text
$sel:regionName:DescribeUpdateDirectory' :: DescribeUpdateDirectory -> Maybe Text
$sel:nextToken:DescribeUpdateDirectory' :: DescribeUpdateDirectory -> 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 Text
regionName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
directoryId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf UpdateType
updateType

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

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

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

-- | /See:/ 'newDescribeUpdateDirectoryResponse' smart constructor.
data DescribeUpdateDirectoryResponse = DescribeUpdateDirectoryResponse'
  { -- | If not null, more results are available. Pass this value for the
    -- @NextToken@ parameter.
    DescribeUpdateDirectoryResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The list of update activities on a directory for the requested update
    -- type.
    DescribeUpdateDirectoryResponse -> Maybe [UpdateInfoEntry]
updateActivities :: Prelude.Maybe [UpdateInfoEntry],
    -- | The response's http status code.
    DescribeUpdateDirectoryResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeUpdateDirectoryResponse
-> DescribeUpdateDirectoryResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeUpdateDirectoryResponse
-> DescribeUpdateDirectoryResponse -> Bool
$c/= :: DescribeUpdateDirectoryResponse
-> DescribeUpdateDirectoryResponse -> Bool
== :: DescribeUpdateDirectoryResponse
-> DescribeUpdateDirectoryResponse -> Bool
$c== :: DescribeUpdateDirectoryResponse
-> DescribeUpdateDirectoryResponse -> Bool
Prelude.Eq, ReadPrec [DescribeUpdateDirectoryResponse]
ReadPrec DescribeUpdateDirectoryResponse
Int -> ReadS DescribeUpdateDirectoryResponse
ReadS [DescribeUpdateDirectoryResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeUpdateDirectoryResponse]
$creadListPrec :: ReadPrec [DescribeUpdateDirectoryResponse]
readPrec :: ReadPrec DescribeUpdateDirectoryResponse
$creadPrec :: ReadPrec DescribeUpdateDirectoryResponse
readList :: ReadS [DescribeUpdateDirectoryResponse]
$creadList :: ReadS [DescribeUpdateDirectoryResponse]
readsPrec :: Int -> ReadS DescribeUpdateDirectoryResponse
$creadsPrec :: Int -> ReadS DescribeUpdateDirectoryResponse
Prelude.Read, Int -> DescribeUpdateDirectoryResponse -> ShowS
[DescribeUpdateDirectoryResponse] -> ShowS
DescribeUpdateDirectoryResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeUpdateDirectoryResponse] -> ShowS
$cshowList :: [DescribeUpdateDirectoryResponse] -> ShowS
show :: DescribeUpdateDirectoryResponse -> String
$cshow :: DescribeUpdateDirectoryResponse -> String
showsPrec :: Int -> DescribeUpdateDirectoryResponse -> ShowS
$cshowsPrec :: Int -> DescribeUpdateDirectoryResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeUpdateDirectoryResponse x
-> DescribeUpdateDirectoryResponse
forall x.
DescribeUpdateDirectoryResponse
-> Rep DescribeUpdateDirectoryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeUpdateDirectoryResponse x
-> DescribeUpdateDirectoryResponse
$cfrom :: forall x.
DescribeUpdateDirectoryResponse
-> Rep DescribeUpdateDirectoryResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeUpdateDirectoryResponse' 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', 'describeUpdateDirectoryResponse_nextToken' - If not null, more results are available. Pass this value for the
-- @NextToken@ parameter.
--
-- 'updateActivities', 'describeUpdateDirectoryResponse_updateActivities' - The list of update activities on a directory for the requested update
-- type.
--
-- 'httpStatus', 'describeUpdateDirectoryResponse_httpStatus' - The response's http status code.
newDescribeUpdateDirectoryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeUpdateDirectoryResponse
newDescribeUpdateDirectoryResponse :: Int -> DescribeUpdateDirectoryResponse
newDescribeUpdateDirectoryResponse Int
pHttpStatus_ =
  DescribeUpdateDirectoryResponse'
    { $sel:nextToken:DescribeUpdateDirectoryResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:updateActivities:DescribeUpdateDirectoryResponse' :: Maybe [UpdateInfoEntry]
updateActivities = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeUpdateDirectoryResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If not null, more results are available. Pass this value for the
-- @NextToken@ parameter.
describeUpdateDirectoryResponse_nextToken :: Lens.Lens' DescribeUpdateDirectoryResponse (Prelude.Maybe Prelude.Text)
describeUpdateDirectoryResponse_nextToken :: Lens' DescribeUpdateDirectoryResponse (Maybe Text)
describeUpdateDirectoryResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeUpdateDirectoryResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeUpdateDirectoryResponse' :: DescribeUpdateDirectoryResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeUpdateDirectoryResponse
s@DescribeUpdateDirectoryResponse' {} Maybe Text
a -> DescribeUpdateDirectoryResponse
s {$sel:nextToken:DescribeUpdateDirectoryResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeUpdateDirectoryResponse)

-- | The list of update activities on a directory for the requested update
-- type.
describeUpdateDirectoryResponse_updateActivities :: Lens.Lens' DescribeUpdateDirectoryResponse (Prelude.Maybe [UpdateInfoEntry])
describeUpdateDirectoryResponse_updateActivities :: Lens' DescribeUpdateDirectoryResponse (Maybe [UpdateInfoEntry])
describeUpdateDirectoryResponse_updateActivities = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeUpdateDirectoryResponse' {Maybe [UpdateInfoEntry]
updateActivities :: Maybe [UpdateInfoEntry]
$sel:updateActivities:DescribeUpdateDirectoryResponse' :: DescribeUpdateDirectoryResponse -> Maybe [UpdateInfoEntry]
updateActivities} -> Maybe [UpdateInfoEntry]
updateActivities) (\s :: DescribeUpdateDirectoryResponse
s@DescribeUpdateDirectoryResponse' {} Maybe [UpdateInfoEntry]
a -> DescribeUpdateDirectoryResponse
s {$sel:updateActivities:DescribeUpdateDirectoryResponse' :: Maybe [UpdateInfoEntry]
updateActivities = Maybe [UpdateInfoEntry]
a} :: DescribeUpdateDirectoryResponse) 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.
describeUpdateDirectoryResponse_httpStatus :: Lens.Lens' DescribeUpdateDirectoryResponse Prelude.Int
describeUpdateDirectoryResponse_httpStatus :: Lens' DescribeUpdateDirectoryResponse Int
describeUpdateDirectoryResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeUpdateDirectoryResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeUpdateDirectoryResponse' :: DescribeUpdateDirectoryResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeUpdateDirectoryResponse
s@DescribeUpdateDirectoryResponse' {} Int
a -> DescribeUpdateDirectoryResponse
s {$sel:httpStatus:DescribeUpdateDirectoryResponse' :: Int
httpStatus = Int
a} :: DescribeUpdateDirectoryResponse)

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