{-# 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.RAM.Types.ResourceShare
-- 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.RAM.Types.ResourceShare 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.RAM.Types.ResourceShareFeatureSet
import Amazonka.RAM.Types.ResourceShareStatus
import Amazonka.RAM.Types.Tag

-- | Describes a resource share in RAM.
--
-- /See:/ 'newResourceShare' smart constructor.
data ResourceShare = ResourceShare'
  { -- | Indicates whether principals outside your organization in Organizations
    -- can be associated with a resource share.
    ResourceShare -> Maybe Bool
allowExternalPrincipals :: Prelude.Maybe Prelude.Bool,
    -- | The date and time when the resource share was created.
    ResourceShare -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | Indicates how the resource share was created. Possible values include:
    --
    -- -   @CREATED_FROM_POLICY@ - Indicates that the resource share was
    --     created from an Identity and Access Management (IAM) resource-based
    --     permission policy attached to the resource. This type of resource
    --     share is visible only to the Amazon Web Services account that
    --     created it. You can\'t modify it in RAM unless you promote it. For
    --     more information, see PromoteResourceShareCreatedFromPolicy.
    --
    -- -   @PROMOTING_TO_STANDARD@ - The resource share is in the process of
    --     being promoted. For more information, see
    --     PromoteResourceShareCreatedFromPolicy.
    --
    -- -   @STANDARD@ - Indicates that the resource share was created in RAM
    --     using the console or APIs. These resource shares are visible to all
    --     principals you share the resource share with. You can modify these
    --     resource shares in RAM using the console or APIs.
    ResourceShare -> Maybe ResourceShareFeatureSet
featureSet :: Prelude.Maybe ResourceShareFeatureSet,
    -- | The date and time when the resource share was last updated.
    ResourceShare -> Maybe POSIX
lastUpdatedTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the resource share.
    ResourceShare -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Amazon Web Services account that owns the resource share.
    ResourceShare -> Maybe Text
owningAccountId :: Prelude.Maybe Prelude.Text,
    -- | The
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
    -- of the resource share
    ResourceShare -> Maybe Text
resourceShareArn :: Prelude.Maybe Prelude.Text,
    -- | The current status of the resource share.
    ResourceShare -> Maybe ResourceShareStatus
status :: Prelude.Maybe ResourceShareStatus,
    -- | A message about the status of the resource share.
    ResourceShare -> Maybe Text
statusMessage :: Prelude.Maybe Prelude.Text,
    -- | The tag key and value pairs attached to the resource share.
    ResourceShare -> Maybe [Tag]
tags :: Prelude.Maybe [Tag]
  }
  deriving (ResourceShare -> ResourceShare -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResourceShare -> ResourceShare -> Bool
$c/= :: ResourceShare -> ResourceShare -> Bool
== :: ResourceShare -> ResourceShare -> Bool
$c== :: ResourceShare -> ResourceShare -> Bool
Prelude.Eq, ReadPrec [ResourceShare]
ReadPrec ResourceShare
Int -> ReadS ResourceShare
ReadS [ResourceShare]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResourceShare]
$creadListPrec :: ReadPrec [ResourceShare]
readPrec :: ReadPrec ResourceShare
$creadPrec :: ReadPrec ResourceShare
readList :: ReadS [ResourceShare]
$creadList :: ReadS [ResourceShare]
readsPrec :: Int -> ReadS ResourceShare
$creadsPrec :: Int -> ReadS ResourceShare
Prelude.Read, Int -> ResourceShare -> ShowS
[ResourceShare] -> ShowS
ResourceShare -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResourceShare] -> ShowS
$cshowList :: [ResourceShare] -> ShowS
show :: ResourceShare -> String
$cshow :: ResourceShare -> String
showsPrec :: Int -> ResourceShare -> ShowS
$cshowsPrec :: Int -> ResourceShare -> ShowS
Prelude.Show, forall x. Rep ResourceShare x -> ResourceShare
forall x. ResourceShare -> Rep ResourceShare x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResourceShare x -> ResourceShare
$cfrom :: forall x. ResourceShare -> Rep ResourceShare x
Prelude.Generic)

-- |
-- Create a value of 'ResourceShare' 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:
--
-- 'allowExternalPrincipals', 'resourceShare_allowExternalPrincipals' - Indicates whether principals outside your organization in Organizations
-- can be associated with a resource share.
--
-- 'creationTime', 'resourceShare_creationTime' - The date and time when the resource share was created.
--
-- 'featureSet', 'resourceShare_featureSet' - Indicates how the resource share was created. Possible values include:
--
-- -   @CREATED_FROM_POLICY@ - Indicates that the resource share was
--     created from an Identity and Access Management (IAM) resource-based
--     permission policy attached to the resource. This type of resource
--     share is visible only to the Amazon Web Services account that
--     created it. You can\'t modify it in RAM unless you promote it. For
--     more information, see PromoteResourceShareCreatedFromPolicy.
--
-- -   @PROMOTING_TO_STANDARD@ - The resource share is in the process of
--     being promoted. For more information, see
--     PromoteResourceShareCreatedFromPolicy.
--
-- -   @STANDARD@ - Indicates that the resource share was created in RAM
--     using the console or APIs. These resource shares are visible to all
--     principals you share the resource share with. You can modify these
--     resource shares in RAM using the console or APIs.
--
-- 'lastUpdatedTime', 'resourceShare_lastUpdatedTime' - The date and time when the resource share was last updated.
--
-- 'name', 'resourceShare_name' - The name of the resource share.
--
-- 'owningAccountId', 'resourceShare_owningAccountId' - The ID of the Amazon Web Services account that owns the resource share.
--
-- 'resourceShareArn', 'resourceShare_resourceShareArn' - The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the resource share
--
-- 'status', 'resourceShare_status' - The current status of the resource share.
--
-- 'statusMessage', 'resourceShare_statusMessage' - A message about the status of the resource share.
--
-- 'tags', 'resourceShare_tags' - The tag key and value pairs attached to the resource share.
newResourceShare ::
  ResourceShare
newResourceShare :: ResourceShare
newResourceShare =
  ResourceShare'
    { $sel:allowExternalPrincipals:ResourceShare' :: Maybe Bool
allowExternalPrincipals =
        forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:ResourceShare' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:featureSet:ResourceShare' :: Maybe ResourceShareFeatureSet
featureSet = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedTime:ResourceShare' :: Maybe POSIX
lastUpdatedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:name:ResourceShare' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:owningAccountId:ResourceShare' :: Maybe Text
owningAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShareArn:ResourceShare' :: Maybe Text
resourceShareArn = forall a. Maybe a
Prelude.Nothing,
      $sel:status:ResourceShare' :: Maybe ResourceShareStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:statusMessage:ResourceShare' :: Maybe Text
statusMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:ResourceShare' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing
    }

-- | Indicates whether principals outside your organization in Organizations
-- can be associated with a resource share.
resourceShare_allowExternalPrincipals :: Lens.Lens' ResourceShare (Prelude.Maybe Prelude.Bool)
resourceShare_allowExternalPrincipals :: Lens' ResourceShare (Maybe Bool)
resourceShare_allowExternalPrincipals = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceShare' {Maybe Bool
allowExternalPrincipals :: Maybe Bool
$sel:allowExternalPrincipals:ResourceShare' :: ResourceShare -> Maybe Bool
allowExternalPrincipals} -> Maybe Bool
allowExternalPrincipals) (\s :: ResourceShare
s@ResourceShare' {} Maybe Bool
a -> ResourceShare
s {$sel:allowExternalPrincipals:ResourceShare' :: Maybe Bool
allowExternalPrincipals = Maybe Bool
a} :: ResourceShare)

-- | The date and time when the resource share was created.
resourceShare_creationTime :: Lens.Lens' ResourceShare (Prelude.Maybe Prelude.UTCTime)
resourceShare_creationTime :: Lens' ResourceShare (Maybe UTCTime)
resourceShare_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceShare' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:ResourceShare' :: ResourceShare -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: ResourceShare
s@ResourceShare' {} Maybe POSIX
a -> ResourceShare
s {$sel:creationTime:ResourceShare' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: ResourceShare) 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

-- | Indicates how the resource share was created. Possible values include:
--
-- -   @CREATED_FROM_POLICY@ - Indicates that the resource share was
--     created from an Identity and Access Management (IAM) resource-based
--     permission policy attached to the resource. This type of resource
--     share is visible only to the Amazon Web Services account that
--     created it. You can\'t modify it in RAM unless you promote it. For
--     more information, see PromoteResourceShareCreatedFromPolicy.
--
-- -   @PROMOTING_TO_STANDARD@ - The resource share is in the process of
--     being promoted. For more information, see
--     PromoteResourceShareCreatedFromPolicy.
--
-- -   @STANDARD@ - Indicates that the resource share was created in RAM
--     using the console or APIs. These resource shares are visible to all
--     principals you share the resource share with. You can modify these
--     resource shares in RAM using the console or APIs.
resourceShare_featureSet :: Lens.Lens' ResourceShare (Prelude.Maybe ResourceShareFeatureSet)
resourceShare_featureSet :: Lens' ResourceShare (Maybe ResourceShareFeatureSet)
resourceShare_featureSet = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceShare' {Maybe ResourceShareFeatureSet
featureSet :: Maybe ResourceShareFeatureSet
$sel:featureSet:ResourceShare' :: ResourceShare -> Maybe ResourceShareFeatureSet
featureSet} -> Maybe ResourceShareFeatureSet
featureSet) (\s :: ResourceShare
s@ResourceShare' {} Maybe ResourceShareFeatureSet
a -> ResourceShare
s {$sel:featureSet:ResourceShare' :: Maybe ResourceShareFeatureSet
featureSet = Maybe ResourceShareFeatureSet
a} :: ResourceShare)

-- | The date and time when the resource share was last updated.
resourceShare_lastUpdatedTime :: Lens.Lens' ResourceShare (Prelude.Maybe Prelude.UTCTime)
resourceShare_lastUpdatedTime :: Lens' ResourceShare (Maybe UTCTime)
resourceShare_lastUpdatedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceShare' {Maybe POSIX
lastUpdatedTime :: Maybe POSIX
$sel:lastUpdatedTime:ResourceShare' :: ResourceShare -> Maybe POSIX
lastUpdatedTime} -> Maybe POSIX
lastUpdatedTime) (\s :: ResourceShare
s@ResourceShare' {} Maybe POSIX
a -> ResourceShare
s {$sel:lastUpdatedTime:ResourceShare' :: Maybe POSIX
lastUpdatedTime = Maybe POSIX
a} :: ResourceShare) 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 name of the resource share.
resourceShare_name :: Lens.Lens' ResourceShare (Prelude.Maybe Prelude.Text)
resourceShare_name :: Lens' ResourceShare (Maybe Text)
resourceShare_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceShare' {Maybe Text
name :: Maybe Text
$sel:name:ResourceShare' :: ResourceShare -> Maybe Text
name} -> Maybe Text
name) (\s :: ResourceShare
s@ResourceShare' {} Maybe Text
a -> ResourceShare
s {$sel:name:ResourceShare' :: Maybe Text
name = Maybe Text
a} :: ResourceShare)

-- | The ID of the Amazon Web Services account that owns the resource share.
resourceShare_owningAccountId :: Lens.Lens' ResourceShare (Prelude.Maybe Prelude.Text)
resourceShare_owningAccountId :: Lens' ResourceShare (Maybe Text)
resourceShare_owningAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceShare' {Maybe Text
owningAccountId :: Maybe Text
$sel:owningAccountId:ResourceShare' :: ResourceShare -> Maybe Text
owningAccountId} -> Maybe Text
owningAccountId) (\s :: ResourceShare
s@ResourceShare' {} Maybe Text
a -> ResourceShare
s {$sel:owningAccountId:ResourceShare' :: Maybe Text
owningAccountId = Maybe Text
a} :: ResourceShare)

-- | The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the resource share
resourceShare_resourceShareArn :: Lens.Lens' ResourceShare (Prelude.Maybe Prelude.Text)
resourceShare_resourceShareArn :: Lens' ResourceShare (Maybe Text)
resourceShare_resourceShareArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceShare' {Maybe Text
resourceShareArn :: Maybe Text
$sel:resourceShareArn:ResourceShare' :: ResourceShare -> Maybe Text
resourceShareArn} -> Maybe Text
resourceShareArn) (\s :: ResourceShare
s@ResourceShare' {} Maybe Text
a -> ResourceShare
s {$sel:resourceShareArn:ResourceShare' :: Maybe Text
resourceShareArn = Maybe Text
a} :: ResourceShare)

-- | The current status of the resource share.
resourceShare_status :: Lens.Lens' ResourceShare (Prelude.Maybe ResourceShareStatus)
resourceShare_status :: Lens' ResourceShare (Maybe ResourceShareStatus)
resourceShare_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceShare' {Maybe ResourceShareStatus
status :: Maybe ResourceShareStatus
$sel:status:ResourceShare' :: ResourceShare -> Maybe ResourceShareStatus
status} -> Maybe ResourceShareStatus
status) (\s :: ResourceShare
s@ResourceShare' {} Maybe ResourceShareStatus
a -> ResourceShare
s {$sel:status:ResourceShare' :: Maybe ResourceShareStatus
status = Maybe ResourceShareStatus
a} :: ResourceShare)

-- | A message about the status of the resource share.
resourceShare_statusMessage :: Lens.Lens' ResourceShare (Prelude.Maybe Prelude.Text)
resourceShare_statusMessage :: Lens' ResourceShare (Maybe Text)
resourceShare_statusMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceShare' {Maybe Text
statusMessage :: Maybe Text
$sel:statusMessage:ResourceShare' :: ResourceShare -> Maybe Text
statusMessage} -> Maybe Text
statusMessage) (\s :: ResourceShare
s@ResourceShare' {} Maybe Text
a -> ResourceShare
s {$sel:statusMessage:ResourceShare' :: Maybe Text
statusMessage = Maybe Text
a} :: ResourceShare)

-- | The tag key and value pairs attached to the resource share.
resourceShare_tags :: Lens.Lens' ResourceShare (Prelude.Maybe [Tag])
resourceShare_tags :: Lens' ResourceShare (Maybe [Tag])
resourceShare_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResourceShare' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:ResourceShare' :: ResourceShare -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: ResourceShare
s@ResourceShare' {} Maybe [Tag]
a -> ResourceShare
s {$sel:tags:ResourceShare' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: ResourceShare) 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

instance Data.FromJSON ResourceShare where
  parseJSON :: Value -> Parser ResourceShare
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ResourceShare"
      ( \Object
x ->
          Maybe Bool
-> Maybe POSIX
-> Maybe ResourceShareFeatureSet
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ResourceShareStatus
-> Maybe Text
-> Maybe [Tag]
-> ResourceShare
ResourceShare'
            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
"allowExternalPrincipals")
            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
"creationTime")
            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
"featureSet")
            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
"lastUpdatedTime")
            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
"name")
            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
"owningAccountId")
            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
"resourceShareArn")
            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
"statusMessage")
            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
"tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable ResourceShare where
  hashWithSalt :: Int -> ResourceShare -> Int
hashWithSalt Int
_salt ResourceShare' {Maybe Bool
Maybe [Tag]
Maybe Text
Maybe POSIX
Maybe ResourceShareFeatureSet
Maybe ResourceShareStatus
tags :: Maybe [Tag]
statusMessage :: Maybe Text
status :: Maybe ResourceShareStatus
resourceShareArn :: Maybe Text
owningAccountId :: Maybe Text
name :: Maybe Text
lastUpdatedTime :: Maybe POSIX
featureSet :: Maybe ResourceShareFeatureSet
creationTime :: Maybe POSIX
allowExternalPrincipals :: Maybe Bool
$sel:tags:ResourceShare' :: ResourceShare -> Maybe [Tag]
$sel:statusMessage:ResourceShare' :: ResourceShare -> Maybe Text
$sel:status:ResourceShare' :: ResourceShare -> Maybe ResourceShareStatus
$sel:resourceShareArn:ResourceShare' :: ResourceShare -> Maybe Text
$sel:owningAccountId:ResourceShare' :: ResourceShare -> Maybe Text
$sel:name:ResourceShare' :: ResourceShare -> Maybe Text
$sel:lastUpdatedTime:ResourceShare' :: ResourceShare -> Maybe POSIX
$sel:featureSet:ResourceShare' :: ResourceShare -> Maybe ResourceShareFeatureSet
$sel:creationTime:ResourceShare' :: ResourceShare -> Maybe POSIX
$sel:allowExternalPrincipals:ResourceShare' :: ResourceShare -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
allowExternalPrincipals
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResourceShareFeatureSet
featureSet
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastUpdatedTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
owningAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceShareArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResourceShareStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
statusMessage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags

instance Prelude.NFData ResourceShare where
  rnf :: ResourceShare -> ()
rnf ResourceShare' {Maybe Bool
Maybe [Tag]
Maybe Text
Maybe POSIX
Maybe ResourceShareFeatureSet
Maybe ResourceShareStatus
tags :: Maybe [Tag]
statusMessage :: Maybe Text
status :: Maybe ResourceShareStatus
resourceShareArn :: Maybe Text
owningAccountId :: Maybe Text
name :: Maybe Text
lastUpdatedTime :: Maybe POSIX
featureSet :: Maybe ResourceShareFeatureSet
creationTime :: Maybe POSIX
allowExternalPrincipals :: Maybe Bool
$sel:tags:ResourceShare' :: ResourceShare -> Maybe [Tag]
$sel:statusMessage:ResourceShare' :: ResourceShare -> Maybe Text
$sel:status:ResourceShare' :: ResourceShare -> Maybe ResourceShareStatus
$sel:resourceShareArn:ResourceShare' :: ResourceShare -> Maybe Text
$sel:owningAccountId:ResourceShare' :: ResourceShare -> Maybe Text
$sel:name:ResourceShare' :: ResourceShare -> Maybe Text
$sel:lastUpdatedTime:ResourceShare' :: ResourceShare -> Maybe POSIX
$sel:featureSet:ResourceShare' :: ResourceShare -> Maybe ResourceShareFeatureSet
$sel:creationTime:ResourceShare' :: ResourceShare -> Maybe POSIX
$sel:allowExternalPrincipals:ResourceShare' :: ResourceShare -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
allowExternalPrincipals
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceShareFeatureSet
featureSet
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
owningAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceShareArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceShareStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
statusMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags