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

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Nimble.GetLaunchProfile
import Amazonka.Nimble.GetStreamingImage
import Amazonka.Nimble.GetStreamingSession
import Amazonka.Nimble.GetStreamingSessionStream
import Amazonka.Nimble.GetStudio
import Amazonka.Nimble.GetStudioComponent
import Amazonka.Nimble.Lens
import Amazonka.Nimble.Types
import qualified Amazonka.Prelude as Prelude

-- | Polls 'Amazonka.Nimble.GetLaunchProfile' every 5 seconds until a successful state is reached. An error is returned after 150 failed checks.
newLaunchProfileDeleted :: Core.Wait GetLaunchProfile
newLaunchProfileDeleted :: Wait GetLaunchProfile
newLaunchProfileDeleted =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"LaunchProfileDeleted",
      $sel:attempts:Wait :: Int
Core.attempts = Int
150,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
5,
      $sel:acceptors:Wait :: [Acceptor GetLaunchProfile]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"DELETED"
            Accept
Core.AcceptSuccess
            ( Lens' GetLaunchProfileResponse (Maybe LaunchProfile)
getLaunchProfileResponse_launchProfile
                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' LaunchProfile (Maybe LaunchProfileState)
launchProfile_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"DELETE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetLaunchProfileResponse (Maybe LaunchProfile)
getLaunchProfileResponse_launchProfile
                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' LaunchProfile (Maybe LaunchProfileState)
launchProfile_state
                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
            )
        ]
    }

-- | Polls 'Amazonka.Nimble.GetLaunchProfile' every 5 seconds until a successful state is reached. An error is returned after 150 failed checks.
newLaunchProfileReady :: Core.Wait GetLaunchProfile
newLaunchProfileReady :: Wait GetLaunchProfile
newLaunchProfileReady =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"LaunchProfileReady",
      $sel:attempts:Wait :: Int
Core.attempts = Int
150,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
5,
      $sel:acceptors:Wait :: [Acceptor GetLaunchProfile]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"READY"
            Accept
Core.AcceptSuccess
            ( Lens' GetLaunchProfileResponse (Maybe LaunchProfile)
getLaunchProfileResponse_launchProfile
                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' LaunchProfile (Maybe LaunchProfileState)
launchProfile_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"CREATE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetLaunchProfileResponse (Maybe LaunchProfile)
getLaunchProfileResponse_launchProfile
                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' LaunchProfile (Maybe LaunchProfileState)
launchProfile_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"UPDATE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetLaunchProfileResponse (Maybe LaunchProfile)
getLaunchProfileResponse_launchProfile
                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' LaunchProfile (Maybe LaunchProfileState)
launchProfile_state
                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
            )
        ]
    }

-- | Polls 'Amazonka.Nimble.GetStreamingImage' every 2 seconds until a successful state is reached. An error is returned after 60 failed checks.
newStreamingImageDeleted :: Core.Wait GetStreamingImage
newStreamingImageDeleted :: Wait GetStreamingImage
newStreamingImageDeleted =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"StreamingImageDeleted",
      $sel:attempts:Wait :: Int
Core.attempts = Int
60,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
2,
      $sel:acceptors:Wait :: [Acceptor GetStreamingImage]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"DELETED"
            Accept
Core.AcceptSuccess
            ( Lens' GetStreamingImageResponse (Maybe StreamingImage)
getStreamingImageResponse_streamingImage
                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' StreamingImage (Maybe StreamingImageState)
streamingImage_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"DELETE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetStreamingImageResponse (Maybe StreamingImage)
getStreamingImageResponse_streamingImage
                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' StreamingImage (Maybe StreamingImageState)
streamingImage_state
                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
            )
        ]
    }

-- | Polls 'Amazonka.Nimble.GetStreamingImage' every 2 seconds until a successful state is reached. An error is returned after 60 failed checks.
newStreamingImageReady :: Core.Wait GetStreamingImage
newStreamingImageReady :: Wait GetStreamingImage
newStreamingImageReady =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"StreamingImageReady",
      $sel:attempts:Wait :: Int
Core.attempts = Int
60,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
2,
      $sel:acceptors:Wait :: [Acceptor GetStreamingImage]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"READY"
            Accept
Core.AcceptSuccess
            ( Lens' GetStreamingImageResponse (Maybe StreamingImage)
getStreamingImageResponse_streamingImage
                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' StreamingImage (Maybe StreamingImageState)
streamingImage_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"CREATE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetStreamingImageResponse (Maybe StreamingImage)
getStreamingImageResponse_streamingImage
                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' StreamingImage (Maybe StreamingImageState)
streamingImage_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"UPDATE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetStreamingImageResponse (Maybe StreamingImage)
getStreamingImageResponse_streamingImage
                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' StreamingImage (Maybe StreamingImageState)
streamingImage_state
                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
            )
        ]
    }

-- | Polls 'Amazonka.Nimble.GetStreamingSession' every 5 seconds until a successful state is reached. An error is returned after 180 failed checks.
newStreamingSessionDeleted :: Core.Wait GetStreamingSession
newStreamingSessionDeleted :: Wait GetStreamingSession
newStreamingSessionDeleted =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"StreamingSessionDeleted",
      $sel:attempts:Wait :: Int
Core.attempts = Int
180,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
5,
      $sel:acceptors:Wait :: [Acceptor GetStreamingSession]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"DELETED"
            Accept
Core.AcceptSuccess
            ( Lens' GetStreamingSessionResponse (Maybe StreamingSession)
getStreamingSessionResponse_session
                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' StreamingSession (Maybe StreamingSessionState)
streamingSession_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"DELETE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetStreamingSessionResponse (Maybe StreamingSession)
getStreamingSessionResponse_session
                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' StreamingSession (Maybe StreamingSessionState)
streamingSession_state
                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
            )
        ]
    }

-- | Polls 'Amazonka.Nimble.GetStreamingSession' every 10 seconds until a successful state is reached. An error is returned after 180 failed checks.
newStreamingSessionReady :: Core.Wait GetStreamingSession
newStreamingSessionReady :: Wait GetStreamingSession
newStreamingSessionReady =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"StreamingSessionReady",
      $sel:attempts:Wait :: Int
Core.attempts = Int
180,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
10,
      $sel:acceptors:Wait :: [Acceptor GetStreamingSession]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"READY"
            Accept
Core.AcceptSuccess
            ( Lens' GetStreamingSessionResponse (Maybe StreamingSession)
getStreamingSessionResponse_session
                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' StreamingSession (Maybe StreamingSessionState)
streamingSession_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"CREATE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetStreamingSessionResponse (Maybe StreamingSession)
getStreamingSessionResponse_session
                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' StreamingSession (Maybe StreamingSessionState)
streamingSession_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"START_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetStreamingSessionResponse (Maybe StreamingSession)
getStreamingSessionResponse_session
                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' StreamingSession (Maybe StreamingSessionState)
streamingSession_state
                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
            )
        ]
    }

-- | Polls 'Amazonka.Nimble.GetStreamingSession' every 5 seconds until a successful state is reached. An error is returned after 180 failed checks.
newStreamingSessionStopped :: Core.Wait GetStreamingSession
newStreamingSessionStopped :: Wait GetStreamingSession
newStreamingSessionStopped =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"StreamingSessionStopped",
      $sel:attempts:Wait :: Int
Core.attempts = Int
180,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
5,
      $sel:acceptors:Wait :: [Acceptor GetStreamingSession]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"STOPPED"
            Accept
Core.AcceptSuccess
            ( Lens' GetStreamingSessionResponse (Maybe StreamingSession)
getStreamingSessionResponse_session
                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' StreamingSession (Maybe StreamingSessionState)
streamingSession_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"STOP_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetStreamingSessionResponse (Maybe StreamingSession)
getStreamingSessionResponse_session
                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' StreamingSession (Maybe StreamingSessionState)
streamingSession_state
                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
            )
        ]
    }

-- | Polls 'Amazonka.Nimble.GetStreamingSessionStream' every 5 seconds until a successful state is reached. An error is returned after 30 failed checks.
newStreamingSessionStreamReady :: Core.Wait GetStreamingSessionStream
newStreamingSessionStreamReady :: Wait GetStreamingSessionStream
newStreamingSessionStreamReady =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name =
        ByteString
"StreamingSessionStreamReady",
      $sel:attempts:Wait :: Int
Core.attempts = Int
30,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
5,
      $sel:acceptors:Wait :: [Acceptor GetStreamingSessionStream]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"READY"
            Accept
Core.AcceptSuccess
            ( Lens'
  GetStreamingSessionStreamResponse (Maybe StreamingSessionStream)
getStreamingSessionStreamResponse_stream
                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' StreamingSessionStream (Maybe StreamingSessionStreamState)
streamingSessionStream_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"CREATE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens'
  GetStreamingSessionStreamResponse (Maybe StreamingSessionStream)
getStreamingSessionStreamResponse_stream
                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' StreamingSessionStream (Maybe StreamingSessionStreamState)
streamingSessionStream_state
                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
            )
        ]
    }

-- | Polls 'Amazonka.Nimble.GetStudioComponent' every 1 seconds until a successful state is reached. An error is returned after 120 failed checks.
newStudioComponentDeleted :: Core.Wait GetStudioComponent
newStudioComponentDeleted :: Wait GetStudioComponent
newStudioComponentDeleted =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"StudioComponentDeleted",
      $sel:attempts:Wait :: Int
Core.attempts = Int
120,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
1,
      $sel:acceptors:Wait :: [Acceptor GetStudioComponent]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"DELETED"
            Accept
Core.AcceptSuccess
            ( Lens' GetStudioComponentResponse (Maybe StudioComponent)
getStudioComponentResponse_studioComponent
                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' StudioComponent (Maybe StudioComponentState)
studioComponent_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"DELETE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetStudioComponentResponse (Maybe StudioComponent)
getStudioComponentResponse_studioComponent
                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' StudioComponent (Maybe StudioComponentState)
studioComponent_state
                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
            )
        ]
    }

-- | Polls 'Amazonka.Nimble.GetStudioComponent' every 2 seconds until a successful state is reached. An error is returned after 60 failed checks.
newStudioComponentReady :: Core.Wait GetStudioComponent
newStudioComponentReady :: Wait GetStudioComponent
newStudioComponentReady =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"StudioComponentReady",
      $sel:attempts:Wait :: Int
Core.attempts = Int
60,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
2,
      $sel:acceptors:Wait :: [Acceptor GetStudioComponent]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"READY"
            Accept
Core.AcceptSuccess
            ( Lens' GetStudioComponentResponse (Maybe StudioComponent)
getStudioComponentResponse_studioComponent
                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' StudioComponent (Maybe StudioComponentState)
studioComponent_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"CREATE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetStudioComponentResponse (Maybe StudioComponent)
getStudioComponentResponse_studioComponent
                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' StudioComponent (Maybe StudioComponentState)
studioComponent_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"UPDATE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetStudioComponentResponse (Maybe StudioComponent)
getStudioComponentResponse_studioComponent
                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' StudioComponent (Maybe StudioComponentState)
studioComponent_state
                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
            )
        ]
    }

-- | Polls 'Amazonka.Nimble.GetStudio' every 2 seconds until a successful state is reached. An error is returned after 60 failed checks.
newStudioDeleted :: Core.Wait GetStudio
newStudioDeleted :: Wait GetStudio
newStudioDeleted =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"StudioDeleted",
      $sel:attempts:Wait :: Int
Core.attempts = Int
60,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
2,
      $sel:acceptors:Wait :: [Acceptor GetStudio]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"DELETED"
            Accept
Core.AcceptSuccess
            ( Lens' GetStudioResponse Studio
getStudioResponse_studio
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' Studio (Maybe StudioState)
studio_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"DELETE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetStudioResponse Studio
getStudioResponse_studio
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' Studio (Maybe StudioState)
studio_state
                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
            )
        ]
    }

-- | Polls 'Amazonka.Nimble.GetStudio' every 2 seconds until a successful state is reached. An error is returned after 60 failed checks.
newStudioReady :: Core.Wait GetStudio
newStudioReady :: Wait GetStudio
newStudioReady =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"StudioReady",
      $sel:attempts:Wait :: Int
Core.attempts = Int
60,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
2,
      $sel:acceptors:Wait :: [Acceptor GetStudio]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"READY"
            Accept
Core.AcceptSuccess
            ( Lens' GetStudioResponse Studio
getStudioResponse_studio
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' Studio (Maybe StudioState)
studio_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"CREATE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetStudioResponse Studio
getStudioResponse_studio
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' Studio (Maybe StudioState)
studio_state
                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 b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"UPDATE_FAILED"
            Accept
Core.AcceptFailure
            ( Lens' GetStudioResponse Studio
getStudioResponse_studio
                forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' Studio (Maybe StudioState)
studio_state
                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
            )
        ]
    }