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

-- | We are retiring EC2-Classic. We recommend that you migrate from
-- EC2-Classic to a VPC. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/vpc-migrate.html Migrate from EC2-Classic to a VPC>
-- in the /Amazon Elastic Compute Cloud User Guide/.
--
-- Describes a linked EC2-Classic instance.
--
-- /See:/ 'newClassicLinkInstance' smart constructor.
data ClassicLinkInstance = ClassicLinkInstance'
  { -- | A list of security groups.
    ClassicLinkInstance -> Maybe [GroupIdentifier]
groups :: Prelude.Maybe [GroupIdentifier],
    -- | The ID of the instance.
    ClassicLinkInstance -> Maybe Text
instanceId :: Prelude.Maybe Prelude.Text,
    -- | Any tags assigned to the instance.
    ClassicLinkInstance -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The ID of the VPC.
    ClassicLinkInstance -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text
  }
  deriving (ClassicLinkInstance -> ClassicLinkInstance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassicLinkInstance -> ClassicLinkInstance -> Bool
$c/= :: ClassicLinkInstance -> ClassicLinkInstance -> Bool
== :: ClassicLinkInstance -> ClassicLinkInstance -> Bool
$c== :: ClassicLinkInstance -> ClassicLinkInstance -> Bool
Prelude.Eq, ReadPrec [ClassicLinkInstance]
ReadPrec ClassicLinkInstance
Int -> ReadS ClassicLinkInstance
ReadS [ClassicLinkInstance]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassicLinkInstance]
$creadListPrec :: ReadPrec [ClassicLinkInstance]
readPrec :: ReadPrec ClassicLinkInstance
$creadPrec :: ReadPrec ClassicLinkInstance
readList :: ReadS [ClassicLinkInstance]
$creadList :: ReadS [ClassicLinkInstance]
readsPrec :: Int -> ReadS ClassicLinkInstance
$creadsPrec :: Int -> ReadS ClassicLinkInstance
Prelude.Read, Int -> ClassicLinkInstance -> ShowS
[ClassicLinkInstance] -> ShowS
ClassicLinkInstance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClassicLinkInstance] -> ShowS
$cshowList :: [ClassicLinkInstance] -> ShowS
show :: ClassicLinkInstance -> String
$cshow :: ClassicLinkInstance -> String
showsPrec :: Int -> ClassicLinkInstance -> ShowS
$cshowsPrec :: Int -> ClassicLinkInstance -> ShowS
Prelude.Show, forall x. Rep ClassicLinkInstance x -> ClassicLinkInstance
forall x. ClassicLinkInstance -> Rep ClassicLinkInstance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClassicLinkInstance x -> ClassicLinkInstance
$cfrom :: forall x. ClassicLinkInstance -> Rep ClassicLinkInstance x
Prelude.Generic)

-- |
-- Create a value of 'ClassicLinkInstance' 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:
--
-- 'groups', 'classicLinkInstance_groups' - A list of security groups.
--
-- 'instanceId', 'classicLinkInstance_instanceId' - The ID of the instance.
--
-- 'tags', 'classicLinkInstance_tags' - Any tags assigned to the instance.
--
-- 'vpcId', 'classicLinkInstance_vpcId' - The ID of the VPC.
newClassicLinkInstance ::
  ClassicLinkInstance
newClassicLinkInstance :: ClassicLinkInstance
newClassicLinkInstance =
  ClassicLinkInstance'
    { $sel:groups:ClassicLinkInstance' :: Maybe [GroupIdentifier]
groups = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:ClassicLinkInstance' :: Maybe Text
instanceId = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:ClassicLinkInstance' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:ClassicLinkInstance' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing
    }

-- | A list of security groups.
classicLinkInstance_groups :: Lens.Lens' ClassicLinkInstance (Prelude.Maybe [GroupIdentifier])
classicLinkInstance_groups :: Lens' ClassicLinkInstance (Maybe [GroupIdentifier])
classicLinkInstance_groups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClassicLinkInstance' {Maybe [GroupIdentifier]
groups :: Maybe [GroupIdentifier]
$sel:groups:ClassicLinkInstance' :: ClassicLinkInstance -> Maybe [GroupIdentifier]
groups} -> Maybe [GroupIdentifier]
groups) (\s :: ClassicLinkInstance
s@ClassicLinkInstance' {} Maybe [GroupIdentifier]
a -> ClassicLinkInstance
s {$sel:groups:ClassicLinkInstance' :: Maybe [GroupIdentifier]
groups = Maybe [GroupIdentifier]
a} :: ClassicLinkInstance) 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 ID of the instance.
classicLinkInstance_instanceId :: Lens.Lens' ClassicLinkInstance (Prelude.Maybe Prelude.Text)
classicLinkInstance_instanceId :: Lens' ClassicLinkInstance (Maybe Text)
classicLinkInstance_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClassicLinkInstance' {Maybe Text
instanceId :: Maybe Text
$sel:instanceId:ClassicLinkInstance' :: ClassicLinkInstance -> Maybe Text
instanceId} -> Maybe Text
instanceId) (\s :: ClassicLinkInstance
s@ClassicLinkInstance' {} Maybe Text
a -> ClassicLinkInstance
s {$sel:instanceId:ClassicLinkInstance' :: Maybe Text
instanceId = Maybe Text
a} :: ClassicLinkInstance)

-- | Any tags assigned to the instance.
classicLinkInstance_tags :: Lens.Lens' ClassicLinkInstance (Prelude.Maybe [Tag])
classicLinkInstance_tags :: Lens' ClassicLinkInstance (Maybe [Tag])
classicLinkInstance_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClassicLinkInstance' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:ClassicLinkInstance' :: ClassicLinkInstance -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: ClassicLinkInstance
s@ClassicLinkInstance' {} Maybe [Tag]
a -> ClassicLinkInstance
s {$sel:tags:ClassicLinkInstance' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: ClassicLinkInstance) 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 ID of the VPC.
classicLinkInstance_vpcId :: Lens.Lens' ClassicLinkInstance (Prelude.Maybe Prelude.Text)
classicLinkInstance_vpcId :: Lens' ClassicLinkInstance (Maybe Text)
classicLinkInstance_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClassicLinkInstance' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:ClassicLinkInstance' :: ClassicLinkInstance -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: ClassicLinkInstance
s@ClassicLinkInstance' {} Maybe Text
a -> ClassicLinkInstance
s {$sel:vpcId:ClassicLinkInstance' :: Maybe Text
vpcId = Maybe Text
a} :: ClassicLinkInstance)

instance Data.FromXML ClassicLinkInstance where
  parseXML :: [Node] -> Either String ClassicLinkInstance
parseXML [Node]
x =
    Maybe [GroupIdentifier]
-> Maybe Text -> Maybe [Tag] -> Maybe Text -> ClassicLinkInstance
ClassicLinkInstance'
      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
"groupSet"
                      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")
                  )
      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
"instanceId")
      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")
                  )
      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
"vpcId")

instance Prelude.Hashable ClassicLinkInstance where
  hashWithSalt :: Int -> ClassicLinkInstance -> Int
hashWithSalt Int
_salt ClassicLinkInstance' {Maybe [GroupIdentifier]
Maybe [Tag]
Maybe Text
vpcId :: Maybe Text
tags :: Maybe [Tag]
instanceId :: Maybe Text
groups :: Maybe [GroupIdentifier]
$sel:vpcId:ClassicLinkInstance' :: ClassicLinkInstance -> Maybe Text
$sel:tags:ClassicLinkInstance' :: ClassicLinkInstance -> Maybe [Tag]
$sel:instanceId:ClassicLinkInstance' :: ClassicLinkInstance -> Maybe Text
$sel:groups:ClassicLinkInstance' :: ClassicLinkInstance -> Maybe [GroupIdentifier]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [GroupIdentifier]
groups
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcId

instance Prelude.NFData ClassicLinkInstance where
  rnf :: ClassicLinkInstance -> ()
rnf ClassicLinkInstance' {Maybe [GroupIdentifier]
Maybe [Tag]
Maybe Text
vpcId :: Maybe Text
tags :: Maybe [Tag]
instanceId :: Maybe Text
groups :: Maybe [GroupIdentifier]
$sel:vpcId:ClassicLinkInstance' :: ClassicLinkInstance -> Maybe Text
$sel:tags:ClassicLinkInstance' :: ClassicLinkInstance -> Maybe [Tag]
$sel:instanceId:ClassicLinkInstance' :: ClassicLinkInstance -> Maybe Text
$sel:groups:ClassicLinkInstance' :: ClassicLinkInstance -> Maybe [GroupIdentifier]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [GroupIdentifier]
groups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcId