{-# 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.ListModelPackageGroups
-- 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 model groups in your Amazon Web Services account.
--
-- This operation returns paginated results.
module Amazonka.SageMaker.ListModelPackageGroups
  ( -- * Creating a Request
    ListModelPackageGroups (..),
    newListModelPackageGroups,

    -- * Request Lenses
    listModelPackageGroups_creationTimeAfter,
    listModelPackageGroups_creationTimeBefore,
    listModelPackageGroups_maxResults,
    listModelPackageGroups_nameContains,
    listModelPackageGroups_nextToken,
    listModelPackageGroups_sortBy,
    listModelPackageGroups_sortOrder,

    -- * Destructuring the Response
    ListModelPackageGroupsResponse (..),
    newListModelPackageGroupsResponse,

    -- * Response Lenses
    listModelPackageGroupsResponse_nextToken,
    listModelPackageGroupsResponse_httpStatus,
    listModelPackageGroupsResponse_modelPackageGroupSummaryList,
  )
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:/ 'newListModelPackageGroups' smart constructor.
data ListModelPackageGroups = ListModelPackageGroups'
  { -- | A filter that returns only model groups created after the specified
    -- time.
    ListModelPackageGroups -> Maybe POSIX
creationTimeAfter :: Prelude.Maybe Data.POSIX,
    -- | A filter that returns only model groups created before the specified
    -- time.
    ListModelPackageGroups -> Maybe POSIX
creationTimeBefore :: Prelude.Maybe Data.POSIX,
    -- | The maximum number of results to return in the response.
    ListModelPackageGroups -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A string in the model group name. This filter returns only model groups
    -- whose name contains the specified string.
    ListModelPackageGroups -> Maybe Text
nameContains :: Prelude.Maybe Prelude.Text,
    -- | If the result of the previous @ListModelPackageGroups@ request was
    -- truncated, the response includes a @NextToken@. To retrieve the next set
    -- of model groups, use the token in the next request.
    ListModelPackageGroups -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The field to sort results by. The default is @CreationTime@.
    ListModelPackageGroups -> Maybe ModelPackageGroupSortBy
sortBy :: Prelude.Maybe ModelPackageGroupSortBy,
    -- | The sort order for results. The default is @Ascending@.
    ListModelPackageGroups -> Maybe SortOrder
sortOrder :: Prelude.Maybe SortOrder
  }
  deriving (ListModelPackageGroups -> ListModelPackageGroups -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListModelPackageGroups -> ListModelPackageGroups -> Bool
$c/= :: ListModelPackageGroups -> ListModelPackageGroups -> Bool
== :: ListModelPackageGroups -> ListModelPackageGroups -> Bool
$c== :: ListModelPackageGroups -> ListModelPackageGroups -> Bool
Prelude.Eq, ReadPrec [ListModelPackageGroups]
ReadPrec ListModelPackageGroups
Int -> ReadS ListModelPackageGroups
ReadS [ListModelPackageGroups]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListModelPackageGroups]
$creadListPrec :: ReadPrec [ListModelPackageGroups]
readPrec :: ReadPrec ListModelPackageGroups
$creadPrec :: ReadPrec ListModelPackageGroups
readList :: ReadS [ListModelPackageGroups]
$creadList :: ReadS [ListModelPackageGroups]
readsPrec :: Int -> ReadS ListModelPackageGroups
$creadsPrec :: Int -> ReadS ListModelPackageGroups
Prelude.Read, Int -> ListModelPackageGroups -> ShowS
[ListModelPackageGroups] -> ShowS
ListModelPackageGroups -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListModelPackageGroups] -> ShowS
$cshowList :: [ListModelPackageGroups] -> ShowS
show :: ListModelPackageGroups -> String
$cshow :: ListModelPackageGroups -> String
showsPrec :: Int -> ListModelPackageGroups -> ShowS
$cshowsPrec :: Int -> ListModelPackageGroups -> ShowS
Prelude.Show, forall x. Rep ListModelPackageGroups x -> ListModelPackageGroups
forall x. ListModelPackageGroups -> Rep ListModelPackageGroups x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListModelPackageGroups x -> ListModelPackageGroups
$cfrom :: forall x. ListModelPackageGroups -> Rep ListModelPackageGroups x
Prelude.Generic)

-- |
-- Create a value of 'ListModelPackageGroups' 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', 'listModelPackageGroups_creationTimeAfter' - A filter that returns only model groups created after the specified
-- time.
--
-- 'creationTimeBefore', 'listModelPackageGroups_creationTimeBefore' - A filter that returns only model groups created before the specified
-- time.
--
-- 'maxResults', 'listModelPackageGroups_maxResults' - The maximum number of results to return in the response.
--
-- 'nameContains', 'listModelPackageGroups_nameContains' - A string in the model group name. This filter returns only model groups
-- whose name contains the specified string.
--
-- 'nextToken', 'listModelPackageGroups_nextToken' - If the result of the previous @ListModelPackageGroups@ request was
-- truncated, the response includes a @NextToken@. To retrieve the next set
-- of model groups, use the token in the next request.
--
-- 'sortBy', 'listModelPackageGroups_sortBy' - The field to sort results by. The default is @CreationTime@.
--
-- 'sortOrder', 'listModelPackageGroups_sortOrder' - The sort order for results. The default is @Ascending@.
newListModelPackageGroups ::
  ListModelPackageGroups
newListModelPackageGroups :: ListModelPackageGroups
newListModelPackageGroups =
  ListModelPackageGroups'
    { $sel:creationTimeAfter:ListModelPackageGroups' :: Maybe POSIX
creationTimeAfter =
        forall a. Maybe a
Prelude.Nothing,
      $sel:creationTimeBefore:ListModelPackageGroups' :: Maybe POSIX
creationTimeBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListModelPackageGroups' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nameContains:ListModelPackageGroups' :: Maybe Text
nameContains = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListModelPackageGroups' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortBy:ListModelPackageGroups' :: Maybe ModelPackageGroupSortBy
sortBy = forall a. Maybe a
Prelude.Nothing,
      $sel:sortOrder:ListModelPackageGroups' :: Maybe SortOrder
sortOrder = forall a. Maybe a
Prelude.Nothing
    }

-- | A filter that returns only model groups created after the specified
-- time.
listModelPackageGroups_creationTimeAfter :: Lens.Lens' ListModelPackageGroups (Prelude.Maybe Prelude.UTCTime)
listModelPackageGroups_creationTimeAfter :: Lens' ListModelPackageGroups (Maybe UTCTime)
listModelPackageGroups_creationTimeAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelPackageGroups' {Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:creationTimeAfter:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe POSIX
creationTimeAfter} -> Maybe POSIX
creationTimeAfter) (\s :: ListModelPackageGroups
s@ListModelPackageGroups' {} Maybe POSIX
a -> ListModelPackageGroups
s {$sel:creationTimeAfter:ListModelPackageGroups' :: Maybe POSIX
creationTimeAfter = Maybe POSIX
a} :: ListModelPackageGroups) 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 only model groups created before the specified
-- time.
listModelPackageGroups_creationTimeBefore :: Lens.Lens' ListModelPackageGroups (Prelude.Maybe Prelude.UTCTime)
listModelPackageGroups_creationTimeBefore :: Lens' ListModelPackageGroups (Maybe UTCTime)
listModelPackageGroups_creationTimeBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelPackageGroups' {Maybe POSIX
creationTimeBefore :: Maybe POSIX
$sel:creationTimeBefore:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe POSIX
creationTimeBefore} -> Maybe POSIX
creationTimeBefore) (\s :: ListModelPackageGroups
s@ListModelPackageGroups' {} Maybe POSIX
a -> ListModelPackageGroups
s {$sel:creationTimeBefore:ListModelPackageGroups' :: Maybe POSIX
creationTimeBefore = Maybe POSIX
a} :: ListModelPackageGroups) 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 results to return in the response.
listModelPackageGroups_maxResults :: Lens.Lens' ListModelPackageGroups (Prelude.Maybe Prelude.Natural)
listModelPackageGroups_maxResults :: Lens' ListModelPackageGroups (Maybe Natural)
listModelPackageGroups_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelPackageGroups' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListModelPackageGroups
s@ListModelPackageGroups' {} Maybe Natural
a -> ListModelPackageGroups
s {$sel:maxResults:ListModelPackageGroups' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListModelPackageGroups)

-- | A string in the model group name. This filter returns only model groups
-- whose name contains the specified string.
listModelPackageGroups_nameContains :: Lens.Lens' ListModelPackageGroups (Prelude.Maybe Prelude.Text)
listModelPackageGroups_nameContains :: Lens' ListModelPackageGroups (Maybe Text)
listModelPackageGroups_nameContains = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelPackageGroups' {Maybe Text
nameContains :: Maybe Text
$sel:nameContains:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe Text
nameContains} -> Maybe Text
nameContains) (\s :: ListModelPackageGroups
s@ListModelPackageGroups' {} Maybe Text
a -> ListModelPackageGroups
s {$sel:nameContains:ListModelPackageGroups' :: Maybe Text
nameContains = Maybe Text
a} :: ListModelPackageGroups)

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

-- | The field to sort results by. The default is @CreationTime@.
listModelPackageGroups_sortBy :: Lens.Lens' ListModelPackageGroups (Prelude.Maybe ModelPackageGroupSortBy)
listModelPackageGroups_sortBy :: Lens' ListModelPackageGroups (Maybe ModelPackageGroupSortBy)
listModelPackageGroups_sortBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelPackageGroups' {Maybe ModelPackageGroupSortBy
sortBy :: Maybe ModelPackageGroupSortBy
$sel:sortBy:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe ModelPackageGroupSortBy
sortBy} -> Maybe ModelPackageGroupSortBy
sortBy) (\s :: ListModelPackageGroups
s@ListModelPackageGroups' {} Maybe ModelPackageGroupSortBy
a -> ListModelPackageGroups
s {$sel:sortBy:ListModelPackageGroups' :: Maybe ModelPackageGroupSortBy
sortBy = Maybe ModelPackageGroupSortBy
a} :: ListModelPackageGroups)

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

instance Core.AWSPager ListModelPackageGroups where
  page :: ListModelPackageGroups
-> AWSResponse ListModelPackageGroups
-> Maybe ListModelPackageGroups
page ListModelPackageGroups
rq AWSResponse ListModelPackageGroups
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListModelPackageGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListModelPackageGroupsResponse (Maybe Text)
listModelPackageGroupsResponse_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 ListModelPackageGroups
rs
            forall s a. s -> Getting a s a -> a
Lens.^. Lens' ListModelPackageGroupsResponse [ModelPackageGroupSummary]
listModelPackageGroupsResponse_modelPackageGroupSummaryList
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListModelPackageGroups
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListModelPackageGroups (Maybe Text)
listModelPackageGroups_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListModelPackageGroups
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListModelPackageGroupsResponse (Maybe Text)
listModelPackageGroupsResponse_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 ListModelPackageGroups where
  type
    AWSResponse ListModelPackageGroups =
      ListModelPackageGroupsResponse
  request :: (Service -> Service)
-> ListModelPackageGroups -> Request ListModelPackageGroups
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 ListModelPackageGroups
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListModelPackageGroups)))
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
-> [ModelPackageGroupSummary]
-> ListModelPackageGroupsResponse
ListModelPackageGroupsResponse'
            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
"ModelPackageGroupSummaryList"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable ListModelPackageGroups where
  hashWithSalt :: Int -> ListModelPackageGroups -> Int
hashWithSalt Int
_salt ListModelPackageGroups' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe ModelPackageGroupSortBy
Maybe SortOrder
sortOrder :: Maybe SortOrder
sortBy :: Maybe ModelPackageGroupSortBy
nextToken :: Maybe Text
nameContains :: Maybe Text
maxResults :: Maybe Natural
creationTimeBefore :: Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:sortOrder:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe SortOrder
$sel:sortBy:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe ModelPackageGroupSortBy
$sel:nextToken:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe Text
$sel:nameContains:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe Text
$sel:maxResults:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe Natural
$sel:creationTimeBefore:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe POSIX
$sel:creationTimeAfter:ListModelPackageGroups' :: ListModelPackageGroups -> 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 Text
nameContains
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ModelPackageGroupSortBy
sortBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortOrder
sortOrder

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

instance Data.ToHeaders ListModelPackageGroups where
  toHeaders :: ListModelPackageGroups -> 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.ListModelPackageGroups" ::
                          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 ListModelPackageGroups where
  toJSON :: ListModelPackageGroups -> Value
toJSON ListModelPackageGroups' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe ModelPackageGroupSortBy
Maybe SortOrder
sortOrder :: Maybe SortOrder
sortBy :: Maybe ModelPackageGroupSortBy
nextToken :: Maybe Text
nameContains :: Maybe Text
maxResults :: Maybe Natural
creationTimeBefore :: Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:sortOrder:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe SortOrder
$sel:sortBy:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe ModelPackageGroupSortBy
$sel:nextToken:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe Text
$sel:nameContains:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe Text
$sel:maxResults:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe Natural
$sel:creationTimeBefore:ListModelPackageGroups' :: ListModelPackageGroups -> Maybe POSIX
$sel:creationTimeAfter:ListModelPackageGroups' :: ListModelPackageGroups -> 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
"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 ModelPackageGroupSortBy
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
          ]
      )

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

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

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

-- |
-- Create a value of 'ListModelPackageGroupsResponse' 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', 'listModelPackageGroupsResponse_nextToken' - If the response is truncated, SageMaker returns this token. To retrieve
-- the next set of model groups, use it in the subsequent request.
--
-- 'httpStatus', 'listModelPackageGroupsResponse_httpStatus' - The response's http status code.
--
-- 'modelPackageGroupSummaryList', 'listModelPackageGroupsResponse_modelPackageGroupSummaryList' - A list of summaries of the model groups in your Amazon Web Services
-- account.
newListModelPackageGroupsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListModelPackageGroupsResponse
newListModelPackageGroupsResponse :: Int -> ListModelPackageGroupsResponse
newListModelPackageGroupsResponse Int
pHttpStatus_ =
  ListModelPackageGroupsResponse'
    { $sel:nextToken:ListModelPackageGroupsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListModelPackageGroupsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:modelPackageGroupSummaryList:ListModelPackageGroupsResponse' :: [ModelPackageGroupSummary]
modelPackageGroupSummaryList =
        forall a. Monoid a => a
Prelude.mempty
    }

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

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

-- | A list of summaries of the model groups in your Amazon Web Services
-- account.
listModelPackageGroupsResponse_modelPackageGroupSummaryList :: Lens.Lens' ListModelPackageGroupsResponse [ModelPackageGroupSummary]
listModelPackageGroupsResponse_modelPackageGroupSummaryList :: Lens' ListModelPackageGroupsResponse [ModelPackageGroupSummary]
listModelPackageGroupsResponse_modelPackageGroupSummaryList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListModelPackageGroupsResponse' {[ModelPackageGroupSummary]
modelPackageGroupSummaryList :: [ModelPackageGroupSummary]
$sel:modelPackageGroupSummaryList:ListModelPackageGroupsResponse' :: ListModelPackageGroupsResponse -> [ModelPackageGroupSummary]
modelPackageGroupSummaryList} -> [ModelPackageGroupSummary]
modelPackageGroupSummaryList) (\s :: ListModelPackageGroupsResponse
s@ListModelPackageGroupsResponse' {} [ModelPackageGroupSummary]
a -> ListModelPackageGroupsResponse
s {$sel:modelPackageGroupSummaryList:ListModelPackageGroupsResponse' :: [ModelPackageGroupSummary]
modelPackageGroupSummaryList = [ModelPackageGroupSummary]
a} :: ListModelPackageGroupsResponse) 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
    ListModelPackageGroupsResponse
  where
  rnf :: ListModelPackageGroupsResponse -> ()
rnf ListModelPackageGroupsResponse' {Int
[ModelPackageGroupSummary]
Maybe Text
modelPackageGroupSummaryList :: [ModelPackageGroupSummary]
httpStatus :: Int
nextToken :: Maybe Text
$sel:modelPackageGroupSummaryList:ListModelPackageGroupsResponse' :: ListModelPackageGroupsResponse -> [ModelPackageGroupSummary]
$sel:httpStatus:ListModelPackageGroupsResponse' :: ListModelPackageGroupsResponse -> Int
$sel:nextToken:ListModelPackageGroupsResponse' :: ListModelPackageGroupsResponse -> 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 [ModelPackageGroupSummary]
modelPackageGroupSummaryList