{-# 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 #-}
module Amazonka.Wisdom.GetAssistant
(
GetAssistant (..),
newGetAssistant,
getAssistant_assistantId,
GetAssistantResponse (..),
newGetAssistantResponse,
getAssistantResponse_assistant,
getAssistantResponse_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.Wisdom.Types
data GetAssistant = GetAssistant'
{
GetAssistant -> Text
assistantId :: Prelude.Text
}
deriving (GetAssistant -> GetAssistant -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAssistant -> GetAssistant -> Bool
$c/= :: GetAssistant -> GetAssistant -> Bool
== :: GetAssistant -> GetAssistant -> Bool
$c== :: GetAssistant -> GetAssistant -> Bool
Prelude.Eq, ReadPrec [GetAssistant]
ReadPrec GetAssistant
Int -> ReadS GetAssistant
ReadS [GetAssistant]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAssistant]
$creadListPrec :: ReadPrec [GetAssistant]
readPrec :: ReadPrec GetAssistant
$creadPrec :: ReadPrec GetAssistant
readList :: ReadS [GetAssistant]
$creadList :: ReadS [GetAssistant]
readsPrec :: Int -> ReadS GetAssistant
$creadsPrec :: Int -> ReadS GetAssistant
Prelude.Read, Int -> GetAssistant -> ShowS
[GetAssistant] -> ShowS
GetAssistant -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAssistant] -> ShowS
$cshowList :: [GetAssistant] -> ShowS
show :: GetAssistant -> String
$cshow :: GetAssistant -> String
showsPrec :: Int -> GetAssistant -> ShowS
$cshowsPrec :: Int -> GetAssistant -> ShowS
Prelude.Show, forall x. Rep GetAssistant x -> GetAssistant
forall x. GetAssistant -> Rep GetAssistant x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAssistant x -> GetAssistant
$cfrom :: forall x. GetAssistant -> Rep GetAssistant x
Prelude.Generic)
newGetAssistant ::
Prelude.Text ->
GetAssistant
newGetAssistant :: Text -> GetAssistant
newGetAssistant Text
pAssistantId_ =
GetAssistant' {$sel:assistantId:GetAssistant' :: Text
assistantId = Text
pAssistantId_}
getAssistant_assistantId :: Lens.Lens' GetAssistant Prelude.Text
getAssistant_assistantId :: Lens' GetAssistant Text
getAssistant_assistantId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssistant' {Text
assistantId :: Text
$sel:assistantId:GetAssistant' :: GetAssistant -> Text
assistantId} -> Text
assistantId) (\s :: GetAssistant
s@GetAssistant' {} Text
a -> GetAssistant
s {$sel:assistantId:GetAssistant' :: Text
assistantId = Text
a} :: GetAssistant)
instance Core.AWSRequest GetAssistant where
type AWSResponse GetAssistant = GetAssistantResponse
request :: (Service -> Service) -> GetAssistant -> Request GetAssistant
request Service -> Service
overrides =
forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetAssistant
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetAssistant)))
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 AssistantData -> Int -> GetAssistantResponse
GetAssistantResponse'
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
"assistant")
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 GetAssistant where
hashWithSalt :: Int -> GetAssistant -> Int
hashWithSalt Int
_salt GetAssistant' {Text
assistantId :: Text
$sel:assistantId:GetAssistant' :: GetAssistant -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
assistantId
instance Prelude.NFData GetAssistant where
rnf :: GetAssistant -> ()
rnf GetAssistant' {Text
assistantId :: Text
$sel:assistantId:GetAssistant' :: GetAssistant -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
assistantId
instance Data.ToHeaders GetAssistant where
toHeaders :: GetAssistant -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToPath GetAssistant where
toPath :: GetAssistant -> ByteString
toPath GetAssistant' {Text
assistantId :: Text
$sel:assistantId:GetAssistant' :: GetAssistant -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/assistants/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
assistantId]
instance Data.ToQuery GetAssistant where
toQuery :: GetAssistant -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data GetAssistantResponse = GetAssistantResponse'
{
GetAssistantResponse -> Maybe AssistantData
assistant :: Prelude.Maybe AssistantData,
GetAssistantResponse -> Int
httpStatus :: Prelude.Int
}
deriving (GetAssistantResponse -> GetAssistantResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAssistantResponse -> GetAssistantResponse -> Bool
$c/= :: GetAssistantResponse -> GetAssistantResponse -> Bool
== :: GetAssistantResponse -> GetAssistantResponse -> Bool
$c== :: GetAssistantResponse -> GetAssistantResponse -> Bool
Prelude.Eq, ReadPrec [GetAssistantResponse]
ReadPrec GetAssistantResponse
Int -> ReadS GetAssistantResponse
ReadS [GetAssistantResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAssistantResponse]
$creadListPrec :: ReadPrec [GetAssistantResponse]
readPrec :: ReadPrec GetAssistantResponse
$creadPrec :: ReadPrec GetAssistantResponse
readList :: ReadS [GetAssistantResponse]
$creadList :: ReadS [GetAssistantResponse]
readsPrec :: Int -> ReadS GetAssistantResponse
$creadsPrec :: Int -> ReadS GetAssistantResponse
Prelude.Read, Int -> GetAssistantResponse -> ShowS
[GetAssistantResponse] -> ShowS
GetAssistantResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAssistantResponse] -> ShowS
$cshowList :: [GetAssistantResponse] -> ShowS
show :: GetAssistantResponse -> String
$cshow :: GetAssistantResponse -> String
showsPrec :: Int -> GetAssistantResponse -> ShowS
$cshowsPrec :: Int -> GetAssistantResponse -> ShowS
Prelude.Show, forall x. Rep GetAssistantResponse x -> GetAssistantResponse
forall x. GetAssistantResponse -> Rep GetAssistantResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAssistantResponse x -> GetAssistantResponse
$cfrom :: forall x. GetAssistantResponse -> Rep GetAssistantResponse x
Prelude.Generic)
newGetAssistantResponse ::
Prelude.Int ->
GetAssistantResponse
newGetAssistantResponse :: Int -> GetAssistantResponse
newGetAssistantResponse Int
pHttpStatus_ =
GetAssistantResponse'
{ $sel:assistant:GetAssistantResponse' :: Maybe AssistantData
assistant = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:GetAssistantResponse' :: Int
httpStatus = Int
pHttpStatus_
}
getAssistantResponse_assistant :: Lens.Lens' GetAssistantResponse (Prelude.Maybe AssistantData)
getAssistantResponse_assistant :: Lens' GetAssistantResponse (Maybe AssistantData)
getAssistantResponse_assistant = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssistantResponse' {Maybe AssistantData
assistant :: Maybe AssistantData
$sel:assistant:GetAssistantResponse' :: GetAssistantResponse -> Maybe AssistantData
assistant} -> Maybe AssistantData
assistant) (\s :: GetAssistantResponse
s@GetAssistantResponse' {} Maybe AssistantData
a -> GetAssistantResponse
s {$sel:assistant:GetAssistantResponse' :: Maybe AssistantData
assistant = Maybe AssistantData
a} :: GetAssistantResponse)
getAssistantResponse_httpStatus :: Lens.Lens' GetAssistantResponse Prelude.Int
getAssistantResponse_httpStatus :: Lens' GetAssistantResponse Int
getAssistantResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssistantResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetAssistantResponse' :: GetAssistantResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetAssistantResponse
s@GetAssistantResponse' {} Int
a -> GetAssistantResponse
s {$sel:httpStatus:GetAssistantResponse' :: Int
httpStatus = Int
a} :: GetAssistantResponse)
instance Prelude.NFData GetAssistantResponse where
rnf :: GetAssistantResponse -> ()
rnf GetAssistantResponse' {Int
Maybe AssistantData
httpStatus :: Int
assistant :: Maybe AssistantData
$sel:httpStatus:GetAssistantResponse' :: GetAssistantResponse -> Int
$sel:assistant:GetAssistantResponse' :: GetAssistantResponse -> Maybe AssistantData
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe AssistantData
assistant
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus