{-# 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.DynamoDB.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.DynamoDB.Waiters where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DynamoDB.DescribeTable
import Amazonka.DynamoDB.Lens
import Amazonka.DynamoDB.Types
import qualified Amazonka.Prelude as Prelude

-- | Polls 'Amazonka.DynamoDB.DescribeTable' every 20 seconds until a successful state is reached. An error is returned after 25 failed checks.
newTableExists :: Core.Wait DescribeTable
newTableExists :: Wait DescribeTable
newTableExists =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"TableExists",
      $sel:attempts:Wait :: Int
Core.attempts = Int
25,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
20,
      $sel:acceptors:Wait :: [Acceptor DescribeTable]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"ACTIVE"
            Accept
Core.AcceptSuccess
            ( Lens' DescribeTableResponse (Maybe TableDescription)
describeTableResponse_table
                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' TableDescription (Maybe TableStatus)
tableDescription_tableStatus
                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.AcceptRetry
        ]
    }

-- | Polls 'Amazonka.DynamoDB.DescribeTable' every 20 seconds until a successful state is reached. An error is returned after 25 failed checks.
newTableNotExists :: Core.Wait DescribeTable
newTableNotExists :: Wait DescribeTable
newTableNotExists =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"TableNotExists",
      $sel:attempts:Wait :: Int
Core.attempts = Int
25,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
20,
      $sel:acceptors:Wait :: [Acceptor DescribeTable]
Core.acceptors =
        [ forall a. ErrorCode -> Accept -> Acceptor a
Core.matchError
            ErrorCode
"ResourceNotFoundException"
            Accept
Core.AcceptSuccess
        ]
    }