{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.GlobalAccelerator.Types.ByoipCidr
-- 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.GlobalAccelerator.Types.ByoipCidr where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.GlobalAccelerator.Types.ByoipCidrEvent
import Amazonka.GlobalAccelerator.Types.ByoipCidrState
import qualified Amazonka.Prelude as Prelude

-- | Information about an IP address range that is provisioned for use with
-- your Amazon Web Services resources through bring your own IP address
-- (BYOIP).
--
-- The following describes each BYOIP @State@ that your IP address range
-- can be in.
--
-- -   __PENDING_PROVISIONING__ — You’ve submitted a request to provision
--     an IP address range but it is not yet provisioned with Global
--     Accelerator.
--
-- -   __READY__ — The address range is provisioned with Global Accelerator
--     and can be advertised.
--
-- -   __PENDING_ADVERTISING__ — You’ve submitted a request for Global
--     Accelerator to advertise an address range but it is not yet being
--     advertised.
--
-- -   __ADVERTISING__ — The address range is being advertised by Global
--     Accelerator.
--
-- -   __PENDING_WITHDRAWING__ — You’ve submitted a request to withdraw an
--     address range from being advertised but it is still being advertised
--     by Global Accelerator.
--
-- -   __PENDING_DEPROVISIONING__ — You’ve submitted a request to
--     deprovision an address range from Global Accelerator but it is still
--     provisioned.
--
-- -   __DEPROVISIONED__ — The address range is deprovisioned from Global
--     Accelerator.
--
-- -   __FAILED_PROVISION__ — The request to provision the address range
--     from Global Accelerator was not successful. Please make sure that
--     you provide all of the correct information, and try again. If the
--     request fails a second time, contact Amazon Web Services support.
--
-- -   __FAILED_ADVERTISING__ — The request for Global Accelerator to
--     advertise the address range was not successful. Please make sure
--     that you provide all of the correct information, and try again. If
--     the request fails a second time, contact Amazon Web Services
--     support.
--
-- -   __FAILED_WITHDRAW__ — The request to withdraw the address range from
--     advertising by Global Accelerator was not successful. Please make
--     sure that you provide all of the correct information, and try again.
--     If the request fails a second time, contact Amazon Web Services
--     support.
--
-- -   __FAILED_DEPROVISION__ — The request to deprovision the address
--     range from Global Accelerator was not successful. Please make sure
--     that you provide all of the correct information, and try again. If
--     the request fails a second time, contact Amazon Web Services
--     support.
--
-- /See:/ 'newByoipCidr' smart constructor.
data ByoipCidr = ByoipCidr'
  { -- | The address range, in CIDR notation.
    ByoipCidr -> Maybe Text
cidr :: Prelude.Maybe Prelude.Text,
    -- | A history of status changes for an IP address range that you bring to
    -- Global Accelerator through bring your own IP address (BYOIP).
    ByoipCidr -> Maybe [ByoipCidrEvent]
events :: Prelude.Maybe [ByoipCidrEvent],
    -- | The state of the address pool.
    ByoipCidr -> Maybe ByoipCidrState
state :: Prelude.Maybe ByoipCidrState
  }
  deriving (ByoipCidr -> ByoipCidr -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ByoipCidr -> ByoipCidr -> Bool
$c/= :: ByoipCidr -> ByoipCidr -> Bool
== :: ByoipCidr -> ByoipCidr -> Bool
$c== :: ByoipCidr -> ByoipCidr -> Bool
Prelude.Eq, ReadPrec [ByoipCidr]
ReadPrec ByoipCidr
Int -> ReadS ByoipCidr
ReadS [ByoipCidr]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ByoipCidr]
$creadListPrec :: ReadPrec [ByoipCidr]
readPrec :: ReadPrec ByoipCidr
$creadPrec :: ReadPrec ByoipCidr
readList :: ReadS [ByoipCidr]
$creadList :: ReadS [ByoipCidr]
readsPrec :: Int -> ReadS ByoipCidr
$creadsPrec :: Int -> ReadS ByoipCidr
Prelude.Read, Int -> ByoipCidr -> ShowS
[ByoipCidr] -> ShowS
ByoipCidr -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ByoipCidr] -> ShowS
$cshowList :: [ByoipCidr] -> ShowS
show :: ByoipCidr -> String
$cshow :: ByoipCidr -> String
showsPrec :: Int -> ByoipCidr -> ShowS
$cshowsPrec :: Int -> ByoipCidr -> ShowS
Prelude.Show, forall x. Rep ByoipCidr x -> ByoipCidr
forall x. ByoipCidr -> Rep ByoipCidr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ByoipCidr x -> ByoipCidr
$cfrom :: forall x. ByoipCidr -> Rep ByoipCidr x
Prelude.Generic)

-- |
-- Create a value of 'ByoipCidr' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'cidr', 'byoipCidr_cidr' - The address range, in CIDR notation.
--
-- 'events', 'byoipCidr_events' - A history of status changes for an IP address range that you bring to
-- Global Accelerator through bring your own IP address (BYOIP).
--
-- 'state', 'byoipCidr_state' - The state of the address pool.
newByoipCidr ::
  ByoipCidr
newByoipCidr :: ByoipCidr
newByoipCidr =
  ByoipCidr'
    { $sel:cidr:ByoipCidr' :: Maybe Text
cidr = forall a. Maybe a
Prelude.Nothing,
      $sel:events:ByoipCidr' :: Maybe [ByoipCidrEvent]
events = forall a. Maybe a
Prelude.Nothing,
      $sel:state:ByoipCidr' :: Maybe ByoipCidrState
state = forall a. Maybe a
Prelude.Nothing
    }

-- | The address range, in CIDR notation.
byoipCidr_cidr :: Lens.Lens' ByoipCidr (Prelude.Maybe Prelude.Text)
byoipCidr_cidr :: Lens' ByoipCidr (Maybe Text)
byoipCidr_cidr = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ByoipCidr' {Maybe Text
cidr :: Maybe Text
$sel:cidr:ByoipCidr' :: ByoipCidr -> Maybe Text
cidr} -> Maybe Text
cidr) (\s :: ByoipCidr
s@ByoipCidr' {} Maybe Text
a -> ByoipCidr
s {$sel:cidr:ByoipCidr' :: Maybe Text
cidr = Maybe Text
a} :: ByoipCidr)

-- | A history of status changes for an IP address range that you bring to
-- Global Accelerator through bring your own IP address (BYOIP).
byoipCidr_events :: Lens.Lens' ByoipCidr (Prelude.Maybe [ByoipCidrEvent])
byoipCidr_events :: Lens' ByoipCidr (Maybe [ByoipCidrEvent])
byoipCidr_events = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ByoipCidr' {Maybe [ByoipCidrEvent]
events :: Maybe [ByoipCidrEvent]
$sel:events:ByoipCidr' :: ByoipCidr -> Maybe [ByoipCidrEvent]
events} -> Maybe [ByoipCidrEvent]
events) (\s :: ByoipCidr
s@ByoipCidr' {} Maybe [ByoipCidrEvent]
a -> ByoipCidr
s {$sel:events:ByoipCidr' :: Maybe [ByoipCidrEvent]
events = Maybe [ByoipCidrEvent]
a} :: ByoipCidr) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The state of the address pool.
byoipCidr_state :: Lens.Lens' ByoipCidr (Prelude.Maybe ByoipCidrState)
byoipCidr_state :: Lens' ByoipCidr (Maybe ByoipCidrState)
byoipCidr_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ByoipCidr' {Maybe ByoipCidrState
state :: Maybe ByoipCidrState
$sel:state:ByoipCidr' :: ByoipCidr -> Maybe ByoipCidrState
state} -> Maybe ByoipCidrState
state) (\s :: ByoipCidr
s@ByoipCidr' {} Maybe ByoipCidrState
a -> ByoipCidr
s {$sel:state:ByoipCidr' :: Maybe ByoipCidrState
state = Maybe ByoipCidrState
a} :: ByoipCidr)

instance Data.FromJSON ByoipCidr where
  parseJSON :: Value -> Parser ByoipCidr
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ByoipCidr"
      ( \Object
x ->
          Maybe Text
-> Maybe [ByoipCidrEvent] -> Maybe ByoipCidrState -> ByoipCidr
ByoipCidr'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Cidr")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Events" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"State")
      )

instance Prelude.Hashable ByoipCidr where
  hashWithSalt :: Int -> ByoipCidr -> Int
hashWithSalt Int
_salt ByoipCidr' {Maybe [ByoipCidrEvent]
Maybe Text
Maybe ByoipCidrState
state :: Maybe ByoipCidrState
events :: Maybe [ByoipCidrEvent]
cidr :: Maybe Text
$sel:state:ByoipCidr' :: ByoipCidr -> Maybe ByoipCidrState
$sel:events:ByoipCidr' :: ByoipCidr -> Maybe [ByoipCidrEvent]
$sel:cidr:ByoipCidr' :: ByoipCidr -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cidr
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ByoipCidrEvent]
events
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ByoipCidrState
state

instance Prelude.NFData ByoipCidr where
  rnf :: ByoipCidr -> ()
rnf ByoipCidr' {Maybe [ByoipCidrEvent]
Maybe Text
Maybe ByoipCidrState
state :: Maybe ByoipCidrState
events :: Maybe [ByoipCidrEvent]
cidr :: Maybe Text
$sel:state:ByoipCidr' :: ByoipCidr -> Maybe ByoipCidrState
$sel:events:ByoipCidr' :: ByoipCidr -> Maybe [ByoipCidrEvent]
$sel:cidr:ByoipCidr' :: ByoipCidr -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cidr
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ByoipCidrEvent]
events
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ByoipCidrState
state