{-# 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.XRay.GetInsightImpactGraph
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves a service graph structure filtered by the specified insight.
-- The service graph is limited to only structural information. For a
-- complete service graph, use this API with the GetServiceGraph API.
module Amazonka.XRay.GetInsightImpactGraph
  ( -- * Creating a Request
    GetInsightImpactGraph (..),
    newGetInsightImpactGraph,

    -- * Request Lenses
    getInsightImpactGraph_nextToken,
    getInsightImpactGraph_insightId,
    getInsightImpactGraph_startTime,
    getInsightImpactGraph_endTime,

    -- * Destructuring the Response
    GetInsightImpactGraphResponse (..),
    newGetInsightImpactGraphResponse,

    -- * Response Lenses
    getInsightImpactGraphResponse_endTime,
    getInsightImpactGraphResponse_insightId,
    getInsightImpactGraphResponse_nextToken,
    getInsightImpactGraphResponse_serviceGraphEndTime,
    getInsightImpactGraphResponse_serviceGraphStartTime,
    getInsightImpactGraphResponse_services,
    getInsightImpactGraphResponse_startTime,
    getInsightImpactGraphResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.XRay.Types

-- | /See:/ 'newGetInsightImpactGraph' smart constructor.
data GetInsightImpactGraph = GetInsightImpactGraph'
  { -- | Specify the pagination token returned by a previous request to retrieve
    -- the next page of results.
    GetInsightImpactGraph -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The insight\'s unique identifier. Use the GetInsightSummaries action to
    -- retrieve an InsightId.
    GetInsightImpactGraph -> Text
insightId :: Prelude.Text,
    -- | The estimated start time of the insight, in Unix time seconds. The
    -- StartTime is inclusive of the value provided and can\'t be more than 30
    -- days old.
    GetInsightImpactGraph -> POSIX
startTime :: Data.POSIX,
    -- | The estimated end time of the insight, in Unix time seconds. The EndTime
    -- is exclusive of the value provided. The time range between the start
    -- time and end time can\'t be more than six hours.
    GetInsightImpactGraph -> POSIX
endTime :: Data.POSIX
  }
  deriving (GetInsightImpactGraph -> GetInsightImpactGraph -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetInsightImpactGraph -> GetInsightImpactGraph -> Bool
$c/= :: GetInsightImpactGraph -> GetInsightImpactGraph -> Bool
== :: GetInsightImpactGraph -> GetInsightImpactGraph -> Bool
$c== :: GetInsightImpactGraph -> GetInsightImpactGraph -> Bool
Prelude.Eq, ReadPrec [GetInsightImpactGraph]
ReadPrec GetInsightImpactGraph
Int -> ReadS GetInsightImpactGraph
ReadS [GetInsightImpactGraph]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetInsightImpactGraph]
$creadListPrec :: ReadPrec [GetInsightImpactGraph]
readPrec :: ReadPrec GetInsightImpactGraph
$creadPrec :: ReadPrec GetInsightImpactGraph
readList :: ReadS [GetInsightImpactGraph]
$creadList :: ReadS [GetInsightImpactGraph]
readsPrec :: Int -> ReadS GetInsightImpactGraph
$creadsPrec :: Int -> ReadS GetInsightImpactGraph
Prelude.Read, Int -> GetInsightImpactGraph -> ShowS
[GetInsightImpactGraph] -> ShowS
GetInsightImpactGraph -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetInsightImpactGraph] -> ShowS
$cshowList :: [GetInsightImpactGraph] -> ShowS
show :: GetInsightImpactGraph -> String
$cshow :: GetInsightImpactGraph -> String
showsPrec :: Int -> GetInsightImpactGraph -> ShowS
$cshowsPrec :: Int -> GetInsightImpactGraph -> ShowS
Prelude.Show, forall x. Rep GetInsightImpactGraph x -> GetInsightImpactGraph
forall x. GetInsightImpactGraph -> Rep GetInsightImpactGraph x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetInsightImpactGraph x -> GetInsightImpactGraph
$cfrom :: forall x. GetInsightImpactGraph -> Rep GetInsightImpactGraph x
Prelude.Generic)

-- |
-- Create a value of 'GetInsightImpactGraph' 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:
--
-- 'nextToken', 'getInsightImpactGraph_nextToken' - Specify the pagination token returned by a previous request to retrieve
-- the next page of results.
--
-- 'insightId', 'getInsightImpactGraph_insightId' - The insight\'s unique identifier. Use the GetInsightSummaries action to
-- retrieve an InsightId.
--
-- 'startTime', 'getInsightImpactGraph_startTime' - The estimated start time of the insight, in Unix time seconds. The
-- StartTime is inclusive of the value provided and can\'t be more than 30
-- days old.
--
-- 'endTime', 'getInsightImpactGraph_endTime' - The estimated end time of the insight, in Unix time seconds. The EndTime
-- is exclusive of the value provided. The time range between the start
-- time and end time can\'t be more than six hours.
newGetInsightImpactGraph ::
  -- | 'insightId'
  Prelude.Text ->
  -- | 'startTime'
  Prelude.UTCTime ->
  -- | 'endTime'
  Prelude.UTCTime ->
  GetInsightImpactGraph
newGetInsightImpactGraph :: Text -> UTCTime -> UTCTime -> GetInsightImpactGraph
newGetInsightImpactGraph
  Text
pInsightId_
  UTCTime
pStartTime_
  UTCTime
pEndTime_ =
    GetInsightImpactGraph'
      { $sel:nextToken:GetInsightImpactGraph' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:insightId:GetInsightImpactGraph' :: Text
insightId = Text
pInsightId_,
        $sel:startTime:GetInsightImpactGraph' :: POSIX
startTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pStartTime_,
        $sel:endTime:GetInsightImpactGraph' :: POSIX
endTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pEndTime_
      }

-- | Specify the pagination token returned by a previous request to retrieve
-- the next page of results.
getInsightImpactGraph_nextToken :: Lens.Lens' GetInsightImpactGraph (Prelude.Maybe Prelude.Text)
getInsightImpactGraph_nextToken :: Lens' GetInsightImpactGraph (Maybe Text)
getInsightImpactGraph_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInsightImpactGraph' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetInsightImpactGraph' :: GetInsightImpactGraph -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetInsightImpactGraph
s@GetInsightImpactGraph' {} Maybe Text
a -> GetInsightImpactGraph
s {$sel:nextToken:GetInsightImpactGraph' :: Maybe Text
nextToken = Maybe Text
a} :: GetInsightImpactGraph)

-- | The insight\'s unique identifier. Use the GetInsightSummaries action to
-- retrieve an InsightId.
getInsightImpactGraph_insightId :: Lens.Lens' GetInsightImpactGraph Prelude.Text
getInsightImpactGraph_insightId :: Lens' GetInsightImpactGraph Text
getInsightImpactGraph_insightId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInsightImpactGraph' {Text
insightId :: Text
$sel:insightId:GetInsightImpactGraph' :: GetInsightImpactGraph -> Text
insightId} -> Text
insightId) (\s :: GetInsightImpactGraph
s@GetInsightImpactGraph' {} Text
a -> GetInsightImpactGraph
s {$sel:insightId:GetInsightImpactGraph' :: Text
insightId = Text
a} :: GetInsightImpactGraph)

-- | The estimated start time of the insight, in Unix time seconds. The
-- StartTime is inclusive of the value provided and can\'t be more than 30
-- days old.
getInsightImpactGraph_startTime :: Lens.Lens' GetInsightImpactGraph Prelude.UTCTime
getInsightImpactGraph_startTime :: Lens' GetInsightImpactGraph UTCTime
getInsightImpactGraph_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInsightImpactGraph' {POSIX
startTime :: POSIX
$sel:startTime:GetInsightImpactGraph' :: GetInsightImpactGraph -> POSIX
startTime} -> POSIX
startTime) (\s :: GetInsightImpactGraph
s@GetInsightImpactGraph' {} POSIX
a -> GetInsightImpactGraph
s {$sel:startTime:GetInsightImpactGraph' :: POSIX
startTime = POSIX
a} :: GetInsightImpactGraph) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The estimated end time of the insight, in Unix time seconds. The EndTime
-- is exclusive of the value provided. The time range between the start
-- time and end time can\'t be more than six hours.
getInsightImpactGraph_endTime :: Lens.Lens' GetInsightImpactGraph Prelude.UTCTime
getInsightImpactGraph_endTime :: Lens' GetInsightImpactGraph UTCTime
getInsightImpactGraph_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInsightImpactGraph' {POSIX
endTime :: POSIX
$sel:endTime:GetInsightImpactGraph' :: GetInsightImpactGraph -> POSIX
endTime} -> POSIX
endTime) (\s :: GetInsightImpactGraph
s@GetInsightImpactGraph' {} POSIX
a -> GetInsightImpactGraph
s {$sel:endTime:GetInsightImpactGraph' :: POSIX
endTime = POSIX
a} :: GetInsightImpactGraph) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Core.AWSRequest GetInsightImpactGraph where
  type
    AWSResponse GetInsightImpactGraph =
      GetInsightImpactGraphResponse
  request :: (Service -> Service)
-> GetInsightImpactGraph -> Request GetInsightImpactGraph
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 GetInsightImpactGraph
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetInsightImpactGraph)))
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 Text
-> Maybe Text
-> Maybe POSIX
-> Maybe POSIX
-> Maybe [InsightImpactGraphService]
-> Maybe POSIX
-> Int
-> GetInsightImpactGraphResponse
GetInsightImpactGraphResponse'
            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
"EndTime")
            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
"InsightId")
            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
"NextToken")
            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
"ServiceGraphEndTime")
            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
"ServiceGraphStartTime")
            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
"Services" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (Maybe a)
Data..?> Key
"StartTime")
            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 GetInsightImpactGraph where
  hashWithSalt :: Int -> GetInsightImpactGraph -> Int
hashWithSalt Int
_salt GetInsightImpactGraph' {Maybe Text
Text
POSIX
endTime :: POSIX
startTime :: POSIX
insightId :: Text
nextToken :: Maybe Text
$sel:endTime:GetInsightImpactGraph' :: GetInsightImpactGraph -> POSIX
$sel:startTime:GetInsightImpactGraph' :: GetInsightImpactGraph -> POSIX
$sel:insightId:GetInsightImpactGraph' :: GetInsightImpactGraph -> Text
$sel:nextToken:GetInsightImpactGraph' :: GetInsightImpactGraph -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
insightId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
endTime

instance Prelude.NFData GetInsightImpactGraph where
  rnf :: GetInsightImpactGraph -> ()
rnf GetInsightImpactGraph' {Maybe Text
Text
POSIX
endTime :: POSIX
startTime :: POSIX
insightId :: Text
nextToken :: Maybe Text
$sel:endTime:GetInsightImpactGraph' :: GetInsightImpactGraph -> POSIX
$sel:startTime:GetInsightImpactGraph' :: GetInsightImpactGraph -> POSIX
$sel:insightId:GetInsightImpactGraph' :: GetInsightImpactGraph -> Text
$sel:nextToken:GetInsightImpactGraph' :: GetInsightImpactGraph -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
insightId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
endTime

instance Data.ToHeaders GetInsightImpactGraph where
  toHeaders :: GetInsightImpactGraph -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON GetInsightImpactGraph where
  toJSON :: GetInsightImpactGraph -> Value
toJSON GetInsightImpactGraph' {Maybe Text
Text
POSIX
endTime :: POSIX
startTime :: POSIX
insightId :: Text
nextToken :: Maybe Text
$sel:endTime:GetInsightImpactGraph' :: GetInsightImpactGraph -> POSIX
$sel:startTime:GetInsightImpactGraph' :: GetInsightImpactGraph -> POSIX
$sel:insightId:GetInsightImpactGraph' :: GetInsightImpactGraph -> Text
$sel:nextToken:GetInsightImpactGraph' :: GetInsightImpactGraph -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"NextToken" 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
nextToken,
            forall a. a -> Maybe a
Prelude.Just (Key
"InsightId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
insightId),
            forall a. a -> Maybe a
Prelude.Just (Key
"StartTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= POSIX
startTime),
            forall a. a -> Maybe a
Prelude.Just (Key
"EndTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= POSIX
endTime)
          ]
      )

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

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

-- | /See:/ 'newGetInsightImpactGraphResponse' smart constructor.
data GetInsightImpactGraphResponse = GetInsightImpactGraphResponse'
  { -- | The provided end time.
    GetInsightImpactGraphResponse -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    -- | The insight\'s unique identifier.
    GetInsightImpactGraphResponse -> Maybe Text
insightId :: Prelude.Maybe Prelude.Text,
    -- | Pagination token.
    GetInsightImpactGraphResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The time, in Unix seconds, at which the service graph ended.
    GetInsightImpactGraphResponse -> Maybe POSIX
serviceGraphEndTime :: Prelude.Maybe Data.POSIX,
    -- | The time, in Unix seconds, at which the service graph started.
    GetInsightImpactGraphResponse -> Maybe POSIX
serviceGraphStartTime :: Prelude.Maybe Data.POSIX,
    -- | The Amazon Web Services instrumented services related to the insight.
    GetInsightImpactGraphResponse -> Maybe [InsightImpactGraphService]
services :: Prelude.Maybe [InsightImpactGraphService],
    -- | The provided start time.
    GetInsightImpactGraphResponse -> Maybe POSIX
startTime :: Prelude.Maybe Data.POSIX,
    -- | The response's http status code.
    GetInsightImpactGraphResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetInsightImpactGraphResponse
-> GetInsightImpactGraphResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetInsightImpactGraphResponse
-> GetInsightImpactGraphResponse -> Bool
$c/= :: GetInsightImpactGraphResponse
-> GetInsightImpactGraphResponse -> Bool
== :: GetInsightImpactGraphResponse
-> GetInsightImpactGraphResponse -> Bool
$c== :: GetInsightImpactGraphResponse
-> GetInsightImpactGraphResponse -> Bool
Prelude.Eq, ReadPrec [GetInsightImpactGraphResponse]
ReadPrec GetInsightImpactGraphResponse
Int -> ReadS GetInsightImpactGraphResponse
ReadS [GetInsightImpactGraphResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetInsightImpactGraphResponse]
$creadListPrec :: ReadPrec [GetInsightImpactGraphResponse]
readPrec :: ReadPrec GetInsightImpactGraphResponse
$creadPrec :: ReadPrec GetInsightImpactGraphResponse
readList :: ReadS [GetInsightImpactGraphResponse]
$creadList :: ReadS [GetInsightImpactGraphResponse]
readsPrec :: Int -> ReadS GetInsightImpactGraphResponse
$creadsPrec :: Int -> ReadS GetInsightImpactGraphResponse
Prelude.Read, Int -> GetInsightImpactGraphResponse -> ShowS
[GetInsightImpactGraphResponse] -> ShowS
GetInsightImpactGraphResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetInsightImpactGraphResponse] -> ShowS
$cshowList :: [GetInsightImpactGraphResponse] -> ShowS
show :: GetInsightImpactGraphResponse -> String
$cshow :: GetInsightImpactGraphResponse -> String
showsPrec :: Int -> GetInsightImpactGraphResponse -> ShowS
$cshowsPrec :: Int -> GetInsightImpactGraphResponse -> ShowS
Prelude.Show, forall x.
Rep GetInsightImpactGraphResponse x
-> GetInsightImpactGraphResponse
forall x.
GetInsightImpactGraphResponse
-> Rep GetInsightImpactGraphResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetInsightImpactGraphResponse x
-> GetInsightImpactGraphResponse
$cfrom :: forall x.
GetInsightImpactGraphResponse
-> Rep GetInsightImpactGraphResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetInsightImpactGraphResponse' 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:
--
-- 'endTime', 'getInsightImpactGraphResponse_endTime' - The provided end time.
--
-- 'insightId', 'getInsightImpactGraphResponse_insightId' - The insight\'s unique identifier.
--
-- 'nextToken', 'getInsightImpactGraphResponse_nextToken' - Pagination token.
--
-- 'serviceGraphEndTime', 'getInsightImpactGraphResponse_serviceGraphEndTime' - The time, in Unix seconds, at which the service graph ended.
--
-- 'serviceGraphStartTime', 'getInsightImpactGraphResponse_serviceGraphStartTime' - The time, in Unix seconds, at which the service graph started.
--
-- 'services', 'getInsightImpactGraphResponse_services' - The Amazon Web Services instrumented services related to the insight.
--
-- 'startTime', 'getInsightImpactGraphResponse_startTime' - The provided start time.
--
-- 'httpStatus', 'getInsightImpactGraphResponse_httpStatus' - The response's http status code.
newGetInsightImpactGraphResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetInsightImpactGraphResponse
newGetInsightImpactGraphResponse :: Int -> GetInsightImpactGraphResponse
newGetInsightImpactGraphResponse Int
pHttpStatus_ =
  GetInsightImpactGraphResponse'
    { $sel:endTime:GetInsightImpactGraphResponse' :: Maybe POSIX
endTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:insightId:GetInsightImpactGraphResponse' :: Maybe Text
insightId = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetInsightImpactGraphResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceGraphEndTime:GetInsightImpactGraphResponse' :: Maybe POSIX
serviceGraphEndTime = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceGraphStartTime:GetInsightImpactGraphResponse' :: Maybe POSIX
serviceGraphStartTime = forall a. Maybe a
Prelude.Nothing,
      $sel:services:GetInsightImpactGraphResponse' :: Maybe [InsightImpactGraphService]
services = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:GetInsightImpactGraphResponse' :: Maybe POSIX
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetInsightImpactGraphResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The provided end time.
getInsightImpactGraphResponse_endTime :: Lens.Lens' GetInsightImpactGraphResponse (Prelude.Maybe Prelude.UTCTime)
getInsightImpactGraphResponse_endTime :: Lens' GetInsightImpactGraphResponse (Maybe UTCTime)
getInsightImpactGraphResponse_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInsightImpactGraphResponse' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: GetInsightImpactGraphResponse
s@GetInsightImpactGraphResponse' {} Maybe POSIX
a -> GetInsightImpactGraphResponse
s {$sel:endTime:GetInsightImpactGraphResponse' :: Maybe POSIX
endTime = Maybe POSIX
a} :: GetInsightImpactGraphResponse) 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 insight\'s unique identifier.
getInsightImpactGraphResponse_insightId :: Lens.Lens' GetInsightImpactGraphResponse (Prelude.Maybe Prelude.Text)
getInsightImpactGraphResponse_insightId :: Lens' GetInsightImpactGraphResponse (Maybe Text)
getInsightImpactGraphResponse_insightId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInsightImpactGraphResponse' {Maybe Text
insightId :: Maybe Text
$sel:insightId:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Maybe Text
insightId} -> Maybe Text
insightId) (\s :: GetInsightImpactGraphResponse
s@GetInsightImpactGraphResponse' {} Maybe Text
a -> GetInsightImpactGraphResponse
s {$sel:insightId:GetInsightImpactGraphResponse' :: Maybe Text
insightId = Maybe Text
a} :: GetInsightImpactGraphResponse)

-- | Pagination token.
getInsightImpactGraphResponse_nextToken :: Lens.Lens' GetInsightImpactGraphResponse (Prelude.Maybe Prelude.Text)
getInsightImpactGraphResponse_nextToken :: Lens' GetInsightImpactGraphResponse (Maybe Text)
getInsightImpactGraphResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInsightImpactGraphResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetInsightImpactGraphResponse
s@GetInsightImpactGraphResponse' {} Maybe Text
a -> GetInsightImpactGraphResponse
s {$sel:nextToken:GetInsightImpactGraphResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetInsightImpactGraphResponse)

-- | The time, in Unix seconds, at which the service graph ended.
getInsightImpactGraphResponse_serviceGraphEndTime :: Lens.Lens' GetInsightImpactGraphResponse (Prelude.Maybe Prelude.UTCTime)
getInsightImpactGraphResponse_serviceGraphEndTime :: Lens' GetInsightImpactGraphResponse (Maybe UTCTime)
getInsightImpactGraphResponse_serviceGraphEndTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInsightImpactGraphResponse' {Maybe POSIX
serviceGraphEndTime :: Maybe POSIX
$sel:serviceGraphEndTime:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Maybe POSIX
serviceGraphEndTime} -> Maybe POSIX
serviceGraphEndTime) (\s :: GetInsightImpactGraphResponse
s@GetInsightImpactGraphResponse' {} Maybe POSIX
a -> GetInsightImpactGraphResponse
s {$sel:serviceGraphEndTime:GetInsightImpactGraphResponse' :: Maybe POSIX
serviceGraphEndTime = Maybe POSIX
a} :: GetInsightImpactGraphResponse) 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 time, in Unix seconds, at which the service graph started.
getInsightImpactGraphResponse_serviceGraphStartTime :: Lens.Lens' GetInsightImpactGraphResponse (Prelude.Maybe Prelude.UTCTime)
getInsightImpactGraphResponse_serviceGraphStartTime :: Lens' GetInsightImpactGraphResponse (Maybe UTCTime)
getInsightImpactGraphResponse_serviceGraphStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInsightImpactGraphResponse' {Maybe POSIX
serviceGraphStartTime :: Maybe POSIX
$sel:serviceGraphStartTime:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Maybe POSIX
serviceGraphStartTime} -> Maybe POSIX
serviceGraphStartTime) (\s :: GetInsightImpactGraphResponse
s@GetInsightImpactGraphResponse' {} Maybe POSIX
a -> GetInsightImpactGraphResponse
s {$sel:serviceGraphStartTime:GetInsightImpactGraphResponse' :: Maybe POSIX
serviceGraphStartTime = Maybe POSIX
a} :: GetInsightImpactGraphResponse) 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 Amazon Web Services instrumented services related to the insight.
getInsightImpactGraphResponse_services :: Lens.Lens' GetInsightImpactGraphResponse (Prelude.Maybe [InsightImpactGraphService])
getInsightImpactGraphResponse_services :: Lens'
  GetInsightImpactGraphResponse (Maybe [InsightImpactGraphService])
getInsightImpactGraphResponse_services = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInsightImpactGraphResponse' {Maybe [InsightImpactGraphService]
services :: Maybe [InsightImpactGraphService]
$sel:services:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Maybe [InsightImpactGraphService]
services} -> Maybe [InsightImpactGraphService]
services) (\s :: GetInsightImpactGraphResponse
s@GetInsightImpactGraphResponse' {} Maybe [InsightImpactGraphService]
a -> GetInsightImpactGraphResponse
s {$sel:services:GetInsightImpactGraphResponse' :: Maybe [InsightImpactGraphService]
services = Maybe [InsightImpactGraphService]
a} :: GetInsightImpactGraphResponse) 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 provided start time.
getInsightImpactGraphResponse_startTime :: Lens.Lens' GetInsightImpactGraphResponse (Prelude.Maybe Prelude.UTCTime)
getInsightImpactGraphResponse_startTime :: Lens' GetInsightImpactGraphResponse (Maybe UTCTime)
getInsightImpactGraphResponse_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInsightImpactGraphResponse' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: GetInsightImpactGraphResponse
s@GetInsightImpactGraphResponse' {} Maybe POSIX
a -> GetInsightImpactGraphResponse
s {$sel:startTime:GetInsightImpactGraphResponse' :: Maybe POSIX
startTime = Maybe POSIX
a} :: GetInsightImpactGraphResponse) 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.
getInsightImpactGraphResponse_httpStatus :: Lens.Lens' GetInsightImpactGraphResponse Prelude.Int
getInsightImpactGraphResponse_httpStatus :: Lens' GetInsightImpactGraphResponse Int
getInsightImpactGraphResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetInsightImpactGraphResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetInsightImpactGraphResponse
s@GetInsightImpactGraphResponse' {} Int
a -> GetInsightImpactGraphResponse
s {$sel:httpStatus:GetInsightImpactGraphResponse' :: Int
httpStatus = Int
a} :: GetInsightImpactGraphResponse)

instance Prelude.NFData GetInsightImpactGraphResponse where
  rnf :: GetInsightImpactGraphResponse -> ()
rnf GetInsightImpactGraphResponse' {Int
Maybe [InsightImpactGraphService]
Maybe Text
Maybe POSIX
httpStatus :: Int
startTime :: Maybe POSIX
services :: Maybe [InsightImpactGraphService]
serviceGraphStartTime :: Maybe POSIX
serviceGraphEndTime :: Maybe POSIX
nextToken :: Maybe Text
insightId :: Maybe Text
endTime :: Maybe POSIX
$sel:httpStatus:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Int
$sel:startTime:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Maybe POSIX
$sel:services:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Maybe [InsightImpactGraphService]
$sel:serviceGraphStartTime:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Maybe POSIX
$sel:serviceGraphEndTime:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Maybe POSIX
$sel:nextToken:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Maybe Text
$sel:insightId:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Maybe Text
$sel:endTime:GetInsightImpactGraphResponse' :: GetInsightImpactGraphResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
insightId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
serviceGraphEndTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
serviceGraphStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [InsightImpactGraphService]
services
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus