{-# 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.AppFlow.DescribeConnector
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the given custom connector registered in your Amazon Web
-- Services account. This API can be used for custom connectors that are
-- registered in your account and also for Amazon authored connectors.
module Amazonka.AppFlow.DescribeConnector
  ( -- * Creating a Request
    DescribeConnector (..),
    newDescribeConnector,

    -- * Request Lenses
    describeConnector_connectorLabel,
    describeConnector_connectorType,

    -- * Destructuring the Response
    DescribeConnectorResponse (..),
    newDescribeConnectorResponse,

    -- * Response Lenses
    describeConnectorResponse_connectorConfiguration,
    describeConnectorResponse_httpStatus,
  )
where

import Amazonka.AppFlow.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:/ 'newDescribeConnector' smart constructor.
data DescribeConnector = DescribeConnector'
  { -- | The label of the connector. The label is unique for each
    -- @ConnectorRegistration@ in your Amazon Web Services account. Only needed
    -- if calling for CUSTOMCONNECTOR connector type\/.
    DescribeConnector -> Maybe Text
connectorLabel :: Prelude.Maybe Prelude.Text,
    -- | The connector type, such as CUSTOMCONNECTOR, Saleforce, Marketo. Please
    -- choose CUSTOMCONNECTOR for Lambda based custom connectors.
    DescribeConnector -> ConnectorType
connectorType :: ConnectorType
  }
  deriving (DescribeConnector -> DescribeConnector -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeConnector -> DescribeConnector -> Bool
$c/= :: DescribeConnector -> DescribeConnector -> Bool
== :: DescribeConnector -> DescribeConnector -> Bool
$c== :: DescribeConnector -> DescribeConnector -> Bool
Prelude.Eq, ReadPrec [DescribeConnector]
ReadPrec DescribeConnector
Int -> ReadS DescribeConnector
ReadS [DescribeConnector]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeConnector]
$creadListPrec :: ReadPrec [DescribeConnector]
readPrec :: ReadPrec DescribeConnector
$creadPrec :: ReadPrec DescribeConnector
readList :: ReadS [DescribeConnector]
$creadList :: ReadS [DescribeConnector]
readsPrec :: Int -> ReadS DescribeConnector
$creadsPrec :: Int -> ReadS DescribeConnector
Prelude.Read, Int -> DescribeConnector -> ShowS
[DescribeConnector] -> ShowS
DescribeConnector -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeConnector] -> ShowS
$cshowList :: [DescribeConnector] -> ShowS
show :: DescribeConnector -> String
$cshow :: DescribeConnector -> String
showsPrec :: Int -> DescribeConnector -> ShowS
$cshowsPrec :: Int -> DescribeConnector -> ShowS
Prelude.Show, forall x. Rep DescribeConnector x -> DescribeConnector
forall x. DescribeConnector -> Rep DescribeConnector x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeConnector x -> DescribeConnector
$cfrom :: forall x. DescribeConnector -> Rep DescribeConnector x
Prelude.Generic)

-- |
-- Create a value of 'DescribeConnector' 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:
--
-- 'connectorLabel', 'describeConnector_connectorLabel' - The label of the connector. The label is unique for each
-- @ConnectorRegistration@ in your Amazon Web Services account. Only needed
-- if calling for CUSTOMCONNECTOR connector type\/.
--
-- 'connectorType', 'describeConnector_connectorType' - The connector type, such as CUSTOMCONNECTOR, Saleforce, Marketo. Please
-- choose CUSTOMCONNECTOR for Lambda based custom connectors.
newDescribeConnector ::
  -- | 'connectorType'
  ConnectorType ->
  DescribeConnector
newDescribeConnector :: ConnectorType -> DescribeConnector
newDescribeConnector ConnectorType
pConnectorType_ =
  DescribeConnector'
    { $sel:connectorLabel:DescribeConnector' :: Maybe Text
connectorLabel =
        forall a. Maybe a
Prelude.Nothing,
      $sel:connectorType:DescribeConnector' :: ConnectorType
connectorType = ConnectorType
pConnectorType_
    }

-- | The label of the connector. The label is unique for each
-- @ConnectorRegistration@ in your Amazon Web Services account. Only needed
-- if calling for CUSTOMCONNECTOR connector type\/.
describeConnector_connectorLabel :: Lens.Lens' DescribeConnector (Prelude.Maybe Prelude.Text)
describeConnector_connectorLabel :: Lens' DescribeConnector (Maybe Text)
describeConnector_connectorLabel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnector' {Maybe Text
connectorLabel :: Maybe Text
$sel:connectorLabel:DescribeConnector' :: DescribeConnector -> Maybe Text
connectorLabel} -> Maybe Text
connectorLabel) (\s :: DescribeConnector
s@DescribeConnector' {} Maybe Text
a -> DescribeConnector
s {$sel:connectorLabel:DescribeConnector' :: Maybe Text
connectorLabel = Maybe Text
a} :: DescribeConnector)

-- | The connector type, such as CUSTOMCONNECTOR, Saleforce, Marketo. Please
-- choose CUSTOMCONNECTOR for Lambda based custom connectors.
describeConnector_connectorType :: Lens.Lens' DescribeConnector ConnectorType
describeConnector_connectorType :: Lens' DescribeConnector ConnectorType
describeConnector_connectorType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnector' {ConnectorType
connectorType :: ConnectorType
$sel:connectorType:DescribeConnector' :: DescribeConnector -> ConnectorType
connectorType} -> ConnectorType
connectorType) (\s :: DescribeConnector
s@DescribeConnector' {} ConnectorType
a -> DescribeConnector
s {$sel:connectorType:DescribeConnector' :: ConnectorType
connectorType = ConnectorType
a} :: DescribeConnector)

instance Core.AWSRequest DescribeConnector where
  type
    AWSResponse DescribeConnector =
      DescribeConnectorResponse
  request :: (Service -> Service)
-> DescribeConnector -> Request DescribeConnector
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 DescribeConnector
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeConnector)))
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 ConnectorConfiguration -> Int -> DescribeConnectorResponse
DescribeConnectorResponse'
            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
"connectorConfiguration")
            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 DescribeConnector where
  hashWithSalt :: Int -> DescribeConnector -> Int
hashWithSalt Int
_salt DescribeConnector' {Maybe Text
ConnectorType
connectorType :: ConnectorType
connectorLabel :: Maybe Text
$sel:connectorType:DescribeConnector' :: DescribeConnector -> ConnectorType
$sel:connectorLabel:DescribeConnector' :: DescribeConnector -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
connectorLabel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ConnectorType
connectorType

instance Prelude.NFData DescribeConnector where
  rnf :: DescribeConnector -> ()
rnf DescribeConnector' {Maybe Text
ConnectorType
connectorType :: ConnectorType
connectorLabel :: Maybe Text
$sel:connectorType:DescribeConnector' :: DescribeConnector -> ConnectorType
$sel:connectorLabel:DescribeConnector' :: DescribeConnector -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
connectorLabel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ConnectorType
connectorType

instance Data.ToHeaders DescribeConnector where
  toHeaders :: DescribeConnector -> 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 DescribeConnector where
  toJSON :: DescribeConnector -> Value
toJSON DescribeConnector' {Maybe Text
ConnectorType
connectorType :: ConnectorType
connectorLabel :: Maybe Text
$sel:connectorType:DescribeConnector' :: DescribeConnector -> ConnectorType
$sel:connectorLabel:DescribeConnector' :: DescribeConnector -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"connectorLabel" 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
connectorLabel,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"connectorType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ConnectorType
connectorType)
          ]
      )

instance Data.ToPath DescribeConnector where
  toPath :: DescribeConnector -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/describe-connector"

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

-- | /See:/ 'newDescribeConnectorResponse' smart constructor.
data DescribeConnectorResponse = DescribeConnectorResponse'
  { -- | Configuration info of all the connectors that the user requested.
    DescribeConnectorResponse -> Maybe ConnectorConfiguration
connectorConfiguration :: Prelude.Maybe ConnectorConfiguration,
    -- | The response's http status code.
    DescribeConnectorResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeConnectorResponse -> DescribeConnectorResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeConnectorResponse -> DescribeConnectorResponse -> Bool
$c/= :: DescribeConnectorResponse -> DescribeConnectorResponse -> Bool
== :: DescribeConnectorResponse -> DescribeConnectorResponse -> Bool
$c== :: DescribeConnectorResponse -> DescribeConnectorResponse -> Bool
Prelude.Eq, ReadPrec [DescribeConnectorResponse]
ReadPrec DescribeConnectorResponse
Int -> ReadS DescribeConnectorResponse
ReadS [DescribeConnectorResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeConnectorResponse]
$creadListPrec :: ReadPrec [DescribeConnectorResponse]
readPrec :: ReadPrec DescribeConnectorResponse
$creadPrec :: ReadPrec DescribeConnectorResponse
readList :: ReadS [DescribeConnectorResponse]
$creadList :: ReadS [DescribeConnectorResponse]
readsPrec :: Int -> ReadS DescribeConnectorResponse
$creadsPrec :: Int -> ReadS DescribeConnectorResponse
Prelude.Read, Int -> DescribeConnectorResponse -> ShowS
[DescribeConnectorResponse] -> ShowS
DescribeConnectorResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeConnectorResponse] -> ShowS
$cshowList :: [DescribeConnectorResponse] -> ShowS
show :: DescribeConnectorResponse -> String
$cshow :: DescribeConnectorResponse -> String
showsPrec :: Int -> DescribeConnectorResponse -> ShowS
$cshowsPrec :: Int -> DescribeConnectorResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeConnectorResponse x -> DescribeConnectorResponse
forall x.
DescribeConnectorResponse -> Rep DescribeConnectorResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeConnectorResponse x -> DescribeConnectorResponse
$cfrom :: forall x.
DescribeConnectorResponse -> Rep DescribeConnectorResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeConnectorResponse' 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:
--
-- 'connectorConfiguration', 'describeConnectorResponse_connectorConfiguration' - Configuration info of all the connectors that the user requested.
--
-- 'httpStatus', 'describeConnectorResponse_httpStatus' - The response's http status code.
newDescribeConnectorResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeConnectorResponse
newDescribeConnectorResponse :: Int -> DescribeConnectorResponse
newDescribeConnectorResponse Int
pHttpStatus_ =
  DescribeConnectorResponse'
    { $sel:connectorConfiguration:DescribeConnectorResponse' :: Maybe ConnectorConfiguration
connectorConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeConnectorResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Configuration info of all the connectors that the user requested.
describeConnectorResponse_connectorConfiguration :: Lens.Lens' DescribeConnectorResponse (Prelude.Maybe ConnectorConfiguration)
describeConnectorResponse_connectorConfiguration :: Lens' DescribeConnectorResponse (Maybe ConnectorConfiguration)
describeConnectorResponse_connectorConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConnectorResponse' {Maybe ConnectorConfiguration
connectorConfiguration :: Maybe ConnectorConfiguration
$sel:connectorConfiguration:DescribeConnectorResponse' :: DescribeConnectorResponse -> Maybe ConnectorConfiguration
connectorConfiguration} -> Maybe ConnectorConfiguration
connectorConfiguration) (\s :: DescribeConnectorResponse
s@DescribeConnectorResponse' {} Maybe ConnectorConfiguration
a -> DescribeConnectorResponse
s {$sel:connectorConfiguration:DescribeConnectorResponse' :: Maybe ConnectorConfiguration
connectorConfiguration = Maybe ConnectorConfiguration
a} :: DescribeConnectorResponse)

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

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