{-# 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.Rekognition.DescribeProjectVersions
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists and describes the versions of a model in an Amazon Rekognition
-- Custom Labels project. You can specify up to 10 model versions in
-- @ProjectVersionArns@. If you don\'t specify a value, descriptions for
-- all model versions in the project are returned.
--
-- This operation requires permissions to perform the
-- @rekognition:DescribeProjectVersions@ action.
--
-- This operation returns paginated results.
module Amazonka.Rekognition.DescribeProjectVersions
  ( -- * Creating a Request
    DescribeProjectVersions (..),
    newDescribeProjectVersions,

    -- * Request Lenses
    describeProjectVersions_maxResults,
    describeProjectVersions_nextToken,
    describeProjectVersions_versionNames,
    describeProjectVersions_projectArn,

    -- * Destructuring the Response
    DescribeProjectVersionsResponse (..),
    newDescribeProjectVersionsResponse,

    -- * Response Lenses
    describeProjectVersionsResponse_nextToken,
    describeProjectVersionsResponse_projectVersionDescriptions,
    describeProjectVersionsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.Rekognition.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeProjectVersions' smart constructor.
data DescribeProjectVersions = DescribeProjectVersions'
  { -- | The maximum number of results to return per paginated call. The largest
    -- value you can specify is 100. If you specify a value greater than 100, a
    -- ValidationException error occurs. The default value is 100.
    DescribeProjectVersions -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the previous response was incomplete (because there is more results
    -- to retrieve), Amazon Rekognition Custom Labels returns a pagination
    -- token in the response. You can use this pagination token to retrieve the
    -- next set of results.
    DescribeProjectVersions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of model version names that you want to describe. You can add up
    -- to 10 model version names to the list. If you don\'t specify a value,
    -- all model descriptions are returned. A version name is part of a model
    -- (ProjectVersion) ARN. For example, @my-model.2020-01-21T09.10.15@ is the
    -- version name in the following ARN.
    -- @arn:aws:rekognition:us-east-1:123456789012:project\/getting-started\/version\/@/@my-model.2020-01-21T09.10.15@/@\/1234567890123@.
    DescribeProjectVersions -> Maybe (NonEmpty Text)
versionNames :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The Amazon Resource Name (ARN) of the project that contains the models
    -- you want to describe.
    DescribeProjectVersions -> Text
projectArn :: Prelude.Text
  }
  deriving (DescribeProjectVersions -> DescribeProjectVersions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeProjectVersions -> DescribeProjectVersions -> Bool
$c/= :: DescribeProjectVersions -> DescribeProjectVersions -> Bool
== :: DescribeProjectVersions -> DescribeProjectVersions -> Bool
$c== :: DescribeProjectVersions -> DescribeProjectVersions -> Bool
Prelude.Eq, ReadPrec [DescribeProjectVersions]
ReadPrec DescribeProjectVersions
Int -> ReadS DescribeProjectVersions
ReadS [DescribeProjectVersions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeProjectVersions]
$creadListPrec :: ReadPrec [DescribeProjectVersions]
readPrec :: ReadPrec DescribeProjectVersions
$creadPrec :: ReadPrec DescribeProjectVersions
readList :: ReadS [DescribeProjectVersions]
$creadList :: ReadS [DescribeProjectVersions]
readsPrec :: Int -> ReadS DescribeProjectVersions
$creadsPrec :: Int -> ReadS DescribeProjectVersions
Prelude.Read, Int -> DescribeProjectVersions -> ShowS
[DescribeProjectVersions] -> ShowS
DescribeProjectVersions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeProjectVersions] -> ShowS
$cshowList :: [DescribeProjectVersions] -> ShowS
show :: DescribeProjectVersions -> String
$cshow :: DescribeProjectVersions -> String
showsPrec :: Int -> DescribeProjectVersions -> ShowS
$cshowsPrec :: Int -> DescribeProjectVersions -> ShowS
Prelude.Show, forall x. Rep DescribeProjectVersions x -> DescribeProjectVersions
forall x. DescribeProjectVersions -> Rep DescribeProjectVersions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeProjectVersions x -> DescribeProjectVersions
$cfrom :: forall x. DescribeProjectVersions -> Rep DescribeProjectVersions x
Prelude.Generic)

-- |
-- Create a value of 'DescribeProjectVersions' 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:
--
-- 'maxResults', 'describeProjectVersions_maxResults' - The maximum number of results to return per paginated call. The largest
-- value you can specify is 100. If you specify a value greater than 100, a
-- ValidationException error occurs. The default value is 100.
--
-- 'nextToken', 'describeProjectVersions_nextToken' - If the previous response was incomplete (because there is more results
-- to retrieve), Amazon Rekognition Custom Labels returns a pagination
-- token in the response. You can use this pagination token to retrieve the
-- next set of results.
--
-- 'versionNames', 'describeProjectVersions_versionNames' - A list of model version names that you want to describe. You can add up
-- to 10 model version names to the list. If you don\'t specify a value,
-- all model descriptions are returned. A version name is part of a model
-- (ProjectVersion) ARN. For example, @my-model.2020-01-21T09.10.15@ is the
-- version name in the following ARN.
-- @arn:aws:rekognition:us-east-1:123456789012:project\/getting-started\/version\/@/@my-model.2020-01-21T09.10.15@/@\/1234567890123@.
--
-- 'projectArn', 'describeProjectVersions_projectArn' - The Amazon Resource Name (ARN) of the project that contains the models
-- you want to describe.
newDescribeProjectVersions ::
  -- | 'projectArn'
  Prelude.Text ->
  DescribeProjectVersions
newDescribeProjectVersions :: Text -> DescribeProjectVersions
newDescribeProjectVersions Text
pProjectArn_ =
  DescribeProjectVersions'
    { $sel:maxResults:DescribeProjectVersions' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeProjectVersions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:versionNames:DescribeProjectVersions' :: Maybe (NonEmpty Text)
versionNames = forall a. Maybe a
Prelude.Nothing,
      $sel:projectArn:DescribeProjectVersions' :: Text
projectArn = Text
pProjectArn_
    }

-- | The maximum number of results to return per paginated call. The largest
-- value you can specify is 100. If you specify a value greater than 100, a
-- ValidationException error occurs. The default value is 100.
describeProjectVersions_maxResults :: Lens.Lens' DescribeProjectVersions (Prelude.Maybe Prelude.Natural)
describeProjectVersions_maxResults :: Lens' DescribeProjectVersions (Maybe Natural)
describeProjectVersions_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProjectVersions' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:DescribeProjectVersions' :: DescribeProjectVersions -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: DescribeProjectVersions
s@DescribeProjectVersions' {} Maybe Natural
a -> DescribeProjectVersions
s {$sel:maxResults:DescribeProjectVersions' :: Maybe Natural
maxResults = Maybe Natural
a} :: DescribeProjectVersions)

-- | If the previous response was incomplete (because there is more results
-- to retrieve), Amazon Rekognition Custom Labels returns a pagination
-- token in the response. You can use this pagination token to retrieve the
-- next set of results.
describeProjectVersions_nextToken :: Lens.Lens' DescribeProjectVersions (Prelude.Maybe Prelude.Text)
describeProjectVersions_nextToken :: Lens' DescribeProjectVersions (Maybe Text)
describeProjectVersions_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProjectVersions' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeProjectVersions' :: DescribeProjectVersions -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeProjectVersions
s@DescribeProjectVersions' {} Maybe Text
a -> DescribeProjectVersions
s {$sel:nextToken:DescribeProjectVersions' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeProjectVersions)

-- | A list of model version names that you want to describe. You can add up
-- to 10 model version names to the list. If you don\'t specify a value,
-- all model descriptions are returned. A version name is part of a model
-- (ProjectVersion) ARN. For example, @my-model.2020-01-21T09.10.15@ is the
-- version name in the following ARN.
-- @arn:aws:rekognition:us-east-1:123456789012:project\/getting-started\/version\/@/@my-model.2020-01-21T09.10.15@/@\/1234567890123@.
describeProjectVersions_versionNames :: Lens.Lens' DescribeProjectVersions (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
describeProjectVersions_versionNames :: Lens' DescribeProjectVersions (Maybe (NonEmpty Text))
describeProjectVersions_versionNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProjectVersions' {Maybe (NonEmpty Text)
versionNames :: Maybe (NonEmpty Text)
$sel:versionNames:DescribeProjectVersions' :: DescribeProjectVersions -> Maybe (NonEmpty Text)
versionNames} -> Maybe (NonEmpty Text)
versionNames) (\s :: DescribeProjectVersions
s@DescribeProjectVersions' {} Maybe (NonEmpty Text)
a -> DescribeProjectVersions
s {$sel:versionNames:DescribeProjectVersions' :: Maybe (NonEmpty Text)
versionNames = Maybe (NonEmpty Text)
a} :: DescribeProjectVersions) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The Amazon Resource Name (ARN) of the project that contains the models
-- you want to describe.
describeProjectVersions_projectArn :: Lens.Lens' DescribeProjectVersions Prelude.Text
describeProjectVersions_projectArn :: Lens' DescribeProjectVersions Text
describeProjectVersions_projectArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProjectVersions' {Text
projectArn :: Text
$sel:projectArn:DescribeProjectVersions' :: DescribeProjectVersions -> Text
projectArn} -> Text
projectArn) (\s :: DescribeProjectVersions
s@DescribeProjectVersions' {} Text
a -> DescribeProjectVersions
s {$sel:projectArn:DescribeProjectVersions' :: Text
projectArn = Text
a} :: DescribeProjectVersions)

instance Core.AWSPager DescribeProjectVersions where
  page :: DescribeProjectVersions
-> AWSResponse DescribeProjectVersions
-> Maybe DescribeProjectVersions
page DescribeProjectVersions
rq AWSResponse DescribeProjectVersions
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeProjectVersions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeProjectVersionsResponse (Maybe Text)
describeProjectVersionsResponse_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 DescribeProjectVersions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  DescribeProjectVersionsResponse (Maybe [ProjectVersionDescription])
describeProjectVersionsResponse_projectVersionDescriptions
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ DescribeProjectVersions
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeProjectVersions (Maybe Text)
describeProjectVersions_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeProjectVersions
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeProjectVersionsResponse (Maybe Text)
describeProjectVersionsResponse_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 DescribeProjectVersions where
  type
    AWSResponse DescribeProjectVersions =
      DescribeProjectVersionsResponse
  request :: (Service -> Service)
-> DescribeProjectVersions -> Request DescribeProjectVersions
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 DescribeProjectVersions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeProjectVersions)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe [ProjectVersionDescription]
-> Int
-> DescribeProjectVersionsResponse
DescribeProjectVersionsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ProjectVersionDescriptions"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable DescribeProjectVersions where
  hashWithSalt :: Int -> DescribeProjectVersions -> Int
hashWithSalt Int
_salt DescribeProjectVersions' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Text
projectArn :: Text
versionNames :: Maybe (NonEmpty Text)
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:projectArn:DescribeProjectVersions' :: DescribeProjectVersions -> Text
$sel:versionNames:DescribeProjectVersions' :: DescribeProjectVersions -> Maybe (NonEmpty Text)
$sel:nextToken:DescribeProjectVersions' :: DescribeProjectVersions -> Maybe Text
$sel:maxResults:DescribeProjectVersions' :: DescribeProjectVersions -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
versionNames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
projectArn

instance Prelude.NFData DescribeProjectVersions where
  rnf :: DescribeProjectVersions -> ()
rnf DescribeProjectVersions' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Text
projectArn :: Text
versionNames :: Maybe (NonEmpty Text)
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:projectArn:DescribeProjectVersions' :: DescribeProjectVersions -> Text
$sel:versionNames:DescribeProjectVersions' :: DescribeProjectVersions -> Maybe (NonEmpty Text)
$sel:nextToken:DescribeProjectVersions' :: DescribeProjectVersions -> Maybe Text
$sel:maxResults:DescribeProjectVersions' :: DescribeProjectVersions -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
versionNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
projectArn

instance Data.ToHeaders DescribeProjectVersions where
  toHeaders :: DescribeProjectVersions -> 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
"RekognitionService.DescribeProjectVersions" ::
                          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 DescribeProjectVersions where
  toJSON :: DescribeProjectVersions -> Value
toJSON DescribeProjectVersions' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Text
projectArn :: Text
versionNames :: Maybe (NonEmpty Text)
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:projectArn:DescribeProjectVersions' :: DescribeProjectVersions -> Text
$sel:versionNames:DescribeProjectVersions' :: DescribeProjectVersions -> Maybe (NonEmpty Text)
$sel:nextToken:DescribeProjectVersions' :: DescribeProjectVersions -> Maybe Text
$sel:maxResults:DescribeProjectVersions' :: DescribeProjectVersions -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MaxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
maxResults,
            (Key
"NextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
            (Key
"VersionNames" 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 (NonEmpty Text)
versionNames,
            forall a. a -> Maybe a
Prelude.Just (Key
"ProjectArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
projectArn)
          ]
      )

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

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

-- | /See:/ 'newDescribeProjectVersionsResponse' smart constructor.
data DescribeProjectVersionsResponse = DescribeProjectVersionsResponse'
  { -- | If the previous response was incomplete (because there is more results
    -- to retrieve), Amazon Rekognition Custom Labels returns a pagination
    -- token in the response. You can use this pagination token to retrieve the
    -- next set of results.
    DescribeProjectVersionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of model descriptions. The list is sorted by the creation date
    -- and time of the model versions, latest to earliest.
    DescribeProjectVersionsResponse
-> Maybe [ProjectVersionDescription]
projectVersionDescriptions :: Prelude.Maybe [ProjectVersionDescription],
    -- | The response's http status code.
    DescribeProjectVersionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeProjectVersionsResponse
-> DescribeProjectVersionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeProjectVersionsResponse
-> DescribeProjectVersionsResponse -> Bool
$c/= :: DescribeProjectVersionsResponse
-> DescribeProjectVersionsResponse -> Bool
== :: DescribeProjectVersionsResponse
-> DescribeProjectVersionsResponse -> Bool
$c== :: DescribeProjectVersionsResponse
-> DescribeProjectVersionsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeProjectVersionsResponse]
ReadPrec DescribeProjectVersionsResponse
Int -> ReadS DescribeProjectVersionsResponse
ReadS [DescribeProjectVersionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeProjectVersionsResponse]
$creadListPrec :: ReadPrec [DescribeProjectVersionsResponse]
readPrec :: ReadPrec DescribeProjectVersionsResponse
$creadPrec :: ReadPrec DescribeProjectVersionsResponse
readList :: ReadS [DescribeProjectVersionsResponse]
$creadList :: ReadS [DescribeProjectVersionsResponse]
readsPrec :: Int -> ReadS DescribeProjectVersionsResponse
$creadsPrec :: Int -> ReadS DescribeProjectVersionsResponse
Prelude.Read, Int -> DescribeProjectVersionsResponse -> ShowS
[DescribeProjectVersionsResponse] -> ShowS
DescribeProjectVersionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeProjectVersionsResponse] -> ShowS
$cshowList :: [DescribeProjectVersionsResponse] -> ShowS
show :: DescribeProjectVersionsResponse -> String
$cshow :: DescribeProjectVersionsResponse -> String
showsPrec :: Int -> DescribeProjectVersionsResponse -> ShowS
$cshowsPrec :: Int -> DescribeProjectVersionsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeProjectVersionsResponse x
-> DescribeProjectVersionsResponse
forall x.
DescribeProjectVersionsResponse
-> Rep DescribeProjectVersionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeProjectVersionsResponse x
-> DescribeProjectVersionsResponse
$cfrom :: forall x.
DescribeProjectVersionsResponse
-> Rep DescribeProjectVersionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeProjectVersionsResponse' 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', 'describeProjectVersionsResponse_nextToken' - If the previous response was incomplete (because there is more results
-- to retrieve), Amazon Rekognition Custom Labels returns a pagination
-- token in the response. You can use this pagination token to retrieve the
-- next set of results.
--
-- 'projectVersionDescriptions', 'describeProjectVersionsResponse_projectVersionDescriptions' - A list of model descriptions. The list is sorted by the creation date
-- and time of the model versions, latest to earliest.
--
-- 'httpStatus', 'describeProjectVersionsResponse_httpStatus' - The response's http status code.
newDescribeProjectVersionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeProjectVersionsResponse
newDescribeProjectVersionsResponse :: Int -> DescribeProjectVersionsResponse
newDescribeProjectVersionsResponse Int
pHttpStatus_ =
  DescribeProjectVersionsResponse'
    { $sel:nextToken:DescribeProjectVersionsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:projectVersionDescriptions:DescribeProjectVersionsResponse' :: Maybe [ProjectVersionDescription]
projectVersionDescriptions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeProjectVersionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If the previous response was incomplete (because there is more results
-- to retrieve), Amazon Rekognition Custom Labels returns a pagination
-- token in the response. You can use this pagination token to retrieve the
-- next set of results.
describeProjectVersionsResponse_nextToken :: Lens.Lens' DescribeProjectVersionsResponse (Prelude.Maybe Prelude.Text)
describeProjectVersionsResponse_nextToken :: Lens' DescribeProjectVersionsResponse (Maybe Text)
describeProjectVersionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProjectVersionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeProjectVersionsResponse' :: DescribeProjectVersionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeProjectVersionsResponse
s@DescribeProjectVersionsResponse' {} Maybe Text
a -> DescribeProjectVersionsResponse
s {$sel:nextToken:DescribeProjectVersionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeProjectVersionsResponse)

-- | A list of model descriptions. The list is sorted by the creation date
-- and time of the model versions, latest to earliest.
describeProjectVersionsResponse_projectVersionDescriptions :: Lens.Lens' DescribeProjectVersionsResponse (Prelude.Maybe [ProjectVersionDescription])
describeProjectVersionsResponse_projectVersionDescriptions :: Lens'
  DescribeProjectVersionsResponse (Maybe [ProjectVersionDescription])
describeProjectVersionsResponse_projectVersionDescriptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProjectVersionsResponse' {Maybe [ProjectVersionDescription]
projectVersionDescriptions :: Maybe [ProjectVersionDescription]
$sel:projectVersionDescriptions:DescribeProjectVersionsResponse' :: DescribeProjectVersionsResponse
-> Maybe [ProjectVersionDescription]
projectVersionDescriptions} -> Maybe [ProjectVersionDescription]
projectVersionDescriptions) (\s :: DescribeProjectVersionsResponse
s@DescribeProjectVersionsResponse' {} Maybe [ProjectVersionDescription]
a -> DescribeProjectVersionsResponse
s {$sel:projectVersionDescriptions:DescribeProjectVersionsResponse' :: Maybe [ProjectVersionDescription]
projectVersionDescriptions = Maybe [ProjectVersionDescription]
a} :: DescribeProjectVersionsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance
  Prelude.NFData
    DescribeProjectVersionsResponse
  where
  rnf :: DescribeProjectVersionsResponse -> ()
rnf DescribeProjectVersionsResponse' {Int
Maybe [ProjectVersionDescription]
Maybe Text
httpStatus :: Int
projectVersionDescriptions :: Maybe [ProjectVersionDescription]
nextToken :: Maybe Text
$sel:httpStatus:DescribeProjectVersionsResponse' :: DescribeProjectVersionsResponse -> Int
$sel:projectVersionDescriptions:DescribeProjectVersionsResponse' :: DescribeProjectVersionsResponse
-> Maybe [ProjectVersionDescription]
$sel:nextToken:DescribeProjectVersionsResponse' :: DescribeProjectVersionsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ProjectVersionDescription]
projectVersionDescriptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus