{-# 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.IoTWireless.GetDestination
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets information about a destination.
module Amazonka.IoTWireless.GetDestination
  ( -- * Creating a Request
    GetDestination (..),
    newGetDestination,

    -- * Request Lenses
    getDestination_name,

    -- * Destructuring the Response
    GetDestinationResponse (..),
    newGetDestinationResponse,

    -- * Response Lenses
    getDestinationResponse_arn,
    getDestinationResponse_description,
    getDestinationResponse_expression,
    getDestinationResponse_expressionType,
    getDestinationResponse_name,
    getDestinationResponse_roleArn,
    getDestinationResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoTWireless.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetDestination' smart constructor.
data GetDestination = GetDestination'
  { -- | The name of the resource to get.
    GetDestination -> Text
name :: Prelude.Text
  }
  deriving (GetDestination -> GetDestination -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDestination -> GetDestination -> Bool
$c/= :: GetDestination -> GetDestination -> Bool
== :: GetDestination -> GetDestination -> Bool
$c== :: GetDestination -> GetDestination -> Bool
Prelude.Eq, ReadPrec [GetDestination]
ReadPrec GetDestination
Int -> ReadS GetDestination
ReadS [GetDestination]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDestination]
$creadListPrec :: ReadPrec [GetDestination]
readPrec :: ReadPrec GetDestination
$creadPrec :: ReadPrec GetDestination
readList :: ReadS [GetDestination]
$creadList :: ReadS [GetDestination]
readsPrec :: Int -> ReadS GetDestination
$creadsPrec :: Int -> ReadS GetDestination
Prelude.Read, Int -> GetDestination -> ShowS
[GetDestination] -> ShowS
GetDestination -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDestination] -> ShowS
$cshowList :: [GetDestination] -> ShowS
show :: GetDestination -> String
$cshow :: GetDestination -> String
showsPrec :: Int -> GetDestination -> ShowS
$cshowsPrec :: Int -> GetDestination -> ShowS
Prelude.Show, forall x. Rep GetDestination x -> GetDestination
forall x. GetDestination -> Rep GetDestination x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDestination x -> GetDestination
$cfrom :: forall x. GetDestination -> Rep GetDestination x
Prelude.Generic)

-- |
-- Create a value of 'GetDestination' 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:
--
-- 'name', 'getDestination_name' - The name of the resource to get.
newGetDestination ::
  -- | 'name'
  Prelude.Text ->
  GetDestination
newGetDestination :: Text -> GetDestination
newGetDestination Text
pName_ =
  GetDestination' {$sel:name:GetDestination' :: Text
name = Text
pName_}

-- | The name of the resource to get.
getDestination_name :: Lens.Lens' GetDestination Prelude.Text
getDestination_name :: Lens' GetDestination Text
getDestination_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDestination' {Text
name :: Text
$sel:name:GetDestination' :: GetDestination -> Text
name} -> Text
name) (\s :: GetDestination
s@GetDestination' {} Text
a -> GetDestination
s {$sel:name:GetDestination' :: Text
name = Text
a} :: GetDestination)

instance Core.AWSRequest GetDestination where
  type
    AWSResponse GetDestination =
      GetDestinationResponse
  request :: (Service -> Service) -> GetDestination -> Request GetDestination
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 GetDestination
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetDestination)))
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 Text
-> Maybe ExpressionType
-> Maybe Text
-> Maybe Text
-> Int
-> GetDestinationResponse
GetDestinationResponse'
            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
"Arn")
            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
"Description")
            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
"Expression")
            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
"ExpressionType")
            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
"Name")
            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
"RoleArn")
            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 GetDestination where
  hashWithSalt :: Int -> GetDestination -> Int
hashWithSalt Int
_salt GetDestination' {Text
name :: Text
$sel:name:GetDestination' :: GetDestination -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

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

instance Data.ToHeaders GetDestination where
  toHeaders :: GetDestination -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath GetDestination where
  toPath :: GetDestination -> ByteString
toPath GetDestination' {Text
name :: Text
$sel:name:GetDestination' :: GetDestination -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/destinations/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
name]

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

-- | /See:/ 'newGetDestinationResponse' smart constructor.
data GetDestinationResponse = GetDestinationResponse'
  { -- | The Amazon Resource Name of the resource.
    GetDestinationResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The description of the resource.
    GetDestinationResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The rule name or topic rule to send messages to.
    GetDestinationResponse -> Maybe Text
expression :: Prelude.Maybe Prelude.Text,
    -- | The type of value in @Expression@.
    GetDestinationResponse -> Maybe ExpressionType
expressionType :: Prelude.Maybe ExpressionType,
    -- | The name of the resource.
    GetDestinationResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the IAM Role that authorizes the destination.
    GetDestinationResponse -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetDestinationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetDestinationResponse -> GetDestinationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDestinationResponse -> GetDestinationResponse -> Bool
$c/= :: GetDestinationResponse -> GetDestinationResponse -> Bool
== :: GetDestinationResponse -> GetDestinationResponse -> Bool
$c== :: GetDestinationResponse -> GetDestinationResponse -> Bool
Prelude.Eq, ReadPrec [GetDestinationResponse]
ReadPrec GetDestinationResponse
Int -> ReadS GetDestinationResponse
ReadS [GetDestinationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDestinationResponse]
$creadListPrec :: ReadPrec [GetDestinationResponse]
readPrec :: ReadPrec GetDestinationResponse
$creadPrec :: ReadPrec GetDestinationResponse
readList :: ReadS [GetDestinationResponse]
$creadList :: ReadS [GetDestinationResponse]
readsPrec :: Int -> ReadS GetDestinationResponse
$creadsPrec :: Int -> ReadS GetDestinationResponse
Prelude.Read, Int -> GetDestinationResponse -> ShowS
[GetDestinationResponse] -> ShowS
GetDestinationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDestinationResponse] -> ShowS
$cshowList :: [GetDestinationResponse] -> ShowS
show :: GetDestinationResponse -> String
$cshow :: GetDestinationResponse -> String
showsPrec :: Int -> GetDestinationResponse -> ShowS
$cshowsPrec :: Int -> GetDestinationResponse -> ShowS
Prelude.Show, forall x. Rep GetDestinationResponse x -> GetDestinationResponse
forall x. GetDestinationResponse -> Rep GetDestinationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDestinationResponse x -> GetDestinationResponse
$cfrom :: forall x. GetDestinationResponse -> Rep GetDestinationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetDestinationResponse' 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:
--
-- 'arn', 'getDestinationResponse_arn' - The Amazon Resource Name of the resource.
--
-- 'description', 'getDestinationResponse_description' - The description of the resource.
--
-- 'expression', 'getDestinationResponse_expression' - The rule name or topic rule to send messages to.
--
-- 'expressionType', 'getDestinationResponse_expressionType' - The type of value in @Expression@.
--
-- 'name', 'getDestinationResponse_name' - The name of the resource.
--
-- 'roleArn', 'getDestinationResponse_roleArn' - The ARN of the IAM Role that authorizes the destination.
--
-- 'httpStatus', 'getDestinationResponse_httpStatus' - The response's http status code.
newGetDestinationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetDestinationResponse
newGetDestinationResponse :: Int -> GetDestinationResponse
newGetDestinationResponse Int
pHttpStatus_ =
  GetDestinationResponse'
    { $sel:arn:GetDestinationResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:description:GetDestinationResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:expression:GetDestinationResponse' :: Maybe Text
expression = forall a. Maybe a
Prelude.Nothing,
      $sel:expressionType:GetDestinationResponse' :: Maybe ExpressionType
expressionType = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetDestinationResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:GetDestinationResponse' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetDestinationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name of the resource.
getDestinationResponse_arn :: Lens.Lens' GetDestinationResponse (Prelude.Maybe Prelude.Text)
getDestinationResponse_arn :: Lens' GetDestinationResponse (Maybe Text)
getDestinationResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDestinationResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:GetDestinationResponse' :: GetDestinationResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: GetDestinationResponse
s@GetDestinationResponse' {} Maybe Text
a -> GetDestinationResponse
s {$sel:arn:GetDestinationResponse' :: Maybe Text
arn = Maybe Text
a} :: GetDestinationResponse)

-- | The description of the resource.
getDestinationResponse_description :: Lens.Lens' GetDestinationResponse (Prelude.Maybe Prelude.Text)
getDestinationResponse_description :: Lens' GetDestinationResponse (Maybe Text)
getDestinationResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDestinationResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetDestinationResponse' :: GetDestinationResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetDestinationResponse
s@GetDestinationResponse' {} Maybe Text
a -> GetDestinationResponse
s {$sel:description:GetDestinationResponse' :: Maybe Text
description = Maybe Text
a} :: GetDestinationResponse)

-- | The rule name or topic rule to send messages to.
getDestinationResponse_expression :: Lens.Lens' GetDestinationResponse (Prelude.Maybe Prelude.Text)
getDestinationResponse_expression :: Lens' GetDestinationResponse (Maybe Text)
getDestinationResponse_expression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDestinationResponse' {Maybe Text
expression :: Maybe Text
$sel:expression:GetDestinationResponse' :: GetDestinationResponse -> Maybe Text
expression} -> Maybe Text
expression) (\s :: GetDestinationResponse
s@GetDestinationResponse' {} Maybe Text
a -> GetDestinationResponse
s {$sel:expression:GetDestinationResponse' :: Maybe Text
expression = Maybe Text
a} :: GetDestinationResponse)

-- | The type of value in @Expression@.
getDestinationResponse_expressionType :: Lens.Lens' GetDestinationResponse (Prelude.Maybe ExpressionType)
getDestinationResponse_expressionType :: Lens' GetDestinationResponse (Maybe ExpressionType)
getDestinationResponse_expressionType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDestinationResponse' {Maybe ExpressionType
expressionType :: Maybe ExpressionType
$sel:expressionType:GetDestinationResponse' :: GetDestinationResponse -> Maybe ExpressionType
expressionType} -> Maybe ExpressionType
expressionType) (\s :: GetDestinationResponse
s@GetDestinationResponse' {} Maybe ExpressionType
a -> GetDestinationResponse
s {$sel:expressionType:GetDestinationResponse' :: Maybe ExpressionType
expressionType = Maybe ExpressionType
a} :: GetDestinationResponse)

-- | The name of the resource.
getDestinationResponse_name :: Lens.Lens' GetDestinationResponse (Prelude.Maybe Prelude.Text)
getDestinationResponse_name :: Lens' GetDestinationResponse (Maybe Text)
getDestinationResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDestinationResponse' {Maybe Text
name :: Maybe Text
$sel:name:GetDestinationResponse' :: GetDestinationResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: GetDestinationResponse
s@GetDestinationResponse' {} Maybe Text
a -> GetDestinationResponse
s {$sel:name:GetDestinationResponse' :: Maybe Text
name = Maybe Text
a} :: GetDestinationResponse)

-- | The ARN of the IAM Role that authorizes the destination.
getDestinationResponse_roleArn :: Lens.Lens' GetDestinationResponse (Prelude.Maybe Prelude.Text)
getDestinationResponse_roleArn :: Lens' GetDestinationResponse (Maybe Text)
getDestinationResponse_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDestinationResponse' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:GetDestinationResponse' :: GetDestinationResponse -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: GetDestinationResponse
s@GetDestinationResponse' {} Maybe Text
a -> GetDestinationResponse
s {$sel:roleArn:GetDestinationResponse' :: Maybe Text
roleArn = Maybe Text
a} :: GetDestinationResponse)

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

instance Prelude.NFData GetDestinationResponse where
  rnf :: GetDestinationResponse -> ()
rnf GetDestinationResponse' {Int
Maybe Text
Maybe ExpressionType
httpStatus :: Int
roleArn :: Maybe Text
name :: Maybe Text
expressionType :: Maybe ExpressionType
expression :: Maybe Text
description :: Maybe Text
arn :: Maybe Text
$sel:httpStatus:GetDestinationResponse' :: GetDestinationResponse -> Int
$sel:roleArn:GetDestinationResponse' :: GetDestinationResponse -> Maybe Text
$sel:name:GetDestinationResponse' :: GetDestinationResponse -> Maybe Text
$sel:expressionType:GetDestinationResponse' :: GetDestinationResponse -> Maybe ExpressionType
$sel:expression:GetDestinationResponse' :: GetDestinationResponse -> Maybe Text
$sel:description:GetDestinationResponse' :: GetDestinationResponse -> Maybe Text
$sel:arn:GetDestinationResponse' :: GetDestinationResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
expression
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExpressionType
expressionType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus