module Stratosphere.ApiGateway.DocumentationPart (
module Exports, DocumentationPart(..), mkDocumentationPart
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.ApiGateway.DocumentationPart.LocationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data DocumentationPart
=
DocumentationPart {DocumentationPart -> ()
haddock_workaround_ :: (),
DocumentationPart -> LocationProperty
location :: LocationProperty,
DocumentationPart -> Value Text
properties :: (Value Prelude.Text),
DocumentationPart -> Value Text
restApiId :: (Value Prelude.Text)}
deriving stock (DocumentationPart -> DocumentationPart -> Bool
(DocumentationPart -> DocumentationPart -> Bool)
-> (DocumentationPart -> DocumentationPart -> Bool)
-> Eq DocumentationPart
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DocumentationPart -> DocumentationPart -> Bool
== :: DocumentationPart -> DocumentationPart -> Bool
$c/= :: DocumentationPart -> DocumentationPart -> Bool
/= :: DocumentationPart -> DocumentationPart -> Bool
Prelude.Eq, Int -> DocumentationPart -> ShowS
[DocumentationPart] -> ShowS
DocumentationPart -> String
(Int -> DocumentationPart -> ShowS)
-> (DocumentationPart -> String)
-> ([DocumentationPart] -> ShowS)
-> Show DocumentationPart
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DocumentationPart -> ShowS
showsPrec :: Int -> DocumentationPart -> ShowS
$cshow :: DocumentationPart -> String
show :: DocumentationPart -> String
$cshowList :: [DocumentationPart] -> ShowS
showList :: [DocumentationPart] -> ShowS
Prelude.Show)
mkDocumentationPart ::
LocationProperty
-> Value Prelude.Text -> Value Prelude.Text -> DocumentationPart
mkDocumentationPart :: LocationProperty -> Value Text -> Value Text -> DocumentationPart
mkDocumentationPart LocationProperty
location Value Text
properties Value Text
restApiId
= DocumentationPart
{haddock_workaround_ :: ()
haddock_workaround_ = (), location :: LocationProperty
location = LocationProperty
location,
properties :: Value Text
properties = Value Text
properties, restApiId :: Value Text
restApiId = Value Text
restApiId}
instance ToResourceProperties DocumentationPart where
toResourceProperties :: DocumentationPart -> ResourceProperties
toResourceProperties DocumentationPart {()
Value Text
LocationProperty
haddock_workaround_ :: DocumentationPart -> ()
location :: DocumentationPart -> LocationProperty
properties :: DocumentationPart -> Value Text
restApiId :: DocumentationPart -> Value Text
haddock_workaround_ :: ()
location :: LocationProperty
properties :: Value Text
restApiId :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::ApiGateway::DocumentationPart",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"Location" Key -> LocationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= LocationProperty
location,
Key
"Properties" 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
properties, Key
"RestApiId" 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
restApiId]}
instance JSON.ToJSON DocumentationPart where
toJSON :: DocumentationPart -> Value
toJSON DocumentationPart {()
Value Text
LocationProperty
haddock_workaround_ :: DocumentationPart -> ()
location :: DocumentationPart -> LocationProperty
properties :: DocumentationPart -> Value Text
restApiId :: DocumentationPart -> Value Text
haddock_workaround_ :: ()
location :: LocationProperty
properties :: Value Text
restApiId :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"Location" Key -> LocationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= LocationProperty
location, Key
"Properties" 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
properties,
Key
"RestApiId" 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
restApiId]
instance Property "Location" DocumentationPart where
type PropertyType "Location" DocumentationPart = LocationProperty
set :: PropertyType "Location" DocumentationPart
-> DocumentationPart -> DocumentationPart
set PropertyType "Location" DocumentationPart
newValue DocumentationPart {()
Value Text
LocationProperty
haddock_workaround_ :: DocumentationPart -> ()
location :: DocumentationPart -> LocationProperty
properties :: DocumentationPart -> Value Text
restApiId :: DocumentationPart -> Value Text
haddock_workaround_ :: ()
location :: LocationProperty
properties :: Value Text
restApiId :: Value Text
..}
= DocumentationPart {location :: LocationProperty
location = PropertyType "Location" DocumentationPart
LocationProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
properties :: Value Text
restApiId :: Value Text
haddock_workaround_ :: ()
properties :: Value Text
restApiId :: Value Text
..}
instance Property "Properties" DocumentationPart where
type PropertyType "Properties" DocumentationPart = Value Prelude.Text
set :: PropertyType "Properties" DocumentationPart
-> DocumentationPart -> DocumentationPart
set PropertyType "Properties" DocumentationPart
newValue DocumentationPart {()
Value Text
LocationProperty
haddock_workaround_ :: DocumentationPart -> ()
location :: DocumentationPart -> LocationProperty
properties :: DocumentationPart -> Value Text
restApiId :: DocumentationPart -> Value Text
haddock_workaround_ :: ()
location :: LocationProperty
properties :: Value Text
restApiId :: Value Text
..}
= DocumentationPart {properties :: Value Text
properties = PropertyType "Properties" DocumentationPart
Value Text
newValue, ()
Value Text
LocationProperty
haddock_workaround_ :: ()
location :: LocationProperty
restApiId :: Value Text
haddock_workaround_ :: ()
location :: LocationProperty
restApiId :: Value Text
..}
instance Property "RestApiId" DocumentationPart where
type PropertyType "RestApiId" DocumentationPart = Value Prelude.Text
set :: PropertyType "RestApiId" DocumentationPart
-> DocumentationPart -> DocumentationPart
set PropertyType "RestApiId" DocumentationPart
newValue DocumentationPart {()
Value Text
LocationProperty
haddock_workaround_ :: DocumentationPart -> ()
location :: DocumentationPart -> LocationProperty
properties :: DocumentationPart -> Value Text
restApiId :: DocumentationPart -> Value Text
haddock_workaround_ :: ()
location :: LocationProperty
properties :: Value Text
restApiId :: Value Text
..}
= DocumentationPart {restApiId :: Value Text
restApiId = PropertyType "RestApiId" DocumentationPart
Value Text
newValue, ()
Value Text
LocationProperty
haddock_workaround_ :: ()
location :: LocationProperty
properties :: Value Text
haddock_workaround_ :: ()
location :: LocationProperty
properties :: Value Text
..}