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

    -- * Request Lenses
    getForm_appId,
    getForm_environmentName,
    getForm_id,

    -- * Destructuring the Response
    GetFormResponse (..),
    newGetFormResponse,

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

-- |
-- Create a value of 'GetForm' 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', 'getForm_appId' - The unique ID of the Amplify app.
--
-- 'environmentName', 'getForm_environmentName' - The name of the backend environment that is part of the Amplify app.
--
-- 'id', 'getForm_id' - The unique ID of the form.
newGetForm ::
  -- | 'appId'
  Prelude.Text ->
  -- | 'environmentName'
  Prelude.Text ->
  -- | 'id'
  Prelude.Text ->
  GetForm
newGetForm :: Text -> Text -> Text -> GetForm
newGetForm Text
pAppId_ Text
pEnvironmentName_ Text
pId_ =
  GetForm'
    { $sel:appId:GetForm' :: Text
appId = Text
pAppId_,
      $sel:environmentName:GetForm' :: Text
environmentName = Text
pEnvironmentName_,
      $sel:id:GetForm' :: Text
id = Text
pId_
    }

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

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

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

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

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

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

-- |
-- Create a value of 'GetFormResponse' 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:
--
-- 'form', 'getFormResponse_form' - Represents the configuration settings for the form.
--
-- 'httpStatus', 'getFormResponse_httpStatus' - The response's http status code.
newGetFormResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetFormResponse
newGetFormResponse :: Int -> GetFormResponse
newGetFormResponse Int
pHttpStatus_ =
  GetFormResponse'
    { $sel:form:GetFormResponse' :: Maybe Form
form = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetFormResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Represents the configuration settings for the form.
getFormResponse_form :: Lens.Lens' GetFormResponse (Prelude.Maybe Form)
getFormResponse_form :: Lens' GetFormResponse (Maybe Form)
getFormResponse_form = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFormResponse' {Maybe Form
form :: Maybe Form
$sel:form:GetFormResponse' :: GetFormResponse -> Maybe Form
form} -> Maybe Form
form) (\s :: GetFormResponse
s@GetFormResponse' {} Maybe Form
a -> GetFormResponse
s {$sel:form:GetFormResponse' :: Maybe Form
form = Maybe Form
a} :: GetFormResponse)

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

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