{-# 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.GetMulticastGroupSession
-- 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 multicast group session.
module Amazonka.IoTWireless.GetMulticastGroupSession
  ( -- * Creating a Request
    GetMulticastGroupSession (..),
    newGetMulticastGroupSession,

    -- * Request Lenses
    getMulticastGroupSession_id,

    -- * Destructuring the Response
    GetMulticastGroupSessionResponse (..),
    newGetMulticastGroupSessionResponse,

    -- * Response Lenses
    getMulticastGroupSessionResponse_loRaWAN,
    getMulticastGroupSessionResponse_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:/ 'newGetMulticastGroupSession' smart constructor.
data GetMulticastGroupSession = GetMulticastGroupSession'
  { GetMulticastGroupSession -> Text
id :: Prelude.Text
  }
  deriving (GetMulticastGroupSession -> GetMulticastGroupSession -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMulticastGroupSession -> GetMulticastGroupSession -> Bool
$c/= :: GetMulticastGroupSession -> GetMulticastGroupSession -> Bool
== :: GetMulticastGroupSession -> GetMulticastGroupSession -> Bool
$c== :: GetMulticastGroupSession -> GetMulticastGroupSession -> Bool
Prelude.Eq, ReadPrec [GetMulticastGroupSession]
ReadPrec GetMulticastGroupSession
Int -> ReadS GetMulticastGroupSession
ReadS [GetMulticastGroupSession]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMulticastGroupSession]
$creadListPrec :: ReadPrec [GetMulticastGroupSession]
readPrec :: ReadPrec GetMulticastGroupSession
$creadPrec :: ReadPrec GetMulticastGroupSession
readList :: ReadS [GetMulticastGroupSession]
$creadList :: ReadS [GetMulticastGroupSession]
readsPrec :: Int -> ReadS GetMulticastGroupSession
$creadsPrec :: Int -> ReadS GetMulticastGroupSession
Prelude.Read, Int -> GetMulticastGroupSession -> ShowS
[GetMulticastGroupSession] -> ShowS
GetMulticastGroupSession -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMulticastGroupSession] -> ShowS
$cshowList :: [GetMulticastGroupSession] -> ShowS
show :: GetMulticastGroupSession -> String
$cshow :: GetMulticastGroupSession -> String
showsPrec :: Int -> GetMulticastGroupSession -> ShowS
$cshowsPrec :: Int -> GetMulticastGroupSession -> ShowS
Prelude.Show, forall x.
Rep GetMulticastGroupSession x -> GetMulticastGroupSession
forall x.
GetMulticastGroupSession -> Rep GetMulticastGroupSession x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetMulticastGroupSession x -> GetMulticastGroupSession
$cfrom :: forall x.
GetMulticastGroupSession -> Rep GetMulticastGroupSession x
Prelude.Generic)

-- |
-- Create a value of 'GetMulticastGroupSession' 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:
--
-- 'id', 'getMulticastGroupSession_id' - Undocumented member.
newGetMulticastGroupSession ::
  -- | 'id'
  Prelude.Text ->
  GetMulticastGroupSession
newGetMulticastGroupSession :: Text -> GetMulticastGroupSession
newGetMulticastGroupSession Text
pId_ =
  GetMulticastGroupSession' {$sel:id:GetMulticastGroupSession' :: Text
id = Text
pId_}

-- | Undocumented member.
getMulticastGroupSession_id :: Lens.Lens' GetMulticastGroupSession Prelude.Text
getMulticastGroupSession_id :: Lens' GetMulticastGroupSession Text
getMulticastGroupSession_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMulticastGroupSession' {Text
id :: Text
$sel:id:GetMulticastGroupSession' :: GetMulticastGroupSession -> Text
id} -> Text
id) (\s :: GetMulticastGroupSession
s@GetMulticastGroupSession' {} Text
a -> GetMulticastGroupSession
s {$sel:id:GetMulticastGroupSession' :: Text
id = Text
a} :: GetMulticastGroupSession)

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

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

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

instance Data.ToPath GetMulticastGroupSession where
  toPath :: GetMulticastGroupSession -> ByteString
toPath GetMulticastGroupSession' {Text
id :: Text
$sel:id:GetMulticastGroupSession' :: GetMulticastGroupSession -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/multicast-groups/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id, ByteString
"/session"]

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

-- | /See:/ 'newGetMulticastGroupSessionResponse' smart constructor.
data GetMulticastGroupSessionResponse = GetMulticastGroupSessionResponse'
  { GetMulticastGroupSessionResponse -> Maybe LoRaWANMulticastSession
loRaWAN :: Prelude.Maybe LoRaWANMulticastSession,
    -- | The response's http status code.
    GetMulticastGroupSessionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetMulticastGroupSessionResponse
-> GetMulticastGroupSessionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMulticastGroupSessionResponse
-> GetMulticastGroupSessionResponse -> Bool
$c/= :: GetMulticastGroupSessionResponse
-> GetMulticastGroupSessionResponse -> Bool
== :: GetMulticastGroupSessionResponse
-> GetMulticastGroupSessionResponse -> Bool
$c== :: GetMulticastGroupSessionResponse
-> GetMulticastGroupSessionResponse -> Bool
Prelude.Eq, ReadPrec [GetMulticastGroupSessionResponse]
ReadPrec GetMulticastGroupSessionResponse
Int -> ReadS GetMulticastGroupSessionResponse
ReadS [GetMulticastGroupSessionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMulticastGroupSessionResponse]
$creadListPrec :: ReadPrec [GetMulticastGroupSessionResponse]
readPrec :: ReadPrec GetMulticastGroupSessionResponse
$creadPrec :: ReadPrec GetMulticastGroupSessionResponse
readList :: ReadS [GetMulticastGroupSessionResponse]
$creadList :: ReadS [GetMulticastGroupSessionResponse]
readsPrec :: Int -> ReadS GetMulticastGroupSessionResponse
$creadsPrec :: Int -> ReadS GetMulticastGroupSessionResponse
Prelude.Read, Int -> GetMulticastGroupSessionResponse -> ShowS
[GetMulticastGroupSessionResponse] -> ShowS
GetMulticastGroupSessionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMulticastGroupSessionResponse] -> ShowS
$cshowList :: [GetMulticastGroupSessionResponse] -> ShowS
show :: GetMulticastGroupSessionResponse -> String
$cshow :: GetMulticastGroupSessionResponse -> String
showsPrec :: Int -> GetMulticastGroupSessionResponse -> ShowS
$cshowsPrec :: Int -> GetMulticastGroupSessionResponse -> ShowS
Prelude.Show, forall x.
Rep GetMulticastGroupSessionResponse x
-> GetMulticastGroupSessionResponse
forall x.
GetMulticastGroupSessionResponse
-> Rep GetMulticastGroupSessionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetMulticastGroupSessionResponse x
-> GetMulticastGroupSessionResponse
$cfrom :: forall x.
GetMulticastGroupSessionResponse
-> Rep GetMulticastGroupSessionResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetMulticastGroupSessionResponse' 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:
--
-- 'loRaWAN', 'getMulticastGroupSessionResponse_loRaWAN' - Undocumented member.
--
-- 'httpStatus', 'getMulticastGroupSessionResponse_httpStatus' - The response's http status code.
newGetMulticastGroupSessionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetMulticastGroupSessionResponse
newGetMulticastGroupSessionResponse :: Int -> GetMulticastGroupSessionResponse
newGetMulticastGroupSessionResponse Int
pHttpStatus_ =
  GetMulticastGroupSessionResponse'
    { $sel:loRaWAN:GetMulticastGroupSessionResponse' :: Maybe LoRaWANMulticastSession
loRaWAN =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetMulticastGroupSessionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
getMulticastGroupSessionResponse_loRaWAN :: Lens.Lens' GetMulticastGroupSessionResponse (Prelude.Maybe LoRaWANMulticastSession)
getMulticastGroupSessionResponse_loRaWAN :: Lens'
  GetMulticastGroupSessionResponse (Maybe LoRaWANMulticastSession)
getMulticastGroupSessionResponse_loRaWAN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMulticastGroupSessionResponse' {Maybe LoRaWANMulticastSession
loRaWAN :: Maybe LoRaWANMulticastSession
$sel:loRaWAN:GetMulticastGroupSessionResponse' :: GetMulticastGroupSessionResponse -> Maybe LoRaWANMulticastSession
loRaWAN} -> Maybe LoRaWANMulticastSession
loRaWAN) (\s :: GetMulticastGroupSessionResponse
s@GetMulticastGroupSessionResponse' {} Maybe LoRaWANMulticastSession
a -> GetMulticastGroupSessionResponse
s {$sel:loRaWAN:GetMulticastGroupSessionResponse' :: Maybe LoRaWANMulticastSession
loRaWAN = Maybe LoRaWANMulticastSession
a} :: GetMulticastGroupSessionResponse)

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

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