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

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.LexV2Models.DescribeBot
import Amazonka.LexV2Models.DescribeBotAlias
import Amazonka.LexV2Models.DescribeBotLocale
import Amazonka.LexV2Models.DescribeBotVersion
import Amazonka.LexV2Models.DescribeExport
import Amazonka.LexV2Models.DescribeImport
import Amazonka.LexV2Models.Lens
import Amazonka.LexV2Models.Types
import qualified Amazonka.Prelude as Prelude

-- | Polls 'Amazonka.LexV2Models.DescribeBotAlias' every 10 seconds until a successful state is reached. An error is returned after 35 failed checks.
newBotAliasAvailable :: Core.Wait DescribeBotAlias
newBotAliasAvailable :: Wait DescribeBotAlias
newBotAliasAvailable =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"BotAliasAvailable",
      $sel:attempts:Wait :: Int
Core.attempts = Int
35,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
10,
      $sel:acceptors:Wait :: [Acceptor DescribeBotAlias]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"Available"
            Accept
Core.AcceptSuccess
            ( Lens' DescribeBotAliasResponse (Maybe BotAliasStatus)
describeBotAliasResponse_botAliasStatus
                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
"Failed"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotAliasResponse (Maybe BotAliasStatus)
describeBotAliasResponse_botAliasStatus
                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
"Deleting"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotAliasResponse (Maybe BotAliasStatus)
describeBotAliasResponse_botAliasStatus
                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.LexV2Models.DescribeBot' every 10 seconds until a successful state is reached. An error is returned after 35 failed checks.
newBotAvailable :: Core.Wait DescribeBot
newBotAvailable :: Wait DescribeBot
newBotAvailable =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"BotAvailable",
      $sel:attempts:Wait :: Int
Core.attempts = Int
35,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
10,
      $sel:acceptors:Wait :: [Acceptor DescribeBot]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"Available"
            Accept
Core.AcceptSuccess
            ( Lens' DescribeBotResponse (Maybe BotStatus)
describeBotResponse_botStatus
                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
"Deleting"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotResponse (Maybe BotStatus)
describeBotResponse_botStatus
                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
"Failed"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotResponse (Maybe BotStatus)
describeBotResponse_botStatus
                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
"Inactive"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotResponse (Maybe BotStatus)
describeBotResponse_botStatus
                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.LexV2Models.DescribeExport' every 10 seconds until a successful state is reached. An error is returned after 35 failed checks.
newBotExportCompleted :: Core.Wait DescribeExport
newBotExportCompleted :: Wait DescribeExport
newBotExportCompleted =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"BotExportCompleted",
      $sel:attempts:Wait :: Int
Core.attempts = Int
35,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
10,
      $sel:acceptors:Wait :: [Acceptor DescribeExport]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"Completed"
            Accept
Core.AcceptSuccess
            ( Lens' DescribeExportResponse (Maybe ExportStatus)
describeExportResponse_exportStatus
                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
"Deleting"
            Accept
Core.AcceptFailure
            ( Lens' DescribeExportResponse (Maybe ExportStatus)
describeExportResponse_exportStatus
                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
"Failed"
            Accept
Core.AcceptFailure
            ( Lens' DescribeExportResponse (Maybe ExportStatus)
describeExportResponse_exportStatus
                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.LexV2Models.DescribeImport' every 10 seconds until a successful state is reached. An error is returned after 35 failed checks.
newBotImportCompleted :: Core.Wait DescribeImport
newBotImportCompleted :: Wait DescribeImport
newBotImportCompleted =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"BotImportCompleted",
      $sel:attempts:Wait :: Int
Core.attempts = Int
35,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
10,
      $sel:acceptors:Wait :: [Acceptor DescribeImport]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"Completed"
            Accept
Core.AcceptSuccess
            ( Lens' DescribeImportResponse (Maybe ImportStatus)
describeImportResponse_importStatus
                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
"Deleting"
            Accept
Core.AcceptFailure
            ( Lens' DescribeImportResponse (Maybe ImportStatus)
describeImportResponse_importStatus
                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
"Failed"
            Accept
Core.AcceptFailure
            ( Lens' DescribeImportResponse (Maybe ImportStatus)
describeImportResponse_importStatus
                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.LexV2Models.DescribeBotLocale' every 10 seconds until a successful state is reached. An error is returned after 35 failed checks.
newBotLocaleBuilt :: Core.Wait DescribeBotLocale
newBotLocaleBuilt :: Wait DescribeBotLocale
newBotLocaleBuilt =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"BotLocaleBuilt",
      $sel:attempts:Wait :: Int
Core.attempts = Int
35,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
10,
      $sel:acceptors:Wait :: [Acceptor DescribeBotLocale]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"Built"
            Accept
Core.AcceptSuccess
            ( Lens' DescribeBotLocaleResponse (Maybe BotLocaleStatus)
describeBotLocaleResponse_botLocaleStatus
                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
"Deleting"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotLocaleResponse (Maybe BotLocaleStatus)
describeBotLocaleResponse_botLocaleStatus
                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
"Failed"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotLocaleResponse (Maybe BotLocaleStatus)
describeBotLocaleResponse_botLocaleStatus
                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
"NotBuilt"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotLocaleResponse (Maybe BotLocaleStatus)
describeBotLocaleResponse_botLocaleStatus
                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.LexV2Models.DescribeBotLocale' every 10 seconds until a successful state is reached. An error is returned after 35 failed checks.
newBotLocaleCreated :: Core.Wait DescribeBotLocale
newBotLocaleCreated :: Wait DescribeBotLocale
newBotLocaleCreated =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"BotLocaleCreated",
      $sel:attempts:Wait :: Int
Core.attempts = Int
35,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
10,
      $sel:acceptors:Wait :: [Acceptor DescribeBotLocale]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"Built"
            Accept
Core.AcceptSuccess
            ( Lens' DescribeBotLocaleResponse (Maybe BotLocaleStatus)
describeBotLocaleResponse_botLocaleStatus
                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
"ReadyExpressTesting"
            Accept
Core.AcceptSuccess
            ( Lens' DescribeBotLocaleResponse (Maybe BotLocaleStatus)
describeBotLocaleResponse_botLocaleStatus
                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
"NotBuilt"
            Accept
Core.AcceptSuccess
            ( Lens' DescribeBotLocaleResponse (Maybe BotLocaleStatus)
describeBotLocaleResponse_botLocaleStatus
                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
"Deleting"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotLocaleResponse (Maybe BotLocaleStatus)
describeBotLocaleResponse_botLocaleStatus
                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
"Failed"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotLocaleResponse (Maybe BotLocaleStatus)
describeBotLocaleResponse_botLocaleStatus
                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.LexV2Models.DescribeBotLocale' every 10 seconds until a successful state is reached. An error is returned after 35 failed checks.
newBotLocaleExpressTestingAvailable :: Core.Wait DescribeBotLocale
newBotLocaleExpressTestingAvailable :: Wait DescribeBotLocale
newBotLocaleExpressTestingAvailable =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name =
        ByteString
"BotLocaleExpressTestingAvailable",
      $sel:attempts:Wait :: Int
Core.attempts = Int
35,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
10,
      $sel:acceptors:Wait :: [Acceptor DescribeBotLocale]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"Built"
            Accept
Core.AcceptSuccess
            ( Lens' DescribeBotLocaleResponse (Maybe BotLocaleStatus)
describeBotLocaleResponse_botLocaleStatus
                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
"ReadyExpressTesting"
            Accept
Core.AcceptSuccess
            ( Lens' DescribeBotLocaleResponse (Maybe BotLocaleStatus)
describeBotLocaleResponse_botLocaleStatus
                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
"Deleting"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotLocaleResponse (Maybe BotLocaleStatus)
describeBotLocaleResponse_botLocaleStatus
                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
"Failed"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotLocaleResponse (Maybe BotLocaleStatus)
describeBotLocaleResponse_botLocaleStatus
                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
"NotBuilt"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotLocaleResponse (Maybe BotLocaleStatus)
describeBotLocaleResponse_botLocaleStatus
                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.LexV2Models.DescribeBotVersion' every 10 seconds until a successful state is reached. An error is returned after 35 failed checks.
newBotVersionAvailable :: Core.Wait DescribeBotVersion
newBotVersionAvailable :: Wait DescribeBotVersion
newBotVersionAvailable =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"BotVersionAvailable",
      $sel:attempts:Wait :: Int
Core.attempts = Int
35,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
10,
      $sel:acceptors:Wait :: [Acceptor DescribeBotVersion]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"Available"
            Accept
Core.AcceptSuccess
            ( Lens' DescribeBotVersionResponse (Maybe BotStatus)
describeBotVersionResponse_botStatus
                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
"Deleting"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotVersionResponse (Maybe BotStatus)
describeBotVersionResponse_botStatus
                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
"Failed"
            Accept
Core.AcceptFailure
            ( Lens' DescribeBotVersionResponse (Maybe BotStatus)
describeBotVersionResponse_botStatus
                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. Int -> Accept -> Acceptor a
Core.matchStatus Int
404 Accept
Core.AcceptRetry
        ]
    }