{-# 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.Pinpoint.Types.SegmentImportResource
-- 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.Pinpoint.Types.SegmentImportResource where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Pinpoint.Types.DefinitionFormat
import qualified Amazonka.Prelude as Prelude

-- | Provides information about the import job that created a segment. An
-- import job is a job that creates a user segment by importing endpoint
-- definitions.
--
-- /See:/ 'newSegmentImportResource' smart constructor.
data SegmentImportResource = SegmentImportResource'
  { -- | The number of channel types in the endpoint definitions that were
    -- imported to create the segment.
    SegmentImportResource -> Maybe (HashMap Text Int)
channelCounts :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Int),
    -- | The format of the files that were imported to create the segment. Valid
    -- values are: CSV, for comma-separated values format; and, JSON, for
    -- newline-delimited JSON format.
    SegmentImportResource -> DefinitionFormat
format :: DefinitionFormat,
    -- | The URL of the Amazon Simple Storage Service (Amazon S3) bucket that the
    -- endpoint definitions were imported from to create the segment.
    SegmentImportResource -> Text
s3Url :: Prelude.Text,
    -- | The number of endpoint definitions that were imported successfully to
    -- create the segment.
    SegmentImportResource -> Int
size :: Prelude.Int,
    -- | (Deprecated) Your AWS account ID, which you assigned to an external ID
    -- key in an IAM trust policy. Amazon Pinpoint previously used this value
    -- to assume an IAM role when importing endpoint definitions, but we
    -- removed this requirement. We don\'t recommend use of external IDs for
    -- IAM roles that are assumed by Amazon Pinpoint.
    SegmentImportResource -> Text
externalId :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the AWS Identity and Access Management
    -- (IAM) role that authorized Amazon Pinpoint to access the Amazon S3
    -- location to import endpoint definitions from.
    SegmentImportResource -> Text
roleArn :: Prelude.Text
  }
  deriving (SegmentImportResource -> SegmentImportResource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SegmentImportResource -> SegmentImportResource -> Bool
$c/= :: SegmentImportResource -> SegmentImportResource -> Bool
== :: SegmentImportResource -> SegmentImportResource -> Bool
$c== :: SegmentImportResource -> SegmentImportResource -> Bool
Prelude.Eq, ReadPrec [SegmentImportResource]
ReadPrec SegmentImportResource
Int -> ReadS SegmentImportResource
ReadS [SegmentImportResource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SegmentImportResource]
$creadListPrec :: ReadPrec [SegmentImportResource]
readPrec :: ReadPrec SegmentImportResource
$creadPrec :: ReadPrec SegmentImportResource
readList :: ReadS [SegmentImportResource]
$creadList :: ReadS [SegmentImportResource]
readsPrec :: Int -> ReadS SegmentImportResource
$creadsPrec :: Int -> ReadS SegmentImportResource
Prelude.Read, Int -> SegmentImportResource -> ShowS
[SegmentImportResource] -> ShowS
SegmentImportResource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SegmentImportResource] -> ShowS
$cshowList :: [SegmentImportResource] -> ShowS
show :: SegmentImportResource -> String
$cshow :: SegmentImportResource -> String
showsPrec :: Int -> SegmentImportResource -> ShowS
$cshowsPrec :: Int -> SegmentImportResource -> ShowS
Prelude.Show, forall x. Rep SegmentImportResource x -> SegmentImportResource
forall x. SegmentImportResource -> Rep SegmentImportResource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SegmentImportResource x -> SegmentImportResource
$cfrom :: forall x. SegmentImportResource -> Rep SegmentImportResource x
Prelude.Generic)

-- |
-- Create a value of 'SegmentImportResource' 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:
--
-- 'channelCounts', 'segmentImportResource_channelCounts' - The number of channel types in the endpoint definitions that were
-- imported to create the segment.
--
-- 'format', 'segmentImportResource_format' - The format of the files that were imported to create the segment. Valid
-- values are: CSV, for comma-separated values format; and, JSON, for
-- newline-delimited JSON format.
--
-- 's3Url', 'segmentImportResource_s3Url' - The URL of the Amazon Simple Storage Service (Amazon S3) bucket that the
-- endpoint definitions were imported from to create the segment.
--
-- 'size', 'segmentImportResource_size' - The number of endpoint definitions that were imported successfully to
-- create the segment.
--
-- 'externalId', 'segmentImportResource_externalId' - (Deprecated) Your AWS account ID, which you assigned to an external ID
-- key in an IAM trust policy. Amazon Pinpoint previously used this value
-- to assume an IAM role when importing endpoint definitions, but we
-- removed this requirement. We don\'t recommend use of external IDs for
-- IAM roles that are assumed by Amazon Pinpoint.
--
-- 'roleArn', 'segmentImportResource_roleArn' - The Amazon Resource Name (ARN) of the AWS Identity and Access Management
-- (IAM) role that authorized Amazon Pinpoint to access the Amazon S3
-- location to import endpoint definitions from.
newSegmentImportResource ::
  -- | 'format'
  DefinitionFormat ->
  -- | 's3Url'
  Prelude.Text ->
  -- | 'size'
  Prelude.Int ->
  -- | 'externalId'
  Prelude.Text ->
  -- | 'roleArn'
  Prelude.Text ->
  SegmentImportResource
newSegmentImportResource :: DefinitionFormat
-> Text -> Int -> Text -> Text -> SegmentImportResource
newSegmentImportResource
  DefinitionFormat
pFormat_
  Text
pS3Url_
  Int
pSize_
  Text
pExternalId_
  Text
pRoleArn_ =
    SegmentImportResource'
      { $sel:channelCounts:SegmentImportResource' :: Maybe (HashMap Text Int)
channelCounts =
          forall a. Maybe a
Prelude.Nothing,
        $sel:format:SegmentImportResource' :: DefinitionFormat
format = DefinitionFormat
pFormat_,
        $sel:s3Url:SegmentImportResource' :: Text
s3Url = Text
pS3Url_,
        $sel:size:SegmentImportResource' :: Int
size = Int
pSize_,
        $sel:externalId:SegmentImportResource' :: Text
externalId = Text
pExternalId_,
        $sel:roleArn:SegmentImportResource' :: Text
roleArn = Text
pRoleArn_
      }

-- | The number of channel types in the endpoint definitions that were
-- imported to create the segment.
segmentImportResource_channelCounts :: Lens.Lens' SegmentImportResource (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Int))
segmentImportResource_channelCounts :: Lens' SegmentImportResource (Maybe (HashMap Text Int))
segmentImportResource_channelCounts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SegmentImportResource' {Maybe (HashMap Text Int)
channelCounts :: Maybe (HashMap Text Int)
$sel:channelCounts:SegmentImportResource' :: SegmentImportResource -> Maybe (HashMap Text Int)
channelCounts} -> Maybe (HashMap Text Int)
channelCounts) (\s :: SegmentImportResource
s@SegmentImportResource' {} Maybe (HashMap Text Int)
a -> SegmentImportResource
s {$sel:channelCounts:SegmentImportResource' :: Maybe (HashMap Text Int)
channelCounts = Maybe (HashMap Text Int)
a} :: SegmentImportResource) 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 format of the files that were imported to create the segment. Valid
-- values are: CSV, for comma-separated values format; and, JSON, for
-- newline-delimited JSON format.
segmentImportResource_format :: Lens.Lens' SegmentImportResource DefinitionFormat
segmentImportResource_format :: Lens' SegmentImportResource DefinitionFormat
segmentImportResource_format = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SegmentImportResource' {DefinitionFormat
format :: DefinitionFormat
$sel:format:SegmentImportResource' :: SegmentImportResource -> DefinitionFormat
format} -> DefinitionFormat
format) (\s :: SegmentImportResource
s@SegmentImportResource' {} DefinitionFormat
a -> SegmentImportResource
s {$sel:format:SegmentImportResource' :: DefinitionFormat
format = DefinitionFormat
a} :: SegmentImportResource)

-- | The URL of the Amazon Simple Storage Service (Amazon S3) bucket that the
-- endpoint definitions were imported from to create the segment.
segmentImportResource_s3Url :: Lens.Lens' SegmentImportResource Prelude.Text
segmentImportResource_s3Url :: Lens' SegmentImportResource Text
segmentImportResource_s3Url = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SegmentImportResource' {Text
s3Url :: Text
$sel:s3Url:SegmentImportResource' :: SegmentImportResource -> Text
s3Url} -> Text
s3Url) (\s :: SegmentImportResource
s@SegmentImportResource' {} Text
a -> SegmentImportResource
s {$sel:s3Url:SegmentImportResource' :: Text
s3Url = Text
a} :: SegmentImportResource)

-- | The number of endpoint definitions that were imported successfully to
-- create the segment.
segmentImportResource_size :: Lens.Lens' SegmentImportResource Prelude.Int
segmentImportResource_size :: Lens' SegmentImportResource Int
segmentImportResource_size = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SegmentImportResource' {Int
size :: Int
$sel:size:SegmentImportResource' :: SegmentImportResource -> Int
size} -> Int
size) (\s :: SegmentImportResource
s@SegmentImportResource' {} Int
a -> SegmentImportResource
s {$sel:size:SegmentImportResource' :: Int
size = Int
a} :: SegmentImportResource)

-- | (Deprecated) Your AWS account ID, which you assigned to an external ID
-- key in an IAM trust policy. Amazon Pinpoint previously used this value
-- to assume an IAM role when importing endpoint definitions, but we
-- removed this requirement. We don\'t recommend use of external IDs for
-- IAM roles that are assumed by Amazon Pinpoint.
segmentImportResource_externalId :: Lens.Lens' SegmentImportResource Prelude.Text
segmentImportResource_externalId :: Lens' SegmentImportResource Text
segmentImportResource_externalId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SegmentImportResource' {Text
externalId :: Text
$sel:externalId:SegmentImportResource' :: SegmentImportResource -> Text
externalId} -> Text
externalId) (\s :: SegmentImportResource
s@SegmentImportResource' {} Text
a -> SegmentImportResource
s {$sel:externalId:SegmentImportResource' :: Text
externalId = Text
a} :: SegmentImportResource)

-- | The Amazon Resource Name (ARN) of the AWS Identity and Access Management
-- (IAM) role that authorized Amazon Pinpoint to access the Amazon S3
-- location to import endpoint definitions from.
segmentImportResource_roleArn :: Lens.Lens' SegmentImportResource Prelude.Text
segmentImportResource_roleArn :: Lens' SegmentImportResource Text
segmentImportResource_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SegmentImportResource' {Text
roleArn :: Text
$sel:roleArn:SegmentImportResource' :: SegmentImportResource -> Text
roleArn} -> Text
roleArn) (\s :: SegmentImportResource
s@SegmentImportResource' {} Text
a -> SegmentImportResource
s {$sel:roleArn:SegmentImportResource' :: Text
roleArn = Text
a} :: SegmentImportResource)

instance Data.FromJSON SegmentImportResource where
  parseJSON :: Value -> Parser SegmentImportResource
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"SegmentImportResource"
      ( \Object
x ->
          Maybe (HashMap Text Int)
-> DefinitionFormat
-> Text
-> Int
-> Text
-> Text
-> SegmentImportResource
SegmentImportResource'
            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
"ChannelCounts" 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 a
Data..: Key
"Format")
            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
"S3Url")
            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
"Size")
            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
"ExternalId")
            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")
      )

instance Prelude.Hashable SegmentImportResource where
  hashWithSalt :: Int -> SegmentImportResource -> Int
hashWithSalt Int
_salt SegmentImportResource' {Int
Maybe (HashMap Text Int)
Text
DefinitionFormat
roleArn :: Text
externalId :: Text
size :: Int
s3Url :: Text
format :: DefinitionFormat
channelCounts :: Maybe (HashMap Text Int)
$sel:roleArn:SegmentImportResource' :: SegmentImportResource -> Text
$sel:externalId:SegmentImportResource' :: SegmentImportResource -> Text
$sel:size:SegmentImportResource' :: SegmentImportResource -> Int
$sel:s3Url:SegmentImportResource' :: SegmentImportResource -> Text
$sel:format:SegmentImportResource' :: SegmentImportResource -> DefinitionFormat
$sel:channelCounts:SegmentImportResource' :: SegmentImportResource -> Maybe (HashMap Text Int)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Int)
channelCounts
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` DefinitionFormat
format
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
s3Url
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
size
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
externalId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleArn

instance Prelude.NFData SegmentImportResource where
  rnf :: SegmentImportResource -> ()
rnf SegmentImportResource' {Int
Maybe (HashMap Text Int)
Text
DefinitionFormat
roleArn :: Text
externalId :: Text
size :: Int
s3Url :: Text
format :: DefinitionFormat
channelCounts :: Maybe (HashMap Text Int)
$sel:roleArn:SegmentImportResource' :: SegmentImportResource -> Text
$sel:externalId:SegmentImportResource' :: SegmentImportResource -> Text
$sel:size:SegmentImportResource' :: SegmentImportResource -> Int
$sel:s3Url:SegmentImportResource' :: SegmentImportResource -> Text
$sel:format:SegmentImportResource' :: SegmentImportResource -> DefinitionFormat
$sel:channelCounts:SegmentImportResource' :: SegmentImportResource -> Maybe (HashMap Text Int)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Int)
channelCounts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DefinitionFormat
format
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
s3Url
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
size
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
externalId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn