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

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ElastiCache.DescribeCacheClusters
import Amazonka.ElastiCache.DescribeReplicationGroups
import Amazonka.ElastiCache.Lens
import Amazonka.ElastiCache.Types
import qualified Amazonka.Prelude as Prelude

-- | Polls 'Amazonka.ElastiCache.DescribeCacheClusters' every 15 seconds until a successful state is reached. An error is returned after 40 failed checks.
newCacheClusterAvailable :: Core.Wait DescribeCacheClusters
newCacheClusterAvailable :: Wait DescribeCacheClusters
newCacheClusterAvailable =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"CacheClusterAvailable",
      $sel:attempts:Wait :: Int
Core.attempts = Int
40,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
15,
      $sel:acceptors:Wait :: [Acceptor DescribeCacheClusters]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"available"
            Accept
Core.AcceptSuccess
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeCacheClustersResponse (Maybe [CacheCluster])
describeCacheClustersResponse_cacheClusters
                        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' CacheCluster (Maybe Text)
cacheCluster_cacheClusterStatus
                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.matchAny
            CI Text
"deleted"
            Accept
Core.AcceptFailure
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeCacheClustersResponse (Maybe [CacheCluster])
describeCacheClustersResponse_cacheClusters
                        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' CacheCluster (Maybe Text)
cacheCluster_cacheClusterStatus
                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.matchAny
            CI Text
"deleting"
            Accept
Core.AcceptFailure
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeCacheClustersResponse (Maybe [CacheCluster])
describeCacheClustersResponse_cacheClusters
                        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' CacheCluster (Maybe Text)
cacheCluster_cacheClusterStatus
                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.matchAny
            CI Text
"incompatible-network"
            Accept
Core.AcceptFailure
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeCacheClustersResponse (Maybe [CacheCluster])
describeCacheClustersResponse_cacheClusters
                        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' CacheCluster (Maybe Text)
cacheCluster_cacheClusterStatus
                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.matchAny
            CI Text
"restore-failed"
            Accept
Core.AcceptFailure
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeCacheClustersResponse (Maybe [CacheCluster])
describeCacheClustersResponse_cacheClusters
                        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' CacheCluster (Maybe Text)
cacheCluster_cacheClusterStatus
                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.ElastiCache.DescribeCacheClusters' every 15 seconds until a successful state is reached. An error is returned after 40 failed checks.
newCacheClusterDeleted :: Core.Wait DescribeCacheClusters
newCacheClusterDeleted :: Wait DescribeCacheClusters
newCacheClusterDeleted =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"CacheClusterDeleted",
      $sel:attempts:Wait :: Int
Core.attempts = Int
40,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
15,
      $sel:acceptors:Wait :: [Acceptor DescribeCacheClusters]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"deleted"
            Accept
Core.AcceptSuccess
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeCacheClustersResponse (Maybe [CacheCluster])
describeCacheClustersResponse_cacheClusters
                        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' CacheCluster (Maybe Text)
cacheCluster_cacheClusterStatus
                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. ErrorCode -> Accept -> Acceptor a
Core.matchError
            ErrorCode
"CacheClusterNotFound"
            Accept
Core.AcceptSuccess,
          forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAny
            CI Text
"available"
            Accept
Core.AcceptFailure
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeCacheClustersResponse (Maybe [CacheCluster])
describeCacheClustersResponse_cacheClusters
                        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' CacheCluster (Maybe Text)
cacheCluster_cacheClusterStatus
                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.matchAny
            CI Text
"creating"
            Accept
Core.AcceptFailure
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeCacheClustersResponse (Maybe [CacheCluster])
describeCacheClustersResponse_cacheClusters
                        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' CacheCluster (Maybe Text)
cacheCluster_cacheClusterStatus
                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.matchAny
            CI Text
"incompatible-network"
            Accept
Core.AcceptFailure
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeCacheClustersResponse (Maybe [CacheCluster])
describeCacheClustersResponse_cacheClusters
                        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' CacheCluster (Maybe Text)
cacheCluster_cacheClusterStatus
                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.matchAny
            CI Text
"modifying"
            Accept
Core.AcceptFailure
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeCacheClustersResponse (Maybe [CacheCluster])
describeCacheClustersResponse_cacheClusters
                        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' CacheCluster (Maybe Text)
cacheCluster_cacheClusterStatus
                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.matchAny
            CI Text
"restore-failed"
            Accept
Core.AcceptFailure
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeCacheClustersResponse (Maybe [CacheCluster])
describeCacheClustersResponse_cacheClusters
                        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' CacheCluster (Maybe Text)
cacheCluster_cacheClusterStatus
                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.matchAny
            CI Text
"snapshotting"
            Accept
Core.AcceptFailure
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeCacheClustersResponse (Maybe [CacheCluster])
describeCacheClustersResponse_cacheClusters
                        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' CacheCluster (Maybe Text)
cacheCluster_cacheClusterStatus
                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.ElastiCache.DescribeReplicationGroups' every 15 seconds until a successful state is reached. An error is returned after 40 failed checks.
newReplicationGroupAvailable :: Core.Wait DescribeReplicationGroups
newReplicationGroupAvailable :: Wait DescribeReplicationGroups
newReplicationGroupAvailable =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"ReplicationGroupAvailable",
      $sel:attempts:Wait :: Int
Core.attempts = Int
40,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
15,
      $sel:acceptors:Wait :: [Acceptor DescribeReplicationGroups]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"available"
            Accept
Core.AcceptSuccess
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeReplicationGroupsResponse (Maybe [ReplicationGroup])
describeReplicationGroupsResponse_replicationGroups
                        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' ReplicationGroup (Maybe Text)
replicationGroup_status
                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.matchAny
            CI Text
"deleted"
            Accept
Core.AcceptFailure
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeReplicationGroupsResponse (Maybe [ReplicationGroup])
describeReplicationGroupsResponse_replicationGroups
                        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' ReplicationGroup (Maybe Text)
replicationGroup_status
                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.ElastiCache.DescribeReplicationGroups' every 15 seconds until a successful state is reached. An error is returned after 40 failed checks.
newReplicationGroupDeleted :: Core.Wait DescribeReplicationGroups
newReplicationGroupDeleted :: Wait DescribeReplicationGroups
newReplicationGroupDeleted =
  Core.Wait
    { $sel:name:Wait :: ByteString
Core.name = ByteString
"ReplicationGroupDeleted",
      $sel:attempts:Wait :: Int
Core.attempts = Int
40,
      $sel:delay:Wait :: Seconds
Core.delay = Seconds
15,
      $sel:acceptors:Wait :: [Acceptor DescribeReplicationGroups]
Core.acceptors =
        [ forall b a.
Eq b =>
b -> Accept -> Fold (AWSResponse a) b -> Acceptor a
Core.matchAll
            CI Text
"deleted"
            Accept
Core.AcceptSuccess
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeReplicationGroupsResponse (Maybe [ReplicationGroup])
describeReplicationGroupsResponse_replicationGroups
                        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' ReplicationGroup (Maybe Text)
replicationGroup_status
                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.matchAny
            CI Text
"available"
            Accept
Core.AcceptFailure
            ( forall (f :: * -> *) s a. Foldable f => (s -> f a) -> Fold s a
Lens.folding
                ( forall r s. Getting [r] s [r] -> s -> [r]
Lens.concatOf
                    ( Lens' DescribeReplicationGroupsResponse (Maybe [ReplicationGroup])
describeReplicationGroupsResponse_replicationGroups
                        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' ReplicationGroup (Maybe Text)
replicationGroup_status
                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. ErrorCode -> Accept -> Acceptor a
Core.matchError
            ErrorCode
"ReplicationGroupNotFoundFault"
            Accept
Core.AcceptSuccess
        ]
    }