module Stratosphere.EC2.NetworkInterface.Ipv4PrefixSpecificationProperty (
        Ipv4PrefixSpecificationProperty(..),
        mkIpv4PrefixSpecificationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data Ipv4PrefixSpecificationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-ec2-networkinterface-ipv4prefixspecification.html>
    Ipv4PrefixSpecificationProperty {Ipv4PrefixSpecificationProperty -> ()
haddock_workaround_ :: (),
                                     -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-ec2-networkinterface-ipv4prefixspecification.html#cfn-ec2-networkinterface-ipv4prefixspecification-ipv4prefix>
                                     Ipv4PrefixSpecificationProperty -> Value Text
ipv4Prefix :: (Value Prelude.Text)}
  deriving stock (Ipv4PrefixSpecificationProperty
-> Ipv4PrefixSpecificationProperty -> Bool
(Ipv4PrefixSpecificationProperty
 -> Ipv4PrefixSpecificationProperty -> Bool)
-> (Ipv4PrefixSpecificationProperty
    -> Ipv4PrefixSpecificationProperty -> Bool)
-> Eq Ipv4PrefixSpecificationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Ipv4PrefixSpecificationProperty
-> Ipv4PrefixSpecificationProperty -> Bool
== :: Ipv4PrefixSpecificationProperty
-> Ipv4PrefixSpecificationProperty -> Bool
$c/= :: Ipv4PrefixSpecificationProperty
-> Ipv4PrefixSpecificationProperty -> Bool
/= :: Ipv4PrefixSpecificationProperty
-> Ipv4PrefixSpecificationProperty -> Bool
Prelude.Eq, Int -> Ipv4PrefixSpecificationProperty -> ShowS
[Ipv4PrefixSpecificationProperty] -> ShowS
Ipv4PrefixSpecificationProperty -> String
(Int -> Ipv4PrefixSpecificationProperty -> ShowS)
-> (Ipv4PrefixSpecificationProperty -> String)
-> ([Ipv4PrefixSpecificationProperty] -> ShowS)
-> Show Ipv4PrefixSpecificationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Ipv4PrefixSpecificationProperty -> ShowS
showsPrec :: Int -> Ipv4PrefixSpecificationProperty -> ShowS
$cshow :: Ipv4PrefixSpecificationProperty -> String
show :: Ipv4PrefixSpecificationProperty -> String
$cshowList :: [Ipv4PrefixSpecificationProperty] -> ShowS
showList :: [Ipv4PrefixSpecificationProperty] -> ShowS
Prelude.Show)
mkIpv4PrefixSpecificationProperty ::
  Value Prelude.Text -> Ipv4PrefixSpecificationProperty
mkIpv4PrefixSpecificationProperty :: Value Text -> Ipv4PrefixSpecificationProperty
mkIpv4PrefixSpecificationProperty Value Text
ipv4Prefix
  = Ipv4PrefixSpecificationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), ipv4Prefix :: Value Text
ipv4Prefix = Value Text
ipv4Prefix}
instance ToResourceProperties Ipv4PrefixSpecificationProperty where
  toResourceProperties :: Ipv4PrefixSpecificationProperty -> ResourceProperties
toResourceProperties Ipv4PrefixSpecificationProperty {()
Value Text
haddock_workaround_ :: Ipv4PrefixSpecificationProperty -> ()
ipv4Prefix :: Ipv4PrefixSpecificationProperty -> Value Text
haddock_workaround_ :: ()
ipv4Prefix :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::EC2::NetworkInterface.Ipv4PrefixSpecification",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"Ipv4Prefix" 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
ipv4Prefix]}
instance JSON.ToJSON Ipv4PrefixSpecificationProperty where
  toJSON :: Ipv4PrefixSpecificationProperty -> Value
toJSON Ipv4PrefixSpecificationProperty {()
Value Text
haddock_workaround_ :: Ipv4PrefixSpecificationProperty -> ()
ipv4Prefix :: Ipv4PrefixSpecificationProperty -> Value Text
haddock_workaround_ :: ()
ipv4Prefix :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"Ipv4Prefix" 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
ipv4Prefix]
instance Property "Ipv4Prefix" Ipv4PrefixSpecificationProperty where
  type PropertyType "Ipv4Prefix" Ipv4PrefixSpecificationProperty = Value Prelude.Text
  set :: PropertyType "Ipv4Prefix" Ipv4PrefixSpecificationProperty
-> Ipv4PrefixSpecificationProperty
-> Ipv4PrefixSpecificationProperty
set PropertyType "Ipv4Prefix" Ipv4PrefixSpecificationProperty
newValue Ipv4PrefixSpecificationProperty {()
Value Text
haddock_workaround_ :: Ipv4PrefixSpecificationProperty -> ()
ipv4Prefix :: Ipv4PrefixSpecificationProperty -> Value Text
haddock_workaround_ :: ()
ipv4Prefix :: Value Text
..}
    = Ipv4PrefixSpecificationProperty {ipv4Prefix :: Value Text
ipv4Prefix = PropertyType "Ipv4Prefix" Ipv4PrefixSpecificationProperty
Value Text
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}