{-# 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.IoTFleetWise.RegisterAccount
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Registers your Amazon Web Services account, IAM, and Amazon Timestream
-- resources so Amazon Web Services IoT FleetWise can transfer your vehicle
-- data to the Amazon Web Services Cloud. For more information, including
-- step-by-step procedures, see
-- <https://docs.aws.amazon.com/iot-fleetwise/latest/developerguide/setting-up.html Setting up Amazon Web Services IoT FleetWise>.
--
-- An Amazon Web Services account is __not__ the same thing as a \"user
-- account\". An
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/introduction_identity-management.html#intro-identity-users Amazon Web Services user>
-- is an identity that you create using Identity and Access Management
-- (IAM) and takes the form of either an
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_users.html IAM user>
-- or an
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_roles.html IAM role, both with credentials>.
-- A single Amazon Web Services account can, and typically does, contain
-- many users and roles.
module Amazonka.IoTFleetWise.RegisterAccount
  ( -- * Creating a Request
    RegisterAccount (..),
    newRegisterAccount,

    -- * Request Lenses
    registerAccount_iamResources,
    registerAccount_timestreamResources,

    -- * Destructuring the Response
    RegisterAccountResponse (..),
    newRegisterAccountResponse,

    -- * Response Lenses
    registerAccountResponse_httpStatus,
    registerAccountResponse_registerAccountStatus,
    registerAccountResponse_timestreamResources,
    registerAccountResponse_iamResources,
    registerAccountResponse_creationTime,
    registerAccountResponse_lastModificationTime,
  )
where

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

-- | /See:/ 'newRegisterAccount' smart constructor.
data RegisterAccount = RegisterAccount'
  { -- | The IAM resource that allows Amazon Web Services IoT FleetWise to send
    -- data to Amazon Timestream.
    RegisterAccount -> Maybe IamResources
iamResources :: Prelude.Maybe IamResources,
    RegisterAccount -> TimestreamResources
timestreamResources :: TimestreamResources
  }
  deriving (RegisterAccount -> RegisterAccount -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegisterAccount -> RegisterAccount -> Bool
$c/= :: RegisterAccount -> RegisterAccount -> Bool
== :: RegisterAccount -> RegisterAccount -> Bool
$c== :: RegisterAccount -> RegisterAccount -> Bool
Prelude.Eq, ReadPrec [RegisterAccount]
ReadPrec RegisterAccount
Int -> ReadS RegisterAccount
ReadS [RegisterAccount]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RegisterAccount]
$creadListPrec :: ReadPrec [RegisterAccount]
readPrec :: ReadPrec RegisterAccount
$creadPrec :: ReadPrec RegisterAccount
readList :: ReadS [RegisterAccount]
$creadList :: ReadS [RegisterAccount]
readsPrec :: Int -> ReadS RegisterAccount
$creadsPrec :: Int -> ReadS RegisterAccount
Prelude.Read, Int -> RegisterAccount -> ShowS
[RegisterAccount] -> ShowS
RegisterAccount -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegisterAccount] -> ShowS
$cshowList :: [RegisterAccount] -> ShowS
show :: RegisterAccount -> String
$cshow :: RegisterAccount -> String
showsPrec :: Int -> RegisterAccount -> ShowS
$cshowsPrec :: Int -> RegisterAccount -> ShowS
Prelude.Show, forall x. Rep RegisterAccount x -> RegisterAccount
forall x. RegisterAccount -> Rep RegisterAccount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegisterAccount x -> RegisterAccount
$cfrom :: forall x. RegisterAccount -> Rep RegisterAccount x
Prelude.Generic)

-- |
-- Create a value of 'RegisterAccount' 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:
--
-- 'iamResources', 'registerAccount_iamResources' - The IAM resource that allows Amazon Web Services IoT FleetWise to send
-- data to Amazon Timestream.
--
-- 'timestreamResources', 'registerAccount_timestreamResources' - Undocumented member.
newRegisterAccount ::
  -- | 'timestreamResources'
  TimestreamResources ->
  RegisterAccount
newRegisterAccount :: TimestreamResources -> RegisterAccount
newRegisterAccount TimestreamResources
pTimestreamResources_ =
  RegisterAccount'
    { $sel:iamResources:RegisterAccount' :: Maybe IamResources
iamResources = forall a. Maybe a
Prelude.Nothing,
      $sel:timestreamResources:RegisterAccount' :: TimestreamResources
timestreamResources = TimestreamResources
pTimestreamResources_
    }

-- | The IAM resource that allows Amazon Web Services IoT FleetWise to send
-- data to Amazon Timestream.
registerAccount_iamResources :: Lens.Lens' RegisterAccount (Prelude.Maybe IamResources)
registerAccount_iamResources :: Lens' RegisterAccount (Maybe IamResources)
registerAccount_iamResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterAccount' {Maybe IamResources
iamResources :: Maybe IamResources
$sel:iamResources:RegisterAccount' :: RegisterAccount -> Maybe IamResources
iamResources} -> Maybe IamResources
iamResources) (\s :: RegisterAccount
s@RegisterAccount' {} Maybe IamResources
a -> RegisterAccount
s {$sel:iamResources:RegisterAccount' :: Maybe IamResources
iamResources = Maybe IamResources
a} :: RegisterAccount)

-- | Undocumented member.
registerAccount_timestreamResources :: Lens.Lens' RegisterAccount TimestreamResources
registerAccount_timestreamResources :: Lens' RegisterAccount TimestreamResources
registerAccount_timestreamResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterAccount' {TimestreamResources
timestreamResources :: TimestreamResources
$sel:timestreamResources:RegisterAccount' :: RegisterAccount -> TimestreamResources
timestreamResources} -> TimestreamResources
timestreamResources) (\s :: RegisterAccount
s@RegisterAccount' {} TimestreamResources
a -> RegisterAccount
s {$sel:timestreamResources:RegisterAccount' :: TimestreamResources
timestreamResources = TimestreamResources
a} :: RegisterAccount)

instance Core.AWSRequest RegisterAccount where
  type
    AWSResponse RegisterAccount =
      RegisterAccountResponse
  request :: (Service -> Service) -> RegisterAccount -> Request RegisterAccount
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 RegisterAccount
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse RegisterAccount)))
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 ->
          Int
-> RegistrationStatus
-> TimestreamResources
-> IamResources
-> POSIX
-> POSIX
-> RegisterAccountResponse
RegisterAccountResponse'
            forall (f :: * -> *) a b. Functor 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
"registerAccountStatus")
            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
"timestreamResources")
            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
"iamResources")
            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
"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 a
Data..:> Key
"lastModificationTime")
      )

instance Prelude.Hashable RegisterAccount where
  hashWithSalt :: Int -> RegisterAccount -> Int
hashWithSalt Int
_salt RegisterAccount' {Maybe IamResources
TimestreamResources
timestreamResources :: TimestreamResources
iamResources :: Maybe IamResources
$sel:timestreamResources:RegisterAccount' :: RegisterAccount -> TimestreamResources
$sel:iamResources:RegisterAccount' :: RegisterAccount -> Maybe IamResources
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe IamResources
iamResources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` TimestreamResources
timestreamResources

instance Prelude.NFData RegisterAccount where
  rnf :: RegisterAccount -> ()
rnf RegisterAccount' {Maybe IamResources
TimestreamResources
timestreamResources :: TimestreamResources
iamResources :: Maybe IamResources
$sel:timestreamResources:RegisterAccount' :: RegisterAccount -> TimestreamResources
$sel:iamResources:RegisterAccount' :: RegisterAccount -> Maybe IamResources
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe IamResources
iamResources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf TimestreamResources
timestreamResources

instance Data.ToHeaders RegisterAccount where
  toHeaders :: RegisterAccount -> 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
"IoTAutobahnControlPlane.RegisterAccount" ::
                          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 RegisterAccount where
  toJSON :: RegisterAccount -> Value
toJSON RegisterAccount' {Maybe IamResources
TimestreamResources
timestreamResources :: TimestreamResources
iamResources :: Maybe IamResources
$sel:timestreamResources:RegisterAccount' :: RegisterAccount -> TimestreamResources
$sel:iamResources:RegisterAccount' :: RegisterAccount -> Maybe IamResources
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"iamResources" 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 IamResources
iamResources,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"timestreamResources" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= TimestreamResources
timestreamResources)
          ]
      )

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

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

-- | /See:/ 'newRegisterAccountResponse' smart constructor.
data RegisterAccountResponse = RegisterAccountResponse'
  { -- | The response's http status code.
    RegisterAccountResponse -> Int
httpStatus :: Prelude.Int,
    -- | The status of registering your Amazon Web Services account, IAM role,
    -- and Timestream resources.
    RegisterAccountResponse -> RegistrationStatus
registerAccountStatus :: RegistrationStatus,
    RegisterAccountResponse -> TimestreamResources
timestreamResources :: TimestreamResources,
    -- | The registered IAM resource that allows Amazon Web Services IoT
    -- FleetWise to send data to Amazon Timestream.
    RegisterAccountResponse -> IamResources
iamResources :: IamResources,
    -- | The time the account was registered, in seconds since epoch (January 1,
    -- 1970 at midnight UTC time).
    RegisterAccountResponse -> POSIX
creationTime :: Data.POSIX,
    -- | The time this registration was last updated, in seconds since epoch
    -- (January 1, 1970 at midnight UTC time).
    RegisterAccountResponse -> POSIX
lastModificationTime :: Data.POSIX
  }
  deriving (RegisterAccountResponse -> RegisterAccountResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegisterAccountResponse -> RegisterAccountResponse -> Bool
$c/= :: RegisterAccountResponse -> RegisterAccountResponse -> Bool
== :: RegisterAccountResponse -> RegisterAccountResponse -> Bool
$c== :: RegisterAccountResponse -> RegisterAccountResponse -> Bool
Prelude.Eq, ReadPrec [RegisterAccountResponse]
ReadPrec RegisterAccountResponse
Int -> ReadS RegisterAccountResponse
ReadS [RegisterAccountResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RegisterAccountResponse]
$creadListPrec :: ReadPrec [RegisterAccountResponse]
readPrec :: ReadPrec RegisterAccountResponse
$creadPrec :: ReadPrec RegisterAccountResponse
readList :: ReadS [RegisterAccountResponse]
$creadList :: ReadS [RegisterAccountResponse]
readsPrec :: Int -> ReadS RegisterAccountResponse
$creadsPrec :: Int -> ReadS RegisterAccountResponse
Prelude.Read, Int -> RegisterAccountResponse -> ShowS
[RegisterAccountResponse] -> ShowS
RegisterAccountResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegisterAccountResponse] -> ShowS
$cshowList :: [RegisterAccountResponse] -> ShowS
show :: RegisterAccountResponse -> String
$cshow :: RegisterAccountResponse -> String
showsPrec :: Int -> RegisterAccountResponse -> ShowS
$cshowsPrec :: Int -> RegisterAccountResponse -> ShowS
Prelude.Show, forall x. Rep RegisterAccountResponse x -> RegisterAccountResponse
forall x. RegisterAccountResponse -> Rep RegisterAccountResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegisterAccountResponse x -> RegisterAccountResponse
$cfrom :: forall x. RegisterAccountResponse -> Rep RegisterAccountResponse x
Prelude.Generic)

-- |
-- Create a value of 'RegisterAccountResponse' 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:
--
-- 'httpStatus', 'registerAccountResponse_httpStatus' - The response's http status code.
--
-- 'registerAccountStatus', 'registerAccountResponse_registerAccountStatus' - The status of registering your Amazon Web Services account, IAM role,
-- and Timestream resources.
--
-- 'timestreamResources', 'registerAccountResponse_timestreamResources' - Undocumented member.
--
-- 'iamResources', 'registerAccountResponse_iamResources' - The registered IAM resource that allows Amazon Web Services IoT
-- FleetWise to send data to Amazon Timestream.
--
-- 'creationTime', 'registerAccountResponse_creationTime' - The time the account was registered, in seconds since epoch (January 1,
-- 1970 at midnight UTC time).
--
-- 'lastModificationTime', 'registerAccountResponse_lastModificationTime' - The time this registration was last updated, in seconds since epoch
-- (January 1, 1970 at midnight UTC time).
newRegisterAccountResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'registerAccountStatus'
  RegistrationStatus ->
  -- | 'timestreamResources'
  TimestreamResources ->
  -- | 'iamResources'
  IamResources ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'lastModificationTime'
  Prelude.UTCTime ->
  RegisterAccountResponse
newRegisterAccountResponse :: Int
-> RegistrationStatus
-> TimestreamResources
-> IamResources
-> UTCTime
-> UTCTime
-> RegisterAccountResponse
newRegisterAccountResponse
  Int
pHttpStatus_
  RegistrationStatus
pRegisterAccountStatus_
  TimestreamResources
pTimestreamResources_
  IamResources
pIamResources_
  UTCTime
pCreationTime_
  UTCTime
pLastModificationTime_ =
    RegisterAccountResponse'
      { $sel:httpStatus:RegisterAccountResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:registerAccountStatus:RegisterAccountResponse' :: RegistrationStatus
registerAccountStatus = RegistrationStatus
pRegisterAccountStatus_,
        $sel:timestreamResources:RegisterAccountResponse' :: TimestreamResources
timestreamResources = TimestreamResources
pTimestreamResources_,
        $sel:iamResources:RegisterAccountResponse' :: IamResources
iamResources = IamResources
pIamResources_,
        $sel:creationTime:RegisterAccountResponse' :: POSIX
creationTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:lastModificationTime:RegisterAccountResponse' :: POSIX
lastModificationTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastModificationTime_
      }

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

-- | The status of registering your Amazon Web Services account, IAM role,
-- and Timestream resources.
registerAccountResponse_registerAccountStatus :: Lens.Lens' RegisterAccountResponse RegistrationStatus
registerAccountResponse_registerAccountStatus :: Lens' RegisterAccountResponse RegistrationStatus
registerAccountResponse_registerAccountStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterAccountResponse' {RegistrationStatus
registerAccountStatus :: RegistrationStatus
$sel:registerAccountStatus:RegisterAccountResponse' :: RegisterAccountResponse -> RegistrationStatus
registerAccountStatus} -> RegistrationStatus
registerAccountStatus) (\s :: RegisterAccountResponse
s@RegisterAccountResponse' {} RegistrationStatus
a -> RegisterAccountResponse
s {$sel:registerAccountStatus:RegisterAccountResponse' :: RegistrationStatus
registerAccountStatus = RegistrationStatus
a} :: RegisterAccountResponse)

-- | Undocumented member.
registerAccountResponse_timestreamResources :: Lens.Lens' RegisterAccountResponse TimestreamResources
registerAccountResponse_timestreamResources :: Lens' RegisterAccountResponse TimestreamResources
registerAccountResponse_timestreamResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterAccountResponse' {TimestreamResources
timestreamResources :: TimestreamResources
$sel:timestreamResources:RegisterAccountResponse' :: RegisterAccountResponse -> TimestreamResources
timestreamResources} -> TimestreamResources
timestreamResources) (\s :: RegisterAccountResponse
s@RegisterAccountResponse' {} TimestreamResources
a -> RegisterAccountResponse
s {$sel:timestreamResources:RegisterAccountResponse' :: TimestreamResources
timestreamResources = TimestreamResources
a} :: RegisterAccountResponse)

-- | The registered IAM resource that allows Amazon Web Services IoT
-- FleetWise to send data to Amazon Timestream.
registerAccountResponse_iamResources :: Lens.Lens' RegisterAccountResponse IamResources
registerAccountResponse_iamResources :: Lens' RegisterAccountResponse IamResources
registerAccountResponse_iamResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterAccountResponse' {IamResources
iamResources :: IamResources
$sel:iamResources:RegisterAccountResponse' :: RegisterAccountResponse -> IamResources
iamResources} -> IamResources
iamResources) (\s :: RegisterAccountResponse
s@RegisterAccountResponse' {} IamResources
a -> RegisterAccountResponse
s {$sel:iamResources:RegisterAccountResponse' :: IamResources
iamResources = IamResources
a} :: RegisterAccountResponse)

-- | The time the account was registered, in seconds since epoch (January 1,
-- 1970 at midnight UTC time).
registerAccountResponse_creationTime :: Lens.Lens' RegisterAccountResponse Prelude.UTCTime
registerAccountResponse_creationTime :: Lens' RegisterAccountResponse UTCTime
registerAccountResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterAccountResponse' {POSIX
creationTime :: POSIX
$sel:creationTime:RegisterAccountResponse' :: RegisterAccountResponse -> POSIX
creationTime} -> POSIX
creationTime) (\s :: RegisterAccountResponse
s@RegisterAccountResponse' {} POSIX
a -> RegisterAccountResponse
s {$sel:creationTime:RegisterAccountResponse' :: POSIX
creationTime = POSIX
a} :: RegisterAccountResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The time this registration was last updated, in seconds since epoch
-- (January 1, 1970 at midnight UTC time).
registerAccountResponse_lastModificationTime :: Lens.Lens' RegisterAccountResponse Prelude.UTCTime
registerAccountResponse_lastModificationTime :: Lens' RegisterAccountResponse UTCTime
registerAccountResponse_lastModificationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RegisterAccountResponse' {POSIX
lastModificationTime :: POSIX
$sel:lastModificationTime:RegisterAccountResponse' :: RegisterAccountResponse -> POSIX
lastModificationTime} -> POSIX
lastModificationTime) (\s :: RegisterAccountResponse
s@RegisterAccountResponse' {} POSIX
a -> RegisterAccountResponse
s {$sel:lastModificationTime:RegisterAccountResponse' :: POSIX
lastModificationTime = POSIX
a} :: RegisterAccountResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Prelude.NFData RegisterAccountResponse where
  rnf :: RegisterAccountResponse -> ()
rnf RegisterAccountResponse' {Int
POSIX
IamResources
RegistrationStatus
TimestreamResources
lastModificationTime :: POSIX
creationTime :: POSIX
iamResources :: IamResources
timestreamResources :: TimestreamResources
registerAccountStatus :: RegistrationStatus
httpStatus :: Int
$sel:lastModificationTime:RegisterAccountResponse' :: RegisterAccountResponse -> POSIX
$sel:creationTime:RegisterAccountResponse' :: RegisterAccountResponse -> POSIX
$sel:iamResources:RegisterAccountResponse' :: RegisterAccountResponse -> IamResources
$sel:timestreamResources:RegisterAccountResponse' :: RegisterAccountResponse -> TimestreamResources
$sel:registerAccountStatus:RegisterAccountResponse' :: RegisterAccountResponse -> RegistrationStatus
$sel:httpStatus:RegisterAccountResponse' :: RegisterAccountResponse -> Int
..} =
    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 RegistrationStatus
registerAccountStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf TimestreamResources
timestreamResources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf IamResources
iamResources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
lastModificationTime