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