{-# 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.ExportThemes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Exports theme configurations to code that is ready to integrate into an
-- Amplify app.
--
-- This operation returns paginated results.
module Amazonka.AmplifyUiBuilder.ExportThemes
  ( -- * Creating a Request
    ExportThemes (..),
    newExportThemes,

    -- * Request Lenses
    exportThemes_nextToken,
    exportThemes_appId,
    exportThemes_environmentName,

    -- * Destructuring the Response
    ExportThemesResponse (..),
    newExportThemesResponse,

    -- * Response Lenses
    exportThemesResponse_nextToken,
    exportThemesResponse_httpStatus,
    exportThemesResponse_entities,
  )
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:/ 'newExportThemes' smart constructor.
data ExportThemes = ExportThemes'
  { -- | The token to request the next page of results.
    ExportThemes -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The unique ID of the Amplify app to export the themes to.
    ExportThemes -> Text
appId :: Prelude.Text,
    -- | The name of the backend environment that is part of the Amplify app.
    ExportThemes -> Text
environmentName :: Prelude.Text
  }
  deriving (ExportThemes -> ExportThemes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportThemes -> ExportThemes -> Bool
$c/= :: ExportThemes -> ExportThemes -> Bool
== :: ExportThemes -> ExportThemes -> Bool
$c== :: ExportThemes -> ExportThemes -> Bool
Prelude.Eq, ReadPrec [ExportThemes]
ReadPrec ExportThemes
Int -> ReadS ExportThemes
ReadS [ExportThemes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExportThemes]
$creadListPrec :: ReadPrec [ExportThemes]
readPrec :: ReadPrec ExportThemes
$creadPrec :: ReadPrec ExportThemes
readList :: ReadS [ExportThemes]
$creadList :: ReadS [ExportThemes]
readsPrec :: Int -> ReadS ExportThemes
$creadsPrec :: Int -> ReadS ExportThemes
Prelude.Read, Int -> ExportThemes -> ShowS
[ExportThemes] -> ShowS
ExportThemes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExportThemes] -> ShowS
$cshowList :: [ExportThemes] -> ShowS
show :: ExportThemes -> String
$cshow :: ExportThemes -> String
showsPrec :: Int -> ExportThemes -> ShowS
$cshowsPrec :: Int -> ExportThemes -> ShowS
Prelude.Show, forall x. Rep ExportThemes x -> ExportThemes
forall x. ExportThemes -> Rep ExportThemes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExportThemes x -> ExportThemes
$cfrom :: forall x. ExportThemes -> Rep ExportThemes x
Prelude.Generic)

-- |
-- Create a value of 'ExportThemes' 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:
--
-- 'nextToken', 'exportThemes_nextToken' - The token to request the next page of results.
--
-- 'appId', 'exportThemes_appId' - The unique ID of the Amplify app to export the themes to.
--
-- 'environmentName', 'exportThemes_environmentName' - The name of the backend environment that is part of the Amplify app.
newExportThemes ::
  -- | 'appId'
  Prelude.Text ->
  -- | 'environmentName'
  Prelude.Text ->
  ExportThemes
newExportThemes :: Text -> Text -> ExportThemes
newExportThemes Text
pAppId_ Text
pEnvironmentName_ =
  ExportThemes'
    { $sel:nextToken:ExportThemes' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:appId:ExportThemes' :: Text
appId = Text
pAppId_,
      $sel:environmentName:ExportThemes' :: Text
environmentName = Text
pEnvironmentName_
    }

-- | The token to request the next page of results.
exportThemes_nextToken :: Lens.Lens' ExportThemes (Prelude.Maybe Prelude.Text)
exportThemes_nextToken :: Lens' ExportThemes (Maybe Text)
exportThemes_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportThemes' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ExportThemes' :: ExportThemes -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ExportThemes
s@ExportThemes' {} Maybe Text
a -> ExportThemes
s {$sel:nextToken:ExportThemes' :: Maybe Text
nextToken = Maybe Text
a} :: ExportThemes)

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

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

instance Core.AWSPager ExportThemes where
  page :: ExportThemes -> AWSResponse ExportThemes -> Maybe ExportThemes
page ExportThemes
rq AWSResponse ExportThemes
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ExportThemes
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ExportThemesResponse (Maybe Text)
exportThemesResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        (AWSResponse ExportThemes
rs forall s a. s -> Getting a s a -> a
Lens.^. Lens' ExportThemesResponse [Theme]
exportThemesResponse_entities) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ExportThemes
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ExportThemes (Maybe Text)
exportThemes_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ExportThemes
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ExportThemesResponse (Maybe Text)
exportThemesResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ExportThemes where
  type AWSResponse ExportThemes = ExportThemesResponse
  request :: (Service -> Service) -> ExportThemes -> Request ExportThemes
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 ExportThemes
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ExportThemes)))
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 Text -> Int -> [Theme] -> ExportThemesResponse
ExportThemesResponse'
            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
"nextToken")
            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))
            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
"entities" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable ExportThemes where
  hashWithSalt :: Int -> ExportThemes -> Int
hashWithSalt Int
_salt ExportThemes' {Maybe Text
Text
environmentName :: Text
appId :: Text
nextToken :: Maybe Text
$sel:environmentName:ExportThemes' :: ExportThemes -> Text
$sel:appId:ExportThemes' :: ExportThemes -> Text
$sel:nextToken:ExportThemes' :: ExportThemes -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      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 ExportThemes where
  rnf :: ExportThemes -> ()
rnf ExportThemes' {Maybe Text
Text
environmentName :: Text
appId :: Text
nextToken :: Maybe Text
$sel:environmentName:ExportThemes' :: ExportThemes -> Text
$sel:appId:ExportThemes' :: ExportThemes -> Text
$sel:nextToken:ExportThemes' :: ExportThemes -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 ExportThemes where
  toHeaders :: ExportThemes -> 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 ExportThemes where
  toPath :: ExportThemes -> ByteString
toPath ExportThemes' {Maybe Text
Text
environmentName :: Text
appId :: Text
nextToken :: Maybe Text
$sel:environmentName:ExportThemes' :: ExportThemes -> Text
$sel:appId:ExportThemes' :: ExportThemes -> Text
$sel:nextToken:ExportThemes' :: ExportThemes -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/export/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"
      ]

instance Data.ToQuery ExportThemes where
  toQuery :: ExportThemes -> QueryString
toQuery ExportThemes' {Maybe Text
Text
environmentName :: Text
appId :: Text
nextToken :: Maybe Text
$sel:environmentName:ExportThemes' :: ExportThemes -> Text
$sel:appId:ExportThemes' :: ExportThemes -> Text
$sel:nextToken:ExportThemes' :: ExportThemes -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken]

-- | /See:/ 'newExportThemesResponse' smart constructor.
data ExportThemesResponse = ExportThemesResponse'
  { -- | The pagination token that\'s included if more results are available.
    ExportThemesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ExportThemesResponse -> Int
httpStatus :: Prelude.Int,
    -- | Represents the configuration of the exported themes.
    ExportThemesResponse -> [Theme]
entities :: [Theme]
  }
  deriving (ExportThemesResponse -> ExportThemesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportThemesResponse -> ExportThemesResponse -> Bool
$c/= :: ExportThemesResponse -> ExportThemesResponse -> Bool
== :: ExportThemesResponse -> ExportThemesResponse -> Bool
$c== :: ExportThemesResponse -> ExportThemesResponse -> Bool
Prelude.Eq, ReadPrec [ExportThemesResponse]
ReadPrec ExportThemesResponse
Int -> ReadS ExportThemesResponse
ReadS [ExportThemesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExportThemesResponse]
$creadListPrec :: ReadPrec [ExportThemesResponse]
readPrec :: ReadPrec ExportThemesResponse
$creadPrec :: ReadPrec ExportThemesResponse
readList :: ReadS [ExportThemesResponse]
$creadList :: ReadS [ExportThemesResponse]
readsPrec :: Int -> ReadS ExportThemesResponse
$creadsPrec :: Int -> ReadS ExportThemesResponse
Prelude.Read, Int -> ExportThemesResponse -> ShowS
[ExportThemesResponse] -> ShowS
ExportThemesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExportThemesResponse] -> ShowS
$cshowList :: [ExportThemesResponse] -> ShowS
show :: ExportThemesResponse -> String
$cshow :: ExportThemesResponse -> String
showsPrec :: Int -> ExportThemesResponse -> ShowS
$cshowsPrec :: Int -> ExportThemesResponse -> ShowS
Prelude.Show, forall x. Rep ExportThemesResponse x -> ExportThemesResponse
forall x. ExportThemesResponse -> Rep ExportThemesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExportThemesResponse x -> ExportThemesResponse
$cfrom :: forall x. ExportThemesResponse -> Rep ExportThemesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ExportThemesResponse' 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:
--
-- 'nextToken', 'exportThemesResponse_nextToken' - The pagination token that\'s included if more results are available.
--
-- 'httpStatus', 'exportThemesResponse_httpStatus' - The response's http status code.
--
-- 'entities', 'exportThemesResponse_entities' - Represents the configuration of the exported themes.
newExportThemesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ExportThemesResponse
newExportThemesResponse :: Int -> ExportThemesResponse
newExportThemesResponse Int
pHttpStatus_ =
  ExportThemesResponse'
    { $sel:nextToken:ExportThemesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ExportThemesResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:entities:ExportThemesResponse' :: [Theme]
entities = forall a. Monoid a => a
Prelude.mempty
    }

-- | The pagination token that\'s included if more results are available.
exportThemesResponse_nextToken :: Lens.Lens' ExportThemesResponse (Prelude.Maybe Prelude.Text)
exportThemesResponse_nextToken :: Lens' ExportThemesResponse (Maybe Text)
exportThemesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportThemesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ExportThemesResponse' :: ExportThemesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ExportThemesResponse
s@ExportThemesResponse' {} Maybe Text
a -> ExportThemesResponse
s {$sel:nextToken:ExportThemesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ExportThemesResponse)

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

-- | Represents the configuration of the exported themes.
exportThemesResponse_entities :: Lens.Lens' ExportThemesResponse [Theme]
exportThemesResponse_entities :: Lens' ExportThemesResponse [Theme]
exportThemesResponse_entities = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportThemesResponse' {[Theme]
entities :: [Theme]
$sel:entities:ExportThemesResponse' :: ExportThemesResponse -> [Theme]
entities} -> [Theme]
entities) (\s :: ExportThemesResponse
s@ExportThemesResponse' {} [Theme]
a -> ExportThemesResponse
s {$sel:entities:ExportThemesResponse' :: [Theme]
entities = [Theme]
a} :: ExportThemesResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Prelude.NFData ExportThemesResponse where
  rnf :: ExportThemesResponse -> ()
rnf ExportThemesResponse' {Int
[Theme]
Maybe Text
entities :: [Theme]
httpStatus :: Int
nextToken :: Maybe Text
$sel:entities:ExportThemesResponse' :: ExportThemesResponse -> [Theme]
$sel:httpStatus:ExportThemesResponse' :: ExportThemesResponse -> Int
$sel:nextToken:ExportThemesResponse' :: ExportThemesResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 [Theme]
entities