{-# 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.ListAppImageConfigs
-- 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 the AppImageConfigs in your account and their properties. The list
-- can be filtered by creation time or modified time, and whether the
-- AppImageConfig name contains a specified string.
--
-- This operation returns paginated results.
module Amazonka.SageMaker.ListAppImageConfigs
  ( -- * Creating a Request
    ListAppImageConfigs (..),
    newListAppImageConfigs,

    -- * Request Lenses
    listAppImageConfigs_creationTimeAfter,
    listAppImageConfigs_creationTimeBefore,
    listAppImageConfigs_maxResults,
    listAppImageConfigs_modifiedTimeAfter,
    listAppImageConfigs_modifiedTimeBefore,
    listAppImageConfigs_nameContains,
    listAppImageConfigs_nextToken,
    listAppImageConfigs_sortBy,
    listAppImageConfigs_sortOrder,

    -- * Destructuring the Response
    ListAppImageConfigsResponse (..),
    newListAppImageConfigsResponse,

    -- * Response Lenses
    listAppImageConfigsResponse_appImageConfigs,
    listAppImageConfigsResponse_nextToken,
    listAppImageConfigsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListAppImageConfigs' smart constructor.
data ListAppImageConfigs = ListAppImageConfigs'
  { -- | A filter that returns only AppImageConfigs created on or after the
    -- specified time.
    ListAppImageConfigs -> Maybe POSIX
creationTimeAfter :: Prelude.Maybe Data.POSIX,
    -- | A filter that returns only AppImageConfigs created on or before the
    -- specified time.
    ListAppImageConfigs -> Maybe POSIX
creationTimeBefore :: Prelude.Maybe Data.POSIX,
    -- | The maximum number of AppImageConfigs to return in the response. The
    -- default value is 10.
    ListAppImageConfigs -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A filter that returns only AppImageConfigs modified on or after the
    -- specified time.
    ListAppImageConfigs -> Maybe POSIX
modifiedTimeAfter :: Prelude.Maybe Data.POSIX,
    -- | A filter that returns only AppImageConfigs modified on or before the
    -- specified time.
    ListAppImageConfigs -> Maybe POSIX
modifiedTimeBefore :: Prelude.Maybe Data.POSIX,
    -- | A filter that returns only AppImageConfigs whose name contains the
    -- specified string.
    ListAppImageConfigs -> Maybe Text
nameContains :: Prelude.Maybe Prelude.Text,
    -- | If the previous call to @ListImages@ didn\'t return the full set of
    -- AppImageConfigs, the call returns a token for getting the next set of
    -- AppImageConfigs.
    ListAppImageConfigs -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The property used to sort results. The default value is @CreationTime@.
    ListAppImageConfigs -> Maybe AppImageConfigSortKey
sortBy :: Prelude.Maybe AppImageConfigSortKey,
    -- | The sort order. The default value is @Descending@.
    ListAppImageConfigs -> Maybe SortOrder
sortOrder :: Prelude.Maybe SortOrder
  }
  deriving (ListAppImageConfigs -> ListAppImageConfigs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAppImageConfigs -> ListAppImageConfigs -> Bool
$c/= :: ListAppImageConfigs -> ListAppImageConfigs -> Bool
== :: ListAppImageConfigs -> ListAppImageConfigs -> Bool
$c== :: ListAppImageConfigs -> ListAppImageConfigs -> Bool
Prelude.Eq, ReadPrec [ListAppImageConfigs]
ReadPrec ListAppImageConfigs
Int -> ReadS ListAppImageConfigs
ReadS [ListAppImageConfigs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAppImageConfigs]
$creadListPrec :: ReadPrec [ListAppImageConfigs]
readPrec :: ReadPrec ListAppImageConfigs
$creadPrec :: ReadPrec ListAppImageConfigs
readList :: ReadS [ListAppImageConfigs]
$creadList :: ReadS [ListAppImageConfigs]
readsPrec :: Int -> ReadS ListAppImageConfigs
$creadsPrec :: Int -> ReadS ListAppImageConfigs
Prelude.Read, Int -> ListAppImageConfigs -> ShowS
[ListAppImageConfigs] -> ShowS
ListAppImageConfigs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAppImageConfigs] -> ShowS
$cshowList :: [ListAppImageConfigs] -> ShowS
show :: ListAppImageConfigs -> String
$cshow :: ListAppImageConfigs -> String
showsPrec :: Int -> ListAppImageConfigs -> ShowS
$cshowsPrec :: Int -> ListAppImageConfigs -> ShowS
Prelude.Show, forall x. Rep ListAppImageConfigs x -> ListAppImageConfigs
forall x. ListAppImageConfigs -> Rep ListAppImageConfigs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAppImageConfigs x -> ListAppImageConfigs
$cfrom :: forall x. ListAppImageConfigs -> Rep ListAppImageConfigs x
Prelude.Generic)

-- |
-- Create a value of 'ListAppImageConfigs' 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', 'listAppImageConfigs_creationTimeAfter' - A filter that returns only AppImageConfigs created on or after the
-- specified time.
--
-- 'creationTimeBefore', 'listAppImageConfigs_creationTimeBefore' - A filter that returns only AppImageConfigs created on or before the
-- specified time.
--
-- 'maxResults', 'listAppImageConfigs_maxResults' - The maximum number of AppImageConfigs to return in the response. The
-- default value is 10.
--
-- 'modifiedTimeAfter', 'listAppImageConfigs_modifiedTimeAfter' - A filter that returns only AppImageConfigs modified on or after the
-- specified time.
--
-- 'modifiedTimeBefore', 'listAppImageConfigs_modifiedTimeBefore' - A filter that returns only AppImageConfigs modified on or before the
-- specified time.
--
-- 'nameContains', 'listAppImageConfigs_nameContains' - A filter that returns only AppImageConfigs whose name contains the
-- specified string.
--
-- 'nextToken', 'listAppImageConfigs_nextToken' - If the previous call to @ListImages@ didn\'t return the full set of
-- AppImageConfigs, the call returns a token for getting the next set of
-- AppImageConfigs.
--
-- 'sortBy', 'listAppImageConfigs_sortBy' - The property used to sort results. The default value is @CreationTime@.
--
-- 'sortOrder', 'listAppImageConfigs_sortOrder' - The sort order. The default value is @Descending@.
newListAppImageConfigs ::
  ListAppImageConfigs
newListAppImageConfigs :: ListAppImageConfigs
newListAppImageConfigs =
  ListAppImageConfigs'
    { $sel:creationTimeAfter:ListAppImageConfigs' :: Maybe POSIX
creationTimeAfter =
        forall a. Maybe a
Prelude.Nothing,
      $sel:creationTimeBefore:ListAppImageConfigs' :: Maybe POSIX
creationTimeBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListAppImageConfigs' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:modifiedTimeAfter:ListAppImageConfigs' :: Maybe POSIX
modifiedTimeAfter = forall a. Maybe a
Prelude.Nothing,
      $sel:modifiedTimeBefore:ListAppImageConfigs' :: Maybe POSIX
modifiedTimeBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:nameContains:ListAppImageConfigs' :: Maybe Text
nameContains = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAppImageConfigs' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortBy:ListAppImageConfigs' :: Maybe AppImageConfigSortKey
sortBy = forall a. Maybe a
Prelude.Nothing,
      $sel:sortOrder:ListAppImageConfigs' :: Maybe SortOrder
sortOrder = forall a. Maybe a
Prelude.Nothing
    }

-- | A filter that returns only AppImageConfigs created on or after the
-- specified time.
listAppImageConfigs_creationTimeAfter :: Lens.Lens' ListAppImageConfigs (Prelude.Maybe Prelude.UTCTime)
listAppImageConfigs_creationTimeAfter :: Lens' ListAppImageConfigs (Maybe UTCTime)
listAppImageConfigs_creationTimeAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAppImageConfigs' {Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:creationTimeAfter:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe POSIX
creationTimeAfter} -> Maybe POSIX
creationTimeAfter) (\s :: ListAppImageConfigs
s@ListAppImageConfigs' {} Maybe POSIX
a -> ListAppImageConfigs
s {$sel:creationTimeAfter:ListAppImageConfigs' :: Maybe POSIX
creationTimeAfter = Maybe POSIX
a} :: ListAppImageConfigs) 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 AppImageConfigs created on or before the
-- specified time.
listAppImageConfigs_creationTimeBefore :: Lens.Lens' ListAppImageConfigs (Prelude.Maybe Prelude.UTCTime)
listAppImageConfigs_creationTimeBefore :: Lens' ListAppImageConfigs (Maybe UTCTime)
listAppImageConfigs_creationTimeBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAppImageConfigs' {Maybe POSIX
creationTimeBefore :: Maybe POSIX
$sel:creationTimeBefore:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe POSIX
creationTimeBefore} -> Maybe POSIX
creationTimeBefore) (\s :: ListAppImageConfigs
s@ListAppImageConfigs' {} Maybe POSIX
a -> ListAppImageConfigs
s {$sel:creationTimeBefore:ListAppImageConfigs' :: Maybe POSIX
creationTimeBefore = Maybe POSIX
a} :: ListAppImageConfigs) 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 AppImageConfigs to return in the response. The
-- default value is 10.
listAppImageConfigs_maxResults :: Lens.Lens' ListAppImageConfigs (Prelude.Maybe Prelude.Natural)
listAppImageConfigs_maxResults :: Lens' ListAppImageConfigs (Maybe Natural)
listAppImageConfigs_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAppImageConfigs' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListAppImageConfigs
s@ListAppImageConfigs' {} Maybe Natural
a -> ListAppImageConfigs
s {$sel:maxResults:ListAppImageConfigs' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListAppImageConfigs)

-- | A filter that returns only AppImageConfigs modified on or after the
-- specified time.
listAppImageConfigs_modifiedTimeAfter :: Lens.Lens' ListAppImageConfigs (Prelude.Maybe Prelude.UTCTime)
listAppImageConfigs_modifiedTimeAfter :: Lens' ListAppImageConfigs (Maybe UTCTime)
listAppImageConfigs_modifiedTimeAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAppImageConfigs' {Maybe POSIX
modifiedTimeAfter :: Maybe POSIX
$sel:modifiedTimeAfter:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe POSIX
modifiedTimeAfter} -> Maybe POSIX
modifiedTimeAfter) (\s :: ListAppImageConfigs
s@ListAppImageConfigs' {} Maybe POSIX
a -> ListAppImageConfigs
s {$sel:modifiedTimeAfter:ListAppImageConfigs' :: Maybe POSIX
modifiedTimeAfter = Maybe POSIX
a} :: ListAppImageConfigs) 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 AppImageConfigs modified on or before the
-- specified time.
listAppImageConfigs_modifiedTimeBefore :: Lens.Lens' ListAppImageConfigs (Prelude.Maybe Prelude.UTCTime)
listAppImageConfigs_modifiedTimeBefore :: Lens' ListAppImageConfigs (Maybe UTCTime)
listAppImageConfigs_modifiedTimeBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAppImageConfigs' {Maybe POSIX
modifiedTimeBefore :: Maybe POSIX
$sel:modifiedTimeBefore:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe POSIX
modifiedTimeBefore} -> Maybe POSIX
modifiedTimeBefore) (\s :: ListAppImageConfigs
s@ListAppImageConfigs' {} Maybe POSIX
a -> ListAppImageConfigs
s {$sel:modifiedTimeBefore:ListAppImageConfigs' :: Maybe POSIX
modifiedTimeBefore = Maybe POSIX
a} :: ListAppImageConfigs) 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 AppImageConfigs whose name contains the
-- specified string.
listAppImageConfigs_nameContains :: Lens.Lens' ListAppImageConfigs (Prelude.Maybe Prelude.Text)
listAppImageConfigs_nameContains :: Lens' ListAppImageConfigs (Maybe Text)
listAppImageConfigs_nameContains = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAppImageConfigs' {Maybe Text
nameContains :: Maybe Text
$sel:nameContains:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe Text
nameContains} -> Maybe Text
nameContains) (\s :: ListAppImageConfigs
s@ListAppImageConfigs' {} Maybe Text
a -> ListAppImageConfigs
s {$sel:nameContains:ListAppImageConfigs' :: Maybe Text
nameContains = Maybe Text
a} :: ListAppImageConfigs)

-- | If the previous call to @ListImages@ didn\'t return the full set of
-- AppImageConfigs, the call returns a token for getting the next set of
-- AppImageConfigs.
listAppImageConfigs_nextToken :: Lens.Lens' ListAppImageConfigs (Prelude.Maybe Prelude.Text)
listAppImageConfigs_nextToken :: Lens' ListAppImageConfigs (Maybe Text)
listAppImageConfigs_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAppImageConfigs' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAppImageConfigs
s@ListAppImageConfigs' {} Maybe Text
a -> ListAppImageConfigs
s {$sel:nextToken:ListAppImageConfigs' :: Maybe Text
nextToken = Maybe Text
a} :: ListAppImageConfigs)

-- | The property used to sort results. The default value is @CreationTime@.
listAppImageConfigs_sortBy :: Lens.Lens' ListAppImageConfigs (Prelude.Maybe AppImageConfigSortKey)
listAppImageConfigs_sortBy :: Lens' ListAppImageConfigs (Maybe AppImageConfigSortKey)
listAppImageConfigs_sortBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAppImageConfigs' {Maybe AppImageConfigSortKey
sortBy :: Maybe AppImageConfigSortKey
$sel:sortBy:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe AppImageConfigSortKey
sortBy} -> Maybe AppImageConfigSortKey
sortBy) (\s :: ListAppImageConfigs
s@ListAppImageConfigs' {} Maybe AppImageConfigSortKey
a -> ListAppImageConfigs
s {$sel:sortBy:ListAppImageConfigs' :: Maybe AppImageConfigSortKey
sortBy = Maybe AppImageConfigSortKey
a} :: ListAppImageConfigs)

-- | The sort order. The default value is @Descending@.
listAppImageConfigs_sortOrder :: Lens.Lens' ListAppImageConfigs (Prelude.Maybe SortOrder)
listAppImageConfigs_sortOrder :: Lens' ListAppImageConfigs (Maybe SortOrder)
listAppImageConfigs_sortOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAppImageConfigs' {Maybe SortOrder
sortOrder :: Maybe SortOrder
$sel:sortOrder:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe SortOrder
sortOrder} -> Maybe SortOrder
sortOrder) (\s :: ListAppImageConfigs
s@ListAppImageConfigs' {} Maybe SortOrder
a -> ListAppImageConfigs
s {$sel:sortOrder:ListAppImageConfigs' :: Maybe SortOrder
sortOrder = Maybe SortOrder
a} :: ListAppImageConfigs)

instance Core.AWSPager ListAppImageConfigs where
  page :: ListAppImageConfigs
-> AWSResponse ListAppImageConfigs -> Maybe ListAppImageConfigs
page ListAppImageConfigs
rq AWSResponse ListAppImageConfigs
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListAppImageConfigs
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAppImageConfigsResponse (Maybe Text)
listAppImageConfigsResponse_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 ListAppImageConfigs
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAppImageConfigsResponse (Maybe [AppImageConfigDetails])
listAppImageConfigsResponse_appImageConfigs
            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.$ ListAppImageConfigs
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListAppImageConfigs (Maybe Text)
listAppImageConfigs_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListAppImageConfigs
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAppImageConfigsResponse (Maybe Text)
listAppImageConfigsResponse_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 ListAppImageConfigs where
  type
    AWSResponse ListAppImageConfigs =
      ListAppImageConfigsResponse
  request :: (Service -> Service)
