{-# 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.AmplifyUiBuilder.GetComponent
-- 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 an existing component for an Amplify app.
module Amazonka.AmplifyUiBuilder.GetComponent
  ( -- * Creating a Request
    GetComponent (..),
    newGetComponent,

    -- * Request Lenses
    getComponent_appId,
    getComponent_environmentName,
    getComponent_id,

    -- * Destructuring the Response
    GetComponentResponse (..),
    newGetComponentResponse,

    -- * Response Lenses
    getComponentResponse_component,
    getComponentResponse_httpStatus,
  )
where

import Amazonka.AmplifyUiBuilder.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:/ 'newGetComponent' smart constructor.
data GetComponent = GetComponent'
  { -- | The unique ID of the Amplify app.
    GetComponent -> Text
appId :: Prelude.Text,
    -- | The name of the backend environment that is part of the Amplify app.
    GetComponent -> Text
environmentName :: Prelude.Text,
    -- | The unique ID of the component.
    GetComponent -> Text
id :: Prelude.Text
  }
  deriving (GetComponent -> GetComponent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetComponent -> GetComponent -> Bool
$c/= :: GetComponent -> GetComponent -> Bool
== :: GetComponent -> GetComponent -> Bool
$c== :: GetComponent -> GetComponent -> Bool
Prelude.Eq, ReadPrec [GetComponent]
ReadPrec GetComponent
Int -> ReadS GetComponent
ReadS [GetComponent]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetComponent]
$creadListPrec :: ReadPrec [GetComponent]
readPrec :: ReadPrec GetComponent
$creadPrec :: ReadPrec GetComponent
readList :: ReadS [GetComponent]
$creadList :: ReadS [GetComponent]
readsPrec :: Int -> ReadS GetComponent
$creadsPrec :: Int -> ReadS GetComponent
Prelude.Read, Int -> GetComponent -> ShowS
[GetComponent] -> ShowS
GetComponent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetComponent] -> ShowS
$cshowList :: [GetComponent] -> ShowS
show :: GetComponent -> String
$cshow :: GetComponent -> String
showsPrec :: Int -> GetComponent -> ShowS
$cshowsPrec :: Int -> GetComponent -> ShowS
Prelude.Show, forall x. Rep GetComponent x -> GetComponent
forall x. GetComponent -> Rep GetComponent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetComponent x -> GetComponent
$cfrom :: forall x. GetComponent -> Rep GetComponent x
Prelude.Generic)

-- |
-- Create a value of 'GetComponent' 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:
--
-- 'appId', 'getComponent_appId' - The unique ID of the Amplify app.
--
-- 'environmentName', 'getComponent_environmentName' - The name of the backend environment that is part of the Amplify app.
--
-- 'id', 'getComponent_id' - The unique ID of the component.
newGetComponent ::
  -- | 'appId'
  Prelude.Text ->
  -- | 'environmentName'
  Prelude.Text ->
  -- | 'id'
  Prelude.Text ->
  GetComponent
newGetComponent :: Text -> Text -> Text -> GetComponent
newGetComponent Text
pAppId_ Text
pEnvironmentName_ Text
pId_ =
  GetComponent'
    { $sel:appId:GetComponent' :: Text
appId = Text
pAppId_,
      $sel:environmentName:GetComponent' :: Text
environmentName = Text
pEnvironmentName_,
      $sel:id:GetComponent' :: Text
id = Text
pId_
    }

-- | The unique ID of the Amplify app.
getComponent_appId :: Lens.Lens' GetComponent Prelude.Text
getComponent_appId :: Lens' GetComponent Text
getComponent_appId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetComponent' {Text
appId :: Text
$sel:appId:GetComponent' :: GetComponent -> Text
appId} -> Text
appId) (\s :: GetComponent
s@GetComponent' {} Text
a -> GetComponent
s {$sel:appId:GetComponent' :: Text
appId = Text
a} :: GetComponent)

-- | The name of the backend environment that is part of the Amplify app.
getComponent_environmentName :: Lens.Lens' GetComponent Prelude.Text
getComponent_environmentName :: Lens' GetComponent Text
getComponent_environmentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetComponent' {Text
environmentName :: Text
$sel:environmentName:GetComponent' :: GetComponent -> Text
environmentName} -> Text
environmentName) (\s :: GetComponent
s@GetComponent' {} Text
a -> GetComponent
s {$sel:environmentName:GetComponent' :: Text
environmentName = Text
a} :: GetComponent)

-- | The unique ID of the component.
getComponent_id :: Lens.Lens' GetComponent Prelude.Text
getComponent_id :: Lens' GetComponent Text
getComponent_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetComponent' {Text
id :: Text
$sel:id:GetComponent' :: GetComponent -> Text
id} -> Text
id) (\s :: GetComponent
s@GetComponent' {} Text
a -> GetComponent
s {$sel:id:GetComponent' :: Text
id = Text
a} :: GetComponent)

instance Core.AWSRequest GetComponent where
  type AWSResponse GetComponent = GetComponentResponse
  request :: (Service -> Service) -> GetComponent -> Request GetComponent
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 GetComponent
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetComponent)))
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 Component -> Int -> GetComponentResponse
GetComponentResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)
            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 GetComponent where
  hashWithSalt :: Int -> GetComponent -> Int
hashWithSalt Int
_salt GetComponent' {Text
id :: Text
environmentName :: Text
appId :: Text
$sel:id:GetComponent' :: GetComponent -> Text
$sel:environmentName:GetComponent' :: GetComponent -> Text
$sel:appId:GetComponent' :: GetComponent -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
appId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
environmentName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData GetComponent where
  rnf :: GetComponent -> ()
rnf GetComponent' {Text
id :: Text
environmentName :: Text
appId :: Text
$sel:id:GetComponent' :: GetComponent -> Text
$sel:environmentName:GetComponent' :: GetComponent -> Text
$sel:appId:GetComponent' :: GetComponent -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
appId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
environmentName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id

instance Data.ToHeaders GetComponent where
  toHeaders :: GetComponent -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath GetComponent where
  toPath :: GetComponent -> ByteString
toPath GetComponent' {Text
id :: Text
environmentName :: Text
appId :: Text
$sel:id:GetComponent' :: GetComponent -> Text
$sel:environmentName:GetComponent' :: GetComponent -> Text
$sel:appId:GetComponent' :: GetComponent -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/app/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
appId,
        ByteString
"/environment/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
environmentName,
        ByteString
"/components/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
id
      ]

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

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

-- |
-- Create a value of 'GetComponentResponse' 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:
--
-- 'component', 'getComponentResponse_component' - Represents the configuration settings for the component.
--
-- 'httpStatus', 'getComponentResponse_httpStatus' - The response's http status code.
newGetComponentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetComponentResponse
newGetComponentResponse :: Int -> GetComponentResponse
newGetComponentResponse Int
pHttpStatus_ =
  GetComponentResponse'
    { $sel:component:GetComponentResponse' :: Maybe Component
component = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetComponentResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Represents the configuration settings for the component.
getComponentResponse_component :: Lens.Lens' GetComponentResponse (Prelude.Maybe Component)
getComponentResponse_component :: Lens' GetComponentResponse (Maybe Component)
getComponentResponse_component = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetComponentResponse' {Maybe Component
component :: Maybe Component
$sel:component:GetComponentResponse' :: GetComponentResponse -> Maybe Component
component} -> Maybe Component
component) (\s :: GetComponentResponse
s@GetComponentResponse' {} Maybe Component
a -> GetComponentResponse
s {$sel:component:GetComponentResponse' :: Maybe Component
component = Maybe Component
a} :: GetComponentResponse)

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

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