{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.ConnectorProfile
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.AppFlow.Types.ConnectorProfile where

import Amazonka.AppFlow.Types.ConnectionMode
import Amazonka.AppFlow.Types.ConnectorProfileProperties
import Amazonka.AppFlow.Types.ConnectorType
import Amazonka.AppFlow.Types.PrivateConnectionProvisioningState
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

-- | Describes an instance of a connector. This includes the provided name,
-- credentials ARN, connection-mode, and so on. To keep the API intuitive
-- and extensible, the fields that are common to all types of connector
-- profiles are explicitly specified at the top level. The rest of the
-- connector-specific properties are available via the
-- @connectorProfileProperties@ field.
--
-- /See:/ 'newConnectorProfile' smart constructor.
data ConnectorProfile = ConnectorProfile'
  { -- | Indicates the connection mode and if it is public or private.
    ConnectorProfile -> Maybe ConnectionMode
connectionMode :: Prelude.Maybe ConnectionMode,
    -- | The label for the connector profile being created.
    ConnectorProfile -> Maybe Text
connectorLabel :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the connector profile.
    ConnectorProfile -> Maybe Text
connectorProfileArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the connector profile. The name is unique for each
    -- @ConnectorProfile@ in the Amazon Web Services account.
    ConnectorProfile -> Maybe Text
connectorProfileName :: Prelude.Maybe Prelude.Text,
    -- | The connector-specific properties of the profile configuration.
    ConnectorProfile -> Maybe ConnectorProfileProperties
connectorProfileProperties :: Prelude.Maybe ConnectorProfileProperties,
    -- | The type of connector, such as Salesforce, Amplitude, and so on.
    ConnectorProfile -> Maybe ConnectorType
connectorType :: Prelude.Maybe ConnectorType,
    -- | Specifies when the connector profile was created.
    ConnectorProfile -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | The Amazon Resource Name (ARN) of the connector profile credentials.
    ConnectorProfile -> Maybe Text
credentialsArn :: Prelude.Maybe Prelude.Text,
    -- | Specifies when the connector profile was last updated.
    ConnectorProfile -> Maybe POSIX
lastUpdatedAt :: Prelude.Maybe Data.POSIX,
    -- | Specifies the private connection provisioning state.
    ConnectorProfile -> Maybe PrivateConnectionProvisioningState
privateConnectionProvisioningState :: Prelude.Maybe PrivateConnectionProvisioningState
  }
  deriving (ConnectorProfile -> ConnectorProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnectorProfile -> ConnectorProfile -> Bool
$c/= :: ConnectorProfile -> ConnectorProfile -> Bool
== :: ConnectorProfile -> ConnectorProfile -> Bool
$c== :: ConnectorProfile -> ConnectorProfile -> Bool
Prelude.Eq, ReadPrec [ConnectorProfile]
ReadPrec ConnectorProfile
Int -> ReadS ConnectorProfile
ReadS [ConnectorProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConnectorProfile]
$creadListPrec :: ReadPrec [ConnectorProfile]
readPrec :: ReadPrec ConnectorProfile
$creadPrec :: ReadPrec ConnectorProfile
readList :: ReadS [ConnectorProfile]
$creadList :: ReadS [ConnectorProfile]
readsPrec :: Int -> ReadS ConnectorProfile
$creadsPrec :: Int -> ReadS ConnectorProfile
Prelude.Read, Int -> ConnectorProfile -> ShowS
[ConnectorProfile] -> ShowS
ConnectorProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnectorProfile] -> ShowS
$cshowList :: [ConnectorProfile] -> ShowS
show :: ConnectorProfile -> String
$cshow :: ConnectorProfile -> String
showsPrec :: Int -> ConnectorProfile -> ShowS
$cshowsPrec :: Int -> ConnectorProfile -> ShowS
Prelude.Show, forall x. Rep ConnectorProfile x -> ConnectorProfile
forall x. ConnectorProfile -> Rep ConnectorProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConnectorProfile x -> ConnectorProfile
$cfrom :: forall x. ConnectorProfile -> Rep ConnectorProfile x
Prelude.Generic)

-- |
-- Create a value of 'ConnectorProfile' 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:
--
-- 'connectionMode', 'connectorProfile_connectionMode' - Indicates the connection mode and if it is public or private.
--
-- 'connectorLabel', 'connectorProfile_connectorLabel' - The label for the connector profile being created.
--
-- 'connectorProfileArn', 'connectorProfile_connectorProfileArn' - The Amazon Resource Name (ARN) of the connector profile.
--
-- 'connectorProfileName', 'connectorProfile_connectorProfileName' - The name of the connector profile. The name is unique for each
-- @ConnectorProfile@ in the Amazon Web Services account.
--
-- 'connectorProfileProperties', 'connectorProfile_connectorProfileProperties' - The connector-specific properties of the profile configuration.
--
-- 'connectorType', 'connectorProfile_connectorType' - The type of connector, such as Salesforce, Amplitude, and so on.
--
-- 'createdAt', 'connectorProfile_createdAt' - Specifies when the connector profile was created.
--
-- 'credentialsArn', 'connectorProfile_credentialsArn' - The Amazon Resource Name (ARN) of the connector profile credentials.
--
-- 'lastUpdatedAt', 'connectorProfile_lastUpdatedAt' - Specifies when the connector profile was last updated.
--
-- 'privateConnectionProvisioningState', 'connectorProfile_privateConnectionProvisioningState' - Specifies the private connection provisioning state.
newConnectorProfile ::
  ConnectorProfile
newConnectorProfile :: ConnectorProfile
newConnectorProfile =
  ConnectorProfile'
    { $sel:connectionMode:ConnectorProfile' :: Maybe ConnectionMode
connectionMode = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorLabel:ConnectorProfile' :: Maybe Text
connectorLabel = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorProfileArn:ConnectorProfile' :: Maybe Text
connectorProfileArn = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorProfileName:ConnectorProfile' :: Maybe Text
connectorProfileName = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorProfileProperties:ConnectorProfile' :: Maybe ConnectorProfileProperties
connectorProfileProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:connectorType:ConnectorProfile' :: Maybe ConnectorType
connectorType = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:ConnectorProfile' :: Maybe POSIX
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:credentialsArn:ConnectorProfile' :: Maybe Text
credentialsArn = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedAt:ConnectorProfile' :: Maybe POSIX
lastUpdatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:privateConnectionProvisioningState:ConnectorProfile' :: Maybe PrivateConnectionProvisioningState
privateConnectionProvisioningState = forall a. Maybe a
Prelude.Nothing
    }

-- | Indicates the connection mode and if it is public or private.
connectorProfile_connectionMode :: Lens.Lens' ConnectorProfile (Prelude.Maybe ConnectionMode)
connectorProfile_connectionMode :: Lens' ConnectorProfile (Maybe ConnectionMode)
connectorProfile_connectionMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfile' {Maybe ConnectionMode
connectionMode :: Maybe ConnectionMode
$sel:connectionMode:ConnectorProfile' :: ConnectorProfile -> Maybe ConnectionMode
connectionMode} -> Maybe ConnectionMode
connectionMode) (\s :: ConnectorProfile
s@ConnectorProfile' {} Maybe ConnectionMode
a -> ConnectorProfile
s {$sel:connectionMode:ConnectorProfile' :: Maybe ConnectionMode
connectionMode = Maybe ConnectionMode
a} :: ConnectorProfile)

-- | The label for the connector profile being created.
connectorProfile_connectorLabel :: Lens.Lens' ConnectorProfile (Prelude.Maybe Prelude.Text)
connectorProfile_connectorLabel :: Lens' ConnectorProfile (Maybe Text)
connectorProfile_connectorLabel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfile' {Maybe Text
connectorLabel :: Maybe Text
$sel:connectorLabel:ConnectorProfile' :: ConnectorProfile -> Maybe Text
connectorLabel} -> Maybe Text
connectorLabel) (\s :: ConnectorProfile
s@ConnectorProfile' {} Maybe Text
a -> ConnectorProfile
s {$sel:connectorLabel:ConnectorProfile' :: Maybe Text
connectorLabel = Maybe Text
a} :: ConnectorProfile)

