{-# 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.Athena.ListSessions
-- 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 sessions in a workgroup that are in an active state like
-- @CREATING@, @CREATED@, @IDLE@, or @BUSY@. Newer sessions are listed
-- first; older sessions are listed later.
module Amazonka.Athena.ListSessions
  ( -- * Creating a Request
    ListSessions (..),
    newListSessions,

    -- * Request Lenses
    listSessions_maxResults,
    listSessions_nextToken,
    listSessions_stateFilter,
    listSessions_workGroup,

    -- * Destructuring the Response
    ListSessionsResponse (..),
    newListSessionsResponse,

    -- * Response Lenses
    listSessionsResponse_nextToken,
    listSessionsResponse_sessions,
    listSessionsResponse_httpStatus,
  )
where

import Amazonka.Athena.Types
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

-- | /See:/ 'newListSessions' smart constructor.
data ListSessions = ListSessions'
  { -- | The maximum number of sessions to return.
    ListSessions -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A token generated by the Athena service that specifies where to continue
    -- pagination if a previous request was truncated. To obtain the next set
    -- of pages, pass in the @NextToken@ from the response object of the
    -- previous page call.
    ListSessions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A filter for a specific session state. A description of each state
    -- follows.
    --
    -- @CREATING@ - The session is being started, including acquiring
    -- resources.
    --
    -- @CREATED@ - The session has been started.
    --
    -- @IDLE@ - The session is able to accept a calculation.
    --
    -- @BUSY@ - The session is processing another task and is unable to accept
    -- a calculation.
    --
    -- @TERMINATING@ - The session is in the process of shutting down.
    --
    -- @TERMINATED@ - The session and its resources are no longer running.
    --
    -- @DEGRADED@ - The session has no healthy coordinators.
    --
    -- @FAILED@ - Due to a failure, the session and its resources are no longer
    -- running.
    ListSessions -> Maybe SessionState
stateFilter :: Prelude.Maybe SessionState,
    -- | The workgroup to which the session belongs.
    ListSessions -> Text
workGroup :: Prelude.Text
  }
  deriving (ListSessions -> ListSessions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListSessions -> ListSessions -> Bool
$c/= :: ListSessions -> ListSessions -> Bool
== :: ListSessions -> ListSessions -> Bool
$c== :: ListSessions -> ListSessions -> Bool
Prelude.Eq, ReadPrec [ListSessions]
ReadPrec ListSessions
Int -> ReadS ListSessions
ReadS [ListSessions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListSessions]
$creadListPrec :: ReadPrec [ListSessions]
readPrec :: ReadPrec ListSessions
$creadPrec :: ReadPrec ListSessions
readList :: ReadS [ListSessions]
$creadList :: ReadS [ListSessions]
readsPrec :: Int -> ReadS ListSessions
$creadsPrec :: Int -> ReadS ListSessions
Prelude.Read, Int -> ListSessions -> ShowS
[ListSessions] -> ShowS
ListSessions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListSessions] -> ShowS
$cshowList :: [ListSessions] -> ShowS
show :: ListSessions -> String
$cshow :: ListSessions -> String
showsPrec :: Int -> ListSessions -> ShowS
$cshowsPrec :: Int -> ListSessions -> ShowS
Prelude.Show, forall x. Rep ListSessions x -> ListSessions
forall x. ListSessions -> Rep ListSessions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListSessions x -> ListSessions
$cfrom :: forall x. ListSessions -> Rep ListSessions x
Prelude.Generic)

-- |
-- Create a value of 'ListSessions' 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', 'listSessions_maxResults' - The maximum number of sessions to return.
--
-- 'nextToken', 'listSessions_nextToken' - A token generated by the Athena service that specifies where to continue
-- pagination if a previous request was truncated. To obtain the next set
-- of pages, pass in the @NextToken@ from the response object of the
-- previous page call.
--
-- 'stateFilter', 'listSessions_stateFilter' - A filter for a specific session state. A description of each state
-- follows.
--
-- @CREATING@ - The session is being started, including acquiring
-- resources.
--
-- @CREATED@ - The session has been started.
--
-- @IDLE@ - The session is able to accept a calculation.
--
-- @BUSY@ - The session is processing another task and is unable to accept
-- a calculation.
--
-- @TERMINATING@ - The session is in the process of shutting down.
--
-- @TERMINATED@ - The session and its resources are no longer running.
--
-- @DEGRADED@ - The session has no healthy coordinators.
--
-- @FAILED@ - Due to a failure, the session and its resources are no longer
-- running.
--
-- 'workGroup', 'listSessions_workGroup' - The workgroup to which the session belongs.
newListSessions ::
  -- | 'workGroup'
  Prelude.Text ->
  ListSessions
newListSessions :: Text -> ListSessions
newListSessions Text
pWorkGroup_ =
  ListSessions'
    { $sel:maxResults:ListSessions' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListSessions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:stateFilter:ListSessions' :: Maybe SessionState
stateFilter = forall a. Maybe a
Prelude.Nothing,
      $sel:workGroup:ListSessions' :: Text
workGroup = Text
pWorkGroup_
    }

-- | The maximum number of sessions to return.
listSessions_maxResults :: Lens.Lens' ListSessions (Prelude.Maybe Prelude.Natural)
listSessions_maxResults :: Lens' ListSessions (Maybe Natural)
listSessions_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSessions' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListSessions' :: ListSessions -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListSessions
s@ListSessions' {} Maybe Natural
a -> ListSessions
s {$sel:maxResults:ListSessions' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListSessions)

-- | A token generated by the Athena service that specifies where to continue
-- pagination if a previous request was truncated. To obtain the next set
-- of pages, pass in the @NextToken@ from the response object of the
-- previous page call.
listSessions_nextToken :: Lens.Lens' ListSessions (Prelude.Maybe Prelude.Text)
listSessions_nextToken :: Lens' ListSessions (Maybe Text)
listSessions_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSessions' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListSessions' :: ListSessions -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListSessions
s@ListSessions' {} Maybe Text
a -> ListSessions
s {$sel:nextToken:ListSessions' :: Maybe Text
nextToken = Maybe Text
a} :: ListSessions)

-- | A filter for a specific session state. A description of each state
-- follows.
--
-- @CREATING@ - The session is being started, including acquiring
-- resources.
--
-- @CREATED@ - The session has been started.
--
-- @IDLE@ - The session is able to accept a calculation.
--
-- @BUSY@ - The session is processing another task and is unable to accept
-- a calculation.
--
-- @TERMINATING@ - The session is in the process of shutting down.
--
-- @TERMINATED@ - The session and its resources are no longer running.
--
-- @DEGRADED@ - The session has no healthy coordinators.
--
-- @FAILED@ - Due to a failure, the session and its resources are no longer
-- running.
listSessions_stateFilter :: Lens.Lens' ListSessions (Prelude.Maybe SessionState)
listSessions_stateFilter :: Lens' ListSessions (Maybe SessionState)
listSessions_stateFilter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSessions' {Maybe SessionState
stateFilter :: Maybe SessionState
$sel:stateFilter:ListSessions' :: ListSessions -> Maybe SessionState
stateFilter} -> Maybe SessionState
stateFilter) (\s :: ListSessions
s@ListSessions' {} Maybe SessionState
a -> ListSessions
s {$sel:stateFilter:ListSessions' :: Maybe SessionState
stateFilter = Maybe SessionState
a} :: ListSessions)

-- | The workgroup to which the session belongs.
listSessions_workGroup :: Lens.Lens' ListSessions Prelude.Text
listSessions_workGroup :: Lens' ListSessions Text
listSessions_workGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSessions' {Text
workGroup :: Text
$sel:workGroup:ListSessions' :: ListSessions -> Text
workGroup} -> Text
workGroup) (\s :: ListSessions
s@ListSessions' {} Text
a -> ListSessions
s {$sel:workGroup:ListSessions' :: Text
workGroup = Text
a} :: ListSessions)

instance Core.AWSRequest ListSessions where
  type AWSResponse ListSessions = ListSessionsResponse
  request :: (Service -> Service) -> ListSessions -> Request ListSessions
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 ListSessions
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListSessions)))
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 [SessionSummary] -> Int -> ListSessionsResponse
ListSessionsResponse'
            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
"Sessions" 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 ListSessions where
  hashWithSalt :: Int -> ListSessions -> Int
hashWithSalt Int
_salt ListSessions' {Maybe Natural
Maybe Text
Maybe SessionState
Text
workGroup :: Text
stateFilter :: Maybe SessionState
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:workGroup:ListSessions' :: ListSessions -> Text
$sel:stateFilter:ListSessions' :: ListSessions -> Maybe SessionState
$sel:nextToken:ListSessions' :: ListSessions -> Maybe Text
$sel:maxResults:ListSessions' :: ListSessions -> 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 SessionState
stateFilter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workGroup

instance Prelude.NFData ListSessions where
  rnf :: ListSessions -> ()
rnf ListSessions' {Maybe Natural
Maybe Text
Maybe SessionState
Text
workGroup :: Text
stateFilter :: Maybe SessionState
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:workGroup:ListSessions' :: ListSessions -> Text
$sel:stateFilter:ListSessions' :: ListSessions -> Maybe SessionState
$sel:nextToken:ListSessions' :: ListSessions -> Maybe Text
$sel:maxResults:ListSessions' :: ListSessions -> 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 SessionState
stateFilter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
workGroup

instance Data.ToHeaders ListSessions where
  toHeaders :: ListSessions -> 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
"AmazonAthena.ListSessions" :: 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 ListSessions where
  toJSON :: ListSessions -> Value
toJSON ListSessions' {Maybe Natural
Maybe Text
Maybe SessionState
Text
workGroup :: Text
stateFilter :: Maybe SessionState
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:workGroup:ListSessions' :: ListSessions -> Text
$sel:stateFilter:ListSessions' :: ListSessions -> Maybe SessionState
$sel:nextToken:ListSessions' :: ListSessions -> Maybe Text
$sel:maxResults:ListSessions' :: ListSessions -> 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
"StateFilter" 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 SessionState
stateFilter,
            forall a. a -> Maybe a
Prelude.Just (Key
"WorkGroup" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
workGroup)
          ]
      )

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

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

-- | /See:/ 'newListSessionsResponse' smart constructor.
data ListSessionsResponse = ListSessionsResponse'
  { -- | A token generated by the Athena service that specifies where to continue
    -- pagination if a previous request was truncated. To obtain the next set
    -- of pages, pass in the @NextToken@ from the response object of the
    -- previous page call.
    ListSessionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of sessions.
    ListSessionsResponse -> Maybe [SessionSummary]
sessions :: Prelude.Maybe [SessionSummary],
    -- | The response's http status code.
    ListSessionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListSessionsResponse -> ListSessionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListSessionsResponse -> ListSessionsResponse -> Bool
$c/= :: ListSessionsResponse -> ListSessionsResponse -> Bool
== :: ListSessionsResponse -> ListSessionsResponse -> Bool
$c== :: ListSessionsResponse -> ListSessionsResponse -> Bool
Prelude.Eq, ReadPrec [ListSessionsResponse]
ReadPrec ListSessionsResponse
Int -> ReadS ListSessionsResponse
ReadS [ListSessionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListSessionsResponse]
$creadListPrec :: ReadPrec [ListSessionsResponse]
readPrec :: ReadPrec ListSessionsResponse
$creadPrec :: ReadPrec ListSessionsResponse
readList :: ReadS [ListSessionsResponse]
$creadList :: ReadS [ListSessionsResponse]
readsPrec :: Int -> ReadS ListSessionsResponse
$creadsPrec :: Int -> ReadS ListSessionsResponse
Prelude.Read, Int -> ListSessionsResponse -> ShowS
[ListSessionsResponse] -> ShowS
ListSessionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListSessionsResponse] -> ShowS
$cshowList :: [ListSessionsResponse] -> ShowS
show :: ListSessionsResponse -> String
$cshow :: ListSessionsResponse -> String
showsPrec :: Int -> ListSessionsResponse -> ShowS
$cshowsPrec :: Int -> ListSessionsResponse -> ShowS
Prelude.Show, forall x. Rep ListSessionsResponse x -> ListSessionsResponse
forall x. ListSessionsResponse -> Rep ListSessionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListSessionsResponse x -> ListSessionsResponse
$cfrom :: forall x. ListSessionsResponse -> Rep ListSessionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListSessionsResponse' 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', 'listSessionsResponse_nextToken' - A token generated by the Athena service that specifies where to continue
-- pagination if a previous request was truncated. To obtain the next set
-- of pages, pass in the @NextToken@ from the response object of the
-- previous page call.
--
-- 'sessions', 'listSessionsResponse_sessions' - A list of sessions.
--
-- 'httpStatus', 'listSessionsResponse_httpStatus' - The response's http status code.
newListSessionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListSessionsResponse
newListSessionsResponse :: Int -> ListSessionsResponse
newListSessionsResponse Int
pHttpStatus_ =
  ListSessionsResponse'
    { $sel:nextToken:ListSessionsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sessions:ListSessionsResponse' :: Maybe [SessionSummary]
sessions = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListSessionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A token generated by the Athena service that specifies where to continue
-- pagination if a previous request was truncated. To obtain the next set
-- of pages, pass in the @NextToken@ from the response object of the
-- previous page call.
listSessionsResponse_nextToken :: Lens.Lens' ListSessionsResponse (Prelude.Maybe Prelude.Text)
listSessionsResponse_nextToken :: Lens' ListSessionsResponse (Maybe Text)
listSessionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSessionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListSessionsResponse' :: ListSessionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListSessionsResponse
s@ListSessionsResponse' {} Maybe Text
a -> ListSessionsResponse
s {$sel:nextToken:ListSessionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListSessionsResponse)

-- | A list of sessions.
listSessionsResponse_sessions :: Lens.Lens' ListSessionsResponse (Prelude.Maybe [SessionSummary])
listSessionsResponse_sessions :: Lens' ListSessionsResponse (Maybe [SessionSummary])
listSessionsResponse_sessions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSessionsResponse' {Maybe [SessionSummary]
sessions :: Maybe [SessionSummary]
$sel:sessions:ListSessionsResponse' :: ListSessionsResponse -> Maybe [SessionSummary]
sessions} -> Maybe [SessionSummary]
sessions) (\s :: ListSessionsResponse
s@ListSessionsResponse' {} Maybe [SessionSummary]
a -> ListSessionsResponse
s {$sel:sessions:ListSessionsResponse' :: Maybe [SessionSummary]
sessions = Maybe [SessionSummary]
a} :: ListSessionsResponse) 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.
listSessionsResponse_httpStatus :: Lens.Lens' ListSessionsResponse Prelude.Int
listSessionsResponse_httpStatus :: Lens' ListSessionsResponse Int
listSessionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSessionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListSessionsResponse' :: ListSessionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListSessionsResponse
s@ListSessionsResponse' {} Int
a -> ListSessionsResponse
s {$sel:httpStatus:ListSessionsResponse' :: Int
httpStatus = Int
a} :: ListSessionsResponse)

instance Prelude.NFData ListSessionsResponse where
  rnf :: ListSessionsResponse -> ()
rnf ListSessionsResponse' {Int
Maybe [SessionSummary]
Maybe Text
httpStatus :: Int
sessions :: Maybe [SessionSummary]
nextToken :: Maybe Text
$sel:httpStatus:ListSessionsResponse' :: ListSessionsResponse -> Int
$sel:sessions:ListSessionsResponse' :: ListSessionsResponse -> Maybe [SessionSummary]
$sel:nextToken:ListSessionsResponse' :: ListSessionsResponse -> 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 [SessionSummary]
sessions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus