{-# 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 #-}
module Amazonka.EC2.Types.TransitGatewayPolicyTable 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.Tag
import Amazonka.EC2.Types.TransitGatewayPolicyTableState
import qualified Amazonka.Prelude as Prelude
data TransitGatewayPolicyTable = TransitGatewayPolicyTable'
{
TransitGatewayPolicyTable -> Maybe ISO8601
creationTime :: Prelude.Maybe Data.ISO8601,
TransitGatewayPolicyTable -> Maybe TransitGatewayPolicyTableState
state :: Prelude.Maybe TransitGatewayPolicyTableState,
TransitGatewayPolicyTable -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
TransitGatewayPolicyTable -> Maybe Text
transitGatewayId :: Prelude.Maybe Prelude.Text,
TransitGatewayPolicyTable -> Maybe Text
transitGatewayPolicyTableId :: Prelude.Maybe Prelude.Text
}
deriving (TransitGatewayPolicyTable -> TransitGatewayPolicyTable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransitGatewayPolicyTable -> TransitGatewayPolicyTable -> Bool
$c/= :: TransitGatewayPolicyTable -> TransitGatewayPolicyTable -> Bool
== :: TransitGatewayPolicyTable -> TransitGatewayPolicyTable -> Bool
$c== :: TransitGatewayPolicyTable -> TransitGatewayPolicyTable -> Bool
Prelude.Eq, ReadPrec [TransitGatewayPolicyTable]
ReadPrec TransitGatewayPolicyTable
Int -> ReadS TransitGatewayPolicyTable
ReadS [TransitGatewayPolicyTable]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TransitGatewayPolicyTable]
$creadListPrec :: ReadPrec [TransitGatewayPolicyTable]
readPrec :: ReadPrec TransitGatewayPolicyTable
$creadPrec :: ReadPrec TransitGatewayPolicyTable
readList :: ReadS [TransitGatewayPolicyTable]
$creadList :: ReadS [TransitGatewayPolicyTable]
readsPrec :: Int -> ReadS TransitGatewayPolicyTable
$creadsPrec :: Int -> ReadS TransitGatewayPolicyTable
Prelude.Read, Int -> TransitGatewayPolicyTable -> ShowS
[TransitGatewayPolicyTable] -> ShowS
TransitGatewayPolicyTable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransitGatewayPolicyTable] -> ShowS
$cshowList :: [TransitGatewayPolicyTable] -> ShowS
show :: TransitGatewayPolicyTable -> String
$cshow :: TransitGatewayPolicyTable -> String
showsPrec :: Int -> TransitGatewayPolicyTable -> ShowS
$cshowsPrec :: Int -> TransitGatewayPolicyTable -> ShowS
Prelude.Show, forall x.
Rep TransitGatewayPolicyTable x -> TransitGatewayPolicyTable
forall x.
TransitGatewayPolicyTable -> Rep TransitGatewayPolicyTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep TransitGatewayPolicyTable x -> TransitGatewayPolicyTable
$cfrom :: forall x.
TransitGatewayPolicyTable -> Rep TransitGatewayPolicyTable x
Prelude.Generic)
newTransitGatewayPolicyTable ::
TransitGatewayPolicyTable
newTransitGatewayPolicyTable :: TransitGatewayPolicyTable
newTransitGatewayPolicyTable =
TransitGatewayPolicyTable'
{ $sel:creationTime:TransitGatewayPolicyTable' :: Maybe ISO8601
creationTime =
forall a. Maybe a
Prelude.Nothing,
$sel:state:TransitGatewayPolicyTable' :: Maybe TransitGatewayPolicyTableState
state = forall a. Maybe a
Prelude.Nothing,
$sel:tags:TransitGatewayPolicyTable' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
$sel:transitGatewayId:TransitGatewayPolicyTable' :: Maybe Text
transitGatewayId = forall a. Maybe a
Prelude.Nothing,
$sel:transitGatewayPolicyTableId:TransitGatewayPolicyTable' :: Maybe Text
transitGatewayPolicyTableId = forall a. Maybe a
Prelude.Nothing
}
transitGatewayPolicyTable_creationTime :: Lens.Lens' TransitGatewayPolicyTable (Prelude.Maybe Prelude.UTCTime)
transitGatewayPolicyTable_creationTime :: Lens' TransitGatewayPolicyTable (Maybe UTCTime)
transitGatewayPolicyTable_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransitGatewayPolicyTable' {Maybe ISO8601
creationTime :: Maybe ISO8601
$sel:creationTime:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe ISO8601
creationTime} -> Maybe ISO8601
creationTime) (\s :: TransitGatewayPolicyTable
s@TransitGatewayPolicyTable' {} Maybe ISO8601
a -> TransitGatewayPolicyTable
s {$sel:creationTime:TransitGatewayPolicyTable' :: Maybe ISO8601
creationTime = Maybe ISO8601
a} :: TransitGatewayPolicyTable) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time
transitGatewayPolicyTable_state :: Lens.Lens' TransitGatewayPolicyTable (Prelude.Maybe TransitGatewayPolicyTableState)
transitGatewayPolicyTable_state :: Lens'
TransitGatewayPolicyTable (Maybe TransitGatewayPolicyTableState)
transitGatewayPolicyTable_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransitGatewayPolicyTable' {Maybe TransitGatewayPolicyTableState
state :: Maybe TransitGatewayPolicyTableState
$sel:state:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe TransitGatewayPolicyTableState
state} -> Maybe TransitGatewayPolicyTableState
state) (\s :: TransitGatewayPolicyTable
s@TransitGatewayPolicyTable' {} Maybe TransitGatewayPolicyTableState
a -> TransitGatewayPolicyTable
s {$sel:state:TransitGatewayPolicyTable' :: Maybe TransitGatewayPolicyTableState
state = Maybe TransitGatewayPolicyTableState
a} :: TransitGatewayPolicyTable)
transitGatewayPolicyTable_tags :: Lens.Lens' TransitGatewayPolicyTable (Prelude.Maybe [Tag])
transitGatewayPolicyTable_tags :: Lens' TransitGatewayPolicyTable (Maybe [Tag])
transitGatewayPolicyTable_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransitGatewayPolicyTable' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: TransitGatewayPolicyTable
s@TransitGatewayPolicyTable' {} Maybe [Tag]
a -> TransitGatewayPolicyTable
s {$sel:tags:TransitGatewayPolicyTable' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: TransitGatewayPolicyTable) 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
transitGatewayPolicyTable_transitGatewayId :: Lens.Lens' TransitGatewayPolicyTable (Prelude.Maybe Prelude.Text)
transitGatewayPolicyTable_transitGatewayId :: Lens' TransitGatewayPolicyTable (Maybe Text)
transitGatewayPolicyTable_transitGatewayId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransitGatewayPolicyTable' {Maybe Text
transitGatewayId :: Maybe Text
$sel:transitGatewayId:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe Text
transitGatewayId} -> Maybe Text
transitGatewayId) (\s :: TransitGatewayPolicyTable
s@TransitGatewayPolicyTable' {} Maybe Text
a -> TransitGatewayPolicyTable
s {$sel:transitGatewayId:TransitGatewayPolicyTable' :: Maybe Text
transitGatewayId = Maybe Text
a} :: TransitGatewayPolicyTable)
transitGatewayPolicyTable_transitGatewayPolicyTableId :: Lens.Lens' TransitGatewayPolicyTable (Prelude.Maybe Prelude.Text)
transitGatewayPolicyTable_transitGatewayPolicyTableId :: Lens' TransitGatewayPolicyTable (Maybe Text)
transitGatewayPolicyTable_transitGatewayPolicyTableId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransitGatewayPolicyTable' {Maybe Text
transitGatewayPolicyTableId :: Maybe Text
$sel:transitGatewayPolicyTableId:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe Text
transitGatewayPolicyTableId} -> Maybe Text
transitGatewayPolicyTableId) (\s :: TransitGatewayPolicyTable
s@TransitGatewayPolicyTable' {} Maybe Text
a -> TransitGatewayPolicyTable
s {$sel:transitGatewayPolicyTableId:TransitGatewayPolicyTable' :: Maybe Text
transitGatewayPolicyTableId = Maybe Text
a} :: TransitGatewayPolicyTable)
instance Data.FromXML TransitGatewayPolicyTable where
parseXML :: [Node] -> Either String TransitGatewayPolicyTable
parseXML [Node]
x =
Maybe ISO8601
-> Maybe TransitGatewayPolicyTableState
-> Maybe [Tag]
-> Maybe Text
-> Maybe Text
-> TransitGatewayPolicyTable
TransitGatewayPolicyTable'
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
"creationTime")
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
"state")
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
"transitGatewayId")
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
"transitGatewayPolicyTableId")
instance Prelude.Hashable TransitGatewayPolicyTable where
hashWithSalt :: Int -> TransitGatewayPolicyTable -> Int
hashWithSalt Int
_salt TransitGatewayPolicyTable' {Maybe [Tag]
Maybe Text
Maybe ISO8601
Maybe TransitGatewayPolicyTableState
transitGatewayPolicyTableId :: Maybe Text
transitGatewayId :: Maybe Text
tags :: Maybe [Tag]
state :: Maybe TransitGatewayPolicyTableState
creationTime :: Maybe ISO8601
$sel:transitGatewayPolicyTableId:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe Text
$sel:transitGatewayId:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe Text
$sel:tags:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe [Tag]
$sel:state:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe TransitGatewayPolicyTableState
$sel:creationTime:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe ISO8601
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
creationTime
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TransitGatewayPolicyTableState
state
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
transitGatewayId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
transitGatewayPolicyTableId
instance Prelude.NFData TransitGatewayPolicyTable where
rnf :: TransitGatewayPolicyTable -> ()
rnf TransitGatewayPolicyTable' {Maybe [Tag]
Maybe Text
Maybe ISO8601
Maybe TransitGatewayPolicyTableState
transitGatewayPolicyTableId :: Maybe Text
transitGatewayId :: Maybe Text
tags :: Maybe [Tag]
state :: Maybe TransitGatewayPolicyTableState
creationTime :: Maybe ISO8601
$sel:transitGatewayPolicyTableId:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe Text
$sel:transitGatewayId:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe Text
$sel:tags:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe [Tag]
$sel:state:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe TransitGatewayPolicyTableState
$sel:creationTime:TransitGatewayPolicyTable' :: TransitGatewayPolicyTable -> Maybe ISO8601
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
creationTime
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TransitGatewayPolicyTableState
state
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
transitGatewayId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
transitGatewayPolicyTableId