{-# 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 #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.APIGateway.Types.DocumentationPart
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.APIGateway.Types.DocumentationPart where

import Amazonka.APIGateway.Types.DocumentationPartLocation
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | A documentation part for a targeted API entity.
--
-- /See:/ 'newDocumentationPart' smart constructor.
data DocumentationPart = DocumentationPart'
  { -- | The DocumentationPart identifier, generated by API Gateway when the
    -- @DocumentationPart@ is created.
    DocumentationPart -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The location of the API entity to which the documentation applies. Valid
    -- fields depend on the targeted API entity type. All the valid location
    -- fields are not required. If not explicitly specified, a valid location
    -- field is treated as a wildcard and associated documentation content may
    -- be inherited by matching entities, unless overridden.
    DocumentationPart -> Maybe DocumentationPartLocation
location :: Prelude.Maybe DocumentationPartLocation,
    -- | A content map of API-specific key-value pairs describing the targeted
    -- API entity. The map must be encoded as a JSON string, e.g.,
    -- @\"{ \\\"description\\\": \\\"The API does ...\\\" }\"@. Only
    -- OpenAPI-compliant documentation-related fields from the properties map
    -- are exported and, hence, published as part of the API entity
    -- definitions, while the original documentation parts are exported in a
    -- OpenAPI extension of @x-amazon-apigateway-documentation@.
    DocumentationPart -> Maybe Text
properties :: Prelude.Maybe Prelude.Text
  }
  deriving (DocumentationPart -> DocumentationPart -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DocumentationPart -> DocumentationPart -> Bool
$c/= :: DocumentationPart -> DocumentationPart -> Bool
== :: DocumentationPart -> DocumentationPart -> Bool
$c== :: DocumentationPart -> DocumentationPart -> Bool
Prelude.Eq, ReadPrec [DocumentationPart]
ReadPrec DocumentationPart
Int -> ReadS DocumentationPart
ReadS [DocumentationPart]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DocumentationPart]
$creadListPrec :: ReadPrec [DocumentationPart]
readPrec :: ReadPrec DocumentationPart
$creadPrec :: ReadPrec DocumentationPart
readList :: ReadS [DocumentationPart]
$creadList :: ReadS [DocumentationPart]
readsPrec :: Int -> ReadS DocumentationPart
$creadsPrec :: Int -> ReadS DocumentationPart
Prelude.Read, Int -> DocumentationPart -> ShowS
[DocumentationPart] -> ShowS
DocumentationPart -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DocumentationPart] -> ShowS
$cshowList :: [DocumentationPart] -> ShowS
show :: DocumentationPart -> String
$cshow :: DocumentationPart -> String
showsPrec :: Int -> DocumentationPart -> ShowS
$cshowsPrec :: Int -> DocumentationPart -> ShowS
Prelude.Show, forall x. Rep DocumentationPart x -> DocumentationPart
forall x. DocumentationPart -> Rep DocumentationPart x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DocumentationPart x -> DocumentationPart
$cfrom :: forall x. DocumentationPart -> Rep DocumentationPart x
Prelude.Generic)

-- |
-- Create a value of 'DocumentationPart' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'id', 'documentationPart_id' - The DocumentationPart identifier, generated by API Gateway when the
-- @DocumentationPart@ is created.
--
-- 'location', 'documentationPart_location' - The location of the API entity to which the documentation applies. Valid
-- fields depend on the targeted API entity type. All the valid location
-- fields are not required. If not explicitly specified, a valid location
-- field is treated as a wildcard and associated documentation content may
-- be inherited by matching entities, unless overridden.
--
-- 'properties', 'documentationPart_properties' - A content map of API-specific key-value pairs describing the targeted
-- API entity. The map must be encoded as a JSON string, e.g.,
-- @\"{ \\\"description\\\": \\\"The API does ...\\\" }\"@. Only
-- OpenAPI-compliant documentation-related fields from the properties map
-- are exported and, hence, published as part of the API entity
-- definitions, while the original documentation parts are exported in a
-- OpenAPI extension of @x-amazon-apigateway-documentation@.
newDocumentationPart ::
  DocumentationPart
newDocumentationPart :: DocumentationPart
newDocumentationPart =
  DocumentationPart'
    { $sel:id:DocumentationPart' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:location:DocumentationPart' :: Maybe DocumentationPartLocation
location = forall a. Maybe a
Prelude.Nothing,
      $sel:properties:DocumentationPart' :: Maybe Text
properties = forall a. Maybe a
Prelude.Nothing
    }

-- | The DocumentationPart identifier, generated by API Gateway when the
-- @DocumentationPart@ is created.
documentationPart_id :: Lens.Lens' DocumentationPart (Prelude.Maybe Prelude.Text)
documentationPart_id :: Lens' DocumentationPart (Maybe Text)
documentationPart_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentationPart' {Maybe Text
id :: Maybe Text
$sel:id:DocumentationPart' :: DocumentationPart -> Maybe Text
id} -> Maybe Text
id) (\s :: DocumentationPart
s@DocumentationPart' {} Maybe Text
a -> DocumentationPart
s {$sel:id:DocumentationPart' :: Maybe Text
id = Maybe Text
a} :: DocumentationPart)

-- | The location of the API entity to which the documentation applies. Valid
-- fields depend on the targeted API entity type. All the valid location
-- fields are not required. If not explicitly specified, a valid location
-- field is treated as a wildcard and associated documentation content may
-- be inherited by matching entities, unless overridden.
documentationPart_location :: Lens.Lens' DocumentationPart (Prelude.Maybe DocumentationPartLocation)
documentationPart_location :: Lens' DocumentationPart (Maybe DocumentationPartLocation)
documentationPart_location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentationPart' {Maybe DocumentationPartLocation
location :: Maybe DocumentationPartLocation
$sel:location:DocumentationPart' :: DocumentationPart -> Maybe DocumentationPartLocation
location} -> Maybe DocumentationPartLocation
location) (\s :: DocumentationPart
s@DocumentationPart' {} Maybe DocumentationPartLocation
a -> DocumentationPart
s {$sel:location:DocumentationPart' :: Maybe DocumentationPartLocation
location = Maybe DocumentationPartLocation
a} :: DocumentationPart)

-- | A content map of API-specific key-value pairs describing the targeted
-- API entity. The map must be encoded as a JSON string, e.g.,
-- @\"{ \\\"description\\\": \\\"The API does ...\\\" }\"@. Only
-- OpenAPI-compliant documentation-related fields from the properties map
-- are exported and, hence, published as part of the API entity
-- definitions, while the original documentation parts are exported in a
-- OpenAPI extension of @x-amazon-apigateway-documentation@.
documentationPart_properties :: Lens.Lens' DocumentationPart (Prelude.Maybe Prelude.Text)
documentationPart_properties :: Lens' DocumentationPart (Maybe Text)
documentationPart_properties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentationPart' {Maybe Text
properties :: Maybe Text
$sel:properties:DocumentationPart' :: DocumentationPart -> Maybe Text
properties} -> Maybe Text
properties) (\s :: DocumentationPart
s@DocumentationPart' {} Maybe Text
a -> DocumentationPart
s {$sel:properties:DocumentationPart' :: Maybe Text
properties = Maybe Text
a} :: DocumentationPart)

instance Data.FromJSON DocumentationPart where
  parseJSON :: Value -> Parser DocumentationPart
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"DocumentationPart"
      ( \Object
x ->
          Maybe Text
-> Maybe DocumentationPartLocation
-> Maybe Text
-> DocumentationPart
DocumentationPart'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"id")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"location")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"properties")
      )

instance Prelude.Hashable DocumentationPart where
  hashWithSalt :: Int -> DocumentationPart -> Int
hashWithSalt Int
_salt DocumentationPart' {Maybe Text
Maybe DocumentationPartLocation
properties :: Maybe Text
location :: Maybe DocumentationPartLocation
id :: Maybe Text
$sel:properties:DocumentationPart' :: DocumentationPart -> Maybe Text
$sel:location:DocumentationPart' :: DocumentationPart -> Maybe DocumentationPartLocation
$sel:id:DocumentationPart' :: DocumentationPart -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DocumentationPartLocation
location
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
properties

instance Prelude.NFData DocumentationPart where
  rnf :: DocumentationPart -> ()
rnf DocumentationPart' {Maybe Text
Maybe DocumentationPartLocation
properties :: Maybe Text
location :: Maybe DocumentationPartLocation
id :: Maybe Text
$sel:properties:DocumentationPart' :: DocumentationPart -> Maybe Text
$sel:location:DocumentationPart' :: DocumentationPart -> Maybe DocumentationPartLocation
$sel:id:DocumentationPart' :: DocumentationPart -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DocumentationPartLocation
location
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
properties