{-# 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.ListHubContentVersions
-- 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 hub content versions.
module Amazonka.SageMaker.ListHubContentVersions
  ( -- * Creating a Request
    ListHubContentVersions (..),
    newListHubContentVersions,

    -- * Request Lenses
    listHubContentVersions_creationTimeAfter,
    listHubContentVersions_creationTimeBefore,
    listHubContentVersions_maxResults,
    listHubContentVersions_maxSchemaVersion,
    listHubContentVersions_minVersion,
    listHubContentVersions_nextToken,
    listHubContentVersions_sortBy,
    listHubContentVersions_sortOrder,
    listHubContentVersions_hubName,
    listHubContentVersions_hubContentType,
    listHubContentVersions_hubContentName,

    -- * Destructuring the Response
    ListHubContentVersionsResponse (..),
    newListHubContentVersionsResponse,

    -- * Response Lenses
    listHubContentVersionsResponse_nextToken,
    listHubContentVersionsResponse_httpStatus,
    listHubContentVersionsResponse_hubContentSummaries,
  )
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:/ 'newListHubContentVersions' smart constructor.
data ListHubContentVersions = ListHubContentVersions'
  { -- | Only list hub content versions that were created after the time
    -- specified.
    ListHubContentVersions -> Maybe POSIX
creationTimeAfter :: Prelude.Maybe Data.POSIX,
    -- | Only list hub content versions that were created before the time
    -- specified.
    ListHubContentVersions -> Maybe POSIX
creationTimeBefore :: Prelude.Maybe Data.POSIX,
    -- | The maximum number of hub content versions to list.
    ListHubContentVersions -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The upper bound of the hub content schema version.
    ListHubContentVersions -> Maybe Text
maxSchemaVersion :: Prelude.Maybe Prelude.Text,
    -- | The lower bound of the hub content versions to list.
    ListHubContentVersions -> Maybe Text
minVersion :: Prelude.Maybe Prelude.Text,
    -- | If the response to a previous @ListHubContentVersions@ request was
    -- truncated, the response includes a @NextToken@. To retrieve the next set
    -- of hub content versions, use the token in the next request.
    ListHubContentVersions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Sort hub content versions by either name or creation time.
    ListHubContentVersions -> Maybe HubContentSortBy
sortBy :: Prelude.Maybe HubContentSortBy,
    -- | Sort hub content versions by ascending or descending order.
    ListHubContentVersions -> Maybe SortOrder
sortOrder :: Prelude.Maybe SortOrder,
    -- | The name of the hub to list the content versions of.
    ListHubContentVersions -> Text
hubName :: Prelude.Text,
    -- | The type of hub content to list versions of.
    ListHubContentVersions -> HubContentType
hubContentType :: HubContentType,
    -- | The name of the hub content.
    ListHubContentVersions -> Text
hubContentName :: Prelude.Text
  }
  deriving (ListHubContentVersions -> ListHubContentVersions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListHubContentVersions -> ListHubContentVersions -> Bool
$c/= :: ListHubContentVersions -> ListHubContentVersions -> Bool
== :: ListHubContentVersions -> ListHubContentVersions -> Bool
$c== :: ListHubContentVersions -> ListHubContentVersions -> Bool
Prelude.Eq, ReadPrec [ListHubContentVersions]
ReadPrec ListHubContentVersions
Int -> ReadS ListHubContentVersions
ReadS [ListHubContentVersions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListHubContentVersions]
$creadListPrec :: ReadPrec [ListHubContentVersions]
readPrec :: ReadPrec ListHubContentVersions
$creadPrec :: ReadPrec ListHubContentVersions
readList :: ReadS [ListHubContentVersions]
$creadList :: ReadS [ListHubContentVersions]
readsPrec :: Int -> ReadS ListHubContentVersions
$creadsPrec :: Int -> ReadS ListHubContentVersions
Prelude.Read, Int -> ListHubContentVersions -> ShowS
[ListHubContentVersions] -> ShowS
ListHubContentVersions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListHubContentVersions] -> ShowS
$cshowList :: [ListHubContentVersions] -> ShowS
show :: ListHubContentVersions -> String
$cshow :: ListHubContentVersions -> String
showsPrec :: Int -> ListHubContentVersions -> ShowS
$cshowsPrec :: Int -> ListHubContentVersions -> ShowS
Prelude.Show, forall x. Rep ListHubContentVersions x -> ListHubContentVersions
forall x. ListHubContentVersions -> Rep ListHubContentVersions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListHubContentVersions x -> ListHubContentVersions
$cfrom :: forall x. ListHubContentVersions -> Rep ListHubContentVersions x
Prelude.Generic)

-- |
-- Create a value of 'ListHubContentVersions' 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', 'listHubContentVersions_creationTimeAfter' - Only list hub content versions that were created after the time
-- specified.
--
-- 'creationTimeBefore', 'listHubContentVersions_creationTimeBefore' - Only list hub content versions that were created before the time
-- specified.
--
-- 'maxResults', 'listHubContentVersions_maxResults' - The maximum number of hub content versions to list.
--
-- 'maxSchemaVersion', 'listHubContentVersions_maxSchemaVersion' - The upper bound of the hub content schema version.
--
-- 'minVersion', 'listHubContentVersions_minVersion' - The lower bound of the hub content versions to list.
--
-- 'nextToken', 'listHubContentVersions_nextToken' - If the response to a previous @ListHubContentVersions@ request was
-- truncated, the response includes a @NextToken@. To retrieve the next set
-- of hub content versions, use the token in the next request.
--
-- 'sortBy', 'listHubContentVersions_sortBy' - Sort hub content versions by either name or creation time.
--
-- 'sortOrder', 'listHubContentVersions_sortOrder' - Sort hub content versions by ascending or descending order.
--
-- 'hubName', 'listHubContentVersions_hubName' - The name of the hub to list the content versions of.
--
-- 'hubContentType', 'listHubContentVersions_hubContentType' - The type of hub content to list versions of.
--
-- 'hubContentName', 'listHubContentVersions_hubContentName' - The name of the hub content.
newListHubContentVersions ::
  -- | 'hubName'
  Prelude.Text ->
  -- | 'hubContentType'
  HubContentType ->
  -- | 'hubContentName'
  Prelude.Text ->
  ListHubContentVersions
newListHubContentVersions :: Text -> HubContentType -> Text -> ListHubContentVersions
newListHubContentVersions
  Text
pHubName_
  HubContentType
pHubContentType_
  Text
pHubContentName_ =
    ListHubContentVersions'
      { $sel:creationTimeAfter:ListHubContentVersions' :: Maybe POSIX
creationTimeAfter =
          forall a. Maybe a
Prelude.Nothing,
        $sel:creationTimeBefore:ListHubContentVersions' :: Maybe POSIX
creationTimeBefore = forall a. Maybe a
Prelude.Nothing,
        $sel:maxResults:ListHubContentVersions' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
        $sel:maxSchemaVersion:ListHubContentVersions' :: Maybe Text
maxSchemaVersion = forall a. Maybe a
Prelude.Nothing,
        $sel:minVersion:ListHubContentVersions' :: Maybe Text
minVersion = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListHubContentVersions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:sortBy:ListHubContentVersions' :: Maybe HubContentSortBy
sortBy = forall a. Maybe a
Prelude.Nothing,
        $sel:sortOrder:ListHubContentVersions' :: Maybe SortOrder
sortOrder = forall a. Maybe a
Prelude.Nothing,
        $sel:hubName:ListHubContentVersions' :: Text
hubName = Text
pHubName_,
        $sel:hubContentType:ListHubContentVersions' :: HubContentType
hubContentType = HubContentType
pHubContentType_,
        $sel:hubContentName:ListHubContentVersions' :: Text
hubContentName = Text
pHubContentName_
      }

-- | Only list hub content versions that were created after the time
-- specified.
listHubContentVersions_creationTimeAfter :: Lens.Lens' ListHubContentVersions (Prelude.Maybe Prelude.UTCTime)
listHubContentVersions_creationTimeAfter :: Lens' ListHubContentVersions (Maybe UTCTime)
listHubContentVersions_creationTimeAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHubContentVersions' {Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:creationTimeAfter:ListHubContentVersions' :: ListHubContentVersions -> Maybe POSIX
creationTimeAfter} -> Maybe POSIX
creationTimeAfter) (\s :: ListHubContentVersions
s@ListHubContentVersions' {} Maybe POSIX
a -> ListHubContentVersions
s {$sel:creationTimeAfter:ListHubContentVersions' :: Maybe POSIX
creationTimeAfter = Maybe POSIX
a} :: ListHubContentVersions) 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 hub content versions that were created before the time
-- specified.
listHubContentVersions_creationTimeBefore :: Lens.Lens' ListHubContentVersions (Prelude.Maybe Prelude.UTCTime)
listHubContentVersions_creationTimeBefore :: Lens' ListHubContentVersions (Maybe UTCTime)
listHubContentVersions_creationTimeBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHubContentVersions' {Maybe POSIX
creationTimeBefore :: Maybe POSIX
$sel:creationTimeBefore:ListHubContentVersions' :: ListHubContentVersions -> Maybe POSIX
creationTimeBefore} -> Maybe POSIX
creationTimeBefore) (\s :: ListHubContentVersions
s@ListHubContentVersions' {} Maybe POSIX
a -> ListHubContentVersions
s {$sel:creationTimeBefore:ListHubContentVersions' :: Maybe POSIX
creationTimeBefore = Maybe POSIX
a} :: ListHubContentVersions) 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 hub content versions to list.
listHubContentVersions_maxResults :: Lens.Lens' ListHubContentVersions (Prelude.Maybe Prelude.Natural)
listHubContentVersions_maxResults :: Lens' ListHubContentVersions (Maybe Natural)
listHubContentVersions_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHubContentVersions' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListHubContentVersions' :: ListHubContentVersions -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListHubContentVersions
s@ListHubContentVersions' {} Maybe Natural
a -> ListHubContentVersions
s {$sel:maxResults:ListHubContentVersions' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListHubContentVersions)

-- | The upper bound of the hub content schema version.
listHubContentVersions_maxSchemaVersion :: Lens.Lens' ListHubContentVersions (Prelude.Maybe Prelude.Text)
listHubContentVersions_maxSchemaVersion :: Lens' ListHubContentVersions (Maybe Text)
listHubContentVersions_maxSchemaVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHubContentVersions' {Maybe Text
maxSchemaVersion :: Maybe Text
$sel:maxSchemaVersion:ListHubContentVersions' :: ListHubContentVersions -> Maybe Text
maxSchemaVersion} -> Maybe Text
maxSchemaVersion) (\s :: ListHubContentVersions
s@ListHubContentVersions' {} Maybe Text
a -> ListHubContentVersions
s {$sel:maxSchemaVersion:ListHubContentVersions' :: Maybe Text
maxSchemaVersion = Maybe Text
a} :: ListHubContentVersions)

-- | The lower bound of the hub content versions to list.
listHubContentVersions_minVersion :: Lens.Lens' ListHubContentVersions (Prelude.Maybe Prelude.Text)
listHubContentVersions_minVersion :: Lens' ListHubContentVersions (Maybe Text)
listHubContentVersions_minVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHubContentVersions' {Maybe Text
minVersion :: Maybe Text
$sel:minVersion:ListHubContentVersions' :: ListHubContentVersions -> Maybe Text
minVersion} -> Maybe Text
minVersion) (\s :: ListHubContentVersions
s@ListHubContentVersions' {} Maybe Text
a -> ListHubContentVersions
s {$sel:minVersion:ListHubContentVersions' :: Maybe Text
minVersion = Maybe Text
a} :: ListHubContentVersions)

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

-- | Sort hub content versions by either name or creation time.
listHubContentVersions_sortBy :: Lens.Lens' ListHubContentVersions (Prelude.Maybe HubContentSortBy)
listHubContentVersions_sortBy :: Lens' ListHubContentVersions (Maybe HubContentSortBy)
listHubContentVersions_sortBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHubContentVersions' {Maybe HubContentSortBy
sortBy :: Maybe HubContentSortBy
$sel:sortBy:ListHubContentVersions' :: ListHubContentVersions -> Maybe HubContentSortBy
sortBy} -> Maybe HubContentSortBy
sortBy) (\s :: ListHubContentVersions
s@ListHubContentVersions' {} Maybe HubContentSortBy
a -> ListHubContentVersions
s {$sel:sortBy:ListHubContentVersions' :: Maybe HubContentSortBy
sortBy = Maybe HubContentSortBy
a} :: ListHubContentVersions)

-- | Sort hub content versions by ascending or descending order.
listHubContentVersions_sortOrder :: Lens.Lens' ListHubContentVersions (Prelude.Maybe SortOrder)
listHubContentVersions_sortOrder :: Lens' ListHubContentVersions (Maybe SortOrder)
listHubContentVersions_sortOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHubContentVersions' {Maybe SortOrder
sortOrder :: Maybe SortOrder
$sel:sortOrder:ListHubContentVersions' :: ListHubContentVersions -> Maybe SortOrder
sortOrder} -> Maybe SortOrder
sortOrder) (\s :: ListHubContentVersions
s@ListHubContentVersions' {} Maybe SortOrder
a -> ListHubContentVersions
s {$sel:sortOrder:ListHubContentVersions' :: Maybe SortOrder
sortOrder = Maybe SortOrder
a} :: ListHubContentVersions)

-- | The name of the hub to list the content versions of.
listHubContentVersions_hubName :: Lens.Lens' ListHubContentVersions Prelude.Text
listHubContentVersions_hubName :: Lens' ListHubContentVersions Text
listHubContentVersions_hubName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHubContentVersions' {Text
hubName :: Text
$sel:hubName:ListHubContentVersions' :: ListHubContentVersions -> Text
hubName} -> Text
hubName) (\s :: ListHubContentVersions
s@ListHubContentVersions' {} Text
a -> ListHubContentVersions
s {$sel:hubName:ListHubContentVersions' :: Text
hubName = Text
a} :: ListHubContentVersions)

-- | The type of hub content to list versions of.
listHubContentVersions_hubContentType :: Lens.Lens' ListHubContentVersions HubContentType
listHubContentVersions_hubContentType :: Lens' ListHubContentVersions HubContentType
listHubContentVersions_hubContentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHubContentVersions' {HubContentType
hubContentType :: HubContentType
$sel:hubContentType:ListHubContentVersions' :: ListHubContentVersions -> HubContentType
hubContentType} -> HubContentType
hubContentType) (\s :: ListHubContentVersions
s@ListHubContentVersions' {} HubContentType
a -> ListHubContentVersions
s {$sel:hubContentType:ListHubContentVersions' :: HubContentType
hubContentType = HubContentType
a} :: ListHubContentVersions)

-- | The name of the hub content.
listHubContentVersions_hubContentName :: Lens.Lens' ListHubContentVersions Prelude.Text
listHubContentVersions_hubContentName :: Lens' ListHubContentVersions Text
listHubContentVersions_hubContentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHubContentVersions' {Text
hubContentName :: Text
$sel:hubContentName:ListHubContentVersions' :: ListHubContentVersions -> Text
hubContentName} -> Text
hubContentName) (\s :: ListHubContentVersions
s@ListHubContentVersions' {} Text
a -> ListHubContentVersions
s {$sel:hubContentName:ListHubContentVersions' :: Text
hubContentName = Text
a} :: ListHubContentVersions)

instance Core.AWSRequest ListHubContentVersions where
  type
    AWSResponse ListHubContentVersions =
      ListHubContentVersionsResponse
  request :: (Service -> Service)
-> ListHubContentVersions -> Request ListHubContentVersions
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 ListHubContentVersions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListHubContentVersions)))
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 -> [HubContentInfo] -> ListHubContentVersionsResponse
ListHubContentVersionsResponse'
            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
"HubContentSummaries"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable ListHubContentVersions where
  hashWithSalt :: Int -> ListHubContentVersions -> Int
hashWithSalt Int
_salt ListHubContentVersions' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe HubContentSortBy
Maybe SortOrder
Text
HubContentType
hubContentName :: Text
hubContentType :: HubContentType
hubName :: Text
sortOrder :: Maybe SortOrder
sortBy :: Maybe HubContentSortBy
nextToken :: Maybe Text
minVersion :: Maybe Text
maxSchemaVersion :: Maybe Text
maxResults :: Maybe Natural
creationTimeBefore :: Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:hubContentName:ListHubContentVersions' :: ListHubContentVersions -> Text
$sel:hubContentType:ListHubContentVersions' :: ListHubContentVersions -> HubContentType
$sel:hubName:ListHubContentVersions' :: ListHubContentVersions -> Text
$sel:sortOrder:ListHubContentVersions' :: ListHubContentVersions -> Maybe SortOrder
$sel:sortBy:ListHubContentVersions' :: ListHubContentVersions -> Maybe HubContentSortBy
$sel:nextToken:ListHubContentVersions' :: ListHubContentVersions -> Maybe Text
$sel:minVersion:ListHubContentVersions' :: ListHubContentVersions -> Maybe Text
$sel:maxSchemaVersion:ListHubContentVersions' :: ListHubContentVersions -> Maybe Text
$sel:maxResults:ListHubContentVersions' :: ListHubContentVersions -> Maybe Natural
$sel:creationTimeBefore:ListHubContentVersions' :: ListHubContentVersions -> Maybe POSIX
$sel:creationTimeAfter:ListHubContentVersions' :: ListHubContentVersions -> 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
maxSchemaVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
minVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HubContentSortBy
sortBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortOrder
sortOrder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
hubName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HubContentType
hubContentType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
hubContentName

instance Prelude.NFData ListHubContentVersions where
  rnf :: ListHubContentVersions -> ()
rnf ListHubContentVersions' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe HubContentSortBy
Maybe SortOrder
Text
HubContentType
hubContentName :: Text
hubContentType :: HubContentType
hubName :: Text
sortOrder :: Maybe SortOrder
sortBy :: Maybe HubContentSortBy
nextToken :: Maybe Text
minVersion :: Maybe Text
maxSchemaVersion :: Maybe Text
maxResults :: Maybe Natural
creationTimeBefore :: Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:hubContentName:ListHubContentVersions' :: ListHubContentVersions -> Text
$sel:hubContentType:ListHubContentVersions' :: ListHubContentVersions -> HubContentType
$sel:hubName:ListHubContentVersions' :: ListHubContentVersions -> Text
$sel:sortOrder:ListHubContentVersions' :: ListHubContentVersions -> Maybe SortOrder
$sel:sortBy:ListHubContentVersions' :: ListHubContentVersions -> Maybe HubContentSortBy
$sel:nextToken:ListHubContentVersions' :: ListHubContentVersions -> Maybe Text
$sel:minVersion:ListHubContentVersions' :: ListHubContentVersions -> Maybe Text
$sel:maxSchemaVersion:ListHubContentVersions' :: ListHubContentVersions -> Maybe Text
$sel:maxResults:ListHubContentVersions' :: ListHubContentVersions -> Maybe Natural
$sel:creationTimeBefore:ListHubContentVersions' :: ListHubContentVersions -> Maybe POSIX
$sel:creationTimeAfter:ListHubContentVersions' :: ListHubContentVersions -> 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
maxSchemaVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
minVersion
      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 HubContentSortBy
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
hubName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf HubContentType
hubContentType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
hubContentName

instance Data.ToHeaders ListHubContentVersions where
  toHeaders :: ListHubContentVersions -> 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.ListHubContentVersions" ::
                          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 ListHubContentVersions where
  toJSON :: ListHubContentVersions -> Value
toJSON ListHubContentVersions' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe HubContentSortBy
Maybe SortOrder
Text
HubContentType
hubContentName :: Text
hubContentType :: HubContentType
hubName :: Text
sortOrder :: Maybe SortOrder
sortBy :: Maybe HubContentSortBy
nextToken :: Maybe Text
minVersion :: Maybe Text
maxSchemaVersion :: Maybe Text
maxResults :: Maybe Natural
creationTimeBefore :: Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:hubContentName:ListHubContentVersions' :: ListHubContentVersions -> Text
$sel:hubContentType:ListHubContentVersions' :: ListHubContentVersions -> HubContentType
$sel:hubName:ListHubContentVersions' :: ListHubContentVersions -> Text
$sel:sortOrder:ListHubContentVersions' :: ListHubContentVersions -> Maybe SortOrder
$sel:sortBy:ListHubContentVersions' :: ListHubContentVersions -> Maybe HubContentSortBy
$sel:nextToken:ListHubContentVersions' :: ListHubContentVersions -> Maybe Text
$sel:minVersion:ListHubContentVersions' :: ListHubContentVersions -> Maybe Text
$sel:maxSchemaVersion:ListHubContentVersions' :: ListHubContentVersions -> Maybe Text
$sel:maxResults:ListHubContentVersions' :: ListHubContentVersions -> Maybe Natural
$sel:creationTimeBefore:ListHubContentVersions' :: ListHubContentVersions -> Maybe POSIX
$sel:creationTimeAfter:ListHubContentVersions' :: ListHubContentVersions -> 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
"MaxSchemaVersion" 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
maxSchemaVersion,
            (Key
"MinVersion" 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
minVersion,
            (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 HubContentSortBy
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
"HubName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
hubName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"HubContentType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= HubContentType
hubContentType),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"HubContentName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
hubContentName)
          ]
      )

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

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

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

-- |
-- Create a value of 'ListHubContentVersionsResponse' 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', 'listHubContentVersionsResponse_nextToken' - If the response is truncated, SageMaker returns this token. To retrieve
-- the next set of hub content versions, use it in the subsequent request.
--
-- 'httpStatus', 'listHubContentVersionsResponse_httpStatus' - The response's http status code.
--
-- 'hubContentSummaries', 'listHubContentVersionsResponse_hubContentSummaries' - The summaries of the listed hub content versions.
newListHubContentVersionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListHubContentVersionsResponse
newListHubContentVersionsResponse :: Int -> ListHubContentVersionsResponse
newListHubContentVersionsResponse Int
pHttpStatus_ =
  ListHubContentVersionsResponse'
    { $sel:nextToken:ListHubContentVersionsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListHubContentVersionsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:hubContentSummaries:ListHubContentVersionsResponse' :: [HubContentInfo]
hubContentSummaries = forall a. Monoid a => a
Prelude.mempty
    }

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

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

-- | The summaries of the listed hub content versions.
listHubContentVersionsResponse_hubContentSummaries :: Lens.Lens' ListHubContentVersionsResponse [HubContentInfo]
listHubContentVersionsResponse_hubContentSummaries :: Lens' ListHubContentVersionsResponse [HubContentInfo]
listHubContentVersionsResponse_hubContentSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHubContentVersionsResponse' {[HubContentInfo]
hubContentSummaries :: [HubContentInfo]
$sel:hubContentSummaries:ListHubContentVersionsResponse' :: ListHubContentVersionsResponse -> [HubContentInfo]
hubContentSummaries} -> [HubContentInfo]
hubContentSummaries) (\s :: ListHubContentVersionsResponse
s@ListHubContentVersionsResponse' {} [HubContentInfo]
a -> ListHubContentVersionsResponse
s {$sel:hubContentSummaries:ListHubContentVersionsResponse' :: [HubContentInfo]
hubContentSummaries = [HubContentInfo]
a} :: ListHubContentVersionsResponse) 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
    ListHubContentVersionsResponse
  where
  rnf :: ListHubContentVersionsResponse -> ()
rnf ListHubContentVersionsResponse' {Int
[HubContentInfo]
Maybe Text
hubContentSummaries :: [HubContentInfo]
httpStatus :: Int
nextToken :: Maybe Text
$sel:hubContentSummaries:ListHubContentVersionsResponse' :: ListHubContentVersionsResponse -> [HubContentInfo]
$sel:httpStatus:ListHubContentVersionsResponse' :: ListHubContentVersionsResponse -> Int
$sel:nextToken:ListHubContentVersionsResponse' :: ListHubContentVersionsResponse -> 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 [HubContentInfo]
hubContentSummaries