amazonka-apigateway-1.4.5: Amazon API Gateway SDK.

Copyright(c) 2013-2016 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.AWS.APIGateway.PutRestAPI

Contents

Description

A feature of the Amazon API Gateway control service for updating an existing API with an input of external API definitions. The update can take the form of merging the supplied definition into the existing API or overwriting the existing API.

Synopsis

Creating a Request

putRestAPI Source #

Creates a value of PutRestAPI with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • praMode - The mode query parameter to specify the update mode. Valid values are "merge" and "overwrite". By default, the update mode is "merge".
  • praFailOnWarnings - A query parameter to indicate whether to rollback the API update (true ) or not (false ) when a warning is encountered. The default value is false .
  • praParameters - Custom headers supplied as part of the request.
  • praRestAPIId - The identifier of the RestApi to be updated.
  • praBody - The PUT request body containing external API definitions. Currently, only Swagger definition JSON files are supported.

data PutRestAPI Source #

A PUT request to update an existing API, with external API definitions specified as the request body.

See: putRestAPI smart constructor.

Instances

Eq PutRestAPI Source # 
Data PutRestAPI Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PutRestAPI -> c PutRestAPI #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PutRestAPI #

toConstr :: PutRestAPI -> Constr #

dataTypeOf :: PutRestAPI -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PutRestAPI) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PutRestAPI) #

gmapT :: (forall b. Data b => b -> b) -> PutRestAPI -> PutRestAPI #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PutRestAPI -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PutRestAPI -> r #

gmapQ :: (forall d. Data d => d -> u) -> PutRestAPI -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PutRestAPI -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PutRestAPI -> m PutRestAPI #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PutRestAPI -> m PutRestAPI #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PutRestAPI -> m PutRestAPI #

Show PutRestAPI Source # 
Generic PutRestAPI Source # 

Associated Types

type Rep PutRestAPI :: * -> * #

Hashable PutRestAPI Source # 
NFData PutRestAPI Source # 

Methods

rnf :: PutRestAPI -> () #

AWSRequest PutRestAPI Source # 
ToBody PutRestAPI Source # 

Methods

toBody :: PutRestAPI -> RqBody #

ToPath PutRestAPI Source # 
ToHeaders PutRestAPI Source # 

Methods

toHeaders :: PutRestAPI -> [Header] #

ToQuery PutRestAPI Source # 
type Rep PutRestAPI Source # 
type Rep PutRestAPI = D1 (MetaData "PutRestAPI" "Network.AWS.APIGateway.PutRestAPI" "amazonka-apigateway-1.4.5-BIK2fycuXdJFBbWQ9Hqf16" False) (C1 (MetaCons "PutRestAPI'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_praMode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PutMode))) (S1 (MetaSel (Just Symbol "_praFailOnWarnings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_praParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Map Text Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_praRestAPIId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_praBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap Text Value)))))))
type Rs PutRestAPI Source # 

Request Lenses

praMode :: Lens' PutRestAPI (Maybe PutMode) Source #

The mode query parameter to specify the update mode. Valid values are "merge" and "overwrite". By default, the update mode is "merge".

praFailOnWarnings :: Lens' PutRestAPI (Maybe Bool) Source #

A query parameter to indicate whether to rollback the API update (true ) or not (false ) when a warning is encountered. The default value is false .

praParameters :: Lens' PutRestAPI (HashMap Text Text) Source #

Custom headers supplied as part of the request.

praRestAPIId :: Lens' PutRestAPI Text Source #

The identifier of the RestApi to be updated.

praBody :: Lens' PutRestAPI (HashMap Text Value) Source #

The PUT request body containing external API definitions. Currently, only Swagger definition JSON files are supported.

Destructuring the Response

restAPI :: RestAPI Source #

Creates a value of RestAPI with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • raBinaryMediaTypes - The list of binary media types supported by the RestApi . By default, the RestApi supports only UTF-8-encoded text payloads.
  • raWarnings - The warning messages reported when failonwarnings is turned on during API import.
  • raCreatedDate - The date when the API was created, in ISO 8601 format .
  • raName - The API's name.
  • raVersion - A version identifier for the API.
  • raId - The API's identifier. This identifier is unique across all of your APIs in Amazon API Gateway.
  • raDescription - The API's description.

data RestAPI Source #

Represents a REST API.

Create an API

See: restAPI smart constructor.

Instances

Eq RestAPI Source # 

Methods

(==) :: RestAPI -> RestAPI -> Bool #

(/=) :: RestAPI -> RestAPI -> Bool #

Data RestAPI Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RestAPI -> c RestAPI #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RestAPI #

toConstr :: RestAPI -> Constr #

dataTypeOf :: RestAPI -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RestAPI) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RestAPI) #

gmapT :: (forall b. Data b => b -> b) -> RestAPI -> RestAPI #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RestAPI -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RestAPI -> r #

gmapQ :: (forall d. Data d => d -> u) -> RestAPI -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RestAPI -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RestAPI -> m RestAPI #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RestAPI -> m RestAPI #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RestAPI -> m RestAPI #

Read RestAPI Source # 
Show RestAPI Source # 
Generic RestAPI Source # 

Associated Types

type Rep RestAPI :: * -> * #

Methods

from :: RestAPI -> Rep RestAPI x #

to :: Rep RestAPI x -> RestAPI #

Hashable RestAPI Source # 

Methods

hashWithSalt :: Int -> RestAPI -> Int #

hash :: RestAPI -> Int #

FromJSON RestAPI Source # 
NFData RestAPI Source # 

Methods

rnf :: RestAPI -> () #

type Rep RestAPI Source # 

Response Lenses

raBinaryMediaTypes :: Lens' RestAPI [Text] Source #

The list of binary media types supported by the RestApi . By default, the RestApi supports only UTF-8-encoded text payloads.

raWarnings :: Lens' RestAPI [Text] Source #

The warning messages reported when failonwarnings is turned on during API import.

raCreatedDate :: Lens' RestAPI (Maybe UTCTime) Source #

The date when the API was created, in ISO 8601 format .

raName :: Lens' RestAPI (Maybe Text) Source #

The API's name.

raVersion :: Lens' RestAPI (Maybe Text) Source #

A version identifier for the API.

raId :: Lens' RestAPI (Maybe Text) Source #

The API's identifier. This identifier is unique across all of your APIs in Amazon API Gateway.

raDescription :: Lens' RestAPI (Maybe Text) Source #

The API's description.