{-# 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.SageMaker.QueryLineage
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Use this action to inspect your lineage and discover relationships
-- between entities. For more information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/querying-lineage-entities.html Querying Lineage Entities>
-- in the /Amazon SageMaker Developer Guide/.
module Amazonka.SageMaker.QueryLineage
  ( -- * Creating a Request
    QueryLineage (..),
    newQueryLineage,

    -- * Request Lenses
    queryLineage_direction,
    queryLineage_filters,
    queryLineage_includeEdges,
    queryLineage_maxDepth,
    queryLineage_maxResults,
    queryLineage_nextToken,
    queryLineage_startArns,

    -- * Destructuring the Response
    QueryLineageResponse (..),
    newQueryLineageResponse,

    -- * Response Lenses
    queryLineageResponse_edges,
    queryLineageResponse_nextToken,
    queryLineageResponse_vertices,
    queryLineageResponse_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.SageMaker.Types

-- | /See:/ 'newQueryLineage' smart constructor.
data QueryLineage = QueryLineage'
  { -- | Associations between lineage entities have a direction. This parameter
    -- determines the direction from the StartArn(s) that the query traverses.
    QueryLineage -> Maybe Direction
direction :: Prelude.Maybe Direction,
    -- | A set of filtering parameters that allow you to specify which entities
    -- should be returned.
    --
    -- -   Properties - Key-value pairs to match on the lineage entities\'
    --     properties.
    --
    -- -   LineageTypes - A set of lineage entity types to match on. For
    --     example: @TrialComponent@, @Artifact@, or @Context@.
    --
    -- -   CreatedBefore - Filter entities created before this date.
    --
    -- -   ModifiedBefore - Filter entities modified before this date.
    --
    -- -   ModifiedAfter - Filter entities modified after this date.
    QueryLineage -> Maybe QueryFilters
filters :: Prelude.Maybe QueryFilters,
    -- | Setting this value to @True@ retrieves not only the entities of interest
    -- but also the
    -- <https://docs.aws.amazon.com/sagemaker/latest/dg/lineage-tracking-entities.html Associations>
    -- and lineage entities on the path. Set to @False@ to only return lineage
    -- entities that match your query.
    QueryLineage -> Maybe Bool
includeEdges :: Prelude.Maybe Prelude.Bool,
    -- | The maximum depth in lineage relationships from the @StartArns@ that are
    -- traversed. Depth is a measure of the number of @Associations@ from the
    -- @StartArn@ entity to the matched results.
    QueryLineage -> Maybe Int
maxDepth :: Prelude.Maybe Prelude.Int,
    -- | Limits the number of vertices in the results. Use the @NextToken@ in a
    -- response to to retrieve the next page of results.
    QueryLineage -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | Limits the number of vertices in the request. Use the @NextToken@ in a
    -- response to to retrieve the next page of results.
    QueryLineage -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of resource Amazon Resource Name (ARN) that represent the
    -- starting point for your lineage query.
    QueryLineage -> Maybe [Text]
startArns :: Prelude.Maybe [Prelude.Text]
  }
  deriving (QueryLineage -> QueryLineage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryLineage -> QueryLineage -> Bool
$c/= :: QueryLineage -> QueryLineage -> Bool
== :: QueryLineage -> QueryLineage -> Bool
$c== :: QueryLineage -> QueryLineage -> Bool
Prelude.Eq, ReadPrec [QueryLineage]
ReadPrec QueryLineage
Int -> ReadS QueryLineage
ReadS [QueryLineage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [QueryLineage]
$creadListPrec :: ReadPrec [QueryLineage]
readPrec :: ReadPrec QueryLineage
$creadPrec :: ReadPrec QueryLineage
readList :: ReadS [QueryLineage]
$creadList :: ReadS [QueryLineage]
readsPrec :: Int -> ReadS QueryLineage
$creadsPrec :: Int -> ReadS QueryLineage
Prelude.Read, Int -> QueryLineage -> ShowS
[QueryLineage] -> ShowS
QueryLineage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryLineage] -> ShowS
$cshowList :: [QueryLineage] -> ShowS
show :: QueryLineage -> String
$cshow :: QueryLineage -> String
showsPrec :: Int -> QueryLineage -> ShowS
$cshowsPrec :: Int -> QueryLineage -> ShowS
Prelude.Show, forall x. Rep QueryLineage x -> QueryLineage
forall x. QueryLineage -> Rep QueryLineage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QueryLineage x -> QueryLineage
$cfrom :: forall x. QueryLineage -> Rep QueryLineage x
Prelude.Generic)

-- |
-- Create a value of 'QueryLineage' 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:
--
-- 'direction', 'queryLineage_direction' - Associations between lineage entities have a direction. This parameter
-- determines the direction from the StartArn(s) that the query traverses.
--
-- 'filters', 'queryLineage_filters' - A set of filtering parameters that allow you to specify which entities
-- should be returned.
--
-- -   Properties - Key-value pairs to match on the lineage entities\'
--     properties.
--
-- -   LineageTypes - A set of lineage entity types to match on. For
--     example: @TrialComponent@, @Artifact@, or @Context@.
--
-- -   CreatedBefore - Filter entities created before this date.
--
-- -   ModifiedBefore - Filter entities modified before this date.
--
-- -   ModifiedAfter - Filter entities modified after this date.
--
-- 'includeEdges', 'queryLineage_includeEdges' - Setting this value to @True@ retrieves not only the entities of interest
-- but also the
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/lineage-tracking-entities.html Associations>
-- and lineage entities on the path. Set to @False@ to only return lineage
-- entities that match your query.
--
-- 'maxDepth', 'queryLineage_maxDepth' - The maximum depth in lineage relationships from the @StartArns@ that are
-- traversed. Depth is a measure of the number of @Associations@ from the
-- @StartArn@ entity to the matched results.
--
-- 'maxResults', 'queryLineage_maxResults' - Limits the number of vertices in the results. Use the @NextToken@ in a
-- response to to retrieve the next page of results.
--
-- 'nextToken', 'queryLineage_nextToken' - Limits the number of vertices in the request. Use the @NextToken@ in a
-- response to to retrieve the next page of results.
--
-- 'startArns', 'queryLineage_startArns' - A list of resource Amazon Resource Name (ARN) that represent the
-- starting point for your lineage query.
newQueryLineage ::
  QueryLineage
newQueryLineage :: QueryLineage
newQueryLineage =
  QueryLineage'
    { $sel:direction:QueryLineage' :: Maybe Direction
direction = forall a. Maybe a
Prelude.Nothing,
      $sel:filters:QueryLineage' :: Maybe QueryFilters
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:includeEdges:QueryLineage' :: Maybe Bool
includeEdges = forall a. Maybe a
Prelude.Nothing,
      $sel:maxDepth:QueryLineage' :: Maybe Int
maxDepth = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:QueryLineage' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:QueryLineage' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:startArns:QueryLineage' :: Maybe [Text]
startArns = forall a. Maybe a
Prelude.Nothing
    }

-- | Associations between lineage entities have a direction. This parameter
-- determines the direction from the StartArn(s) that the query traverses.
queryLineage_direction :: Lens.Lens' QueryLineage (Prelude.Maybe Direction)
queryLineage_direction :: Lens' QueryLineage (Maybe Direction)
queryLineage_direction = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryLineage' {Maybe Direction
direction :: Maybe Direction
$sel:direction:QueryLineage' :: QueryLineage -> Maybe Direction
direction} -> Maybe Direction
direction) (\s :: QueryLineage
s@QueryLineage' {} Maybe Direction
a -> QueryLineage
s {$sel:direction:QueryLineage' :: Maybe Direction
direction = Maybe Direction
a} :: QueryLineage)

-- | A set of filtering parameters that allow you to specify which entities
-- should be returned.
--
-- -   Properties - Key-value pairs to match on the lineage entities\'
--     properties.
--
-- -   LineageTypes - A set of lineage entity types to match on. For
--     example: @TrialComponent@, @Artifact@, or @Context@.
--
-- -   CreatedBefore - Filter entities created before this date.
--
-- -   ModifiedBefore - Filter entities modified before this date.
--
-- -   ModifiedAfter - Filter entities modified after this date.
queryLineage_filters :: Lens.Lens' QueryLineage (Prelude.Maybe QueryFilters)
queryLineage_filters :: Lens' QueryLineage (Maybe QueryFilters)
queryLineage_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryLineage' {Maybe QueryFilters
filters :: Maybe QueryFilters
$sel:filters:QueryLineage' :: QueryLineage -> Maybe QueryFilters
filters} -> Maybe QueryFilters
filters) (\s :: QueryLineage
s@QueryLineage' {} Maybe QueryFilters
a -> QueryLineage
s {$sel:filters:QueryLineage' :: Maybe QueryFilters
filters = Maybe QueryFilters
a} :: QueryLineage)

-- | Setting this value to @True@ retrieves not only the entities of interest
-- but also the
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/lineage-tracking-entities.html Associations>
-- and lineage entities on the path. Set to @False@ to only return lineage
-- entities that match your query.
queryLineage_includeEdges :: Lens.Lens' QueryLineage (Prelude.Maybe Prelude.Bool)
queryLineage_includeEdges :: Lens' QueryLineage (Maybe Bool)
queryLineage_includeEdges = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryLineage' {Maybe Bool
includeEdges :: Maybe Bool
$sel:includeEdges:QueryLineage' :: QueryLineage -> Maybe Bool
includeEdges} -> Maybe Bool
includeEdges) (\s :: QueryLineage
s@QueryLineage' {} Maybe Bool
a -> QueryLineage
s {$sel:includeEdges:QueryLineage' :: Maybe Bool
includeEdges = Maybe Bool
a} :: QueryLineage)

-- | The maximum depth in lineage relationships from the @StartArns@ that are
-- traversed. Depth is a measure of the number of @Associations@ from the
-- @StartArn@ entity to the matched results.
queryLineage_maxDepth :: Lens.Lens' QueryLineage (Prelude.Maybe Prelude.Int)
queryLineage_maxDepth :: Lens' QueryLineage (Maybe Int)
queryLineage_maxDepth = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryLineage' {Maybe Int
maxDepth :: Maybe Int
$sel:maxDepth:QueryLineage' :: QueryLineage -> Maybe Int
maxDepth} -> Maybe Int
maxDepth) (\s :: QueryLineage
s@QueryLineage' {} Maybe Int
a -> QueryLineage
s {$sel:maxDepth:QueryLineage' :: Maybe Int
maxDepth = Maybe Int
a} :: QueryLineage)

-- | Limits the number of vertices in the results. Use the @NextToken@ in a
-- response to to retrieve the next page of results.
queryLineage_maxResults :: Lens.Lens' QueryLineage (Prelude.Maybe Prelude.Int)
queryLineage_maxResults :: Lens' QueryLineage (Maybe Int)
queryLineage_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryLineage' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:QueryLineage' :: QueryLineage -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: QueryLineage
s@QueryLineage' {} Maybe Int
a -> QueryLineage
s {$sel:maxResults:QueryLineage' :: Maybe Int
maxResults = Maybe Int
a} :: QueryLineage)

-- | Limits the number of vertices in the request. Use the @NextToken@ in a
-- response to to retrieve the next page of results.
queryLineage_nextToken :: Lens.Lens' QueryLineage (Prelude.Maybe Prelude.Text)
queryLineage_nextToken :: Lens' QueryLineage (Maybe Text)
queryLineage_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryLineage' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:QueryLineage' :: QueryLineage -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: QueryLineage
s@QueryLineage' {} Maybe Text
a -> QueryLineage
s {$sel:nextToken:QueryLineage' :: Maybe Text
nextToken = Maybe Text
a} :: QueryLineage)

