{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Proton.Types.EnvironmentAccountConnection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Proton.Types.EnvironmentAccountConnection where

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 Amazonka.Proton.Types.EnvironmentAccountConnectionStatus

-- | Detailed data of an Proton environment account connection resource.
--
-- /See:/ 'newEnvironmentAccountConnection' smart constructor.
data EnvironmentAccountConnection = EnvironmentAccountConnection'
  { -- | The Amazon Resource Name (ARN) of an IAM service role in the environment
    -- account. Proton uses this role to provision infrastructure resources
    -- using CodeBuild-based provisioning in the associated environment
    -- account.
    EnvironmentAccountConnection -> Maybe Text
codebuildRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the IAM service role that Proton uses
    -- when provisioning directly defined components in the associated
    -- environment account. It determines the scope of infrastructure that a
    -- component can provision in the account.
    --
    -- The environment account connection must have a @componentRoleArn@ to
    -- allow directly defined components to be associated with any environments
    -- running in the account.
    --
    -- For more information about components, see
    -- <https://docs.aws.amazon.com/proton/latest/userguide/ag-components.html Proton components>
    -- in the /Proton User Guide/.
    EnvironmentAccountConnection -> Maybe Text
componentRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the environment account connection.
    EnvironmentAccountConnection -> Text
arn :: Prelude.Text,
    -- | The environment account that\'s connected to the environment account
    -- connection.
    EnvironmentAccountConnection -> Text
environmentAccountId :: Prelude.Text,
    -- | The name of the environment that\'s associated with the environment
    -- account connection.
    EnvironmentAccountConnection -> Text
environmentName :: Prelude.Text,
    -- | The ID of the environment account connection.
    EnvironmentAccountConnection -> Text
id :: Prelude.Text,
    -- | The time when the environment account connection was last modified.
    EnvironmentAccountConnection -> POSIX
lastModifiedAt :: Data.POSIX,
    -- | The ID of the management account that\'s connected to the environment
    -- account connection.
    EnvironmentAccountConnection -> Text
managementAccountId :: Prelude.Text,
    -- | The time when the environment account connection request was made.
    EnvironmentAccountConnection -> POSIX
requestedAt :: Data.POSIX,
    -- | The IAM service role that\'s associated with the environment account
    -- connection.
    EnvironmentAccountConnection -> Text
roleArn :: Prelude.Text,
    -- | The status of the environment account connection.
    EnvironmentAccountConnection -> EnvironmentAccountConnectionStatus
status :: EnvironmentAccountConnectionStatus
  }
  deriving (EnvironmentAccountConnection
-> EnvironmentAccountConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnvironmentAccountConnection
-> EnvironmentAccountConnection -> Bool
$c/= :: EnvironmentAccountConnection
-> EnvironmentAccountConnection -> Bool
== :: EnvironmentAccountConnection
-> EnvironmentAccountConnection -> Bool
$c== :: EnvironmentAccountConnection
-> EnvironmentAccountConnection -> Bool
Prelude.Eq, ReadPrec [EnvironmentAccountConnection]
ReadPrec EnvironmentAccountConnection
Int -> ReadS EnvironmentAccountConnection
ReadS [EnvironmentAccountConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnvironmentAccountConnection]
$creadListPrec :: ReadPrec [EnvironmentAccountConnection]
readPrec :: ReadPrec EnvironmentAccountConnection
$creadPrec :: ReadPrec EnvironmentAccountConnection
readList :: ReadS [EnvironmentAccountConnection]
$creadList :: ReadS [EnvironmentAccountConnection]
readsPrec :: Int -> ReadS EnvironmentAccountConnection
$creadsPrec :: Int -> ReadS EnvironmentAccountConnection
Prelude.Read, Int -> EnvironmentAccountConnection -> ShowS
[EnvironmentAccountConnection] -> ShowS
EnvironmentAccountConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnvironmentAccountConnection] -> ShowS
$cshowList :: [EnvironmentAccountConnection] -> ShowS
show :: EnvironmentAccountConnection -> String
$cshow :: EnvironmentAccountConnection -> String
showsPrec :: Int -> EnvironmentAccountConnection -> ShowS
$cshowsPrec :: Int -> EnvironmentAccountConnection -> ShowS
Prelude.Show, forall x.
Rep EnvironmentAccountConnection x -> EnvironmentAccountConnection
forall x.
EnvironmentAccountConnection -> Rep EnvironmentAccountConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EnvironmentAccountConnection x -> EnvironmentAccountConnection
$cfrom :: forall x.
EnvironmentAccountConnection -> Rep EnvironmentAccountConnection x
Prelude.Generic)

-- |
-- Create a value of 'EnvironmentAccountConnection' 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:
--
-- 'codebuildRoleArn', 'environmentAccountConnection_codebuildRoleArn' - The Amazon Resource Name (ARN) of an IAM service role in the environment
-- account. Proton uses this role to provision infrastructure resources
-- using CodeBuild-based provisioning in the associated environment
-- account.
--
-- 'componentRoleArn', 'environmentAccountConnection_componentRoleArn' - The Amazon Resource Name (ARN) of the IAM service role that Proton uses
-- when provisioning directly defined components in the associated
-- environment account. It determines the scope of infrastructure that a
-- component can provision in the account.
--
-- The environment account connection must have a @componentRoleArn@ to
-- allow directly defined components to be associated with any environments
-- running in the account.
--
-- For more information about components, see
-- <https://docs.aws.amazon.com/proton/latest/userguide/ag-components.html Proton components>
-- in the /Proton User Guide/.
--
-- 'arn', 'environmentAccountConnection_arn' - The Amazon Resource Name (ARN) of the environment account connection.
--
-- 'environmentAccountId', 'environmentAccountConnection_environmentAccountId' - The environment account that\'s connected to the environment account
-- connection.
--
-- 'environmentName', 'environmentAccountConnection_environmentName' - The name of the environment that\'s associated with the environment
-- account connection.
--
-- 'id', 'environmentAccountConnection_id' - The ID of the environment account connection.
--
-- 'lastModifiedAt', 'environmentAccountConnection_lastModifiedAt' - The time when the environment account connection was last modified.
--
-- 'managementAccountId', 'environmentAccountConnection_managementAccountId' - The ID of the management account that\'s connected to the environment
-- account connection.
--
-- 'requestedAt', 'environmentAccountConnection_requestedAt' - The time when the environment account connection request was made.
--
-- 'roleArn', 'environmentAccountConnection_roleArn' - The IAM service role that\'s associated with the environment account
-- connection.
--
-- 'status', 'environmentAccountConnection_status' - The status of the environment account connection.
newEnvironmentAccountConnection ::
  -- | 'arn'
  Prelude.Text ->
  -- | 'environmentAccountId'
  Prelude.Text ->
  -- | 'environmentName'
  Prelude.Text ->
  -- | 'id'
  Prelude.Text ->
  -- | 'lastModifiedAt'
  Prelude.UTCTime ->
  -- | 'managementAccountId'
  Prelude.Text ->
  -- | 'requestedAt'
  Prelude.UTCTime ->
  -- | 'roleArn'
  Prelude.Text ->
  -- | 'status'
  EnvironmentAccountConnectionStatus ->
  EnvironmentAccountConnection
newEnvironmentAccountConnection :: Text
-> Text
-> Text
-> Text
-> UTCTime
-> Text
-> UTCTime
-> Text
-> EnvironmentAccountConnectionStatus
-> EnvironmentAccountConnection
newEnvironmentAccountConnection
  Text
pArn_
  Text
pEnvironmentAccountId_
  Text
pEnvironmentName_
  Text
pId_
  UTCTime
pLastModifiedAt_
  Text
pManagementAccountId_
  UTCTime
pRequestedAt_
  Text
pRoleArn_
  EnvironmentAccountConnectionStatus
pStatus_ =
    EnvironmentAccountConnection'
      { $sel:codebuildRoleArn:EnvironmentAccountConnection' :: Maybe Text
codebuildRoleArn =
          forall a. Maybe a
Prelude.Nothing,
        $sel:componentRoleArn:EnvironmentAccountConnection' :: Maybe Text
componentRoleArn = forall a. Maybe a
Prelude.Nothing,
        $sel:arn:EnvironmentAccountConnection' :: Text
arn = Text
pArn_,
        $sel:environmentAccountId:EnvironmentAccountConnection' :: Text
environmentAccountId = Text
pEnvironmentAccountId_,
        $sel:environmentName:EnvironmentAccountConnection' :: Text
environmentName = Text
pEnvironmentName_,
        $sel:id:EnvironmentAccountConnection' :: Text
id = Text
pId_,
        $sel:lastModifiedAt:EnvironmentAccountConnection' :: POSIX
lastModifiedAt =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastModifiedAt_,
        $sel:managementAccountId:EnvironmentAccountConnection' :: Text
managementAccountId = Text
pManagementAccountId_,
        $sel:requestedAt:EnvironmentAccountConnection' :: POSIX
requestedAt = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pRequestedAt_,
        $sel:roleArn:EnvironmentAccountConnection' :: Text
roleArn = Text
pRoleArn_,
        $sel:status:EnvironmentAccountConnection' :: EnvironmentAccountConnectionStatus
status = EnvironmentAccountConnectionStatus
pStatus_
      }

-- | The Amazon Resource Name (ARN) of an IAM service role in the environment
-- account. Proton uses this role to provision infrastructure resources
-- using CodeBuild-based provisioning in the associated environment
-- account.
environmentAccountConnection_codebuildRoleArn :: Lens.Lens' EnvironmentAccountConnection (Prelude.Maybe Prelude.Text)
environmentAccountConnection_codebuildRoleArn :: Lens' EnvironmentAccountConnection (Maybe Text)
environmentAccountConnection_codebuildRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnvironmentAccountConnection' {Maybe Text
codebuildRoleArn :: Maybe Text
$sel:codebuildRoleArn:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Maybe Text
codebuildRoleArn} -> Maybe Text
codebuildRoleArn) (\s :: EnvironmentAccountConnection
s@EnvironmentAccountConnection' {} Maybe Text
a -> EnvironmentAccountConnection
s {$sel:codebuildRoleArn:EnvironmentAccountConnection' :: Maybe Text
codebuildRoleArn = Maybe Text
a} :: EnvironmentAccountConnection)

-- | The Amazon Resource Name (ARN) of the IAM service role that Proton uses
-- when provisioning directly defined components in the associated
-- environment account. It determines the scope of infrastructure that a
-- component can provision in the account.
--
-- The environment account connection must have a @componentRoleArn@ to
-- allow directly defined components to be associated with any environments
-- running in the account.
--
-- For more information about components, see
-- <https://docs.aws.amazon.com/proton/latest/userguide/ag-components.html Proton components>
-- in the /Proton User Guide/.
environmentAccountConnection_componentRoleArn :: Lens.Lens' EnvironmentAccountConnection (Prelude.Maybe Prelude.Text)
environmentAccountConnection_componentRoleArn :: Lens' EnvironmentAccountConnection (Maybe Text)
environmentAccountConnection_componentRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnvironmentAccountConnection' {Maybe Text
componentRoleArn :: Maybe Text
$sel:componentRoleArn:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Maybe Text
componentRoleArn} -> Maybe Text
componentRoleArn) (\s :: EnvironmentAccountConnection
s@EnvironmentAccountConnection' {} Maybe Text
a -> EnvironmentAccountConnection
s {$sel:componentRoleArn:EnvironmentAccountConnection' :: Maybe Text
componentRoleArn = Maybe Text
a} :: EnvironmentAccountConnection)

-- | The Amazon Resource Name (ARN) of the environment account connection.
environmentAccountConnection_arn :: Lens.Lens' EnvironmentAccountConnection Prelude.Text
environmentAccountConnection_arn :: Lens' EnvironmentAccountConnection Text
environmentAccountConnection_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnvironmentAccountConnection' {Text
arn :: Text
$sel:arn:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
arn} -> Text
arn) (\s :: EnvironmentAccountConnection
s@EnvironmentAccountConnection' {} Text
a -> EnvironmentAccountConnection
s {$sel:arn:EnvironmentAccountConnection' :: Text
arn = Text
a} :: EnvironmentAccountConnection)

-- | The environment account that\'s connected to the environment account
-- connection.
environmentAccountConnection_environmentAccountId :: Lens.Lens' EnvironmentAccountConnection Prelude.Text
environmentAccountConnection_environmentAccountId :: Lens' EnvironmentAccountConnection Text
environmentAccountConnection_environmentAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnvironmentAccountConnection' {Text
environmentAccountId :: Text
$sel:environmentAccountId:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
environmentAccountId} -> Text
environmentAccountId) (\s :: EnvironmentAccountConnection
s@EnvironmentAccountConnection' {} Text
a -> EnvironmentAccountConnection
s {$sel:environmentAccountId:EnvironmentAccountConnection' :: Text
environmentAccountId = Text
a} :: EnvironmentAccountConnection)

-- | The name of the environment that\'s associated with the environment
-- account connection.
environmentAccountConnection_environmentName :: Lens.Lens' EnvironmentAccountConnection Prelude.Text
environmentAccountConnection_environmentName :: Lens' EnvironmentAccountConnection Text
environmentAccountConnection_environmentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnvironmentAccountConnection' {Text
environmentName :: Text
$sel:environmentName:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
environmentName} -> Text
environmentName) (\s :: EnvironmentAccountConnection
s@EnvironmentAccountConnection' {} Text
a -> EnvironmentAccountConnection
s {$sel:environmentName:EnvironmentAccountConnection' :: Text
environmentName = Text
a} :: EnvironmentAccountConnection)

-- | The ID of the environment account connection.
environmentAccountConnection_id :: Lens.Lens' EnvironmentAccountConnection Prelude.Text
environmentAccountConnection_id :: Lens' EnvironmentAccountConnection Text
environmentAccountConnection_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnvironmentAccountConnection' {Text
id :: Text
$sel:id:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
id} -> Text
id) (\s :: EnvironmentAccountConnection
s@EnvironmentAccountConnection' {} Text
a -> EnvironmentAccountConnection
s {$sel:id:EnvironmentAccountConnection' :: Text
id = Text
a} :: EnvironmentAccountConnection)

-- | The time when the environment account connection was last modified.
environmentAccountConnection_lastModifiedAt :: Lens.Lens' EnvironmentAccountConnection Prelude.UTCTime
environmentAccountConnection_lastModifiedAt :: Lens' EnvironmentAccountConnection UTCTime
environmentAccountConnection_lastModifiedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnvironmentAccountConnection' {POSIX
lastModifiedAt :: POSIX
$sel:lastModifiedAt:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> POSIX
lastModifiedAt} -> POSIX
lastModifiedAt) (\s :: EnvironmentAccountConnection
s@EnvironmentAccountConnection' {} POSIX
a -> EnvironmentAccountConnection
s {$sel:lastModifiedAt:EnvironmentAccountConnection' :: POSIX
lastModifiedAt = POSIX
a} :: EnvironmentAccountConnection) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The ID of the management account that\'s connected to the environment
-- account connection.
environmentAccountConnection_managementAccountId :: Lens.Lens' EnvironmentAccountConnection Prelude.Text
environmentAccountConnection_managementAccountId :: Lens' EnvironmentAccountConnection Text
environmentAccountConnection_managementAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnvironmentAccountConnection' {Text
managementAccountId :: Text
$sel:managementAccountId:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
managementAccountId} -> Text
managementAccountId) (\s :: EnvironmentAccountConnection
s@EnvironmentAccountConnection' {} Text
a -> EnvironmentAccountConnection
s {$sel:managementAccountId:EnvironmentAccountConnection' :: Text
managementAccountId = Text
a} :: EnvironmentAccountConnection)

-- | The time when the environment account connection request was made.
environmentAccountConnection_requestedAt :: Lens.Lens' EnvironmentAccountConnection Prelude.UTCTime
environmentAccountConnection_requestedAt :: Lens' EnvironmentAccountConnection UTCTime
environmentAccountConnection_requestedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnvironmentAccountConnection' {POSIX
requestedAt :: POSIX
$sel:requestedAt:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> POSIX
requestedAt} -> POSIX
requestedAt) (\s :: EnvironmentAccountConnection
s@EnvironmentAccountConnection' {} POSIX
a -> EnvironmentAccountConnection
s {$sel:requestedAt:EnvironmentAccountConnection' :: POSIX
requestedAt = POSIX
a} :: EnvironmentAccountConnection) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The IAM service role that\'s associated with the environment account
-- connection.
environmentAccountConnection_roleArn :: Lens.Lens' EnvironmentAccountConnection Prelude.Text
environmentAccountConnection_roleArn :: Lens' EnvironmentAccountConnection Text
environmentAccountConnection_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnvironmentAccountConnection' {Text
roleArn :: Text
$sel:roleArn:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
roleArn} -> Text
roleArn) (\s :: EnvironmentAccountConnection
s@EnvironmentAccountConnection' {} Text
a -> EnvironmentAccountConnection
s {$sel:roleArn:EnvironmentAccountConnection' :: Text
roleArn = Text
a} :: EnvironmentAccountConnection)

