{-# 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.ConnectParticipant.GetTranscript
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves a transcript of the session, including details about any
-- attachments.
--
-- @ConnectionToken@ is used for invoking this API instead of
-- @ParticipantToken@.
--
-- The Amazon Connect Participant Service APIs do not use
-- <https://docs.aws.amazon.com/general/latest/gr/signature-version-4.html Signature Version 4 authentication>.
module Amazonka.ConnectParticipant.GetTranscript
  ( -- * Creating a Request
    GetTranscript (..),
    newGetTranscript,

    -- * Request Lenses
    getTranscript_contactId,
    getTranscript_maxResults,
    getTranscript_nextToken,
    getTranscript_scanDirection,
    getTranscript_sortOrder,
    getTranscript_startPosition,
    getTranscript_connectionToken,

    -- * Destructuring the Response
    GetTranscriptResponse (..),
    newGetTranscriptResponse,

    -- * Response Lenses
    getTranscriptResponse_initialContactId,
    getTranscriptResponse_nextToken,
    getTranscriptResponse_transcript,
    getTranscriptResponse_httpStatus,
  )
where

import Amazonka.ConnectParticipant.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:/ 'newGetTranscript' smart constructor.
data GetTranscript = GetTranscript'
  { -- | The contactId from the current contact chain for which transcript is
    -- needed.
    GetTranscript -> Maybe Text
contactId :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of results to return in the page. Default: 10.
    GetTranscript -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The pagination token. Use the value returned previously in the next
    -- subsequent request to retrieve the next set of results.
    GetTranscript -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The direction from StartPosition from which to retrieve message.
    -- Default: BACKWARD when no StartPosition is provided, FORWARD with
    -- StartPosition.
    GetTranscript -> Maybe ScanDirection
scanDirection :: Prelude.Maybe ScanDirection,
    -- | The sort order for the records. Default: DESCENDING.
    GetTranscript -> Maybe SortKey
sortOrder :: Prelude.Maybe SortKey,
    -- | A filtering option for where to start.
    GetTranscript -> Maybe StartPosition
startPosition :: Prelude.Maybe StartPosition,
    -- | The authentication token associated with the participant\'s connection.
    GetTranscript -> Text
connectionToken :: Prelude.Text
  }
  deriving (GetTranscript -> GetTranscript -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTranscript -> GetTranscript -> Bool
$c/= :: GetTranscript -> GetTranscript -> Bool
== :: GetTranscript -> GetTranscript -> Bool
$c== :: GetTranscript -> GetTranscript -> Bool
Prelude.Eq, ReadPrec [GetTranscript]
ReadPrec GetTranscript
Int -> ReadS GetTranscript
ReadS [GetTranscript]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTranscript]
$creadListPrec :: ReadPrec [GetTranscript]
readPrec :: ReadPrec GetTranscript
$creadPrec :: ReadPrec GetTranscript
readList :: ReadS [GetTranscript]
$creadList :: ReadS [GetTranscript]
readsPrec :: Int -> ReadS GetTranscript
$creadsPrec :: Int -> ReadS GetTranscript
Prelude.Read, Int -> GetTranscript -> ShowS
[GetTranscript] -> ShowS
GetTranscript -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTranscript] -> ShowS
$cshowList :: [GetTranscript] -> ShowS
show :: GetTranscript -> String
$cshow :: GetTranscript -> String
showsPrec :: Int -> GetTranscript -> ShowS
$cshowsPrec :: Int -> GetTranscript -> ShowS
Prelude.Show, forall x. Rep GetTranscript x -> GetTranscript
forall x. GetTranscript -> Rep GetTranscript x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetTranscript x -> GetTranscript
$cfrom :: forall x. GetTranscript -> Rep GetTranscript x
Prelude.Generic)

-- |
-- Create a value of 'GetTranscript' 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:
--
-- 'contactId', 'getTranscript_contactId' - The contactId from the current contact chain for which transcript is
-- needed.
--
-- 'maxResults', 'getTranscript_maxResults' - The maximum number of results to return in the page. Default: 10.
--
-- 'nextToken', 'getTranscript_nextToken' - The pagination token. Use the value returned previously in the next
-- subsequent request to retrieve the next set of results.
--
-- 'scanDirection', 'getTranscript_scanDirection' - The direction from StartPosition from which to retrieve message.
-- Default: BACKWARD when no StartPosition is provided, FORWARD with
-- StartPosition.
--
-- 'sortOrder', 'getTranscript_sortOrder' - The sort order for the records. Default: DESCENDING.
--
-- 'startPosition', 'getTranscript_startPosition' - A filtering option for where to start.
--
-- 'connectionToken', 'getTranscript_connectionToken' - The authentication token associated with the participant\'s connection.
newGetTranscript ::
  -- | 'connectionToken'
  Prelude.Text ->
  GetTranscript
newGetTranscript :: Text -> GetTranscript
newGetTranscript Text
pConnectionToken_ =
  GetTranscript'
    { $sel:contactId:GetTranscript' :: Maybe Text
contactId = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:GetTranscript' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetTranscript' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:scanDirection:GetTranscript' :: Maybe ScanDirection
scanDirection = forall a. Maybe a
Prelude.Nothing,
      $sel:sortOrder:GetTranscript' :: Maybe SortKey
sortOrder = forall a. Maybe a
Prelude.Nothing,
      $sel:startPosition:GetTranscript' :: Maybe StartPosition
startPosition = forall a. Maybe a
Prelude.Nothing,
      $sel:connectionToken:GetTranscript' :: Text
connectionToken = Text
pConnectionToken_
    }

-- | The contactId from the current contact chain for which transcript is
-- needed.
getTranscript_contactId :: Lens.Lens' GetTranscript (Prelude.Maybe Prelude.Text)
getTranscript_contactId :: Lens' GetTranscript (Maybe Text)
getTranscript_contactId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTranscript' {Maybe Text
contactId :: Maybe Text
$sel:contactId:GetTranscript' :: GetTranscript -> Maybe Text
contactId} -> Maybe Text
contactId) (\s :: GetTranscript
s@GetTranscript' {} Maybe Text
a -> GetTranscript
s {$sel:contactId:GetTranscript' :: Maybe Text
contactId = Maybe Text
a} :: GetTranscript)

-- | The maximum number of results to return in the page. Default: 10.
getTranscript_maxResults :: Lens.Lens' GetTranscript (Prelude.Maybe Prelude.Natural)
getTranscript_maxResults :: Lens' GetTranscript (Maybe Natural)
getTranscript_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTranscript' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetTranscript' :: GetTranscript -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetTranscript
s@GetTranscript' {} Maybe Natural
a -> GetTranscript
s {$sel:maxResults:GetTranscript' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetTranscript)

-- | The pagination token. Use the value returned previously in the next
-- subsequent request to retrieve the next set of results.
getTranscript_nextToken :: Lens.Lens' GetTranscript (Prelude.Maybe Prelude.Text)
getTranscript_nextToken :: Lens' GetTranscript (Maybe Text)
getTranscript_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTranscript' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetTranscript' :: GetTranscript -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetTranscript
s@GetTranscript' {} Maybe Text
a -> GetTranscript
s {$sel:nextToken:GetTranscript' :: Maybe Text
nextToken = Maybe Text
a} :: GetTranscript)

-- | The direction from StartPosition from which to retrieve message.
-- Default: BACKWARD when no StartPosition is provided, FORWARD with
-- StartPosition.
getTranscript_scanDirection :: Lens.Lens' GetTranscript (Prelude.Maybe ScanDirection)
getTranscript_scanDirection :: Lens' GetTranscript (Maybe ScanDirection)
getTranscript_scanDirection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTranscript' {Maybe ScanDirection
scanDirection :: Maybe ScanDirection
$sel:scanDirection:GetTranscript' :: GetTranscript -> Maybe ScanDirection
scanDirection} -> Maybe ScanDirection
scanDirection) (\s :: GetTranscript
s@GetTranscript' {} Maybe ScanDirection
a -> GetTranscript
s {$sel:scanDirection:GetTranscript' :: Maybe ScanDirection
scanDirection = Maybe ScanDirection
a} :: GetTranscript)

-- | The sort order for the records. Default: DESCENDING.
getTranscript_sortOrder :: Lens.Lens' GetTranscript (Prelude.Maybe SortKey)
getTranscript_sortOrder :: Lens' GetTranscript (Maybe SortKey)
getTranscript_sortOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTranscript' {Maybe SortKey
sortOrder :: Maybe SortKey
$sel:sortOrder:GetTranscript' :: GetTranscript -> Maybe SortKey
sortOrder} -> Maybe SortKey
sortOrder) (\s :: GetTranscript
s@GetTranscript' {} Maybe SortKey
a -> GetTranscript
s {$sel:sortOrder:GetTranscript' :: Maybe SortKey
sortOrder = Maybe SortKey
a} :: GetTranscript)

-- | A filtering option for where to start.
getTranscript_startPosition :: Lens.Lens' GetTranscript (Prelude.Maybe StartPosition)
getTranscript_startPosition :: Lens' GetTranscript (Maybe StartPosition)
getTranscript_startPosition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTranscript' {Maybe StartPosition
startPosition :: Maybe StartPosition
$sel:startPosition:GetTranscript' :: GetTranscript -> Maybe StartPosition
startPosition} -> Maybe StartPosition
startPosition) (\s :: GetTranscript
s@GetTranscript' {} Maybe StartPosition
a -> GetTranscript
s {$sel:startPosition:GetTranscript' :: Maybe StartPosition
startPosition = Maybe StartPosition
a} :: GetTranscript)

-- | The authentication token associated with the participant\'s connection.
getTranscript_connectionToken :: Lens.Lens' GetTranscript Prelude.Text
getTranscript_connectionToken :: Lens' GetTranscript Text
getTranscript_connectionToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTranscript' {Text
connectionToken :: Text
$sel:connectionToken:GetTranscript' :: GetTranscript -> Text
connectionToken} -> Text
connectionToken) (\s :: GetTranscript
s@GetTranscript' {} Text
a -> GetTranscript
s {$sel:connectionToken:GetTranscript' :: Text
connectionToken = Text
a} :: GetTranscript)

instance Core.AWSRequest GetTranscript where
  type
    AWSResponse GetTranscript =
      GetTranscriptResponse
  request :: (Service -> Service) -> GetTranscript -> Request GetTranscript
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 GetTranscript
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetTranscript)))
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 Text -> Maybe [Item] -> Int -> GetTranscriptResponse
GetTranscriptResponse'
            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
"InitialContactId")
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Transcript" 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 GetTranscript where
  hashWithSalt :: Int -> GetTranscript -> Int
hashWithSalt Int
_salt GetTranscript' {Maybe Natural
Maybe Text
Maybe ScanDirection
Maybe SortKey
Maybe StartPosition
Text
connectionToken :: Text
startPosition :: Maybe StartPosition
sortOrder :: Maybe SortKey
scanDirection :: Maybe ScanDirection
nextToken :: Maybe Text
maxResults :: Maybe Natural
contactId :: Maybe Text
$sel:connectionToken:GetTranscript' :: GetTranscript -> Text
$sel:startPosition:GetTranscript' :: GetTranscript -> Maybe StartPosition
$sel:sortOrder:GetTranscript' :: GetTranscript -> Maybe SortKey
$sel:scanDirection:GetTranscript' :: GetTranscript -> Maybe ScanDirection
$sel:nextToken:GetTranscript' :: GetTranscript -> Maybe Text
$sel:maxResults:GetTranscript' :: GetTranscript -> Maybe Natural
$sel:contactId:GetTranscript' :: GetTranscript -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
contactId
      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 ScanDirection
scanDirection
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortKey
sortOrder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StartPosition
startPosition
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
connectionToken

instance Prelude.NFData GetTranscript where
  rnf :: GetTranscript -> ()
rnf GetTranscript' {Maybe Natural
Maybe Text
Maybe ScanDirection
Maybe SortKey
Maybe StartPosition
Text
connectionToken :: Text
startPosition :: Maybe StartPosition
sortOrder :: Maybe SortKey
scanDirection :: Maybe ScanDirection
nextToken :: Maybe Text
maxResults :: Maybe Natural
contactId :: Maybe Text
$sel:connectionToken:GetTranscript' :: GetTranscript -> Text
$sel:startPosition:GetTranscript' :: GetTranscript -> Maybe StartPosition
$sel:sortOrder:GetTranscript' :: GetTranscript -> Maybe SortKey
$sel:scanDirection:GetTranscript' :: GetTranscript -> Maybe ScanDirection
$sel:nextToken:GetTranscript' :: GetTranscript -> Maybe Text
$sel:maxResults:GetTranscript' :: GetTranscript -> Maybe Natural
$sel:contactId:GetTranscript' :: GetTranscript -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
contactId
      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 ScanDirection
scanDirection
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SortKey
sortOrder
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StartPosition
startPosition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
connectionToken

instance Data.ToHeaders GetTranscript where
  toHeaders :: GetTranscript -> ResponseHeaders
toHeaders GetTranscript' {Maybe Natural
Maybe Text
Maybe ScanDirection
Maybe SortKey
Maybe StartPosition
Text
connectionToken :: Text
startPosition :: Maybe StartPosition
sortOrder :: Maybe SortKey
scanDirection :: Maybe ScanDirection
nextToken :: Maybe Text
maxResults :: Maybe Natural
contactId :: Maybe Text
$sel:connectionToken:GetTranscript' :: GetTranscript -> Text
$sel:startPosition:GetTranscript' :: GetTranscript -> Maybe StartPosition
$sel:sortOrder:GetTranscript' :: GetTranscript -> Maybe SortKey
$sel:scanDirection:GetTranscript' :: GetTranscript -> Maybe ScanDirection
$sel:nextToken:GetTranscript' :: GetTranscript -> Maybe Text
$sel:maxResults:GetTranscript' :: GetTranscript -> Maybe Natural
$sel:contactId:GetTranscript' :: GetTranscript -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"X-Amz-Bearer" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Text
connectionToken,
        HeaderName
"Content-Type"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/x-amz-json-1.1" :: Prelude.ByteString)
      ]

instance Data.ToJSON GetTranscript where
  toJSON :: GetTranscript -> Value
toJSON GetTranscript' {Maybe Natural
Maybe Text
Maybe ScanDirection
Maybe SortKey
Maybe StartPosition
Text
connectionToken :: Text
startPosition :: Maybe StartPosition
sortOrder :: Maybe SortKey
scanDirection :: Maybe ScanDirection
nextToken :: Maybe Text
maxResults :: Maybe Natural
contactId :: Maybe Text
$sel:connectionToken:GetTranscript' :: GetTranscript -> Text
$sel:startPosition:GetTranscript' :: GetTranscript -> Maybe StartPosition
$sel:sortOrder:GetTranscript' :: GetTranscript -> Maybe SortKey
$sel:scanDirection:GetTranscript' :: GetTranscript -> Maybe ScanDirection
$sel:nextToken:GetTranscript' :: GetTranscript -> Maybe Text
$sel:maxResults:GetTranscript' :: GetTranscript -> Maybe Natural
$sel:contactId:GetTranscript' :: GetTranscript -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ContactId" 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
contactId,
            (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
"ScanDirection" 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 ScanDirection
scanDirection,
            (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 SortKey
sortOrder,
            (Key
"StartPosition" 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 StartPosition
startPosition
          ]
      )

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

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

-- | /See:/ 'newGetTranscriptResponse' smart constructor.
data GetTranscriptResponse = GetTranscriptResponse'
  { -- | The initial contact ID for the contact.
    GetTranscriptResponse -> Maybe Text
initialContactId :: Prelude.Maybe Prelude.Text,
    -- | The pagination token. Use the value returned previously in the next
    -- subsequent request to retrieve the next set of results.
    GetTranscriptResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The list of messages in the session.
    GetTranscriptResponse -> Maybe [Item]
transcript :: Prelude.Maybe [Item],
    -- | The response's http status code.
    GetTranscriptResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetTranscriptResponse -> GetTranscriptResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTranscriptResponse -> GetTranscriptResponse -> Bool
$c/= :: GetTranscriptResponse -> GetTranscriptResponse -> Bool
== :: GetTranscriptResponse -> GetTranscriptResponse -> Bool
$c== :: GetTranscriptResponse -> GetTranscriptResponse -> Bool
Prelude.Eq, ReadPrec [GetTranscriptResponse]
ReadPrec GetTranscriptResponse
Int -> ReadS GetTranscriptResponse
ReadS [GetTranscriptResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTranscriptResponse]
$creadListPrec :: ReadPrec [GetTranscriptResponse]
readPrec :: ReadPrec GetTranscriptResponse
$creadPrec :: ReadPrec GetTranscriptResponse
readList :: ReadS [GetTranscriptResponse]
$creadList :: ReadS [GetTranscriptResponse]
readsPrec :: Int -> ReadS GetTranscriptResponse
$creadsPrec :: Int -> ReadS GetTranscriptResponse
Prelude.Read, Int -> GetTranscriptResponse -> ShowS
[GetTranscriptResponse] -> ShowS
GetTranscriptResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTranscriptResponse] -> ShowS
$cshowList :: [GetTranscriptResponse] -> ShowS
show :: GetTranscriptResponse -> String
$cshow :: GetTranscriptResponse -> String
showsPrec :: Int -> GetTranscriptResponse -> ShowS
$cshowsPrec :: Int -> GetTranscriptResponse -> ShowS
Prelude.Show, forall x. Rep GetTranscriptResponse x -> GetTranscriptResponse
forall x. GetTranscriptResponse -> Rep GetTranscriptResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetTranscriptResponse x -> GetTranscriptResponse
$cfrom :: forall x. GetTranscriptResponse -> Rep GetTranscriptResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetTranscriptResponse' 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:
--
-- 'initialContactId', 'getTranscriptResponse_initialContactId' - The initial contact ID for the contact.
--
-- 'nextToken', 'getTranscriptResponse_nextToken' - The pagination token. Use the value returned previously in the next
-- subsequent request to retrieve the next set of results.
--
-- 'transcript', 'getTranscriptResponse_transcript' - The list of messages in the session.
--
-- 'httpStatus', 'getTranscriptResponse_httpStatus' - The response's http status code.
newGetTranscriptResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetTranscriptResponse
newGetTranscriptResponse :: Int -> GetTranscriptResponse
newGetTranscriptResponse Int
pHttpStatus_ =
  GetTranscriptResponse'
    { $sel:initialContactId:GetTranscriptResponse' :: Maybe Text
initialContactId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetTranscriptResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:transcript:GetTranscriptResponse' :: Maybe [Item]
transcript = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetTranscriptResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The initial contact ID for the contact.
getTranscriptResponse_initialContactId :: Lens.Lens' GetTranscriptResponse (Prelude.Maybe Prelude.Text)
getTranscriptResponse_initialContactId :: Lens' GetTranscriptResponse (Maybe Text)
getTranscriptResponse_initialContactId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTranscriptResponse' {Maybe Text
initialContactId :: Maybe Text
$sel:initialContactId:GetTranscriptResponse' :: GetTranscriptResponse -> Maybe Text
initialContactId} -> Maybe Text
initialContactId) (\s :: GetTranscriptResponse
s@GetTranscriptResponse' {} Maybe Text
a -> GetTranscriptResponse
s {$sel:initialContactId:GetTranscriptResponse' :: Maybe Text
initialContactId = Maybe Text
a} :: GetTranscriptResponse)

-- | The pagination token. Use the value returned previously in the next
-- subsequent request to retrieve the next set of results.
getTranscriptResponse_nextToken :: Lens.Lens' GetTranscriptResponse (Prelude.Maybe Prelude.Text)
getTranscriptResponse_nextToken :: Lens' GetTranscriptResponse (Maybe Text)
getTranscriptResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTranscriptResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetTranscriptResponse' :: GetTranscriptResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetTranscriptResponse
s@GetTranscriptResponse' {} Maybe Text
a -> GetTranscriptResponse
s {$sel:nextToken:GetTranscriptResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetTranscriptResponse)

-- | The list of messages in the session.
getTranscriptResponse_transcript :: Lens.Lens' GetTranscriptResponse (Prelude.Maybe [Item])
getTranscriptResponse_transcript :: Lens' GetTranscriptResponse (Maybe [Item])
getTranscriptResponse_transcript = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTranscriptResponse' {Maybe [Item]
transcript :: Maybe [Item]
$sel:transcript:GetTranscriptResponse' :: GetTranscriptResponse -> Maybe [Item]
transcript} -> Maybe [Item]
transcript) (\s :: GetTranscriptResponse
s@GetTranscriptResponse' {} Maybe [Item]
a -> GetTranscriptResponse
s {$sel:transcript:GetTranscriptResponse' :: Maybe [Item]
transcript = Maybe [Item]
a} :: GetTranscriptResponse) 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.
getTranscriptResponse_httpStatus :: Lens.Lens' GetTranscriptResponse Prelude.Int
getTranscriptResponse_httpStatus :: Lens' GetTranscriptResponse Int
getTranscriptResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTranscriptResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetTranscriptResponse' :: GetTranscriptResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetTranscriptResponse
s@GetTranscriptResponse' {} Int
a -> GetTranscriptResponse
s {$sel:httpStatus:GetTranscriptResponse' :: Int
httpStatus = Int
a} :: GetTranscriptResponse)

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