{-# 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.Support.DescribeAttachment
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the attachment that has the specified ID. Attachments can
-- include screenshots, error logs, or other files that describe your
-- issue. Attachment IDs are generated by the case management system when
-- you add an attachment to a case or case communication. Attachment IDs
-- are returned in the AttachmentDetails objects that are returned by the
-- DescribeCommunications operation.
--
-- -   You must have a Business, Enterprise On-Ramp, or Enterprise Support
--     plan to use the Amazon Web Services Support API.
--
-- -   If you call the Amazon Web Services Support API from an account that
--     doesn\'t have a Business, Enterprise On-Ramp, or Enterprise Support
--     plan, the @SubscriptionRequiredException@ error message appears. For
--     information about changing your support plan, see
--     <http://aws.amazon.com/premiumsupport/ Amazon Web Services Support>.
module Amazonka.Support.DescribeAttachment
  ( -- * Creating a Request
    DescribeAttachment (..),
    newDescribeAttachment,

    -- * Request Lenses
    describeAttachment_attachmentId,

    -- * Destructuring the Response
    DescribeAttachmentResponse (..),
    newDescribeAttachmentResponse,

    -- * Response Lenses
    describeAttachmentResponse_attachment,
    describeAttachmentResponse_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.Support.Types

-- | /See:/ 'newDescribeAttachment' smart constructor.
data DescribeAttachment = DescribeAttachment'
  { -- | The ID of the attachment to return. Attachment IDs are returned by the
    -- DescribeCommunications operation.
    DescribeAttachment -> Text
attachmentId :: Prelude.Text
  }
  deriving (DescribeAttachment -> DescribeAttachment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAttachment -> DescribeAttachment -> Bool
$c/= :: DescribeAttachment -> DescribeAttachment -> Bool
== :: DescribeAttachment -> DescribeAttachment -> Bool
$c== :: DescribeAttachment -> DescribeAttachment -> Bool
Prelude.Eq, ReadPrec [DescribeAttachment]
ReadPrec DescribeAttachment
Int -> ReadS DescribeAttachment
ReadS [DescribeAttachment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAttachment]
$creadListPrec :: ReadPrec [DescribeAttachment]
readPrec :: ReadPrec DescribeAttachment
$creadPrec :: ReadPrec DescribeAttachment
readList :: ReadS [DescribeAttachment]
$creadList :: ReadS [DescribeAttachment]
readsPrec :: Int -> ReadS DescribeAttachment
$creadsPrec :: Int -> ReadS DescribeAttachment
Prelude.Read, Int -> DescribeAttachment -> ShowS
[DescribeAttachment] -> ShowS
DescribeAttachment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAttachment] -> ShowS
$cshowList :: [DescribeAttachment] -> ShowS
show :: DescribeAttachment -> String
$cshow :: DescribeAttachment -> String
showsPrec :: Int -> DescribeAttachment -> ShowS
$cshowsPrec :: Int -> DescribeAttachment -> ShowS
Prelude.Show, forall x. Rep DescribeAttachment x -> DescribeAttachment
forall x. DescribeAttachment -> Rep DescribeAttachment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeAttachment x -> DescribeAttachment
$cfrom :: forall x. DescribeAttachment -> Rep DescribeAttachment x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAttachment' 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:
--
-- 'attachmentId', 'describeAttachment_attachmentId' - The ID of the attachment to return. Attachment IDs are returned by the
-- DescribeCommunications operation.
newDescribeAttachment ::
  -- | 'attachmentId'
  Prelude.Text ->
  DescribeAttachment
newDescribeAttachment :: Text -> DescribeAttachment
newDescribeAttachment Text
pAttachmentId_ =
  DescribeAttachment' {$sel:attachmentId:DescribeAttachment' :: Text
attachmentId = Text
pAttachmentId_}

-- | The ID of the attachment to return. Attachment IDs are returned by the
-- DescribeCommunications operation.
describeAttachment_attachmentId :: Lens.Lens' DescribeAttachment Prelude.Text
describeAttachment_attachmentId :: Lens' DescribeAttachment Text
describeAttachment_attachmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAttachment' {Text
attachmentId :: Text
$sel:attachmentId:DescribeAttachment' :: DescribeAttachment -> Text
attachmentId} -> Text
attachmentId) (\s :: DescribeAttachment
s@DescribeAttachment' {} Text
a -> DescribeAttachment
s {$sel:attachmentId:DescribeAttachment' :: Text
attachmentId = Text
a} :: DescribeAttachment)

instance Core.AWSRequest DescribeAttachment where
  type
    AWSResponse DescribeAttachment =
      DescribeAttachmentResponse
  request :: (Service -> Service)
-> DescribeAttachment -> Request DescribeAttachment
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 DescribeAttachment
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeAttachment)))
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 Attachment -> Int -> DescribeAttachmentResponse
DescribeAttachmentResponse'
            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
"attachment")
            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 DescribeAttachment where
  hashWithSalt :: Int -> DescribeAttachment -> Int
hashWithSalt Int
_salt DescribeAttachment' {Text
attachmentId :: Text
$sel:attachmentId:DescribeAttachment' :: DescribeAttachment -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
attachmentId

instance Prelude.NFData DescribeAttachment where
  rnf :: DescribeAttachment -> ()
rnf DescribeAttachment' {Text
attachmentId :: Text
$sel:attachmentId:DescribeAttachment' :: DescribeAttachment -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
attachmentId

instance Data.ToHeaders DescribeAttachment where
  toHeaders :: DescribeAttachment -> 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
"AWSSupport_20130415.DescribeAttachment" ::
                          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 DescribeAttachment where
  toJSON :: DescribeAttachment -> Value
toJSON DescribeAttachment' {Text
attachmentId :: Text
$sel:attachmentId:DescribeAttachment' :: DescribeAttachment -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"attachmentId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
attachmentId)]
      )

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

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

-- | The content and file name of the attachment returned by the
-- DescribeAttachment operation.
--
-- /See:/ 'newDescribeAttachmentResponse' smart constructor.
data DescribeAttachmentResponse = DescribeAttachmentResponse'
  { -- | This object includes the attachment content and file name.
    --
    -- In the previous response syntax, the value for the @data@ parameter
    -- appears as @blob@, which is represented as a base64-encoded string. The
    -- value for @fileName@ is the name of the attachment, such as
    -- @troubleshoot-screenshot.png@.
    DescribeAttachmentResponse -> Maybe Attachment
attachment :: Prelude.Maybe Attachment,
    -- | The response's http status code.
    DescribeAttachmentResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeAttachmentResponse -> DescribeAttachmentResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAttachmentResponse -> DescribeAttachmentResponse -> Bool
$c/= :: DescribeAttachmentResponse -> DescribeAttachmentResponse -> Bool
== :: DescribeAttachmentResponse -> DescribeAttachmentResponse -> Bool
$c== :: DescribeAttachmentResponse -> DescribeAttachmentResponse -> Bool
Prelude.Eq, ReadPrec [DescribeAttachmentResponse]
ReadPrec DescribeAttachmentResponse
Int -> ReadS DescribeAttachmentResponse
ReadS [DescribeAttachmentResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAttachmentResponse]
$creadListPrec :: ReadPrec [DescribeAttachmentResponse]
readPrec :: ReadPrec DescribeAttachmentResponse
$creadPrec :: ReadPrec DescribeAttachmentResponse
readList :: ReadS [DescribeAttachmentResponse]
$creadList :: ReadS [DescribeAttachmentResponse]
readsPrec :: Int -> ReadS DescribeAttachmentResponse
$creadsPrec :: Int -> ReadS DescribeAttachmentResponse
Prelude.Read, Int -> DescribeAttachmentResponse -> ShowS
[DescribeAttachmentResponse] -> ShowS
DescribeAttachmentResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAttachmentResponse] -> ShowS
$cshowList :: [DescribeAttachmentResponse] -> ShowS
show :: DescribeAttachmentResponse -> String
$cshow :: DescribeAttachmentResponse -> String
showsPrec :: Int -> DescribeAttachmentResponse -> ShowS
$cshowsPrec :: Int -> DescribeAttachmentResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeAttachmentResponse x -> DescribeAttachmentResponse
forall x.
DescribeAttachmentResponse -> Rep DescribeAttachmentResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeAttachmentResponse x -> DescribeAttachmentResponse
$cfrom :: forall x.
DescribeAttachmentResponse -> Rep DescribeAttachmentResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAttachmentResponse' 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:
--
-- 'attachment', 'describeAttachmentResponse_attachment' - This object includes the attachment content and file name.
--
-- In the previous response syntax, the value for the @data@ parameter
-- appears as @blob@, which is represented as a base64-encoded string. The
-- value for @fileName@ is the name of the attachment, such as
-- @troubleshoot-screenshot.png@.
--
-- 'httpStatus', 'describeAttachmentResponse_httpStatus' - The response's http status code.
newDescribeAttachmentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeAttachmentResponse
newDescribeAttachmentResponse :: Int -> DescribeAttachmentResponse
newDescribeAttachmentResponse Int
pHttpStatus_ =
  DescribeAttachmentResponse'
    { $sel:attachment:DescribeAttachmentResponse' :: Maybe Attachment
attachment =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeAttachmentResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | This object includes the attachment content and file name.
--
-- In the previous response syntax, the value for the @data@ parameter
-- appears as @blob@, which is represented as a base64-encoded string. The
-- value for @fileName@ is the name of the attachment, such as
-- @troubleshoot-screenshot.png@.
describeAttachmentResponse_attachment :: Lens.Lens' DescribeAttachmentResponse (Prelude.Maybe Attachment)
describeAttachmentResponse_attachment :: Lens' DescribeAttachmentResponse (Maybe Attachment)
describeAttachmentResponse_attachment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAttachmentResponse' {Maybe Attachment
attachment :: Maybe Attachment
$sel:attachment:DescribeAttachmentResponse' :: DescribeAttachmentResponse -> Maybe Attachment
attachment} -> Maybe Attachment
attachment) (\s :: DescribeAttachmentResponse
s@DescribeAttachmentResponse' {} Maybe Attachment
a -> DescribeAttachmentResponse
s {$sel:attachment:DescribeAttachmentResponse' :: Maybe Attachment
attachment = Maybe Attachment
a} :: DescribeAttachmentResponse)

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

instance Prelude.NFData DescribeAttachmentResponse where
  rnf :: DescribeAttachmentResponse -> ()
rnf DescribeAttachmentResponse' {Int
Maybe Attachment
httpStatus :: Int
attachment :: Maybe Attachment
$sel:httpStatus:DescribeAttachmentResponse' :: DescribeAttachmentResponse -> Int
$sel:attachment:DescribeAttachmentResponse' :: DescribeAttachmentResponse -> Maybe Attachment
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Attachment
attachment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus