{-# 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.ListPipelineExecutions
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets a list of the pipeline executions.
--
-- This operation returns paginated results.
module Amazonka.SageMaker.ListPipelineExecutions
  ( -- * Creating a Request
    ListPipelineExecutions (..),
    newListPipelineExecutions,

    -- * Request Lenses
    listPipelineExecutions_createdAfter,
    listPipelineExecutions_createdBefore,
    listPipelineExecutions_maxResults,
    listPipelineExecutions_nextToken,
    listPipelineExecutions_sortBy,
    listPipelineExecutions_sortOrder,
    listPipelineExecutions_pipelineName,

    -- * Destructuring the Response
    ListPipelineExecutionsResponse (..),
    newListPipelineExecutionsResponse,

    -- * Response Lenses
    listPipelineExecutionsResponse_nextToken,
    listPipelineExecutionsResponse_pipelineExecutionSummaries,
    listPipelineExecutionsResponse_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:/ 'newListPipelineExecutions' smart constructor.
data ListPipelineExecutions = ListPipelineExecutions'
  { -- | A filter that returns the pipeline executions that were created after a
    -- specified time.
    ListPipelineExecutions -> Maybe POSIX
createdAfter :: Prelude.Maybe Data.POSIX,
    -- | A filter that returns the pipeline executions that were created before a
    -- specified time.
    ListPipelineExecutions -> Maybe POSIX
createdBefore :: Prelude.Maybe Data.POSIX,
    -- | The maximum number of pipeline executions to return in the response.
    ListPipelineExecutions -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the result of the previous @ListPipelineExecutions@ request was
    -- truncated, the response includes a @NextToken@. To retrieve the next set
    -- of pipeline executions, use the token in the next request.
    ListPipelineExecutions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The field by which to sort results. The default is @CreatedTime@.
    ListPipelineExecutions -> Maybe SortPipelineExecutionsBy
sortBy :: Prelude.Maybe SortPipelineExecutionsBy,
    -- | The sort order for results.
    ListPipelineExecutions -> Maybe SortOrder
sortOrder :: Prelude.Maybe SortOrder,
    -- | The name of the pipeline.
    ListPipelineExecutions -> Text
pipelineName :: Prelude.Text
  }
  deriving (ListPipelineExecutions -> ListPipelineExecutions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPipelineExecutions -> ListPipelineExecutions -> Bool
$c/= :: ListPipelineExecutions -> ListPipelineExecutions -> Bool
== :: ListPipelineExecutions -> ListPipelineExecutions -> Bool
$c== :: ListPipelineExecutions -> ListPipelineExecutions -> Bool
Prelude.Eq, ReadPrec [ListPipelineExecutions]
ReadPrec ListPipelineExecutions
Int -> ReadS ListPipelineExecutions
ReadS [ListPipelineExecutions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPipelineExecutions]
$creadListPrec :: ReadPrec [ListPipelineExecutions]
readPrec :: ReadPrec ListPipelineExecutions
$creadPrec :: ReadPrec ListPipelineExecutions
readList :: ReadS [ListPipelineExecutions]
$creadList :: ReadS [ListPipelineExecutions]
readsPrec :: Int -> ReadS ListPipelineExecutions
$creadsPrec :: Int -> ReadS ListPipelineExecutions
Prelude.Read, Int -> ListPipelineExecutions -> ShowS
[ListPipelineExecutions] -> ShowS
ListPipelineExecutions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPipelineExecutions] -> ShowS
$cshowList :: [ListPipelineExecutions] -> ShowS
show :: ListPipelineExecutions -> String
$cshow :: ListPipelineExecutions -> String
showsPrec :: Int -> ListPipelineExecutions -> ShowS
$cshowsPrec :: Int -> ListPipelineExecutions -> ShowS
Prelude.Show, forall x. Rep ListPipelineExecutions x -> ListPipelineExecutions
forall x. ListPipelineExecutions -> Rep ListPipelineExecutions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPipelineExecutions x -> ListPipelineExecutions
$cfrom :: forall x. ListPipelineExecutions -> Rep ListPipelineExecutions x
Prelude.Generic)

-- |
-- Create a value of 'ListPipelineExecutions' 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:
--
-- 'createdAfter', 'listPipelineExecutions_createdAfter' - A filter that returns the pipeline executions that were created after a
-- specified time.
--
-- 'createdBefore', 'listPipelineExecutions_createdBefore' - A filter that returns the pipeline executions that were created before a
-- specified time.
--
-- 'maxResults', 'listPipelineExecutions_maxResults' - The maximum number of pipeline executions to return in the response.
--
-- 'nextToken', 'listPipelineExecutions_nextToken' - If the result of the previous @ListPipelineExecutions@ request was
-- truncated, the response includes a @NextToken@. To retrieve the next set
-- of pipeline executions, use the token in the next request.
--
-- 'sortBy', 'listPipelineExecutions_sortBy' - The field by which to sort results. The default is @CreatedTime@.
--
-- 'sortOrder', 'listPipelineExecutions_sortOrder' - The sort order for results.
--
-- 'pipelineName', 'listPipelineExecutions_pipelineName' - The name of the pipeline.
newListPipelineExecutions ::
  -- | 'pipelineName'
  Prelude.Text ->
  ListPipelineExecutions
newListPipelineExecutions :: Text -> ListPipelineExecutions
newListPipelineExecutions Text
pPipelineName_ =
  ListPipelineExecutions'
    { $sel:createdAfter:ListPipelineExecutions' :: Maybe POSIX
createdAfter =
        forall a. Maybe a
Prelude.Nothing,
      $sel:createdBefore:ListPipelineExecutions' :: Maybe POSIX
createdBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListPipelineExecutions' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListPipelineExecutions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortBy:ListPipelineExecutions' :: Maybe SortPipelineExecutionsBy
sortBy = forall a. Maybe a
Prelude.Nothing,
      $sel:sortOrder:ListPipelineExecutions' :: Maybe SortOrder
sortOrder = forall a. Maybe a
Prelude.Nothing,
      $sel:pipelineName:ListPipelineExecutions' :: Text
pipelineName = Text
pPipelineName_
    }

-- | A filter that returns the pipeline executions that were created after a
-- specified time.
listPipelineExecutions_createdAfter :: Lens.Lens' ListPipelineExecutions (Prelude.Maybe Prelude.UTCTime)
listPipelineExecutions_createdAfter :: Lens' ListPipelineExecutions (Maybe UTCTime)
listPipelineExecutions_createdAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelineExecutions' {Maybe POSIX
createdAfter :: Maybe POSIX
$sel:createdAfter:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe POSIX
createdAfter} -> Maybe POSIX
createdAfter) (\s :: ListPipelineExecutions
s@ListPipelineExecutions' {} Maybe POSIX
a -> ListPipelineExecutions
s {$sel:createdAfter:ListPipelineExecutions' :: Maybe POSIX
createdAfter = Maybe POSIX
a} :: ListPipelineExecutions) 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

-- | A filter that returns the pipeline executions that were created before a
-- specified time.
listPipelineExecutions_createdBefore :: Lens.Lens' ListPipelineExecutions (Prelude.Maybe Prelude.UTCTime)
listPipelineExecutions_createdBefore :: Lens' ListPipelineExecutions (Maybe UTCTime)
listPipelineExecutions_createdBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelineExecutions' {Maybe POSIX
createdBefore :: Maybe POSIX
$sel:createdBefore:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe POSIX
createdBefore} -> Maybe POSIX
createdBefore) (\s :: ListPipelineExecutions
s@ListPipelineExecutions' {} Maybe POSIX
a -> ListPipelineExecutions
s {$sel:createdBefore:ListPipelineExecutions' :: Maybe POSIX
createdBefore = Maybe POSIX
a} :: ListPipelineExecutions) 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 maximum number of pipeline executions to return in the response.
listPipelineExecutions_maxResults :: Lens.Lens' ListPipelineExecutions (Prelude.Maybe Prelude.Natural)
listPipelineExecutions_maxResults :: Lens' ListPipelineExecutions (Maybe Natural)
listPipelineExecutions_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelineExecutions' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListPipelineExecutions
s@ListPipelineExecutions' {} Maybe Natural
a -> ListPipelineExecutions
s {$sel:maxResults:ListPipelineExecutions' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListPipelineExecutions)

-- | If the result of the previous @ListPipelineExecutions@ request was
-- truncated, the response includes a @NextToken@. To retrieve the next set
-- of pipeline executions, use the token in the next request.
listPipelineExecutions_nextToken :: Lens.Lens' ListPipelineExecutions (Prelude.Maybe Prelude.Text)
listPipelineExecutions_nextToken :: Lens' ListPipelineExecutions (Maybe Text)
listPipelineExecutions_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelineExecutions' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPipelineExecutions
s@ListPipelineExecutions' {} Maybe Text
a -> ListPipelineExecutions
s {$sel:nextToken:ListPipelineExecutions' :: Maybe Text
nextToken = Maybe Text
a} :: ListPipelineExecutions)

-- | The field by which to sort results. The default is @CreatedTime@.
listPipelineExecutions_sortBy :: Lens.Lens' ListPipelineExecutions (Prelude.Maybe SortPipelineExecutionsBy)
listPipelineExecutions_sortBy :: Lens' ListPipelineExecutions (Maybe SortPipelineExecutionsBy)
listPipelineExecutions_sortBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelineExecutions' {Maybe SortPipelineExecutionsBy
sortBy :: Maybe SortPipelineExecutionsBy
$sel:sortBy:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe SortPipelineExecutionsBy
sortBy} -> Maybe SortPipelineExecutionsBy
sortBy) (\s :: ListPipelineExecutions
s@ListPipelineExecutions' {} Maybe SortPipelineExecutionsBy
a -> ListPipelineExecutions
s {$sel:sortBy:ListPipelineExecutions' :: Maybe SortPipelineExecutionsBy
sortBy = Maybe SortPipelineExecutionsBy
a} :: ListPipelineExecutions)

-- | The sort order for results.
listPipelineExecutions_sortOrder :: Lens.Lens' ListPipelineExecutions (Prelude.Maybe SortOrder)
listPipelineExecutions_sortOrder :: Lens' ListPipelineExecutions (Maybe SortOrder)
listPipelineExecutions_sortOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelineExecutions' {Maybe SortOrder
sortOrder :: Maybe SortOrder
$sel:sortOrder:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe SortOrder
sortOrder} -> Maybe SortOrder
sortOrder) (\s :: ListPipelineExecutions
s@ListPipelineExecutions' {} Maybe SortOrder
a -> ListPipelineExecutions
s {$sel:sortOrder:ListPipelineExecutions' :: Maybe SortOrder
sortOrder = Maybe SortOrder
a} :: ListPipelineExecutions)

-- | The name of the pipeline.
listPipelineExecutions_pipelineName :: Lens.Lens' ListPipelineExecutions Prelude.Text
listPipelineExecutions_pipelineName :: Lens' ListPipelineExecutions Text
listPipelineExecutions_pipelineName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelineExecutions' {Text
pipelineName :: Text
$sel:pipelineName:ListPipelineExecutions' :: ListPipelineExecutions -> Text
pipelineName} -> Text
pipelineName) (\s :: ListPipelineExecutions
s@ListPipelineExecutions' {} Text
a -> ListPipelineExecutions
s {$sel:pipelineName:ListPipelineExecutions' :: Text
pipelineName = Text
a} :: ListPipelineExecutions)

instance Core.AWSPager ListPipelineExecutions where
  page :: ListPipelineExecutions
-> AWSResponse ListPipelineExecutions
-> Maybe ListPipelineExecutions
page ListPipelineExecutions
rq AWSResponse ListPipelineExecutions
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListPipelineExecutions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPipelineExecutionsResponse (Maybe Text)
listPipelineExecutionsResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListPipelineExecutions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  ListPipelineExecutionsResponse (Maybe [PipelineExecutionSummary])
listPipelineExecutionsResponse_pipelineExecutionSummaries
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListPipelineExecutions
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListPipelineExecutions (Maybe Text)
listPipelineExecutions_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListPipelineExecutions
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPipelineExecutionsResponse (Maybe Text)
listPipelineExecutionsResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ListPipelineExecutions where
  type
    AWSResponse ListPipelineExecutions =
      ListPipelineExecutionsResponse
  request :: (Service -> Service)
-> ListPipelineExecutions -> Request ListPipelineExecutions
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 ListPipelineExecutions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListPipelineExecutions)))
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 Text
-> Maybe [PipelineExecutionSummary]
-> Int
-> ListPipelineExecutionsResponse
ListPipelineExecutionsResponse'
            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
"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
"PipelineExecutionSummaries"
                            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 ListPipelineExecutions where
  hashWithSalt :: Int -> ListPipelineExecutions -> Int
hashWithSalt Int
_salt ListPipelineExecutions' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe SortOrder
Maybe SortPipelineExecutionsBy
Text
pipelineName :: Text
sortOrder :: Maybe SortOrder
sortBy :: Maybe SortPipelineExecutionsBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
createdBefore :: Maybe POSIX
createdAfter :: Maybe POSIX
$sel:pipelineName:ListPipelineExecutions' :: ListPipelineExecutions -> Text
$sel:sortOrder:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe SortOrder
$sel:sortBy:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe SortPipelineExecutionsBy
$sel:nextToken:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe Text
$sel:maxResults:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe Natural
$sel:createdBefore:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe POSIX
$sel:createdAfter:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdAfter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdBefore
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortPipelineExecutionsBy
sortBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortOrder
sortOrder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
pipelineName

instance Prelude.NFData ListPipelineExecutions where
  rnf :: ListPipelineExecutions -> ()
rnf ListPipelineExecutions' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe SortOrder
Maybe SortPipelineExecutionsBy
Text
pipelineName :: Text
sortOrder :: Maybe SortOrder
sortBy :: Maybe SortPipelineExecutionsBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
createdBefore :: Maybe POSIX
createdAfter :: Maybe POSIX
$sel:pipelineName:ListPipelineExecutions' :: ListPipelineExecutions -> Text
$sel:sortOrder:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe SortOrder
$sel:sortBy:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe SortPipelineExecutionsBy
$sel:nextToken:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe Text
$sel:maxResults:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe Natural
$sel:createdBefore:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe POSIX
$sel:createdAfter:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAfter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdBefore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
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 SortPipelineExecutionsBy
sortBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SortOrder
sortOrder
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
pipelineName

instance Data.ToHeaders ListPipelineExecutions where
  toHeaders :: ListPipelineExecutions -> 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.ListPipelineExecutions" ::
                          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 ListPipelineExecutions where
  toJSON :: ListPipelineExecutions -> Value
toJSON ListPipelineExecutions' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe SortOrder
Maybe SortPipelineExecutionsBy
Text
pipelineName :: Text
sortOrder :: Maybe SortOrder
sortBy :: Maybe SortPipelineExecutionsBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
createdBefore :: Maybe POSIX
createdAfter :: Maybe POSIX
$sel:pipelineName:ListPipelineExecutions' :: ListPipelineExecutions -> Text
$sel:sortOrder:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe SortOrder
$sel:sortBy:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe SortPipelineExecutionsBy
$sel:nextToken:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe Text
$sel:maxResults:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe Natural
$sel:createdBefore:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe POSIX
$sel:createdAfter:ListPipelineExecutions' :: ListPipelineExecutions -> Maybe POSIX
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"CreatedAfter" 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
createdAfter,
            (Key
"CreatedBefore" 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
createdBefore,
            (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 Natural
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
"SortBy" 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 SortPipelineExecutionsBy
sortBy,
            (Key
"SortOrder" 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 SortOrder
sortOrder,
            forall a. a -> Maybe a
Prelude.Just (Key
"PipelineName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
pipelineName)
          ]
      )

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

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

-- | /See:/ 'newListPipelineExecutionsResponse' smart constructor.
data ListPipelineExecutionsResponse = ListPipelineExecutionsResponse'
  { -- | If the result of the previous @ListPipelineExecutions@ request was
    -- truncated, the response includes a @NextToken@. To retrieve the next set
    -- of pipeline executions, use the token in the next request.
    ListPipelineExecutionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Contains a sorted list of pipeline execution summary objects matching
    -- the specified filters. Each run summary includes the Amazon Resource
    -- Name (ARN) of the pipeline execution, the run date, and the status. This
    -- list can be empty.
    ListPipelineExecutionsResponse -> Maybe [PipelineExecutionSummary]
pipelineExecutionSummaries :: Prelude.Maybe [PipelineExecutionSummary],
    -- | The response's http status code.
    ListPipelineExecutionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListPipelineExecutionsResponse
-> ListPipelineExecutionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPipelineExecutionsResponse
-> ListPipelineExecutionsResponse -> Bool
$c/= :: ListPipelineExecutionsResponse
-> ListPipelineExecutionsResponse -> Bool
== :: ListPipelineExecutionsResponse
-> ListPipelineExecutionsResponse -> Bool
$c== :: ListPipelineExecutionsResponse
-> ListPipelineExecutionsResponse -> Bool
Prelude.Eq, ReadPrec [ListPipelineExecutionsResponse]
ReadPrec ListPipelineExecutionsResponse
Int -> ReadS ListPipelineExecutionsResponse
ReadS [ListPipelineExecutionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPipelineExecutionsResponse]
$creadListPrec :: ReadPrec [ListPipelineExecutionsResponse]
readPrec :: ReadPrec ListPipelineExecutionsResponse
$creadPrec :: ReadPrec ListPipelineExecutionsResponse
readList :: ReadS [ListPipelineExecutionsResponse]
$creadList :: ReadS [ListPipelineExecutionsResponse]
readsPrec :: Int -> ReadS ListPipelineExecutionsResponse
$creadsPrec :: Int -> ReadS ListPipelineExecutionsResponse
Prelude.Read, Int -> ListPipelineExecutionsResponse -> ShowS
[ListPipelineExecutionsResponse] -> ShowS
ListPipelineExecutionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPipelineExecutionsResponse] -> ShowS
$cshowList :: [ListPipelineExecutionsResponse] -> ShowS
show :: ListPipelineExecutionsResponse -> String
$cshow :: ListPipelineExecutionsResponse -> String
showsPrec :: Int -> ListPipelineExecutionsResponse -> ShowS
$cshowsPrec :: Int -> ListPipelineExecutionsResponse -> ShowS
Prelude.Show, forall x.
Rep ListPipelineExecutionsResponse x
-> ListPipelineExecutionsResponse
forall x.
ListPipelineExecutionsResponse
-> Rep ListPipelineExecutionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListPipelineExecutionsResponse x
-> ListPipelineExecutionsResponse
$cfrom :: forall x.
ListPipelineExecutionsResponse
-> Rep ListPipelineExecutionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListPipelineExecutionsResponse' 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', 'listPipelineExecutionsResponse_nextToken' - If the result of the previous @ListPipelineExecutions@ request was
-- truncated, the response includes a @NextToken@. To retrieve the next set
-- of pipeline executions, use the token in the next request.
--
-- 'pipelineExecutionSummaries', 'listPipelineExecutionsResponse_pipelineExecutionSummaries' - Contains a sorted list of pipeline execution summary objects matching
-- the specified filters. Each run summary includes the Amazon Resource
-- Name (ARN) of the pipeline execution, the run date, and the status. This
-- list can be empty.
--
-- 'httpStatus', 'listPipelineExecutionsResponse_httpStatus' - The response's http status code.
newListPipelineExecutionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListPipelineExecutionsResponse
newListPipelineExecutionsResponse :: Int -> ListPipelineExecutionsResponse
newListPipelineExecutionsResponse Int
pHttpStatus_ =
  ListPipelineExecutionsResponse'
    { $sel:nextToken:ListPipelineExecutionsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:pipelineExecutionSummaries:ListPipelineExecutionsResponse' :: Maybe [PipelineExecutionSummary]
pipelineExecutionSummaries =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListPipelineExecutionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If the result of the previous @ListPipelineExecutions@ request was
-- truncated, the response includes a @NextToken@. To retrieve the next set
-- of pipeline executions, use the token in the next request.
listPipelineExecutionsResponse_nextToken :: Lens.Lens' ListPipelineExecutionsResponse (Prelude.Maybe Prelude.Text)
listPipelineExecutionsResponse_nextToken :: Lens' ListPipelineExecutionsResponse (Maybe Text)
listPipelineExecutionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelineExecutionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPipelineExecutionsResponse' :: ListPipelineExecutionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPipelineExecutionsResponse
s@ListPipelineExecutionsResponse' {} Maybe Text
a -> ListPipelineExecutionsResponse
s {$sel:nextToken:ListPipelineExecutionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListPipelineExecutionsResponse)

-- | Contains a sorted list of pipeline execution summary objects matching
-- the specified filters. Each run summary includes the Amazon Resource
-- Name (ARN) of the pipeline execution, the run date, and the status. This
-- list can be empty.
listPipelineExecutionsResponse_pipelineExecutionSummaries :: Lens.Lens' ListPipelineExecutionsResponse (Prelude.Maybe [PipelineExecutionSummary])
listPipelineExecutionsResponse_pipelineExecutionSummaries :: Lens'
  ListPipelineExecutionsResponse (Maybe [PipelineExecutionSummary])
listPipelineExecutionsResponse_pipelineExecutionSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelineExecutionsResponse' {Maybe [PipelineExecutionSummary]
pipelineExecutionSummaries :: Maybe [PipelineExecutionSummary]
$sel:pipelineExecutionSummaries:ListPipelineExecutionsResponse' :: ListPipelineExecutionsResponse -> Maybe [PipelineExecutionSummary]
pipelineExecutionSummaries} -> Maybe [PipelineExecutionSummary]
pipelineExecutionSummaries) (\s :: ListPipelineExecutionsResponse
s@ListPipelineExecutionsResponse' {} Maybe [PipelineExecutionSummary]
a -> ListPipelineExecutionsResponse
s {$sel:pipelineExecutionSummaries:ListPipelineExecutionsResponse' :: Maybe [PipelineExecutionSummary]
pipelineExecutionSummaries = Maybe [PipelineExecutionSummary]
a} :: ListPipelineExecutionsResponse) 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.
listPipelineExecutionsResponse_httpStatus :: Lens.Lens' ListPipelineExecutionsResponse Prelude.Int
listPipelineExecutionsResponse_httpStatus :: Lens' ListPipelineExecutionsResponse Int
listPipelineExecutionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPipelineExecutionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListPipelineExecutionsResponse' :: ListPipelineExecutionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListPipelineExecutionsResponse
s@ListPipelineExecutionsResponse' {} Int
a -> ListPipelineExecutionsResponse
s {$sel:httpStatus:ListPipelineExecutionsResponse' :: Int
httpStatus = Int
a} :: ListPipelineExecutionsResponse)

instance
  Prelude.NFData
    ListPipelineExecutionsResponse
  where
  rnf :: ListPipelineExecutionsResponse -> ()
rnf ListPipelineExecutionsResponse' {Int
Maybe [PipelineExecutionSummary]
Maybe Text
httpStatus :: Int
pipelineExecutionSummaries :: Maybe [PipelineExecutionSummary]
nextToken :: Maybe Text
$sel:httpStatus:ListPipelineExecutionsResponse' :: ListPipelineExecutionsResponse -> Int
$sel:pipelineExecutionSummaries:ListPipelineExecutionsResponse' :: ListPipelineExecutionsResponse -> Maybe [PipelineExecutionSummary]
$sel:nextToken:ListPipelineExecutionsResponse' :: ListPipelineExecutionsResponse -> 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 Maybe [PipelineExecutionSummary]
pipelineExecutionSummaries
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus