{-# 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.ReplaceRows
(
TableReplaceRowsResource
, tableReplaceRows
, TableReplaceRows
, trrStartLine
, trrEndLine
, trrTableId
, trrDelimiter
, trrEncoding
, trrIsStrict
) where
import Network.Google.FusionTables.Types
import Network.Google.Prelude
type TableReplaceRowsResource =
"fusiontables" :>
"v2" :>
"tables" :>
Capture "tableId" Text :>
"replace" :>
QueryParam "startLine" (Textual Int32) :>
QueryParam "endLine" (Textual Int32) :>
QueryParam "delimiter" Text :>
QueryParam "encoding" Text :>
QueryParam "isStrict" Bool :>
QueryParam "alt" AltJSON :> Post '[JSON] Task
:<|>
"upload" :>
"fusiontables" :>
"v2" :>
"tables" :>
Capture "tableId" Text :>
"replace" :>
QueryParam "startLine" (Textual Int32) :>
QueryParam "endLine" (Textual Int32) :>
QueryParam "delimiter" Text :>
QueryParam "encoding" Text :>
QueryParam "isStrict" Bool :>
QueryParam "alt" AltJSON :>
QueryParam "uploadType" AltMedia :>
AltMedia :> Post '[JSON] Task
data TableReplaceRows = TableReplaceRows'
{ _trrStartLine :: !(Maybe (Textual Int32))
, _trrEndLine :: !(Maybe (Textual Int32))
, _trrTableId :: !Text
, _trrDelimiter :: !(Maybe Text)
, _trrEncoding :: !(Maybe Text)
, _trrIsStrict :: !(Maybe Bool)
} deriving (Eq,Show,Data,Typeable,Generic)
tableReplaceRows
:: Text
-> TableReplaceRows
tableReplaceRows pTrrTableId_ =
TableReplaceRows'
{ _trrStartLine = Nothing
, _trrEndLine = Nothing
, _trrTableId = pTrrTableId_
, _trrDelimiter = Nothing
, _trrEncoding = Nothing
, _trrIsStrict = Nothing
}
trrStartLine :: Lens' TableReplaceRows (Maybe Int32)
trrStartLine
= lens _trrStartLine (\ s a -> s{_trrStartLine = a})
. mapping _Coerce
trrEndLine :: Lens' TableReplaceRows (Maybe Int32)
trrEndLine
= lens _trrEndLine (\ s a -> s{_trrEndLine = a}) .
mapping _Coerce
trrTableId :: Lens' TableReplaceRows Text
trrTableId
= lens _trrTableId (\ s a -> s{_trrTableId = a})
trrDelimiter :: Lens' TableReplaceRows (Maybe Text)
trrDelimiter
= lens _trrDelimiter (\ s a -> s{_trrDelimiter = a})
trrEncoding :: Lens' TableReplaceRows (Maybe Text)
trrEncoding
= lens _trrEncoding (\ s a -> s{_trrEncoding = a})
trrIsStrict :: Lens' TableReplaceRows (Maybe Bool)
trrIsStrict
= lens _trrIsStrict (\ s a -> s{_trrIsStrict = a})
instance GoogleRequest TableReplaceRows where
type Rs TableReplaceRows = Task
type Scopes TableReplaceRows =
'["https://www.googleapis.com/auth/fusiontables"]
requestClient TableReplaceRows'{..}
= go _trrTableId _trrStartLine _trrEndLine
_trrDelimiter
_trrEncoding
_trrIsStrict
(Just AltJSON)
fusionTablesService
where go :<|> _
= buildClient
(Proxy :: Proxy TableReplaceRowsResource)
mempty
instance GoogleRequest (MediaUpload TableReplaceRows)
where
type Rs (MediaUpload TableReplaceRows) = Task
type Scopes (MediaUpload TableReplaceRows) =
Scopes TableReplaceRows
requestClient
(MediaUpload TableReplaceRows'{..} body)
= go _trrTableId _trrStartLine _trrEndLine
_trrDelimiter
_trrEncoding
_trrIsStrict
(Just AltJSON)
(Just AltMedia)
body
fusionTablesService
where _ :<|> go
= buildClient
(Proxy :: Proxy TableReplaceRowsResource)
mempty