{-# 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.ExportForms
-- 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 form configurations to code that is ready to integrate into an
-- Amplify app.
--
-- This operation returns paginated results.
module Amazonka.AmplifyUiBuilder.ExportForms
  ( -- * Creating a Request
    ExportForms (..),
    newExportForms,

    -- * Request Lenses
    exportForms_nextToken,
    exportForms_appId,
    exportForms_environmentName,

    -- * Destructuring the Response
    ExportFormsResponse (..),
    newExportFormsResponse,

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

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

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

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

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

instance Core.AWSPager ExportForms where
  page :: ExportForms -> AWSResponse ExportForms -> Maybe ExportForms
page ExportForms
rq AWSResponse ExportForms
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ExportForms
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ExportFormsResponse (Maybe Text)
exportFormsResponse_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 ExportForms
rs forall s a. s -> Getting a s a -> a
Lens.^. Lens' ExportFormsResponse [Form]
exportFormsResponse_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.$ ExportForms
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ExportForms (Maybe Text)
exportForms_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ExportForms
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ExportFormsResponse (Maybe Text)
exportFormsResponse_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 ExportForms where
  type AWSResponse ExportForms = ExportFormsResponse
  request :: (Service -> Service) -> ExportForms -> Request ExportForms
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 ExportForms
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ExportForms)))
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 -> [Form] -> ExportFormsResponse
ExportFormsResponse'
            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 ExportForms where
  hashWithSalt :: Int -> ExportForms -> Int
hashWithSalt Int
_salt ExportForms' {Maybe Text
Text
environmentName :: Text
appId :: Text
nextToken :: Maybe Text
$sel:environmentName:ExportForms' :: ExportForms -> Text
$sel:appId:ExportForms' :: ExportForms -> Text
$sel:nextToken:ExportForms' :: ExportForms -> 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 ExportForms where
  rnf :: ExportForms -> ()
rnf ExportForms' {Maybe Text
Text
environmentName :: Text
appId :: Text
nextToken :: Maybe Text
$sel:environmentName:ExportForms' :: ExportForms -> Text
$sel:appId:ExportForms' :: ExportForms -> Text
$sel:nextToken:ExportForms' :: ExportForms -> 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 ExportForms where
  toHeaders :: ExportForms -> 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 ExportForms where
  toPath :: ExportForms -> ByteString
toPath ExportForms' {Maybe Text
Text
environmentName :: Text
appId :: Text
nextToken :: Maybe Text
$sel:environmentName:ExportForms' :: ExportForms -> Text
$sel:appId:ExportForms' :: ExportForms -> Text
$sel:nextToken:ExportForms' :: ExportForms -> 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
"/forms"
      ]

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

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

-- |
-- Create a value of 'ExportFormsResponse' 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', 'exportFormsResponse_nextToken' - The pagination token that\'s included if more results are available.
--
-- 'httpStatus', 'exportFormsResponse_httpStatus' - The response's http status code.
--
-- 'entities', 'exportFormsResponse_entities' - Represents the configuration of the exported forms.
newExportFormsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ExportFormsResponse
newExportFormsResponse :: Int -> ExportFormsResponse
newExportFormsResponse Int
pHttpStatus_ =
  ExportFormsResponse'
    { $sel:nextToken:ExportFormsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ExportFormsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:entities:ExportFormsResponse' :: [Form]
entities = forall a. Monoid a => a
Prelude.mempty
    }

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

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

-- | Represents the configuration of the exported forms.
exportFormsResponse_entities :: Lens.Lens' ExportFormsResponse [Form]
exportFormsResponse_entities :: Lens' ExportFormsResponse [Form]
exportFormsResponse_entities = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportFormsResponse' {[Form]
entities :: [Form]
$sel:entities:ExportFormsResponse' :: ExportFormsResponse -> [Form]
entities} -> [Form]
entities) (\s :: ExportFormsResponse
s@ExportFormsResponse' {} [Form]
a -> ExportFormsResponse
s {$sel:entities:ExportFormsResponse' :: [Form]
entities = [Form]
a} :: ExportFormsResponse) 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 ExportFormsResponse where
  rnf :: ExportFormsResponse -> ()
rnf ExportFormsResponse' {Int
[Form]
Maybe Text
entities :: [Form]
httpStatus :: Int
nextToken :: Maybe Text
$sel:entities:ExportFormsResponse' :: ExportFormsResponse -> [Form]
$sel:httpStatus:ExportFormsResponse' :: ExportFormsResponse -> Int
$sel:nextToken:ExportFormsResponse' :: ExportFormsResponse -> 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 [Form]
entities