-- | The Amazon Resource Name (ARN) of the connector profile.
connectorProfile_connectorProfileArn :: Lens.Lens' ConnectorProfile (Prelude.Maybe Prelude.Text)
connectorProfile_connectorProfileArn :: Lens' ConnectorProfile (Maybe Text)
connectorProfile_connectorProfileArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfile' {Maybe Text
connectorProfileArn :: Maybe Text
$sel:connectorProfileArn:ConnectorProfile' :: ConnectorProfile -> Maybe Text
connectorProfileArn} -> Maybe Text
connectorProfileArn) (\s :: ConnectorProfile
s@ConnectorProfile' {} Maybe Text
a -> ConnectorProfile
s {$sel:connectorProfileArn:ConnectorProfile' :: Maybe Text
connectorProfileArn = Maybe Text
a} :: ConnectorProfile)

-- | The name of the connector profile. The name is unique for each
-- @ConnectorProfile@ in the Amazon Web Services account.
connectorProfile_connectorProfileName :: Lens.Lens' ConnectorProfile (Prelude.Maybe Prelude.Text)
connectorProfile_connectorProfileName :: Lens' ConnectorProfile (Maybe Text)
connectorProfile_connectorProfileName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfile' {Maybe Text
connectorProfileName :: Maybe Text
$sel:connectorProfileName:ConnectorProfile' :: ConnectorProfile -> Maybe Text
connectorProfileName} -> Maybe Text
connectorProfileName) (\s :: ConnectorProfile
s@ConnectorProfile' {} Maybe Text
a -> ConnectorProfile
s {$sel:connectorProfileName:ConnectorProfile' :: Maybe Text
connectorProfileName = Maybe Text
a} :: ConnectorProfile)

-- | The connector-specific properties of the profile configuration.
connectorProfile_connectorProfileProperties :: Lens.Lens' ConnectorProfile (Prelude.Maybe ConnectorProfileProperties)
connectorProfile_connectorProfileProperties :: Lens' ConnectorProfile (Maybe ConnectorProfileProperties)
connectorProfile_connectorProfileProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfile' {Maybe ConnectorProfileProperties
connectorProfileProperties :: Maybe ConnectorProfileProperties
$sel:connectorProfileProperties:ConnectorProfile' :: ConnectorProfile -> Maybe ConnectorProfileProperties
connectorProfileProperties} -> Maybe ConnectorProfileProperties
connectorProfileProperties) (\s :: ConnectorProfile
s@ConnectorProfile' {} Maybe ConnectorProfileProperties
a -> ConnectorProfile
s {$sel:connectorProfileProperties:ConnectorProfile' :: Maybe ConnectorProfileProperties
connectorProfileProperties = Maybe ConnectorProfileProperties
a} :: ConnectorProfile)

-- | The type of connector, such as Salesforce, Amplitude, and so on.
connectorProfile_connectorType :: Lens.Lens' ConnectorProfile (Prelude.Maybe ConnectorType)
connectorProfile_connectorType :: Lens' ConnectorProfile (Maybe ConnectorType)
connectorProfile_connectorType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfile' {Maybe ConnectorType
connectorType :: Maybe ConnectorType
$sel:connectorType:ConnectorProfile' :: ConnectorProfile -> Maybe ConnectorType
connectorType} -> Maybe ConnectorType
connectorType) (\s :: ConnectorProfile
s@ConnectorProfile' {} Maybe ConnectorType
a -> ConnectorProfile
s {$sel:connectorType:ConnectorProfile' :: Maybe ConnectorType
connectorType = Maybe ConnectorType
a} :: ConnectorProfile)

-- | Specifies when the connector profile was created.
connectorProfile_createdAt :: Lens.Lens' ConnectorProfile (Prelude.Maybe Prelude.UTCTime)
connectorProfile_createdAt :: Lens' ConnectorProfile (Maybe UTCTime)
connectorProfile_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfile' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:ConnectorProfile' :: ConnectorProfile -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: ConnectorProfile
s@ConnectorProfile' {} Maybe POSIX
a -> ConnectorProfile
s {$sel:createdAt:ConnectorProfile' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: ConnectorProfile) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The Amazon Resource Name (ARN) of the connector profile credentials.
connectorProfile_credentialsArn :: Lens.Lens' ConnectorProfile (Prelude.Maybe Prelude.Text)
connectorProfile_credentialsArn :: Lens' ConnectorProfile (Maybe Text)
connectorProfile_credentialsArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfile' {Maybe Text
credentialsArn :: Maybe Text
$sel:credentialsArn:ConnectorProfile' :: ConnectorProfile -> Maybe Text
credentialsArn} -> Maybe Text
credentialsArn) (\s :: ConnectorProfile
s@ConnectorProfile' {} Maybe Text
a -> ConnectorProfile
s {$sel:credentialsArn:ConnectorProfile' :: Maybe Text
credentialsArn = Maybe Text
a} :: ConnectorProfile)

-- | Specifies when the connector profile was last updated.
connectorProfile_lastUpdatedAt :: Lens.Lens' ConnectorProfile (Prelude.Maybe Prelude.UTCTime)
connectorProfile_lastUpdatedAt :: Lens' ConnectorProfile (Maybe UTCTime)
connectorProfile_lastUpdatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfile' {Maybe POSIX
lastUpdatedAt :: Maybe POSIX
$sel:lastUpdatedAt:ConnectorProfile' :: ConnectorProfile -> Maybe POSIX
lastUpdatedAt} -> Maybe POSIX
lastUpdatedAt) (\s :: ConnectorProfile
s@ConnectorProfile' {} Maybe POSIX
a -> ConnectorProfile
s {$sel:lastUpdatedAt:ConnectorProfile' :: Maybe POSIX
lastUpdatedAt = Maybe POSIX
a} :: ConnectorProfile) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Specifies the private connection provisioning state.
connectorProfile_privateConnectionProvisioningState :: Lens.Lens' ConnectorProfile (Prelude.Maybe PrivateConnectionProvisioningState)
connectorProfile_privateConnectionProvisioningState :: Lens' ConnectorProfile (Maybe PrivateConnectionProvisioningState)
connectorProfile_privateConnectionProvisioningState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ConnectorProfile' {Maybe PrivateConnectionProvisioningState
privateConnectionProvisioningState :: Maybe PrivateConnectionProvisioningState
$sel:privateConnectionProvisioningState:ConnectorProfile' :: ConnectorProfile -> Maybe PrivateConnectionProvisioningState
privateConnectionProvisioningState} -> Maybe PrivateConnectionProvisioningState
privateConnectionProvisioningState) (\s :: ConnectorProfile
s@ConnectorProfile' {} Maybe PrivateConnectionProvisioningState
a -> ConnectorProfile
s {$sel:privateConnectionProvisioningState:ConnectorProfile' :: Maybe PrivateConnectionProvisioningState
privateConnectionProvisioningState = Maybe PrivateConnectionProvisioningState
a} :: ConnectorProfile)

instance Data.FromJSON ConnectorProfile where
  parseJSON :: Value -> Parser ConnectorProfile
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ConnectorProfile"
      ( \Object
x ->
          Maybe ConnectionMode
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ConnectorProfileProperties
-> Maybe ConnectorType
-> Maybe POSIX
-> Maybe Text
-> Maybe POSIX
-> Maybe PrivateConnectionProvisioningState
-> ConnectorProfile
ConnectorProfile'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"connectionMode")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"connectorLabel")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"connectorProfileArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"connectorProfileName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"connectorProfileProperties")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"connectorType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"createdAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"credentialsArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"lastUpdatedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"privateConnectionProvisioningState")
      )

instance Prelude.Hashable ConnectorProfile where
  hashWithSalt :: Int -> ConnectorProfile -> Int
hashWithSalt Int
_salt ConnectorProfile' {Maybe Text
Maybe POSIX
Maybe ConnectionMode
Maybe ConnectorType
Maybe PrivateConnectionProvisioningState
Maybe ConnectorProfileProperties
privateConnectionProvisioningState :: Maybe PrivateConnectionProvisioningState
lastUpdatedAt :: Maybe POSIX
credentialsArn :: Maybe Text
createdAt :: Maybe POSIX
connectorType :: Maybe ConnectorType
connectorProfileProperties :: Maybe ConnectorProfileProperties
connectorProfileName :: Maybe Text
connectorProfileArn :: Maybe Text
connectorLabel :: Maybe Text
connectionMode :: Maybe ConnectionMode
$sel:privateConnectionProvisioningState:ConnectorProfile' :: ConnectorProfile -> Maybe PrivateConnectionProvisioningState
$sel:lastUpdatedAt:ConnectorProfile' :: ConnectorProfile -> Maybe POSIX
$sel:credentialsArn:ConnectorProfile' :: ConnectorProfile -> Maybe Text
$sel:createdAt:ConnectorProfile' :: ConnectorProfile -> Maybe POSIX
$sel:connectorType:ConnectorProfile' :: ConnectorProfile -> Maybe ConnectorType
$sel:connectorProfileProperties:ConnectorProfile' :: ConnectorProfile -> Maybe ConnectorProfileProperties
$sel:connectorProfileName:ConnectorProfile' :: ConnectorProfile -> Maybe Text
$sel:connectorProfileArn:ConnectorProfile' :: ConnectorProfile -> Maybe Text
$sel:connectorLabel:ConnectorProfile' :: ConnectorProfile -> Maybe Text
$sel:connectionMode:ConnectorProfile' :: ConnectorProfile -> Maybe ConnectionMode
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConnectionMode
connectionMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
connectorLabel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
connectorProfileArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
connectorProfileName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConnectorProfileProperties
connectorProfileProperties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConnectorType
connectorType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
credentialsArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastUpdatedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PrivateConnectionProvisioningState
privateConnectionProvisioningState

instance Prelude.NFData ConnectorProfile where
  rnf :: ConnectorProfile -> ()
rnf ConnectorProfile' {Maybe Text
Maybe POSIX
Maybe ConnectionMode
Maybe ConnectorType
Maybe PrivateConnectionProvisioningState
Maybe ConnectorProfileProperties
privateConnectionProvisioningState :: Maybe PrivateConnectionProvisioningState
lastUpdatedAt :: Maybe POSIX
credentialsArn :: Maybe Text
createdAt :: Maybe POSIX
connectorType :: Maybe ConnectorType
connectorProfileProperties :: Maybe ConnectorProfileProperties
connectorProfileName :: Maybe Text
connectorProfileArn :: Maybe Text
connectorLabel :: Maybe Text
connectionMode :: Maybe ConnectionMode
$sel:privateConnectionProvisioningState:ConnectorProfile' :: ConnectorProfile -> Maybe PrivateConnectionProvisioningState
$sel:lastUpdatedAt:ConnectorProfile' :: ConnectorProfile -> Maybe POSIX
$sel:credentialsArn:ConnectorProfile' :: ConnectorProfile -> Maybe Text
$sel:createdAt:ConnectorProfile' :: ConnectorProfile -> Maybe POSIX
$sel:connectorType:ConnectorProfile' :: ConnectorProfile -> Maybe ConnectorType
$sel:connectorProfileProperties:ConnectorProfile' :: ConnectorProfile -> Maybe ConnectorProfileProperties
$sel:connectorProfileName:ConnectorProfile' :: ConnectorProfile -> Maybe Text
$sel:connectorProfileArn:ConnectorProfile' :: ConnectorProfile -> Maybe Text
$sel:connectorLabel:ConnectorProfile' :: ConnectorProfile -> Maybe Text
$sel:connectionMode:ConnectorProfile' :: ConnectorProfile -> Maybe ConnectionMode
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectionMode
connectionMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Maybe Text
connectorProfileArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
connectorProfileName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectorProfileProperties
connectorProfileProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectorType
connectorType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
credentialsArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PrivateConnectionProvisioningState
privateConnectionProvisioningState