{-# 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.IoTRoboRunner.UpdateSite
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Grants permission to update a site
module Amazonka.IoTRoboRunner.UpdateSite
  ( -- * Creating a Request
    UpdateSite (..),
    newUpdateSite,

    -- * Request Lenses
    updateSite_countryCode,
    updateSite_description,
    updateSite_name,
    updateSite_id,

    -- * Destructuring the Response
    UpdateSiteResponse (..),
    newUpdateSiteResponse,

    -- * Response Lenses
    updateSiteResponse_countryCode,
    updateSiteResponse_description,
    updateSiteResponse_httpStatus,
    updateSiteResponse_arn,
    updateSiteResponse_id,
    updateSiteResponse_name,
    updateSiteResponse_updatedAt,
  )
where

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

-- | /See:/ 'newUpdateSite' smart constructor.
data UpdateSite = UpdateSite'
  { UpdateSite -> Maybe Text
countryCode :: Prelude.Maybe Prelude.Text,
    UpdateSite -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    UpdateSite -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    UpdateSite -> Text
id :: Prelude.Text
  }
  deriving (UpdateSite -> UpdateSite -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSite -> UpdateSite -> Bool
$c/= :: UpdateSite -> UpdateSite -> Bool
== :: UpdateSite -> UpdateSite -> Bool
$c== :: UpdateSite -> UpdateSite -> Bool
Prelude.Eq, ReadPrec [UpdateSite]
ReadPrec UpdateSite
Int -> ReadS UpdateSite
ReadS [UpdateSite]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSite]
$creadListPrec :: ReadPrec [UpdateSite]
readPrec :: ReadPrec UpdateSite
$creadPrec :: ReadPrec UpdateSite
readList :: ReadS [UpdateSite]
$creadList :: ReadS [UpdateSite]
readsPrec :: Int -> ReadS UpdateSite
$creadsPrec :: Int -> ReadS UpdateSite
Prelude.Read, Int -> UpdateSite -> ShowS
[UpdateSite] -> ShowS
UpdateSite -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSite] -> ShowS
$cshowList :: [UpdateSite] -> ShowS
show :: UpdateSite -> String
$cshow :: UpdateSite -> String
showsPrec :: Int -> UpdateSite -> ShowS
$cshowsPrec :: Int -> UpdateSite -> ShowS
Prelude.Show, forall x. Rep UpdateSite x -> UpdateSite
forall x. UpdateSite -> Rep UpdateSite x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateSite x -> UpdateSite
$cfrom :: forall x. UpdateSite -> Rep UpdateSite x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSite' 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:
--
-- 'countryCode', 'updateSite_countryCode' - Undocumented member.
--
-- 'description', 'updateSite_description' - Undocumented member.
--
-- 'name', 'updateSite_name' - Undocumented member.
--
-- 'id', 'updateSite_id' - Undocumented member.
newUpdateSite ::
  -- | 'id'
  Prelude.Text ->
  UpdateSite
newUpdateSite :: Text -> UpdateSite
newUpdateSite Text
pId_ =
  UpdateSite'
    { $sel:countryCode:UpdateSite' :: Maybe Text
countryCode = forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateSite' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateSite' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:id:UpdateSite' :: Text
id = Text
pId_
    }

-- | Undocumented member.
updateSite_countryCode :: Lens.Lens' UpdateSite (Prelude.Maybe Prelude.Text)
updateSite_countryCode :: Lens' UpdateSite (Maybe Text)
updateSite_countryCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSite' {Maybe Text
countryCode :: Maybe Text
$sel:countryCode:UpdateSite' :: UpdateSite -> Maybe Text
countryCode} -> Maybe Text
countryCode) (\s :: UpdateSite
s@UpdateSite' {} Maybe Text
a -> UpdateSite
s {$sel:countryCode:UpdateSite' :: Maybe Text
countryCode = Maybe Text
a} :: UpdateSite)

-- | Undocumented member.
updateSite_description :: Lens.Lens' UpdateSite (Prelude.Maybe Prelude.Text)
updateSite_description :: Lens' UpdateSite (Maybe Text)
updateSite_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSite' {Maybe Text
description :: Maybe Text
$sel:description:UpdateSite' :: UpdateSite -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateSite
s@UpdateSite' {} Maybe Text
a -> UpdateSite
s {$sel:description:UpdateSite' :: Maybe Text
description = Maybe Text
a} :: UpdateSite)

-- | Undocumented member.
updateSite_name :: Lens.Lens' UpdateSite (Prelude.Maybe Prelude.Text)
updateSite_name :: Lens' UpdateSite (Maybe Text)
updateSite_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSite' {Maybe Text
name :: Maybe Text
$sel:name:UpdateSite' :: UpdateSite -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateSite
s@UpdateSite' {} Maybe Text
a -> UpdateSite
s {$sel:name:UpdateSite' :: Maybe Text
name = Maybe Text
a} :: UpdateSite)

-- | Undocumented member.
updateSite_id :: Lens.Lens' UpdateSite Prelude.Text
updateSite_id :: Lens' UpdateSite Text
updateSite_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSite' {Text
id :: Text
$sel:id:UpdateSite' :: UpdateSite -> Text
id} -> Text
id) (\s :: UpdateSite
s@UpdateSite' {} Text
a -> UpdateSite
s {$sel:id:UpdateSite' :: Text
id = Text
a} :: UpdateSite)

instance Core.AWSRequest UpdateSite where
  type AWSResponse UpdateSite = UpdateSiteResponse
  request :: (Service -> Service) -> UpdateSite -> Request UpdateSite
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 UpdateSite
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateSite)))
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 Text
-> Int
-> Text
-> Text
-> Text
-> POSIX
-> UpdateSiteResponse
UpdateSiteResponse'
            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
"countryCode")
            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
"description")
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"id")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"updatedAt")
      )

instance Prelude.Hashable UpdateSite where
  hashWithSalt :: Int -> UpdateSite -> Int
hashWithSalt Int
_salt UpdateSite' {Maybe Text
Text
id :: Text
name :: Maybe Text
description :: Maybe Text
countryCode :: Maybe Text
$sel:id:UpdateSite' :: UpdateSite -> Text
$sel:name:UpdateSite' :: UpdateSite -> Maybe Text
$sel:description:UpdateSite' :: UpdateSite -> Maybe Text
$sel:countryCode:UpdateSite' :: UpdateSite -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
countryCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData UpdateSite where
  rnf :: UpdateSite -> ()
rnf UpdateSite' {Maybe Text
Text
id :: Text
name :: Maybe Text
description :: Maybe Text
countryCode :: Maybe Text
$sel:id:UpdateSite' :: UpdateSite -> Text
$sel:name:UpdateSite' :: UpdateSite -> Maybe Text
$sel:description:UpdateSite' :: UpdateSite -> Maybe Text
$sel:countryCode:UpdateSite' :: UpdateSite -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
countryCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id

instance Data.ToHeaders UpdateSite where
  toHeaders :: UpdateSite -> 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 UpdateSite where
  toJSON :: UpdateSite -> Value
toJSON UpdateSite' {Maybe Text
Text
id :: Text
name :: Maybe Text
description :: Maybe Text
countryCode :: Maybe Text
$sel:id:UpdateSite' :: UpdateSite -> Text
$sel:name:UpdateSite' :: UpdateSite -> Maybe Text
$sel:description:UpdateSite' :: UpdateSite -> Maybe Text
$sel:countryCode:UpdateSite' :: UpdateSite -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"countryCode" 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
countryCode,
            (Key
"description" 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
description,
            (Key
"name" 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
name,
            forall a. a -> Maybe a
Prelude.Just (Key
"id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
id)
          ]
      )

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

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

-- | /See:/ 'newUpdateSiteResponse' smart constructor.
data UpdateSiteResponse = UpdateSiteResponse'
  { UpdateSiteResponse -> Maybe Text
countryCode :: Prelude.Maybe Prelude.Text,
    UpdateSiteResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateSiteResponse -> Int
httpStatus :: Prelude.Int,
    UpdateSiteResponse -> Text
arn :: Prelude.Text,
    UpdateSiteResponse -> Text
id :: Prelude.Text,
    UpdateSiteResponse -> Text
name :: Prelude.Text,
    UpdateSiteResponse -> POSIX
updatedAt :: Data.POSIX
  }
  deriving (UpdateSiteResponse -> UpdateSiteResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSiteResponse -> UpdateSiteResponse -> Bool
$c/= :: UpdateSiteResponse -> UpdateSiteResponse -> Bool
== :: UpdateSiteResponse -> UpdateSiteResponse -> Bool
$c== :: UpdateSiteResponse -> UpdateSiteResponse -> Bool
Prelude.Eq, ReadPrec [UpdateSiteResponse]
ReadPrec UpdateSiteResponse
Int -> ReadS UpdateSiteResponse
ReadS [UpdateSiteResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSiteResponse]
$creadListPrec :: ReadPrec [UpdateSiteResponse]
readPrec :: ReadPrec UpdateSiteResponse
$creadPrec :: ReadPrec UpdateSiteResponse
readList :: ReadS [UpdateSiteResponse]
$creadList :: ReadS [UpdateSiteResponse]
readsPrec :: Int -> ReadS UpdateSiteResponse
$creadsPrec :: Int -> ReadS UpdateSiteResponse
Prelude.Read, Int -> UpdateSiteResponse -> ShowS
[UpdateSiteResponse] -> ShowS
UpdateSiteResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSiteResponse] -> ShowS
$cshowList :: [UpdateSiteResponse] -> ShowS
show :: UpdateSiteResponse -> String
$cshow :: UpdateSiteResponse -> String
showsPrec :: Int -> UpdateSiteResponse -> ShowS
$cshowsPrec :: Int -> UpdateSiteResponse -> ShowS
Prelude.Show, forall x. Rep UpdateSiteResponse x -> UpdateSiteResponse
forall x. UpdateSiteResponse -> Rep UpdateSiteResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateSiteResponse x -> UpdateSiteResponse
$cfrom :: forall x. UpdateSiteResponse -> Rep UpdateSiteResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSiteResponse' 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:
--
-- 'countryCode', 'updateSiteResponse_countryCode' - Undocumented member.
--
-- 'description', 'updateSiteResponse_description' - Undocumented member.
--
-- 'httpStatus', 'updateSiteResponse_httpStatus' - The response's http status code.
--
-- 'arn', 'updateSiteResponse_arn' - Undocumented member.
--
-- 'id', 'updateSiteResponse_id' - Undocumented member.
--
-- 'name', 'updateSiteResponse_name' - Undocumented member.
--
-- 'updatedAt', 'updateSiteResponse_updatedAt' - Undocumented member.
newUpdateSiteResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'arn'
  Prelude.Text ->
  -- | 'id'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  -- | 'updatedAt'
  Prelude.UTCTime ->
  UpdateSiteResponse
newUpdateSiteResponse :: Int -> Text -> Text -> Text -> UTCTime -> UpdateSiteResponse
newUpdateSiteResponse
  Int
pHttpStatus_
  Text
pArn_
  Text
pId_
  Text
pName_
  UTCTime
pUpdatedAt_ =
    UpdateSiteResponse'
      { $sel:countryCode:UpdateSiteResponse' :: Maybe Text
countryCode = forall a. Maybe a
Prelude.Nothing,
        $sel:description:UpdateSiteResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:UpdateSiteResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:arn:UpdateSiteResponse' :: Text
arn = Text
pArn_,
        $sel:id:UpdateSiteResponse' :: Text
id = Text
pId_,
        $sel:name:UpdateSiteResponse' :: Text
name = Text
pName_,
        $sel:updatedAt:UpdateSiteResponse' :: POSIX
updatedAt = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pUpdatedAt_
      }

-- | Undocumented member.
updateSiteResponse_countryCode :: Lens.Lens' UpdateSiteResponse (Prelude.Maybe Prelude.Text)
updateSiteResponse_countryCode :: Lens' UpdateSiteResponse (Maybe Text)
updateSiteResponse_countryCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSiteResponse' {Maybe Text
countryCode :: Maybe Text
$sel:countryCode:UpdateSiteResponse' :: UpdateSiteResponse -> Maybe Text
countryCode} -> Maybe Text
countryCode) (\s :: UpdateSiteResponse
s@UpdateSiteResponse' {} Maybe Text
a -> UpdateSiteResponse
s {$sel:countryCode:UpdateSiteResponse' :: Maybe Text
countryCode = Maybe Text
a} :: UpdateSiteResponse)

-- | Undocumented member.
updateSiteResponse_description :: Lens.Lens' UpdateSiteResponse (Prelude.Maybe Prelude.Text)
updateSiteResponse_description :: Lens' UpdateSiteResponse (Maybe Text)
updateSiteResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSiteResponse' {Maybe Text
description :: Maybe Text
$sel:description:UpdateSiteResponse' :: UpdateSiteResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateSiteResponse
s@UpdateSiteResponse' {} Maybe Text
a -> UpdateSiteResponse
s {$sel:description:UpdateSiteResponse' :: Maybe Text
description = Maybe Text
a} :: UpdateSiteResponse)

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

-- | Undocumented member.
updateSiteResponse_arn :: Lens.Lens' UpdateSiteResponse Prelude.Text
updateSiteResponse_arn :: Lens' UpdateSiteResponse Text
updateSiteResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSiteResponse' {Text
arn :: Text
$sel:arn:UpdateSiteResponse' :: UpdateSiteResponse -> Text
arn} -> Text
arn) (\s :: UpdateSiteResponse
s@UpdateSiteResponse' {} Text
a -> UpdateSiteResponse
s {$sel:arn:UpdateSiteResponse' :: Text
arn = Text
a} :: UpdateSiteResponse)

-- | Undocumented member.
updateSiteResponse_id :: Lens.Lens' UpdateSiteResponse Prelude.Text
updateSiteResponse_id :: Lens' UpdateSiteResponse Text
updateSiteResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSiteResponse' {Text
id :: Text
$sel:id:UpdateSiteResponse' :: UpdateSiteResponse -> Text
id} -> Text
id) (\s :: UpdateSiteResponse
s@UpdateSiteResponse' {} Text
a -> UpdateSiteResponse
s {$sel:id:UpdateSiteResponse' :: Text
id = Text
a} :: UpdateSiteResponse)

-- | Undocumented member.
updateSiteResponse_name :: Lens.Lens' UpdateSiteResponse Prelude.Text
updateSiteResponse_name :: Lens' UpdateSiteResponse Text
updateSiteResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSiteResponse' {Text
name :: Text
$sel:name:UpdateSiteResponse' :: UpdateSiteResponse -> Text
name} -> Text
name) (\s :: UpdateSiteResponse
s@UpdateSiteResponse' {} Text
a -> UpdateSiteResponse
s {$sel:name:UpdateSiteResponse' :: Text
name = Text
a} :: UpdateSiteResponse)

-- | Undocumented member.
updateSiteResponse_updatedAt :: Lens.Lens' UpdateSiteResponse Prelude.UTCTime
updateSiteResponse_updatedAt :: Lens' UpdateSiteResponse UTCTime
updateSiteResponse_updatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSiteResponse' {POSIX
updatedAt :: POSIX
$sel:updatedAt:UpdateSiteResponse' :: UpdateSiteResponse -> POSIX
updatedAt} -> POSIX
updatedAt) (\s :: UpdateSiteResponse
s@UpdateSiteResponse' {} POSIX
a -> UpdateSiteResponse
s {$sel:updatedAt:UpdateSiteResponse' :: POSIX
updatedAt = POSIX
a} :: UpdateSiteResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Prelude.NFData UpdateSiteResponse where
  rnf :: UpdateSiteResponse -> ()
rnf UpdateSiteResponse' {Int
Maybe Text
Text
POSIX
updatedAt :: POSIX
name :: Text
id :: Text
arn :: Text
httpStatus :: Int
description :: Maybe Text
countryCode :: Maybe Text
$sel:updatedAt:UpdateSiteResponse' :: UpdateSiteResponse -> POSIX
$sel:name:UpdateSiteResponse' :: UpdateSiteResponse -> Text
$sel:id:UpdateSiteResponse' :: UpdateSiteResponse -> Text
$sel:arn:UpdateSiteResponse' :: UpdateSiteResponse -> Text
$sel:httpStatus:UpdateSiteResponse' :: UpdateSiteResponse -> Int
$sel:description:UpdateSiteResponse' :: UpdateSiteResponse -> Maybe Text
$sel:countryCode:UpdateSiteResponse' :: UpdateSiteResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
countryCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
updatedAt