{-# 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.EC2.Types.CoipAddressUsage
-- 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.EC2.Types.CoipAddressUsage where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Internal
import qualified Amazonka.Prelude as Prelude

-- | Describes address usage for a customer-owned address pool.
--
-- /See:/ 'newCoipAddressUsage' smart constructor.
data CoipAddressUsage = CoipAddressUsage'
  { -- | The allocation ID of the address.
    CoipAddressUsage -> Maybe Text
allocationId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services account ID.
    CoipAddressUsage -> Maybe Text
awsAccountId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services service.
    CoipAddressUsage -> Maybe Text
awsService :: Prelude.Maybe Prelude.Text,
    -- | The customer-owned IP address.
    CoipAddressUsage -> Maybe Text
coIp :: Prelude.Maybe Prelude.Text
  }
  deriving (CoipAddressUsage -> CoipAddressUsage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CoipAddressUsage -> CoipAddressUsage -> Bool
$c/= :: CoipAddressUsage -> CoipAddressUsage -> Bool
== :: CoipAddressUsage -> CoipAddressUsage -> Bool
$c== :: CoipAddressUsage -> CoipAddressUsage -> Bool
Prelude.Eq, ReadPrec [CoipAddressUsage]
ReadPrec CoipAddressUsage
Int -> ReadS CoipAddressUsage
ReadS [CoipAddressUsage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CoipAddressUsage]
$creadListPrec :: ReadPrec [CoipAddressUsage]
readPrec :: ReadPrec CoipAddressUsage
$creadPrec :: ReadPrec CoipAddressUsage
readList :: ReadS [CoipAddressUsage]
$creadList :: ReadS [CoipAddressUsage]
readsPrec :: Int -> ReadS CoipAddressUsage
$creadsPrec :: Int -> ReadS CoipAddressUsage
Prelude.Read, Int -> CoipAddressUsage -> ShowS
[CoipAddressUsage] -> ShowS
CoipAddressUsage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CoipAddressUsage] -> ShowS
$cshowList :: [CoipAddressUsage] -> ShowS
show :: CoipAddressUsage -> String
$cshow :: CoipAddressUsage -> String
showsPrec :: Int -> CoipAddressUsage -> ShowS
$cshowsPrec :: Int -> CoipAddressUsage -> ShowS
Prelude.Show, forall x. Rep CoipAddressUsage x -> CoipAddressUsage
forall x. CoipAddressUsage -> Rep CoipAddressUsage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CoipAddressUsage x -> CoipAddressUsage
$cfrom :: forall x. CoipAddressUsage -> Rep CoipAddressUsage x
Prelude.Generic)

-- |
-- Create a value of 'CoipAddressUsage' 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:
--
-- 'allocationId', 'coipAddressUsage_allocationId' - The allocation ID of the address.
--
-- 'awsAccountId', 'coipAddressUsage_awsAccountId' - The Amazon Web Services account ID.
--
-- 'awsService', 'coipAddressUsage_awsService' - The Amazon Web Services service.
--
-- 'coIp', 'coipAddressUsage_coIp' - The customer-owned IP address.
newCoipAddressUsage ::
  CoipAddressUsage
newCoipAddressUsage :: CoipAddressUsage
newCoipAddressUsage =
  CoipAddressUsage'
    { $sel:allocationId:CoipAddressUsage' :: Maybe Text
allocationId = forall a. Maybe a
Prelude.Nothing,
      $sel:awsAccountId:CoipAddressUsage' :: Maybe Text
awsAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:awsService:CoipAddressUsage' :: Maybe Text
awsService = forall a. Maybe a
Prelude.Nothing,
      $sel:coIp:CoipAddressUsage' :: Maybe Text
coIp = forall a. Maybe a
Prelude.Nothing
    }

-- | The allocation ID of the address.
coipAddressUsage_allocationId :: Lens.Lens' CoipAddressUsage (Prelude.Maybe Prelude.Text)
coipAddressUsage_allocationId :: Lens' CoipAddressUsage (Maybe Text)
coipAddressUsage_allocationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CoipAddressUsage' {Maybe Text
allocationId :: Maybe Text
$sel:allocationId:CoipAddressUsage' :: CoipAddressUsage -> Maybe Text
allocationId} -> Maybe Text
allocationId) (\s :: CoipAddressUsage
s@CoipAddressUsage' {} Maybe Text
a -> CoipAddressUsage
s {$sel:allocationId:CoipAddressUsage' :: Maybe Text
allocationId = Maybe Text
a} :: CoipAddressUsage)

-- | The Amazon Web Services account ID.
coipAddressUsage_awsAccountId :: Lens.Lens' CoipAddressUsage (Prelude.Maybe Prelude.Text)
coipAddressUsage_awsAccountId :: Lens' CoipAddressUsage (Maybe Text)
coipAddressUsage_awsAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CoipAddressUsage' {Maybe Text
awsAccountId :: Maybe Text
$sel:awsAccountId:CoipAddressUsage' :: CoipAddressUsage -> Maybe Text
awsAccountId} -> Maybe Text
awsAccountId) (\s :: CoipAddressUsage
s@CoipAddressUsage' {} Maybe Text
a -> CoipAddressUsage
s {$sel:awsAccountId:CoipAddressUsage' :: Maybe Text
awsAccountId = Maybe Text
a} :: CoipAddressUsage)

-- | The Amazon Web Services service.
coipAddressUsage_awsService :: Lens.Lens' CoipAddressUsage (Prelude.Maybe Prelude.Text)
coipAddressUsage_awsService :: Lens' CoipAddressUsage (Maybe Text)
coipAddressUsage_awsService = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CoipAddressUsage' {Maybe Text
awsService :: Maybe Text
$sel:awsService:CoipAddressUsage' :: CoipAddressUsage -> Maybe Text
awsService} -> Maybe Text
awsService) (\s :: CoipAddressUsage
s@CoipAddressUsage' {} Maybe Text
a -> CoipAddressUsage
s {$sel:awsService:CoipAddressUsage' :: Maybe Text
awsService = Maybe Text
a} :: CoipAddressUsage)

-- | The customer-owned IP address.
coipAddressUsage_coIp :: Lens.Lens' CoipAddressUsage (Prelude.Maybe Prelude.Text)
coipAddressUsage_coIp :: Lens' CoipAddressUsage (Maybe Text)
coipAddressUsage_coIp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CoipAddressUsage' {Maybe Text
coIp :: Maybe Text
$sel:coIp:CoipAddressUsage' :: CoipAddressUsage -> Maybe Text
coIp} -> Maybe Text
coIp) (\s :: CoipAddressUsage
s@CoipAddressUsage' {} Maybe Text
a -> CoipAddressUsage
s {$sel:coIp:CoipAddressUsage' :: Maybe Text
coIp = Maybe Text
a} :: CoipAddressUsage)

instance Data.FromXML CoipAddressUsage where
  parseXML :: [Node] -> Either String CoipAddressUsage
parseXML [Node]
x =
    Maybe Text
-> Maybe Text -> Maybe Text -> Maybe Text -> CoipAddressUsage
CoipAddressUsage'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"allocationId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"awsAccountId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"awsService")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"coIp")

instance Prelude.Hashable CoipAddressUsage where
  hashWithSalt :: Int -> CoipAddressUsage -> Int
hashWithSalt Int
_salt CoipAddressUsage' {Maybe Text
coIp :: Maybe Text
awsService :: Maybe Text
awsAccountId :: Maybe Text
allocationId :: Maybe Text
$sel:coIp:CoipAddressUsage' :: CoipAddressUsage -> Maybe Text
$sel:awsService:CoipAddressUsage' :: CoipAddressUsage -> Maybe Text
$sel:awsAccountId:CoipAddressUsage' :: CoipAddressUsage -> Maybe Text
$sel:allocationId:CoipAddressUsage' :: CoipAddressUsage -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
allocationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
awsAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
awsService
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
coIp

instance Prelude.NFData CoipAddressUsage where
  rnf :: CoipAddressUsage -> ()
rnf CoipAddressUsage' {Maybe Text
coIp :: Maybe Text
awsService :: Maybe Text
awsAccountId :: Maybe Text
allocationId :: Maybe Text
$sel:coIp:CoipAddressUsage' :: CoipAddressUsage -> Maybe Text
$sel:awsService:CoipAddressUsage' :: CoipAddressUsage -> Maybe Text
$sel:awsAccountId:CoipAddressUsage' :: CoipAddressUsage -> Maybe Text
$sel:allocationId:CoipAddressUsage' :: CoipAddressUsage -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
allocationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
awsAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
awsService
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
coIp