-- | A list of resource Amazon Resource Name (ARN) that represent the
-- starting point for your lineage query.
queryLineage_startArns :: Lens.Lens' QueryLineage (Prelude.Maybe [Prelude.Text])
queryLineage_startArns :: Lens' QueryLineage (Maybe [Text])
queryLineage_startArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryLineage' {Maybe [Text]
startArns :: Maybe [Text]
$sel:startArns:QueryLineage' :: QueryLineage -> Maybe [Text]
startArns} -> Maybe [Text]
startArns) (\s :: QueryLineage
s@QueryLineage' {} Maybe [Text]
a -> QueryLineage
s {$sel:startArns:QueryLineage' :: Maybe [Text]
startArns = Maybe [Text]
a} :: QueryLineage) 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

instance Core.AWSRequest QueryLineage where
  type AWSResponse QueryLineage = QueryLineageResponse
  request :: (Service -> Service) -> QueryLineage -> Request QueryLineage
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 QueryLineage
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse QueryLineage)))
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 [Edge]
-> Maybe Text -> Maybe [Vertex] -> Int -> QueryLineageResponse
QueryLineageResponse'
            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
"Edges" 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
"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
"Vertices" 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable QueryLineage where
  hashWithSalt :: Int -> QueryLineage -> Int
hashWithSalt Int
_salt QueryLineage' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe Text
Maybe Direction
Maybe QueryFilters
startArns :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Int
maxDepth :: Maybe Int
includeEdges :: Maybe Bool
filters :: Maybe QueryFilters
direction :: Maybe Direction
$sel:startArns:QueryLineage' :: QueryLineage -> Maybe [Text]
$sel:nextToken:QueryLineage' :: QueryLineage -> Maybe Text
$sel:maxResults:QueryLineage' :: QueryLineage -> Maybe Int
$sel:maxDepth:QueryLineage' :: QueryLineage -> Maybe Int
$sel:includeEdges:QueryLineage' :: QueryLineage -> Maybe Bool
$sel:filters:QueryLineage' :: QueryLineage -> Maybe QueryFilters
$sel:direction:QueryLineage' :: QueryLineage -> Maybe Direction
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Direction
direction
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe QueryFilters
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
includeEdges
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxDepth
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
startArns

instance Prelude.NFData QueryLineage where
  rnf :: QueryLineage -> ()
rnf QueryLineage' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe Text
Maybe Direction
Maybe QueryFilters
startArns :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Int
maxDepth :: Maybe Int
includeEdges :: Maybe Bool
filters :: Maybe QueryFilters
direction :: Maybe Direction
$sel:startArns:QueryLineage' :: QueryLineage -> Maybe [Text]
$sel:nextToken:QueryLineage' :: QueryLineage -> Maybe Text
$sel:maxResults:QueryLineage' :: QueryLineage -> Maybe Int
$sel:maxDepth:QueryLineage' :: QueryLineage -> Maybe Int
$sel:includeEdges:QueryLineage' :: QueryLineage -> Maybe Bool
$sel:filters:QueryLineage' :: QueryLineage -> Maybe QueryFilters
$sel:direction:QueryLineage' :: QueryLineage -> Maybe Direction
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Direction
direction
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe QueryFilters
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
includeEdges
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxDepth
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxResults
      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 [Text]
startArns

instance Data.ToHeaders QueryLineage where
  toHeaders :: QueryLineage -> 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
"SageMaker.QueryLineage" :: 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 QueryLineage where
  toJSON :: QueryLineage -> Value
toJSON QueryLineage' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe Text
Maybe Direction
Maybe QueryFilters
startArns :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Int
maxDepth :: Maybe Int
includeEdges :: Maybe Bool
filters :: Maybe QueryFilters
direction :: Maybe Direction
$sel:startArns:QueryLineage' :: QueryLineage -> Maybe [Text]
$sel:nextToken:QueryLineage' :: QueryLineage -> Maybe Text
$sel:maxResults:QueryLineage' :: QueryLineage -> Maybe Int
$sel:maxDepth:QueryLineage' :: QueryLineage -> Maybe Int
$sel:includeEdges:QueryLineage' :: QueryLineage -> Maybe Bool
$sel:filters:QueryLineage' :: QueryLineage -> Maybe QueryFilters
$sel:direction:QueryLineage' :: QueryLineage -> Maybe Direction
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Direction" 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 Direction
direction,
            (Key
"Filters" 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 QueryFilters
filters,
            (Key
"IncludeEdges" 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 Bool
includeEdges,
            (Key
"MaxDepth" 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 Int
maxDepth,
            (Key
"MaxResults" 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 Int
maxResults,
            (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,
            (Key
"StartArns" 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]
startArns
          ]
      )

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

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

-- | /See:/ 'newQueryLineageResponse' smart constructor.
data QueryLineageResponse = QueryLineageResponse'
  { -- | A list of edges that connect vertices in the response.
    QueryLineageResponse -> Maybe [Edge]
edges :: Prelude.Maybe [Edge],
    -- | Limits the number of vertices in the response. Use the @NextToken@ in a
    -- response to to retrieve the next page of results.
    QueryLineageResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of vertices connected to the start entity(ies) in the lineage
    -- graph.
    QueryLineageResponse -> Maybe [Vertex]
vertices :: Prelude.Maybe [Vertex],
    -- | The response's http status code.
    QueryLineageResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (QueryLineageResponse -> QueryLineageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryLineageResponse -> QueryLineageResponse -> Bool
$c/= :: QueryLineageResponse -> QueryLineageResponse -> Bool
== :: QueryLineageResponse -> QueryLineageResponse -> Bool
$c== :: QueryLineageResponse -> QueryLineageResponse -> Bool
Prelude.Eq, ReadPrec [QueryLineageResponse]
ReadPrec QueryLineageResponse
Int -> ReadS QueryLineageResponse
ReadS [QueryLineageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [QueryLineageResponse]
$creadListPrec :: ReadPrec [QueryLineageResponse]
readPrec :: ReadPrec QueryLineageResponse
$creadPrec :: ReadPrec QueryLineageResponse
readList :: ReadS [QueryLineageResponse]
$creadList :: ReadS [QueryLineageResponse]
readsPrec :: Int -> ReadS QueryLineageResponse
$creadsPrec :: Int -> ReadS QueryLineageResponse
Prelude.Read, Int -> QueryLineageResponse -> ShowS
[QueryLineageResponse] -> ShowS
QueryLineageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryLineageResponse] -> ShowS
$cshowList :: [QueryLineageResponse] -> ShowS
show :: QueryLineageResponse -> String
$cshow :: QueryLineageResponse -> String
showsPrec :: Int -> QueryLineageResponse -> ShowS
$cshowsPrec :: Int -> QueryLineageResponse -> ShowS
Prelude.Show, forall x. Rep QueryLineageResponse x -> QueryLineageResponse
forall x. QueryLineageResponse -> Rep QueryLineageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QueryLineageResponse x -> QueryLineageResponse
$cfrom :: forall x. QueryLineageResponse -> Rep QueryLineageResponse x
Prelude.Generic)

-- |
-- Create a value of 'QueryLineageResponse' 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:
--
-- 'edges', 'queryLineageResponse_edges' - A list of edges that connect vertices in the response.
--
-- 'nextToken', 'queryLineageResponse_nextToken' - Limits the number of vertices in the response. Use the @NextToken@ in a
-- response to to retrieve the next page of results.
--
-- 'vertices', 'queryLineageResponse_vertices' - A list of vertices connected to the start entity(ies) in the lineage
-- graph.
--
-- 'httpStatus', 'queryLineageResponse_httpStatus' - The response's http status code.
newQueryLineageResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  QueryLineageResponse
newQueryLineageResponse :: Int -> QueryLineageResponse
newQueryLineageResponse Int
pHttpStatus_ =
  QueryLineageResponse'
    { $sel:edges:QueryLineageResponse' :: Maybe [Edge]
edges = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:QueryLineageResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:vertices:QueryLineageResponse' :: Maybe [Vertex]
vertices = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:QueryLineageResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of edges that connect vertices in the response.
queryLineageResponse_edges :: Lens.Lens' QueryLineageResponse (Prelude.Maybe [Edge])
queryLineageResponse_edges :: Lens' QueryLineageResponse (Maybe [Edge])
queryLineageResponse_edges = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryLineageResponse' {Maybe [Edge]
edges :: Maybe [Edge]
$sel:edges:QueryLineageResponse' :: QueryLineageResponse -> Maybe [Edge]
edges} -> Maybe [Edge]
edges) (\s :: QueryLineageResponse
s@QueryLineageResponse' {} Maybe [Edge]
a -> QueryLineageResponse
s {$sel:edges:QueryLineageResponse' :: Maybe [Edge]
edges = Maybe [Edge]
a} :: QueryLineageResponse) 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

-- | Limits the number of vertices in the response. Use the @NextToken@ in a
-- response to to retrieve the next page of results.
queryLineageResponse_nextToken :: Lens.Lens' QueryLineageResponse (Prelude.Maybe Prelude.Text)
queryLineageResponse_nextToken :: Lens' QueryLineageResponse (Maybe Text)
queryLineageResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryLineageResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:QueryLineageResponse' :: QueryLineageResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: QueryLineageResponse
s@QueryLineageResponse' {} Maybe Text
a -> QueryLineageResponse
s {$sel:nextToken:QueryLineageResponse' :: Maybe Text
nextToken = Maybe Text
a} :: QueryLineageResponse)

-- | A list of vertices connected to the start entity(ies) in the lineage
-- graph.
queryLineageResponse_vertices :: Lens.Lens' QueryLineageResponse (Prelude.Maybe [Vertex])
queryLineageResponse_vertices :: Lens' QueryLineageResponse (Maybe [Vertex])
queryLineageResponse_vertices = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryLineageResponse' {Maybe [Vertex]
vertices :: Maybe [Vertex]
$sel:vertices:QueryLineageResponse' :: QueryLineageResponse -> Maybe [Vertex]
vertices} -> Maybe [Vertex]
vertices) (\s :: QueryLineageResponse
s@QueryLineageResponse' {} Maybe [Vertex]
a -> QueryLineageResponse
s {$sel:vertices:QueryLineageResponse' :: Maybe [Vertex]
vertices = Maybe [Vertex]
a} :: QueryLineageResponse) 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 response's http status code.
queryLineageResponse_httpStatus :: Lens.Lens' QueryLineageResponse Prelude.Int
queryLineageResponse_httpStatus :: Lens' QueryLineageResponse Int
queryLineageResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryLineageResponse' {Int
httpStatus :: Int
$sel:httpStatus:QueryLineageResponse' :: QueryLineageResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: QueryLineageResponse
s@QueryLineageResponse' {} Int
a -> QueryLineageResponse
s {$sel:httpStatus:QueryLineageResponse' :: Int
httpStatus = Int
a} :: QueryLineageResponse)

instance Prelude.NFData QueryLineageResponse where
  rnf :: QueryLineageResponse -> ()
rnf QueryLineageResponse' {Int
Maybe [Edge]
Maybe [Vertex]
Maybe Text
httpStatus :: Int
vertices :: Maybe [Vertex]
nextToken :: Maybe Text
edges :: Maybe [Edge]
$sel:httpStatus:QueryLineageResponse' :: QueryLineageResponse -> Int
$sel:vertices:QueryLineageResponse' :: QueryLineageResponse -> Maybe [Vertex]
$sel:nextToken:QueryLineageResponse' :: QueryLineageResponse -> Maybe Text
$sel:edges:QueryLineageResponse' :: QueryLineageResponse -> Maybe [Edge]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Edge]
edges
      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 [Vertex]
vertices
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus