{-# 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.Mobile.DescribeProject
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets details about a project in AWS Mobile Hub.
module Amazonka.Mobile.DescribeProject
  ( -- * Creating a Request
    DescribeProject (..),
    newDescribeProject,

    -- * Request Lenses
    describeProject_syncFromResources,
    describeProject_projectId,

    -- * Destructuring the Response
    DescribeProjectResponse (..),
    newDescribeProjectResponse,

    -- * Response Lenses
    describeProjectResponse_details,
    describeProjectResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Mobile.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Request structure used to request details about a project.
--
-- /See:/ 'newDescribeProject' smart constructor.
data DescribeProject = DescribeProject'
  { -- | If set to true, causes AWS Mobile Hub to synchronize information from
    -- other services, e.g., update state of AWS CloudFormation stacks in the
    -- AWS Mobile Hub project.
    DescribeProject -> Maybe Bool
syncFromResources :: Prelude.Maybe Prelude.Bool,
    -- | Unique project identifier.
    DescribeProject -> Text
projectId :: Prelude.Text
  }
  deriving (DescribeProject -> DescribeProject -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeProject -> DescribeProject -> Bool
$c/= :: DescribeProject -> DescribeProject -> Bool
== :: DescribeProject -> DescribeProject -> Bool
$c== :: DescribeProject -> DescribeProject -> Bool
Prelude.Eq, ReadPrec [DescribeProject]
ReadPrec DescribeProject
Int -> ReadS DescribeProject
ReadS [DescribeProject]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeProject]
$creadListPrec :: ReadPrec [DescribeProject]
readPrec :: ReadPrec DescribeProject
$creadPrec :: ReadPrec DescribeProject
readList :: ReadS [DescribeProject]
$creadList :: ReadS [DescribeProject]
readsPrec :: Int -> ReadS DescribeProject
$creadsPrec :: Int -> ReadS DescribeProject
Prelude.Read, Int -> DescribeProject -> ShowS
[DescribeProject] -> ShowS
DescribeProject -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeProject] -> ShowS
$cshowList :: [DescribeProject] -> ShowS
show :: DescribeProject -> String
$cshow :: DescribeProject -> String
showsPrec :: Int -> DescribeProject -> ShowS
$cshowsPrec :: Int -> DescribeProject -> ShowS
Prelude.Show, forall x. Rep DescribeProject x -> DescribeProject
forall x. DescribeProject -> Rep DescribeProject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeProject x -> DescribeProject
$cfrom :: forall x. DescribeProject -> Rep DescribeProject x
Prelude.Generic)

-- |
-- Create a value of 'DescribeProject' 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:
--
-- 'syncFromResources', 'describeProject_syncFromResources' - If set to true, causes AWS Mobile Hub to synchronize information from
-- other services, e.g., update state of AWS CloudFormation stacks in the
-- AWS Mobile Hub project.
--
-- 'projectId', 'describeProject_projectId' - Unique project identifier.
newDescribeProject ::
  -- | 'projectId'
  Prelude.Text ->
  DescribeProject
newDescribeProject :: Text -> DescribeProject
newDescribeProject Text
pProjectId_ =
  DescribeProject'
    { $sel:syncFromResources:DescribeProject' :: Maybe Bool
syncFromResources =
        forall a. Maybe a
Prelude.Nothing,
      $sel:projectId:DescribeProject' :: Text
projectId = Text
pProjectId_
    }

-- | If set to true, causes AWS Mobile Hub to synchronize information from
-- other services, e.g., update state of AWS CloudFormation stacks in the
-- AWS Mobile Hub project.
describeProject_syncFromResources :: Lens.Lens' DescribeProject (Prelude.Maybe Prelude.Bool)
describeProject_syncFromResources :: Lens' DescribeProject (Maybe Bool)
describeProject_syncFromResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProject' {Maybe Bool
syncFromResources :: Maybe Bool
$sel:syncFromResources:DescribeProject' :: DescribeProject -> Maybe Bool
syncFromResources} -> Maybe Bool
syncFromResources) (\s :: DescribeProject
s@DescribeProject' {} Maybe Bool
a -> DescribeProject
s {$sel:syncFromResources:DescribeProject' :: Maybe Bool
syncFromResources = Maybe Bool
a} :: DescribeProject)

-- | Unique project identifier.
describeProject_projectId :: Lens.Lens' DescribeProject Prelude.Text
describeProject_projectId :: Lens' DescribeProject Text
describeProject_projectId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProject' {Text
projectId :: Text
$sel:projectId:DescribeProject' :: DescribeProject -> Text
projectId} -> Text
projectId) (\s :: DescribeProject
s@DescribeProject' {} Text
a -> DescribeProject
s {$sel:projectId:DescribeProject' :: Text
projectId = Text
a} :: DescribeProject)

instance Core.AWSRequest DescribeProject where
  type
    AWSResponse DescribeProject =
      DescribeProjectResponse
  request :: (Service -> Service) -> DescribeProject -> Request DescribeProject
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 DescribeProject
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeProject)))
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 ProjectDetails -> Int -> DescribeProjectResponse
DescribeProjectResponse'
            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
"details")
            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 DescribeProject where
  hashWithSalt :: Int -> DescribeProject -> Int
hashWithSalt Int
_salt DescribeProject' {Maybe Bool
Text
projectId :: Text
syncFromResources :: Maybe Bool
$sel:projectId:DescribeProject' :: DescribeProject -> Text
$sel:syncFromResources:DescribeProject' :: DescribeProject -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
syncFromResources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
projectId

instance Prelude.NFData DescribeProject where
  rnf :: DescribeProject -> ()
rnf DescribeProject' {Maybe Bool
Text
projectId :: Text
syncFromResources :: Maybe Bool
$sel:projectId:DescribeProject' :: DescribeProject -> Text
$sel:syncFromResources:DescribeProject' :: DescribeProject -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
syncFromResources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
projectId

instance Data.ToHeaders DescribeProject where
  toHeaders :: DescribeProject -> 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 DescribeProject where
  toPath :: DescribeProject -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/project"

instance Data.ToQuery DescribeProject where
  toQuery :: DescribeProject -> QueryString
toQuery DescribeProject' {Maybe Bool
Text
projectId :: Text
syncFromResources :: Maybe Bool
$sel:projectId:DescribeProject' :: DescribeProject -> Text
$sel:syncFromResources:DescribeProject' :: DescribeProject -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"syncFromResources" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
syncFromResources,
        ByteString
"projectId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
projectId
      ]

-- | Result structure used for requests of project details.
--
-- /See:/ 'newDescribeProjectResponse' smart constructor.
data DescribeProjectResponse = DescribeProjectResponse'
  { DescribeProjectResponse -> Maybe ProjectDetails
details :: Prelude.Maybe ProjectDetails,
    -- | The response's http status code.
    DescribeProjectResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeProjectResponse -> DescribeProjectResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeProjectResponse -> DescribeProjectResponse -> Bool
$c/= :: DescribeProjectResponse -> DescribeProjectResponse -> Bool
== :: DescribeProjectResponse -> DescribeProjectResponse -> Bool
$c== :: DescribeProjectResponse -> DescribeProjectResponse -> Bool
Prelude.Eq, ReadPrec [DescribeProjectResponse]
ReadPrec DescribeProjectResponse
Int -> ReadS DescribeProjectResponse
ReadS [DescribeProjectResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeProjectResponse]
$creadListPrec :: ReadPrec [DescribeProjectResponse]
readPrec :: ReadPrec DescribeProjectResponse
$creadPrec :: ReadPrec DescribeProjectResponse
readList :: ReadS [DescribeProjectResponse]
$creadList :: ReadS [DescribeProjectResponse]
readsPrec :: Int -> ReadS DescribeProjectResponse
$creadsPrec :: Int -> ReadS DescribeProjectResponse
Prelude.Read, Int -> DescribeProjectResponse -> ShowS
[DescribeProjectResponse] -> ShowS
DescribeProjectResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeProjectResponse] -> ShowS
$cshowList :: [DescribeProjectResponse] -> ShowS
show :: DescribeProjectResponse -> String
$cshow :: DescribeProjectResponse -> String
showsPrec :: Int -> DescribeProjectResponse -> ShowS
$cshowsPrec :: Int -> DescribeProjectResponse -> ShowS
Prelude.Show, forall x. Rep DescribeProjectResponse x -> DescribeProjectResponse
forall x. DescribeProjectResponse -> Rep DescribeProjectResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeProjectResponse x -> DescribeProjectResponse
$cfrom :: forall x. DescribeProjectResponse -> Rep DescribeProjectResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeProjectResponse' 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:
--
-- 'details', 'describeProjectResponse_details' - Undocumented member.
--
-- 'httpStatus', 'describeProjectResponse_httpStatus' - The response's http status code.
newDescribeProjectResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeProjectResponse
newDescribeProjectResponse :: Int -> DescribeProjectResponse
newDescribeProjectResponse Int
pHttpStatus_ =
  DescribeProjectResponse'
    { $sel:details:DescribeProjectResponse' :: Maybe ProjectDetails
details = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeProjectResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
describeProjectResponse_details :: Lens.Lens' DescribeProjectResponse (Prelude.Maybe ProjectDetails)
describeProjectResponse_details :: Lens' DescribeProjectResponse (Maybe ProjectDetails)
describeProjectResponse_details = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProjectResponse' {Maybe ProjectDetails
details :: Maybe ProjectDetails
$sel:details:DescribeProjectResponse' :: DescribeProjectResponse -> Maybe ProjectDetails
details} -> Maybe ProjectDetails
details) (\s :: DescribeProjectResponse
s@DescribeProjectResponse' {} Maybe ProjectDetails
a -> DescribeProjectResponse
s {$sel:details:DescribeProjectResponse' :: Maybe ProjectDetails
details = Maybe ProjectDetails
a} :: DescribeProjectResponse)

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

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