{-# 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.GetImport
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about a specific import.
module Amazonka.CloudTrail.GetImport
  ( -- * Creating a Request
    GetImport (..),
    newGetImport,

    -- * Request Lenses
    getImport_importId,

    -- * Destructuring the Response
    GetImportResponse (..),
    newGetImportResponse,

    -- * Response Lenses
    getImportResponse_createdTimestamp,
    getImportResponse_destinations,
    getImportResponse_endEventTime,
    getImportResponse_importId,
    getImportResponse_importSource,
    getImportResponse_importStatistics,
    getImportResponse_importStatus,
    getImportResponse_startEventTime,
    getImportResponse_updatedTimestamp,
    getImportResponse_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:/ 'newGetImport' smart constructor.
data GetImport = GetImport'
  { -- | The ID for the import.
    GetImport -> Text
importId :: Prelude.Text
  }
  deriving (GetImport -> GetImport -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetImport -> GetImport -> Bool
$c/= :: GetImport -> GetImport -> Bool
== :: GetImport -> GetImport -> Bool
$c== :: GetImport -> GetImport -> Bool
Prelude.Eq, ReadPrec [GetImport]
ReadPrec GetImport
Int -> ReadS GetImport
ReadS [GetImport]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetImport]
$creadListPrec :: ReadPrec [GetImport]
readPrec :: ReadPrec GetImport
$creadPrec :: ReadPrec GetImport
readList :: ReadS [GetImport]
$creadList :: ReadS [GetImport]
readsPrec :: Int -> ReadS GetImport
$creadsPrec :: Int -> ReadS GetImport
Prelude.Read, Int -> GetImport -> ShowS
[GetImport] -> ShowS
GetImport -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetImport] -> ShowS
$cshowList :: [GetImport] -> ShowS
show :: GetImport -> String
$cshow :: GetImport -> String
showsPrec :: Int -> GetImport -> ShowS
$cshowsPrec :: Int -> GetImport -> ShowS
Prelude.Show, forall x. Rep GetImport x -> GetImport
forall x. GetImport -> Rep GetImport x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetImport x -> GetImport
$cfrom :: forall x. GetImport -> Rep GetImport x
Prelude.Generic)

-- |
-- Create a value of 'GetImport' 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:
--
-- 'importId', 'getImport_importId' - The ID for the import.
newGetImport ::
  -- | 'importId'
  Prelude.Text ->
  GetImport
newGetImport :: Text -> GetImport
newGetImport Text
pImportId_ =
  GetImport' {$sel:importId:GetImport' :: Text
importId = Text
pImportId_}

-- | The ID for the import.
getImport_importId :: Lens.Lens' GetImport Prelude.Text
getImport_importId :: Lens' GetImport Text
getImport_importId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetImport' {Text
importId :: Text
$sel:importId:GetImport' :: GetImport -> Text
importId} -> Text
importId) (\s :: GetImport
s@GetImport' {} Text
a -> GetImport
s {$sel:importId:GetImport' :: Text
importId = Text
a} :: GetImport)

instance Core.AWSRequest GetImport where
  type AWSResponse GetImport = GetImportResponse
  request :: (Service -> Service) -> GetImport -> Request GetImport
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 GetImport
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetImport)))
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 ImportStatistics
-> Maybe ImportStatus
-> Maybe POSIX
-> Maybe POSIX
-> Int
-> GetImportResponse
GetImportResponse'
            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
"ImportStatistics")
            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 GetImport where
  hashWithSalt :: Int -> GetImport -> Int
hashWithSalt Int
_salt GetImport' {Text
importId :: Text
$sel:importId:GetImport' :: GetImport -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
importId

instance Prelude.NFData GetImport where
  rnf :: GetImport -> ()
rnf GetImport' {Text
importId :: Text
$sel:importId:GetImport' :: GetImport -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
importId

instance Data.ToHeaders GetImport where
  toHeaders :: GetImport -> 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.GetImport" ::
                          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 GetImport where
  toJSON :: GetImport -> Value
toJSON GetImport' {Text
importId :: Text
$sel:importId:GetImport' :: GetImport -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"ImportId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
importId)]
      )

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

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

-- | /See:/ 'newGetImportResponse' smart constructor.
data GetImportResponse = GetImportResponse'
  { -- | The timestamp of the import\'s creation.
    GetImportResponse -> Maybe POSIX
createdTimestamp :: Prelude.Maybe Data.POSIX,
    -- | The ARN of the destination event data store.
    GetImportResponse -> 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.
    GetImportResponse -> Maybe POSIX
endEventTime :: Prelude.Maybe Data.POSIX,
    -- | The ID of the import.
    GetImportResponse -> Maybe Text
importId :: Prelude.Maybe Prelude.Text,
    -- | The source S3 bucket.
    GetImportResponse -> Maybe ImportSource
importSource :: Prelude.Maybe ImportSource,
    -- | Provides statistics for the import. CloudTrail does not update import
    -- statistics in real-time. Returned values for parameters such as
    -- @EventsCompleted@ may be lower than the actual value, because CloudTrail
    -- updates statistics incrementally over the course of the import.
    GetImportResponse -> Maybe ImportStatistics
importStatistics :: Prelude.Maybe ImportStatistics,
    -- | The status of the import.
    GetImportResponse -> 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.
    GetImportResponse -> Maybe POSIX
startEventTime :: Prelude.Maybe Data.POSIX,
    -- | The timestamp of when the import was updated.
    GetImportResponse -> Maybe POSIX
updatedTimestamp :: Prelude.Maybe Data.POSIX,
    -- | The response's http status code.
    GetImportResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetImportResponse -> GetImportResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetImportResponse -> GetImportResponse -> Bool
$c/= :: GetImportResponse -> GetImportResponse -> Bool
== :: GetImportResponse -> GetImportResponse -> Bool
$c== :: GetImportResponse -> GetImportResponse -> Bool
Prelude.Eq, ReadPrec [GetImportResponse]
ReadPrec GetImportResponse
Int -> ReadS GetImportResponse
ReadS [GetImportResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetImportResponse]
$creadListPrec :: ReadPrec [GetImportResponse]
readPrec :: ReadPrec GetImportResponse
$creadPrec :: ReadPrec GetImportResponse
readList :: ReadS [GetImportResponse]
$creadList :: ReadS [GetImportResponse]
readsPrec :: Int -> ReadS GetImportResponse
$creadsPrec :: Int -> ReadS GetImportResponse
Prelude.Read, Int -> GetImportResponse -> ShowS
[GetImportResponse] -> ShowS
GetImportResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetImportResponse] -> ShowS
$cshowList :: [GetImportResponse] -> ShowS
show :: GetImportResponse -> String
$cshow :: GetImportResponse -> String
showsPrec :: Int -> GetImportResponse -> ShowS
$cshowsPrec :: Int -> GetImportResponse -> ShowS
Prelude.Show, forall x. Rep GetImportResponse x -> GetImportResponse
forall x. GetImportResponse -> Rep GetImportResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetImportResponse x -> GetImportResponse
$cfrom :: forall x. GetImportResponse -> Rep GetImportResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetImportResponse' 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', 'getImportResponse_createdTimestamp' - The timestamp of the import\'s creation.
--
-- 'destinations', 'getImportResponse_destinations' - The ARN of the destination event data store.
--
-- 'endEventTime', 'getImportResponse_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', 'getImportResponse_importId' - The ID of the import.
--
-- 'importSource', 'getImportResponse_importSource' - The source S3 bucket.
--
-- 'importStatistics', 'getImportResponse_importStatistics' - Provides statistics for the import. CloudTrail does not update import
-- statistics in real-time. Returned values for parameters such as
-- @EventsCompleted@ may be lower than the actual value, because CloudTrail
-- updates statistics incrementally over the course of the import.
--
-- 'importStatus', 'getImportResponse_importStatus' - The status of the import.
--
-- 'startEventTime', 'getImportResponse_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', 'getImportResponse_updatedTimestamp' - The timestamp of when the import was updated.
--
-- 'httpStatus', 'getImportResponse_httpStatus' - The response's http status code.
newGetImportResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetImportResponse
newGetImportResponse :: Int -> GetImportResponse
newGetImportResponse Int
pHttpStatus_ =
  GetImportResponse'
    { $sel:createdTimestamp:GetImportResponse' :: Maybe POSIX
createdTimestamp =
        forall a. Maybe a
Prelude.Nothing,
      $sel:destinations:GetImportResponse' :: Maybe (NonEmpty Text)
destinations = forall a. Maybe a
Prelude.Nothing,
      $sel:endEventTime:GetImportResponse' :: Maybe POSIX
endEventTime = forall a. Maybe a
Prelude.Nothing,
      $sel:importId:GetImportResponse' :: Maybe Text
importId = forall a. Maybe a
Prelude.Nothing,
      $sel:importSource:GetImportResponse' :: Maybe ImportSource
importSource = forall a. Maybe a
Prelude.Nothing,
      $sel:importStatistics:GetImportResponse' :: Maybe ImportStatistics
importStatistics = forall a. Maybe a
Prelude.Nothing,
      $sel:importStatus:GetImportResponse' :: Maybe ImportStatus
importStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:startEventTime:GetImportResponse' :: Maybe POSIX
startEventTime = forall a. Maybe a
Prelude.Nothing,
      $sel:updatedTimestamp:GetImportResponse' :: Maybe POSIX
updatedTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetImportResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The timestamp of the import\'s creation.
getImportResponse_createdTimestamp :: Lens.Lens' GetImportResponse (Prelude.Maybe Prelude.UTCTime)
getImportResponse_createdTimestamp :: Lens' GetImportResponse (Maybe UTCTime)
getImportResponse_createdTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetImportResponse' {Maybe POSIX
createdTimestamp :: Maybe POSIX
$sel:createdTimestamp:GetImportResponse' :: GetImportResponse -> Maybe POSIX
createdTimestamp} -> Maybe POSIX
createdTimestamp) (\s :: GetImportResponse
s@GetImportResponse' {} Maybe POSIX
a -> GetImportResponse
s {$sel:createdTimestamp:GetImportResponse' :: Maybe POSIX
createdTimestamp = Maybe POSIX
a} :: GetImportResponse) 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.
getImportResponse_destinations :: Lens.Lens' GetImportResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
getImportResponse_destinations :: Lens' GetImportResponse (Maybe (NonEmpty Text))
getImportResponse_destinations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetImportResponse' {Maybe (NonEmpty Text)
destinations :: Maybe (NonEmpty Text)
$sel:destinations:GetImportResponse' :: GetImportResponse -> Maybe (NonEmpty Text)
destinations} -> Maybe (NonEmpty Text)
destinations) (\s :: GetImportResponse
s@GetImportResponse' {} Maybe (NonEmpty Text)
a -> GetImportResponse
s {$sel:destinations:GetImportResponse' :: Maybe (NonEmpty Text)
destinations = Maybe (NonEmpty Text)
a} :: GetImportResponse) 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.
getImportResponse_endEventTime :: Lens.Lens' GetImportResponse (Prelude.Maybe Prelude.UTCTime)
getImportResponse_endEventTime :: Lens' GetImportResponse (Maybe UTCTime)
getImportResponse_endEventTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetImportResponse' {Maybe POSIX
endEventTime :: Maybe POSIX
$sel:endEventTime:GetImportResponse' :: GetImportResponse -> Maybe POSIX
endEventTime} -> Maybe POSIX
endEventTime) (\s :: GetImportResponse
s@GetImportResponse' {} Maybe POSIX
a -> GetImportResponse
s {$sel:endEventTime:GetImportResponse' :: Maybe POSIX
endEventTime = Maybe POSIX
a} :: GetImportResponse) 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.
getImportResponse_importId :: Lens.Lens' GetImportResponse (Prelude.Maybe Prelude.Text)
getImportResponse_importId :: Lens' GetImportResponse (Maybe Text)
getImportResponse_importId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetImportResponse' {Maybe Text
importId :: Maybe Text
$sel:importId:GetImportResponse' :: GetImportResponse -> Maybe Text
importId} -> Maybe Text
importId) (\s :: GetImportResponse
s@GetImportResponse' {} Maybe Text
a -> GetImportResponse
s {$sel:importId:GetImportResponse' :: Maybe Text
importId = Maybe Text
a} :: GetImportResponse)

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

-- | Provides statistics for the import. CloudTrail does not update import
-- statistics in real-time. Returned values for parameters such as
-- @EventsCompleted@ may be lower than the actual value, because CloudTrail
-- updates statistics incrementally over the course of the import.
getImportResponse_importStatistics :: Lens.Lens' GetImportResponse (Prelude.Maybe ImportStatistics)
getImportResponse_importStatistics :: Lens' GetImportResponse (Maybe ImportStatistics)
getImportResponse_importStatistics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetImportResponse' {Maybe ImportStatistics
importStatistics :: Maybe ImportStatistics
$sel:importStatistics:GetImportResponse' :: GetImportResponse -> Maybe ImportStatistics
importStatistics} -> Maybe ImportStatistics
importStatistics) (\s :: GetImportResponse
s@GetImportResponse' {} Maybe ImportStatistics
a -> GetImportResponse
s {$sel:importStatistics:GetImportResponse' :: Maybe ImportStatistics
importStatistics = Maybe ImportStatistics
a} :: GetImportResponse)

-- | The status of the import.
getImportResponse_importStatus :: Lens.Lens' GetImportResponse (Prelude.Maybe ImportStatus)
getImportResponse_importStatus :: Lens' GetImportResponse (Maybe ImportStatus)
getImportResponse_importStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetImportResponse' {Maybe ImportStatus
importStatus :: Maybe ImportStatus
$sel:importStatus:GetImportResponse' :: GetImportResponse -> Maybe ImportStatus
importStatus} -> Maybe ImportStatus
importStatus) (\s :: GetImportResponse
s@GetImportResponse' {} Maybe ImportStatus
a -> GetImportResponse
s {$sel:importStatus:GetImportResponse' :: Maybe ImportStatus
importStatus = Maybe ImportStatus
a} :: GetImportResponse)

-- | Used with @EndEventTime@ to bound a @StartImport@ request, and limit
-- imported trail events to only those events logged within a specified
-- time period.
getImportResponse_startEventTime :: Lens.Lens' GetImportResponse (Prelude.Maybe Prelude.UTCTime)
getImportResponse_startEventTime :: Lens' GetImportResponse (Maybe UTCTime)
getImportResponse_startEventTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetImportResponse' {Maybe POSIX
startEventTime :: Maybe POSIX
$sel:startEventTime:GetImportResponse' :: GetImportResponse -> Maybe POSIX
startEventTime} -> Maybe POSIX
startEventTime) (\s :: GetImportResponse
s@GetImportResponse' {} Maybe POSIX
a -> GetImportResponse
s {$sel:startEventTime:GetImportResponse' :: Maybe POSIX
startEventTime = Maybe POSIX
a} :: GetImportResponse) 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 when the import was updated.
getImportResponse_updatedTimestamp :: Lens.Lens' GetImportResponse (Prelude.Maybe Prelude.UTCTime)
getImportResponse_updatedTimestamp :: Lens' GetImportResponse (Maybe UTCTime)
getImportResponse_updatedTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetImportResponse' {Maybe POSIX
updatedTimestamp :: Maybe POSIX
$sel:updatedTimestamp:GetImportResponse' :: GetImportResponse -> Maybe POSIX
updatedTimestamp} -> Maybe POSIX
updatedTimestamp) (\s :: GetImportResponse
s@GetImportResponse' {} Maybe POSIX
a -> GetImportResponse
s {$sel:updatedTimestamp:GetImportResponse' :: Maybe POSIX
updatedTimestamp = Maybe POSIX
a} :: GetImportResponse) 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.
getImportResponse_httpStatus :: Lens.Lens' GetImportResponse Prelude.Int
getImportResponse_httpStatus :: Lens' GetImportResponse Int
getImportResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetImportResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetImportResponse' :: GetImportResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetImportResponse
s@GetImportResponse' {} Int
a -> GetImportResponse
s {$sel:httpStatus:GetImportResponse' :: Int
httpStatus = Int
a} :: GetImportResponse)

instance Prelude.NFData GetImportResponse where
  rnf :: GetImportResponse -> ()
rnf GetImportResponse' {Int
Maybe (NonEmpty Text)
Maybe Text
Maybe POSIX
Maybe ImportStatistics
Maybe ImportStatus
Maybe ImportSource
httpStatus :: Int
updatedTimestamp :: Maybe POSIX
startEventTime :: Maybe POSIX
importStatus :: Maybe ImportStatus
importStatistics :: Maybe ImportStatistics
importSource :: Maybe ImportSource
importId :: Maybe Text
endEventTime :: Maybe POSIX
destinations :: Maybe (NonEmpty Text)
createdTimestamp :: Maybe POSIX
$sel:httpStatus:GetImportResponse' :: GetImportResponse -> Int
$sel:updatedTimestamp:GetImportResponse' :: GetImportResponse -> Maybe POSIX
$sel:startEventTime:GetImportResponse' :: GetImportResponse -> Maybe POSIX
$sel:importStatus:GetImportResponse' :: GetImportResponse -> Maybe ImportStatus
$sel:importStatistics:GetImportResponse' :: GetImportResponse -> Maybe ImportStatistics
$sel:importSource:GetImportResponse' :: GetImportResponse -> Maybe ImportSource
$sel:importId:GetImportResponse' :: GetImportResponse -> Maybe Text
$sel:endEventTime:GetImportResponse' :: GetImportResponse -> Maybe POSIX
$sel:destinations:GetImportResponse' :: GetImportResponse -> Maybe (NonEmpty Text)
$sel:createdTimestamp:GetImportResponse' :: GetImportResponse -> 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 ImportStatistics
importStatistics
      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