{-# LANGUAGE DisambiguateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.CertificateManager.Waiters
-- 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.CertificateManager.Waiters where

import Amazonka.CertificateManager.DescribeCertificate
import Amazonka.CertificateManager.Lens
import Amazonka.CertificateManager.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

-- | Polls 'Amazonka.CertificateManager.DescribeCertificate' every 60 seconds until a successful state is reached. An error is returned after 40 failed checks.
newCertificateValidated :: Core.Wait DescribeCertificate
newCertificateValidated :: Wait DescribeCertificate
newCertificateValidated =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"CertificateValidated",
      $sel:attempts:Wait :: Int
Core.attempts = Int
40,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
60,
      $sel:acceptors:Wait :: [Acceptor DescribeCertificate]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"SUCCESS"
            Accept
Core.AcceptSuccess
            ( Lens' DescribeCertificateResponse (Maybe CertificateDetail)
describeCertificateResponse_certificate
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                  ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                      ( Lens' CertificateDetail (Maybe (NonEmpty DomainValidation))
certificateDetail_domainValidationOptions
                          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
                          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
Lens.to forall l. IsList l => l -> [Item l]
Prelude.toList
                      )
                  )
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' DomainValidation (Maybe DomainStatus)
domainValidation_validationStatus
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
Lens.to forall a. ToText a => a -> CI Text
Data.toTextCI
            ),
          forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAny
            CI Text
"PENDING_VALIDATION"
            Accept
Core.AcceptRetry
            ( Lens' DescribeCertificateResponse (Maybe CertificateDetail)
describeCertificateResponse_certificate
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                  ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                      ( Lens' CertificateDetail (Maybe (NonEmpty DomainValidation))
certificateDetail_domainValidationOptions
                          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
                          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
Lens.to forall l. IsList l => l -> [Item l]
Prelude.toList
                      )
                  )
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' DomainValidation (Maybe DomainStatus)
domainValidation_validationStatus
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
Lens.to forall a. ToText a => a -> CI Text
Data.toTextCI
            ),
          forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"FAILED"
            Accept
Core.AcceptFailure
            ( Lens' DescribeCertificateResponse (Maybe CertificateDetail)
describeCertificateResponse_certificate
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' CertificateDetail (Maybe CertificateStatus)
certificateDetail_status
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
Lens.to forall a. ToText a => a -> CI Text
Data.toTextCI
            ),
          forall a. ErrorCode -> Accept -> Acceptor a
Core.matchError
            ErrorCode
"ResourceNotFoundException"
            Accept
Core.AcceptFailure
        ]
    }