{-# 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.ApplicationInsights.DescribeComponent
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes a component and lists the resources that are grouped together
-- in a component.
module Amazonka.ApplicationInsights.DescribeComponent
  ( -- * Creating a Request
    DescribeComponent (..),
    newDescribeComponent,

    -- * Request Lenses
    describeComponent_resourceGroupName,
    describeComponent_componentName,

    -- * Destructuring the Response
    DescribeComponentResponse (..),
    newDescribeComponentResponse,

    -- * Response Lenses
    describeComponentResponse_applicationComponent,
    describeComponentResponse_resourceList,
    describeComponentResponse_httpStatus,
  )
where

import Amazonka.ApplicationInsights.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:/ 'newDescribeComponent' smart constructor.
data DescribeComponent = DescribeComponent'
  { -- | The name of the resource group.
    DescribeComponent -> Text
resourceGroupName :: Prelude.Text,
    -- | The name of the component.
    DescribeComponent -> Text
componentName :: Prelude.Text
  }
  deriving (DescribeComponent -> DescribeComponent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeComponent -> DescribeComponent -> Bool
$c/= :: DescribeComponent -> DescribeComponent -> Bool
== :: DescribeComponent -> DescribeComponent -> Bool
$c== :: DescribeComponent -> DescribeComponent -> Bool
Prelude.Eq, ReadPrec [DescribeComponent]
ReadPrec DescribeComponent
Int -> ReadS DescribeComponent
ReadS [DescribeComponent]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeComponent]
$creadListPrec :: ReadPrec [DescribeComponent]
readPrec :: ReadPrec DescribeComponent
$creadPrec :: ReadPrec DescribeComponent
readList :: ReadS [DescribeComponent]
$creadList :: ReadS [DescribeComponent]
readsPrec :: Int -> ReadS DescribeComponent
$creadsPrec :: Int -> ReadS DescribeComponent
Prelude.Read, Int -> DescribeComponent -> ShowS
[DescribeComponent] -> ShowS
DescribeComponent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeComponent] -> ShowS
$cshowList :: [DescribeComponent] -> ShowS
show :: DescribeComponent -> String
$cshow :: DescribeComponent -> String
showsPrec :: Int -> DescribeComponent -> ShowS
$cshowsPrec :: Int -> DescribeComponent -> ShowS
Prelude.Show, forall x. Rep DescribeComponent x -> DescribeComponent
forall x. DescribeComponent -> Rep DescribeComponent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeComponent x -> DescribeComponent
$cfrom :: forall x. DescribeComponent -> Rep DescribeComponent x
Prelude.Generic)

-- |
-- Create a value of 'DescribeComponent' 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:
--
-- 'resourceGroupName', 'describeComponent_resourceGroupName' - The name of the resource group.
--
-- 'componentName', 'describeComponent_componentName' - The name of the component.
newDescribeComponent ::
  -- | 'resourceGroupName'
  Prelude.Text ->
  -- | 'componentName'
  Prelude.Text ->
  DescribeComponent
newDescribeComponent :: Text -> Text -> DescribeComponent
newDescribeComponent
  Text
pResourceGroupName_
  Text
pComponentName_ =
    DescribeComponent'
      { $sel:resourceGroupName:DescribeComponent' :: Text
resourceGroupName =
          Text
pResourceGroupName_,
        $sel:componentName:DescribeComponent' :: Text
componentName = Text
pComponentName_
      }

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

-- | The name of the component.
describeComponent_componentName :: Lens.Lens' DescribeComponent Prelude.Text
describeComponent_componentName :: Lens' DescribeComponent Text
describeComponent_componentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComponent' {Text
componentName :: Text
$sel:componentName:DescribeComponent' :: DescribeComponent -> Text
componentName} -> Text
componentName) (\s :: DescribeComponent
s@DescribeComponent' {} Text
a -> DescribeComponent
s {$sel:componentName:DescribeComponent' :: Text
componentName = Text
a} :: DescribeComponent)

instance Core.AWSRequest DescribeComponent where
  type
    AWSResponse DescribeComponent =
      DescribeComponentResponse
  request :: (Service -> Service)
-> DescribeComponent -> Request DescribeComponent
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 DescribeComponent
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeComponent)))
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 ApplicationComponent
-> Maybe [Text] -> Int -> DescribeComponentResponse
DescribeComponentResponse'
            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
"ApplicationComponent")
            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
"ResourceList" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 DescribeComponent where
  hashWithSalt :: Int -> DescribeComponent -> Int
hashWithSalt Int
_salt DescribeComponent' {Text
componentName :: Text
resourceGroupName :: Text
$sel:componentName:DescribeComponent' :: DescribeComponent -> Text
$sel:resourceGroupName:DescribeComponent' :: DescribeComponent -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
componentName

instance Prelude.NFData DescribeComponent where
  rnf :: DescribeComponent -> ()
rnf DescribeComponent' {Text
componentName :: Text
resourceGroupName :: Text
$sel:componentName:DescribeComponent' :: DescribeComponent -> Text
$sel:resourceGroupName:DescribeComponent' :: DescribeComponent -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
resourceGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
componentName

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

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

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

-- | /See:/ 'newDescribeComponentResponse' smart constructor.
data DescribeComponentResponse = DescribeComponentResponse'
  { DescribeComponentResponse -> Maybe ApplicationComponent
applicationComponent :: Prelude.Maybe ApplicationComponent,
    -- | The list of resource ARNs that belong to the component.
    DescribeComponentResponse -> Maybe [Text]
resourceList :: Prelude.Maybe [Prelude.Text],
    -- | The response's http status code.
    DescribeComponentResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeComponentResponse -> DescribeComponentResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeComponentResponse -> DescribeComponentResponse -> Bool
$c/= :: DescribeComponentResponse -> DescribeComponentResponse -> Bool
== :: DescribeComponentResponse -> DescribeComponentResponse -> Bool
$c== :: DescribeComponentResponse -> DescribeComponentResponse -> Bool
Prelude.Eq, ReadPrec [DescribeComponentResponse]
ReadPrec DescribeComponentResponse
Int -> ReadS DescribeComponentResponse
ReadS [DescribeComponentResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeComponentResponse]
$creadListPrec :: ReadPrec [DescribeComponentResponse]
readPrec :: ReadPrec DescribeComponentResponse
$creadPrec :: ReadPrec DescribeComponentResponse
readList :: ReadS [DescribeComponentResponse]
$creadList :: ReadS [DescribeComponentResponse]
readsPrec :: Int -> ReadS DescribeComponentResponse
$creadsPrec :: Int -> ReadS DescribeComponentResponse
Prelude.Read, Int -> DescribeComponentResponse -> ShowS
[DescribeComponentResponse] -> ShowS
DescribeComponentResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeComponentResponse] -> ShowS
$cshowList :: [DescribeComponentResponse] -> ShowS
show :: DescribeComponentResponse -> String
$cshow :: DescribeComponentResponse -> String
showsPrec :: Int -> DescribeComponentResponse -> ShowS
$cshowsPrec :: Int -> DescribeComponentResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeComponentResponse x -> DescribeComponentResponse
forall x.
DescribeComponentResponse -> Rep DescribeComponentResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeComponentResponse x -> DescribeComponentResponse
$cfrom :: forall x.
DescribeComponentResponse -> Rep DescribeComponentResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeComponentResponse' 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:
--
-- 'applicationComponent', 'describeComponentResponse_applicationComponent' - Undocumented member.
--
-- 'resourceList', 'describeComponentResponse_resourceList' - The list of resource ARNs that belong to the component.
--
-- 'httpStatus', 'describeComponentResponse_httpStatus' - The response's http status code.
newDescribeComponentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeComponentResponse
newDescribeComponentResponse :: Int -> DescribeComponentResponse
newDescribeComponentResponse Int
pHttpStatus_ =
  DescribeComponentResponse'
    { $sel:applicationComponent:DescribeComponentResponse' :: Maybe ApplicationComponent
applicationComponent =
        forall a. Maybe a
Prelude.Nothing,
      $sel:resourceList:DescribeComponentResponse' :: Maybe [Text]
resourceList = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeComponentResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
describeComponentResponse_applicationComponent :: Lens.Lens' DescribeComponentResponse (Prelude.Maybe ApplicationComponent)
describeComponentResponse_applicationComponent :: Lens' DescribeComponentResponse (Maybe ApplicationComponent)
describeComponentResponse_applicationComponent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComponentResponse' {Maybe ApplicationComponent
applicationComponent :: Maybe ApplicationComponent
$sel:applicationComponent:DescribeComponentResponse' :: DescribeComponentResponse -> Maybe ApplicationComponent
applicationComponent} -> Maybe ApplicationComponent
applicationComponent) (\s :: DescribeComponentResponse
s@DescribeComponentResponse' {} Maybe ApplicationComponent
a -> DescribeComponentResponse
s {$sel:applicationComponent:DescribeComponentResponse' :: Maybe ApplicationComponent
applicationComponent = Maybe ApplicationComponent
a} :: DescribeComponentResponse)

-- | The list of resource ARNs that belong to the component.
describeComponentResponse_resourceList :: Lens.Lens' DescribeComponentResponse (Prelude.Maybe [Prelude.Text])
describeComponentResponse_resourceList :: Lens' DescribeComponentResponse (Maybe [Text])
describeComponentResponse_resourceList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComponentResponse' {Maybe [Text]
resourceList :: Maybe [Text]
$sel:resourceList:DescribeComponentResponse' :: DescribeComponentResponse -> Maybe [Text]
resourceList} -> Maybe [Text]
resourceList) (\s :: DescribeComponentResponse
s@DescribeComponentResponse' {} Maybe [Text]
a -> DescribeComponentResponse
s {$sel:resourceList:DescribeComponentResponse' :: Maybe [Text]
resourceList = Maybe [Text]
a} :: DescribeComponentResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData DescribeComponentResponse where
  rnf :: DescribeComponentResponse -> ()
rnf DescribeComponentResponse' {Int
Maybe [Text]
Maybe ApplicationComponent
httpStatus :: Int
resourceList :: Maybe [Text]
applicationComponent :: Maybe ApplicationComponent
$sel:httpStatus:DescribeComponentResponse' :: DescribeComponentResponse -> Int
$sel:resourceList:DescribeComponentResponse' :: DescribeComponentResponse -> Maybe [Text]
$sel:applicationComponent:DescribeComponentResponse' :: DescribeComponentResponse -> Maybe ApplicationComponent
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ApplicationComponent
applicationComponent
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
resourceList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus