{-# 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.LaunchTemplateTagSpecification
-- 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.LaunchTemplateTagSpecification 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 Amazonka.EC2.Types.ResourceType
import Amazonka.EC2.Types.Tag
import qualified Amazonka.Prelude as Prelude

-- | The tags specification for the launch template.
--
-- /See:/ 'newLaunchTemplateTagSpecification' smart constructor.
data LaunchTemplateTagSpecification = LaunchTemplateTagSpecification'
  { -- | The type of resource to tag.
    LaunchTemplateTagSpecification -> Maybe ResourceType
resourceType :: Prelude.Maybe ResourceType,
    -- | The tags for the resource.
    LaunchTemplateTagSpecification -> Maybe [Tag]
tags :: Prelude.Maybe [Tag]
  }
  deriving (LaunchTemplateTagSpecification
-> LaunchTemplateTagSpecification -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LaunchTemplateTagSpecification
-> LaunchTemplateTagSpecification -> Bool
$c/= :: LaunchTemplateTagSpecification
-> LaunchTemplateTagSpecification -> Bool
== :: LaunchTemplateTagSpecification
-> LaunchTemplateTagSpecification -> Bool
$c== :: LaunchTemplateTagSpecification
-> LaunchTemplateTagSpecification -> Bool
Prelude.Eq, ReadPrec [LaunchTemplateTagSpecification]
ReadPrec LaunchTemplateTagSpecification
Int -> ReadS LaunchTemplateTagSpecification
ReadS [LaunchTemplateTagSpecification]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LaunchTemplateTagSpecification]
$creadListPrec :: ReadPrec [LaunchTemplateTagSpecification]
readPrec :: ReadPrec LaunchTemplateTagSpecification
$creadPrec :: ReadPrec LaunchTemplateTagSpecification
readList :: ReadS [LaunchTemplateTagSpecification]
$creadList :: ReadS [LaunchTemplateTagSpecification]
readsPrec :: Int -> ReadS LaunchTemplateTagSpecification
$creadsPrec :: Int -> ReadS LaunchTemplateTagSpecification
Prelude.Read, Int -> LaunchTemplateTagSpecification -> ShowS
[LaunchTemplateTagSpecification] -> ShowS
LaunchTemplateTagSpecification -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LaunchTemplateTagSpecification] -> ShowS
$cshowList :: [LaunchTemplateTagSpecification] -> ShowS
show :: LaunchTemplateTagSpecification -> String
$cshow :: LaunchTemplateTagSpecification -> String
showsPrec :: Int -> LaunchTemplateTagSpecification -> ShowS
$cshowsPrec :: Int -> LaunchTemplateTagSpecification -> ShowS
Prelude.Show, forall x.
Rep LaunchTemplateTagSpecification x
-> LaunchTemplateTagSpecification
forall x.
LaunchTemplateTagSpecification
-> Rep LaunchTemplateTagSpecification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep LaunchTemplateTagSpecification x
-> LaunchTemplateTagSpecification
$cfrom :: forall x.
LaunchTemplateTagSpecification
-> Rep LaunchTemplateTagSpecification x
Prelude.Generic)

-- |
-- Create a value of 'LaunchTemplateTagSpecification' 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:
--
-- 'resourceType', 'launchTemplateTagSpecification_resourceType' - The type of resource to tag.
--
-- 'tags', 'launchTemplateTagSpecification_tags' - The tags for the resource.
newLaunchTemplateTagSpecification ::
  LaunchTemplateTagSpecification
newLaunchTemplateTagSpecification :: LaunchTemplateTagSpecification
newLaunchTemplateTagSpecification =
  LaunchTemplateTagSpecification'
    { $sel:resourceType:LaunchTemplateTagSpecification' :: Maybe ResourceType
resourceType =
        forall a. Maybe a
Prelude.Nothing,
      $sel:tags:LaunchTemplateTagSpecification' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing
    }

-- | The type of resource to tag.
launchTemplateTagSpecification_resourceType :: Lens.Lens' LaunchTemplateTagSpecification (Prelude.Maybe ResourceType)
launchTemplateTagSpecification_resourceType :: Lens' LaunchTemplateTagSpecification (Maybe ResourceType)
launchTemplateTagSpecification_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateTagSpecification' {Maybe ResourceType
resourceType :: Maybe ResourceType
$sel:resourceType:LaunchTemplateTagSpecification' :: LaunchTemplateTagSpecification -> Maybe ResourceType
resourceType} -> Maybe ResourceType
resourceType) (\s :: LaunchTemplateTagSpecification
s@LaunchTemplateTagSpecification' {} Maybe ResourceType
a -> LaunchTemplateTagSpecification
s {$sel:resourceType:LaunchTemplateTagSpecification' :: Maybe ResourceType
resourceType = Maybe ResourceType
a} :: LaunchTemplateTagSpecification)

-- | The tags for the resource.
launchTemplateTagSpecification_tags :: Lens.Lens' LaunchTemplateTagSpecification (Prelude.Maybe [Tag])
launchTemplateTagSpecification_tags :: Lens' LaunchTemplateTagSpecification (Maybe [Tag])
launchTemplateTagSpecification_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateTagSpecification' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:LaunchTemplateTagSpecification' :: LaunchTemplateTagSpecification -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: LaunchTemplateTagSpecification
s@LaunchTemplateTagSpecification' {} Maybe [Tag]
a -> LaunchTemplateTagSpecification
s {$sel:tags:LaunchTemplateTagSpecification' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: LaunchTemplateTagSpecification) 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

instance Data.FromXML LaunchTemplateTagSpecification where
  parseXML :: [Node] -> Either String LaunchTemplateTagSpecification
parseXML [Node]
x =
    Maybe ResourceType -> Maybe [Tag] -> LaunchTemplateTagSpecification
LaunchTemplateTagSpecification'
      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
"resourceType")
      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
"tagSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )

instance
  Prelude.Hashable
    LaunchTemplateTagSpecification
  where
  hashWithSalt :: Int -> LaunchTemplateTagSpecification -> Int
hashWithSalt
    Int
_salt
    LaunchTemplateTagSpecification' {Maybe [Tag]
Maybe ResourceType
tags :: Maybe [Tag]
resourceType :: Maybe ResourceType
$sel:tags:LaunchTemplateTagSpecification' :: LaunchTemplateTagSpecification -> Maybe [Tag]
$sel:resourceType:LaunchTemplateTagSpecification' :: LaunchTemplateTagSpecification -> Maybe ResourceType
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResourceType
resourceType
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags

instance
  Prelude.NFData
    LaunchTemplateTagSpecification
  where
  rnf :: LaunchTemplateTagSpecification -> ()
rnf LaunchTemplateTagSpecification' {Maybe [Tag]
Maybe ResourceType
tags :: Maybe [Tag]
resourceType :: Maybe ResourceType
$sel:tags:LaunchTemplateTagSpecification' :: LaunchTemplateTagSpecification -> Maybe [Tag]
$sel:resourceType:LaunchTemplateTagSpecification' :: LaunchTemplateTagSpecification -> Maybe ResourceType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceType
resourceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags