{-# 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.SSMSAP.GetDatabase
-- 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 the SAP HANA database of an application registered with AWS Systems
-- Manager for SAP.
module Amazonka.SSMSAP.GetDatabase
  ( -- * Creating a Request
    GetDatabase (..),
    newGetDatabase,

    -- * Request Lenses
    getDatabase_applicationId,
    getDatabase_componentId,
    getDatabase_databaseArn,
    getDatabase_databaseId,

    -- * Destructuring the Response
    GetDatabaseResponse (..),
    newGetDatabaseResponse,

    -- * Response Lenses
    getDatabaseResponse_database,
    getDatabaseResponse_tags,
    getDatabaseResponse_httpStatus,
  )
where

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
import Amazonka.SSMSAP.Types

-- | /See:/ 'newGetDatabase' smart constructor.
data GetDatabase = GetDatabase'
  { GetDatabase -> Maybe Text
applicationId :: Prelude.Maybe Prelude.Text,
    GetDatabase -> Maybe Text
componentId :: Prelude.Maybe Prelude.Text,
    GetDatabase -> Maybe Text
databaseArn :: Prelude.Maybe Prelude.Text,
    GetDatabase -> Maybe Text
databaseId :: Prelude.Maybe Prelude.Text
  }
  deriving (GetDatabase -> GetDatabase -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDatabase -> GetDatabase -> Bool
$c/= :: GetDatabase -> GetDatabase -> Bool
== :: GetDatabase -> GetDatabase -> Bool
$c== :: GetDatabase -> GetDatabase -> Bool
Prelude.Eq, ReadPrec [GetDatabase]
ReadPrec GetDatabase
Int -> ReadS GetDatabase
ReadS [GetDatabase]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDatabase]
$creadListPrec :: ReadPrec [GetDatabase]
readPrec :: ReadPrec GetDatabase
$creadPrec :: ReadPrec GetDatabase
readList :: ReadS [GetDatabase]
$creadList :: ReadS [GetDatabase]
readsPrec :: Int -> ReadS GetDatabase
$creadsPrec :: Int -> ReadS GetDatabase
Prelude.Read, Int -> GetDatabase -> ShowS
[GetDatabase] -> ShowS
GetDatabase -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDatabase] -> ShowS
$cshowList :: [GetDatabase] -> ShowS
show :: GetDatabase -> String
$cshow :: GetDatabase -> String
showsPrec :: Int -> GetDatabase -> ShowS
$cshowsPrec :: Int -> GetDatabase -> ShowS
Prelude.Show, forall x. Rep GetDatabase x -> GetDatabase
forall x. GetDatabase -> Rep GetDatabase x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDatabase x -> GetDatabase
$cfrom :: forall x. GetDatabase -> Rep GetDatabase x
Prelude.Generic)

-- |
-- Create a value of 'GetDatabase' 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:
--
-- 'applicationId', 'getDatabase_applicationId' -
--
-- 'componentId', 'getDatabase_componentId' -
--
-- 'databaseArn', 'getDatabase_databaseArn' -
--
-- 'databaseId', 'getDatabase_databaseId' -
newGetDatabase ::
  GetDatabase
newGetDatabase :: GetDatabase
newGetDatabase =
  GetDatabase'
    { $sel:applicationId:GetDatabase' :: Maybe Text
applicationId = forall a. Maybe a
Prelude.Nothing,
      $sel:componentId:GetDatabase' :: Maybe Text
componentId = forall a. Maybe a
Prelude.Nothing,
      $sel:databaseArn:GetDatabase' :: Maybe Text
databaseArn = forall a. Maybe a
Prelude.Nothing,
      $sel:databaseId:GetDatabase' :: Maybe Text
databaseId = forall a. Maybe a
Prelude.Nothing
    }

getDatabase_applicationId :: Lens.Lens' GetDatabase (Prelude.Maybe Prelude.Text)
getDatabase_applicationId :: Lens' GetDatabase (Maybe Text)
getDatabase_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDatabase' {Maybe Text
applicationId :: Maybe Text
$sel:applicationId:GetDatabase' :: GetDatabase -> Maybe Text
applicationId} -> Maybe Text
applicationId) (\s :: GetDatabase
s@GetDatabase' {} Maybe Text
a -> GetDatabase
s {$sel:applicationId:GetDatabase' :: Maybe Text
applicationId = Maybe Text
a} :: GetDatabase)

getDatabase_componentId :: Lens.Lens' GetDatabase (Prelude.Maybe Prelude.Text)
getDatabase_componentId :: Lens' GetDatabase (Maybe Text)
getDatabase_componentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDatabase' {Maybe Text
componentId :: Maybe Text
$sel:componentId:GetDatabase' :: GetDatabase -> Maybe Text
componentId} -> Maybe Text
componentId) (\s :: GetDatabase
s@GetDatabase' {} Maybe Text
a -> GetDatabase
s {$sel:componentId:GetDatabase' :: Maybe Text
componentId = Maybe Text
a} :: GetDatabase)

getDatabase_databaseArn :: Lens.Lens' GetDatabase (Prelude.Maybe Prelude.Text)
getDatabase_databaseArn :: Lens' GetDatabase (Maybe Text)
getDatabase_databaseArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDatabase' {Maybe Text
databaseArn :: Maybe Text
$sel:databaseArn:GetDatabase' :: GetDatabase -> Maybe Text
databaseArn} -> Maybe Text
databaseArn) (\s :: GetDatabase
s@GetDatabase' {} Maybe Text
a -> GetDatabase
s {$sel:databaseArn:GetDatabase' :: Maybe Text
databaseArn = Maybe Text
a} :: GetDatabase)

getDatabase_databaseId :: Lens.Lens' GetDatabase (Prelude.Maybe Prelude.Text)
getDatabase_databaseId :: Lens' GetDatabase (Maybe Text)
getDatabase_databaseId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDatabase' {Maybe Text
databaseId :: Maybe Text
$sel:databaseId:GetDatabase' :: GetDatabase -> Maybe Text
databaseId} -> Maybe Text
databaseId) (\s :: GetDatabase
s@GetDatabase' {} Maybe Text
a -> GetDatabase
s {$sel:databaseId:GetDatabase' :: Maybe Text
databaseId = Maybe Text
a} :: GetDatabase)

instance Core.AWSRequest GetDatabase where
  type AWSResponse GetDatabase = GetDatabaseResponse
  request :: (Service -> Service) -> GetDatabase -> Request GetDatabase
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetDatabase
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetDatabase)))
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 Database
-> Maybe (HashMap Text Text) -> Int -> GetDatabaseResponse
GetDatabaseResponse'
            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
"Database")
            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
"Tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 GetDatabase where
  hashWithSalt :: Int -> GetDatabase -> Int
hashWithSalt Int
_salt GetDatabase' {Maybe Text
databaseId :: Maybe Text
databaseArn :: Maybe Text
componentId :: Maybe Text
applicationId :: Maybe Text
$sel:databaseId:GetDatabase' :: GetDatabase -> Maybe Text
$sel:databaseArn:GetDatabase' :: GetDatabase -> Maybe Text
$sel:componentId:GetDatabase' :: GetDatabase -> Maybe Text
$sel:applicationId:GetDatabase' :: GetDatabase -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
applicationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
componentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
databaseArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
databaseId

instance Prelude.NFData GetDatabase where
  rnf :: GetDatabase -> ()
rnf GetDatabase' {Maybe Text
databaseId :: Maybe Text
databaseArn :: Maybe Text
componentId :: Maybe Text
applicationId :: Maybe Text
$sel:databaseId:GetDatabase' :: GetDatabase -> Maybe Text
$sel:databaseArn:GetDatabase' :: GetDatabase -> Maybe Text
$sel:componentId:GetDatabase' :: GetDatabase -> Maybe Text
$sel:applicationId:GetDatabase' :: GetDatabase -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
componentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
databaseArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
databaseId

instance Data.ToHeaders GetDatabase where
  toHeaders :: GetDatabase -> 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.ToJSON GetDatabase where
  toJSON :: GetDatabase -> Value
toJSON GetDatabase' {Maybe Text
databaseId :: Maybe Text
databaseArn :: Maybe Text
componentId :: Maybe Text
applicationId :: Maybe Text
$sel:databaseId:GetDatabase' :: GetDatabase -> Maybe Text
$sel:databaseArn:GetDatabase' :: GetDatabase -> Maybe Text
$sel:componentId:GetDatabase' :: GetDatabase -> Maybe Text
$sel:applicationId:GetDatabase' :: GetDatabase -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ApplicationId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
applicationId,
            (Key
"ComponentId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
componentId,
            (Key
"DatabaseArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
databaseArn,
            (Key
"DatabaseId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
databaseId
          ]
      )

instance Data.ToPath GetDatabase where
  toPath :: GetDatabase -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/get-database"

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

-- | /See:/ 'newGetDatabaseResponse' smart constructor.
data GetDatabaseResponse = GetDatabaseResponse'
  { GetDatabaseResponse -> Maybe Database
database :: Prelude.Maybe Database,
    GetDatabaseResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    GetDatabaseResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetDatabaseResponse -> GetDatabaseResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDatabaseResponse -> GetDatabaseResponse -> Bool
$c/= :: GetDatabaseResponse -> GetDatabaseResponse -> Bool
== :: GetDatabaseResponse -> GetDatabaseResponse -> Bool
$c== :: GetDatabaseResponse -> GetDatabaseResponse -> Bool
Prelude.Eq, Int -> GetDatabaseResponse -> ShowS
[GetDatabaseResponse] -> ShowS
GetDatabaseResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDatabaseResponse] -> ShowS
$cshowList :: [GetDatabaseResponse] -> ShowS
show :: GetDatabaseResponse -> String
$cshow :: GetDatabaseResponse -> String
showsPrec :: Int -> GetDatabaseResponse -> ShowS
$cshowsPrec :: Int -> GetDatabaseResponse -> ShowS
Prelude.Show, forall x. Rep GetDatabaseResponse x -> GetDatabaseResponse
forall x. GetDatabaseResponse -> Rep GetDatabaseResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDatabaseResponse x -> GetDatabaseResponse
$cfrom :: forall x. GetDatabaseResponse -> Rep GetDatabaseResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetDatabaseResponse' 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:
--
-- 'database', 'getDatabaseResponse_database' -
--
-- 'tags', 'getDatabaseResponse_tags' -
--
-- 'httpStatus', 'getDatabaseResponse_httpStatus' - The response's http status code.
newGetDatabaseResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetDatabaseResponse
newGetDatabaseResponse :: Int -> GetDatabaseResponse
newGetDatabaseResponse Int
pHttpStatus_ =
  GetDatabaseResponse'
    { $sel:database:GetDatabaseResponse' :: Maybe Database
database = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:GetDatabaseResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetDatabaseResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

getDatabaseResponse_database :: Lens.Lens' GetDatabaseResponse (Prelude.Maybe Database)
getDatabaseResponse_database :: Lens' GetDatabaseResponse (Maybe Database)
getDatabaseResponse_database = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDatabaseResponse' {Maybe Database
database :: Maybe Database
$sel:database:GetDatabaseResponse' :: GetDatabaseResponse -> Maybe Database
database} -> Maybe Database
database) (\s :: GetDatabaseResponse
s@GetDatabaseResponse' {} Maybe Database
a -> GetDatabaseResponse
s {$sel:database:GetDatabaseResponse' :: Maybe Database
database = Maybe Database
a} :: GetDatabaseResponse)

getDatabaseResponse_tags :: Lens.Lens' GetDatabaseResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getDatabaseResponse_tags :: Lens' GetDatabaseResponse (Maybe (HashMap Text Text))
getDatabaseResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDatabaseResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:GetDatabaseResponse' :: GetDatabaseResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: GetDatabaseResponse
s@GetDatabaseResponse' {} Maybe (HashMap Text Text)
a -> GetDatabaseResponse
s {$sel:tags:GetDatabaseResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: GetDatabaseResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData GetDatabaseResponse where
  rnf :: GetDatabaseResponse -> ()
rnf GetDatabaseResponse' {Int
Maybe (HashMap Text Text)
Maybe Database
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
database :: Maybe Database
$sel:httpStatus:GetDatabaseResponse' :: GetDatabaseResponse -> Int
$sel:tags:GetDatabaseResponse' :: GetDatabaseResponse -> Maybe (HashMap Text Text)
$sel:database:GetDatabaseResponse' :: GetDatabaseResponse -> Maybe Database
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Database
database
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus