{-# 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.ComputeOptimizer.UpdateEnrollmentStatus
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the enrollment (opt in and opt out) status of an account to the
-- Compute Optimizer service.
--
-- If the account is a management account of an organization, this action
-- can also be used to enroll member accounts of the organization.
--
-- You must have the appropriate permissions to opt in to Compute
-- Optimizer, to view its recommendations, and to opt out. For more
-- information, see
-- <https://docs.aws.amazon.com/compute-optimizer/latest/ug/security-iam.html Controlling access with Amazon Web Services Identity and Access Management>
-- in the /Compute Optimizer User Guide/.
--
-- When you opt in, Compute Optimizer automatically creates a
-- service-linked role in your account to access its data. For more
-- information, see
-- <https://docs.aws.amazon.com/compute-optimizer/latest/ug/using-service-linked-roles.html Using Service-Linked Roles for Compute Optimizer>
-- in the /Compute Optimizer User Guide/.
module Amazonka.ComputeOptimizer.UpdateEnrollmentStatus
  ( -- * Creating a Request
    UpdateEnrollmentStatus (..),
    newUpdateEnrollmentStatus,

    -- * Request Lenses
    updateEnrollmentStatus_includeMemberAccounts,
    updateEnrollmentStatus_status,

    -- * Destructuring the Response
    UpdateEnrollmentStatusResponse (..),
    newUpdateEnrollmentStatusResponse,

    -- * Response Lenses
    updateEnrollmentStatusResponse_status,
    updateEnrollmentStatusResponse_statusReason,
    updateEnrollmentStatusResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateEnrollmentStatus' smart constructor.
data UpdateEnrollmentStatus = UpdateEnrollmentStatus'
  { -- | Indicates whether to enroll member accounts of the organization if the
    -- account is the management account of an organization.
    UpdateEnrollmentStatus -> Maybe Bool
includeMemberAccounts :: Prelude.Maybe Prelude.Bool,
    -- | The new enrollment status of the account.
    --
    -- The following status options are available:
    --
    -- -   @Active@ - Opts in your account to the Compute Optimizer service.
    --     Compute Optimizer begins analyzing the configuration and utilization
    --     metrics of your Amazon Web Services resources after you opt in. For
    --     more information, see
    --     <https://docs.aws.amazon.com/compute-optimizer/latest/ug/metrics.html Metrics analyzed by Compute Optimizer>
    --     in the /Compute Optimizer User Guide/.
    --
    -- -   @Inactive@ - Opts out your account from the Compute Optimizer
    --     service. Your account\'s recommendations and related metrics data
    --     will be deleted from Compute Optimizer after you opt out.
    --
    -- The @Pending@ and @Failed@ options cannot be used to update the
    -- enrollment status of an account. They are returned in the response of a
    -- request to update the enrollment status of an account.
    UpdateEnrollmentStatus -> Status
status :: Status
  }
  deriving (UpdateEnrollmentStatus -> UpdateEnrollmentStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateEnrollmentStatus -> UpdateEnrollmentStatus -> Bool
$c/= :: UpdateEnrollmentStatus -> UpdateEnrollmentStatus -> Bool
== :: UpdateEnrollmentStatus -> UpdateEnrollmentStatus -> Bool
$c== :: UpdateEnrollmentStatus -> UpdateEnrollmentStatus -> Bool
Prelude.Eq, ReadPrec [UpdateEnrollmentStatus]
ReadPrec UpdateEnrollmentStatus
Int -> ReadS UpdateEnrollmentStatus
ReadS [UpdateEnrollmentStatus]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateEnrollmentStatus]
$creadListPrec :: ReadPrec [UpdateEnrollmentStatus]
readPrec :: ReadPrec UpdateEnrollmentStatus
$creadPrec :: ReadPrec UpdateEnrollmentStatus
readList :: ReadS [UpdateEnrollmentStatus]
$creadList :: ReadS [UpdateEnrollmentStatus]
readsPrec :: Int -> ReadS UpdateEnrollmentStatus
$creadsPrec :: Int -> ReadS UpdateEnrollmentStatus
Prelude.Read, Int -> UpdateEnrollmentStatus -> ShowS
[UpdateEnrollmentStatus] -> ShowS
UpdateEnrollmentStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateEnrollmentStatus] -> ShowS
$cshowList :: [UpdateEnrollmentStatus] -> ShowS
show :: UpdateEnrollmentStatus -> String
$cshow :: UpdateEnrollmentStatus -> String
showsPrec :: Int -> UpdateEnrollmentStatus -> ShowS
$cshowsPrec :: Int -> UpdateEnrollmentStatus -> ShowS
Prelude.Show, forall x. Rep UpdateEnrollmentStatus x -> UpdateEnrollmentStatus
forall x. UpdateEnrollmentStatus -> Rep UpdateEnrollmentStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateEnrollmentStatus x -> UpdateEnrollmentStatus
$cfrom :: forall x. UpdateEnrollmentStatus -> Rep UpdateEnrollmentStatus x
Prelude.Generic)

-- |
-- Create a value of 'UpdateEnrollmentStatus' 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:
--
-- 'includeMemberAccounts', 'updateEnrollmentStatus_includeMemberAccounts' - Indicates whether to enroll member accounts of the organization if the
-- account is the management account of an organization.
--
-- 'status', 'updateEnrollmentStatus_status' - The new enrollment status of the account.
--
-- The following status options are available:
--
-- -   @Active@ - Opts in your account to the Compute Optimizer service.
--     Compute Optimizer begins analyzing the configuration and utilization
--     metrics of your Amazon Web Services resources after you opt in. For
--     more information, see
--     <https://docs.aws.amazon.com/compute-optimizer/latest/ug/metrics.html Metrics analyzed by Compute Optimizer>
--     in the /Compute Optimizer User Guide/.
--
-- -   @Inactive@ - Opts out your account from the Compute Optimizer
--     service. Your account\'s recommendations and related metrics data
--     will be deleted from Compute Optimizer after you opt out.
--
-- The @Pending@ and @Failed@ options cannot be used to update the
-- enrollment status of an account. They are returned in the response of a
-- request to update the enrollment status of an account.
newUpdateEnrollmentStatus ::
  -- | 'status'
  Status ->
  UpdateEnrollmentStatus
newUpdateEnrollmentStatus :: Status -> UpdateEnrollmentStatus
newUpdateEnrollmentStatus Status
pStatus_ =
  UpdateEnrollmentStatus'
    { $sel:includeMemberAccounts:UpdateEnrollmentStatus' :: Maybe Bool
includeMemberAccounts =
        forall a. Maybe a
Prelude.Nothing,
      $sel:status:UpdateEnrollmentStatus' :: Status
status = Status
pStatus_
    }

-- | Indicates whether to enroll member accounts of the organization if the
-- account is the management account of an organization.
updateEnrollmentStatus_includeMemberAccounts :: Lens.Lens' UpdateEnrollmentStatus (Prelude.Maybe Prelude.Bool)
updateEnrollmentStatus_includeMemberAccounts :: Lens' UpdateEnrollmentStatus (Maybe Bool)
updateEnrollmentStatus_includeMemberAccounts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnrollmentStatus' {Maybe Bool
includeMemberAccounts :: Maybe Bool
$sel:includeMemberAccounts:UpdateEnrollmentStatus' :: UpdateEnrollmentStatus -> Maybe Bool
includeMemberAccounts} -> Maybe Bool
includeMemberAccounts) (\s :: UpdateEnrollmentStatus
s@UpdateEnrollmentStatus' {} Maybe Bool
a -> UpdateEnrollmentStatus
s {$sel:includeMemberAccounts:UpdateEnrollmentStatus' :: Maybe Bool
includeMemberAccounts = Maybe Bool
a} :: UpdateEnrollmentStatus)

-- | The new enrollment status of the account.
--
-- The following status options are available:
--
-- -   @Active@ - Opts in your account to the Compute Optimizer service.
--     Compute Optimizer begins analyzing the configuration and utilization
--     metrics of your Amazon Web Services resources after you opt in. For
--     more information, see
--     <https://docs.aws.amazon.com/compute-optimizer/latest/ug/metrics.html Metrics analyzed by Compute Optimizer>
--     in the /Compute Optimizer User Guide/.
--
-- -   @Inactive@ - Opts out your account from the Compute Optimizer
--     service. Your account\'s recommendations and related metrics data
--     will be deleted from Compute Optimizer after you opt out.
--
-- The @Pending@ and @Failed@ options cannot be used to update the
-- enrollment status of an account. They are returned in the response of a
-- request to update the enrollment status of an account.
updateEnrollmentStatus_status :: Lens.Lens' UpdateEnrollmentStatus Status
updateEnrollmentStatus_status :: Lens' UpdateEnrollmentStatus Status
updateEnrollmentStatus_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnrollmentStatus' {Status
status :: Status
$sel:status:UpdateEnrollmentStatus' :: UpdateEnrollmentStatus -> Status
status} -> Status
status) (\s :: UpdateEnrollmentStatus
s@UpdateEnrollmentStatus' {} Status
a -> UpdateEnrollmentStatus
s {$sel:status:UpdateEnrollmentStatus' :: Status
status = Status
a} :: UpdateEnrollmentStatus)

instance Core.AWSRequest UpdateEnrollmentStatus where
  type
    AWSResponse UpdateEnrollmentStatus =
      UpdateEnrollmentStatusResponse
  request :: (Service -> Service)
-> UpdateEnrollmentStatus -> Request UpdateEnrollmentStatus
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 UpdateEnrollmentStatus
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateEnrollmentStatus)))
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 Status -> Maybe Text -> Int -> UpdateEnrollmentStatusResponse
UpdateEnrollmentStatusResponse'
            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
"status")
            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
"statusReason")
            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 UpdateEnrollmentStatus where
  hashWithSalt :: Int -> UpdateEnrollmentStatus -> Int
hashWithSalt Int
_salt UpdateEnrollmentStatus' {Maybe Bool
Status
status :: Status
includeMemberAccounts :: Maybe Bool
$sel:status:UpdateEnrollmentStatus' :: UpdateEnrollmentStatus -> Status
$sel:includeMemberAccounts:UpdateEnrollmentStatus' :: UpdateEnrollmentStatus -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
includeMemberAccounts
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Status
status

instance Prelude.NFData UpdateEnrollmentStatus where
  rnf :: UpdateEnrollmentStatus -> ()
rnf UpdateEnrollmentStatus' {Maybe Bool
Status
status :: Status
includeMemberAccounts :: Maybe Bool
$sel:status:UpdateEnrollmentStatus' :: UpdateEnrollmentStatus -> Status
$sel:includeMemberAccounts:UpdateEnrollmentStatus' :: UpdateEnrollmentStatus -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
includeMemberAccounts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Status
status

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

instance Data.ToJSON UpdateEnrollmentStatus where
  toJSON :: UpdateEnrollmentStatus -> Value
toJSON UpdateEnrollmentStatus' {Maybe Bool
Status
status :: Status
includeMemberAccounts :: Maybe Bool
$sel:status:UpdateEnrollmentStatus' :: UpdateEnrollmentStatus -> Status
$sel:includeMemberAccounts:UpdateEnrollmentStatus' :: UpdateEnrollmentStatus -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"includeMemberAccounts" 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 Bool
includeMemberAccounts,
            forall a. a -> Maybe a
Prelude.Just (Key
"status" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Status
status)
          ]
      )

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

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

-- | /See:/ 'newUpdateEnrollmentStatusResponse' smart constructor.
data UpdateEnrollmentStatusResponse = UpdateEnrollmentStatusResponse'
  { -- | The enrollment status of the account.
    UpdateEnrollmentStatusResponse -> Maybe Status
status :: Prelude.Maybe Status,
    -- | The reason for the enrollment status of the account. For example, an
    -- account might show a status of @Pending@ because member accounts of an
    -- organization require more time to be enrolled in the service.
    UpdateEnrollmentStatusResponse -> Maybe Text
statusReason :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateEnrollmentStatusResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateEnrollmentStatusResponse
-> UpdateEnrollmentStatusResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateEnrollmentStatusResponse
-> UpdateEnrollmentStatusResponse -> Bool
$c/= :: UpdateEnrollmentStatusResponse
-> UpdateEnrollmentStatusResponse -> Bool
== :: UpdateEnrollmentStatusResponse
-> UpdateEnrollmentStatusResponse -> Bool
$c== :: UpdateEnrollmentStatusResponse
-> UpdateEnrollmentStatusResponse -> Bool
Prelude.Eq, ReadPrec [UpdateEnrollmentStatusResponse]
ReadPrec UpdateEnrollmentStatusResponse
Int -> ReadS UpdateEnrollmentStatusResponse
ReadS [UpdateEnrollmentStatusResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateEnrollmentStatusResponse]
$creadListPrec :: ReadPrec [UpdateEnrollmentStatusResponse]
readPrec :: ReadPrec UpdateEnrollmentStatusResponse
$creadPrec :: ReadPrec UpdateEnrollmentStatusResponse
readList :: ReadS [UpdateEnrollmentStatusResponse]
$creadList :: ReadS [UpdateEnrollmentStatusResponse]
readsPrec :: Int -> ReadS UpdateEnrollmentStatusResponse
$creadsPrec :: Int -> ReadS UpdateEnrollmentStatusResponse
Prelude.Read, Int -> UpdateEnrollmentStatusResponse -> ShowS
[UpdateEnrollmentStatusResponse] -> ShowS
UpdateEnrollmentStatusResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateEnrollmentStatusResponse] -> ShowS
$cshowList :: [UpdateEnrollmentStatusResponse] -> ShowS
show :: UpdateEnrollmentStatusResponse -> String
$cshow :: UpdateEnrollmentStatusResponse -> String
showsPrec :: Int -> UpdateEnrollmentStatusResponse -> ShowS
$cshowsPrec :: Int -> UpdateEnrollmentStatusResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateEnrollmentStatusResponse x
-> UpdateEnrollmentStatusResponse
forall x.
UpdateEnrollmentStatusResponse
-> Rep UpdateEnrollmentStatusResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateEnrollmentStatusResponse x
-> UpdateEnrollmentStatusResponse
$cfrom :: forall x.
UpdateEnrollmentStatusResponse
-> Rep UpdateEnrollmentStatusResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateEnrollmentStatusResponse' 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:
--
-- 'status', 'updateEnrollmentStatusResponse_status' - The enrollment status of the account.
--
-- 'statusReason', 'updateEnrollmentStatusResponse_statusReason' - The reason for the enrollment status of the account. For example, an
-- account might show a status of @Pending@ because member accounts of an
-- organization require more time to be enrolled in the service.
--
-- 'httpStatus', 'updateEnrollmentStatusResponse_httpStatus' - The response's http status code.
newUpdateEnrollmentStatusResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateEnrollmentStatusResponse
newUpdateEnrollmentStatusResponse :: Int -> UpdateEnrollmentStatusResponse
newUpdateEnrollmentStatusResponse Int
pHttpStatus_ =
  UpdateEnrollmentStatusResponse'
    { $sel:status:UpdateEnrollmentStatusResponse' :: Maybe Status
status =
        forall a. Maybe a
Prelude.Nothing,
      $sel:statusReason:UpdateEnrollmentStatusResponse' :: Maybe Text
statusReason = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateEnrollmentStatusResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The enrollment status of the account.
updateEnrollmentStatusResponse_status :: Lens.Lens' UpdateEnrollmentStatusResponse (Prelude.Maybe Status)
updateEnrollmentStatusResponse_status :: Lens' UpdateEnrollmentStatusResponse (Maybe Status)
updateEnrollmentStatusResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnrollmentStatusResponse' {Maybe Status
status :: Maybe Status
$sel:status:UpdateEnrollmentStatusResponse' :: UpdateEnrollmentStatusResponse -> Maybe Status
status} -> Maybe Status
status) (\s :: UpdateEnrollmentStatusResponse
s@UpdateEnrollmentStatusResponse' {} Maybe Status
a -> UpdateEnrollmentStatusResponse
s {$sel:status:UpdateEnrollmentStatusResponse' :: Maybe Status
status = Maybe Status
a} :: UpdateEnrollmentStatusResponse)

-- | The reason for the enrollment status of the account. For example, an
-- account might show a status of @Pending@ because member accounts of an
-- organization require more time to be enrolled in the service.
updateEnrollmentStatusResponse_statusReason :: Lens.Lens' UpdateEnrollmentStatusResponse (Prelude.Maybe Prelude.Text)
updateEnrollmentStatusResponse_statusReason :: Lens' UpdateEnrollmentStatusResponse (Maybe Text)
updateEnrollmentStatusResponse_statusReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnrollmentStatusResponse' {Maybe Text
statusReason :: Maybe Text
$sel:statusReason:UpdateEnrollmentStatusResponse' :: UpdateEnrollmentStatusResponse -> Maybe Text
statusReason} -> Maybe Text
statusReason) (\s :: UpdateEnrollmentStatusResponse
s@UpdateEnrollmentStatusResponse' {} Maybe Text
a -> UpdateEnrollmentStatusResponse
s {$sel:statusReason:UpdateEnrollmentStatusResponse' :: Maybe Text
statusReason = Maybe Text
a} :: UpdateEnrollmentStatusResponse)

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

instance
  Prelude.NFData
    UpdateEnrollmentStatusResponse
  where
  rnf :: UpdateEnrollmentStatusResponse -> ()
rnf UpdateEnrollmentStatusResponse' {Int
Maybe Text
Maybe Status
httpStatus :: Int
statusReason :: Maybe Text
status :: Maybe Status
$sel:httpStatus:UpdateEnrollmentStatusResponse' :: UpdateEnrollmentStatusResponse -> Int
$sel:statusReason:UpdateEnrollmentStatusResponse' :: UpdateEnrollmentStatusResponse -> Maybe Text
$sel:status:UpdateEnrollmentStatusResponse' :: UpdateEnrollmentStatusResponse -> Maybe Status
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Status
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
statusReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus