{-# 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.ListActions
-- 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 actions in your account and their properties.
--
-- This operation returns paginated results.
module Amazonka.SageMaker.ListActions
  ( -- * Creating a Request
    ListActions (..),
    newListActions,

    -- * Request Lenses
    listActions_actionType,
    listActions_createdAfter,
    listActions_createdBefore,
    listActions_maxResults,
    listActions_nextToken,
    listActions_sortBy,
    listActions_sortOrder,
    listActions_sourceUri,

    -- * Destructuring the Response
    ListActionsResponse (..),
    newListActionsResponse,

    -- * Response Lenses
    listActionsResponse_actionSummaries,
    listActionsResponse_nextToken,
    listActionsResponse_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:/ 'newListActions' smart constructor.
data ListActions = ListActions'
  { -- | A filter that returns only actions of the specified type.
    ListActions -> Maybe Text
actionType :: Prelude.Maybe Prelude.Text,
    -- | A filter that returns only actions created on or after the specified
    -- time.
    ListActions -> Maybe POSIX
createdAfter :: Prelude.Maybe Data.POSIX,
    -- | A filter that returns only actions created on or before the specified
    -- time.
    ListActions -> Maybe POSIX
createdBefore :: Prelude.Maybe Data.POSIX,
    -- | The maximum number of actions to return in the response. The default
    -- value is 10.
    ListActions -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the previous call to @ListActions@ didn\'t return the full set of
    -- actions, the call returns a token for getting the next set of actions.
    ListActions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The property used to sort results. The default value is @CreationTime@.
    ListActions -> Maybe SortActionsBy
sortBy :: Prelude.Maybe SortActionsBy,
    -- | The sort order. The default value is @Descending@.
    ListActions -> Maybe SortOrder
sortOrder :: Prelude.Maybe SortOrder,
    -- | A filter that returns only actions with the specified source URI.
    ListActions -> Maybe Text
sourceUri :: Prelude.Maybe Prelude.Text
  }
  deriving (ListActions -> ListActions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListActions -> ListActions -> Bool
$c/= :: ListActions -> ListActions -> Bool
== :: ListActions -> ListActions -> Bool
$c== :: ListActions -> ListActions -> Bool
Prelude.Eq, ReadPrec [ListActions]
ReadPrec ListActions
Int -> ReadS ListActions
ReadS [ListActions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListActions]
$creadListPrec :: ReadPrec [ListActions]
readPrec :: ReadPrec ListActions
$creadPrec :: ReadPrec ListActions
readList :: ReadS [ListActions]
$creadList :: ReadS [ListActions]
readsPrec :: Int -> ReadS ListActions
$creadsPrec :: Int -> ReadS ListActions
Prelude.Read, Int -> ListActions -> ShowS
[ListActions] -> ShowS
ListActions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListActions] -> ShowS
$cshowList :: [ListActions] -> ShowS
show :: ListActions -> String
$cshow :: ListActions -> String
showsPrec :: Int -> ListActions -> ShowS
$cshowsPrec :: Int -> ListActions -> ShowS
Prelude.Show, forall x. Rep ListActions x -> ListActions
forall x. ListActions -> Rep ListActions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListActions x -> ListActions
$cfrom :: forall x. ListActions -> Rep ListActions x
Prelude.Generic)

-- |
-- Create a value of 'ListActions' 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:
--
-- 'actionType', 'listActions_actionType' - A filter that returns only actions of the specified type.
--
-- 'createdAfter', 'listActions_createdAfter' - A filter that returns only actions created on or after the specified
-- time.
--
-- 'createdBefore', 'listActions_createdBefore' - A filter that returns only actions created on or before the specified
-- time.
--
-- 'maxResults', 'listActions_maxResults' - The maximum number of actions to return in the response. The default
-- value is 10.
--
-- 'nextToken', 'listActions_nextToken' - If the previous call to @ListActions@ didn\'t return the full set of
-- actions, the call returns a token for getting the next set of actions.
--
-- 'sortBy', 'listActions_sortBy' - The property used to sort results. The default value is @CreationTime@.
--
-- 'sortOrder', 'listActions_sortOrder' - The sort order. The default value is @Descending@.
--
-- 'sourceUri', 'listActions_sourceUri' - A filter that returns only actions with the specified source URI.
newListActions ::
  ListActions
newListActions :: ListActions
newListActions =
  ListActions'
    { $sel:actionType:ListActions' :: Maybe Text
actionType = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAfter:ListActions' :: Maybe POSIX
createdAfter = forall a. Maybe a
Prelude.Nothing,
      $sel:createdBefore:ListActions' :: Maybe POSIX
createdBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListActions' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListActions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortBy:ListActions' :: Maybe SortActionsBy
sortBy = forall a. Maybe a
Prelude.Nothing,
      $sel:sortOrder:ListActions' :: Maybe SortOrder
sortOrder = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceUri:ListActions' :: Maybe Text
sourceUri = forall a. Maybe a
Prelude.Nothing
    }

-- | A filter that returns only actions of the specified type.
listActions_actionType :: Lens.Lens' ListActions (Prelude.Maybe Prelude.Text)
listActions_actionType :: Lens' ListActions (Maybe Text)
listActions_actionType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListActions' {Maybe Text
actionType :: Maybe Text
$sel:actionType:ListActions' :: ListActions -> Maybe Text
actionType} -> Maybe Text
actionType) (\s :: ListActions
s@ListActions' {} Maybe Text
a -> ListActions
s {$sel:actionType:ListActions' :: Maybe Text
actionType = Maybe Text
a} :: ListActions)

-- | A filter that returns only actions created on or after the specified
-- time.
listActions_createdAfter :: Lens.Lens' ListActions (Prelude.Maybe Prelude.UTCTime)
listActions_createdAfter :: Lens' ListActions (Maybe UTCTime)
listActions_createdAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListActions' {Maybe POSIX
createdAfter :: Maybe POSIX
$sel:createdAfter:ListActions' :: ListActions -> Maybe POSIX
createdAfter} -> Maybe POSIX
createdAfter) (\s :: ListActions
s@ListActions' {} Maybe POSIX
a -> ListActions
s {$sel:createdAfter:ListActions' :: Maybe POSIX
createdAfter = Maybe POSIX
a} :: ListActions) 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 actions created on or before the specified
-- time.
listActions_createdBefore :: Lens.Lens' ListActions (Prelude.Maybe Prelude.UTCTime)
listActions_createdBefore :: Lens' ListActions (Maybe UTCTime)
listActions_createdBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListActions' {Maybe POSIX
createdBefore :: Maybe POSIX
$sel:createdBefore:ListActions' :: ListActions -> Maybe POSIX
createdBefore} -> Maybe POSIX
createdBefore) (\s :: ListActions
s@ListActions' {} Maybe POSIX
a -> ListActions
s {$sel:createdBefore:ListActions' :: Maybe POSIX
createdBefore = Maybe POSIX
a} :: ListActions) 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 actions to return in the response. The default
-- value is 10.
listActions_maxResults :: Lens.Lens' ListActions (Prelude.Maybe Prelude.Natural)
listActions_maxResults :: Lens' ListActions (Maybe Natural)
listActions_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListActions' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListActions' :: ListActions -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListActions
s@ListActions' {} Maybe Natural
a -> ListActions
s {$sel:maxResults:ListActions' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListActions)

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

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

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

-- | A filter that returns only actions with the specified source URI.
listActions_sourceUri :: Lens.Lens' ListActions (Prelude.Maybe Prelude.Text)
listActions_sourceUri :: Lens' ListActions (Maybe Text)
listActions_sourceUri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListActions' {Maybe Text
sourceUri :: Maybe Text
$sel:sourceUri:ListActions' :: ListActions -> Maybe Text
sourceUri} -> Maybe Text
sourceUri) (\s :: ListActions
s@ListActions' {} Maybe Text
a -> ListActions
s {$sel:sourceUri:ListActions' :: Maybe Text
sourceUri = Maybe Text
a} :: ListActions)

instance Core.AWSPager ListActions where
  page :: ListActions -> AWSResponse ListActions -> Maybe ListActions
page ListActions
rq AWSResponse ListActions
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListActions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListActionsResponse (Maybe Text)
listActionsResponse_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 ListActions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListActionsResponse (Maybe [ActionSummary])
listActionsResponse_actionSummaries
            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.$ ListActions
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListActions (Maybe Text)
listActions_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListActions
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListActionsResponse (Maybe Text)
listActionsResponse_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 ListActions where
  type AWSResponse ListActions = ListActionsResponse
  request :: (Service -> Service) -> ListActions -> Request ListActions
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 ListActions
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListActions)))
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 [ActionSummary] -> Maybe Text -> Int -> ListActionsResponse
ListActionsResponse'
            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
"ActionSummaries"
                            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 ListActions where
  hashWithSalt :: Int -> ListActions -> Int
hashWithSalt Int
_salt ListActions' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe SortActionsBy
Maybe SortOrder
sourceUri :: Maybe Text
sortOrder :: Maybe SortOrder
sortBy :: Maybe SortActionsBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
createdBefore :: Maybe POSIX
createdAfter :: Maybe POSIX
actionType :: Maybe Text
$sel:sourceUri:ListActions' :: ListActions -> Maybe Text
$sel:sortOrder:ListActions' :: ListActions -> Maybe SortOrder
$sel:sortBy:ListActions' :: ListActions -> Maybe SortActionsBy
$sel:nextToken:ListActions' :: ListActions -> Maybe Text
$sel:maxResults:ListActions' :: ListActions -> Maybe Natural
$sel:createdBefore:ListActions' :: ListActions -> Maybe POSIX
$sel:createdAfter:ListActions' :: ListActions -> Maybe POSIX
$sel:actionType:ListActions' :: ListActions -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
actionType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdAfter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdBefore
      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 SortActionsBy
sortBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortOrder
sortOrder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceUri

instance Prelude.NFData ListActions where
  rnf :: ListActions -> ()
rnf ListActions' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe SortActionsBy
Maybe SortOrder
sourceUri :: Maybe Text
sortOrder :: Maybe SortOrder
sortBy :: Maybe SortActionsBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
createdBefore :: Maybe POSIX
createdAfter :: Maybe POSIX
actionType :: Maybe Text
$sel:sourceUri:ListActions' :: ListActions -> Maybe Text
$sel:sortOrder:ListActions' :: ListActions -> Maybe SortOrder
$sel:sortBy:ListActions' :: ListActions -> Maybe SortActionsBy
$sel:nextToken:ListActions' :: ListActions -> Maybe Text
$sel:maxResults:ListActions' :: ListActions -> Maybe Natural
$sel:createdBefore:ListActions' :: ListActions -> Maybe POSIX
$sel:createdAfter:ListActions' :: ListActions -> Maybe POSIX
$sel:actionType:ListActions' :: ListActions -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
actionType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAfter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdBefore
      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
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SortActionsBy
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 Maybe Text
sourceUri

instance Data.ToHeaders ListActions where
  toHeaders :: ListActions -> 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.ListActions" :: 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 ListActions where
  toJSON :: ListActions -> Value
toJSON ListActions' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe SortActionsBy
Maybe SortOrder
sourceUri :: Maybe Text
sortOrder :: Maybe SortOrder
sortBy :: Maybe SortActionsBy
nextToken :: Maybe Text
maxResults :: Maybe Natural
createdBefore :: Maybe POSIX
createdAfter :: Maybe POSIX
actionType :: Maybe Text
$sel:sourceUri:ListActions' :: ListActions -> Maybe Text
$sel:sortOrder:ListActions' :: ListActions -> Maybe SortOrder
$sel:sortBy:ListActions' :: ListActions -> Maybe SortActionsBy
$sel:nextToken:ListActions' :: ListActions -> Maybe Text
$sel:maxResults:ListActions' :: ListActions -> Maybe Natural
$sel:createdBefore:ListActions' :: ListActions -> Maybe POSIX
$sel:createdAfter:ListActions' :: ListActions -> Maybe POSIX
$sel:actionType:ListActions' :: ListActions -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ActionType" 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
actionType,
            (Key
"CreatedAfter" 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
createdAfter,
            (Key
"CreatedBefore" 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
createdBefore,
            (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
"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 SortActionsBy
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,
            (Key
"SourceUri" 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
sourceUri
          ]
      )

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

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

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

-- |
-- Create a value of 'ListActionsResponse' 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:
--
-- 'actionSummaries', 'listActionsResponse_actionSummaries' - A list of actions and their properties.
--
-- 'nextToken', 'listActionsResponse_nextToken' - A token for getting the next set of actions, if there are any.
--
-- 'httpStatus', 'listActionsResponse_httpStatus' - The response's http status code.
newListActionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListActionsResponse
newListActionsResponse :: Int -> ListActionsResponse
newListActionsResponse Int
pHttpStatus_ =
  ListActionsResponse'
    { $sel:actionSummaries:ListActionsResponse' :: Maybe [ActionSummary]
actionSummaries =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListActionsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListActionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of actions and their properties.
listActionsResponse_actionSummaries :: Lens.Lens' ListActionsResponse (Prelude.Maybe [ActionSummary])
listActionsResponse_actionSummaries :: Lens' ListActionsResponse (Maybe [ActionSummary])
listActionsResponse_actionSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListActionsResponse' {Maybe [ActionSummary]
actionSummaries :: Maybe [ActionSummary]
$sel:actionSummaries:ListActionsResponse' :: ListActionsResponse -> Maybe [ActionSummary]
actionSummaries} -> Maybe [ActionSummary]
actionSummaries) (\s :: ListActionsResponse
s@ListActionsResponse' {} Maybe [ActionSummary]
a -> ListActionsResponse
s {$sel:actionSummaries:ListActionsResponse' :: Maybe [ActionSummary]
actionSummaries = Maybe [ActionSummary]
a} :: ListActionsResponse) 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 actions, if there are any.
listActionsResponse_nextToken :: Lens.Lens' ListActionsResponse (Prelude.Maybe Prelude.Text)
listActionsResponse_nextToken :: Lens' ListActionsResponse (Maybe Text)
listActionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListActionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListActionsResponse' :: ListActionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListActionsResponse
s@ListActionsResponse' {} Maybe Text
a -> ListActionsResponse
s {$sel:nextToken:ListActionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListActionsResponse)

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

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