{-# 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.SpotFleetTagSpecification
-- 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.SpotFleetTagSpecification 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 for a Spot Fleet resource.
--
-- /See:/ 'newSpotFleetTagSpecification' smart constructor.
data SpotFleetTagSpecification = SpotFleetTagSpecification'
  { -- | The type of resource. Currently, the only resource type that is
    -- supported is @instance@. To tag the Spot Fleet request on creation, use
    -- the @TagSpecifications@ parameter in
    -- @ @<https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_SpotFleetRequestConfigData.html SpotFleetRequestConfigData>@ @.
    SpotFleetTagSpecification -> Maybe ResourceType
resourceType :: Prelude.Maybe ResourceType,
    -- | The tags.
    SpotFleetTagSpecification -> Maybe [Tag]
tags :: Prelude.Maybe [Tag]
  }
  deriving (SpotFleetTagSpecification -> SpotFleetTagSpecification -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpotFleetTagSpecification -> SpotFleetTagSpecification -> Bool
$c/= :: SpotFleetTagSpecification -> SpotFleetTagSpecification -> Bool
== :: SpotFleetTagSpecification -> SpotFleetTagSpecification -> Bool
$c== :: SpotFleetTagSpecification -> SpotFleetTagSpecification -> Bool
Prelude.Eq, ReadPrec [SpotFleetTagSpecification]
ReadPrec SpotFleetTagSpecification
Int -> ReadS SpotFleetTagSpecification
ReadS [SpotFleetTagSpecification]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SpotFleetTagSpecification]
$creadListPrec :: ReadPrec [SpotFleetTagSpecification]
readPrec :: ReadPrec SpotFleetTagSpecification
$creadPrec :: ReadPrec SpotFleetTagSpecification
readList :: ReadS [SpotFleetTagSpecification]
$creadList :: ReadS [SpotFleetTagSpecification]
readsPrec :: Int -> ReadS SpotFleetTagSpecification
$creadsPrec :: Int -> ReadS SpotFleetTagSpecification
Prelude.Read, Int -> SpotFleetTagSpecification -> ShowS
[SpotFleetTagSpecification] -> ShowS
SpotFleetTagSpecification -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpotFleetTagSpecification] -> ShowS
$cshowList :: [SpotFleetTagSpecification] -> ShowS
show :: SpotFleetTagSpecification -> String
$cshow :: SpotFleetTagSpecification -> String
showsPrec :: Int -> SpotFleetTagSpecification -> ShowS
$cshowsPrec :: Int -> SpotFleetTagSpecification -> ShowS
Prelude.Show, forall x.
Rep SpotFleetTagSpecification x -> SpotFleetTagSpecification
forall x.
SpotFleetTagSpecification -> Rep SpotFleetTagSpecification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SpotFleetTagSpecification x -> SpotFleetTagSpecification
$cfrom :: forall x.
SpotFleetTagSpecification -> Rep SpotFleetTagSpecification x
Prelude.Generic)

-- |
-- Create a value of 'SpotFleetTagSpecification' 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', 'spotFleetTagSpecification_resourceType' - The type of resource. Currently, the only resource type that is
-- supported is @instance@. To tag the Spot Fleet request on creation, use
-- the @TagSpecifications@ parameter in
-- @ @<https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_SpotFleetRequestConfigData.html SpotFleetRequestConfigData>@ @.
--
-- 'tags', 'spotFleetTagSpecification_tags' - The tags.
newSpotFleetTagSpecification ::
  SpotFleetTagSpecification
newSpotFleetTagSpecification :: SpotFleetTagSpecification
newSpotFleetTagSpecification =
  SpotFleetTagSpecification'
    { $sel:resourceType:SpotFleetTagSpecification' :: Maybe ResourceType
resourceType =
        forall a. Maybe a
Prelude.Nothing,
      $sel:tags:SpotFleetTagSpecification' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing
    }

-- | The type of resource. Currently, the only resource type that is
-- supported is @instance@. To tag the Spot Fleet request on creation, use
-- the @TagSpecifications@ parameter in
-- @ @<https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_SpotFleetRequestConfigData.html SpotFleetRequestConfigData>@ @.
spotFleetTagSpecification_resourceType :: Lens.Lens' SpotFleetTagSpecification (Prelude.Maybe ResourceType)
spotFleetTagSpecification_resourceType :: Lens' SpotFleetTagSpecification (Maybe ResourceType)
spotFleetTagSpecification_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetTagSpecification' {Maybe ResourceType
resourceType :: Maybe ResourceType
$sel:resourceType:SpotFleetTagSpecification' :: SpotFleetTagSpecification -> Maybe ResourceType
resourceType} -> Maybe ResourceType
resourceType) (\s :: SpotFleetTagSpecification
s@SpotFleetTagSpecification' {} Maybe ResourceType
a -> SpotFleetTagSpecification
s {$sel:resourceType:SpotFleetTagSpecification' :: Maybe ResourceType
resourceType = Maybe ResourceType
a} :: SpotFleetTagSpecification)

-- | The tags.
spotFleetTagSpecification_tags :: Lens.Lens' SpotFleetTagSpecification (Prelude.Maybe [Tag])
spotFleetTagSpecification_tags :: Lens' SpotFleetTagSpecification (Maybe [Tag])
spotFleetTagSpecification_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SpotFleetTagSpecification' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:SpotFleetTagSpecification' :: SpotFleetTagSpecification -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: SpotFleetTagSpecification
s@SpotFleetTagSpecification' {} Maybe [Tag]
a -> SpotFleetTagSpecification
s {$sel:tags:SpotFleetTagSpecification' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: SpotFleetTagSpecification) 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 SpotFleetTagSpecification where
  parseXML :: [Node] -> Either String SpotFleetTagSpecification
parseXML [Node]
x =
    Maybe ResourceType -> Maybe [Tag] -> SpotFleetTagSpecification
SpotFleetTagSpecification'
      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
"tag"
                      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 SpotFleetTagSpecification where
  hashWithSalt :: Int -> SpotFleetTagSpecification -> Int
hashWithSalt Int
_salt SpotFleetTagSpecification' {Maybe [Tag]
Maybe ResourceType
tags :: Maybe [Tag]
resourceType :: Maybe ResourceType
$sel:tags:SpotFleetTagSpecification' :: SpotFleetTagSpecification -> Maybe [Tag]
$sel:resourceType:SpotFleetTagSpecification' :: SpotFleetTagSpecification -> 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 SpotFleetTagSpecification where
  rnf :: SpotFleetTagSpecification -> ()
rnf SpotFleetTagSpecification' {Maybe [Tag]
Maybe ResourceType
tags :: Maybe [Tag]
resourceType :: Maybe ResourceType
$sel:tags:SpotFleetTagSpecification' :: SpotFleetTagSpecification -> Maybe [Tag]
$sel:resourceType:SpotFleetTagSpecification' :: SpotFleetTagSpecification -> 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

instance Data.ToQuery SpotFleetTagSpecification where
  toQuery :: SpotFleetTagSpecification -> QueryString
toQuery SpotFleetTagSpecification' {Maybe [Tag]
Maybe ResourceType
tags :: Maybe [Tag]
resourceType :: Maybe ResourceType
$sel:tags:SpotFleetTagSpecification' :: SpotFleetTagSpecification -> Maybe [Tag]
$sel:resourceType:SpotFleetTagSpecification' :: SpotFleetTagSpecification -> Maybe ResourceType
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"ResourceType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ResourceType
resourceType,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Tag" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags)
      ]