-> ListAppImageConfigs -> Request ListAppImageConfigs
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 ListAppImageConfigs
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListAppImageConfigs)))
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 [AppImageConfigDetails]
-> Maybe Text -> Int -> ListAppImageConfigsResponse
ListAppImageConfigsResponse'
            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
"AppImageConfigs"
                            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.<*> (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))
      )

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

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

instance Data.ToHeaders ListAppImageConfigs where
  toHeaders :: ListAppImageConfigs -> 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.ListAppImageConfigs" ::
                          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 ListAppImageConfigs where
  toJSON :: ListAppImageConfigs -> Value
toJSON ListAppImageConfigs' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe AppImageConfigSortKey
Maybe SortOrder
sortOrder :: Maybe SortOrder
sortBy :: Maybe AppImageConfigSortKey
nextToken :: Maybe Text
nameContains :: Maybe Text
modifiedTimeBefore :: Maybe POSIX
modifiedTimeAfter :: Maybe POSIX
maxResults :: Maybe Natural
creationTimeBefore :: Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:sortOrder:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe SortOrder
$sel:sortBy:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe AppImageConfigSortKey
$sel:nextToken:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe Text
$sel:nameContains:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe Text
$sel:modifiedTimeBefore:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe POSIX
$sel:modifiedTimeAfter:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe POSIX
$sel:maxResults:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe Natural
$sel:creationTimeBefore:ListAppImageConfigs' :: ListAppImageConfigs -> Maybe POSIX
$sel:creationTimeAfter:ListAppImageConfigs' :: ListAppImageConfigs -> 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
"ModifiedTimeAfter" 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
modifiedTimeAfter,
            (Key
"ModifiedTimeBefore" 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
modifiedTimeBefore,
            (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 AppImageConfigSortKey
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 ListAppImageConfigs where
  toPath :: ListAppImageConfigs -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newListAppImageConfigsResponse' smart constructor.
data ListAppImageConfigsResponse = ListAppImageConfigsResponse'
  { -- | A list of AppImageConfigs and their properties.
    ListAppImageConfigsResponse -> Maybe [AppImageConfigDetails]
appImageConfigs :: Prelude.Maybe [AppImageConfigDetails],
    -- | A token for getting the next set of AppImageConfigs, if there are any.
    ListAppImageConfigsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListAppImageConfigsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListAppImageConfigsResponse -> ListAppImageConfigsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAppImageConfigsResponse -> ListAppImageConfigsResponse -> Bool
$c/= :: ListAppImageConfigsResponse -> ListAppImageConfigsResponse -> Bool
== :: ListAppImageConfigsResponse -> ListAppImageConfigsResponse -> Bool
$c== :: ListAppImageConfigsResponse -> ListAppImageConfigsResponse -> Bool
Prelude.Eq, ReadPrec [ListAppImageConfigsResponse]
ReadPrec ListAppImageConfigsResponse
Int -> ReadS ListAppImageConfigsResponse
ReadS [ListAppImageConfigsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAppImageConfigsResponse]
$creadListPrec :: ReadPrec [ListAppImageConfigsResponse]
readPrec :: ReadPrec ListAppImageConfigsResponse
$creadPrec :: ReadPrec ListAppImageConfigsResponse
readList :: ReadS [ListAppImageConfigsResponse]
$creadList :: ReadS [ListAppImageConfigsResponse]
readsPrec :: Int -> ReadS ListAppImageConfigsResponse
$creadsPrec :: Int -> ReadS ListAppImageConfigsResponse
Prelude.Read, Int -> ListAppImageConfigsResponse -> ShowS
[ListAppImageConfigsResponse] -> ShowS
ListAppImageConfigsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAppImageConfigsResponse] -> ShowS
$cshowList :: [ListAppImageConfigsResponse] -> ShowS
show :: ListAppImageConfigsResponse -> String
$cshow :: ListAppImageConfigsResponse -> String
showsPrec :: Int -> ListAppImageConfigsResponse -> ShowS
$cshowsPrec :: Int -> ListAppImageConfigsResponse -> ShowS
Prelude.Show, forall x.
Rep ListAppImageConfigsResponse x -> ListAppImageConfigsResponse
forall x.
ListAppImageConfigsResponse -> Rep ListAppImageConfigsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListAppImageConfigsResponse x -> ListAppImageConfigsResponse
$cfrom :: forall x.
ListAppImageConfigsResponse -> Rep ListAppImageConfigsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListAppImageConfigsResponse' 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:
--
-- 'appImageConfigs', 'listAppImageConfigsResponse_appImageConfigs' - A list of AppImageConfigs and their properties.
--
-- 'nextToken', 'listAppImageConfigsResponse_nextToken' - A token for getting the next set of AppImageConfigs, if there are any.
--
-- 'httpStatus', 'listAppImageConfigsResponse_httpStatus' - The response's http status code.
newListAppImageConfigsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListAppImageConfigsResponse
newListAppImageConfigsResponse :: Int -> ListAppImageConfigsResponse
newListAppImageConfigsResponse Int
pHttpStatus_ =
  ListAppImageConfigsResponse'
    { $sel:appImageConfigs:ListAppImageConfigsResponse' :: Maybe [AppImageConfigDetails]
appImageConfigs =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAppImageConfigsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListAppImageConfigsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of AppImageConfigs and their properties.
listAppImageConfigsResponse_appImageConfigs :: Lens.Lens' ListAppImageConfigsResponse (Prelude.Maybe [AppImageConfigDetails])
listAppImageConfigsResponse_appImageConfigs :: Lens' ListAppImageConfigsResponse (Maybe [AppImageConfigDetails])
listAppImageConfigsResponse_appImageConfigs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAppImageConfigsResponse' {Maybe [AppImageConfigDetails]
appImageConfigs :: Maybe [AppImageConfigDetails]
$sel:appImageConfigs:ListAppImageConfigsResponse' :: ListAppImageConfigsResponse -> Maybe [AppImageConfigDetails]
appImageConfigs} -> Maybe [AppImageConfigDetails]
appImageConfigs) (\s :: ListAppImageConfigsResponse
s@ListAppImageConfigsResponse' {} Maybe [AppImageConfigDetails]
a -> ListAppImageConfigsResponse
s {$sel:appImageConfigs:ListAppImageConfigsResponse' :: Maybe [AppImageConfigDetails]
appImageConfigs = Maybe [AppImageConfigDetails]
a} :: ListAppImageConfigsResponse) 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

-- | A token for getting the next set of AppImageConfigs, if there are any.
listAppImageConfigsResponse_nextToken :: Lens.Lens' ListAppImageConfigsResponse (Prelude.Maybe Prelude.Text)
listAppImageConfigsResponse_nextToken :: Lens' ListAppImageConfigsResponse (Maybe Text)
listAppImageConfigsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAppImageConfigsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAppImageConfigsResponse' :: ListAppImageConfigsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAppImageConfigsResponse
s@ListAppImageConfigsResponse' {} Maybe Text
a -> ListAppImageConfigsResponse
s {$sel:nextToken:ListAppImageConfigsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListAppImageConfigsResponse)

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

instance Prelude.NFData ListAppImageConfigsResponse where
  rnf :: ListAppImageConfigsResponse -> ()
rnf ListAppImageConfigsResponse' {Int
Maybe [AppImageConfigDetails]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
appImageConfigs :: Maybe [AppImageConfigDetails]
$sel:httpStatus:ListAppImageConfigsResponse' :: ListAppImageConfigsResponse -> Int
$sel:nextToken:ListAppImageConfigsResponse' :: ListAppImageConfigsResponse -> Maybe Text
$sel:appImageConfigs:ListAppImageConfigsResponse' :: ListAppImageConfigsResponse -> Maybe [AppImageConfigDetails]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [AppImageConfigDetails]
appImageConfigs
      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 Int
httpStatus