{-# 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.Backup.UpdateFramework
-- 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 an existing framework identified by its @FrameworkName@ with the
-- input document in JSON format.
module Amazonka.Backup.UpdateFramework
  ( -- * Creating a Request
    UpdateFramework (..),
    newUpdateFramework,

    -- * Request Lenses
    updateFramework_frameworkControls,
    updateFramework_frameworkDescription,
    updateFramework_idempotencyToken,
    updateFramework_frameworkName,

    -- * Destructuring the Response
    UpdateFrameworkResponse (..),
    newUpdateFrameworkResponse,

    -- * Response Lenses
    updateFrameworkResponse_creationTime,
    updateFrameworkResponse_frameworkArn,
    updateFrameworkResponse_frameworkName,
    updateFrameworkResponse_httpStatus,
  )
where

import Amazonka.Backup.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:/ 'newUpdateFramework' smart constructor.
data UpdateFramework = UpdateFramework'
  { -- | A list of the controls that make up the framework. Each control in the
    -- list has a name, input parameters, and scope.
    UpdateFramework -> Maybe [FrameworkControl]
frameworkControls :: Prelude.Maybe [FrameworkControl],
    -- | An optional description of the framework with a maximum 1,024
    -- characters.
    UpdateFramework -> Maybe Text
frameworkDescription :: Prelude.Maybe Prelude.Text,
    -- | A customer-chosen string that you can use to distinguish between
    -- otherwise identical calls to @UpdateFrameworkInput@. Retrying a
    -- successful request with the same idempotency token results in a success
    -- message with no action taken.
    UpdateFramework -> Maybe Text
idempotencyToken :: Prelude.Maybe Prelude.Text,
    -- | The unique name of a framework. This name is between 1 and 256
    -- characters, starting with a letter, and consisting of letters (a-z,
    -- A-Z), numbers (0-9), and underscores (_).
    UpdateFramework -> Text
frameworkName :: Prelude.Text
  }
  deriving (UpdateFramework -> UpdateFramework -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateFramework -> UpdateFramework -> Bool
$c/= :: UpdateFramework -> UpdateFramework -> Bool
== :: UpdateFramework -> UpdateFramework -> Bool
$c== :: UpdateFramework -> UpdateFramework -> Bool
Prelude.Eq, ReadPrec [UpdateFramework]
ReadPrec UpdateFramework
Int -> ReadS UpdateFramework
ReadS [UpdateFramework]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateFramework]
$creadListPrec :: ReadPrec [UpdateFramework]
readPrec :: ReadPrec UpdateFramework
$creadPrec :: ReadPrec UpdateFramework
readList :: ReadS [UpdateFramework]
$creadList :: ReadS [UpdateFramework]
readsPrec :: Int -> ReadS UpdateFramework
$creadsPrec :: Int -> ReadS UpdateFramework
Prelude.Read, Int -> UpdateFramework -> ShowS
[UpdateFramework] -> ShowS
UpdateFramework -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateFramework] -> ShowS
$cshowList :: [UpdateFramework] -> ShowS
show :: UpdateFramework -> String
$cshow :: UpdateFramework -> String
showsPrec :: Int -> UpdateFramework -> ShowS
$cshowsPrec :: Int -> UpdateFramework -> ShowS
Prelude.Show, forall x. Rep UpdateFramework x -> UpdateFramework
forall x. UpdateFramework -> Rep UpdateFramework x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateFramework x -> UpdateFramework
$cfrom :: forall x. UpdateFramework -> Rep UpdateFramework x
Prelude.Generic)

-- |
-- Create a value of 'UpdateFramework' 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:
--
-- 'frameworkControls', 'updateFramework_frameworkControls' - A list of the controls that make up the framework. Each control in the
-- list has a name, input parameters, and scope.
--
-- 'frameworkDescription', 'updateFramework_frameworkDescription' - An optional description of the framework with a maximum 1,024
-- characters.
--
-- 'idempotencyToken', 'updateFramework_idempotencyToken' - A customer-chosen string that you can use to distinguish between
-- otherwise identical calls to @UpdateFrameworkInput@. Retrying a
-- successful request with the same idempotency token results in a success
-- message with no action taken.
--
-- 'frameworkName', 'updateFramework_frameworkName' - The unique name of a framework. This name is between 1 and 256
-- characters, starting with a letter, and consisting of letters (a-z,
-- A-Z), numbers (0-9), and underscores (_).
newUpdateFramework ::
  -- | 'frameworkName'
  Prelude.Text ->
  UpdateFramework
newUpdateFramework :: Text -> UpdateFramework
newUpdateFramework Text
pFrameworkName_ =
  UpdateFramework'
    { $sel:frameworkControls:UpdateFramework' :: Maybe [FrameworkControl]
frameworkControls =
        forall a. Maybe a
Prelude.Nothing,
      $sel:frameworkDescription:UpdateFramework' :: Maybe Text
frameworkDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:idempotencyToken:UpdateFramework' :: Maybe Text
idempotencyToken = forall a. Maybe a
Prelude.Nothing,
      $sel:frameworkName:UpdateFramework' :: Text
frameworkName = Text
pFrameworkName_
    }

-- | A list of the controls that make up the framework. Each control in the
-- list has a name, input parameters, and scope.
updateFramework_frameworkControls :: Lens.Lens' UpdateFramework (Prelude.Maybe [FrameworkControl])
updateFramework_frameworkControls :: Lens' UpdateFramework (Maybe [FrameworkControl])
updateFramework_frameworkControls = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFramework' {Maybe [FrameworkControl]
frameworkControls :: Maybe [FrameworkControl]
$sel:frameworkControls:UpdateFramework' :: UpdateFramework -> Maybe [FrameworkControl]
frameworkControls} -> Maybe [FrameworkControl]
frameworkControls) (\s :: UpdateFramework
s@UpdateFramework' {} Maybe [FrameworkControl]
a -> UpdateFramework
s {$sel:frameworkControls:UpdateFramework' :: Maybe [FrameworkControl]
frameworkControls = Maybe [FrameworkControl]
a} :: UpdateFramework) 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

-- | An optional description of the framework with a maximum 1,024
-- characters.
updateFramework_frameworkDescription :: Lens.Lens' UpdateFramework (Prelude.Maybe Prelude.Text)
updateFramework_frameworkDescription :: Lens' UpdateFramework (Maybe Text)
updateFramework_frameworkDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFramework' {Maybe Text
frameworkDescription :: Maybe Text
$sel:frameworkDescription:UpdateFramework' :: UpdateFramework -> Maybe Text
frameworkDescription} -> Maybe Text
frameworkDescription) (\s :: UpdateFramework
s@UpdateFramework' {} Maybe Text
a -> UpdateFramework
s {$sel:frameworkDescription:UpdateFramework' :: Maybe Text
frameworkDescription = Maybe Text
a} :: UpdateFramework)

-- | A customer-chosen string that you can use to distinguish between
-- otherwise identical calls to @UpdateFrameworkInput@. Retrying a
-- successful request with the same idempotency token results in a success
-- message with no action taken.
updateFramework_idempotencyToken :: Lens.Lens' UpdateFramework (Prelude.Maybe Prelude.Text)
updateFramework_idempotencyToken :: Lens' UpdateFramework (Maybe Text)
updateFramework_idempotencyToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFramework' {Maybe Text
idempotencyToken :: Maybe Text
$sel:idempotencyToken:UpdateFramework' :: UpdateFramework -> Maybe Text
idempotencyToken} -> Maybe Text
idempotencyToken) (\s :: UpdateFramework
s@UpdateFramework' {} Maybe Text
a -> UpdateFramework
s {$sel:idempotencyToken:UpdateFramework' :: Maybe Text
idempotencyToken = Maybe Text
a} :: UpdateFramework)

-- | The unique name of a framework. This name is between 1 and 256
-- characters, starting with a letter, and consisting of letters (a-z,
-- A-Z), numbers (0-9), and underscores (_).
updateFramework_frameworkName :: Lens.Lens' UpdateFramework Prelude.Text
updateFramework_frameworkName :: Lens' UpdateFramework Text
updateFramework_frameworkName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFramework' {Text
frameworkName :: Text
$sel:frameworkName:UpdateFramework' :: UpdateFramework -> Text
frameworkName} -> Text
frameworkName) (\s :: UpdateFramework
s@UpdateFramework' {} Text
a -> UpdateFramework
s {$sel:frameworkName:UpdateFramework' :: Text
frameworkName = Text
a} :: UpdateFramework)

instance Core.AWSRequest UpdateFramework where
  type
    AWSResponse UpdateFramework =
      UpdateFrameworkResponse
  request :: (Service -> Service) -> UpdateFramework -> Request UpdateFramework
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateFramework
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateFramework)))
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 POSIX
-> Maybe Text -> Maybe Text -> Int -> UpdateFrameworkResponse
UpdateFrameworkResponse'
            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
"CreationTime")
            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
"FrameworkArn")
            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
"FrameworkName")
            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 UpdateFramework where
  hashWithSalt :: Int -> UpdateFramework -> Int
hashWithSalt Int
_salt UpdateFramework' {Maybe [FrameworkControl]
Maybe Text
Text
frameworkName :: Text
idempotencyToken :: Maybe Text
frameworkDescription :: Maybe Text
frameworkControls :: Maybe [FrameworkControl]
$sel:frameworkName:UpdateFramework' :: UpdateFramework -> Text
$sel:idempotencyToken:UpdateFramework' :: UpdateFramework -> Maybe Text
$sel:frameworkDescription:UpdateFramework' :: UpdateFramework -> Maybe Text
$sel:frameworkControls:UpdateFramework' :: UpdateFramework -> Maybe [FrameworkControl]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [FrameworkControl]
frameworkControls
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
frameworkDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
idempotencyToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
frameworkName

instance Prelude.NFData UpdateFramework where
  rnf :: UpdateFramework -> ()
rnf UpdateFramework' {Maybe [FrameworkControl]
Maybe Text
Text
frameworkName :: Text
idempotencyToken :: Maybe Text
frameworkDescription :: Maybe Text
frameworkControls :: Maybe [FrameworkControl]
$sel:frameworkName:UpdateFramework' :: UpdateFramework -> Text
$sel:idempotencyToken:UpdateFramework' :: UpdateFramework -> Maybe Text
$sel:frameworkDescription:UpdateFramework' :: UpdateFramework -> Maybe Text
$sel:frameworkControls:UpdateFramework' :: UpdateFramework -> Maybe [FrameworkControl]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [FrameworkControl]
frameworkControls
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
frameworkDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
idempotencyToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
frameworkName

instance Data.ToHeaders UpdateFramework where
  toHeaders :: UpdateFramework -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateFramework where
  toJSON :: UpdateFramework -> Value
toJSON UpdateFramework' {Maybe [FrameworkControl]
Maybe Text
Text
frameworkName :: Text
idempotencyToken :: Maybe Text
frameworkDescription :: Maybe Text
frameworkControls :: Maybe [FrameworkControl]
$sel:frameworkName:UpdateFramework' :: UpdateFramework -> Text
$sel:idempotencyToken:UpdateFramework' :: UpdateFramework -> Maybe Text
$sel:frameworkDescription:UpdateFramework' :: UpdateFramework -> Maybe Text
$sel:frameworkControls:UpdateFramework' :: UpdateFramework -> Maybe [FrameworkControl]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"FrameworkControls" 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 [FrameworkControl]
frameworkControls,
            (Key
"FrameworkDescription" 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
frameworkDescription,
            (Key
"IdempotencyToken" 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
idempotencyToken
          ]
      )

instance Data.ToPath UpdateFramework where
  toPath :: UpdateFramework -> ByteString
toPath UpdateFramework' {Maybe [FrameworkControl]
Maybe Text
Text
frameworkName :: Text
idempotencyToken :: Maybe Text
frameworkDescription :: Maybe Text
frameworkControls :: Maybe [FrameworkControl]
$sel:frameworkName:UpdateFramework' :: UpdateFramework -> Text
$sel:idempotencyToken:UpdateFramework' :: UpdateFramework -> Maybe Text
$sel:frameworkDescription:UpdateFramework' :: UpdateFramework -> Maybe Text
$sel:frameworkControls:UpdateFramework' :: UpdateFramework -> Maybe [FrameworkControl]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/audit/frameworks/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
frameworkName]

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

-- | /See:/ 'newUpdateFrameworkResponse' smart constructor.
data UpdateFrameworkResponse = UpdateFrameworkResponse'
  { -- | The date and time that a framework is created, in ISO 8601
    -- representation. The value of @CreationTime@ is accurate to milliseconds.
    -- For example, 2020-07-10T15:00:00.000-08:00 represents the 10th of July
    -- 2020 at 3:00 PM 8 hours behind UTC.
    UpdateFrameworkResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | An Amazon Resource Name (ARN) that uniquely identifies a resource. The
    -- format of the ARN depends on the resource type.
    UpdateFrameworkResponse -> Maybe Text
frameworkArn :: Prelude.Maybe Prelude.Text,
    -- | The unique name of a framework. This name is between 1 and 256
    -- characters, starting with a letter, and consisting of letters (a-z,
    -- A-Z), numbers (0-9), and underscores (_).
    UpdateFrameworkResponse -> Maybe Text
frameworkName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateFrameworkResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateFrameworkResponse -> UpdateFrameworkResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateFrameworkResponse -> UpdateFrameworkResponse -> Bool
$c/= :: UpdateFrameworkResponse -> UpdateFrameworkResponse -> Bool
== :: UpdateFrameworkResponse -> UpdateFrameworkResponse -> Bool
$c== :: UpdateFrameworkResponse -> UpdateFrameworkResponse -> Bool
Prelude.Eq, ReadPrec [UpdateFrameworkResponse]
ReadPrec UpdateFrameworkResponse
Int -> ReadS UpdateFrameworkResponse
ReadS [UpdateFrameworkResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateFrameworkResponse]
$creadListPrec :: ReadPrec [UpdateFrameworkResponse]
readPrec :: ReadPrec UpdateFrameworkResponse
$creadPrec :: ReadPrec UpdateFrameworkResponse
readList :: ReadS [UpdateFrameworkResponse]
$creadList :: ReadS [UpdateFrameworkResponse]
readsPrec :: Int -> ReadS UpdateFrameworkResponse
$creadsPrec :: Int -> ReadS UpdateFrameworkResponse
Prelude.Read, Int -> UpdateFrameworkResponse -> ShowS
[UpdateFrameworkResponse] -> ShowS
UpdateFrameworkResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateFrameworkResponse] -> ShowS
$cshowList :: [UpdateFrameworkResponse] -> ShowS
show :: UpdateFrameworkResponse -> String
$cshow :: UpdateFrameworkResponse -> String
showsPrec :: Int -> UpdateFrameworkResponse -> ShowS
$cshowsPrec :: Int -> UpdateFrameworkResponse -> ShowS
Prelude.Show, forall x. Rep UpdateFrameworkResponse x -> UpdateFrameworkResponse
forall x. UpdateFrameworkResponse -> Rep UpdateFrameworkResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateFrameworkResponse x -> UpdateFrameworkResponse
$cfrom :: forall x. UpdateFrameworkResponse -> Rep UpdateFrameworkResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateFrameworkResponse' 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:
--
-- 'creationTime', 'updateFrameworkResponse_creationTime' - The date and time that a framework is created, in ISO 8601
-- representation. The value of @CreationTime@ is accurate to milliseconds.
-- For example, 2020-07-10T15:00:00.000-08:00 represents the 10th of July
-- 2020 at 3:00 PM 8 hours behind UTC.
--
-- 'frameworkArn', 'updateFrameworkResponse_frameworkArn' - An Amazon Resource Name (ARN) that uniquely identifies a resource. The
-- format of the ARN depends on the resource type.
--
-- 'frameworkName', 'updateFrameworkResponse_frameworkName' - The unique name of a framework. This name is between 1 and 256
-- characters, starting with a letter, and consisting of letters (a-z,
-- A-Z), numbers (0-9), and underscores (_).
--
-- 'httpStatus', 'updateFrameworkResponse_httpStatus' - The response's http status code.
newUpdateFrameworkResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateFrameworkResponse
newUpdateFrameworkResponse :: Int -> UpdateFrameworkResponse
newUpdateFrameworkResponse Int
pHttpStatus_ =
  UpdateFrameworkResponse'
    { $sel:creationTime:UpdateFrameworkResponse' :: Maybe POSIX
creationTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:frameworkArn:UpdateFrameworkResponse' :: Maybe Text
frameworkArn = forall a. Maybe a
Prelude.Nothing,
      $sel:frameworkName:UpdateFrameworkResponse' :: Maybe Text
frameworkName = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateFrameworkResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The date and time that a framework is created, in ISO 8601
-- representation. The value of @CreationTime@ is accurate to milliseconds.
-- For example, 2020-07-10T15:00:00.000-08:00 represents the 10th of July
-- 2020 at 3:00 PM 8 hours behind UTC.
updateFrameworkResponse_creationTime :: Lens.Lens' UpdateFrameworkResponse (Prelude.Maybe Prelude.UTCTime)
updateFrameworkResponse_creationTime :: Lens' UpdateFrameworkResponse (Maybe UTCTime)
updateFrameworkResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFrameworkResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:UpdateFrameworkResponse' :: UpdateFrameworkResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: UpdateFrameworkResponse
s@UpdateFrameworkResponse' {} Maybe POSIX
a -> UpdateFrameworkResponse
s {$sel:creationTime:UpdateFrameworkResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: UpdateFrameworkResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | An Amazon Resource Name (ARN) that uniquely identifies a resource. The
-- format of the ARN depends on the resource type.
updateFrameworkResponse_frameworkArn :: Lens.Lens' UpdateFrameworkResponse (Prelude.Maybe Prelude.Text)
updateFrameworkResponse_frameworkArn :: Lens' UpdateFrameworkResponse (Maybe Text)
updateFrameworkResponse_frameworkArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFrameworkResponse' {Maybe Text
frameworkArn :: Maybe Text
$sel:frameworkArn:UpdateFrameworkResponse' :: UpdateFrameworkResponse -> Maybe Text
frameworkArn} -> Maybe Text
frameworkArn) (\s :: UpdateFrameworkResponse
s@UpdateFrameworkResponse' {} Maybe Text
a -> UpdateFrameworkResponse
s {$sel:frameworkArn:UpdateFrameworkResponse' :: Maybe Text
frameworkArn = Maybe Text
a} :: UpdateFrameworkResponse)

-- | The unique name of a framework. This name is between 1 and 256
-- characters, starting with a letter, and consisting of letters (a-z,
-- A-Z), numbers (0-9), and underscores (_).
updateFrameworkResponse_frameworkName :: Lens.Lens' UpdateFrameworkResponse (Prelude.Maybe Prelude.Text)
updateFrameworkResponse_frameworkName :: Lens' UpdateFrameworkResponse (Maybe Text)
updateFrameworkResponse_frameworkName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFrameworkResponse' {Maybe Text
frameworkName :: Maybe Text
$sel:frameworkName:UpdateFrameworkResponse' :: UpdateFrameworkResponse -> Maybe Text
frameworkName} -> Maybe Text
frameworkName) (\s :: UpdateFrameworkResponse
s@UpdateFrameworkResponse' {} Maybe Text
a -> UpdateFrameworkResponse
s {$sel:frameworkName:UpdateFrameworkResponse' :: Maybe Text
frameworkName = Maybe Text
a} :: UpdateFrameworkResponse)

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

instance Prelude.NFData UpdateFrameworkResponse where
  rnf :: UpdateFrameworkResponse -> ()
rnf UpdateFrameworkResponse' {Int
Maybe Text
Maybe POSIX
httpStatus :: Int
frameworkName :: Maybe Text
frameworkArn :: Maybe Text
creationTime :: Maybe POSIX
$sel:httpStatus:UpdateFrameworkResponse' :: UpdateFrameworkResponse -> Int
$sel:frameworkName:UpdateFrameworkResponse' :: UpdateFrameworkResponse -> Maybe Text
$sel:frameworkArn:UpdateFrameworkResponse' :: UpdateFrameworkResponse -> Maybe Text
$sel:creationTime:UpdateFrameworkResponse' :: UpdateFrameworkResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
frameworkArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
frameworkName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus