{-# 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.Amplify.GetBackendEnvironment
-- 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 a backend environment for an Amplify app.
module Amazonka.Amplify.GetBackendEnvironment
  ( -- * Creating a Request
    GetBackendEnvironment (..),
    newGetBackendEnvironment,

    -- * Request Lenses
    getBackendEnvironment_appId,
    getBackendEnvironment_environmentName,

    -- * Destructuring the Response
    GetBackendEnvironmentResponse (..),
    newGetBackendEnvironmentResponse,

    -- * Response Lenses
    getBackendEnvironmentResponse_httpStatus,
    getBackendEnvironmentResponse_backendEnvironment,
  )
where

import Amazonka.Amplify.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

-- | The request structure for the get backend environment request.
--
-- /See:/ 'newGetBackendEnvironment' smart constructor.
data GetBackendEnvironment = GetBackendEnvironment'
  { -- | The unique id for an Amplify app.
    GetBackendEnvironment -> Text
appId :: Prelude.Text,
    -- | The name for the backend environment.
    GetBackendEnvironment -> Text
environmentName :: Prelude.Text
  }
  deriving (GetBackendEnvironment -> GetBackendEnvironment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBackendEnvironment -> GetBackendEnvironment -> Bool
$c/= :: GetBackendEnvironment -> GetBackendEnvironment -> Bool
== :: GetBackendEnvironment -> GetBackendEnvironment -> Bool
$c== :: GetBackendEnvironment -> GetBackendEnvironment -> Bool
Prelude.Eq, ReadPrec [GetBackendEnvironment]
ReadPrec GetBackendEnvironment
Int -> ReadS GetBackendEnvironment
ReadS [GetBackendEnvironment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBackendEnvironment]
$creadListPrec :: ReadPrec [GetBackendEnvironment]
readPrec :: ReadPrec GetBackendEnvironment
$creadPrec :: ReadPrec GetBackendEnvironment
readList :: ReadS [GetBackendEnvironment]
$creadList :: ReadS [GetBackendEnvironment]
readsPrec :: Int -> ReadS GetBackendEnvironment
$creadsPrec :: Int -> ReadS GetBackendEnvironment
Prelude.Read, Int -> GetBackendEnvironment -> ShowS
[GetBackendEnvironment] -> ShowS
GetBackendEnvironment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBackendEnvironment] -> ShowS
$cshowList :: [GetBackendEnvironment] -> ShowS
show :: GetBackendEnvironment -> String
$cshow :: GetBackendEnvironment -> String
showsPrec :: Int -> GetBackendEnvironment -> ShowS
$cshowsPrec :: Int -> GetBackendEnvironment -> ShowS
Prelude.Show, forall x. Rep GetBackendEnvironment x -> GetBackendEnvironment
forall x. GetBackendEnvironment -> Rep GetBackendEnvironment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBackendEnvironment x -> GetBackendEnvironment
$cfrom :: forall x. GetBackendEnvironment -> Rep GetBackendEnvironment x
Prelude.Generic)

-- |
-- Create a value of 'GetBackendEnvironment' 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', 'getBackendEnvironment_appId' - The unique id for an Amplify app.
--
-- 'environmentName', 'getBackendEnvironment_environmentName' - The name for the backend environment.
newGetBackendEnvironment ::
  -- | 'appId'
  Prelude.Text ->
  -- | 'environmentName'
  Prelude.Text ->
  GetBackendEnvironment
newGetBackendEnvironment :: Text -> Text -> GetBackendEnvironment
newGetBackendEnvironment Text
pAppId_ Text
pEnvironmentName_ =
  GetBackendEnvironment'
    { $sel:appId:GetBackendEnvironment' :: Text
appId = Text
pAppId_,
      $sel:environmentName:GetBackendEnvironment' :: Text
environmentName = Text
pEnvironmentName_
    }

-- | The unique id for an Amplify app.
getBackendEnvironment_appId :: Lens.Lens' GetBackendEnvironment Prelude.Text
getBackendEnvironment_appId :: Lens' GetBackendEnvironment Text
getBackendEnvironment_appId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBackendEnvironment' {Text
appId :: Text
$sel:appId:GetBackendEnvironment' :: GetBackendEnvironment -> Text
appId} -> Text
appId) (\s :: GetBackendEnvironment
s@GetBackendEnvironment' {} Text
a -> GetBackendEnvironment
s {$sel:appId:GetBackendEnvironment' :: Text
appId = Text
a} :: GetBackendEnvironment)

-- | The name for the backend environment.
getBackendEnvironment_environmentName :: Lens.Lens' GetBackendEnvironment Prelude.Text
getBackendEnvironment_environmentName :: Lens' GetBackendEnvironment Text
getBackendEnvironment_environmentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBackendEnvironment' {Text
environmentName :: Text
$sel:environmentName:GetBackendEnvironment' :: GetBackendEnvironment -> Text
environmentName} -> Text
environmentName) (\s :: GetBackendEnvironment
s@GetBackendEnvironment' {} Text
a -> GetBackendEnvironment
s {$sel:environmentName:GetBackendEnvironment' :: Text
environmentName = Text
a} :: GetBackendEnvironment)

instance Core.AWSRequest GetBackendEnvironment where
  type
    AWSResponse GetBackendEnvironment =
      GetBackendEnvironmentResponse
  request :: (Service -> Service)
-> GetBackendEnvironment -> Request GetBackendEnvironment
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 GetBackendEnvironment
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetBackendEnvironment)))
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 ->
          Int -> BackendEnvironment -> GetBackendEnvironmentResponse
GetBackendEnvironmentResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"backendEnvironment")
      )

instance Prelude.Hashable GetBackendEnvironment where
  hashWithSalt :: Int -> GetBackendEnvironment -> Int
hashWithSalt Int
_salt GetBackendEnvironment' {Text
environmentName :: Text
appId :: Text
$sel:environmentName:GetBackendEnvironment' :: GetBackendEnvironment -> Text
$sel:appId:GetBackendEnvironment' :: GetBackendEnvironment -> 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

instance Prelude.NFData GetBackendEnvironment where
  rnf :: GetBackendEnvironment -> ()
rnf GetBackendEnvironment' {Text
environmentName :: Text
appId :: Text
$sel:environmentName:GetBackendEnvironment' :: GetBackendEnvironment -> Text
$sel:appId:GetBackendEnvironment' :: GetBackendEnvironment -> 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

instance Data.ToHeaders GetBackendEnvironment where
  toHeaders :: GetBackendEnvironment -> 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 GetBackendEnvironment where
  toPath :: GetBackendEnvironment -> ByteString
toPath GetBackendEnvironment' {Text
environmentName :: Text
appId :: Text
$sel:environmentName:GetBackendEnvironment' :: GetBackendEnvironment -> Text
$sel:appId:GetBackendEnvironment' :: GetBackendEnvironment -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/apps/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
appId,
        ByteString
"/backendenvironments/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
environmentName
      ]

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

-- | The result structure for the get backend environment result.
--
-- /See:/ 'newGetBackendEnvironmentResponse' smart constructor.
data GetBackendEnvironmentResponse = GetBackendEnvironmentResponse'
  { -- | The response's http status code.
    GetBackendEnvironmentResponse -> Int
httpStatus :: Prelude.Int,
    -- | Describes the backend environment for an Amplify app.
    GetBackendEnvironmentResponse -> BackendEnvironment
backendEnvironment :: BackendEnvironment
  }
  deriving (GetBackendEnvironmentResponse
-> GetBackendEnvironmentResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBackendEnvironmentResponse
-> GetBackendEnvironmentResponse -> Bool
$c/= :: GetBackendEnvironmentResponse
-> GetBackendEnvironmentResponse -> Bool
== :: GetBackendEnvironmentResponse
-> GetBackendEnvironmentResponse -> Bool
$c== :: GetBackendEnvironmentResponse
-> GetBackendEnvironmentResponse -> Bool
Prelude.Eq, ReadPrec [GetBackendEnvironmentResponse]
ReadPrec GetBackendEnvironmentResponse
Int -> ReadS GetBackendEnvironmentResponse
ReadS [GetBackendEnvironmentResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBackendEnvironmentResponse]
$creadListPrec :: ReadPrec [GetBackendEnvironmentResponse]
readPrec :: ReadPrec GetBackendEnvironmentResponse
$creadPrec :: ReadPrec GetBackendEnvironmentResponse
readList :: ReadS [GetBackendEnvironmentResponse]
$creadList :: ReadS [GetBackendEnvironmentResponse]
readsPrec :: Int -> ReadS GetBackendEnvironmentResponse
$creadsPrec :: Int -> ReadS GetBackendEnvironmentResponse
Prelude.Read, Int -> GetBackendEnvironmentResponse -> ShowS
[GetBackendEnvironmentResponse] -> ShowS
GetBackendEnvironmentResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBackendEnvironmentResponse] -> ShowS
$cshowList :: [GetBackendEnvironmentResponse] -> ShowS
show :: GetBackendEnvironmentResponse -> String
$cshow :: GetBackendEnvironmentResponse -> String
showsPrec :: Int -> GetBackendEnvironmentResponse -> ShowS
$cshowsPrec :: Int -> GetBackendEnvironmentResponse -> ShowS
Prelude.Show, forall x.
Rep GetBackendEnvironmentResponse x
-> GetBackendEnvironmentResponse
forall x.
GetBackendEnvironmentResponse
-> Rep GetBackendEnvironmentResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetBackendEnvironmentResponse x
-> GetBackendEnvironmentResponse
$cfrom :: forall x.
GetBackendEnvironmentResponse
-> Rep GetBackendEnvironmentResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBackendEnvironmentResponse' 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:
--
-- 'httpStatus', 'getBackendEnvironmentResponse_httpStatus' - The response's http status code.
--
-- 'backendEnvironment', 'getBackendEnvironmentResponse_backendEnvironment' - Describes the backend environment for an Amplify app.
newGetBackendEnvironmentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'backendEnvironment'
  BackendEnvironment ->
  GetBackendEnvironmentResponse
newGetBackendEnvironmentResponse :: Int -> BackendEnvironment -> GetBackendEnvironmentResponse
newGetBackendEnvironmentResponse
  Int
pHttpStatus_
  BackendEnvironment
pBackendEnvironment_ =
    GetBackendEnvironmentResponse'
      { $sel:httpStatus:GetBackendEnvironmentResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:backendEnvironment:GetBackendEnvironmentResponse' :: BackendEnvironment
backendEnvironment = BackendEnvironment
pBackendEnvironment_
      }

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

-- | Describes the backend environment for an Amplify app.
getBackendEnvironmentResponse_backendEnvironment :: Lens.Lens' GetBackendEnvironmentResponse BackendEnvironment
getBackendEnvironmentResponse_backendEnvironment :: Lens' GetBackendEnvironmentResponse BackendEnvironment
getBackendEnvironmentResponse_backendEnvironment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBackendEnvironmentResponse' {BackendEnvironment
backendEnvironment :: BackendEnvironment
$sel:backendEnvironment:GetBackendEnvironmentResponse' :: GetBackendEnvironmentResponse -> BackendEnvironment
backendEnvironment} -> BackendEnvironment
backendEnvironment) (\s :: GetBackendEnvironmentResponse
s@GetBackendEnvironmentResponse' {} BackendEnvironment
a -> GetBackendEnvironmentResponse
s {$sel:backendEnvironment:GetBackendEnvironmentResponse' :: BackendEnvironment
backendEnvironment = BackendEnvironment
a} :: GetBackendEnvironmentResponse)

instance Prelude.NFData GetBackendEnvironmentResponse where
  rnf :: GetBackendEnvironmentResponse -> ()
rnf GetBackendEnvironmentResponse' {Int
BackendEnvironment
backendEnvironment :: BackendEnvironment
httpStatus :: Int
$sel:backendEnvironment:GetBackendEnvironmentResponse' :: GetBackendEnvironmentResponse -> BackendEnvironment
$sel:httpStatus:GetBackendEnvironmentResponse' :: GetBackendEnvironmentResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf BackendEnvironment
backendEnvironment