-- | The status of the environment account connection.
environmentAccountConnection_status :: Lens.Lens' EnvironmentAccountConnection EnvironmentAccountConnectionStatus
environmentAccountConnection_status :: Lens'
  EnvironmentAccountConnection EnvironmentAccountConnectionStatus
environmentAccountConnection_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnvironmentAccountConnection' {EnvironmentAccountConnectionStatus
status :: EnvironmentAccountConnectionStatus
$sel:status:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> EnvironmentAccountConnectionStatus
status} -> EnvironmentAccountConnectionStatus
status) (\s :: EnvironmentAccountConnection
s@EnvironmentAccountConnection' {} EnvironmentAccountConnectionStatus
a -> EnvironmentAccountConnection
s {$sel:status:EnvironmentAccountConnection' :: EnvironmentAccountConnectionStatus
status = EnvironmentAccountConnectionStatus
a} :: EnvironmentAccountConnection)

instance Data.FromJSON EnvironmentAccountConnection where
  parseJSON :: Value -> Parser EnvironmentAccountConnection
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"EnvironmentAccountConnection"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> POSIX
-> Text
-> POSIX
-> Text
-> EnvironmentAccountConnectionStatus
-> EnvironmentAccountConnection
EnvironmentAccountConnection'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"codebuildRoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"componentRoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser 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 -> Parser a
Data..: Key
"environmentAccountId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"environmentName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser 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 -> Parser a
Data..: Key
"lastModifiedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"managementAccountId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"requestedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"roleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"status")
      )

instance
  Prelude.Hashable
    EnvironmentAccountConnection
  where
  hashWithSalt :: Int -> EnvironmentAccountConnection -> Int
hashWithSalt Int
_salt EnvironmentAccountConnection' {Maybe Text
Text
POSIX
EnvironmentAccountConnectionStatus
status :: EnvironmentAccountConnectionStatus
roleArn :: Text
requestedAt :: POSIX
managementAccountId :: Text
lastModifiedAt :: POSIX
id :: Text
environmentName :: Text
environmentAccountId :: Text
arn :: Text
componentRoleArn :: Maybe Text
codebuildRoleArn :: Maybe Text
$sel:status:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> EnvironmentAccountConnectionStatus
$sel:roleArn:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
$sel:requestedAt:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> POSIX
$sel:managementAccountId:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
$sel:lastModifiedAt:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> POSIX
$sel:id:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
$sel:environmentName:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
$sel:environmentAccountId:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
$sel:arn:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
$sel:componentRoleArn:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Maybe Text
$sel:codebuildRoleArn:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
codebuildRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
componentRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
environmentAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
environmentName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
lastModifiedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
managementAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
requestedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` EnvironmentAccountConnectionStatus
status

instance Prelude.NFData EnvironmentAccountConnection where
  rnf :: EnvironmentAccountConnection -> ()
rnf EnvironmentAccountConnection' {Maybe Text
Text
POSIX
EnvironmentAccountConnectionStatus
status :: EnvironmentAccountConnectionStatus
roleArn :: Text
requestedAt :: POSIX
managementAccountId :: Text
lastModifiedAt :: POSIX
id :: Text
environmentName :: Text
environmentAccountId :: Text
arn :: Text
componentRoleArn :: Maybe Text
codebuildRoleArn :: Maybe Text
$sel:status:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> EnvironmentAccountConnectionStatus
$sel:roleArn:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
$sel:requestedAt:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> POSIX
$sel:managementAccountId:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
$sel:lastModifiedAt:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> POSIX
$sel:id:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
$sel:environmentName:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
$sel:environmentAccountId:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
$sel:arn:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Text
$sel:componentRoleArn:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Maybe Text
$sel:codebuildRoleArn:EnvironmentAccountConnection' :: EnvironmentAccountConnection -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
codebuildRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
componentRoleArn
      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
environmentAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
environmentName
      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 POSIX
lastModifiedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
managementAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
requestedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf EnvironmentAccountConnectionStatus
status