{-# 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.Detective.Types.MemberDetail
-- 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.Detective.Types.MemberDetail where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Detective.Types.DatasourcePackage
import Amazonka.Detective.Types.DatasourcePackageIngestState
import Amazonka.Detective.Types.DatasourcePackageUsageInfo
import Amazonka.Detective.Types.InvitationType
import Amazonka.Detective.Types.MemberDisabledReason
import Amazonka.Detective.Types.MemberStatus
import qualified Amazonka.Prelude as Prelude

-- | Details about a member account in a behavior graph.
--
-- /See:/ 'newMemberDetail' smart constructor.
data MemberDetail = MemberDetail'
  { -- | The Amazon Web Services account identifier for the member account.
    MemberDetail -> Maybe Text
accountId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services account identifier of the administrator account
    -- for the behavior graph.
    MemberDetail -> Maybe Text
administratorId :: Prelude.Maybe Prelude.Text,
    -- | The state of a data source package for the behavior graph.
    MemberDetail
-> Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
datasourcePackageIngestStates :: Prelude.Maybe (Prelude.HashMap DatasourcePackage DatasourcePackageIngestState),
    -- | For member accounts with a status of @ACCEPTED_BUT_DISABLED@, the reason
    -- that the member account is not enabled.
    --
    -- The reason can have one of the following values:
    --
    -- -   @VOLUME_TOO_HIGH@ - Indicates that adding the member account would
    --     cause the data volume for the behavior graph to be too high.
    --
    -- -   @VOLUME_UNKNOWN@ - Indicates that Detective is unable to verify the
    --     data volume for the member account. This is usually because the
    --     member account is not enrolled in Amazon GuardDuty.
    MemberDetail -> Maybe MemberDisabledReason
disabledReason :: Prelude.Maybe MemberDisabledReason,
    -- | The Amazon Web Services account root user email address for the member
    -- account.
    MemberDetail -> Maybe Text
emailAddress :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the behavior graph.
    MemberDetail -> Maybe Text
graphArn :: Prelude.Maybe Prelude.Text,
    -- | The type of behavior graph membership.
    --
    -- For an organization account in the organization behavior graph, the type
    -- is @ORGANIZATION@.
    --
    -- For an account that was invited to a behavior graph, the type is
    -- @INVITATION@.
    MemberDetail -> Maybe InvitationType
invitationType :: Prelude.Maybe InvitationType,
    -- | For invited accounts, the date and time that Detective sent the
    -- invitation to the account. The value is an ISO8601 formatted string. For
    -- example, @2021-08-18T16:35:56.284Z@.
    MemberDetail -> Maybe ISO8601
invitedTime :: Prelude.Maybe Data.ISO8601,
    -- | The Amazon Web Services account identifier of the administrator account
    -- for the behavior graph.
    MemberDetail -> Maybe Text
masterId :: Prelude.Maybe Prelude.Text,
    -- | The member account data volume as a percentage of the maximum allowed
    -- data volume. 0 indicates 0 percent, and 100 indicates 100 percent.
    --
    -- Note that this is not the percentage of the behavior graph data volume.
    --
    -- For example, the data volume for the behavior graph is 80 GB per day.
    -- The maximum data volume is 160 GB per day. If the data volume for the
    -- member account is 40 GB per day, then @PercentOfGraphUtilization@ is 25.
    -- It represents 25% of the maximum allowed data volume.
    MemberDetail -> Maybe Double
percentOfGraphUtilization :: Prelude.Maybe Prelude.Double,
    -- | The date and time when the graph utilization percentage was last
    -- updated. The value is an ISO8601 formatted string. For example,
    -- @2021-08-18T16:35:56.284Z@.
    MemberDetail -> Maybe ISO8601
percentOfGraphUtilizationUpdatedTime :: Prelude.Maybe Data.ISO8601,
    -- | The current membership status of the member account. The status can have
    -- one of the following values:
    --
    -- -   @INVITED@ - For invited accounts only. Indicates that the member was
    --     sent an invitation but has not yet responded.
    --
    -- -   @VERIFICATION_IN_PROGRESS@ - For invited accounts only, indicates
    --     that Detective is verifying that the account identifier and email
    --     address provided for the member account match. If they do match,
    --     then Detective sends the invitation. If the email address and
    --     account identifier don\'t match, then the member cannot be added to
    --     the behavior graph.
    --
    --     For organization accounts in the organization behavior graph,
    --     indicates that Detective is verifying that the account belongs to
    --     the organization.
    --
    -- -   @VERIFICATION_FAILED@ - For invited accounts only. Indicates that
    --     the account and email address provided for the member account do not
    --     match, and Detective did not send an invitation to the account.
    --
    -- -   @ENABLED@ - Indicates that the member account currently contributes
    --     data to the behavior graph. For invited accounts, the member account
    --     accepted the invitation. For organization accounts in the
    --     organization behavior graph, the Detective administrator account
    --     enabled the organization account as a member account.
    --
    -- -   @ACCEPTED_BUT_DISABLED@ - The account accepted the invitation, or
    --     was enabled by the Detective administrator account, but is prevented
    --     from contributing data to the behavior graph. @DisabledReason@
    --     provides the reason why the member account is not enabled.
    --
    -- Invited accounts that declined an invitation or that were removed from
    -- the behavior graph are not included. In the organization behavior graph,
    -- organization accounts that the Detective administrator account did not
    -- enable are not included.
    MemberDetail -> Maybe MemberStatus
status :: Prelude.Maybe MemberStatus,
    -- | The date and time that the member account was last updated. The value is
    -- an ISO8601 formatted string. For example, @2021-08-18T16:35:56.284Z@.
    MemberDetail -> Maybe ISO8601
updatedTime :: Prelude.Maybe Data.ISO8601,
    -- | Details on the volume of usage for each data source package in a
    -- behavior graph.
    MemberDetail
-> Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
volumeUsageByDatasourcePackage :: Prelude.Maybe (Prelude.HashMap DatasourcePackage DatasourcePackageUsageInfo),
    -- | The data volume in bytes per day for the member account.
    MemberDetail -> Maybe Integer
volumeUsageInBytes :: Prelude.Maybe Prelude.Integer,
    -- | The data and time when the member account data volume was last updated.
    -- The value is an ISO8601 formatted string. For example,
    -- @2021-08-18T16:35:56.284Z@.
    MemberDetail -> Maybe ISO8601
volumeUsageUpdatedTime :: Prelude.Maybe Data.ISO8601
  }
  deriving (MemberDetail -> MemberDetail -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemberDetail -> MemberDetail -> Bool
$c/= :: MemberDetail -> MemberDetail -> Bool
== :: MemberDetail -> MemberDetail -> Bool
$c== :: MemberDetail -> MemberDetail -> Bool
Prelude.Eq, ReadPrec [MemberDetail]
ReadPrec MemberDetail
Int -> ReadS MemberDetail
ReadS [MemberDetail]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MemberDetail]
$creadListPrec :: ReadPrec [MemberDetail]
readPrec :: ReadPrec MemberDetail
$creadPrec :: ReadPrec MemberDetail
readList :: ReadS [MemberDetail]
$creadList :: ReadS [MemberDetail]
readsPrec :: Int -> ReadS MemberDetail
$creadsPrec :: Int -> ReadS MemberDetail
Prelude.Read, Int -> MemberDetail -> ShowS
[MemberDetail] -> ShowS
MemberDetail -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MemberDetail] -> ShowS
$cshowList :: [MemberDetail] -> ShowS
show :: MemberDetail -> String
$cshow :: MemberDetail -> String
showsPrec :: Int -> MemberDetail -> ShowS
$cshowsPrec :: Int -> MemberDetail -> ShowS
Prelude.Show, forall x. Rep MemberDetail x -> MemberDetail
forall x. MemberDetail -> Rep MemberDetail x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MemberDetail x -> MemberDetail
$cfrom :: forall x. MemberDetail -> Rep MemberDetail x
Prelude.Generic)

-- |
-- Create a value of 'MemberDetail' 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:
--
-- 'accountId', 'memberDetail_accountId' - The Amazon Web Services account identifier for the member account.
--
-- 'administratorId', 'memberDetail_administratorId' - The Amazon Web Services account identifier of the administrator account
-- for the behavior graph.
--
-- 'datasourcePackageIngestStates', 'memberDetail_datasourcePackageIngestStates' - The state of a data source package for the behavior graph.
--
-- 'disabledReason', 'memberDetail_disabledReason' - For member accounts with a status of @ACCEPTED_BUT_DISABLED@, the reason
-- that the member account is not enabled.
--
-- The reason can have one of the following values:
--
-- -   @VOLUME_TOO_HIGH@ - Indicates that adding the member account would
--     cause the data volume for the behavior graph to be too high.
--
-- -   @VOLUME_UNKNOWN@ - Indicates that Detective is unable to verify the
--     data volume for the member account. This is usually because the
--     member account is not enrolled in Amazon GuardDuty.
--
-- 'emailAddress', 'memberDetail_emailAddress' - The Amazon Web Services account root user email address for the member
-- account.
--
-- 'graphArn', 'memberDetail_graphArn' - The ARN of the behavior graph.
--
-- 'invitationType', 'memberDetail_invitationType' - The type of behavior graph membership.
--
-- For an organization account in the organization behavior graph, the type
-- is @ORGANIZATION@.
--
-- For an account that was invited to a behavior graph, the type is
-- @INVITATION@.
--
-- 'invitedTime', 'memberDetail_invitedTime' - For invited accounts, the date and time that Detective sent the
-- invitation to the account. The value is an ISO8601 formatted string. For
-- example, @2021-08-18T16:35:56.284Z@.
--
-- 'masterId', 'memberDetail_masterId' - The Amazon Web Services account identifier of the administrator account
-- for the behavior graph.
--
-- 'percentOfGraphUtilization', 'memberDetail_percentOfGraphUtilization' - The member account data volume as a percentage of the maximum allowed
-- data volume. 0 indicates 0 percent, and 100 indicates 100 percent.
--
-- Note that this is not the percentage of the behavior graph data volume.
--
-- For example, the data volume for the behavior graph is 80 GB per day.
-- The maximum data volume is 160 GB per day. If the data volume for the
-- member account is 40 GB per day, then @PercentOfGraphUtilization@ is 25.
-- It represents 25% of the maximum allowed data volume.
--
-- 'percentOfGraphUtilizationUpdatedTime', 'memberDetail_percentOfGraphUtilizationUpdatedTime' - The date and time when the graph utilization percentage was last
-- updated. The value is an ISO8601 formatted string. For example,
-- @2021-08-18T16:35:56.284Z@.
--
-- 'status', 'memberDetail_status' - The current membership status of the member account. The status can have
-- one of the following values:
--
-- -   @INVITED@ - For invited accounts only. Indicates that the member was
--     sent an invitation but has not yet responded.
--
-- -   @VERIFICATION_IN_PROGRESS@ - For invited accounts only, indicates
--     that Detective is verifying that the account identifier and email
--     address provided for the member account match. If they do match,
--     then Detective sends the invitation. If the email address and
--     account identifier don\'t match, then the member cannot be added to
--     the behavior graph.
--
--     For organization accounts in the organization behavior graph,
--     indicates that Detective is verifying that the account belongs to
--     the organization.
--
-- -   @VERIFICATION_FAILED@ - For invited accounts only. Indicates that
--     the account and email address provided for the member account do not
--     match, and Detective did not send an invitation to the account.
--
-- -   @ENABLED@ - Indicates that the member account currently contributes
--     data to the behavior graph. For invited accounts, the member account
--     accepted the invitation. For organization accounts in the
--     organization behavior graph, the Detective administrator account
--     enabled the organization account as a member account.
--
-- -   @ACCEPTED_BUT_DISABLED@ - The account accepted the invitation, or
--     was enabled by the Detective administrator account, but is prevented
--     from contributing data to the behavior graph. @DisabledReason@
--     provides the reason why the member account is not enabled.
--
-- Invited accounts that declined an invitation or that were removed from
-- the behavior graph are not included. In the organization behavior graph,
-- organization accounts that the Detective administrator account did not
-- enable are not included.
--
-- 'updatedTime', 'memberDetail_updatedTime' - The date and time that the member account was last updated. The value is
-- an ISO8601 formatted string. For example, @2021-08-18T16:35:56.284Z@.
--
-- 'volumeUsageByDatasourcePackage', 'memberDetail_volumeUsageByDatasourcePackage' - Details on the volume of usage for each data source package in a
-- behavior graph.
--
-- 'volumeUsageInBytes', 'memberDetail_volumeUsageInBytes' - The data volume in bytes per day for the member account.
--
-- 'volumeUsageUpdatedTime', 'memberDetail_volumeUsageUpdatedTime' - The data and time when the member account data volume was last updated.
-- The value is an ISO8601 formatted string. For example,
-- @2021-08-18T16:35:56.284Z@.
newMemberDetail ::
  MemberDetail
newMemberDetail :: MemberDetail
newMemberDetail =
  MemberDetail'
    { $sel:accountId:MemberDetail' :: Maybe Text
accountId = forall a. Maybe a
Prelude.Nothing,
      $sel:administratorId:MemberDetail' :: Maybe Text
administratorId = forall a. Maybe a
Prelude.Nothing,
      $sel:datasourcePackageIngestStates:MemberDetail' :: Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
datasourcePackageIngestStates = forall a. Maybe a
Prelude.Nothing,
      $sel:disabledReason:MemberDetail' :: Maybe MemberDisabledReason
disabledReason = forall a. Maybe a
Prelude.Nothing,
      $sel:emailAddress:MemberDetail' :: Maybe Text
emailAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:graphArn:MemberDetail' :: Maybe Text
graphArn = forall a. Maybe a
Prelude.Nothing,
      $sel:invitationType:MemberDetail' :: Maybe InvitationType
invitationType = forall a. Maybe a
Prelude.Nothing,
      $sel:invitedTime:MemberDetail' :: Maybe ISO8601
invitedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:masterId:MemberDetail' :: Maybe Text
masterId = forall a. Maybe a
Prelude.Nothing,
      $sel:percentOfGraphUtilization:MemberDetail' :: Maybe Double
percentOfGraphUtilization = forall a. Maybe a
Prelude.Nothing,
      $sel:percentOfGraphUtilizationUpdatedTime:MemberDetail' :: Maybe ISO8601
percentOfGraphUtilizationUpdatedTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:status:MemberDetail' :: Maybe MemberStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:updatedTime:MemberDetail' :: Maybe ISO8601
updatedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeUsageByDatasourcePackage:MemberDetail' :: Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
volumeUsageByDatasourcePackage = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeUsageInBytes:MemberDetail' :: Maybe Integer
volumeUsageInBytes = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeUsageUpdatedTime:MemberDetail' :: Maybe ISO8601
volumeUsageUpdatedTime = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Web Services account identifier for the member account.
memberDetail_accountId :: Lens.Lens' MemberDetail (Prelude.Maybe Prelude.Text)
memberDetail_accountId :: Lens' MemberDetail (Maybe Text)
memberDetail_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe Text
accountId :: Maybe Text
$sel:accountId:MemberDetail' :: MemberDetail -> Maybe Text
accountId} -> Maybe Text
accountId) (\s :: MemberDetail
s@MemberDetail' {} Maybe Text
a -> MemberDetail
s {$sel:accountId:MemberDetail' :: Maybe Text
accountId = Maybe Text
a} :: MemberDetail)

-- | The Amazon Web Services account identifier of the administrator account
-- for the behavior graph.
memberDetail_administratorId :: Lens.Lens' MemberDetail (Prelude.Maybe Prelude.Text)
memberDetail_administratorId :: Lens' MemberDetail (Maybe Text)
memberDetail_administratorId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe Text
administratorId :: Maybe Text
$sel:administratorId:MemberDetail' :: MemberDetail -> Maybe Text
administratorId} -> Maybe Text
administratorId) (\s :: MemberDetail
s@MemberDetail' {} Maybe Text
a -> MemberDetail
s {$sel:administratorId:MemberDetail' :: Maybe Text
administratorId = Maybe Text
a} :: MemberDetail)

-- | The state of a data source package for the behavior graph.
memberDetail_datasourcePackageIngestStates :: Lens.Lens' MemberDetail (Prelude.Maybe (Prelude.HashMap DatasourcePackage DatasourcePackageIngestState))
memberDetail_datasourcePackageIngestStates :: Lens'
  MemberDetail
  (Maybe (HashMap DatasourcePackage DatasourcePackageIngestState))
memberDetail_datasourcePackageIngestStates = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
datasourcePackageIngestStates :: Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
$sel:datasourcePackageIngestStates:MemberDetail' :: MemberDetail
-> Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
datasourcePackageIngestStates} -> Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
datasourcePackageIngestStates) (\s :: MemberDetail
s@MemberDetail' {} Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
a -> MemberDetail
s {$sel:datasourcePackageIngestStates:MemberDetail' :: Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
datasourcePackageIngestStates = Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
a} :: MemberDetail) 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

-- | For member accounts with a status of @ACCEPTED_BUT_DISABLED@, the reason
-- that the member account is not enabled.
--
-- The reason can have one of the following values:
--
-- -   @VOLUME_TOO_HIGH@ - Indicates that adding the member account would
--     cause the data volume for the behavior graph to be too high.
--
-- -   @VOLUME_UNKNOWN@ - Indicates that Detective is unable to verify the
--     data volume for the member account. This is usually because the
--     member account is not enrolled in Amazon GuardDuty.
memberDetail_disabledReason :: Lens.Lens' MemberDetail (Prelude.Maybe MemberDisabledReason)
memberDetail_disabledReason :: Lens' MemberDetail (Maybe MemberDisabledReason)
memberDetail_disabledReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe MemberDisabledReason
disabledReason :: Maybe MemberDisabledReason
$sel:disabledReason:MemberDetail' :: MemberDetail -> Maybe MemberDisabledReason
disabledReason} -> Maybe MemberDisabledReason
disabledReason) (\s :: MemberDetail
s@MemberDetail' {} Maybe MemberDisabledReason
a -> MemberDetail
s {$sel:disabledReason:MemberDetail' :: Maybe MemberDisabledReason
disabledReason = Maybe MemberDisabledReason
a} :: MemberDetail)

-- | The Amazon Web Services account root user email address for the member
-- account.
memberDetail_emailAddress :: Lens.Lens' MemberDetail (Prelude.Maybe Prelude.Text)
memberDetail_emailAddress :: Lens' MemberDetail (Maybe Text)
memberDetail_emailAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe Text
emailAddress :: Maybe Text
$sel:emailAddress:MemberDetail' :: MemberDetail -> Maybe Text
emailAddress} -> Maybe Text
emailAddress) (\s :: MemberDetail
s@MemberDetail' {} Maybe Text
a -> MemberDetail
s {$sel:emailAddress:MemberDetail' :: Maybe Text
emailAddress = Maybe Text
a} :: MemberDetail)

-- | The ARN of the behavior graph.
memberDetail_graphArn :: Lens.Lens' MemberDetail (Prelude.Maybe Prelude.Text)
memberDetail_graphArn :: Lens' MemberDetail (Maybe Text)
memberDetail_graphArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe Text
graphArn :: Maybe Text
$sel:graphArn:MemberDetail' :: MemberDetail -> Maybe Text
graphArn} -> Maybe Text
graphArn) (\s :: MemberDetail
s@MemberDetail' {} Maybe Text
a -> MemberDetail
s {$sel:graphArn:MemberDetail' :: Maybe Text
graphArn = Maybe Text
a} :: MemberDetail)

-- | The type of behavior graph membership.
--
-- For an organization account in the organization behavior graph, the type
-- is @ORGANIZATION@.
--
-- For an account that was invited to a behavior graph, the type is
-- @INVITATION@.
memberDetail_invitationType :: Lens.Lens' MemberDetail (Prelude.Maybe InvitationType)
memberDetail_invitationType :: Lens' MemberDetail (Maybe InvitationType)
memberDetail_invitationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe InvitationType
invitationType :: Maybe InvitationType
$sel:invitationType:MemberDetail' :: MemberDetail -> Maybe InvitationType
invitationType} -> Maybe InvitationType
invitationType) (\s :: MemberDetail
s@MemberDetail' {} Maybe InvitationType
a -> MemberDetail
s {$sel:invitationType:MemberDetail' :: Maybe InvitationType
invitationType = Maybe InvitationType
a} :: MemberDetail)

-- | For invited accounts, the date and time that Detective sent the
-- invitation to the account. The value is an ISO8601 formatted string. For
-- example, @2021-08-18T16:35:56.284Z@.
memberDetail_invitedTime :: Lens.Lens' MemberDetail (Prelude.Maybe Prelude.UTCTime)
memberDetail_invitedTime :: Lens' MemberDetail (Maybe UTCTime)
memberDetail_invitedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe ISO8601
invitedTime :: Maybe ISO8601
$sel:invitedTime:MemberDetail' :: MemberDetail -> Maybe ISO8601
invitedTime} -> Maybe ISO8601
invitedTime) (\s :: MemberDetail
s@MemberDetail' {} Maybe ISO8601
a -> MemberDetail
s {$sel:invitedTime:MemberDetail' :: Maybe ISO8601
invitedTime = Maybe ISO8601
a} :: MemberDetail) 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

-- | The Amazon Web Services account identifier of the administrator account
-- for the behavior graph.
memberDetail_masterId :: Lens.Lens' MemberDetail (Prelude.Maybe Prelude.Text)
memberDetail_masterId :: Lens' MemberDetail (Maybe Text)
memberDetail_masterId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe Text
masterId :: Maybe Text
$sel:masterId:MemberDetail' :: MemberDetail -> Maybe Text
masterId} -> Maybe Text
masterId) (\s :: MemberDetail
s@MemberDetail' {} Maybe Text
a -> MemberDetail
s {$sel:masterId:MemberDetail' :: Maybe Text
masterId = Maybe Text
a} :: MemberDetail)

-- | The member account data volume as a percentage of the maximum allowed
-- data volume. 0 indicates 0 percent, and 100 indicates 100 percent.
--
-- Note that this is not the percentage of the behavior graph data volume.
--
-- For example, the data volume for the behavior graph is 80 GB per day.
-- The maximum data volume is 160 GB per day. If the data volume for the
-- member account is 40 GB per day, then @PercentOfGraphUtilization@ is 25.
-- It represents 25% of the maximum allowed data volume.
memberDetail_percentOfGraphUtilization :: Lens.Lens' MemberDetail (Prelude.Maybe Prelude.Double)
memberDetail_percentOfGraphUtilization :: Lens' MemberDetail (Maybe Double)
memberDetail_percentOfGraphUtilization = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe Double
percentOfGraphUtilization :: Maybe Double
$sel:percentOfGraphUtilization:MemberDetail' :: MemberDetail -> Maybe Double
percentOfGraphUtilization} -> Maybe Double
percentOfGraphUtilization) (\s :: MemberDetail
s@MemberDetail' {} Maybe Double
a -> MemberDetail
s {$sel:percentOfGraphUtilization:MemberDetail' :: Maybe Double
percentOfGraphUtilization = Maybe Double
a} :: MemberDetail)

-- | The date and time when the graph utilization percentage was last
-- updated. The value is an ISO8601 formatted string. For example,
-- @2021-08-18T16:35:56.284Z@.
memberDetail_percentOfGraphUtilizationUpdatedTime :: Lens.Lens' MemberDetail (Prelude.Maybe Prelude.UTCTime)
memberDetail_percentOfGraphUtilizationUpdatedTime :: Lens' MemberDetail (Maybe UTCTime)
memberDetail_percentOfGraphUtilizationUpdatedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe ISO8601
percentOfGraphUtilizationUpdatedTime :: Maybe ISO8601
$sel:percentOfGraphUtilizationUpdatedTime:MemberDetail' :: MemberDetail -> Maybe ISO8601
percentOfGraphUtilizationUpdatedTime} -> Maybe ISO8601
percentOfGraphUtilizationUpdatedTime) (\s :: MemberDetail
s@MemberDetail' {} Maybe ISO8601
a -> MemberDetail
s {$sel:percentOfGraphUtilizationUpdatedTime:MemberDetail' :: Maybe ISO8601
percentOfGraphUtilizationUpdatedTime = Maybe ISO8601
a} :: MemberDetail) 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

-- | The current membership status of the member account. The status can have
-- one of the following values:
--
-- -   @INVITED@ - For invited accounts only. Indicates that the member was
--     sent an invitation but has not yet responded.
--
-- -   @VERIFICATION_IN_PROGRESS@ - For invited accounts only, indicates
--     that Detective is verifying that the account identifier and email
--     address provided for the member account match. If they do match,
--     then Detective sends the invitation. If the email address and
--     account identifier don\'t match, then the member cannot be added to
--     the behavior graph.
--
--     For organization accounts in the organization behavior graph,
--     indicates that Detective is verifying that the account belongs to
--     the organization.
--
-- -   @VERIFICATION_FAILED@ - For invited accounts only. Indicates that
--     the account and email address provided for the member account do not
--     match, and Detective did not send an invitation to the account.
--
-- -   @ENABLED@ - Indicates that the member account currently contributes
--     data to the behavior graph. For invited accounts, the member account
--     accepted the invitation. For organization accounts in the
--     organization behavior graph, the Detective administrator account
--     enabled the organization account as a member account.
--
-- -   @ACCEPTED_BUT_DISABLED@ - The account accepted the invitation, or
--     was enabled by the Detective administrator account, but is prevented
--     from contributing data to the behavior graph. @DisabledReason@
--     provides the reason why the member account is not enabled.
--
-- Invited accounts that declined an invitation or that were removed from
-- the behavior graph are not included. In the organization behavior graph,
-- organization accounts that the Detective administrator account did not
-- enable are not included.
memberDetail_status :: Lens.Lens' MemberDetail (Prelude.Maybe MemberStatus)
memberDetail_status :: Lens' MemberDetail (Maybe MemberStatus)
memberDetail_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe MemberStatus
status :: Maybe MemberStatus
$sel:status:MemberDetail' :: MemberDetail -> Maybe MemberStatus
status} -> Maybe MemberStatus
status) (\s :: MemberDetail
s@MemberDetail' {} Maybe MemberStatus
a -> MemberDetail
s {$sel:status:MemberDetail' :: Maybe MemberStatus
status = Maybe MemberStatus
a} :: MemberDetail)

-- | The date and time that the member account was last updated. The value is
-- an ISO8601 formatted string. For example, @2021-08-18T16:35:56.284Z@.
memberDetail_updatedTime :: Lens.Lens' MemberDetail (Prelude.Maybe Prelude.UTCTime)
memberDetail_updatedTime :: Lens' MemberDetail (Maybe UTCTime)
memberDetail_updatedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe ISO8601
updatedTime :: Maybe ISO8601
$sel:updatedTime:MemberDetail' :: MemberDetail -> Maybe ISO8601
updatedTime} -> Maybe ISO8601
updatedTime) (\s :: MemberDetail
s@MemberDetail' {} Maybe ISO8601
a -> MemberDetail
s {$sel:updatedTime:MemberDetail' :: Maybe ISO8601
updatedTime = Maybe ISO8601
a} :: MemberDetail) 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

-- | Details on the volume of usage for each data source package in a
-- behavior graph.
memberDetail_volumeUsageByDatasourcePackage :: Lens.Lens' MemberDetail (Prelude.Maybe (Prelude.HashMap DatasourcePackage DatasourcePackageUsageInfo))
memberDetail_volumeUsageByDatasourcePackage :: Lens'
  MemberDetail
  (Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo))
memberDetail_volumeUsageByDatasourcePackage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
volumeUsageByDatasourcePackage :: Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
$sel:volumeUsageByDatasourcePackage:MemberDetail' :: MemberDetail
-> Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
volumeUsageByDatasourcePackage} -> Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
volumeUsageByDatasourcePackage) (\s :: MemberDetail
s@MemberDetail' {} Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
a -> MemberDetail
s {$sel:volumeUsageByDatasourcePackage:MemberDetail' :: Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
volumeUsageByDatasourcePackage = Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
a} :: MemberDetail) 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

-- | The data volume in bytes per day for the member account.
memberDetail_volumeUsageInBytes :: Lens.Lens' MemberDetail (Prelude.Maybe Prelude.Integer)
memberDetail_volumeUsageInBytes :: Lens' MemberDetail (Maybe Integer)
memberDetail_volumeUsageInBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe Integer
volumeUsageInBytes :: Maybe Integer
$sel:volumeUsageInBytes:MemberDetail' :: MemberDetail -> Maybe Integer
volumeUsageInBytes} -> Maybe Integer
volumeUsageInBytes) (\s :: MemberDetail
s@MemberDetail' {} Maybe Integer
a -> MemberDetail
s {$sel:volumeUsageInBytes:MemberDetail' :: Maybe Integer
volumeUsageInBytes = Maybe Integer
a} :: MemberDetail)

-- | The data and time when the member account data volume was last updated.
-- The value is an ISO8601 formatted string. For example,
-- @2021-08-18T16:35:56.284Z@.
memberDetail_volumeUsageUpdatedTime :: Lens.Lens' MemberDetail (Prelude.Maybe Prelude.UTCTime)
memberDetail_volumeUsageUpdatedTime :: Lens' MemberDetail (Maybe UTCTime)
memberDetail_volumeUsageUpdatedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MemberDetail' {Maybe ISO8601
volumeUsageUpdatedTime :: Maybe ISO8601
$sel:volumeUsageUpdatedTime:MemberDetail' :: MemberDetail -> Maybe ISO8601
volumeUsageUpdatedTime} -> Maybe ISO8601
volumeUsageUpdatedTime) (\s :: MemberDetail
s@MemberDetail' {} Maybe ISO8601
a -> MemberDetail
s {$sel:volumeUsageUpdatedTime:MemberDetail' :: Maybe ISO8601
volumeUsageUpdatedTime = Maybe ISO8601
a} :: MemberDetail) 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

instance Data.FromJSON MemberDetail where
  parseJSON :: Value -> Parser MemberDetail
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"MemberDetail"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
-> Maybe MemberDisabledReason
-> Maybe Text
-> Maybe Text
-> Maybe InvitationType
-> Maybe ISO8601
-> Maybe Text
-> Maybe Double
-> Maybe ISO8601
-> Maybe MemberStatus
-> Maybe ISO8601
-> Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
-> Maybe Integer
-> Maybe ISO8601
-> MemberDetail
MemberDetail'
            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
"AccountId")
            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
"AdministratorId")
            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
"DatasourcePackageIngestStates"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"DisabledReason")
            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
"EmailAddress")
            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
"GraphArn")
            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
"InvitationType")
            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
"InvitedTime")
            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
"MasterId")
            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
"PercentOfGraphUtilization")
            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
"PercentOfGraphUtilizationUpdatedTime")
            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
"Status")
            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
"UpdatedTime")
            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
"VolumeUsageByDatasourcePackage"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"VolumeUsageInBytes")
            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
"VolumeUsageUpdatedTime")
      )

instance Prelude.Hashable MemberDetail where
  hashWithSalt :: Int -> MemberDetail -> Int
hashWithSalt Int
_salt MemberDetail' {Maybe Double
Maybe Integer
Maybe Text
Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
Maybe ISO8601
Maybe InvitationType
Maybe MemberDisabledReason
Maybe MemberStatus
volumeUsageUpdatedTime :: Maybe ISO8601
volumeUsageInBytes :: Maybe Integer
volumeUsageByDatasourcePackage :: Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
updatedTime :: Maybe ISO8601
status :: Maybe MemberStatus
percentOfGraphUtilizationUpdatedTime :: Maybe ISO8601
percentOfGraphUtilization :: Maybe Double
masterId :: Maybe Text
invitedTime :: Maybe ISO8601
invitationType :: Maybe InvitationType
graphArn :: Maybe Text
emailAddress :: Maybe Text
disabledReason :: Maybe MemberDisabledReason
datasourcePackageIngestStates :: Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
administratorId :: Maybe Text
accountId :: Maybe Text
$sel:volumeUsageUpdatedTime:MemberDetail' :: MemberDetail -> Maybe ISO8601
$sel:volumeUsageInBytes:MemberDetail' :: MemberDetail -> Maybe Integer
$sel:volumeUsageByDatasourcePackage:MemberDetail' :: MemberDetail
-> Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
$sel:updatedTime:MemberDetail' :: MemberDetail -> Maybe ISO8601
$sel:status:MemberDetail' :: MemberDetail -> Maybe MemberStatus
$sel:percentOfGraphUtilizationUpdatedTime:MemberDetail' :: MemberDetail -> Maybe ISO8601
$sel:percentOfGraphUtilization:MemberDetail' :: MemberDetail -> Maybe Double
$sel:masterId:MemberDetail' :: MemberDetail -> Maybe Text
$sel:invitedTime:MemberDetail' :: MemberDetail -> Maybe ISO8601
$sel:invitationType:MemberDetail' :: MemberDetail -> Maybe InvitationType
$sel:graphArn:MemberDetail' :: MemberDetail -> Maybe Text
$sel:emailAddress:MemberDetail' :: MemberDetail -> Maybe Text
$sel:disabledReason:MemberDetail' :: MemberDetail -> Maybe MemberDisabledReason
$sel:datasourcePackageIngestStates:MemberDetail' :: MemberDetail
-> Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
$sel:administratorId:MemberDetail' :: MemberDetail -> Maybe Text
$sel:accountId:MemberDetail' :: MemberDetail -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
accountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
administratorId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
datasourcePackageIngestStates
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MemberDisabledReason
disabledReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
emailAddress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
graphArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InvitationType
invitationType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
invitedTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
masterId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
percentOfGraphUtilization
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
percentOfGraphUtilizationUpdatedTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MemberStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
updatedTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
volumeUsageByDatasourcePackage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
volumeUsageInBytes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
volumeUsageUpdatedTime

instance Prelude.NFData MemberDetail where
  rnf :: MemberDetail -> ()
rnf MemberDetail' {Maybe Double
Maybe Integer
Maybe Text
Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
Maybe ISO8601
Maybe InvitationType
Maybe MemberDisabledReason
Maybe MemberStatus
volumeUsageUpdatedTime :: Maybe ISO8601
volumeUsageInBytes :: Maybe Integer
volumeUsageByDatasourcePackage :: Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
updatedTime :: Maybe ISO8601
status :: Maybe MemberStatus
percentOfGraphUtilizationUpdatedTime :: Maybe ISO8601
percentOfGraphUtilization :: Maybe Double
masterId :: Maybe Text
invitedTime :: Maybe ISO8601
invitationType :: Maybe InvitationType
graphArn :: Maybe Text
emailAddress :: Maybe Text
disabledReason :: Maybe MemberDisabledReason
datasourcePackageIngestStates :: Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
administratorId :: Maybe Text
accountId :: Maybe Text
$sel:volumeUsageUpdatedTime:MemberDetail' :: MemberDetail -> Maybe ISO8601
$sel:volumeUsageInBytes:MemberDetail' :: MemberDetail -> Maybe Integer
$sel:volumeUsageByDatasourcePackage:MemberDetail' :: MemberDetail
-> Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
$sel:updatedTime:MemberDetail' :: MemberDetail -> Maybe ISO8601
$sel:status:MemberDetail' :: MemberDetail -> Maybe MemberStatus
$sel:percentOfGraphUtilizationUpdatedTime:MemberDetail' :: MemberDetail -> Maybe ISO8601
$sel:percentOfGraphUtilization:MemberDetail' :: MemberDetail -> Maybe Double
$sel:masterId:MemberDetail' :: MemberDetail -> Maybe Text
$sel:invitedTime:MemberDetail' :: MemberDetail -> Maybe ISO8601
$sel:invitationType:MemberDetail' :: MemberDetail -> Maybe InvitationType
$sel:graphArn:MemberDetail' :: MemberDetail -> Maybe Text
$sel:emailAddress:MemberDetail' :: MemberDetail -> Maybe Text
$sel:disabledReason:MemberDetail' :: MemberDetail -> Maybe MemberDisabledReason
$sel:datasourcePackageIngestStates:MemberDetail' :: MemberDetail
-> Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
$sel:administratorId:MemberDetail' :: MemberDetail -> Maybe Text
$sel:accountId:MemberDetail' :: MemberDetail -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
administratorId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap DatasourcePackage DatasourcePackageIngestState)
datasourcePackageIngestStates
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MemberDisabledReason
disabledReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
emailAddress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
graphArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InvitationType
invitationType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
invitedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
masterId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
percentOfGraphUtilization
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
percentOfGraphUtilizationUpdatedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MemberStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
updatedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap DatasourcePackage DatasourcePackageUsageInfo)
volumeUsageByDatasourcePackage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
volumeUsageInBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
volumeUsageUpdatedTime