{-# 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.DataExchange.Types.AssetDetails
-- 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.DataExchange.Types.AssetDetails where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DataExchange.Types.ApiGatewayApiAsset
import Amazonka.DataExchange.Types.LakeFormationDataPermissionAsset
import Amazonka.DataExchange.Types.RedshiftDataShareAsset
import Amazonka.DataExchange.Types.S3DataAccessAsset
import Amazonka.DataExchange.Types.S3SnapshotAsset
import qualified Amazonka.Prelude as Prelude

-- | Details about the asset.
--
-- /See:/ 'newAssetDetails' smart constructor.
data AssetDetails = AssetDetails'
  { -- | Information about the API Gateway API asset.
    AssetDetails -> Maybe ApiGatewayApiAsset
apiGatewayApiAsset :: Prelude.Maybe ApiGatewayApiAsset,
    -- | The AWS Lake Formation data permission that is the asset.
    AssetDetails -> Maybe LakeFormationDataPermissionAsset
lakeFormationDataPermissionAsset :: Prelude.Maybe LakeFormationDataPermissionAsset,
    -- | The Amazon Redshift datashare that is the asset.
    AssetDetails -> Maybe RedshiftDataShareAsset
redshiftDataShareAsset :: Prelude.Maybe RedshiftDataShareAsset,
    -- | The Amazon S3 data access that is the asset.
    AssetDetails -> Maybe S3DataAccessAsset
s3DataAccessAsset :: Prelude.Maybe S3DataAccessAsset,
    -- | The Amazon S3 object that is the asset.
    AssetDetails -> Maybe S3SnapshotAsset
s3SnapshotAsset :: Prelude.Maybe S3SnapshotAsset
  }
  deriving (AssetDetails -> AssetDetails -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssetDetails -> AssetDetails -> Bool
$c/= :: AssetDetails -> AssetDetails -> Bool
== :: AssetDetails -> AssetDetails -> Bool
$c== :: AssetDetails -> AssetDetails -> Bool
Prelude.Eq, ReadPrec [AssetDetails]
ReadPrec AssetDetails
Int -> ReadS AssetDetails
ReadS [AssetDetails]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssetDetails]
$creadListPrec :: ReadPrec [AssetDetails]
readPrec :: ReadPrec AssetDetails
$creadPrec :: ReadPrec AssetDetails
readList :: ReadS [AssetDetails]
$creadList :: ReadS [AssetDetails]
readsPrec :: Int -> ReadS AssetDetails
$creadsPrec :: Int -> ReadS AssetDetails
Prelude.Read, Int -> AssetDetails -> ShowS
[AssetDetails] -> ShowS
AssetDetails -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssetDetails] -> ShowS
$cshowList :: [AssetDetails] -> ShowS
show :: AssetDetails -> String
$cshow :: AssetDetails -> String
showsPrec :: Int -> AssetDetails -> ShowS
$cshowsPrec :: Int -> AssetDetails -> ShowS
Prelude.Show, forall x. Rep AssetDetails x -> AssetDetails
forall x. AssetDetails -> Rep AssetDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssetDetails x -> AssetDetails
$cfrom :: forall x. AssetDetails -> Rep AssetDetails x
Prelude.Generic)

-- |
-- Create a value of 'AssetDetails' 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:
--
-- 'apiGatewayApiAsset', 'assetDetails_apiGatewayApiAsset' - Information about the API Gateway API asset.
--
-- 'lakeFormationDataPermissionAsset', 'assetDetails_lakeFormationDataPermissionAsset' - The AWS Lake Formation data permission that is the asset.
--
-- 'redshiftDataShareAsset', 'assetDetails_redshiftDataShareAsset' - The Amazon Redshift datashare that is the asset.
--
-- 's3DataAccessAsset', 'assetDetails_s3DataAccessAsset' - The Amazon S3 data access that is the asset.
--
-- 's3SnapshotAsset', 'assetDetails_s3SnapshotAsset' - The Amazon S3 object that is the asset.
newAssetDetails ::
  AssetDetails
newAssetDetails :: AssetDetails
newAssetDetails =
  AssetDetails'
    { $sel:apiGatewayApiAsset:AssetDetails' :: Maybe ApiGatewayApiAsset
apiGatewayApiAsset = forall a. Maybe a
Prelude.Nothing,
      $sel:lakeFormationDataPermissionAsset:AssetDetails' :: Maybe LakeFormationDataPermissionAsset
lakeFormationDataPermissionAsset = forall a. Maybe a
Prelude.Nothing,
      $sel:redshiftDataShareAsset:AssetDetails' :: Maybe RedshiftDataShareAsset
redshiftDataShareAsset = forall a. Maybe a
Prelude.Nothing,
      $sel:s3DataAccessAsset:AssetDetails' :: Maybe S3DataAccessAsset
s3DataAccessAsset = forall a. Maybe a
Prelude.Nothing,
      $sel:s3SnapshotAsset:AssetDetails' :: Maybe S3SnapshotAsset
s3SnapshotAsset = forall a. Maybe a
Prelude.Nothing
    }

-- | Information about the API Gateway API asset.
assetDetails_apiGatewayApiAsset :: Lens.Lens' AssetDetails (Prelude.Maybe ApiGatewayApiAsset)
assetDetails_apiGatewayApiAsset :: Lens' AssetDetails (Maybe ApiGatewayApiAsset)
assetDetails_apiGatewayApiAsset = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssetDetails' {Maybe ApiGatewayApiAsset
apiGatewayApiAsset :: Maybe ApiGatewayApiAsset
$sel:apiGatewayApiAsset:AssetDetails' :: AssetDetails -> Maybe ApiGatewayApiAsset
apiGatewayApiAsset} -> Maybe ApiGatewayApiAsset
apiGatewayApiAsset) (\s :: AssetDetails
s@AssetDetails' {} Maybe ApiGatewayApiAsset
a -> AssetDetails
s {$sel:apiGatewayApiAsset:AssetDetails' :: Maybe ApiGatewayApiAsset
apiGatewayApiAsset = Maybe ApiGatewayApiAsset
a} :: AssetDetails)

-- | The AWS Lake Formation data permission that is the asset.
assetDetails_lakeFormationDataPermissionAsset :: Lens.Lens' AssetDetails (Prelude.Maybe LakeFormationDataPermissionAsset)
assetDetails_lakeFormationDataPermissionAsset :: Lens' AssetDetails (Maybe LakeFormationDataPermissionAsset)
assetDetails_lakeFormationDataPermissionAsset = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssetDetails' {Maybe LakeFormationDataPermissionAsset
lakeFormationDataPermissionAsset :: Maybe LakeFormationDataPermissionAsset
$sel:lakeFormationDataPermissionAsset:AssetDetails' :: AssetDetails -> Maybe LakeFormationDataPermissionAsset
lakeFormationDataPermissionAsset} -> Maybe LakeFormationDataPermissionAsset
lakeFormationDataPermissionAsset) (\s :: AssetDetails
s@AssetDetails' {} Maybe LakeFormationDataPermissionAsset
a -> AssetDetails
s {$sel:lakeFormationDataPermissionAsset:AssetDetails' :: Maybe LakeFormationDataPermissionAsset
lakeFormationDataPermissionAsset = Maybe LakeFormationDataPermissionAsset
a} :: AssetDetails)

-- | The Amazon Redshift datashare that is the asset.
assetDetails_redshiftDataShareAsset :: Lens.Lens' AssetDetails (Prelude.Maybe RedshiftDataShareAsset)
assetDetails_redshiftDataShareAsset :: Lens' AssetDetails (Maybe RedshiftDataShareAsset)
assetDetails_redshiftDataShareAsset = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssetDetails' {Maybe RedshiftDataShareAsset
redshiftDataShareAsset :: Maybe RedshiftDataShareAsset
$sel:redshiftDataShareAsset:AssetDetails' :: AssetDetails -> Maybe RedshiftDataShareAsset
redshiftDataShareAsset} -> Maybe RedshiftDataShareAsset
redshiftDataShareAsset) (\s :: AssetDetails
s@AssetDetails' {} Maybe RedshiftDataShareAsset
a -> AssetDetails
s {$sel:redshiftDataShareAsset:AssetDetails' :: Maybe RedshiftDataShareAsset
redshiftDataShareAsset = Maybe RedshiftDataShareAsset
a} :: AssetDetails)

-- | The Amazon S3 data access that is the asset.
assetDetails_s3DataAccessAsset :: Lens.Lens' AssetDetails (Prelude.Maybe S3DataAccessAsset)
assetDetails_s3DataAccessAsset :: Lens' AssetDetails (Maybe S3DataAccessAsset)
assetDetails_s3DataAccessAsset = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssetDetails' {Maybe S3DataAccessAsset
s3DataAccessAsset :: Maybe S3DataAccessAsset
$sel:s3DataAccessAsset:AssetDetails' :: AssetDetails -> Maybe S3DataAccessAsset
s3DataAccessAsset} -> Maybe S3DataAccessAsset
s3DataAccessAsset) (\s :: AssetDetails
s@AssetDetails' {} Maybe S3DataAccessAsset
a -> AssetDetails
s {$sel:s3DataAccessAsset:AssetDetails' :: Maybe S3DataAccessAsset
s3DataAccessAsset = Maybe S3DataAccessAsset
a} :: AssetDetails)

-- | The Amazon S3 object that is the asset.
assetDetails_s3SnapshotAsset :: Lens.Lens' AssetDetails (Prelude.Maybe S3SnapshotAsset)
assetDetails_s3SnapshotAsset :: Lens' AssetDetails (Maybe S3SnapshotAsset)
assetDetails_s3SnapshotAsset = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssetDetails' {Maybe S3SnapshotAsset
s3SnapshotAsset :: Maybe S3SnapshotAsset
$sel:s3SnapshotAsset:AssetDetails' :: AssetDetails -> Maybe S3SnapshotAsset
s3SnapshotAsset} -> Maybe S3SnapshotAsset
s3SnapshotAsset) (\s :: AssetDetails
s@AssetDetails' {} Maybe S3SnapshotAsset
a -> AssetDetails
s {$sel:s3SnapshotAsset:AssetDetails' :: Maybe S3SnapshotAsset
s3SnapshotAsset = Maybe S3SnapshotAsset
a} :: AssetDetails)

instance Data.FromJSON AssetDetails where
  parseJSON :: Value -> Parser AssetDetails
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AssetDetails"
      ( \Object
x ->
          Maybe ApiGatewayApiAsset
-> Maybe LakeFormationDataPermissionAsset
-> Maybe RedshiftDataShareAsset
-> Maybe S3DataAccessAsset
-> Maybe S3SnapshotAsset
-> AssetDetails
AssetDetails'
            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
"ApiGatewayApiAsset")
            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
"LakeFormationDataPermissionAsset")
            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
"RedshiftDataShareAsset")
            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
"S3DataAccessAsset")
            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
"S3SnapshotAsset")
      )

instance Prelude.Hashable AssetDetails where
  hashWithSalt :: Int -> AssetDetails -> Int
hashWithSalt Int
_salt AssetDetails' {Maybe ApiGatewayApiAsset
Maybe RedshiftDataShareAsset
Maybe S3DataAccessAsset
Maybe S3SnapshotAsset
Maybe LakeFormationDataPermissionAsset
s3SnapshotAsset :: Maybe S3SnapshotAsset
s3DataAccessAsset :: Maybe S3DataAccessAsset
redshiftDataShareAsset :: Maybe RedshiftDataShareAsset
lakeFormationDataPermissionAsset :: Maybe LakeFormationDataPermissionAsset
apiGatewayApiAsset :: Maybe ApiGatewayApiAsset
$sel:s3SnapshotAsset:AssetDetails' :: AssetDetails -> Maybe S3SnapshotAsset
$sel:s3DataAccessAsset:AssetDetails' :: AssetDetails -> Maybe S3DataAccessAsset
$sel:redshiftDataShareAsset:AssetDetails' :: AssetDetails -> Maybe RedshiftDataShareAsset
$sel:lakeFormationDataPermissionAsset:AssetDetails' :: AssetDetails -> Maybe LakeFormationDataPermissionAsset
$sel:apiGatewayApiAsset:AssetDetails' :: AssetDetails -> Maybe ApiGatewayApiAsset
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ApiGatewayApiAsset
apiGatewayApiAsset
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LakeFormationDataPermissionAsset
lakeFormationDataPermissionAsset
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RedshiftDataShareAsset
redshiftDataShareAsset
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe S3DataAccessAsset
s3DataAccessAsset
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe S3SnapshotAsset
s3SnapshotAsset

instance Prelude.NFData AssetDetails where
  rnf :: AssetDetails -> ()
rnf AssetDetails' {Maybe ApiGatewayApiAsset
Maybe RedshiftDataShareAsset
Maybe S3DataAccessAsset
Maybe S3SnapshotAsset
Maybe LakeFormationDataPermissionAsset
s3SnapshotAsset :: Maybe S3SnapshotAsset
s3DataAccessAsset :: Maybe S3DataAccessAsset
redshiftDataShareAsset :: Maybe RedshiftDataShareAsset
lakeFormationDataPermissionAsset :: Maybe LakeFormationDataPermissionAsset
apiGatewayApiAsset :: Maybe ApiGatewayApiAsset
$sel:s3SnapshotAsset:AssetDetails' :: AssetDetails -> Maybe S3SnapshotAsset
$sel:s3DataAccessAsset:AssetDetails' :: AssetDetails -> Maybe S3DataAccessAsset
$sel:redshiftDataShareAsset:AssetDetails' :: AssetDetails -> Maybe RedshiftDataShareAsset
$sel:lakeFormationDataPermissionAsset:AssetDetails' :: AssetDetails -> Maybe LakeFormationDataPermissionAsset
$sel:apiGatewayApiAsset:AssetDetails' :: AssetDetails -> Maybe ApiGatewayApiAsset
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ApiGatewayApiAsset
apiGatewayApiAsset
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LakeFormationDataPermissionAsset
lakeFormationDataPermissionAsset
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RedshiftDataShareAsset
redshiftDataShareAsset
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe S3DataAccessAsset
s3DataAccessAsset
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe S3SnapshotAsset
s3SnapshotAsset