{-# 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.FusionTables.Table.Patch
(
TablePatchResource
, tablePatch
, TablePatch
, tpPayload
, tpReplaceViewDefinition
, tpTableId
) where
import Network.Google.FusionTables.Types
import Network.Google.Prelude
type TablePatchResource =
"fusiontables" :>
"v2" :>
"tables" :>
Capture "tableId" Text :>
QueryParam "replaceViewDefinition" Bool :>
QueryParam "alt" AltJSON :>
ReqBody '[JSON] Table :> Patch '[JSON] Table
data TablePatch = TablePatch'
{ _tpPayload :: !Table
, _tpReplaceViewDefinition :: !(Maybe Bool)
, _tpTableId :: !Text
} deriving (Eq,Show,Data,Typeable,Generic)
tablePatch
:: Table
-> Text
-> TablePatch
tablePatch pTpPayload_ pTpTableId_ =
TablePatch'
{ _tpPayload = pTpPayload_
, _tpReplaceViewDefinition = Nothing
, _tpTableId = pTpTableId_
}
tpPayload :: Lens' TablePatch Table
tpPayload
= lens _tpPayload (\ s a -> s{_tpPayload = a})
tpReplaceViewDefinition :: Lens' TablePatch (Maybe Bool)
tpReplaceViewDefinition
= lens _tpReplaceViewDefinition
(\ s a -> s{_tpReplaceViewDefinition = a})
tpTableId :: Lens' TablePatch Text
tpTableId
= lens _tpTableId (\ s a -> s{_tpTableId = a})
instance GoogleRequest TablePatch where
type Rs TablePatch = Table
type Scopes TablePatch =
'["https://www.googleapis.com/auth/fusiontables"]
requestClient TablePatch'{..}
= go _tpTableId _tpReplaceViewDefinition
(Just AltJSON)
_tpPayload
fusionTablesService
where go
= buildClient (Proxy :: Proxy TablePatchResource)
mempty