{-# 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.Signer.Types.SigningProfile
-- 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.Signer.Types.SigningProfile 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 Amazonka.Signer.Types.SignatureValidityPeriod
import Amazonka.Signer.Types.SigningMaterial
import Amazonka.Signer.Types.SigningProfileStatus

-- | Contains information about the ACM certificates and code signing
-- configuration parameters that can be used by a given code signing user.
--
-- /See:/ 'newSigningProfile' smart constructor.
data SigningProfile = SigningProfile'
  { -- | The Amazon Resource Name (ARN) for the signing profile.
    SigningProfile -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The name of the signing platform.
    SigningProfile -> Maybe Text
platformDisplayName :: Prelude.Maybe Prelude.Text,
    -- | The ID of a platform that is available for use by a signing profile.
    SigningProfile -> Maybe Text
platformId :: Prelude.Maybe Prelude.Text,
    -- | The name of the signing profile.
    SigningProfile -> Maybe Text
profileName :: Prelude.Maybe Prelude.Text,
    -- | The version of a signing profile.
    SigningProfile -> Maybe Text
profileVersion :: Prelude.Maybe Prelude.Text,
    -- | The ARN of a signing profile, including the profile version.
    SigningProfile -> Maybe Text
profileVersionArn :: Prelude.Maybe Prelude.Text,
    -- | The validity period for a signing job created using this signing
    -- profile.
    SigningProfile -> Maybe SignatureValidityPeriod
signatureValidityPeriod :: Prelude.Maybe SignatureValidityPeriod,
    -- | The ACM certificate that is available for use by a signing profile.
    SigningProfile -> Maybe SigningMaterial
signingMaterial :: Prelude.Maybe SigningMaterial,
    -- | The parameters that are available for use by a code signing user.
    SigningProfile -> Maybe (HashMap Text Text)
signingParameters :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The status of a code signing profile.
    SigningProfile -> Maybe SigningProfileStatus
status :: Prelude.Maybe SigningProfileStatus,
    -- | A list of tags associated with the signing profile.
    SigningProfile -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text)
  }
  deriving (SigningProfile -> SigningProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SigningProfile -> SigningProfile -> Bool
$c/= :: SigningProfile -> SigningProfile -> Bool
== :: SigningProfile -> SigningProfile -> Bool
$c== :: SigningProfile -> SigningProfile -> Bool
Prelude.Eq, ReadPrec [SigningProfile]
ReadPrec SigningProfile
Int -> ReadS SigningProfile
ReadS [SigningProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SigningProfile]
$creadListPrec :: ReadPrec [SigningProfile]
readPrec :: ReadPrec SigningProfile
$creadPrec :: ReadPrec SigningProfile
readList :: ReadS [SigningProfile]
$creadList :: ReadS [SigningProfile]
readsPrec :: Int -> ReadS SigningProfile
$creadsPrec :: Int -> ReadS SigningProfile
Prelude.Read, Int -> SigningProfile -> ShowS
[SigningProfile] -> ShowS
SigningProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningProfile] -> ShowS
$cshowList :: [SigningProfile] -> ShowS
show :: SigningProfile -> String
$cshow :: SigningProfile -> String
showsPrec :: Int -> SigningProfile -> ShowS
$cshowsPrec :: Int -> SigningProfile -> ShowS
Prelude.Show, forall x. Rep SigningProfile x -> SigningProfile
forall x. SigningProfile -> Rep SigningProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SigningProfile x -> SigningProfile
$cfrom :: forall x. SigningProfile -> Rep SigningProfile x
Prelude.Generic)

-- |
-- Create a value of 'SigningProfile' 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:
--
-- 'arn', 'signingProfile_arn' - The Amazon Resource Name (ARN) for the signing profile.
--
-- 'platformDisplayName', 'signingProfile_platformDisplayName' - The name of the signing platform.
--
-- 'platformId', 'signingProfile_platformId' - The ID of a platform that is available for use by a signing profile.
--
-- 'profileName', 'signingProfile_profileName' - The name of the signing profile.
--
-- 'profileVersion', 'signingProfile_profileVersion' - The version of a signing profile.
--
-- 'profileVersionArn', 'signingProfile_profileVersionArn' - The ARN of a signing profile, including the profile version.
--
-- 'signatureValidityPeriod', 'signingProfile_signatureValidityPeriod' - The validity period for a signing job created using this signing
-- profile.
--
-- 'signingMaterial', 'signingProfile_signingMaterial' - The ACM certificate that is available for use by a signing profile.
--
-- 'signingParameters', 'signingProfile_signingParameters' - The parameters that are available for use by a code signing user.
--
-- 'status', 'signingProfile_status' - The status of a code signing profile.
--
-- 'tags', 'signingProfile_tags' - A list of tags associated with the signing profile.
newSigningProfile ::
  SigningProfile
newSigningProfile :: SigningProfile
newSigningProfile =
  SigningProfile'
    { $sel:arn:SigningProfile' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:platformDisplayName:SigningProfile' :: Maybe Text
platformDisplayName = forall a. Maybe a
Prelude.Nothing,
      $sel:platformId:SigningProfile' :: Maybe Text
platformId = forall a. Maybe a
Prelude.Nothing,
      $sel:profileName:SigningProfile' :: Maybe Text
profileName = forall a. Maybe a
Prelude.Nothing,
      $sel:profileVersion:SigningProfile' :: Maybe Text
profileVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:profileVersionArn:SigningProfile' :: Maybe Text
profileVersionArn = forall a. Maybe a
Prelude.Nothing,
      $sel:signatureValidityPeriod:SigningProfile' :: Maybe SignatureValidityPeriod
signatureValidityPeriod = forall a. Maybe a
Prelude.Nothing,
      $sel:signingMaterial:SigningProfile' :: Maybe SigningMaterial
signingMaterial = forall a. Maybe a
Prelude.Nothing,
      $sel:signingParameters:SigningProfile' :: Maybe (HashMap Text Text)
signingParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:status:SigningProfile' :: Maybe SigningProfileStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:SigningProfile' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) for the signing profile.
signingProfile_arn :: Lens.Lens' SigningProfile (Prelude.Maybe Prelude.Text)
signingProfile_arn :: Lens' SigningProfile (Maybe Text)
signingProfile_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SigningProfile' {Maybe Text
arn :: Maybe Text
$sel:arn:SigningProfile' :: SigningProfile -> Maybe Text
arn} -> Maybe Text
arn) (\s :: SigningProfile
s@SigningProfile' {} Maybe Text
a -> SigningProfile
s {$sel:arn:SigningProfile' :: Maybe Text
arn = Maybe Text
a} :: SigningProfile)

-- | The name of the signing platform.
signingProfile_platformDisplayName :: Lens.Lens' SigningProfile (Prelude.Maybe Prelude.Text)
signingProfile_platformDisplayName :: Lens' SigningProfile (Maybe Text)
signingProfile_platformDisplayName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SigningProfile' {Maybe Text
platformDisplayName :: Maybe Text
$sel:platformDisplayName:SigningProfile' :: SigningProfile -> Maybe Text
platformDisplayName} -> Maybe Text
platformDisplayName) (\s :: SigningProfile
s@SigningProfile' {} Maybe Text
a -> SigningProfile
s {$sel:platformDisplayName:SigningProfile' :: Maybe Text
platformDisplayName = Maybe Text
a} :: SigningProfile)

-- | The ID of a platform that is available for use by a signing profile.
signingProfile_platformId :: Lens.Lens' SigningProfile (Prelude.Maybe Prelude.Text)
signingProfile_platformId :: Lens' SigningProfile (Maybe Text)
signingProfile_platformId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SigningProfile' {Maybe Text
platformId :: Maybe Text
$sel:platformId:SigningProfile' :: SigningProfile -> Maybe Text
platformId} -> Maybe Text
platformId) (\s :: SigningProfile
s@SigningProfile' {} Maybe Text
a -> SigningProfile
s {$sel:platformId:SigningProfile' :: Maybe Text
platformId = Maybe Text
a} :: SigningProfile)

-- | The name of the signing profile.
signingProfile_profileName :: Lens.Lens' SigningProfile (Prelude.Maybe Prelude.Text)
signingProfile_profileName :: Lens' SigningProfile (Maybe Text)
signingProfile_profileName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SigningProfile' {Maybe Text
profileName :: Maybe Text
$sel:profileName:SigningProfile' :: SigningProfile -> Maybe Text
profileName} -> Maybe Text
profileName) (\s :: SigningProfile
s@SigningProfile' {} Maybe Text
a -> SigningProfile
s {$sel:profileName:SigningProfile' :: Maybe Text
profileName = Maybe Text
a} :: SigningProfile)

-- | The version of a signing profile.
signingProfile_profileVersion :: Lens.Lens' SigningProfile (Prelude.Maybe Prelude.Text)
signingProfile_profileVersion :: Lens' SigningProfile (Maybe Text)
signingProfile_profileVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SigningProfile' {Maybe Text
profileVersion :: Maybe Text
$sel:profileVersion:SigningProfile' :: SigningProfile -> Maybe Text
profileVersion} -> Maybe Text
profileVersion) (\s :: SigningProfile
s@SigningProfile' {} Maybe Text
a -> SigningProfile
s {$sel:profileVersion:SigningProfile' :: Maybe Text
profileVersion = Maybe Text
a} :: SigningProfile)

-- | The ARN of a signing profile, including the profile version.
signingProfile_profileVersionArn :: Lens.Lens' SigningProfile (Prelude.Maybe Prelude.Text)
signingProfile_profileVersionArn :: Lens' SigningProfile (Maybe Text)
signingProfile_profileVersionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SigningProfile' {Maybe Text
profileVersionArn :: Maybe Text
$sel:profileVersionArn:SigningProfile' :: SigningProfile -> Maybe Text
profileVersionArn} -> Maybe Text
profileVersionArn) (\s :: SigningProfile
s@SigningProfile' {} Maybe Text
a -> SigningProfile
s {$sel:profileVersionArn:SigningProfile' :: Maybe Text
profileVersionArn = Maybe Text
a} :: SigningProfile)

-- | The validity period for a signing job created using this signing
-- profile.
signingProfile_signatureValidityPeriod :: Lens.Lens' SigningProfile (Prelude.Maybe SignatureValidityPeriod)
signingProfile_signatureValidityPeriod :: Lens' SigningProfile (Maybe SignatureValidityPeriod)
signingProfile_signatureValidityPeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SigningProfile' {Maybe SignatureValidityPeriod
signatureValidityPeriod :: Maybe SignatureValidityPeriod
$sel:signatureValidityPeriod:SigningProfile' :: SigningProfile -> Maybe SignatureValidityPeriod
signatureValidityPeriod} -> Maybe SignatureValidityPeriod
signatureValidityPeriod) (\s :: SigningProfile
s@SigningProfile' {} Maybe SignatureValidityPeriod
a -> SigningProfile
s {$sel:signatureValidityPeriod:SigningProfile' :: Maybe SignatureValidityPeriod
signatureValidityPeriod = Maybe SignatureValidityPeriod
a} :: SigningProfile)

-- | The ACM certificate that is available for use by a signing profile.
signingProfile_signingMaterial :: Lens.Lens' SigningProfile (Prelude.Maybe SigningMaterial)
signingProfile_signingMaterial :: Lens' SigningProfile (Maybe SigningMaterial)
signingProfile_signingMaterial = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SigningProfile' {Maybe SigningMaterial
signingMaterial :: Maybe SigningMaterial
$sel:signingMaterial:SigningProfile' :: SigningProfile -> Maybe SigningMaterial
signingMaterial} -> Maybe SigningMaterial
signingMaterial) (\s :: SigningProfile
s@SigningProfile' {} Maybe SigningMaterial
a -> SigningProfile
s {$sel:signingMaterial:SigningProfile' :: Maybe SigningMaterial
signingMaterial = Maybe SigningMaterial
a} :: SigningProfile)

-- | The parameters that are available for use by a code signing user.
signingProfile_signingParameters :: Lens.Lens' SigningProfile (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
signingProfile_signingParameters :: Lens' SigningProfile (Maybe (HashMap Text Text))
signingProfile_signingParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SigningProfile' {Maybe (HashMap Text Text)
signingParameters :: Maybe (HashMap Text Text)
$sel:signingParameters:SigningProfile' :: SigningProfile -> Maybe (HashMap Text Text)
signingParameters} -> Maybe (HashMap Text Text)
signingParameters) (\s :: SigningProfile
s@SigningProfile' {} Maybe (HashMap Text Text)
a -> SigningProfile
s {$sel:signingParameters:SigningProfile' :: Maybe (HashMap Text Text)
signingParameters = Maybe (HashMap Text Text)
a} :: SigningProfile) 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 status of a code signing profile.
signingProfile_status :: Lens.Lens' SigningProfile (Prelude.Maybe SigningProfileStatus)
signingProfile_status :: Lens' SigningProfile (Maybe SigningProfileStatus)
signingProfile_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SigningProfile' {Maybe SigningProfileStatus
status :: Maybe SigningProfileStatus
$sel:status:SigningProfile' :: SigningProfile -> Maybe SigningProfileStatus
status} -> Maybe SigningProfileStatus
status) (\s :: SigningProfile
s@SigningProfile' {} Maybe SigningProfileStatus
a -> SigningProfile
s {$sel:status:SigningProfile' :: Maybe SigningProfileStatus
status = Maybe SigningProfileStatus
a} :: SigningProfile)

-- | A list of tags associated with the signing profile.
signingProfile_tags :: Lens.Lens' SigningProfile (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
signingProfile_tags :: Lens' SigningProfile (Maybe (HashMap Text Text))
signingProfile_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SigningProfile' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:SigningProfile' :: SigningProfile -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: SigningProfile
s@SigningProfile' {} Maybe (HashMap Text Text)
a -> SigningProfile
s {$sel:tags:SigningProfile' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: SigningProfile) 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

instance Data.FromJSON SigningProfile where
  parseJSON :: Value -> Parser SigningProfile
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"SigningProfile"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe SignatureValidityPeriod
-> Maybe SigningMaterial
-> Maybe (HashMap Text Text)
-> Maybe SigningProfileStatus
-> Maybe (HashMap Text Text)
-> SigningProfile
SigningProfile'
            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
"arn")
            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
"platformDisplayName")
            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
"platformId")
            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
"profileName")
            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
"profileVersion")
            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
"profileVersionArn")
            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
"signatureValidityPeriod")
            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
"signingMaterial")
            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
"signingParameters"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"status")
            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
"tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable SigningProfile where
  hashWithSalt :: Int -> SigningProfile -> Int
hashWithSalt Int
_salt SigningProfile' {Maybe Text
Maybe (HashMap Text Text)
Maybe SigningMaterial
Maybe SigningProfileStatus
Maybe SignatureValidityPeriod
tags :: Maybe (HashMap Text Text)
status :: Maybe SigningProfileStatus
signingParameters :: Maybe (HashMap Text Text)
signingMaterial :: Maybe SigningMaterial
signatureValidityPeriod :: Maybe SignatureValidityPeriod
profileVersionArn :: Maybe Text
profileVersion :: Maybe Text
profileName :: Maybe Text
platformId :: Maybe Text
platformDisplayName :: Maybe Text
arn :: Maybe Text
$sel:tags:SigningProfile' :: SigningProfile -> Maybe (HashMap Text Text)
$sel:status:SigningProfile' :: SigningProfile -> Maybe SigningProfileStatus
$sel:signingParameters:SigningProfile' :: SigningProfile -> Maybe (HashMap Text Text)
$sel:signingMaterial:SigningProfile' :: SigningProfile -> Maybe SigningMaterial
$sel:signatureValidityPeriod:SigningProfile' :: SigningProfile -> Maybe SignatureValidityPeriod
$sel:profileVersionArn:SigningProfile' :: SigningProfile -> Maybe Text
$sel:profileVersion:SigningProfile' :: SigningProfile -> Maybe Text
$sel:profileName:SigningProfile' :: SigningProfile -> Maybe Text
$sel:platformId:SigningProfile' :: SigningProfile -> Maybe Text
$sel:platformDisplayName:SigningProfile' :: SigningProfile -> Maybe Text
$sel:arn:SigningProfile' :: SigningProfile -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
platformDisplayName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
platformId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
profileName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
profileVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
profileVersionArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SignatureValidityPeriod
signatureValidityPeriod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SigningMaterial
signingMaterial
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
signingParameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SigningProfileStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags

instance Prelude.NFData SigningProfile where
  rnf :: SigningProfile -> ()
rnf SigningProfile' {Maybe Text
Maybe (HashMap Text Text)
Maybe SigningMaterial
Maybe SigningProfileStatus
Maybe SignatureValidityPeriod
tags :: Maybe (HashMap Text Text)
status :: Maybe SigningProfileStatus
signingParameters :: Maybe (HashMap Text Text)
signingMaterial :: Maybe SigningMaterial
signatureValidityPeriod :: Maybe SignatureValidityPeriod
profileVersionArn :: Maybe Text
profileVersion :: Maybe Text
profileName :: Maybe Text
platformId :: Maybe Text
platformDisplayName :: Maybe Text
arn :: Maybe Text
$sel:tags:SigningProfile' :: SigningProfile -> Maybe (HashMap Text Text)
$sel:status:SigningProfile' :: SigningProfile -> Maybe SigningProfileStatus
$sel:signingParameters:SigningProfile' :: SigningProfile -> Maybe (HashMap Text Text)
$sel:signingMaterial:SigningProfile' :: SigningProfile -> Maybe SigningMaterial
$sel:signatureValidityPeriod:SigningProfile' :: SigningProfile -> Maybe SignatureValidityPeriod
$sel:profileVersionArn:SigningProfile' :: SigningProfile -> Maybe Text
$sel:profileVersion:SigningProfile' :: SigningProfile -> Maybe Text
$sel:profileName:SigningProfile' :: SigningProfile -> Maybe Text
$sel:platformId:SigningProfile' :: SigningProfile -> Maybe Text
$sel:platformDisplayName:SigningProfile' :: SigningProfile -> Maybe Text
$sel:arn:SigningProfile' :: SigningProfile -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
platformDisplayName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
platformId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
profileName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
profileVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
profileVersionArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SignatureValidityPeriod
signatureValidityPeriod
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SigningMaterial
signingMaterial
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
signingParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SigningProfileStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags