{-# 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.AlexaBusiness.GetSkillGroup
-- 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 skill group details by skill group ARN.
module Amazonka.AlexaBusiness.GetSkillGroup
  ( -- * Creating a Request
    GetSkillGroup (..),
    newGetSkillGroup,

    -- * Request Lenses
    getSkillGroup_skillGroupArn,

    -- * Destructuring the Response
    GetSkillGroupResponse (..),
    newGetSkillGroupResponse,

    -- * Response Lenses
    getSkillGroupResponse_skillGroup,
    getSkillGroupResponse_httpStatus,
  )
where

import Amazonka.AlexaBusiness.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:/ 'newGetSkillGroup' smart constructor.
data GetSkillGroup = GetSkillGroup'
  { -- | The ARN of the skill group for which to get details. Required.
    GetSkillGroup -> Maybe Text
skillGroupArn :: Prelude.Maybe Prelude.Text
  }
  deriving (GetSkillGroup -> GetSkillGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSkillGroup -> GetSkillGroup -> Bool
$c/= :: GetSkillGroup -> GetSkillGroup -> Bool
== :: GetSkillGroup -> GetSkillGroup -> Bool
$c== :: GetSkillGroup -> GetSkillGroup -> Bool
Prelude.Eq, ReadPrec [GetSkillGroup]
ReadPrec GetSkillGroup
Int -> ReadS GetSkillGroup
ReadS [GetSkillGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSkillGroup]
$creadListPrec :: ReadPrec [GetSkillGroup]
readPrec :: ReadPrec GetSkillGroup
$creadPrec :: ReadPrec GetSkillGroup
readList :: ReadS [GetSkillGroup]
$creadList :: ReadS [GetSkillGroup]
readsPrec :: Int -> ReadS GetSkillGroup
$creadsPrec :: Int -> ReadS GetSkillGroup
Prelude.Read, Int -> GetSkillGroup -> ShowS
[GetSkillGroup] -> ShowS
GetSkillGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSkillGroup] -> ShowS
$cshowList :: [GetSkillGroup] -> ShowS
show :: GetSkillGroup -> String
$cshow :: GetSkillGroup -> String
showsPrec :: Int -> GetSkillGroup -> ShowS
$cshowsPrec :: Int -> GetSkillGroup -> ShowS
Prelude.Show, forall x. Rep GetSkillGroup x -> GetSkillGroup
forall x. GetSkillGroup -> Rep GetSkillGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSkillGroup x -> GetSkillGroup
$cfrom :: forall x. GetSkillGroup -> Rep GetSkillGroup x
Prelude.Generic)

-- |
-- Create a value of 'GetSkillGroup' 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:
--
-- 'skillGroupArn', 'getSkillGroup_skillGroupArn' - The ARN of the skill group for which to get details. Required.
newGetSkillGroup ::
  GetSkillGroup
newGetSkillGroup :: GetSkillGroup
newGetSkillGroup =
  GetSkillGroup' {$sel:skillGroupArn:GetSkillGroup' :: Maybe Text
skillGroupArn = forall a. Maybe a
Prelude.Nothing}

-- | The ARN of the skill group for which to get details. Required.
getSkillGroup_skillGroupArn :: Lens.Lens' GetSkillGroup (Prelude.Maybe Prelude.Text)
getSkillGroup_skillGroupArn :: Lens' GetSkillGroup (Maybe Text)
getSkillGroup_skillGroupArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSkillGroup' {Maybe Text
skillGroupArn :: Maybe Text
$sel:skillGroupArn:GetSkillGroup' :: GetSkillGroup -> Maybe Text
skillGroupArn} -> Maybe Text
skillGroupArn) (\s :: GetSkillGroup
s@GetSkillGroup' {} Maybe Text
a -> GetSkillGroup
s {$sel:skillGroupArn:GetSkillGroup' :: Maybe Text
skillGroupArn = Maybe Text
a} :: GetSkillGroup)

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

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

instance Data.ToHeaders GetSkillGroup where
  toHeaders :: GetSkillGroup -> 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
"AlexaForBusiness.GetSkillGroup" ::
                          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 GetSkillGroup where
  toJSON :: GetSkillGroup -> Value
toJSON GetSkillGroup' {Maybe Text
skillGroupArn :: Maybe Text
$sel:skillGroupArn:GetSkillGroup' :: GetSkillGroup -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"SkillGroupArn" 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
skillGroupArn
          ]
      )

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

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

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

-- |
-- Create a value of 'GetSkillGroupResponse' 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:
--
-- 'skillGroup', 'getSkillGroupResponse_skillGroup' - The details of the skill group requested. Required.
--
-- 'httpStatus', 'getSkillGroupResponse_httpStatus' - The response's http status code.
newGetSkillGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetSkillGroupResponse
newGetSkillGroupResponse :: Int -> GetSkillGroupResponse
newGetSkillGroupResponse Int
pHttpStatus_ =
  GetSkillGroupResponse'
    { $sel:skillGroup:GetSkillGroupResponse' :: Maybe SkillGroup
skillGroup =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetSkillGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The details of the skill group requested. Required.
getSkillGroupResponse_skillGroup :: Lens.Lens' GetSkillGroupResponse (Prelude.Maybe SkillGroup)
getSkillGroupResponse_skillGroup :: Lens' GetSkillGroupResponse (Maybe SkillGroup)
getSkillGroupResponse_skillGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSkillGroupResponse' {Maybe SkillGroup
skillGroup :: Maybe SkillGroup
$sel:skillGroup:GetSkillGroupResponse' :: GetSkillGroupResponse -> Maybe SkillGroup
skillGroup} -> Maybe SkillGroup
skillGroup) (\s :: GetSkillGroupResponse
s@GetSkillGroupResponse' {} Maybe SkillGroup
a -> GetSkillGroupResponse
s {$sel:skillGroup:GetSkillGroupResponse' :: Maybe SkillGroup
skillGroup = Maybe SkillGroup
a} :: GetSkillGroupResponse)

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

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