{-# 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.SSMIncidents.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.SSMIncidents.Waiters 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.SSMIncidents.GetReplicationSet
import Amazonka.SSMIncidents.Lens
import Amazonka.SSMIncidents.Types

-- | Polls 'Amazonka.SSMIncidents.GetReplicationSet' every 30 seconds until a successful state is reached. An error is returned after 5 failed checks.
newWaitForReplicationSetActive :: Core.Wait GetReplicationSet
newWaitForReplicationSetActive :: Wait GetReplicationSet
newWaitForReplicationSetActive =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name =
        ByteString
"WaitForReplicationSetActive",
      $sel:attempts:Wait :: Int
Core.attempts = Int
5,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
30,
      $sel:acceptors:Wait :: [Acceptor GetReplicationSet]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"ACTIVE"
            Accept
Core.AcceptSuccess
            ( Lens' GetReplicationSetResponse ReplicationSet
getReplicationSetResponse_replicationSet
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' ReplicationSet ReplicationSetStatus
replicationSet_status
                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
"CREATING"
            Accept
Core.AcceptRetry
            ( Lens' GetReplicationSetResponse ReplicationSet
getReplicationSetResponse_replicationSet
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' ReplicationSet ReplicationSetStatus
replicationSet_status
                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
"UPDATING"
            Accept
Core.AcceptRetry
            ( Lens' GetReplicationSetResponse ReplicationSet
getReplicationSetResponse_replicationSet
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' ReplicationSet ReplicationSetStatus
replicationSet_status
                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' GetReplicationSetResponse ReplicationSet
getReplicationSetResponse_replicationSet
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' ReplicationSet ReplicationSetStatus
replicationSet_status
                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
            )
        ]
    }

-- | Polls 'Amazonka.SSMIncidents.GetReplicationSet' every 30 seconds until a successful state is reached. An error is returned after 5 failed checks.
newWaitForReplicationSetDeleted :: Core.Wait GetReplicationSet
newWaitForReplicationSetDeleted :: Wait GetReplicationSet
newWaitForReplicationSetDeleted =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name =
        ByteString
"WaitForReplicationSetDeleted",
      $sel:attempts:Wait :: Int
Core.attempts = Int
5,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
30,
      $sel:acceptors:Wait :: [Acceptor GetReplicationSet]
Core.acceptors =
        [ forall a. ErrorCode -> Accept -> Acceptor a
Core.matchError
            ErrorCode
"ResourceNotFoundException"
            Accept
Core.AcceptSuccess,
          forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"DELETING"
            Accept
Core.AcceptRetry
            ( Lens' GetReplicationSetResponse ReplicationSet
getReplicationSetResponse_replicationSet
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' ReplicationSet ReplicationSetStatus
replicationSet_status
                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' GetReplicationSetResponse ReplicationSet
getReplicationSetResponse_replicationSet
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' ReplicationSet ReplicationSetStatus
replicationSet_status
                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
            )
        ]
    }