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

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Glacier.DescribeVault
import Amazonka.Glacier.Lens
import Amazonka.Glacier.Types
import qualified Amazonka.Prelude as Prelude

-- | Polls 'Amazonka.Glacier.DescribeVault' every 3 seconds until a successful state is reached. An error is returned after 15 failed checks.
newVaultExists :: Core.Wait DescribeVault
newVaultExists :: Wait DescribeVault
newVaultExists =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"VaultExists",
      $sel:attempts:Wait :: Int
Core.attempts = Int
15,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
3,
      $sel:acceptors:Wait :: [Acceptor DescribeVault]
Core.acceptors =
        [ forall a. Int -> Accept -> Acceptor a
Core.matchStatus Int
200 Accept
Core.AcceptSuccess,
          forall a. ErrorCode -> Accept -> Acceptor a
Core.matchError
            ErrorCode
"ResourceNotFoundException"
            Accept
Core.AcceptRetry
        ]
    }

-- | Polls 'Amazonka.Glacier.DescribeVault' every 3 seconds until a successful state is reached. An error is returned after 15 failed checks.
newVaultNotExists :: Core.Wait DescribeVault
newVaultNotExists :: Wait DescribeVault
newVaultNotExists =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"VaultNotExists",
      $sel:attempts:Wait :: Int
Core.attempts = Int
15,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
3,
      $sel:acceptors:Wait :: [Acceptor DescribeVault]
Core.acceptors =
        [ forall a. Int -> Accept -> Acceptor a
Core.matchStatus Int
200 Accept
Core.AcceptRetry,
          forall a. ErrorCode -> Accept -> Acceptor a
Core.matchError
            ErrorCode
"ResourceNotFoundException"
            Accept
Core.AcceptSuccess
        ]
    }