{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# 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.GetModel
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes an existing model defined for a RestApi resource.
module Amazonka.APIGateway.GetModel
  ( -- * Creating a Request
    GetModel (..),
    newGetModel,

    -- * Request Lenses
    getModel_flatten,
    getModel_restApiId,
    getModel_modelName,

    -- * Destructuring the Response
    Model (..),
    newModel,

    -- * Response Lenses
    model_contentType,
    model_description,
    model_id,
    model_name,
    model_schema,
  )
where

import Amazonka.APIGateway.Types
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
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Request to list information about a model in an existing RestApi
-- resource.
--
-- /See:/ 'newGetModel' smart constructor.
data GetModel = GetModel'
  { -- | A query parameter of a Boolean value to resolve (@true@) all external
    -- model references and returns a flattened model schema or not (@false@)
    -- The default is @false@.
    GetModel -> Maybe Bool
flatten :: Prelude.Maybe Prelude.Bool,
    -- | The RestApi identifier under which the Model exists.
    GetModel -> Text
restApiId :: Prelude.Text,
    -- | The name of the model as an identifier.
    GetModel -> Text
modelName :: Prelude.Text
  }
  deriving (GetModel -> GetModel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetModel -> GetModel -> Bool
$c/= :: GetModel -> GetModel -> Bool
== :: GetModel -> GetModel -> Bool
$c== :: GetModel -> GetModel -> Bool
Prelude.Eq, ReadPrec [GetModel]
ReadPrec GetModel
Int -> ReadS GetModel
ReadS [GetModel]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetModel]
$creadListPrec :: ReadPrec [GetModel]
readPrec :: ReadPrec GetModel
$creadPrec :: ReadPrec GetModel
readList :: ReadS [GetModel]
$creadList :: ReadS [GetModel]
readsPrec :: Int -> ReadS GetModel
$creadsPrec :: Int -> ReadS GetModel
Prelude.Read, Int -> GetModel -> ShowS
[GetModel] -> ShowS
GetModel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetModel] -> ShowS
$cshowList :: [GetModel] -> ShowS
show :: GetModel -> String
$cshow :: GetModel -> String
showsPrec :: Int -> GetModel -> ShowS
$cshowsPrec :: Int -> GetModel -> ShowS
Prelude.Show, forall x. Rep GetModel x -> GetModel
forall x. GetModel -> Rep GetModel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetModel x -> GetModel
$cfrom :: forall x. GetModel -> Rep GetModel x
Prelude.Generic)

-- |
-- Create a value of 'GetModel' 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:
--
-- 'flatten', 'getModel_flatten' - A query parameter of a Boolean value to resolve (@true@) all external
-- model references and returns a flattened model schema or not (@false@)
-- The default is @false@.
--
-- 'restApiId', 'getModel_restApiId' - The RestApi identifier under which the Model exists.
--
-- 'modelName', 'getModel_modelName' - The name of the model as an identifier.
newGetModel ::
  -- | 'restApiId'
  Prelude.Text ->
  -- | 'modelName'
  Prelude.Text ->
  GetModel
newGetModel :: Text -> Text -> GetModel
newGetModel Text
pRestApiId_ Text
pModelName_ =
  GetModel'
    { $sel:flatten:GetModel' :: Maybe Bool
flatten = forall a. Maybe a
Prelude.Nothing,
      $sel:restApiId:GetModel' :: Text
restApiId = Text
pRestApiId_,
      $sel:modelName:GetModel' :: Text
modelName = Text
pModelName_
    }

-- | A query parameter of a Boolean value to resolve (@true@) all external
-- model references and returns a flattened model schema or not (@false@)
-- The default is @false@.
getModel_flatten :: Lens.Lens' GetModel (Prelude.Maybe Prelude.Bool)
getModel_flatten :: Lens' GetModel (Maybe Bool)
getModel_flatten = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetModel' {Maybe Bool
flatten :: Maybe Bool
$sel:flatten:GetModel' :: GetModel -> Maybe Bool
flatten} -> Maybe Bool
flatten) (\s :: GetModel
s@GetModel' {} Maybe Bool
a -> GetModel
s {$sel:flatten:GetModel' :: Maybe Bool
flatten = Maybe Bool
a} :: GetModel)

-- | The RestApi identifier under which the Model exists.
getModel_restApiId :: Lens.Lens' GetModel Prelude.Text
getModel_restApiId :: Lens' GetModel Text
getModel_restApiId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetModel' {Text
restApiId :: Text
$sel:restApiId:GetModel' :: GetModel -> Text
restApiId} -> Text
restApiId) (\s :: GetModel
s@GetModel' {} Text
a -> GetModel
s {$sel:restApiId:GetModel' :: Text
restApiId = Text
a} :: GetModel)

-- | The name of the model as an identifier.
getModel_modelName :: Lens.Lens' GetModel Prelude.Text
getModel_modelName :: Lens' GetModel Text
getModel_modelName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetModel' {Text
modelName :: Text
$sel:modelName:GetModel' :: GetModel -> Text
modelName} -> Text
modelName) (\s :: GetModel
s@GetModel' {} Text
a -> GetModel
s {$sel:modelName:GetModel' :: Text
modelName = Text
a} :: GetModel)

instance Core.AWSRequest GetModel where
  type AWSResponse GetModel = Model
  request :: (Service -> Service) -> GetModel -> Request GetModel
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetModel
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetModel)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      (\Int
s ResponseHeaders
h Object
x -> forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)

instance Prelude.Hashable GetModel where
  hashWithSalt :: Int -> GetModel -> Int
hashWithSalt Int
_salt GetModel' {Maybe Bool
Text
modelName :: Text
restApiId :: Text
flatten :: Maybe Bool
$sel:modelName:GetModel' :: GetModel -> Text
$sel:restApiId:GetModel' :: GetModel -> Text
$sel:flatten:GetModel' :: GetModel -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
flatten
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
restApiId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
modelName

instance Prelude.NFData GetModel where
  rnf :: GetModel -> ()
rnf GetModel' {Maybe Bool
Text
modelName :: Text
restApiId :: Text
flatten :: Maybe Bool
$sel:modelName:GetModel' :: GetModel -> Text
$sel:restApiId:GetModel' :: GetModel -> Text
$sel:flatten:GetModel' :: GetModel -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
flatten
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
restApiId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
modelName

instance Data.ToHeaders GetModel where
  toHeaders :: GetModel -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Accept"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/json" :: Prelude.ByteString)
          ]
      )

instance Data.ToPath GetModel where
  toPath :: GetModel -> ByteString
toPath GetModel' {Maybe Bool
Text
modelName :: Text
restApiId :: Text
flatten :: Maybe Bool
$sel:modelName:GetModel' :: GetModel -> Text
$sel:restApiId:GetModel' :: GetModel -> Text
$sel:flatten:GetModel' :: GetModel -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/restapis/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
restApiId,
        ByteString
"/models/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
modelName
      ]

instance Data.ToQuery GetModel where
  toQuery :: GetModel -> QueryString
toQuery GetModel' {Maybe Bool
Text
modelName :: Text
restApiId :: Text
flatten :: Maybe Bool
$sel:modelName:GetModel' :: GetModel -> Text
$sel:restApiId:GetModel' :: GetModel -> Text
$sel:flatten:GetModel' :: GetModel -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"flatten" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
flatten]