{-# 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.ImportRows
(
TableImportRowsResource
, tableImportRows
, TableImportRows
, tirStartLine
, tirEndLine
, tirTableId
, tirDelimiter
, tirEncoding
, tirIsStrict
) where
import Network.Google.FusionTables.Types
import Network.Google.Prelude
type TableImportRowsResource =
"fusiontables" :>
"v2" :>
"tables" :>
Capture "tableId" Text :>
"import" :>
QueryParam "startLine" (Textual Int32) :>
QueryParam "endLine" (Textual Int32) :>
QueryParam "delimiter" Text :>
QueryParam "encoding" Text :>
QueryParam "isStrict" Bool :>
QueryParam "alt" AltJSON :> Post '[JSON] Import
:<|>
"upload" :>
"fusiontables" :>
"v2" :>
"tables" :>
Capture "tableId" Text :>
"import" :>
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] Import
data TableImportRows = TableImportRows'
{ _tirStartLine :: !(Maybe (Textual Int32))
, _tirEndLine :: !(Maybe (Textual Int32))
, _tirTableId :: !Text
, _tirDelimiter :: !(Maybe Text)
, _tirEncoding :: !(Maybe Text)
, _tirIsStrict :: !(Maybe Bool)
} deriving (Eq,Show,Data,Typeable,Generic)
tableImportRows
:: Text
-> TableImportRows
tableImportRows pTirTableId_ =
TableImportRows'
{ _tirStartLine = Nothing
, _tirEndLine = Nothing
, _tirTableId = pTirTableId_
, _tirDelimiter = Nothing
, _tirEncoding = Nothing
, _tirIsStrict = Nothing
}
tirStartLine :: Lens' TableImportRows (Maybe Int32)
tirStartLine
= lens _tirStartLine (\ s a -> s{_tirStartLine = a})
. mapping _Coerce
tirEndLine :: Lens' TableImportRows (Maybe Int32)
tirEndLine
= lens _tirEndLine (\ s a -> s{_tirEndLine = a}) .
mapping _Coerce
tirTableId :: Lens' TableImportRows Text
tirTableId
= lens _tirTableId (\ s a -> s{_tirTableId = a})
tirDelimiter :: Lens' TableImportRows (Maybe Text)
tirDelimiter
= lens _tirDelimiter (\ s a -> s{_tirDelimiter = a})
tirEncoding :: Lens' TableImportRows (Maybe Text)
tirEncoding
= lens _tirEncoding (\ s a -> s{_tirEncoding = a})
tirIsStrict :: Lens' TableImportRows (Maybe Bool)
tirIsStrict
= lens _tirIsStrict (\ s a -> s{_tirIsStrict = a})
instance GoogleRequest TableImportRows where
type Rs TableImportRows = Import
type Scopes TableImportRows =
'["https://www.googleapis.com/auth/fusiontables"]
requestClient TableImportRows'{..}
= go _tirTableId _tirStartLine _tirEndLine
_tirDelimiter
_tirEncoding
_tirIsStrict
(Just AltJSON)
fusionTablesService
where go :<|> _
= buildClient
(Proxy :: Proxy TableImportRowsResource)
mempty
instance GoogleRequest (MediaUpload TableImportRows)
where
type Rs (MediaUpload TableImportRows) = Import
type Scopes (MediaUpload TableImportRows) =
Scopes TableImportRows
requestClient (MediaUpload TableImportRows'{..} body)
= go _tirTableId _tirStartLine _tirEndLine
_tirDelimiter
_tirEncoding
_tirIsStrict
(Just AltJSON)
(Just AltMedia)
body
fusionTablesService
where _ :<|> go
= buildClient
(Proxy :: Proxy TableImportRowsResource)
mempty