{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Network.Google.Resource.Compute.Images.Insert
(
ImagesInsertResource
, imagesInsert
, ImagesInsert
, iiRequestId
, iiProject
, iiPayload
, iiForceCreate
) where
import Network.Google.Compute.Types
import Network.Google.Prelude
type ImagesInsertResource =
"compute" :>
"v1" :>
"projects" :>
Capture "project" Text :>
"global" :>
"images" :>
QueryParam "requestId" Text :>
QueryParam "forceCreate" Bool :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] Image :> Post '[JSON] Operation
data ImagesInsert = ImagesInsert'
{ _iiRequestId :: !(Maybe Text)
, _iiProject :: !Text
, _iiPayload :: !Image
, _iiForceCreate :: !(Maybe Bool)
} deriving (Eq,Show,Data,Typeable,Generic)
imagesInsert
:: Text
-> Image
-> ImagesInsert
imagesInsert pIiProject_ pIiPayload_ =
ImagesInsert'
{ _iiRequestId = Nothing
, _iiProject = pIiProject_
, _iiPayload = pIiPayload_
, _iiForceCreate = Nothing
}
iiRequestId :: Lens' ImagesInsert (Maybe Text)
iiRequestId
= lens _iiRequestId (\ s a -> s{_iiRequestId = a})
iiProject :: Lens' ImagesInsert Text
iiProject
= lens _iiProject (\ s a -> s{_iiProject = a})
iiPayload :: Lens' ImagesInsert Image
iiPayload
= lens _iiPayload (\ s a -> s{_iiPayload = a})
iiForceCreate :: Lens' ImagesInsert (Maybe Bool)
iiForceCreate
= lens _iiForceCreate
(\ s a -> s{_iiForceCreate = a})
instance GoogleRequest ImagesInsert where
type Rs ImagesInsert = Operation
type Scopes ImagesInsert =
'["https://www.googleapis.com/auth/cloud-platform",
"https://www.googleapis.com/auth/compute",
"https://www.googleapis.com/auth/devstorage.full_control",
"https://www.googleapis.com/auth/devstorage.read_only",
"https://www.googleapis.com/auth/devstorage.read_write"]
requestClient ImagesInsert'{..}
= go _iiProject _iiRequestId _iiForceCreate
(Just AltJSON)
_iiPayload
computeService
where go
= buildClient (Proxy :: Proxy ImagesInsertResource)
mempty