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

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IAM.GetInstanceProfile
import Amazonka.IAM.GetPolicy
import Amazonka.IAM.GetRole
import Amazonka.IAM.GetUser
import Amazonka.IAM.Lens
import Amazonka.IAM.Types
import qualified Amazonka.Prelude as Prelude

-- | Polls 'Amazonka.IAM.GetInstanceProfile' every 1 seconds until a successful state is reached. An error is returned after 40 failed checks.
newInstanceProfileExists :: Core.Wait GetInstanceProfile
newInstanceProfileExists :: Wait GetInstanceProfile
newInstanceProfileExists =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"InstanceProfileExists",
      $sel:attempts:Wait :: Int
Core.attempts = Int
40,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
1,
      $sel:acceptors:Wait :: [Acceptor GetInstanceProfile]
Core.acceptors =
        [ forall a. Int -> Accept -> Acceptor a
Core.matchStatus Int
200 Accept
Core.AcceptSuccess,
          forall a. Int -> Accept -> Acceptor a
Core.matchStatus Int
404 Accept
Core.AcceptRetry
        ]
    }

-- | Polls 'Amazonka.IAM.GetPolicy' every 1 seconds until a successful state is reached. An error is returned after 20 failed checks.
newPolicyExists :: Core.Wait GetPolicy
newPolicyExists :: Wait GetPolicy
newPolicyExists =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"PolicyExists",
      $sel:attempts:Wait :: Int
Core.attempts = Int
20,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
1,
      $sel:acceptors:Wait :: [Acceptor GetPolicy]
Core.acceptors =
        [ forall a. Int -> Accept -> Acceptor a
Core.matchStatus Int
200 Accept
Core.AcceptSuccess,
          forall a. ErrorCode -> Accept -> Acceptor a
Core.matchError ErrorCode
"NoSuchEntity" Accept
Core.AcceptRetry
        ]
    }

-- | Polls 'Amazonka.IAM.GetRole' every 1 seconds until a successful state is reached. An error is returned after 20 failed checks.
newRoleExists :: Core.Wait GetRole
newRoleExists :: Wait GetRole
newRoleExists =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"RoleExists",
      $sel:attempts:Wait :: Int
Core.attempts = Int
20,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
1,
      $sel:acceptors:Wait :: [Acceptor GetRole]
Core.acceptors =
        [ forall a. Int -> Accept -> Acceptor a
Core.matchStatus Int
200 Accept
Core.AcceptSuccess,
          forall a. ErrorCode -> Accept -> Acceptor a
Core.matchError ErrorCode
"NoSuchEntity" Accept
Core.AcceptRetry
        ]
    }

-- | Polls 'Amazonka.IAM.GetUser' every 1 seconds until a successful state is reached. An error is returned after 20 failed checks.
newUserExists :: Core.Wait GetUser
newUserExists :: Wait GetUser
newUserExists =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"UserExists",
      $sel:attempts:Wait :: Int
Core.attempts = Int
20,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
1,
      $sel:acceptors:Wait :: [Acceptor GetUser]
Core.acceptors =
        [ forall a. Int -> Accept -> Acceptor a
Core.matchStatus Int
200 Accept
Core.AcceptSuccess,
          forall a. ErrorCode -> Accept -> Acceptor a
Core.matchError ErrorCode
"NoSuchEntity" Accept
Core.AcceptRetry
        ]
    }