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

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Kinesis.DescribeStream
import Amazonka.Kinesis.Lens
import Amazonka.Kinesis.Types
import qualified Amazonka.Prelude as Prelude

-- | Polls 'Amazonka.Kinesis.DescribeStream' every 10 seconds until a successful state is reached. An error is returned after 18 failed checks.
newStreamExists :: Core.Wait DescribeStream
newStreamExists :: Wait DescribeStream
newStreamExists =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"StreamExists",
      $sel:attempts:Wait :: Int
Core.attempts = Int
18,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
10,
      $sel:acceptors:Wait :: [Acceptor DescribeStream]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"ACTIVE"
            Accept
Core.AcceptSuccess
            ( Lens' DescribeStreamResponse StreamDescription
describeStreamResponse_streamDescription
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' StreamDescription StreamStatus
streamDescription_streamStatus
                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.Kinesis.DescribeStream' every 10 seconds until a successful state is reached. An error is returned after 18 failed checks.
newStreamNotExists :: Core.Wait DescribeStream
newStreamNotExists :: Wait DescribeStream
newStreamNotExists =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"StreamNotExists",
      $sel:attempts:Wait :: Int
Core.attempts = Int
18,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
10,
      $sel:acceptors:Wait :: [Acceptor DescribeStream]
Core.acceptors =
        [ forall a. ErrorCode -> Accept -> Acceptor a
Core.matchError
            ErrorCode
"ResourceNotFoundException"
            Accept
Core.AcceptSuccess
        ]
    }