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

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

-- |
-- Module      : Amazonka.CloudTrail.StartImport
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts an import of logged trail events from a source S3 bucket to a
-- destination event data store. By default, CloudTrail only imports events
-- contained in the S3 bucket\'s @CloudTrail@ prefix and the prefixes
-- inside the @CloudTrail@ prefix, and does not check prefixes for other
-- Amazon Web Services services. If you want to import CloudTrail events
-- contained in another prefix, you must include the prefix in the
-- @S3LocationUri@. For more considerations about importing trail events,
-- see
-- <https://docs.aws.amazon.com/awscloudtrail/latest/userguide/cloudtrail-copy-trail-to-lake.html#cloudtrail-trail-copy-considerations Considerations>.
--
-- When you start a new import, the @Destinations@ and @ImportSource@
-- parameters are required. Before starting a new import, disable any
-- access control lists (ACLs) attached to the source S3 bucket. For more
-- information about disabling ACLs, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/about-object-ownership.html Controlling ownership of objects and disabling ACLs for your bucket>.
--
-- When you retry an import, the @ImportID@ parameter is required.
module Amazonka.CloudTrail.StartImport
  ( -- * Creating a Request
    StartImport (..),
    newStartImport,

    -- * Request Lenses
    startImport_destinations,
    startImport_endEventTime,
    startImport_importId,
    startImport_importSource,
    startImport_startEventTime,

    -- * Destructuring the Response
    StartImportResponse (..),
    newStartImportResponse,

    -- * Response Lenses
    startImportResponse_createdTimestamp,
    startImportResponse_destinations,
    startImportResponse_endEventTime,
    startImportResponse_importId,
    startImportResponse_importSource,
    startImportResponse_importStatus,
    startImportResponse_startEventTime,
    startImportResponse_updatedTimestamp,
    startImportResponse_httpStatus,
  )
where

import Amazonka.CloudTrail.Types
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newStartImport' smart constructor.
data StartImport = StartImport'
  { -- | The ARN of the destination event data store. Use this parameter for a
    -- new import.
    StartImport -> Maybe (NonEmpty Text)
destinations :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | Use with @StartEventTime@ to bound a @StartImport@ request, and limit
    -- imported trail events to only those events logged within a specified
    -- time period. When you specify a time range, CloudTrail checks the prefix
    -- and log file names to verify the names contain a date between the
    -- specified @StartEventTime@ and @EndEventTime@ before attempting to
    -- import events.
    StartImport -> Maybe POSIX
endEventTime :: Prelude.Maybe Data.POSIX,
    -- | The ID of the import. Use this parameter when you are retrying an
    -- import.
    StartImport -> Maybe Text
importId :: Prelude.Maybe Prelude.Text,
    -- | The source S3 bucket for the import. Use this parameter for a new
    -- import.
    StartImport -> Maybe ImportSource
importSource :: Prelude.Maybe ImportSource,
    -- | Use with @EndEventTime@ to bound a @StartImport@ request, and limit
    -- imported trail events to only those events logged within a specified
    -- time period. When you specify a time range, CloudTrail checks the prefix
    -- and log file names to verify the names contain a date between the
    -- specified @StartEventTime@ and @EndEventTime@ before attempting to
    -- import events.
    StartImport -> Maybe POSIX
startEventTime :: Prelude.Maybe Data.POSIX
  }
  deriving (StartImport -> StartImport -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartImport -> StartImport -> Bool
$c/= :: StartImport -> StartImport -> Bool
== :: StartImport -> StartImport -> Bool
$c== :: StartImport -> StartImport -> Bool
Prelude.Eq, ReadPrec [StartImport]
ReadPrec StartImport
Int -> ReadS StartImport
ReadS [StartImport]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartImport]
$creadListPrec :: ReadPrec [StartImport]
readPrec :: ReadPrec StartImport
$creadPrec :: ReadPrec StartImport
readList :: ReadS [StartImport]
$creadList :: ReadS [StartImport]
readsPrec :: Int -> ReadS StartImport
$creadsPrec :: Int -> ReadS StartImport
Prelude.Read, Int -> StartImport -> ShowS
[StartImport] -> ShowS
StartImport -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartImport] -> ShowS
$cshowList :: [StartImport] -> ShowS
show :: StartImport -> String
$cshow :: StartImport -> String
showsPrec :: Int -> StartImport -> ShowS
$cshowsPrec :: Int -> StartImport -> ShowS
Prelude.Show, forall x. Rep StartImport x -> StartImport
forall x. StartImport -> Rep StartImport x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartImport x -> StartImport
$cfrom :: forall x. StartImport -> Rep StartImport x
Prelude.Generic)

-- |
-- Create a value of 'StartImport' 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:
--
-- 'destinations', 'startImport_destinations' - The ARN of the destination event data store. Use this parameter for a
-- new import.
--
-- 'endEventTime', 'startImport_endEventTime' - Use with @StartEventTime@ to bound a @StartImport@ request, and limit
-- imported trail events to only those events logged within a specified
-- time period. When you specify a time range, CloudTrail checks the prefix
-- and log file names to verify the names contain a date between the
-- specified @StartEventTime@ and @EndEventTime@ before attempting to
-- import events.
--
-- 'importId', 'startImport_importId' - The ID of the import. Use this parameter when you are retrying an
-- import.
--
-- 'importSource', 'startImport_importSource' - The source S3 bucket for the import. Use this parameter for a new
-- import.
--
-- 'startEventTime', 'startImport_startEventTime' - Use with @EndEventTime@ to bound a @StartImport@ request, and limit
-- imported trail events to only those events logged within a specified
-- time period. When you specify a time range, CloudTrail checks the prefix
-- and log file names to verify the names contain a date between the
-- specified @StartEventTime@ and @EndEventTime@ before attempting to
-- import events.
newStartImport ::
  StartImport
newStartImport :: StartImport
newStartImport =
  StartImport'
    { $sel:destinations:StartImport' :: Maybe (NonEmpty Text)
destinations = forall a. Maybe a
Prelude.Nothing,
      $sel:endEventTime:StartImport' :: Maybe POSIX
endEventTime = forall a. Maybe a
Prelude.Nothing,
      $sel:importId:StartImport' :: Maybe Text
importId = forall a. Maybe a
Prelude.Nothing,
      $sel:importSource:StartImport' :: Maybe ImportSource
importSource = forall a. Maybe a
Prelude.Nothing,
      $sel:startEventTime:StartImport' :: Maybe POSIX
startEventTime = forall a. Maybe a
Prelude.Nothing
    }

-- | The ARN of the destination event data store. Use this parameter for a
-- new import.
startImport_destinations :: Lens.Lens' StartImport (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
startImport_destinations :: Lens' StartImport (Maybe (NonEmpty Text))
startImport_destinations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImport' {Maybe (NonEmpty Text)
destinations :: Maybe (NonEmpty Text)
$sel:destinations:StartImport' :: StartImport -> Maybe (NonEmpty Text)
destinations} -> Maybe (NonEmpty Text)
destinations) (\s :: StartImport
s@StartImport' {} Maybe (NonEmpty Text)
a -> StartImport
s {$sel:destinations:StartImport' :: Maybe (NonEmpty Text)
destinations = Maybe (NonEmpty Text)
a} :: StartImport) 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

-- | Use with @StartEventTime@ to bound a @StartImport@ request, and limit
-- imported trail events to only those events logged within a specified
-- time period. When you specify a time range, CloudTrail checks the prefix
-- and log file names to verify the names contain a date between the
-- specified @StartEventTime@ and @EndEventTime@ before attempting to
-- import events.
startImport_endEventTime :: Lens.Lens' StartImport (Prelude.Maybe Prelude.UTCTime)
startImport_endEventTime :: Lens' StartImport (Maybe UTCTime)
startImport_endEventTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImport' {Maybe POSIX
endEventTime :: Maybe POSIX
$sel:endEventTime:StartImport' :: StartImport -> Maybe POSIX
endEventTime} -> Maybe POSIX
endEventTime) (\s :: StartImport
s@StartImport' {} Maybe POSIX
a -> StartImport
s {$sel:endEventTime:StartImport' :: Maybe POSIX
endEventTime = Maybe POSIX
a} :: StartImport) 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 ID of the import. Use this parameter when you are retrying an
-- import.
startImport_importId :: Lens.Lens' StartImport (Prelude.Maybe Prelude.Text)
startImport_importId :: Lens' StartImport (Maybe Text)
startImport_importId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImport' {Maybe Text
importId :: Maybe Text
$sel:importId:StartImport' :: StartImport -> Maybe Text
importId} -> Maybe Text
importId) (\s :: StartImport
s@StartImport' {} Maybe Text
a -> StartImport
s {$sel:importId:StartImport' :: Maybe Text
importId = Maybe Text
a} :: StartImport)

-- | The source S3 bucket for the import. Use this parameter for a new
-- import.
startImport_importSource :: Lens.Lens' StartImport (Prelude.Maybe ImportSource)
startImport_importSource :: Lens' StartImport (Maybe ImportSource)
startImport_importSource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImport' {Maybe ImportSource
importSource :: Maybe ImportSource
$sel:importSource:StartImport' :: StartImport -> Maybe ImportSource
importSource} -> Maybe ImportSource
importSource) (\s :: StartImport
s@StartImport' {} Maybe ImportSource
a -> StartImport
s {$sel:importSource:StartImport' :: Maybe ImportSource
importSource = Maybe ImportSource
a} :: StartImport)

-- | Use with @EndEventTime@ to bound a @StartImport@ request, and limit
-- imported trail events to only those events logged within a specified
-- time period. When you specify a time range, CloudTrail checks the prefix
-- and log file names to verify the names contain a date between the
-- specified @StartEventTime@ and @EndEventTime@ before attempting to
-- import events.
startImport_startEventTime :: Lens.Lens' StartImport (Prelude.Maybe Prelude.UTCTime)
startImport_startEventTime :: Lens' StartImport (Maybe UTCTime)
startImport_startEventTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImport' {Maybe POSIX
startEventTime :: Maybe POSIX
$sel:startEventTime:StartImport' :: StartImport -> Maybe POSIX
startEventTime} -> Maybe POSIX
startEventTime) (\s :: StartImport
s@StartImport' {} Maybe POSIX
a -> StartImport
s {$sel:startEventTime:StartImport' :: Maybe POSIX
startEventTime = Maybe POSIX
a} :: StartImport) 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 Core.AWSRequest StartImport where
  type AWSResponse StartImport = StartImportResponse
  request :: (Service -> Service) -> StartImport -> Request StartImport
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy StartImport
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StartImport)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe POSIX
-> Maybe (NonEmpty Text)
-> Maybe POSIX
-> Maybe Text
-> Maybe ImportSource
-> Maybe ImportStatus
-> Maybe POSIX
-> Maybe POSIX
-> Int
-> StartImportResponse
StartImportResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CreatedTimestamp")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Destinations")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"EndEventTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ImportId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ImportSource")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ImportStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"StartEventTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"UpdatedTimestamp")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable StartImport where
  hashWithSalt :: Int -> StartImport -> Int
hashWithSalt Int
_salt StartImport' {Maybe (NonEmpty Text)
Maybe Text
Maybe POSIX
Maybe ImportSource
startEventTime :: Maybe POSIX
importSource :: Maybe ImportSource
importId :: Maybe Text
endEventTime :: Maybe POSIX
destinations :: Maybe (NonEmpty Text)
$sel:startEventTime:StartImport' :: StartImport -> Maybe POSIX
$sel:importSource:StartImport' :: StartImport -> Maybe ImportSource
$sel:importId:StartImport' :: StartImport -> Maybe Text
$sel:endEventTime:StartImport' :: StartImport -> Maybe POSIX
$sel:destinations:StartImport' :: StartImport -> Maybe (NonEmpty Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
destinations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
endEventTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
importId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ImportSource
importSource
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startEventTime

instance Prelude.NFData StartImport where
  rnf :: StartImport -> ()
rnf StartImport' {Maybe (NonEmpty Text)
Maybe Text
Maybe POSIX
Maybe ImportSource
startEventTime :: Maybe POSIX
importSource :: Maybe ImportSource
importId :: Maybe Text
endEventTime :: Maybe POSIX
destinations :: Maybe (NonEmpty Text)
$sel:startEventTime:StartImport' :: StartImport -> Maybe POSIX
$sel:importSource:StartImport' :: StartImport -> Maybe ImportSource
$sel:importId:StartImport' :: StartImport -> Maybe Text
$sel:endEventTime:StartImport' :: StartImport -> Maybe POSIX
$sel:destinations:StartImport' :: StartImport -> Maybe (NonEmpty Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
destinations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
endEventTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
importId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ImportSource
importSource
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startEventTime

instance Data.ToHeaders StartImport where
  toHeaders :: StartImport -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"com.amazonaws.cloudtrail.v20131101.CloudTrail_20131101.StartImport" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON StartImport where
  toJSON :: StartImport -> Value
toJSON StartImport' {Maybe (NonEmpty Text)
Maybe Text
Maybe POSIX
Maybe ImportSource
startEventTime :: Maybe POSIX
importSource :: Maybe ImportSource
importId :: Maybe Text
endEventTime :: Maybe POSIX
destinations :: Maybe (NonEmpty Text)
$sel:startEventTime:StartImport' :: StartImport -> Maybe POSIX
$sel:importSource:StartImport' :: StartImport -> Maybe ImportSource
$sel:importId:StartImport' :: StartImport -> Maybe Text
$sel:endEventTime:StartImport' :: StartImport -> Maybe POSIX
$sel:destinations:StartImport' :: StartImport -> Maybe (NonEmpty Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Destinations" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (NonEmpty Text)
destinations,
            (Key
"EndEventTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe POSIX
endEventTime,
            (Key
"ImportId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
importId,
            (Key
"ImportSource" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ImportSource
importSource,
            (Key
"StartEventTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe POSIX
startEventTime
          ]
      )

instance Data.ToPath StartImport where
  toPath :: StartImport -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery StartImport where
  toQuery :: StartImport -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newStartImportResponse' smart constructor.
data StartImportResponse = StartImportResponse'
  { -- | The timestamp for the import\'s creation.
    StartImportResponse -> Maybe POSIX
createdTimestamp :: Prelude.Maybe Data.POSIX,
    -- | The ARN of the destination event data store.
    StartImportResponse -> Maybe (NonEmpty Text)
destinations :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | Used with @StartEventTime@ to bound a @StartImport@ request, and limit
    -- imported trail events to only those events logged within a specified
    -- time period.
    StartImportResponse -> Maybe POSIX
endEventTime :: Prelude.Maybe Data.POSIX,
    -- | The ID of the import.
    StartImportResponse -> Maybe Text
importId :: Prelude.Maybe Prelude.Text,
    -- | The source S3 bucket for the import.
    StartImportResponse -> Maybe ImportSource
importSource :: Prelude.Maybe ImportSource,
    -- | Shows the status of the import after a @StartImport@ request. An import
    -- finishes with a status of @COMPLETED@ if there were no failures, or
    -- @FAILED@ if there were failures.
    StartImportResponse -> Maybe ImportStatus
importStatus :: Prelude.Maybe ImportStatus,
    -- | Used with @EndEventTime@ to bound a @StartImport@ request, and limit
    -- imported trail events to only those events logged within a specified
    -- time period.
    StartImportResponse -> Maybe POSIX
startEventTime :: Prelude.Maybe Data.POSIX,
    -- | The timestamp of the import\'s last update, if applicable.
    StartImportResponse -> Maybe POSIX
updatedTimestamp :: Prelude.Maybe Data.POSIX,
    -- | The response's http status code.
    StartImportResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartImportResponse -> StartImportResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartImportResponse -> StartImportResponse -> Bool
$c/= :: StartImportResponse -> StartImportResponse -> Bool
== :: StartImportResponse -> StartImportResponse -> Bool
$c== :: StartImportResponse -> StartImportResponse -> Bool
Prelude.Eq, ReadPrec [StartImportResponse]
ReadPrec StartImportResponse
Int -> ReadS StartImportResponse
ReadS [StartImportResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartImportResponse]
$creadListPrec :: ReadPrec [StartImportResponse]
readPrec :: ReadPrec StartImportResponse
$creadPrec :: ReadPrec StartImportResponse
readList :: ReadS [StartImportResponse]
$creadList :: ReadS [StartImportResponse]
readsPrec :: Int -> ReadS StartImportResponse
$creadsPrec :: Int -> ReadS StartImportResponse
Prelude.Read, Int -> StartImportResponse -> ShowS
[StartImportResponse] -> ShowS
StartImportResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartImportResponse] -> ShowS
$cshowList :: [StartImportResponse] -> ShowS
show :: StartImportResponse -> String
$cshow :: StartImportResponse -> String
showsPrec :: Int -> StartImportResponse -> ShowS
$cshowsPrec :: Int -> StartImportResponse -> ShowS
Prelude.Show, forall x. Rep StartImportResponse x -> StartImportResponse
forall x. StartImportResponse -> Rep StartImportResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartImportResponse x -> StartImportResponse
$cfrom :: forall x. StartImportResponse -> Rep StartImportResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartImportResponse' 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:
--
-- 'createdTimestamp', 'startImportResponse_createdTimestamp' - The timestamp for the import\'s creation.
--
-- 'destinations', 'startImportResponse_destinations' - The ARN of the destination event data store.
--
-- 'endEventTime', 'startImportResponse_endEventTime' - Used with @StartEventTime@ to bound a @StartImport@ request, and limit
-- imported trail events to only those events logged within a specified
-- time period.
--
-- 'importId', 'startImportResponse_importId' - The ID of the import.
--
-- 'importSource', 'startImportResponse_importSource' - The source S3 bucket for the import.
--
-- 'importStatus', 'startImportResponse_importStatus' - Shows the status of the import after a @StartImport@ request. An import
-- finishes with a status of @COMPLETED@ if there were no failures, or
-- @FAILED@ if there were failures.
--
-- 'startEventTime', 'startImportResponse_startEventTime' - Used with @EndEventTime@ to bound a @StartImport@ request, and limit
-- imported trail events to only those events logged within a specified
-- time period.
--
-- 'updatedTimestamp', 'startImportResponse_updatedTimestamp' - The timestamp of the import\'s last update, if applicable.
--
-- 'httpStatus', 'startImportResponse_httpStatus' - The response's http status code.
newStartImportResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartImportResponse
newStartImportResponse :: Int -> StartImportResponse
newStartImportResponse Int
pHttpStatus_ =
  StartImportResponse'
    { $sel:createdTimestamp:StartImportResponse' :: Maybe POSIX
createdTimestamp =
        forall a. Maybe a
Prelude.Nothing,
      $sel:destinations:StartImportResponse' :: Maybe (NonEmpty Text)
destinations = forall a. Maybe a
Prelude.Nothing,
      $sel:endEventTime:StartImportResponse' :: Maybe POSIX
endEventTime = forall a. Maybe a
Prelude.Nothing,
      $sel:importId:StartImportResponse' :: Maybe Text
importId = forall a. Maybe a
Prelude.Nothing,
      $sel:importSource:StartImportResponse' :: Maybe ImportSource
importSource = forall a. Maybe a
Prelude.Nothing,
      $sel:importStatus:StartImportResponse' :: Maybe ImportStatus
importStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:startEventTime:StartImportResponse' :: Maybe POSIX
startEventTime = forall a. Maybe a
Prelude.Nothing,
      $sel:updatedTimestamp:StartImportResponse' :: Maybe POSIX
updatedTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartImportResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The timestamp for the import\'s creation.
startImportResponse_createdTimestamp :: Lens.Lens' StartImportResponse (Prelude.Maybe Prelude.UTCTime)
startImportResponse_createdTimestamp :: Lens' StartImportResponse (Maybe UTCTime)
startImportResponse_createdTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportResponse' {Maybe POSIX
createdTimestamp :: Maybe POSIX
$sel:createdTimestamp:StartImportResponse' :: StartImportResponse -> Maybe POSIX
createdTimestamp} -> Maybe POSIX
createdTimestamp) (\s :: StartImportResponse
s@StartImportResponse' {} Maybe POSIX
a -> StartImportResponse
s {$sel:createdTimestamp:StartImportResponse' :: Maybe POSIX
createdTimestamp = Maybe POSIX
a} :: StartImportResponse) 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 ARN of the destination event data store.
startImportResponse_destinations :: Lens.Lens' StartImportResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
startImportResponse_destinations :: Lens' StartImportResponse (Maybe (NonEmpty Text))
startImportResponse_destinations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportResponse' {Maybe (NonEmpty Text)
destinations :: Maybe (NonEmpty Text)
$sel:destinations:StartImportResponse' :: StartImportResponse -> Maybe (NonEmpty Text)
destinations} -> Maybe (NonEmpty Text)
destinations) (\s :: StartImportResponse
s@StartImportResponse' {} Maybe (NonEmpty Text)
a -> StartImportResponse
s {$sel:destinations:StartImportResponse' :: Maybe (NonEmpty Text)
destinations = Maybe (NonEmpty Text)
a} :: StartImportResponse) 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

-- | Used with @StartEventTime@ to bound a @StartImport@ request, and limit
-- imported trail events to only those events logged within a specified
-- time period.
startImportResponse_endEventTime :: Lens.Lens' StartImportResponse (Prelude.Maybe Prelude.UTCTime)
startImportResponse_endEventTime :: Lens' StartImportResponse (Maybe UTCTime)
startImportResponse_endEventTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportResponse' {Maybe POSIX
endEventTime :: Maybe POSIX
$sel:endEventTime:StartImportResponse' :: StartImportResponse -> Maybe POSIX
endEventTime} -> Maybe POSIX
endEventTime) (\s :: StartImportResponse
s@StartImportResponse' {} Maybe POSIX
a -> StartImportResponse
s {$sel:endEventTime:StartImportResponse' :: Maybe POSIX
endEventTime = Maybe POSIX
a} :: StartImportResponse) 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 ID of the import.
startImportResponse_importId :: Lens.Lens' StartImportResponse (Prelude.Maybe Prelude.Text)
startImportResponse_importId :: Lens' StartImportResponse (Maybe Text)
startImportResponse_importId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportResponse' {Maybe Text
importId :: Maybe Text
$sel:importId:StartImportResponse' :: StartImportResponse -> Maybe Text
importId} -> Maybe Text
importId) (\s :: StartImportResponse
s@StartImportResponse' {} Maybe Text
a -> StartImportResponse
s {$sel:importId:StartImportResponse' :: Maybe Text
importId = Maybe Text
a} :: StartImportResponse)

