{-# 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.ELB.Waiters
-- Copyright   : (c) 2013-2021 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay <brendan.g.hay+amazonka@gmail.com>
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.ELB.Waiters where

import qualified Amazonka.Core as Core
import Amazonka.ELB.DescribeInstanceHealth
import Amazonka.ELB.Lens
import Amazonka.ELB.Types
import qualified Amazonka.Lens as Lens
import qualified Amazonka.Prelude as Prelude

-- | Polls 'Amazonka.ELB.DescribeInstanceHealth' every 15 seconds until a successful state is reached. An error is returned after 40 failed checks.
newAnyInstanceInService :: Core.Wait DescribeInstanceHealth
newAnyInstanceInService :: Wait DescribeInstanceHealth
newAnyInstanceInService =
  Wait :: forall a. ByteString -> Int -> Seconds -> [Acceptor a] -> Wait a
Core.Wait
    { $sel:_waitName:Wait :: ByteString
Core._waitName = ByteString
"AnyInstanceInService",
      $sel:_waitAttempts:Wait :: Int
Core._waitAttempts = Int
40,
      $sel:_waitDelay:Wait :: Seconds
Core._waitDelay = Seconds
15,
      $sel:_waitAcceptors:Wait :: [Acceptor DescribeInstanceHealth]
Core._waitAcceptors =
        [ CI Text
-> Accept
-> Fold (AWSResponse DescribeInstanceHealth) (CI Text)
-> Acceptor DescribeInstanceHealth
forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAny
            CI Text
"InService"
            Accept
Core.AcceptSuccess
            ( (DescribeInstanceHealthResponse -> [InstanceState])
-> Fold DescribeInstanceHealthResponse InstanceState
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( Getting
  [InstanceState] DescribeInstanceHealthResponse [InstanceState]
-> DescribeInstanceHealthResponse -> [InstanceState]
forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( (Maybe [InstanceState]
 -> Const [InstanceState] (Maybe [InstanceState]))
-> DescribeInstanceHealthResponse
-> Const [InstanceState] DescribeInstanceHealthResponse
Lens' DescribeInstanceHealthResponse (Maybe [InstanceState])
describeInstanceHealthResponse_instanceStates
                        ((Maybe [InstanceState]
  -> Const [InstanceState] (Maybe [InstanceState]))
 -> DescribeInstanceHealthResponse
 -> Const [InstanceState] DescribeInstanceHealthResponse)
-> (([InstanceState] -> Const [InstanceState] [InstanceState])
    -> Maybe [InstanceState]
    -> Const [InstanceState] (Maybe [InstanceState]))
-> Getting
     [InstanceState] DescribeInstanceHealthResponse [InstanceState]
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. ([InstanceState] -> Const [InstanceState] [InstanceState])
-> Maybe [InstanceState]
-> Const [InstanceState] (Maybe [InstanceState])
forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
                    )
                )
                ((InstanceState -> f InstanceState)
 -> DescribeInstanceHealthResponse
 -> f DescribeInstanceHealthResponse)
-> ((CI Text -> f (CI Text)) -> InstanceState -> f InstanceState)
-> (CI Text -> f (CI Text))
-> DescribeInstanceHealthResponse
-> f DescribeInstanceHealthResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. (Maybe Text -> f (Maybe Text)) -> InstanceState -> f InstanceState
Lens' InstanceState (Maybe Text)
instanceState_state
                ((Maybe Text -> f (Maybe Text))
 -> InstanceState -> f InstanceState)
-> ((CI Text -> f (CI Text)) -> Maybe Text -> f (Maybe Text))
-> (CI Text -> f (CI Text))
-> InstanceState
-> f InstanceState
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. (Text -> f Text) -> Maybe Text -> f (Maybe Text)
forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
                ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> ((CI Text -> f (CI Text)) -> Text -> f Text)
-> (CI Text -> f (CI Text))
-> Maybe Text
-> f (Maybe Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. (Text -> CI Text) -> (CI Text -> f (CI Text)) -> Text -> f Text
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
Lens.to Text -> CI Text
forall a. ToText a => a -> CI Text
Core.toTextCI
            )
        ]
    }

-- | Polls 'Amazonka.ELB.DescribeInstanceHealth' every 15 seconds until a successful state is reached. An error is returned after 40 failed checks.
newInstanceDeregistered :: Core.Wait DescribeInstanceHealth
newInstanceDeregistered :: Wait DescribeInstanceHealth
newInstanceDeregistered =
  Wait :: forall a. ByteString -> Int -> Seconds -> [Acceptor a] -> Wait a
Core.Wait
    { $sel:_waitName:Wait :: ByteString
Core._waitName = ByteString
"InstanceDeregistered",
      $sel:_waitAttempts:Wait :: Int
Core._waitAttempts = Int
40,
      $sel:_waitDelay:Wait :: Seconds
Core._waitDelay = Seconds
15,
      $sel:_waitAcceptors:Wait :: [Acceptor DescribeInstanceHealth]
Core._waitAcceptors =
        [ CI Text
-> Accept
-> Fold (AWSResponse DescribeInstanceHealth) (CI Text)
-> Acceptor DescribeInstanceHealth
forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"OutOfService"
            Accept
Core.AcceptSuccess
            ( (DescribeInstanceHealthResponse -> [InstanceState])
-> Fold DescribeInstanceHealthResponse InstanceState
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( Getting
  [InstanceState] DescribeInstanceHealthResponse [InstanceState]
-> DescribeInstanceHealthResponse -> [InstanceState]
forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( (Maybe [InstanceState]
 -> Const [InstanceState] (Maybe [InstanceState]))
-> DescribeInstanceHealthResponse
-> Const [InstanceState] DescribeInstanceHealthResponse
Lens' DescribeInstanceHealthResponse (Maybe [InstanceState])
describeInstanceHealthResponse_instanceStates
                        ((Maybe [InstanceState]
  -> Const [InstanceState] (Maybe [InstanceState]))
 -> DescribeInstanceHealthResponse
 -> Const [InstanceState] DescribeInstanceHealthResponse)
-> (([InstanceState] -> Const [InstanceState] [InstanceState])
    -> Maybe [InstanceState]
    -> Const [InstanceState] (Maybe [InstanceState]))
-> Getting
     [InstanceState] DescribeInstanceHealthResponse [InstanceState]
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. ([InstanceState] -> Const [InstanceState] [InstanceState])
-> Maybe [InstanceState]
-> Const [InstanceState] (Maybe [InstanceState])
forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
                    )
                )
                ((InstanceState -> f InstanceState)
 -> DescribeInstanceHealthResponse
 -> f DescribeInstanceHealthResponse)
-> ((CI Text -> f (CI Text)) -> InstanceState -> f InstanceState)
-> (CI Text -> f (CI Text))
-> DescribeInstanceHealthResponse
-> f DescribeInstanceHealthResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. (Maybe Text -> f (Maybe Text)) -> InstanceState -> f InstanceState
Lens' InstanceState (Maybe Text)
instanceState_state
                ((Maybe Text -> f (Maybe Text))
 -> InstanceState -> f InstanceState)
-> ((CI Text -> f (CI Text)) -> Maybe Text -> f (Maybe Text))
-> (CI Text -> f (CI Text))
-> InstanceState
-> f InstanceState
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. (Text -> f Text) -> Maybe Text -> f (Maybe Text)
forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
                ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> ((CI Text -> f (CI Text)) -> Text -> f Text)
-> (CI Text -> f (CI Text))
-> Maybe Text
-> f (Maybe Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. (Text -> CI Text) -> (CI Text -> f (CI Text)) -> Text -> f Text
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
Lens.to Text -> CI Text
forall a. ToText a => a -> CI Text
Core.toTextCI
            ),
          ErrorCode -> Accept -> Acceptor DescribeInstanceHealth
forall a. ErrorCode -> Accept -> Acceptor a
Core.matchError
            ErrorCode
"InvalidInstance"
            Accept
Core.AcceptSuccess
        ]
    }

-- | Polls 'Amazonka.ELB.DescribeInstanceHealth' every 15 seconds until a successful state is reached. An error is returned after 40 failed checks.
newInstanceInService :: Core.Wait DescribeInstanceHealth
newInstanceInService :: Wait DescribeInstanceHealth
newInstanceInService =
  Wait :: forall a. ByteString -> Int -> Seconds -> [Acceptor a] -> Wait a
Core.Wait
    { $sel:_waitName:Wait :: ByteString
Core._waitName = ByteString
"InstanceInService",
      $sel:_waitAttempts:Wait :: Int
Core._waitAttempts = Int
40,
      $sel:_waitDelay:Wait :: Seconds
Core._waitDelay = Seconds
15,
      $sel:_waitAcceptors:Wait :: [Acceptor DescribeInstanceHealth]
Core._waitAcceptors =
        [ CI Text
-> Accept
-> Fold (AWSResponse DescribeInstanceHealth) (CI Text)
-> Acceptor DescribeInstanceHealth
forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"InService"
            Accept
Core.AcceptSuccess
            ( (DescribeInstanceHealthResponse -> [InstanceState])
-> Fold DescribeInstanceHealthResponse InstanceState
forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( Getting
  [InstanceState] DescribeInstanceHealthResponse [InstanceState]
-> DescribeInstanceHealthResponse -> [InstanceState]
forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( (Maybe [InstanceState]
 -> Const [InstanceState] (Maybe [InstanceState]))
-> DescribeInstanceHealthResponse
-> Const [InstanceState] DescribeInstanceHealthResponse
Lens' DescribeInstanceHealthResponse (Maybe [InstanceState])
describeInstanceHealthResponse_instanceStates
                        ((Maybe [InstanceState]
  -> Const [InstanceState] (Maybe [InstanceState]))
 -> DescribeInstanceHealthResponse
 -> Const [InstanceState] DescribeInstanceHealthResponse)
-> (([InstanceState] -> Const [InstanceState] [InstanceState])
    -> Maybe [InstanceState]
    -> Const [InstanceState] (Maybe [InstanceState]))
-> Getting
     [InstanceState] DescribeInstanceHealthResponse [InstanceState]
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. ([InstanceState] -> Const [InstanceState] [InstanceState])
-> Maybe [InstanceState]
-> Const [InstanceState] (Maybe [InstanceState])
forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
                    )
                )
                ((InstanceState -> f InstanceState)
 -> DescribeInstanceHealthResponse
 -> f DescribeInstanceHealthResponse)
-> ((CI Text -> f (CI Text)) -> InstanceState -> f InstanceState)
-> (CI Text -> f (CI Text))
-> DescribeInstanceHealthResponse
-> f DescribeInstanceHealthResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. (Maybe Text -> f (Maybe Text)) -> InstanceState -> f InstanceState
Lens' InstanceState (Maybe Text)
instanceState_state
                ((Maybe Text -> f (Maybe Text))
 -> InstanceState -> f InstanceState)
-> ((CI Text -> f (CI Text)) -> Maybe Text -> f (Maybe Text))
-> (CI Text -> f (CI Text))
-> InstanceState
-> f InstanceState
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. (Text -> f Text) -> Maybe Text -> f (Maybe Text)
forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
                ((Text -> f Text) -> Maybe Text -> f (Maybe Text))
-> ((CI Text -> f (CI Text)) -> Text -> f Text)
-> (CI Text -> f (CI Text))
-> Maybe Text
-> f (Maybe Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. (Text -> CI Text) -> (CI Text -> f (CI Text)) -> Text -> f Text
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
Lens.to Text -> CI Text
forall a. ToText a => a -> CI Text
Core.toTextCI
            ),
          ErrorCode -> Accept -> Acceptor DescribeInstanceHealth
forall a. ErrorCode -> Accept -> Acceptor a
Core.matchError ErrorCode
"InvalidInstance" Accept
Core.AcceptRetry
        ]
    }