{-# 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.ListModelCards
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- List existing model cards.
--
-- This operation returns paginated results.
module Amazonka.SageMaker.ListModelCards
  ( -- * Creating a Request
    ListModelCards (..),
    newListModelCards,

    -- * Request Lenses
    listModelCards_creationTimeAfter,
    listModelCards_creationTimeBefore,
    listModelCards_maxResults,
    listModelCards_modelCardStatus,
    listModelCards_nameContains,
    listModelCards_nextToken,
    listModelCards_sortBy,
    listModelCards_sortOrder,

    -- * Destructuring the Response
    ListModelCardsResponse (..),
    newListModelCardsResponse,

    -- * Response Lenses
    listModelCardsResponse_nextToken,
    listModelCardsResponse_httpStatus,
    listModelCardsResponse_modelCardSummaries,
  )
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:/ 'newListModelCards' smart constructor.
data ListModelCards = ListModelCards'
  { -- | Only list model cards that were created after the time specified.
    ListModelCards -> Maybe POSIX
creationTimeAfter :: Prelude.Maybe Data.POSIX,
    -- | Only list model cards that were created before the time specified.
    ListModelCards -> Maybe POSIX
creationTimeBefore :: Prelude.Maybe Data.POSIX,
    -- | The maximum number of model cards to list.
    ListModelCards -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Only list model cards with the specified approval status.
    ListModelCards -> Maybe ModelCardStatus
modelCardStatus :: Prelude.Maybe ModelCardStatus,
    -- | Only list model cards with names that contain the specified string.
    ListModelCards -> Maybe Text
nameContains :: Prelude.Maybe Prelude.Text,
    -- | If the response to a previous @ListModelCards@ request was truncated,
    -- the response includes a @NextToken@. To retrieve the next set of model
    -- cards, use the token in the next request.
    ListModelCards -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Sort model cards by either name or creation time. Sorts by creation time
    -- by default.
    ListModelCards -> Maybe ModelCardSortBy
sortBy :: Prelude.Maybe ModelCardSortBy,
    -- | Sort model cards by ascending or descending order.
    ListModelCards -> Maybe ModelCardSortOrder
sortOrder :: Prelude.Maybe ModelCardSortOrder
  }
  deriving (ListModelCards -> ListModelCards -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListModelCards -> ListModelCards -> Bool
$c/= :: ListModelCards -> ListModelCards -> Bool
== :: ListModelCards -> ListModelCards -> Bool
$c== :: ListModelCards -> ListModelCards -> Bool
Prelude.Eq, ReadPrec [ListModelCards]
ReadPrec ListModelCards
Int -> ReadS ListModelCards
ReadS [ListModelCards]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListModelCards]
$creadListPrec :: ReadPrec [ListModelCards]
readPrec :: ReadPrec ListModelCards
$creadPrec :: ReadPrec ListModelCards
readList :: ReadS [ListModelCards]
$creadList :: ReadS [ListModelCards]
readsPrec :: Int -> ReadS ListModelCards
$creadsPrec :: Int -> ReadS ListModelCards
Prelude.Read, Int -> ListModelCards -> ShowS
[ListModelCards] -> ShowS
ListModelCards -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListModelCards] -> ShowS
$cshowList :: [ListModelCards] -> ShowS
show :: ListModelCards -> String
$cshow :: ListModelCards -> String
showsPrec :: Int -> ListModelCards -> ShowS
$cshowsPrec :: Int -> ListModelCards -> ShowS
Prelude.Show, forall x. Rep ListModelCards x -> ListModelCards
forall x. ListModelCards -> Rep ListModelCards x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListModelCards x -> ListModelCards
$cfrom :: forall x. ListModelCards -> Rep ListModelCards x
Prelude.Generic)

-- |
-- Create a value of 'ListModelCards' 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:
--
-- 'creationTimeAfter', 'listModelCards_creationTimeAfter' - Only list model cards that were created after the time specified.
--
-- 'creationTimeBefore', 'listModelCards_creationTimeBefore' - Only list model cards that were created before the time specified.
--
-- 'maxResults', 'listModelCards_maxResults' - The maximum number of model cards to list.
--
-- 'modelCardStatus', 'listModelCards_modelCardStatus' - Only list model cards with the specified approval status.
--
-- 'nameContains', 'listModelCards_nameContains' - Only list model cards with names that contain the specified string.
--
-- 'nextToken', 'listModelCards_nextToken' - If the response to a previous @ListModelCards@ request was truncated,
-- the response includes a @NextToken@. To retrieve the next set of model
-- cards, use the token in the next request.
--
-- 'sortBy', 'listModelCards_sortBy' - Sort model cards by either name or creation time. Sorts by creation time
-- by default.
--
-- 'sortOrder', 'listModelCards_sortOrder' - Sort model cards by ascending or descending order.
newListModelCards ::
  ListModelCards
newListModelCards :: ListModelCards
newListModelCards =
  ListModelCards'
    { $sel:creationTimeAfter:ListModelCards' :: Maybe POSIX
creationTimeAfter =
        forall a. Maybe a
Prelude.Nothing,
      $sel:creationTimeBefore:ListModelCards' :: Maybe POSIX
creationTimeBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListModelCards' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:modelCardStatus:ListModelCards' :: Maybe ModelCardStatus
modelCardStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:nameContains:ListModelCards' :: Maybe Text
nameContains = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListModelCards' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortBy:ListModelCards' :: Maybe ModelCardSortBy
sortBy = forall a. Maybe a
Prelude.Nothing,
      $sel:sortOrder:ListModelCards' :: Maybe ModelCardSortOrder
sortOrder = forall a. Maybe a
Prelude.Nothing
    }

-- | Only list model cards that were created after the time specified.
listModelCards_creationTimeAfter :: Lens.Lens' ListModelCards (Prelude.Maybe Prelude.UTCTime)
listModelCards_creationTimeAfter :: Lens' ListModelCards (Maybe UTCTime)
listModelCards_creationTimeAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelCards' {Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:creationTimeAfter:ListModelCards' :: ListModelCards -> Maybe POSIX
creationTimeAfter} -> Maybe POSIX
creationTimeAfter) (\s :: ListModelCards
s@ListModelCards' {} Maybe POSIX
a -> ListModelCards
s {$sel:creationTimeAfter:ListModelCards' :: Maybe POSIX
creationTimeAfter = Maybe POSIX
a} :: ListModelCards) 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

-- | Only list model cards that were created before the time specified.
listModelCards_creationTimeBefore :: Lens.Lens' ListModelCards (Prelude.Maybe Prelude.UTCTime)
listModelCards_creationTimeBefore :: Lens' ListModelCards (Maybe UTCTime)
listModelCards_creationTimeBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelCards' {Maybe POSIX
creationTimeBefore :: Maybe POSIX
$sel:creationTimeBefore:ListModelCards' :: ListModelCards -> Maybe POSIX
creationTimeBefore} -> Maybe POSIX
creationTimeBefore) (\s :: ListModelCards
s@ListModelCards' {} Maybe POSIX
a -> ListModelCards
s {$sel:creationTimeBefore:ListModelCards' :: Maybe POSIX
creationTimeBefore = Maybe POSIX
a} :: ListModelCards) 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 model cards to list.
listModelCards_maxResults :: Lens.Lens' ListModelCards (Prelude.Maybe Prelude.Natural)
listModelCards_maxResults :: Lens' ListModelCards (Maybe Natural)
listModelCards_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelCards' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListModelCards' :: ListModelCards -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListModelCards
s@ListModelCards' {} Maybe Natural
a -> ListModelCards
s {$sel:maxResults:ListModelCards' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListModelCards)

-- | Only list model cards with the specified approval status.
listModelCards_modelCardStatus :: Lens.Lens' ListModelCards (Prelude.Maybe ModelCardStatus)
listModelCards_modelCardStatus :: Lens' ListModelCards (Maybe ModelCardStatus)
listModelCards_modelCardStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelCards' {Maybe ModelCardStatus
modelCardStatus :: Maybe ModelCardStatus
$sel:modelCardStatus:ListModelCards' :: ListModelCards -> Maybe ModelCardStatus
modelCardStatus} -> Maybe ModelCardStatus
modelCardStatus) (\s :: ListModelCards
s@ListModelCards' {} Maybe ModelCardStatus
a -> ListModelCards
s {$sel:modelCardStatus:ListModelCards' :: Maybe ModelCardStatus
modelCardStatus = Maybe ModelCardStatus
a} :: ListModelCards)

-- | Only list model cards with names that contain the specified string.
listModelCards_nameContains :: Lens.Lens' ListModelCards (Prelude.Maybe Prelude.Text)
listModelCards_nameContains :: Lens' ListModelCards (Maybe Text)
listModelCards_nameContains = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelCards' {Maybe Text
nameContains :: Maybe Text
$sel:nameContains:ListModelCards' :: ListModelCards -> Maybe Text
nameContains} -> Maybe Text
nameContains) (\s :: ListModelCards
s@ListModelCards' {} Maybe Text
a -> ListModelCards
s {$sel:nameContains:ListModelCards' :: Maybe Text
nameContains = Maybe Text
a} :: ListModelCards)

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

-- | Sort model cards by either name or creation time. Sorts by creation time
-- by default.
listModelCards_sortBy :: Lens.Lens' ListModelCards (Prelude.Maybe ModelCardSortBy)
listModelCards_sortBy :: Lens' ListModelCards (Maybe ModelCardSortBy)
listModelCards_sortBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelCards' {Maybe ModelCardSortBy
sortBy :: Maybe ModelCardSortBy
$sel:sortBy:ListModelCards' :: ListModelCards -> Maybe ModelCardSortBy
sortBy} -> Maybe ModelCardSortBy
sortBy) (\s :: ListModelCards
s@ListModelCards' {} Maybe ModelCardSortBy
a -> ListModelCards
s {$sel:sortBy:ListModelCards' :: Maybe ModelCardSortBy
sortBy = Maybe ModelCardSortBy
a} :: ListModelCards)

-- | Sort model cards by ascending or descending order.
listModelCards_sortOrder :: Lens.Lens' ListModelCards (Prelude.Maybe ModelCardSortOrder)
listModelCards_sortOrder :: Lens' ListModelCards (Maybe ModelCardSortOrder)
listModelCards_sortOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelCards' {Maybe ModelCardSortOrder
sortOrder :: Maybe ModelCardSortOrder
$sel:sortOrder:ListModelCards' :: ListModelCards -> Maybe ModelCardSortOrder
sortOrder} -> Maybe ModelCardSortOrder
sortOrder) (\s :: ListModelCards
s@ListModelCards' {} Maybe ModelCardSortOrder
a -> ListModelCards
s {$sel:sortOrder:ListModelCards' :: Maybe ModelCardSortOrder
sortOrder = Maybe ModelCardSortOrder
a} :: ListModelCards)

instance Core.AWSPager ListModelCards where
  page :: ListModelCards
-> AWSResponse ListModelCards -> Maybe ListModelCards
page ListModelCards
rq AWSResponse ListModelCards
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListModelCards
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListModelCardsResponse (Maybe Text)
listModelCardsResponse_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 ListModelCards
rs
            forall s a. s -> Getting a s a -> a
Lens.^. Lens' ListModelCardsResponse [ModelCardSummary]
listModelCardsResponse_modelCardSummaries
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListModelCards
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListModelCards (Maybe Text)
listModelCards_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListModelCards
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListModelCardsResponse (Maybe Text)
listModelCardsResponse_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 ListModelCards where
  type
    AWSResponse ListModelCards =
      ListModelCardsResponse
  request :: (Service -> Service) -> ListModelCards -> Request ListModelCards
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 ListModelCards
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListModelCards)))
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 -> Int -> [ModelCardSummary] -> ListModelCardsResponse
ListModelCardsResponse'
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            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
"ModelCardSummaries"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable ListModelCards where
  hashWithSalt :: Int -> ListModelCards -> Int
hashWithSalt Int
_salt ListModelCards' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe ModelCardSortBy
Maybe ModelCardSortOrder
Maybe ModelCardStatus
sortOrder :: Maybe ModelCardSortOrder
sortBy :: Maybe ModelCardSortBy
nextToken :: Maybe Text
nameContains :: Maybe Text
modelCardStatus :: Maybe ModelCardStatus
maxResults :: Maybe Natural
creationTimeBefore :: Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:sortOrder:ListModelCards' :: ListModelCards -> Maybe ModelCardSortOrder
$sel:sortBy:ListModelCards' :: ListModelCards -> Maybe ModelCardSortBy
$sel:nextToken:ListModelCards' :: ListModelCards -> Maybe Text
$sel:nameContains:ListModelCards' :: ListModelCards -> Maybe Text
$sel:modelCardStatus:ListModelCards' :: ListModelCards -> Maybe ModelCardStatus
$sel:maxResults:ListModelCards' :: ListModelCards -> Maybe Natural
$sel:creationTimeBefore:ListModelCards' :: ListModelCards -> Maybe POSIX
$sel:creationTimeAfter:ListModelCards' :: ListModelCards -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTimeAfter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTimeBefore
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ModelCardStatus
modelCardStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nameContains
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ModelCardSortBy
sortBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ModelCardSortOrder
sortOrder

instance Prelude.NFData ListModelCards where
  rnf :: ListModelCards -> ()
rnf ListModelCards' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe ModelCardSortBy
Maybe ModelCardSortOrder
Maybe ModelCardStatus
sortOrder :: Maybe ModelCardSortOrder
sortBy :: Maybe ModelCardSortBy
nextToken :: Maybe Text
nameContains :: Maybe Text
modelCardStatus :: Maybe ModelCardStatus
maxResults :: Maybe Natural
creationTimeBefore :: Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:sortOrder:ListModelCards' :: ListModelCards -> Maybe ModelCardSortOrder
$sel:sortBy:ListModelCards' :: ListModelCards -> Maybe ModelCardSortBy
$sel:nextToken:ListModelCards' :: ListModelCards -> Maybe Text
$sel:nameContains:ListModelCards' :: ListModelCards -> Maybe Text
$sel:modelCardStatus:ListModelCards' :: ListModelCards -> Maybe ModelCardStatus
$sel:maxResults:ListModelCards' :: ListModelCards -> Maybe Natural
$sel:creationTimeBefore:ListModelCards' :: ListModelCards -> Maybe POSIX
$sel:creationTimeAfter:ListModelCards' :: ListModelCards -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTimeAfter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTimeBefore
      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 ModelCardStatus
modelCardStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nameContains
      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 ModelCardSortBy
sortBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ModelCardSortOrder
sortOrder

instance Data.ToHeaders ListModelCards where
  toHeaders :: ListModelCards -> 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.ListModelCards" :: 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 ListModelCards where
  toJSON :: ListModelCards -> Value
toJSON ListModelCards' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe ModelCardSortBy
Maybe ModelCardSortOrder
Maybe ModelCardStatus
sortOrder :: Maybe ModelCardSortOrder
sortBy :: Maybe ModelCardSortBy
nextToken :: Maybe Text
nameContains :: Maybe Text
modelCardStatus :: Maybe ModelCardStatus
maxResults :: Maybe Natural
creationTimeBefore :: Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:sortOrder:ListModelCards' :: ListModelCards -> Maybe ModelCardSortOrder
$sel:sortBy:ListModelCards' :: ListModelCards -> Maybe ModelCardSortBy
$sel:nextToken:ListModelCards' :: ListModelCards -> Maybe Text
$sel:nameContains:ListModelCards' :: ListModelCards -> Maybe Text
$sel:modelCardStatus:ListModelCards' :: ListModelCards -> Maybe ModelCardStatus
$sel:maxResults:ListModelCards' :: ListModelCards -> Maybe Natural
$sel:creationTimeBefore:ListModelCards' :: ListModelCards -> Maybe POSIX
$sel:creationTimeAfter:ListModelCards' :: ListModelCards -> Maybe POSIX
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"CreationTimeAfter" 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
creationTimeAfter,
            (Key
"CreationTimeBefore" 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
creationTimeBefore,
            (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
"ModelCardStatus" 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 ModelCardStatus
modelCardStatus,
            (Key
"NameContains" 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
nameContains,
            (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 ModelCardSortBy
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 ModelCardSortOrder
sortOrder
          ]
      )

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

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

-- | /See:/ 'newListModelCardsResponse' smart constructor.
data ListModelCardsResponse = ListModelCardsResponse'
  { -- | If the response is truncated, SageMaker returns this token. To retrieve
    -- the next set of model cards, use it in the subsequent request.
    ListModelCardsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListModelCardsResponse -> Int
httpStatus :: Prelude.Int,
    -- | The summaries of the listed model cards.
    ListModelCardsResponse -> [ModelCardSummary]
modelCardSummaries :: [ModelCardSummary]
  }
  deriving (ListModelCardsResponse -> ListModelCardsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListModelCardsResponse -> ListModelCardsResponse -> Bool
$c/= :: ListModelCardsResponse -> ListModelCardsResponse -> Bool
== :: ListModelCardsResponse -> ListModelCardsResponse -> Bool
$c== :: ListModelCardsResponse -> ListModelCardsResponse -> Bool
Prelude.Eq, ReadPrec [ListModelCardsResponse]
ReadPrec ListModelCardsResponse
Int -> ReadS ListModelCardsResponse
ReadS [ListModelCardsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListModelCardsResponse]
$creadListPrec :: ReadPrec [ListModelCardsResponse]
readPrec :: ReadPrec ListModelCardsResponse
$creadPrec :: ReadPrec ListModelCardsResponse
readList :: ReadS [ListModelCardsResponse]
$creadList :: ReadS [ListModelCardsResponse]
readsPrec :: Int -> ReadS ListModelCardsResponse
$creadsPrec :: Int -> ReadS ListModelCardsResponse
Prelude.Read, Int -> ListModelCardsResponse -> ShowS
[ListModelCardsResponse] -> ShowS
ListModelCardsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListModelCardsResponse] -> ShowS
$cshowList :: [ListModelCardsResponse] -> ShowS
show :: ListModelCardsResponse -> String
$cshow :: ListModelCardsResponse -> String
showsPrec :: Int -> ListModelCardsResponse -> ShowS
$cshowsPrec :: Int -> ListModelCardsResponse -> ShowS
Prelude.Show, forall x. Rep ListModelCardsResponse x -> ListModelCardsResponse
forall x. ListModelCardsResponse -> Rep ListModelCardsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListModelCardsResponse x -> ListModelCardsResponse
$cfrom :: forall x. ListModelCardsResponse -> Rep ListModelCardsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListModelCardsResponse' 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', 'listModelCardsResponse_nextToken' - If the response is truncated, SageMaker returns this token. To retrieve
-- the next set of model cards, use it in the subsequent request.
--
-- 'httpStatus', 'listModelCardsResponse_httpStatus' - The response's http status code.
--
-- 'modelCardSummaries', 'listModelCardsResponse_modelCardSummaries' - The summaries of the listed model cards.
newListModelCardsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListModelCardsResponse
newListModelCardsResponse :: Int -> ListModelCardsResponse
newListModelCardsResponse Int
pHttpStatus_ =
  ListModelCardsResponse'
    { $sel:nextToken:ListModelCardsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListModelCardsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:modelCardSummaries:ListModelCardsResponse' :: [ModelCardSummary]
modelCardSummaries = forall a. Monoid a => a
Prelude.mempty
    }

-- | If the response is truncated, SageMaker returns this token. To retrieve
-- the next set of model cards, use it in the subsequent request.
listModelCardsResponse_nextToken :: Lens.Lens' ListModelCardsResponse (Prelude.Maybe Prelude.Text)
listModelCardsResponse_nextToken :: Lens' ListModelCardsResponse (Maybe Text)
listModelCardsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelCardsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListModelCardsResponse' :: ListModelCardsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListModelCardsResponse
s@ListModelCardsResponse' {} Maybe Text
a -> ListModelCardsResponse
s {$sel:nextToken:ListModelCardsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListModelCardsResponse)

-- | The response's http status code.
listModelCardsResponse_httpStatus :: Lens.Lens' ListModelCardsResponse Prelude.Int
listModelCardsResponse_httpStatus :: Lens' ListModelCardsResponse Int
listModelCardsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelCardsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListModelCardsResponse' :: ListModelCardsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListModelCardsResponse
s@ListModelCardsResponse' {} Int
a -> ListModelCardsResponse
s {$sel:httpStatus:ListModelCardsResponse' :: Int
httpStatus = Int
a} :: ListModelCardsResponse)

-- | The summaries of the listed model cards.
listModelCardsResponse_modelCardSummaries :: Lens.Lens' ListModelCardsResponse [ModelCardSummary]
listModelCardsResponse_modelCardSummaries :: Lens' ListModelCardsResponse [ModelCardSummary]
listModelCardsResponse_modelCardSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelCardsResponse' {[ModelCardSummary]
modelCardSummaries :: [ModelCardSummary]
$sel:modelCardSummaries:ListModelCardsResponse' :: ListModelCardsResponse -> [ModelCardSummary]
modelCardSummaries} -> [ModelCardSummary]
modelCardSummaries) (\s :: ListModelCardsResponse
s@ListModelCardsResponse' {} [ModelCardSummary]
a -> ListModelCardsResponse
s {$sel:modelCardSummaries:ListModelCardsResponse' :: [ModelCardSummary]
modelCardSummaries = [ModelCardSummary]
a} :: ListModelCardsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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