-- | The source S3 bucket for the import.
startImportResponse_importSource :: Lens.Lens' StartImportResponse (Prelude.Maybe ImportSource)
startImportResponse_importSource :: Lens' StartImportResponse (Maybe ImportSource)
startImportResponse_importSource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportResponse' {Maybe ImportSource
importSource :: Maybe ImportSource
$sel:importSource:StartImportResponse' :: StartImportResponse -> Maybe ImportSource
importSource} -> Maybe ImportSource
importSource) (\s :: StartImportResponse
s@StartImportResponse' {} Maybe ImportSource
a -> StartImportResponse
s {$sel:importSource:StartImportResponse' :: Maybe ImportSource
importSource = Maybe ImportSource
a} :: StartImportResponse)

-- | Shows the status of the import after a @StartImport@ request. An import
-- finishes with a status of @COMPLETED@ if there were no failures, or
-- @FAILED@ if there were failures.
startImportResponse_importStatus :: Lens.Lens' StartImportResponse (Prelude.Maybe ImportStatus)
startImportResponse_importStatus :: Lens' StartImportResponse (Maybe ImportStatus)
startImportResponse_importStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportResponse' {Maybe ImportStatus
importStatus :: Maybe ImportStatus
$sel:importStatus:StartImportResponse' :: StartImportResponse -> Maybe ImportStatus
importStatus} -> Maybe ImportStatus
importStatus) (\s :: StartImportResponse
s@StartImportResponse' {} Maybe ImportStatus
a -> StartImportResponse
s {$sel:importStatus:StartImportResponse' :: Maybe ImportStatus
importStatus = Maybe ImportStatus
a} :: StartImportResponse)

-- | Used with @EndEventTime@ to bound a @StartImport@ request, and limit
-- imported trail events to only those events logged within a specified
-- time period.
startImportResponse_startEventTime :: Lens.Lens' StartImportResponse (Prelude.Maybe Prelude.UTCTime)
startImportResponse_startEventTime :: Lens' StartImportResponse (Maybe UTCTime)
startImportResponse_startEventTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportResponse' {Maybe POSIX
startEventTime :: Maybe POSIX
$sel:startEventTime:StartImportResponse' :: StartImportResponse -> Maybe POSIX
startEventTime} -> Maybe POSIX
startEventTime) (\s :: StartImportResponse
s@StartImportResponse' {} Maybe POSIX
a -> StartImportResponse
s {$sel:startEventTime:StartImportResponse' :: Maybe POSIX
startEventTime = Maybe POSIX
a} :: StartImportResponse) 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 timestamp of the import\'s last update, if applicable.
startImportResponse_updatedTimestamp :: Lens.Lens' StartImportResponse (Prelude.Maybe Prelude.UTCTime)
startImportResponse_updatedTimestamp :: Lens' StartImportResponse (Maybe UTCTime)
startImportResponse_updatedTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportResponse' {Maybe POSIX
updatedTimestamp :: Maybe POSIX
$sel:updatedTimestamp:StartImportResponse' :: StartImportResponse -> Maybe POSIX
updatedTimestamp} -> Maybe POSIX
updatedTimestamp) (\s :: StartImportResponse
s@StartImportResponse' {} Maybe POSIX
a -> StartImportResponse
s {$sel:updatedTimestamp:StartImportResponse' :: Maybe POSIX
updatedTimestamp = Maybe POSIX
a} :: StartImportResponse) 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 response's http status code.
startImportResponse_httpStatus :: Lens.Lens' StartImportResponse Prelude.Int
startImportResponse_httpStatus :: Lens' StartImportResponse Int
startImportResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportResponse' {Int
httpStatus :: Int
$sel:httpStatus:StartImportResponse' :: StartImportResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: StartImportResponse
s@StartImportResponse' {} Int
a -> StartImportResponse
s {$sel:httpStatus:StartImportResponse' :: Int
httpStatus = Int
a} :: StartImportResponse)

instance Prelude.NFData StartImportResponse where
  rnf :: StartImportResponse -> ()
rnf StartImportResponse' {Int
Maybe (NonEmpty Text)
Maybe Text
Maybe POSIX
Maybe ImportStatus
Maybe ImportSource
httpStatus :: Int
updatedTimestamp :: Maybe POSIX
startEventTime :: Maybe POSIX
importStatus :: Maybe ImportStatus
importSource :: Maybe ImportSource
importId :: Maybe Text
endEventTime :: Maybe POSIX
destinations :: Maybe (NonEmpty Text)
createdTimestamp :: Maybe POSIX
$sel:httpStatus:StartImportResponse' :: StartImportResponse -> Int
$sel:updatedTimestamp:StartImportResponse' :: StartImportResponse -> Maybe POSIX
$sel:startEventTime:StartImportResponse' :: StartImportResponse -> Maybe POSIX
$sel:importStatus:StartImportResponse' :: StartImportResponse -> Maybe ImportStatus
$sel:importSource:StartImportResponse' :: StartImportResponse -> Maybe ImportSource
$sel:importId:StartImportResponse' :: StartImportResponse -> Maybe Text
$sel:endEventTime:StartImportResponse' :: StartImportResponse -> Maybe POSIX
$sel:destinations:StartImportResponse' :: StartImportResponse -> Maybe (NonEmpty Text)
$sel:createdTimestamp:StartImportResponse' :: StartImportResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
destinations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
endEventTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
importId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ImportSource
importSource
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ImportStatus
importStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startEventTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
updatedTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus