module Stratosphere.EC2.NetworkInterface.Ipv6PrefixSpecificationProperty (
Ipv6PrefixSpecificationProperty(..),
mkIpv6PrefixSpecificationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data Ipv6PrefixSpecificationProperty
=
Ipv6PrefixSpecificationProperty {Ipv6PrefixSpecificationProperty -> ()
haddock_workaround_ :: (),
Ipv6PrefixSpecificationProperty -> Value Text
ipv6Prefix :: (Value Prelude.Text)}
deriving stock (Ipv6PrefixSpecificationProperty
-> Ipv6PrefixSpecificationProperty -> Bool
(Ipv6PrefixSpecificationProperty
-> Ipv6PrefixSpecificationProperty -> Bool)
-> (Ipv6PrefixSpecificationProperty
-> Ipv6PrefixSpecificationProperty -> Bool)
-> Eq Ipv6PrefixSpecificationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Ipv6PrefixSpecificationProperty
-> Ipv6PrefixSpecificationProperty -> Bool
== :: Ipv6PrefixSpecificationProperty
-> Ipv6PrefixSpecificationProperty -> Bool
$c/= :: Ipv6PrefixSpecificationProperty
-> Ipv6PrefixSpecificationProperty -> Bool
/= :: Ipv6PrefixSpecificationProperty
-> Ipv6PrefixSpecificationProperty -> Bool
Prelude.Eq, Int -> Ipv6PrefixSpecificationProperty -> ShowS
[Ipv6PrefixSpecificationProperty] -> ShowS
Ipv6PrefixSpecificationProperty -> String
(Int -> Ipv6PrefixSpecificationProperty -> ShowS)
-> (Ipv6PrefixSpecificationProperty -> String)
-> ([Ipv6PrefixSpecificationProperty] -> ShowS)
-> Show Ipv6PrefixSpecificationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Ipv6PrefixSpecificationProperty -> ShowS
showsPrec :: Int -> Ipv6PrefixSpecificationProperty -> ShowS
$cshow :: Ipv6PrefixSpecificationProperty -> String
show :: Ipv6PrefixSpecificationProperty -> String
$cshowList :: [Ipv6PrefixSpecificationProperty] -> ShowS
showList :: [Ipv6PrefixSpecificationProperty] -> ShowS
Prelude.Show)
mkIpv6PrefixSpecificationProperty ::
Value Prelude.Text -> Ipv6PrefixSpecificationProperty
mkIpv6PrefixSpecificationProperty :: Value Text -> Ipv6PrefixSpecificationProperty
mkIpv6PrefixSpecificationProperty Value Text
ipv6Prefix
= Ipv6PrefixSpecificationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), ipv6Prefix :: Value Text
ipv6Prefix = Value Text
ipv6Prefix}
instance ToResourceProperties Ipv6PrefixSpecificationProperty where
toResourceProperties :: Ipv6PrefixSpecificationProperty -> ResourceProperties
toResourceProperties Ipv6PrefixSpecificationProperty {()
Value Text
haddock_workaround_ :: Ipv6PrefixSpecificationProperty -> ()
ipv6Prefix :: Ipv6PrefixSpecificationProperty -> Value Text
haddock_workaround_ :: ()
ipv6Prefix :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::EC2::NetworkInterface.Ipv6PrefixSpecification",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"Ipv6Prefix" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
ipv6Prefix]}
instance JSON.ToJSON Ipv6PrefixSpecificationProperty where
toJSON :: Ipv6PrefixSpecificationProperty -> Value
toJSON Ipv6PrefixSpecificationProperty {()
Value Text
haddock_workaround_ :: Ipv6PrefixSpecificationProperty -> ()
ipv6Prefix :: Ipv6PrefixSpecificationProperty -> Value Text
haddock_workaround_ :: ()
ipv6Prefix :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object [Key
"Ipv6Prefix" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
ipv6Prefix]
instance Property "Ipv6Prefix" Ipv6PrefixSpecificationProperty where
type PropertyType "Ipv6Prefix" Ipv6PrefixSpecificationProperty = Value Prelude.Text
set :: PropertyType "Ipv6Prefix" Ipv6PrefixSpecificationProperty
-> Ipv6PrefixSpecificationProperty
-> Ipv6PrefixSpecificationProperty
set PropertyType "Ipv6Prefix" Ipv6PrefixSpecificationProperty
newValue Ipv6PrefixSpecificationProperty {()
Value Text
haddock_workaround_ :: Ipv6PrefixSpecificationProperty -> ()
ipv6Prefix :: Ipv6PrefixSpecificationProperty -> Value Text
haddock_workaround_ :: ()
ipv6Prefix :: Value Text
..}
= Ipv6PrefixSpecificationProperty {ipv6Prefix :: Value Text
ipv6Prefix = PropertyType "Ipv6Prefix" Ipv6PrefixSpecificationProperty
Value Text
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}