{-# 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.GetTheme
-- 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 theme for an Amplify app.
module Amazonka.AmplifyUiBuilder.GetTheme
  ( -- * Creating a Request
    GetTheme (..),
    newGetTheme,

    -- * Request Lenses
    getTheme_appId,
    getTheme_environmentName,
    getTheme_id,

    -- * Destructuring the Response
    GetThemeResponse (..),
    newGetThemeResponse,

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

-- |
-- Create a value of 'GetTheme' 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', 'getTheme_appId' - The unique ID of the Amplify app.
--
-- 'environmentName', 'getTheme_environmentName' - The name of the backend environment that is part of the Amplify app.
--
-- 'id', 'getTheme_id' - The unique ID for the theme.
newGetTheme ::
  -- | 'appId'
  Prelude.Text ->
  -- | 'environmentName'
  Prelude.Text ->
  -- | 'id'
  Prelude.Text ->
  GetTheme
newGetTheme :: Text -> Text -> Text -> GetTheme
newGetTheme Text
pAppId_ Text
pEnvironmentName_ Text
pId_ =
  GetTheme'
    { $sel:appId:GetTheme' :: Text
appId = Text
pAppId_,
      $sel:environmentName:GetTheme' :: Text
environmentName = Text
pEnvironmentName_,
      $sel:id:GetTheme' :: Text
id = Text
pId_
    }

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

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

-- | The unique ID for the theme.
getTheme_id :: Lens.Lens' GetTheme Prelude.Text
getTheme_id :: Lens' GetTheme Text
getTheme_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTheme' {Text
id :: Text
$sel:id:GetTheme' :: GetTheme -> Text
id} -> Text
id) (\s :: GetTheme
s@GetTheme' {} Text
a -> GetTheme
s {$sel:id:GetTheme' :: Text
id = Text
a} :: GetTheme)

instance Core.AWSRequest GetTheme where
  type AWSResponse GetTheme = GetThemeResponse
  request :: (Service -> Service) -> GetTheme -> Request GetTheme
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 GetTheme
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetTheme)))
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 Theme -> Int -> GetThemeResponse
GetThemeResponse'
            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 GetTheme where
  hashWithSalt :: Int -> GetTheme -> Int
hashWithSalt Int
_salt GetTheme' {Text
id :: Text
environmentName :: Text
appId :: Text
$sel:id:GetTheme' :: GetTheme -> Text
$sel:environmentName:GetTheme' :: GetTheme -> Text
$sel:appId:GetTheme' :: GetTheme -> 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 GetTheme where
  rnf :: GetTheme -> ()
rnf GetTheme' {Text
id :: Text
environmentName :: Text
appId :: Text
$sel:id:GetTheme' :: GetTheme -> Text
$sel:environmentName:GetTheme' :: GetTheme -> Text
$sel:appId:GetTheme' :: GetTheme -> 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 GetTheme where
  toHeaders :: GetTheme -> 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 GetTheme where
  toPath :: GetTheme -> ByteString
toPath GetTheme' {Text
id :: Text
environmentName :: Text
appId :: Text
$sel:id:GetTheme' :: GetTheme -> Text
$sel:environmentName:GetTheme' :: GetTheme -> Text
$sel:appId:GetTheme' :: GetTheme -> 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
"/themes/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
id
      ]

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

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

-- |
-- Create a value of 'GetThemeResponse' 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:
--
-- 'theme', 'getThemeResponse_theme' - Represents the configuration settings for the theme.
--
-- 'httpStatus', 'getThemeResponse_httpStatus' - The response's http status code.
newGetThemeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetThemeResponse
newGetThemeResponse :: Int -> GetThemeResponse
newGetThemeResponse Int
pHttpStatus_ =
  GetThemeResponse'
    { $sel:theme:GetThemeResponse' :: Maybe Theme
theme = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetThemeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Represents the configuration settings for the theme.
getThemeResponse_theme :: Lens.Lens' GetThemeResponse (Prelude.Maybe Theme)
getThemeResponse_theme :: Lens' GetThemeResponse (Maybe Theme)
getThemeResponse_theme = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetThemeResponse' {Maybe Theme
theme :: Maybe Theme
$sel:theme:GetThemeResponse' :: GetThemeResponse -> Maybe Theme
theme} -> Maybe Theme
theme) (\s :: GetThemeResponse
s@GetThemeResponse' {} Maybe Theme
a -> GetThemeResponse
s {$sel:theme:GetThemeResponse' :: Maybe Theme
theme = Maybe Theme
a} :: GetThemeResponse)

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

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