gogol-sheets-0.2.0: Google Sheets SDK.

Copyright(c) 2015-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.Google.Sheets

Contents

Description

Reads and writes Google Sheets.

See: Google Sheets API Reference

Synopsis

Service Configuration

sheetsService :: ServiceConfig Source #

Default request referring to version v4 of the Google Sheets API. This contains the host and root path used as a starting point for constructing service requests.

OAuth Scopes

spreadsheetsReadOnlyScope :: Proxy '["https://www.googleapis.com/auth/spreadsheets.readonly"] Source #

View your Google Spreadsheets

driveReadOnlyScope :: Proxy '["https://www.googleapis.com/auth/drive.readonly"] Source #

View the files in your Google Drive

driveScope :: Proxy '["https://www.googleapis.com/auth/drive"] Source #

View and manage the files in your Google Drive

spreadsheetsScope :: Proxy '["https://www.googleapis.com/auth/spreadsheets"] Source #

View and manage your spreadsheets in Google Drive

API Declaration

Resources

sheets.spreadsheets.batchUpdate

sheets.spreadsheets.create

sheets.spreadsheets.get

sheets.spreadsheets.sheets.copyTo

sheets.spreadsheets.values.append

sheets.spreadsheets.values.batchClear

sheets.spreadsheets.values.batchGet

sheets.spreadsheets.values.batchUpdate

sheets.spreadsheets.values.clear

sheets.spreadsheets.values.get

sheets.spreadsheets.values.update

Types

PivotGroupSortValueBucket

data PivotGroupSortValueBucket Source #

Information about which values in a pivot group should be used for sorting.

See: pivotGroupSortValueBucket smart constructor.

Instances

Eq PivotGroupSortValueBucket Source # 
Data PivotGroupSortValueBucket Source # 

Methods

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

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

toConstr :: PivotGroupSortValueBucket -> Constr #

dataTypeOf :: PivotGroupSortValueBucket -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PivotGroupSortValueBucket Source # 
Generic PivotGroupSortValueBucket Source # 
ToJSON PivotGroupSortValueBucket Source # 
FromJSON PivotGroupSortValueBucket Source # 
type Rep PivotGroupSortValueBucket Source # 
type Rep PivotGroupSortValueBucket = D1 (MetaData "PivotGroupSortValueBucket" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "PivotGroupSortValueBucket'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pgsvbBuckets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ExtendedValue]))) (S1 (MetaSel (Just Symbol "_pgsvbValuesIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

pivotGroupSortValueBucket :: PivotGroupSortValueBucket Source #

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

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

pgsvbBuckets :: Lens' PivotGroupSortValueBucket [ExtendedValue] Source #

Determines the bucket from which values are chosen to sort. For example, in a pivot table with one row group & two column groups, the row group can list up to two values. The first value corresponds to a value within the first column group, and the second value corresponds to a value in the second column group. If no values are listed, this would indicate that the row should be sorted according to the "Grand Total" over the column groups. If a single value is listed, this would correspond to using the "Total" of that bucket.

pgsvbValuesIndex :: Lens' PivotGroupSortValueBucket (Maybe Int32) Source #

The offset in the PivotTable.values list which the values in this grouping should be sorted by.

ValueRange

data ValueRange Source #

Data within a range of the spreadsheet.

See: valueRange smart constructor.

Instances

Eq ValueRange Source # 
Data ValueRange Source # 

Methods

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

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

toConstr :: ValueRange -> Constr #

dataTypeOf :: ValueRange -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ValueRange Source # 
Generic ValueRange Source # 

Associated Types

type Rep ValueRange :: * -> * #

ToJSON ValueRange Source # 
FromJSON ValueRange Source # 
type Rep ValueRange Source # 
type Rep ValueRange = D1 (MetaData "ValueRange" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "ValueRange'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_vrValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [[JSONValue]]))) ((:*:) (S1 (MetaSel (Just Symbol "_vrRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_vrMajorDimension") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ValueRangeMajorDimension))))))

valueRange :: ValueRange Source #

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

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

vrValues :: Lens' ValueRange [[JSONValue]] Source #

The data that was read or to be written. This is an array of arrays, the outer array representing all the data and each inner array representing a major dimension. Each item in the inner array corresponds with one cell. For output, empty trailing rows and columns will not be included. For input, supported value types are: bool, string, and double. Null values will be skipped. To set a cell to an empty value, set the string value to an empty string.

vrRange :: Lens' ValueRange (Maybe Text) Source #

The range the values cover, in A1 notation. For output, this range indicates the entire requested range, even though the values will exclude trailing rows and columns. When appending values, this field represents the range to search for a table, after which values will be appended.

vrMajorDimension :: Lens' ValueRange (Maybe ValueRangeMajorDimension) Source #

The major dimension of the values. For output, if the spreadsheet data is: `A1=1,B1=2,A2=3,B2=4`, then requesting `range=A1:B2,majorDimension=ROWS` will return `[[1,2],[3,4]]`, whereas requesting `range=A1:B2,majorDimension=COLUMNS` will return `[[1,3],[2,4]]`. For input, with `range=A1:B2,majorDimension=ROWS` then `[[1,2],[3,4]]` will set `A1=1,B1=2,A2=3,B2=4`. With `range=A1:B2,majorDimension=COLUMNS` then `[[1,2],[3,4]]` will set `A1=1,B1=3,A2=2,B2=4`. When writing, if this field is not set, it defaults to ROWS.

SortRangeRequest

data SortRangeRequest Source #

Sorts data in rows based on a sort order per column.

See: sortRangeRequest smart constructor.

Instances

Eq SortRangeRequest Source # 
Data SortRangeRequest Source # 

Methods

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

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

toConstr :: SortRangeRequest -> Constr #

dataTypeOf :: SortRangeRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SortRangeRequest Source # 
Generic SortRangeRequest Source # 
ToJSON SortRangeRequest Source # 
FromJSON SortRangeRequest Source # 
type Rep SortRangeRequest Source # 
type Rep SortRangeRequest = D1 (MetaData "SortRangeRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "SortRangeRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_srrSortSpecs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SortSpec]))) (S1 (MetaSel (Just Symbol "_srrRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange)))))

sortRangeRequest :: SortRangeRequest Source #

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

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

srrSortSpecs :: Lens' SortRangeRequest [SortSpec] Source #

The sort order per column. Later specifications are used when values are equal in the earlier specifications.

CopyPasteRequestPasteType

data CopyPasteRequestPasteType Source #

What kind of data to paste.

Constructors

PasteNormal

PASTE_NORMAL Paste values, formulas, formats, and merges.

PasteValues

PASTE_VALUES Paste the values ONLY without formats, formulas, or merges.

PasteFormat

PASTE_FORMAT Paste the format and data validation only.

PasteNoBOrders

PASTE_NO_BORDERS Like PASTE_NORMAL but without borders.

PasteFormula

PASTE_FORMULA Paste the formulas only.

PasteDataValidation

PASTE_DATA_VALIDATION Paste the data validation only.

PasteConditionalFormatting

PASTE_CONDITIONAL_FORMATTING Paste the conditional formatting rules only.

Instances

Enum CopyPasteRequestPasteType Source # 
Eq CopyPasteRequestPasteType Source # 
Data CopyPasteRequestPasteType Source # 

Methods

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

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

toConstr :: CopyPasteRequestPasteType -> Constr #

dataTypeOf :: CopyPasteRequestPasteType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CopyPasteRequestPasteType Source # 
Read CopyPasteRequestPasteType Source # 
Show CopyPasteRequestPasteType Source # 
Generic CopyPasteRequestPasteType Source # 
Hashable CopyPasteRequestPasteType Source # 
ToJSON CopyPasteRequestPasteType Source # 
FromJSON CopyPasteRequestPasteType Source # 
FromHttpApiData CopyPasteRequestPasteType Source # 
ToHttpApiData CopyPasteRequestPasteType Source # 
type Rep CopyPasteRequestPasteType Source # 
type Rep CopyPasteRequestPasteType = D1 (MetaData "CopyPasteRequestPasteType" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "PasteNormal" PrefixI False) U1) ((:+:) (C1 (MetaCons "PasteValues" PrefixI False) U1) (C1 (MetaCons "PasteFormat" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PasteNoBOrders" PrefixI False) U1) (C1 (MetaCons "PasteFormula" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PasteDataValidation" PrefixI False) U1) (C1 (MetaCons "PasteConditionalFormatting" PrefixI False) U1))))

DeleteNamedRangeRequest

data DeleteNamedRangeRequest Source #

Removes the named range with the given ID from the spreadsheet.

See: deleteNamedRangeRequest smart constructor.

Instances

Eq DeleteNamedRangeRequest Source # 
Data DeleteNamedRangeRequest Source # 

Methods

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

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

toConstr :: DeleteNamedRangeRequest -> Constr #

dataTypeOf :: DeleteNamedRangeRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DeleteNamedRangeRequest Source # 
Generic DeleteNamedRangeRequest Source # 
ToJSON DeleteNamedRangeRequest Source # 
FromJSON DeleteNamedRangeRequest Source # 
type Rep DeleteNamedRangeRequest Source # 
type Rep DeleteNamedRangeRequest = D1 (MetaData "DeleteNamedRangeRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "DeleteNamedRangeRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_dnrrNamedRangeId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

deleteNamedRangeRequest :: DeleteNamedRangeRequest Source #

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

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

dnrrNamedRangeId :: Lens' DeleteNamedRangeRequest (Maybe Text) Source #

The ID of the named range to delete.

UpdateNamedRangeRequest

data UpdateNamedRangeRequest Source #

Updates properties of the named range with the specified namedRangeId.

See: updateNamedRangeRequest smart constructor.

Instances

Eq UpdateNamedRangeRequest Source # 
Data UpdateNamedRangeRequest Source # 

Methods

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

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

toConstr :: UpdateNamedRangeRequest -> Constr #

dataTypeOf :: UpdateNamedRangeRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show UpdateNamedRangeRequest Source # 
Generic UpdateNamedRangeRequest Source # 
ToJSON UpdateNamedRangeRequest Source # 
FromJSON UpdateNamedRangeRequest Source # 
type Rep UpdateNamedRangeRequest Source # 
type Rep UpdateNamedRangeRequest = D1 (MetaData "UpdateNamedRangeRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "UpdateNamedRangeRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_unrrNamedRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NamedRange))) (S1 (MetaSel (Just Symbol "_unrrFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FieldMask)))))

updateNamedRangeRequest :: UpdateNamedRangeRequest Source #

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

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

unrrNamedRange :: Lens' UpdateNamedRangeRequest (Maybe NamedRange) Source #

The named range to update with the new properties.

unrrFields :: Lens' UpdateNamedRangeRequest (Maybe FieldMask) Source #

The fields that should be updated. At least one field must be specified. The root `namedRange` is implied and should not be specified. A single `"*"` can be used as short-hand for listing every field.

BasicChartAxisPosition

data BasicChartAxisPosition Source #

The position of this axis.

Constructors

BasicChartAxisPositionUnspecified

BASIC_CHART_AXIS_POSITION_UNSPECIFIED Default value, do not use.

BottomAxis

BOTTOM_AXIS The axis rendered at the bottom of a chart. For most charts, this is the standard major axis. For bar charts, this is a minor axis.

LeftAxis

LEFT_AXIS The axis rendered at the left of a chart. For most charts, this is a minor axis. For bar charts, this is the standard major axis.

RightAxis

RIGHT_AXIS The axis rendered at the right of a chart. For most charts, this is a minor axis. For bar charts, this is an unusual major axis.

Instances

Enum BasicChartAxisPosition Source # 
Eq BasicChartAxisPosition Source # 
Data BasicChartAxisPosition Source # 

Methods

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

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

toConstr :: BasicChartAxisPosition -> Constr #

dataTypeOf :: BasicChartAxisPosition -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BasicChartAxisPosition Source # 
Read BasicChartAxisPosition Source # 
Show BasicChartAxisPosition Source # 
Generic BasicChartAxisPosition Source # 
Hashable BasicChartAxisPosition Source # 
ToJSON BasicChartAxisPosition Source # 
FromJSON BasicChartAxisPosition Source # 
FromHttpApiData BasicChartAxisPosition Source # 
ToHttpApiData BasicChartAxisPosition Source # 
type Rep BasicChartAxisPosition Source # 
type Rep BasicChartAxisPosition = D1 (MetaData "BasicChartAxisPosition" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "BasicChartAxisPositionUnspecified" PrefixI False) U1) (C1 (MetaCons "BottomAxis" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LeftAxis" PrefixI False) U1) (C1 (MetaCons "RightAxis" PrefixI False) U1)))

ChartData

data ChartData Source #

The data included in a domain or series.

See: chartData smart constructor.

Instances

Eq ChartData Source # 
Data ChartData Source # 

Methods

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

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

toConstr :: ChartData -> Constr #

dataTypeOf :: ChartData -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ChartData Source # 
Generic ChartData Source # 

Associated Types

type Rep ChartData :: * -> * #

ToJSON ChartData Source # 
FromJSON ChartData Source # 
type Rep ChartData Source # 
type Rep ChartData = D1 (MetaData "ChartData" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "ChartData'" PrefixI True) (S1 (MetaSel (Just Symbol "_cdSourceRange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ChartSourceRange))))

chartData :: ChartData Source #

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

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

cdSourceRange :: Lens' ChartData (Maybe ChartSourceRange) Source #

The source ranges of the data.

BatchClearValuesRequest

data BatchClearValuesRequest Source #

The request for clearing more than one range of values in a spreadsheet.

See: batchClearValuesRequest smart constructor.

Instances

Eq BatchClearValuesRequest Source # 
Data BatchClearValuesRequest Source # 

Methods

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

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

toConstr :: BatchClearValuesRequest -> Constr #

dataTypeOf :: BatchClearValuesRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BatchClearValuesRequest Source # 
Generic BatchClearValuesRequest Source # 
ToJSON BatchClearValuesRequest Source # 
FromJSON BatchClearValuesRequest Source # 
type Rep BatchClearValuesRequest Source # 
type Rep BatchClearValuesRequest = D1 (MetaData "BatchClearValuesRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "BatchClearValuesRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_bcvrRanges") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Text]))))

batchClearValuesRequest :: BatchClearValuesRequest Source #

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

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

bcvrRanges :: Lens' BatchClearValuesRequest [Text] Source #

The ranges to clear, in A1 notation.

DeleteRangeRequestShiftDimension

data DeleteRangeRequestShiftDimension Source #

The dimension from which deleted cells will be replaced with. If ROWS, existing cells will be shifted upward to replace the deleted cells. If COLUMNS, existing cells will be shifted left to replace the deleted cells.

Constructors

DimensionUnspecified

DIMENSION_UNSPECIFIED The default value, do not use.

Rows

ROWS Operates on the rows of a sheet.

Columns

COLUMNS Operates on the columns of a sheet.

Instances

Enum DeleteRangeRequestShiftDimension Source # 
Eq DeleteRangeRequestShiftDimension Source # 
Data DeleteRangeRequestShiftDimension Source # 

Methods

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

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

toConstr :: DeleteRangeRequestShiftDimension -> Constr #

dataTypeOf :: DeleteRangeRequestShiftDimension -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DeleteRangeRequestShiftDimension Source # 
Read DeleteRangeRequestShiftDimension Source # 
Show DeleteRangeRequestShiftDimension Source # 
Generic DeleteRangeRequestShiftDimension Source # 
Hashable DeleteRangeRequestShiftDimension Source # 
ToJSON DeleteRangeRequestShiftDimension Source # 
FromJSON DeleteRangeRequestShiftDimension Source # 
FromHttpApiData DeleteRangeRequestShiftDimension Source # 
ToHttpApiData DeleteRangeRequestShiftDimension Source # 
type Rep DeleteRangeRequestShiftDimension Source # 
type Rep DeleteRangeRequestShiftDimension = D1 (MetaData "DeleteRangeRequestShiftDimension" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "DimensionUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "Rows" PrefixI False) U1) (C1 (MetaCons "Columns" PrefixI False) U1)))

BasicChartSeriesTargetAxis

data BasicChartSeriesTargetAxis Source #

The minor axis that will specify the range of values for this series. For example, if charting stocks over time, the "Volume" series may want to be pinned to the right with the prices pinned to the left, because the scale of trading volume is different than the scale of prices. It is an error to specify an axis that isn't a valid minor axis for the chart's type.

Constructors

BCSTABasicChartAxisPositionUnspecified

BASIC_CHART_AXIS_POSITION_UNSPECIFIED Default value, do not use.

BCSTABottomAxis

BOTTOM_AXIS The axis rendered at the bottom of a chart. For most charts, this is the standard major axis. For bar charts, this is a minor axis.

BCSTALeftAxis

LEFT_AXIS The axis rendered at the left of a chart. For most charts, this is a minor axis. For bar charts, this is the standard major axis.

BCSTARightAxis

RIGHT_AXIS The axis rendered at the right of a chart. For most charts, this is a minor axis. For bar charts, this is an unusual major axis.

Instances

Enum BasicChartSeriesTargetAxis Source # 
Eq BasicChartSeriesTargetAxis Source # 
Data BasicChartSeriesTargetAxis Source # 

Methods

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

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

toConstr :: BasicChartSeriesTargetAxis -> Constr #

dataTypeOf :: BasicChartSeriesTargetAxis -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BasicChartSeriesTargetAxis Source # 
Read BasicChartSeriesTargetAxis Source # 
Show BasicChartSeriesTargetAxis Source # 
Generic BasicChartSeriesTargetAxis Source # 
Hashable BasicChartSeriesTargetAxis Source # 
ToJSON BasicChartSeriesTargetAxis Source # 
FromJSON BasicChartSeriesTargetAxis Source # 
FromHttpApiData BasicChartSeriesTargetAxis Source # 
ToHttpApiData BasicChartSeriesTargetAxis Source # 
type Rep BasicChartSeriesTargetAxis Source # 
type Rep BasicChartSeriesTargetAxis = D1 (MetaData "BasicChartSeriesTargetAxis" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "BCSTABasicChartAxisPositionUnspecified" PrefixI False) U1) (C1 (MetaCons "BCSTABottomAxis" PrefixI False) U1)) ((:+:) (C1 (MetaCons "BCSTALeftAxis" PrefixI False) U1) (C1 (MetaCons "BCSTARightAxis" PrefixI False) U1)))

SpreadsheetProperties

data SpreadsheetProperties Source #

Properties of a spreadsheet.

See: spreadsheetProperties smart constructor.

Instances

Eq SpreadsheetProperties Source # 
Data SpreadsheetProperties Source # 

Methods

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

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

toConstr :: SpreadsheetProperties -> Constr #

dataTypeOf :: SpreadsheetProperties -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SpreadsheetProperties Source # 
Generic SpreadsheetProperties Source # 
ToJSON SpreadsheetProperties Source # 
FromJSON SpreadsheetProperties Source # 
type Rep SpreadsheetProperties Source # 
type Rep SpreadsheetProperties = D1 (MetaData "SpreadsheetProperties" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "SpreadsheetProperties'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_spDefaultFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CellFormat))) (S1 (MetaSel (Just Symbol "_spLocale") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_spAutoRecalc") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SpreadsheetPropertiesAutoRecalc))) ((:*:) (S1 (MetaSel (Just Symbol "_spTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_spTimeZone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

spreadsheetProperties :: SpreadsheetProperties Source #

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

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

spDefaultFormat :: Lens' SpreadsheetProperties (Maybe CellFormat) Source #

The default format of all cells in the spreadsheet. CellData.effectiveFormat will not be set if the cell's format is equal to this default format. This field is read-only.

spLocale :: Lens' SpreadsheetProperties (Maybe Text) Source #

The locale of the spreadsheet in one of the following formats: * an ISO 639-1 language code such as `en` * an ISO 639-2 language code such as `fil`, if no 639-1 code exists * a combination of the ISO language code and country code, such as `en_US` Note: when updating this field, not all locales/languages are supported.

spAutoRecalc :: Lens' SpreadsheetProperties (Maybe SpreadsheetPropertiesAutoRecalc) Source #

The amount of time to wait before volatile functions are recalculated.

spTitle :: Lens' SpreadsheetProperties (Maybe Text) Source #

The title of the spreadsheet.

spTimeZone :: Lens' SpreadsheetProperties (Maybe Text) Source #

The time zone of the spreadsheet, in CLDR format such as `America/New_York`. If the time zone isn't recognized, this may be a custom time zone such as `GMT-07:00`.

BOrders

data BOrders Source #

The borders of the cell.

See: bOrders smart constructor.

Instances

Eq BOrders Source # 

Methods

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

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

Data BOrders Source # 

Methods

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

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

toConstr :: BOrders -> Constr #

dataTypeOf :: BOrders -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BOrders Source # 
Generic BOrders Source # 

Associated Types

type Rep BOrders :: * -> * #

Methods

from :: BOrders -> Rep BOrders x #

to :: Rep BOrders x -> BOrders #

ToJSON BOrders Source # 
FromJSON BOrders Source # 
type Rep BOrders Source # 
type Rep BOrders = D1 (MetaData "BOrders" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BOrders'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_boBottom") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BOrder))) (S1 (MetaSel (Just Symbol "_boLeft") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BOrder)))) ((:*:) (S1 (MetaSel (Just Symbol "_boRight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BOrder))) (S1 (MetaSel (Just Symbol "_boTop") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BOrder))))))

bOrders :: BOrders Source #

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

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

boBottom :: Lens' BOrders (Maybe BOrder) Source #

The bottom border of the cell.

boLeft :: Lens' BOrders (Maybe BOrder) Source #

The left border of the cell.

boRight :: Lens' BOrders (Maybe BOrder) Source #

The right border of the cell.

boTop :: Lens' BOrders (Maybe BOrder) Source #

The top border of the cell.

TextFormatRun

data TextFormatRun Source #

A run of a text format. The format of this run continues until the start index of the next run. When updating, all fields must be set.

See: textFormatRun smart constructor.

Instances

Eq TextFormatRun Source # 
Data TextFormatRun Source # 

Methods

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

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

toConstr :: TextFormatRun -> Constr #

dataTypeOf :: TextFormatRun -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TextFormatRun Source # 
Generic TextFormatRun Source # 

Associated Types

type Rep TextFormatRun :: * -> * #

ToJSON TextFormatRun Source # 
FromJSON TextFormatRun Source # 
type Rep TextFormatRun Source # 
type Rep TextFormatRun = D1 (MetaData "TextFormatRun" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "TextFormatRun'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tfrFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TextFormat))) (S1 (MetaSel (Just Symbol "_tfrStartIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

textFormatRun :: TextFormatRun Source #

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

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

tfrFormat :: Lens' TextFormatRun (Maybe TextFormat) Source #

The format of this run. Absent values inherit the cell's format.

tfrStartIndex :: Lens' TextFormatRun (Maybe Int32) Source #

The character index where this run starts.

AddSheetRequest

data AddSheetRequest Source #

Adds a new sheet. When a sheet is added at a given index, all subsequent sheets' indexes are incremented. To add an object sheet, use AddChartRequest instead and specify EmbeddedObjectPosition.sheetId or EmbeddedObjectPosition.newSheet.

See: addSheetRequest smart constructor.

Instances

Eq AddSheetRequest Source # 
Data AddSheetRequest Source # 

Methods

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

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

toConstr :: AddSheetRequest -> Constr #

dataTypeOf :: AddSheetRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AddSheetRequest Source # 
Generic AddSheetRequest Source # 
ToJSON AddSheetRequest Source # 
FromJSON AddSheetRequest Source # 
type Rep AddSheetRequest Source # 
type Rep AddSheetRequest = D1 (MetaData "AddSheetRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "AddSheetRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_asrProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SheetProperties))))

addSheetRequest :: AddSheetRequest Source #

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

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

asrProperties :: Lens' AddSheetRequest (Maybe SheetProperties) Source #

The properties the new sheet should have. All properties are optional. The sheetId field is optional; if one is not set, an id will be randomly generated. (It is an error to specify the ID of a sheet that already exists.)

SortSpec

data SortSpec Source #

A sort order associated with a specific column or row.

See: sortSpec smart constructor.

Instances

Eq SortSpec Source # 
Data SortSpec Source # 

Methods

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

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

toConstr :: SortSpec -> Constr #

dataTypeOf :: SortSpec -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SortSpec Source # 
Generic SortSpec Source # 

Associated Types

type Rep SortSpec :: * -> * #

Methods

from :: SortSpec -> Rep SortSpec x #

to :: Rep SortSpec x -> SortSpec #

ToJSON SortSpec Source # 
FromJSON SortSpec Source # 
type Rep SortSpec Source # 
type Rep SortSpec = D1 (MetaData "SortSpec" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "SortSpec'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ssSortOrder") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SortSpecSortOrder))) (S1 (MetaSel (Just Symbol "_ssDimensionIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

sortSpec :: SortSpec Source #

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

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

ssSortOrder :: Lens' SortSpec (Maybe SortSpecSortOrder) Source #

The order data should be sorted.

ssDimensionIndex :: Lens' SortSpec (Maybe Int32) Source #

The dimension the sort should be applied to.

BatchUpdateValuesRequestResponseDateTimeRenderOption

data BatchUpdateValuesRequestResponseDateTimeRenderOption Source #

Determines how dates, times, and durations in the response should be rendered. This is ignored if response_value_render_option is FORMATTED_VALUE. The default dateTime render option is [DateTimeRenderOption.SERIAL_NUMBER].

Constructors

SerialNumber

SERIAL_NUMBER Instructs date, time, datetime, and duration fields to be output as doubles in "serial number" format, as popularized by Lotus 1-2-3. Days are counted from December 31st 1899 and are incremented by 1, and times are fractions of a day. For example, January 1st 1900 at noon would be 1.5, 1 because it's 1 day offset from December 31st 1899, and .5 because noon is half a day. February 1st 1900 at 3pm would be 32.625. This correctly treats the year 1900 as not a leap year.

FormattedString

FORMATTED_STRING Instructs date, time, datetime, and duration fields to be output as strings in their given number format (which is dependent on the spreadsheet locale).

Instances

Enum BatchUpdateValuesRequestResponseDateTimeRenderOption Source # 
Eq BatchUpdateValuesRequestResponseDateTimeRenderOption Source # 
Data BatchUpdateValuesRequestResponseDateTimeRenderOption Source # 

Methods

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

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

toConstr :: BatchUpdateValuesRequestResponseDateTimeRenderOption -> Constr #

dataTypeOf :: BatchUpdateValuesRequestResponseDateTimeRenderOption -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BatchUpdateValuesRequestResponseDateTimeRenderOption Source # 
Read BatchUpdateValuesRequestResponseDateTimeRenderOption Source # 
Show BatchUpdateValuesRequestResponseDateTimeRenderOption Source # 
Generic BatchUpdateValuesRequestResponseDateTimeRenderOption Source # 
Hashable BatchUpdateValuesRequestResponseDateTimeRenderOption Source # 
ToJSON BatchUpdateValuesRequestResponseDateTimeRenderOption Source # 
FromJSON BatchUpdateValuesRequestResponseDateTimeRenderOption Source # 
FromHttpApiData BatchUpdateValuesRequestResponseDateTimeRenderOption Source # 
ToHttpApiData BatchUpdateValuesRequestResponseDateTimeRenderOption Source # 
type Rep BatchUpdateValuesRequestResponseDateTimeRenderOption Source # 
type Rep BatchUpdateValuesRequestResponseDateTimeRenderOption = D1 (MetaData "BatchUpdateValuesRequestResponseDateTimeRenderOption" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "SerialNumber" PrefixI False) U1) (C1 (MetaCons "FormattedString" PrefixI False) U1))

CopyPasteRequest

data CopyPasteRequest Source #

Copies data from the source to the destination.

See: copyPasteRequest smart constructor.

Instances

Eq CopyPasteRequest Source # 
Data CopyPasteRequest Source # 

Methods

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

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

toConstr :: CopyPasteRequest -> Constr #

dataTypeOf :: CopyPasteRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CopyPasteRequest Source # 
Generic CopyPasteRequest Source # 
ToJSON CopyPasteRequest Source # 
FromJSON CopyPasteRequest Source # 
type Rep CopyPasteRequest Source # 
type Rep CopyPasteRequest = D1 (MetaData "CopyPasteRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "CopyPasteRequest'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cprDestination") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange))) (S1 (MetaSel (Just Symbol "_cprSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange)))) ((:*:) (S1 (MetaSel (Just Symbol "_cprPasteOrientation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CopyPasteRequestPasteOrientation))) (S1 (MetaSel (Just Symbol "_cprPasteType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CopyPasteRequestPasteType))))))

copyPasteRequest :: CopyPasteRequest Source #

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

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

cprDestination :: Lens' CopyPasteRequest (Maybe GridRange) Source #

The location to paste to. If the range covers a span that's a multiple of the source's height or width, then the data will be repeated to fill in the destination range. If the range is smaller than the source range, the entire source data will still be copied (beyond the end of the destination range).

cprSource :: Lens' CopyPasteRequest (Maybe GridRange) Source #

The source range to copy.

cprPasteOrientation :: Lens' CopyPasteRequest (Maybe CopyPasteRequestPasteOrientation) Source #

How that data should be oriented when pasting.

GridRange

data GridRange Source #

A range on a sheet. All indexes are zero-based. Indexes are half open, e.g the start index is inclusive and the end index is exclusive -- [start_index, end_index). Missing indexes indicate the range is unbounded on that side. For example, if `"Sheet1"` is sheet ID 0, then: `Sheet1!A1:A1 == sheet_id: 0, start_row_index: 0, end_row_index: 1, start_column_index: 0, end_column_index: 1` `Sheet1!A3:B4 == sheet_id: 0, start_row_index: 2, end_row_index: 4, start_column_index: 0, end_column_index: 2` `Sheet1!A:B == sheet_id: 0, start_column_index: 0, end_column_index: 2` `Sheet1!A5:B == sheet_id: 0, start_row_index: 4, start_column_index: 0, end_column_index: 2` `Sheet1 == sheet_id:0` The start index must always be less than or equal to the end index. If the start index equals the end index, then the range is empty. Empty ranges are typically not meaningful and are usually rendered in the UI as `#REF!`.

See: gridRange smart constructor.

Instances

Eq GridRange Source # 
Data GridRange Source # 

Methods

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

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

toConstr :: GridRange -> Constr #

dataTypeOf :: GridRange -> DataType #

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

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

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

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

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

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

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

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

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

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

Show GridRange Source # 
Generic GridRange Source # 

Associated Types

type Rep GridRange :: * -> * #

ToJSON GridRange Source # 
FromJSON GridRange Source # 
type Rep GridRange Source # 
type Rep GridRange = D1 (MetaData "GridRange" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "GridRange'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_grEndColumnIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_grStartColumnIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))) ((:*:) (S1 (MetaSel (Just Symbol "_grEndRowIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) ((:*:) (S1 (MetaSel (Just Symbol "_grStartRowIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_grSheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))))

gridRange :: GridRange Source #

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

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

grEndColumnIndex :: Lens' GridRange (Maybe Int32) Source #

The end column (exclusive) of the range, or not set if unbounded.

grStartColumnIndex :: Lens' GridRange (Maybe Int32) Source #

The start column (inclusive) of the range, or not set if unbounded.

grEndRowIndex :: Lens' GridRange (Maybe Int32) Source #

The end row (exclusive) of the range, or not set if unbounded.

grStartRowIndex :: Lens' GridRange (Maybe Int32) Source #

The start row (inclusive) of the range, or not set if unbounded.

grSheetId :: Lens' GridRange (Maybe Int32) Source #

The sheet this range is on.

AppendDimensionRequestDimension

data AppendDimensionRequestDimension Source #

Whether rows or columns should be appended.

Constructors

ADRDDimensionUnspecified

DIMENSION_UNSPECIFIED The default value, do not use.

ADRDRows

ROWS Operates on the rows of a sheet.

ADRDColumns

COLUMNS Operates on the columns of a sheet.

Instances

Enum AppendDimensionRequestDimension Source # 
Eq AppendDimensionRequestDimension Source # 
Data AppendDimensionRequestDimension Source # 

Methods

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

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

toConstr :: AppendDimensionRequestDimension -> Constr #

dataTypeOf :: AppendDimensionRequestDimension -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AppendDimensionRequestDimension Source # 
Read AppendDimensionRequestDimension Source # 
Show AppendDimensionRequestDimension Source # 
Generic AppendDimensionRequestDimension Source # 
Hashable AppendDimensionRequestDimension Source # 
ToJSON AppendDimensionRequestDimension Source # 
FromJSON AppendDimensionRequestDimension Source # 
FromHttpApiData AppendDimensionRequestDimension Source # 
ToHttpApiData AppendDimensionRequestDimension Source # 
type Rep AppendDimensionRequestDimension Source # 
type Rep AppendDimensionRequestDimension = D1 (MetaData "AppendDimensionRequestDimension" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "ADRDDimensionUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "ADRDRows" PrefixI False) U1) (C1 (MetaCons "ADRDColumns" PrefixI False) U1)))

AddFilterViewResponse

data AddFilterViewResponse Source #

The result of adding a filter view.

See: addFilterViewResponse smart constructor.

Instances

Eq AddFilterViewResponse Source # 
Data AddFilterViewResponse Source # 

Methods

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

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

toConstr :: AddFilterViewResponse -> Constr #

dataTypeOf :: AddFilterViewResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AddFilterViewResponse Source # 
Generic AddFilterViewResponse Source # 
ToJSON AddFilterViewResponse Source # 
FromJSON AddFilterViewResponse Source # 
type Rep AddFilterViewResponse Source # 
type Rep AddFilterViewResponse = D1 (MetaData "AddFilterViewResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "AddFilterViewResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_afvrFilter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilterView))))

addFilterViewResponse :: AddFilterViewResponse Source #

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

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

afvrFilter :: Lens' AddFilterViewResponse (Maybe FilterView) Source #

The newly added filter view.

DimensionRangeDimension

data DimensionRangeDimension Source #

The dimension of the span.

Constructors

DRDDimensionUnspecified

DIMENSION_UNSPECIFIED The default value, do not use.

DRDRows

ROWS Operates on the rows of a sheet.

DRDColumns

COLUMNS Operates on the columns of a sheet.

Instances

Enum DimensionRangeDimension Source # 
Eq DimensionRangeDimension Source # 
Data DimensionRangeDimension Source # 

Methods

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

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

toConstr :: DimensionRangeDimension -> Constr #

dataTypeOf :: DimensionRangeDimension -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DimensionRangeDimension Source # 
Read DimensionRangeDimension Source # 
Show DimensionRangeDimension Source # 
Generic DimensionRangeDimension Source # 
Hashable DimensionRangeDimension Source # 
ToJSON DimensionRangeDimension Source # 
FromJSON DimensionRangeDimension Source # 
FromHttpApiData DimensionRangeDimension Source # 
ToHttpApiData DimensionRangeDimension Source # 
type Rep DimensionRangeDimension Source # 
type Rep DimensionRangeDimension = D1 (MetaData "DimensionRangeDimension" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "DRDDimensionUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "DRDRows" PrefixI False) U1) (C1 (MetaCons "DRDColumns" PrefixI False) U1)))

BooleanCondition

data BooleanCondition Source #

A condition that can evaluate to true or false. BooleanConditions are used by conditional formatting, data validation, and the criteria in filters.

See: booleanCondition smart constructor.

Instances

Eq BooleanCondition Source # 
Data BooleanCondition Source # 

Methods

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

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

toConstr :: BooleanCondition -> Constr #

dataTypeOf :: BooleanCondition -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BooleanCondition Source # 
Generic BooleanCondition Source # 
ToJSON BooleanCondition Source # 
FromJSON BooleanCondition Source # 
type Rep BooleanCondition Source # 
type Rep BooleanCondition = D1 (MetaData "BooleanCondition" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BooleanCondition'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bcValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ConditionValue]))) (S1 (MetaSel (Just Symbol "_bcType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BooleanConditionType)))))

booleanCondition :: BooleanCondition Source #

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

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

bcValues :: Lens' BooleanCondition [ConditionValue] Source #

The values of the condition. The number of supported values depends on the condition type. Some support zero values, others one or two values, and ConditionType.ONE_OF_LIST supports an arbitrary number of values.

AutoResizeDimensionsRequest

data AutoResizeDimensionsRequest Source #

Automatically resizes one or more dimensions based on the contents of the cells in that dimension.

See: autoResizeDimensionsRequest smart constructor.

Instances

Eq AutoResizeDimensionsRequest Source # 
Data AutoResizeDimensionsRequest Source # 

Methods

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

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

toConstr :: AutoResizeDimensionsRequest -> Constr #

dataTypeOf :: AutoResizeDimensionsRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AutoResizeDimensionsRequest Source # 
Generic AutoResizeDimensionsRequest Source # 
ToJSON AutoResizeDimensionsRequest Source # 
FromJSON AutoResizeDimensionsRequest Source # 
type Rep AutoResizeDimensionsRequest Source # 
type Rep AutoResizeDimensionsRequest = D1 (MetaData "AutoResizeDimensionsRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "AutoResizeDimensionsRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_ardrDimensions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe DimensionRange))))

autoResizeDimensionsRequest :: AutoResizeDimensionsRequest Source #

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

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

ardrDimensions :: Lens' AutoResizeDimensionsRequest (Maybe DimensionRange) Source #

The dimensions to automatically resize. Only COLUMNS are supported.

DeleteRangeRequest

data DeleteRangeRequest Source #

Deletes a range of cells, shifting other cells into the deleted area.

See: deleteRangeRequest smart constructor.

Instances

Eq DeleteRangeRequest Source # 
Data DeleteRangeRequest Source # 

Methods

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

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

toConstr :: DeleteRangeRequest -> Constr #

dataTypeOf :: DeleteRangeRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DeleteRangeRequest Source # 
Generic DeleteRangeRequest Source # 
ToJSON DeleteRangeRequest Source # 
FromJSON DeleteRangeRequest Source # 
type Rep DeleteRangeRequest Source # 
type Rep DeleteRangeRequest = D1 (MetaData "DeleteRangeRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "DeleteRangeRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_drrShiftDimension") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeleteRangeRequestShiftDimension))) (S1 (MetaSel (Just Symbol "_drrRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange)))))

deleteRangeRequest :: DeleteRangeRequest Source #

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

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

drrShiftDimension :: Lens' DeleteRangeRequest (Maybe DeleteRangeRequestShiftDimension) Source #

The dimension from which deleted cells will be replaced with. If ROWS, existing cells will be shifted upward to replace the deleted cells. If COLUMNS, existing cells will be shifted left to replace the deleted cells.

drrRange :: Lens' DeleteRangeRequest (Maybe GridRange) Source #

The range of cells to delete.

Sheet

data Sheet Source #

A sheet in a spreadsheet.

See: sheet smart constructor.

Instances

Eq Sheet Source # 

Methods

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

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

Data Sheet Source # 

Methods

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

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

toConstr :: Sheet -> Constr #

dataTypeOf :: Sheet -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Sheet Source # 

Methods

showsPrec :: Int -> Sheet -> ShowS #

show :: Sheet -> String #

showList :: [Sheet] -> ShowS #

Generic Sheet Source # 

Associated Types

type Rep Sheet :: * -> * #

Methods

from :: Sheet -> Rep Sheet x #

to :: Rep Sheet x -> Sheet #

ToJSON Sheet Source # 
FromJSON Sheet Source # 
type Rep Sheet Source # 

sheet :: Sheet Source #

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

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

sData :: Lens' Sheet [GridData] Source #

Data in the grid, if this is a grid sheet. The number of GridData objects returned is dependent on the number of ranges requested on this sheet. For example, if this is representing `Sheet1`, and the spreadsheet was requested with ranges `Sheet1!A1:C10` and `Sheet1!D15:E20`, then the first GridData will have a startRow/startColumn of `0`, while the second one will have `startRow 14` (zero-based row 15), and `startColumn 3` (zero-based column D).

sMerges :: Lens' Sheet [GridRange] Source #

The ranges that are merged together.

sProtectedRanges :: Lens' Sheet [ProtectedRange] Source #

The protected ranges in this sheet.

sBandedRanges :: Lens' Sheet [BandedRange] Source #

The banded (i.e. alternating colors) ranges on this sheet.

sCharts :: Lens' Sheet [EmbeddedChart] Source #

The specifications of every chart on this sheet.

sBasicFilter :: Lens' Sheet (Maybe BasicFilter) Source #

The filter on this sheet, if any.

sConditionalFormats :: Lens' Sheet [ConditionalFormatRule] Source #

The conditional format rules in this sheet.

sFilterViews :: Lens' Sheet [FilterView] Source #

The filter views in this sheet.

sProperties :: Lens' Sheet (Maybe SheetProperties) Source #

The properties of the sheet.

GridCoordinate

data GridCoordinate Source #

A coordinate in a sheet. All indexes are zero-based.

See: gridCoordinate smart constructor.

Instances

Eq GridCoordinate Source # 
Data GridCoordinate Source # 

Methods

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

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

toConstr :: GridCoordinate -> Constr #

dataTypeOf :: GridCoordinate -> DataType #

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

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

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

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

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

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

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

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

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

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

Show GridCoordinate Source # 
Generic GridCoordinate Source # 

Associated Types

type Rep GridCoordinate :: * -> * #

ToJSON GridCoordinate Source # 
FromJSON GridCoordinate Source # 
type Rep GridCoordinate Source # 
type Rep GridCoordinate = D1 (MetaData "GridCoordinate" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "GridCoordinate'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gcColumnIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) ((:*:) (S1 (MetaSel (Just Symbol "_gcRowIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_gcSheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))))

gridCoordinate :: GridCoordinate Source #

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

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

gcColumnIndex :: Lens' GridCoordinate (Maybe Int32) Source #

The column index of the coordinate.

gcRowIndex :: Lens' GridCoordinate (Maybe Int32) Source #

The row index of the coordinate.

gcSheetId :: Lens' GridCoordinate (Maybe Int32) Source #

The sheet this coordinate is on.

ClearValuesResponse

data ClearValuesResponse Source #

The response when clearing a range of values in a spreadsheet.

See: clearValuesResponse smart constructor.

Instances

Eq ClearValuesResponse Source # 
Data ClearValuesResponse Source # 

Methods

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

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

toConstr :: ClearValuesResponse -> Constr #

dataTypeOf :: ClearValuesResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ClearValuesResponse Source # 
Generic ClearValuesResponse Source # 
ToJSON ClearValuesResponse Source # 
FromJSON ClearValuesResponse Source # 
type Rep ClearValuesResponse Source # 
type Rep ClearValuesResponse = D1 (MetaData "ClearValuesResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "ClearValuesResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cvrClearedRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cvrSpreadsheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

clearValuesResponse :: ClearValuesResponse Source #

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

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

cvrClearedRange :: Lens' ClearValuesResponse (Maybe Text) Source #

The range (in A1 notation) that was cleared. (If the request was for an unbounded range or a ranger larger than the bounds of the sheet, this will be the actual range that was cleared, bounded to the sheet's limits.)

cvrSpreadsheetId :: Lens' ClearValuesResponse (Maybe Text) Source #

The spreadsheet the updates were applied to.

ClearBasicFilterRequest

data ClearBasicFilterRequest Source #

Clears the basic filter, if any exists on the sheet.

See: clearBasicFilterRequest smart constructor.

Instances

Eq ClearBasicFilterRequest Source # 
Data ClearBasicFilterRequest Source # 

Methods

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

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

toConstr :: ClearBasicFilterRequest -> Constr #

dataTypeOf :: ClearBasicFilterRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ClearBasicFilterRequest Source # 
Generic ClearBasicFilterRequest Source # 
ToJSON ClearBasicFilterRequest Source # 
FromJSON ClearBasicFilterRequest Source # 
type Rep ClearBasicFilterRequest Source # 
type Rep ClearBasicFilterRequest = D1 (MetaData "ClearBasicFilterRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "ClearBasicFilterRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_cbfrSheetId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Textual Int32)))))

clearBasicFilterRequest :: ClearBasicFilterRequest Source #

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

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

cbfrSheetId :: Lens' ClearBasicFilterRequest (Maybe Int32) Source #

The sheet ID on which the basic filter should be cleared.

UpdateEmbeddedObjectPositionRequest

data UpdateEmbeddedObjectPositionRequest Source #

Update an embedded object's position (such as a moving or resizing a chart or image).

See: updateEmbeddedObjectPositionRequest smart constructor.

Instances

Eq UpdateEmbeddedObjectPositionRequest Source # 
Data UpdateEmbeddedObjectPositionRequest Source # 

Methods

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

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

toConstr :: UpdateEmbeddedObjectPositionRequest -> Constr #

dataTypeOf :: UpdateEmbeddedObjectPositionRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show UpdateEmbeddedObjectPositionRequest Source # 
Generic UpdateEmbeddedObjectPositionRequest Source # 
ToJSON UpdateEmbeddedObjectPositionRequest Source # 
FromJSON UpdateEmbeddedObjectPositionRequest Source # 
type Rep UpdateEmbeddedObjectPositionRequest Source # 
type Rep UpdateEmbeddedObjectPositionRequest = D1 (MetaData "UpdateEmbeddedObjectPositionRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "UpdateEmbeddedObjectPositionRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ueoprNewPosition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EmbeddedObjectPosition))) ((:*:) (S1 (MetaSel (Just Symbol "_ueoprObjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_ueoprFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FieldMask))))))

updateEmbeddedObjectPositionRequest :: UpdateEmbeddedObjectPositionRequest Source #

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

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

ueoprNewPosition :: Lens' UpdateEmbeddedObjectPositionRequest (Maybe EmbeddedObjectPosition) Source #

An explicit position to move the embedded object to. If newPosition.sheetId is set, a new sheet with that ID will be created. If newPosition.newSheet is set to true, a new sheet will be created with an ID that will be chosen for you.

ueoprFields :: Lens' UpdateEmbeddedObjectPositionRequest (Maybe FieldMask) Source #

The fields of OverlayPosition that should be updated when setting a new position. Used only if newPosition.overlayPosition is set, in which case at least one field must be specified. The root `newPosition.overlayPosition` is implied and should not be specified. A single `"*"` can be used as short-hand for listing every field.

SourceAndDestinationDimension

data SourceAndDestinationDimension Source #

The dimension that data should be filled into.

Constructors

SADDDimensionUnspecified

DIMENSION_UNSPECIFIED The default value, do not use.

SADDRows

ROWS Operates on the rows of a sheet.

SADDColumns

COLUMNS Operates on the columns of a sheet.

Instances

Enum SourceAndDestinationDimension Source # 
Eq SourceAndDestinationDimension Source # 
Data SourceAndDestinationDimension Source # 

Methods

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

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

toConstr :: SourceAndDestinationDimension -> Constr #

dataTypeOf :: SourceAndDestinationDimension -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SourceAndDestinationDimension Source # 
Read SourceAndDestinationDimension Source # 
Show SourceAndDestinationDimension Source # 
Generic SourceAndDestinationDimension Source # 
Hashable SourceAndDestinationDimension Source # 
ToJSON SourceAndDestinationDimension Source # 
FromJSON SourceAndDestinationDimension Source # 
FromHttpApiData SourceAndDestinationDimension Source # 
ToHttpApiData SourceAndDestinationDimension Source # 
type Rep SourceAndDestinationDimension Source # 
type Rep SourceAndDestinationDimension = D1 (MetaData "SourceAndDestinationDimension" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "SADDDimensionUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "SADDRows" PrefixI False) U1) (C1 (MetaCons "SADDColumns" PrefixI False) U1)))

BooleanRule

data BooleanRule Source #

A rule that may or may not match, depending on the condition.

See: booleanRule smart constructor.

Instances

Eq BooleanRule Source # 
Data BooleanRule Source # 

Methods

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

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

toConstr :: BooleanRule -> Constr #

dataTypeOf :: BooleanRule -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BooleanRule Source # 
Generic BooleanRule Source # 

Associated Types

type Rep BooleanRule :: * -> * #

ToJSON BooleanRule Source # 
FromJSON BooleanRule Source # 
type Rep BooleanRule Source # 
type Rep BooleanRule = D1 (MetaData "BooleanRule" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BooleanRule'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_brFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CellFormat))) (S1 (MetaSel (Just Symbol "_brCondition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BooleanCondition)))))

booleanRule :: BooleanRule Source #

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

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

brFormat :: Lens' BooleanRule (Maybe CellFormat) Source #

The format to apply. Conditional formatting can only apply a subset of formatting: bold, italic, strikethrough, foreground color & background color.

brCondition :: Lens' BooleanRule (Maybe BooleanCondition) Source #

The condition of the rule. If the condition evaluates to true, the format will be applied.

CellFormatWrapStrategy

data CellFormatWrapStrategy Source #

The wrap strategy for the value in the cell.

Constructors

WrapStrategyUnspecified

WRAP_STRATEGY_UNSPECIFIED The default value, do not use.

OverflowCell

OVERFLOW_CELL Lines that are longer than the cell width will be written in the next cell over, so long as that cell is empty. If the next cell over is non-empty, this behaves the same as CLIP. The text will never wrap to the next line unless the user manually inserts a new line. Example: | First sentence. | | Manual newline that is very long. <- Text continues into next cell | Next newline. |

LegacyWrap

LEGACY_WRAP This wrap strategy represents the old Google Sheets wrap strategy where words that are longer than a line are clipped rather than broken. This strategy is not supported on all platforms and is being phased out. Example: | Cell has a | | loooooooooo| <- Word is clipped. | word. |

Clip

CLIP Lines that are longer than the cell width will be clipped. The text will never wrap to the next line unless the user manually inserts a new line. Example: | First sentence. | | Manual newline t| <- Text is clipped | Next newline. |

Wrap

WRAP Words that are longer than a line are wrapped at the character level rather than clipped. Example: | Cell has a | | loooooooooo| <- Word is broken. | ong word. |

Instances

Enum CellFormatWrapStrategy Source # 
Eq CellFormatWrapStrategy Source # 
Data CellFormatWrapStrategy Source # 

Methods

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

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

toConstr :: CellFormatWrapStrategy -> Constr #

dataTypeOf :: CellFormatWrapStrategy -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CellFormatWrapStrategy Source # 
Read CellFormatWrapStrategy Source # 
Show CellFormatWrapStrategy Source # 
Generic CellFormatWrapStrategy Source # 
Hashable CellFormatWrapStrategy Source # 
ToJSON CellFormatWrapStrategy Source # 
FromJSON CellFormatWrapStrategy Source # 
FromHttpApiData CellFormatWrapStrategy Source # 
ToHttpApiData CellFormatWrapStrategy Source # 
type Rep CellFormatWrapStrategy Source # 
type Rep CellFormatWrapStrategy = D1 (MetaData "CellFormatWrapStrategy" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "WrapStrategyUnspecified" PrefixI False) U1) (C1 (MetaCons "OverflowCell" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LegacyWrap" PrefixI False) U1) ((:+:) (C1 (MetaCons "Clip" PrefixI False) U1) (C1 (MetaCons "Wrap" PrefixI False) U1))))

SourceAndDestination

data SourceAndDestination Source #

A combination of a source range and how to extend that source.

See: sourceAndDestination smart constructor.

Instances

Eq SourceAndDestination Source # 
Data SourceAndDestination Source # 

Methods

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

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

toConstr :: SourceAndDestination -> Constr #

dataTypeOf :: SourceAndDestination -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SourceAndDestination Source # 
Generic SourceAndDestination Source # 
ToJSON SourceAndDestination Source # 
FromJSON SourceAndDestination Source # 
type Rep SourceAndDestination Source # 
type Rep SourceAndDestination = D1 (MetaData "SourceAndDestination" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "SourceAndDestination'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sadDimension") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SourceAndDestinationDimension))) ((:*:) (S1 (MetaSel (Just Symbol "_sadSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange))) (S1 (MetaSel (Just Symbol "_sadFillLength") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))))

sourceAndDestination :: SourceAndDestination Source #

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

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

sadDimension :: Lens' SourceAndDestination (Maybe SourceAndDestinationDimension) Source #

The dimension that data should be filled into.

sadSource :: Lens' SourceAndDestination (Maybe GridRange) Source #

The location of the data to use as the source of the autofill.

sadFillLength :: Lens' SourceAndDestination (Maybe Int32) Source #

The number of rows or columns that data should be filled into. Positive numbers expand beyond the last row or last column of the source. Negative numbers expand before the first row or first column of the source.

PasteDataRequest

data PasteDataRequest Source #

Inserts data into the spreadsheet starting at the specified coordinate.

See: pasteDataRequest smart constructor.

Instances

Eq PasteDataRequest Source # 
Data PasteDataRequest Source # 

Methods

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

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

toConstr :: PasteDataRequest -> Constr #

dataTypeOf :: PasteDataRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PasteDataRequest Source # 
Generic PasteDataRequest Source # 
ToJSON PasteDataRequest Source # 
FromJSON PasteDataRequest Source # 
type Rep PasteDataRequest Source # 

pasteDataRequest :: PasteDataRequest Source #

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

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

pdrData :: Lens' PasteDataRequest (Maybe Text) Source #

The data to insert.

pdrCoordinate :: Lens' PasteDataRequest (Maybe GridCoordinate) Source #

The coordinate at which the data should start being inserted.

pdrHTML :: Lens' PasteDataRequest (Maybe Bool) Source #

True if the data is HTML.

pdrType :: Lens' PasteDataRequest (Maybe PasteDataRequestType) Source #

How the data should be pasted.

pdrDelimiter :: Lens' PasteDataRequest (Maybe Text) Source #

The delimiter in the data.

BatchUpdateValuesRequestValueInputOption

data BatchUpdateValuesRequestValueInputOption Source #

How the input data should be interpreted.

Constructors

InputValueOptionUnspecified

INPUT_VALUE_OPTION_UNSPECIFIED Default input value. This value must not be used.

Raw

RAW The values the user has entered will not be parsed and will be stored as-is.

UserEntered

USER_ENTERED The values will be parsed as if the user typed them into the UI. Numbers will stay as numbers, but strings may be converted to numbers, dates, etc. following the same rules that are applied when entering text into a cell via the Google Sheets UI.

Instances

Enum BatchUpdateValuesRequestValueInputOption Source # 
Eq BatchUpdateValuesRequestValueInputOption Source # 
Data BatchUpdateValuesRequestValueInputOption Source # 

Methods

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

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

toConstr :: BatchUpdateValuesRequestValueInputOption -> Constr #

dataTypeOf :: BatchUpdateValuesRequestValueInputOption -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BatchUpdateValuesRequestValueInputOption Source # 
Read BatchUpdateValuesRequestValueInputOption Source # 
Show BatchUpdateValuesRequestValueInputOption Source # 
Generic BatchUpdateValuesRequestValueInputOption Source # 
Hashable BatchUpdateValuesRequestValueInputOption Source # 
ToJSON BatchUpdateValuesRequestValueInputOption Source # 
FromJSON BatchUpdateValuesRequestValueInputOption Source # 
FromHttpApiData BatchUpdateValuesRequestValueInputOption Source # 
ToHttpApiData BatchUpdateValuesRequestValueInputOption Source # 
type Rep BatchUpdateValuesRequestValueInputOption Source # 
type Rep BatchUpdateValuesRequestValueInputOption = D1 (MetaData "BatchUpdateValuesRequestValueInputOption" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "InputValueOptionUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "Raw" PrefixI False) U1) (C1 (MetaCons "UserEntered" PrefixI False) U1)))

AppendCellsRequest

data AppendCellsRequest Source #

Adds new cells after the last row with data in a sheet, inserting new rows into the sheet if necessary.

See: appendCellsRequest smart constructor.

Instances

Eq AppendCellsRequest Source # 
Data AppendCellsRequest Source # 

Methods

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

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

toConstr :: AppendCellsRequest -> Constr #

dataTypeOf :: AppendCellsRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AppendCellsRequest Source # 
Generic AppendCellsRequest Source # 
ToJSON AppendCellsRequest Source # 
FromJSON AppendCellsRequest Source # 
type Rep AppendCellsRequest Source # 
type Rep AppendCellsRequest = D1 (MetaData "AppendCellsRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "AppendCellsRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_acrRows") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [RowData]))) ((:*:) (S1 (MetaSel (Just Symbol "_acrSheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_acrFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FieldMask))))))

appendCellsRequest :: AppendCellsRequest Source #

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

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

acrSheetId :: Lens' AppendCellsRequest (Maybe Int32) Source #

The sheet ID to append the data to.

acrFields :: Lens' AppendCellsRequest (Maybe FieldMask) Source #

The fields of CellData that should be updated. At least one field must be specified. The root is the CellData; 'row.values.' should not be specified. A single `"*"` can be used as short-hand for listing every field.

FindReplaceResponse

data FindReplaceResponse Source #

The result of the find/replace.

See: findReplaceResponse smart constructor.

Instances

Eq FindReplaceResponse Source # 
Data FindReplaceResponse Source # 

Methods

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

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

toConstr :: FindReplaceResponse -> Constr #

dataTypeOf :: FindReplaceResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FindReplaceResponse Source # 
Generic FindReplaceResponse Source # 
ToJSON FindReplaceResponse Source # 
FromJSON FindReplaceResponse Source # 
type Rep FindReplaceResponse Source # 
type Rep FindReplaceResponse = D1 (MetaData "FindReplaceResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "FindReplaceResponse'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_frrValuesChanged") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_frrFormulasChanged") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))) ((:*:) (S1 (MetaSel (Just Symbol "_frrRowsChanged") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) ((:*:) (S1 (MetaSel (Just Symbol "_frrSheetsChanged") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_frrOccurrencesChanged") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))))

findReplaceResponse :: FindReplaceResponse Source #

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

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

frrValuesChanged :: Lens' FindReplaceResponse (Maybe Int32) Source #

The number of non-formula cells changed.

frrFormulasChanged :: Lens' FindReplaceResponse (Maybe Int32) Source #

The number of formula cells changed.

frrRowsChanged :: Lens' FindReplaceResponse (Maybe Int32) Source #

The number of rows changed.

frrSheetsChanged :: Lens' FindReplaceResponse (Maybe Int32) Source #

The number of sheets changed.

frrOccurrencesChanged :: Lens' FindReplaceResponse (Maybe Int32) Source #

The number of occurrences (possibly multiple within a cell) changed. For example, if replacing `"e"` with `"o"` in `"Google Sheets"`, this would be `"3"` because `"Google Sheets"` -> `"Googlo Shoots"`.

PieChartSpec

data PieChartSpec Source #

A pie chart.

See: pieChartSpec smart constructor.

Instances

Eq PieChartSpec Source # 
Data PieChartSpec Source # 

Methods

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

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

toConstr :: PieChartSpec -> Constr #

dataTypeOf :: PieChartSpec -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PieChartSpec Source # 
Generic PieChartSpec Source # 

Associated Types

type Rep PieChartSpec :: * -> * #

ToJSON PieChartSpec Source # 
FromJSON PieChartSpec Source # 
type Rep PieChartSpec Source # 
type Rep PieChartSpec = D1 (MetaData "PieChartSpec" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "PieChartSpec'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_pcsPieHole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_pcsLegendPosition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PieChartSpecLegendPosition)))) ((:*:) (S1 (MetaSel (Just Symbol "_pcsDomain") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChartData))) ((:*:) (S1 (MetaSel (Just Symbol "_pcsSeries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChartData))) (S1 (MetaSel (Just Symbol "_pcsThreeDimensional") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))))

pieChartSpec :: PieChartSpec Source #

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

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

pcsPieHole :: Lens' PieChartSpec (Maybe Double) Source #

The size of the hole in the pie chart.

pcsLegendPosition :: Lens' PieChartSpec (Maybe PieChartSpecLegendPosition) Source #

Where the legend of the pie chart should be drawn.

pcsDomain :: Lens' PieChartSpec (Maybe ChartData) Source #

The data that covers the domain of the pie chart.

pcsSeries :: Lens' PieChartSpec (Maybe ChartData) Source #

The data that covers the one and only series of the pie chart.

pcsThreeDimensional :: Lens' PieChartSpec (Maybe Bool) Source #

True if the pie is three dimensional.

AppendValuesResponse

data AppendValuesResponse Source #

The response when updating a range of values in a spreadsheet.

See: appendValuesResponse smart constructor.

Instances

Eq AppendValuesResponse Source # 
Data AppendValuesResponse Source # 

Methods

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

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

toConstr :: AppendValuesResponse -> Constr #

dataTypeOf :: AppendValuesResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AppendValuesResponse Source # 
Generic AppendValuesResponse Source # 
ToJSON AppendValuesResponse Source # 
FromJSON AppendValuesResponse Source # 
type Rep AppendValuesResponse Source # 
type Rep AppendValuesResponse = D1 (MetaData "AppendValuesResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "AppendValuesResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_avrSpreadsheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_avrUpdates") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateValuesResponse))) (S1 (MetaSel (Just Symbol "_avrTableRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

appendValuesResponse :: AppendValuesResponse Source #

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

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

avrSpreadsheetId :: Lens' AppendValuesResponse (Maybe Text) Source #

The spreadsheet the updates were applied to.

avrUpdates :: Lens' AppendValuesResponse (Maybe UpdateValuesResponse) Source #

Information about the updates that were applied.

avrTableRange :: Lens' AppendValuesResponse (Maybe Text) Source #

The range (in A1 notation) of the table that values are being appended to (before the values were appended). Empty if no table was found.

BatchUpdateValuesRequestResponseValueRenderOption

data BatchUpdateValuesRequestResponseValueRenderOption Source #

Determines how values in the response should be rendered. The default render option is ValueRenderOption.FORMATTED_VALUE.

Constructors

FormattedValue

FORMATTED_VALUE Values will be calculated & formatted in the reply according to the cell's formatting. Formatting is based on the spreadsheet's locale, not the requesting user's locale. For example, if `A1` is `1.23` and `A2` is `=A1` and formatted as currency, then `A2` would return `"$1.23"`.

UnformattedValue

UNFORMATTED_VALUE Values will be calculated, but not formatted in the reply. For example, if `A1` is `1.23` and `A2` is `=A1` and formatted as currency, then `A2` would return the number `1.23`.

Formula

FORMULA Values will not be calculated. The reply will include the formulas. For example, if `A1` is `1.23` and `A2` is `=A1` and formatted as currency, then A2 would return `"=A1"`.

Instances

Enum BatchUpdateValuesRequestResponseValueRenderOption Source # 
Eq BatchUpdateValuesRequestResponseValueRenderOption Source # 
Data BatchUpdateValuesRequestResponseValueRenderOption Source # 

Methods

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

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

toConstr :: BatchUpdateValuesRequestResponseValueRenderOption -> Constr #

dataTypeOf :: BatchUpdateValuesRequestResponseValueRenderOption -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BatchUpdateValuesRequestResponseValueRenderOption Source # 
Read BatchUpdateValuesRequestResponseValueRenderOption Source # 
Show BatchUpdateValuesRequestResponseValueRenderOption Source # 
Generic BatchUpdateValuesRequestResponseValueRenderOption Source # 
Hashable BatchUpdateValuesRequestResponseValueRenderOption Source # 
ToJSON BatchUpdateValuesRequestResponseValueRenderOption Source # 
FromJSON BatchUpdateValuesRequestResponseValueRenderOption Source # 
FromHttpApiData BatchUpdateValuesRequestResponseValueRenderOption Source # 
ToHttpApiData BatchUpdateValuesRequestResponseValueRenderOption Source # 
type Rep BatchUpdateValuesRequestResponseValueRenderOption Source # 
type Rep BatchUpdateValuesRequestResponseValueRenderOption = D1 (MetaData "BatchUpdateValuesRequestResponseValueRenderOption" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "FormattedValue" PrefixI False) U1) ((:+:) (C1 (MetaCons "UnformattedValue" PrefixI False) U1) (C1 (MetaCons "Formula" PrefixI False) U1)))

DataValidationRule

data DataValidationRule Source #

A data validation rule.

See: dataValidationRule smart constructor.

Instances

Eq DataValidationRule Source # 
Data DataValidationRule Source # 

Methods

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

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

toConstr :: DataValidationRule -> Constr #

dataTypeOf :: DataValidationRule -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DataValidationRule Source # 
Generic DataValidationRule Source # 
ToJSON DataValidationRule Source # 
FromJSON DataValidationRule Source # 
type Rep DataValidationRule Source # 
type Rep DataValidationRule = D1 (MetaData "DataValidationRule" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "DataValidationRule'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dvrShowCustomUi") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_dvrInputMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_dvrStrict") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_dvrCondition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BooleanCondition))))))

dataValidationRule :: DataValidationRule Source #

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

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

dvrShowCustomUi :: Lens' DataValidationRule (Maybe Bool) Source #

True if the UI should be customized based on the kind of condition. If true, "List" conditions will show a dropdown.

dvrInputMessage :: Lens' DataValidationRule (Maybe Text) Source #

A message to show the user when adding data to the cell.

dvrStrict :: Lens' DataValidationRule (Maybe Bool) Source #

True if invalid data should be rejected.

dvrCondition :: Lens' DataValidationRule (Maybe BooleanCondition) Source #

The condition that data in the cell must match.

FilterView

data FilterView Source #

A filter view.

See: filterView smart constructor.

Instances

Eq FilterView Source # 
Data FilterView Source # 

Methods

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

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

toConstr :: FilterView -> Constr #

dataTypeOf :: FilterView -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FilterView Source # 
Generic FilterView Source # 

Associated Types

type Rep FilterView :: * -> * #

ToJSON FilterView Source # 
FromJSON FilterView Source # 
type Rep FilterView Source # 

filterView :: FilterView Source #

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

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

fvSortSpecs :: Lens' FilterView [SortSpec] Source #

The sort order per column. Later specifications are used when values are equal in the earlier specifications.

fvNamedRangeId :: Lens' FilterView (Maybe Text) Source #

The named range this filter view is backed by, if any. When writing, only one of range or named_range_id may be set.

fvRange :: Lens' FilterView (Maybe GridRange) Source #

The range this filter view covers. When writing, only one of range or named_range_id may be set.

fvFilterViewId :: Lens' FilterView (Maybe Int32) Source #

The ID of the filter view.

fvTitle :: Lens' FilterView (Maybe Text) Source #

The name of the filter view.

fvCriteria :: Lens' FilterView (Maybe FilterViewCriteria) Source #

The criteria for showing/hiding values per column. The map's key is the column index, and the value is the criteria for that column.

Color

data Color Source #

Represents a color in the RGBA color space. This representation is designed for simplicity of conversion to/from color representations in various languages over compactness; for example, the fields of this representation can be trivially provided to the constructor of "java.awt.Color" in Java; it can also be trivially provided to UIColor's "+colorWithRed:green:blue:alpha" method in iOS; and, with just a little work, it can be easily formatted into a CSS "rgba()" string in JavaScript, as well. Here are some examples: Example (Java): import com.google.type.Color; // ... public static java.awt.Color fromProto(Color protocolor) { float alpha = protocolor.hasAlpha() ? protocolor.getAlpha().getValue() : 1.0; return new java.awt.Color( protocolor.getRed(), protocolor.getGreen(), protocolor.getBlue(), alpha); } public static Color toProto(java.awt.Color color) { float red = (float) color.getRed(); float green = (float) color.getGreen(); float blue = (float) color.getBlue(); float denominator = 255.0; Color.Builder resultBuilder = Color .newBuilder() .setRed(red / denominator) .setGreen(green / denominator) .setBlue(blue / denominator); int alpha = color.getAlpha(); if (alpha != 255) { result.setAlpha( FloatValue .newBuilder() .setValue(((float) alpha) / denominator) .build()); } return resultBuilder.build(); } // ... Example (iOS / Obj-C): // ... static UIColor* fromProto(Color* protocolor) { float red = [protocolor red]; float green = [protocolor green]; float blue = [protocolor blue]; FloatValue* alpha_wrapper = [protocolor alpha]; float alpha = 1.0; if (alpha_wrapper != nil) { alpha = [alpha_wrapper value]; } return [UIColor colorWithRed:red green:green blue:blue alpha:alpha]; } static Color* toProto(UIColor* color) { CGFloat red, green, blue, alpha; if (![color getRed:&red green:&green blue:&blue alpha:&alpha]) { return nil; } Color* result = [Color alloc] init]; [result setRed:red]; [result setGreen:green]; [result setBlue:blue]; if (alpha <= 0.9999) { [result setAlpha:floatWrapperWithValue(alpha)]; } [result autorelease]; return result; } // ... Example (JavaScript): // ... var protoToCssColor = function(rgb_color) { var redFrac = rgb_color.red || 0.0; var greenFrac = rgb_color.green || 0.0; var blueFrac = rgb_color.blue || 0.0; var red = Math.floor(redFrac * 255); var green = Math.floor(greenFrac * 255); var blue = Math.floor(blueFrac * 255); if (!('alpha' in rgb_color)) { return rgbToCssColor_(red, green, blue); } var alphaFrac = rgb_color.alpha.value || 0.0; var rgbParams = [red, green, blue].join(','); return ['rgba(', rgbParams, ',', alphaFrac, ')'].join(''); }; var rgbToCssColor_ = function(red, green, blue) { var rgbNumber = new Number((red << 16) | (green << 8) | blue); var hexString = rgbNumber.toString(16); var missingZeros = 6 - hexString.length; var resultBuilder = ['#']; for (var i = 0; i < missingZeros; i++) { resultBuilder.push('0'); } resultBuilder.push(hexString); return resultBuilder.join(''); }; // ...

See: color smart constructor.

Instances

Eq Color Source # 

Methods

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

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

Data Color Source # 

Methods

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

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

toConstr :: Color -> Constr #

dataTypeOf :: Color -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Color Source # 

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Generic Color Source # 

Associated Types

type Rep Color :: * -> * #

Methods

from :: Color -> Rep Color x #

to :: Rep Color x -> Color #

ToJSON Color Source # 
FromJSON Color Source # 
type Rep Color Source # 

color :: Color Source #

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

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

cRed :: Lens' Color (Maybe Double) Source #

The amount of red in the color as a value in the interval [0, 1].

cAlpha :: Lens' Color (Maybe Double) Source #

The fraction of this color that should be applied to the pixel. That is, the final pixel color is defined by the equation: pixel color = alpha * (this color) + (1.0 - alpha) * (background color) This means that a value of 1.0 corresponds to a solid color, whereas a value of 0.0 corresponds to a completely transparent color. This uses a wrapper message rather than a simple float scalar so that it is possible to distinguish between a default value and the value being unset. If omitted, this color object is to be rendered as a solid color (as if the alpha value had been explicitly given with a value of 1.0).

cGreen :: Lens' Color (Maybe Double) Source #

The amount of green in the color as a value in the interval [0, 1].

cBlue :: Lens' Color (Maybe Double) Source #

The amount of blue in the color as a value in the interval [0, 1].

DeleteFilterViewRequest

data DeleteFilterViewRequest Source #

Deletes a particular filter view.

See: deleteFilterViewRequest smart constructor.

Instances

Eq DeleteFilterViewRequest Source # 
Data DeleteFilterViewRequest Source # 

Methods

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

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

toConstr :: DeleteFilterViewRequest -> Constr #

dataTypeOf :: DeleteFilterViewRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DeleteFilterViewRequest Source # 
Generic DeleteFilterViewRequest Source # 
ToJSON DeleteFilterViewRequest Source # 
FromJSON DeleteFilterViewRequest Source # 
type Rep DeleteFilterViewRequest Source # 
type Rep DeleteFilterViewRequest = D1 (MetaData "DeleteFilterViewRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "DeleteFilterViewRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_dfvrFilterId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Textual Int32)))))

deleteFilterViewRequest :: DeleteFilterViewRequest Source #

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

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

dfvrFilterId :: Lens' DeleteFilterViewRequest (Maybe Int32) Source #

The ID of the filter to delete.

UpdateFilterViewRequest

data UpdateFilterViewRequest Source #

Updates properties of the filter view.

See: updateFilterViewRequest smart constructor.

Instances

Eq UpdateFilterViewRequest Source # 
Data UpdateFilterViewRequest Source # 

Methods

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

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

toConstr :: UpdateFilterViewRequest -> Constr #

dataTypeOf :: UpdateFilterViewRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show UpdateFilterViewRequest Source # 
Generic UpdateFilterViewRequest Source # 
ToJSON UpdateFilterViewRequest Source # 
FromJSON UpdateFilterViewRequest Source # 
type Rep UpdateFilterViewRequest Source # 
type Rep UpdateFilterViewRequest = D1 (MetaData "UpdateFilterViewRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "UpdateFilterViewRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ufvrFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FilterView))) (S1 (MetaSel (Just Symbol "_ufvrFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FieldMask)))))

updateFilterViewRequest :: UpdateFilterViewRequest Source #

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

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

ufvrFilter :: Lens' UpdateFilterViewRequest (Maybe FilterView) Source #

The new properties of the filter view.

ufvrFields :: Lens' UpdateFilterViewRequest (Maybe FieldMask) Source #

The fields that should be updated. At least one field must be specified. The root `filter` is implied and should not be specified. A single `"*"` can be used as short-hand for listing every field.

BasicChartSeries

data BasicChartSeries Source #

A single series of data in a chart. For example, if charting stock prices over time, multiple series may exist, one for the "Open Price", "High Price", "Low Price" and "Close Price".

See: basicChartSeries smart constructor.

Instances

Eq BasicChartSeries Source # 
Data BasicChartSeries Source # 

Methods

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

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

toConstr :: BasicChartSeries -> Constr #

dataTypeOf :: BasicChartSeries -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BasicChartSeries Source # 
Generic BasicChartSeries Source # 
ToJSON BasicChartSeries Source # 
FromJSON BasicChartSeries Source # 
type Rep BasicChartSeries Source # 
type Rep BasicChartSeries = D1 (MetaData "BasicChartSeries" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BasicChartSeries'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bcsTargetAxis") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BasicChartSeriesTargetAxis))) ((:*:) (S1 (MetaSel (Just Symbol "_bcsSeries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChartData))) (S1 (MetaSel (Just Symbol "_bcsType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BasicChartSeriesType))))))

basicChartSeries :: BasicChartSeries Source #

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

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

bcsTargetAxis :: Lens' BasicChartSeries (Maybe BasicChartSeriesTargetAxis) Source #

The minor axis that will specify the range of values for this series. For example, if charting stocks over time, the "Volume" series may want to be pinned to the right with the prices pinned to the left, because the scale of trading volume is different than the scale of prices. It is an error to specify an axis that isn't a valid minor axis for the chart's type.

bcsSeries :: Lens' BasicChartSeries (Maybe ChartData) Source #

The data being visualized in this chart series.

bcsType :: Lens' BasicChartSeries (Maybe BasicChartSeriesType) Source #

The type of this series. Valid only if the chartType is COMBO. Different types will change the way the series is visualized. Only LINE, AREA, and COLUMN are supported.

AddProtectedRangeRequest

data AddProtectedRangeRequest Source #

Adds a new protected range.

See: addProtectedRangeRequest smart constructor.

Instances

Eq AddProtectedRangeRequest Source # 
Data AddProtectedRangeRequest Source # 

Methods

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

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

toConstr :: AddProtectedRangeRequest -> Constr #

dataTypeOf :: AddProtectedRangeRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AddProtectedRangeRequest Source # 
Generic AddProtectedRangeRequest Source # 
ToJSON AddProtectedRangeRequest Source # 
FromJSON AddProtectedRangeRequest Source # 
type Rep AddProtectedRangeRequest Source # 
type Rep AddProtectedRangeRequest = D1 (MetaData "AddProtectedRangeRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "AddProtectedRangeRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_aprrProtectedRange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ProtectedRange))))

addProtectedRangeRequest :: AddProtectedRangeRequest Source #

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

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

aprrProtectedRange :: Lens' AddProtectedRangeRequest (Maybe ProtectedRange) Source #

The protected range to be added. The protectedRangeId field is optional; if one is not set, an id will be randomly generated. (It is an error to specify the ID of a range that already exists.)

PieChartSpecLegendPosition

data PieChartSpecLegendPosition Source #

Where the legend of the pie chart should be drawn.

Constructors

PieChartLegendPositionUnspecified

PIE_CHART_LEGEND_POSITION_UNSPECIFIED Default value, do not use.

BottomLegend

BOTTOM_LEGEND The legend is rendered on the bottom of the chart.

LeftLegend

LEFT_LEGEND The legend is rendered on the left of the chart.

RightLegend

RIGHT_LEGEND The legend is rendered on the right of the chart.

TopLegend

TOP_LEGEND The legend is rendered on the top of the chart.

NoLegend

NO_LEGEND No legend is rendered.

LabeledLegend

LABELED_LEGEND Each pie slice has a label attached to it.

Instances

Enum PieChartSpecLegendPosition Source # 
Eq PieChartSpecLegendPosition Source # 
Data PieChartSpecLegendPosition Source # 

Methods

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

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

toConstr :: PieChartSpecLegendPosition -> Constr #

dataTypeOf :: PieChartSpecLegendPosition -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PieChartSpecLegendPosition Source # 
Read PieChartSpecLegendPosition Source # 
Show PieChartSpecLegendPosition Source # 
Generic PieChartSpecLegendPosition Source # 
Hashable PieChartSpecLegendPosition Source # 
ToJSON PieChartSpecLegendPosition Source # 
FromJSON PieChartSpecLegendPosition Source # 
FromHttpApiData PieChartSpecLegendPosition Source # 
ToHttpApiData PieChartSpecLegendPosition Source # 
type Rep PieChartSpecLegendPosition Source # 
type Rep PieChartSpecLegendPosition = D1 (MetaData "PieChartSpecLegendPosition" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "PieChartLegendPositionUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "BottomLegend" PrefixI False) U1) (C1 (MetaCons "LeftLegend" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "RightLegend" PrefixI False) U1) (C1 (MetaCons "TopLegend" PrefixI False) U1)) ((:+:) (C1 (MetaCons "NoLegend" PrefixI False) U1) (C1 (MetaCons "LabeledLegend" PrefixI False) U1))))

RepeatCellRequest

data RepeatCellRequest Source #

Updates all cells in the range to the values in the given Cell object. Only the fields listed in the fields field are updated; others are unchanged. If writing a cell with a formula, the formula's ranges will automatically increment for each field in the range. For example, if writing a cell with formula `=A1` into range B2:C4, B2 would be `=A1`, B3 would be `=A2`, B4 would be `=A3`, C2 would be `=B1`, C3 would be `=B2`, C4 would be `=B3`. To keep the formula's ranges static, use the `$` indicator. For example, use the formula `=$A$1` to prevent both the row and the column from incrementing.

See: repeatCellRequest smart constructor.

Instances

Eq RepeatCellRequest Source # 
Data RepeatCellRequest Source # 

Methods

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

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

toConstr :: RepeatCellRequest -> Constr #

dataTypeOf :: RepeatCellRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RepeatCellRequest Source # 
Generic RepeatCellRequest Source # 
ToJSON RepeatCellRequest Source # 
FromJSON RepeatCellRequest Source # 
type Rep RepeatCellRequest Source # 
type Rep RepeatCellRequest = D1 (MetaData "RepeatCellRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "RepeatCellRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rcrCell") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CellData))) ((:*:) (S1 (MetaSel (Just Symbol "_rcrRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange))) (S1 (MetaSel (Just Symbol "_rcrFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FieldMask))))))

repeatCellRequest :: RepeatCellRequest Source #

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

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

rcrRange :: Lens' RepeatCellRequest (Maybe GridRange) Source #

The range to repeat the cell in.

rcrFields :: Lens' RepeatCellRequest (Maybe FieldMask) Source #

The fields that should be updated. At least one field must be specified. The root `cell` is implied and should not be specified. A single `"*"` can be used as short-hand for listing every field.

ConditionValue

data ConditionValue Source #

The value of the condition.

See: conditionValue smart constructor.

Instances

Eq ConditionValue Source # 
Data ConditionValue Source # 

Methods

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

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

toConstr :: ConditionValue -> Constr #

dataTypeOf :: ConditionValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ConditionValue Source # 
Generic ConditionValue Source # 

Associated Types

type Rep ConditionValue :: * -> * #

ToJSON ConditionValue Source # 
FromJSON ConditionValue Source # 
type Rep ConditionValue Source # 
type Rep ConditionValue = D1 (MetaData "ConditionValue" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "ConditionValue'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cvRelativeDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ConditionValueRelativeDate))) (S1 (MetaSel (Just Symbol "_cvUserEnteredValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

conditionValue :: ConditionValue Source #

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

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

cvRelativeDate :: Lens' ConditionValue (Maybe ConditionValueRelativeDate) Source #

A relative date (based on the current date). Valid only if the type is DATE_BEFORE, DATE_AFTER, DATE_ON_OR_BEFORE or DATE_ON_OR_AFTER. Relative dates are not supported in data validation. They are supported only in conditional formatting and conditional filters.

cvUserEnteredValue :: Lens' ConditionValue (Maybe Text) Source #

A value the condition is based on. The value will be parsed as if the user typed into a cell. Formulas are supported (and must begin with an `=`).

DeleteDimensionRequest

data DeleteDimensionRequest Source #

Deletes the dimensions from the sheet.

See: deleteDimensionRequest smart constructor.

Instances

Eq DeleteDimensionRequest Source # 
Data DeleteDimensionRequest Source # 

Methods

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

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

toConstr :: DeleteDimensionRequest -> Constr #

dataTypeOf :: DeleteDimensionRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DeleteDimensionRequest Source # 
Generic DeleteDimensionRequest Source # 
ToJSON DeleteDimensionRequest Source # 
FromJSON DeleteDimensionRequest Source # 
type Rep DeleteDimensionRequest Source # 
type Rep DeleteDimensionRequest = D1 (MetaData "DeleteDimensionRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "DeleteDimensionRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_ddrRange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe DimensionRange))))

deleteDimensionRequest :: DeleteDimensionRequest Source #

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

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

ddrRange :: Lens' DeleteDimensionRequest (Maybe DimensionRange) Source #

The dimensions to delete from the sheet.

ClearValuesRequest

data ClearValuesRequest Source #

The request for clearing a range of values in a spreadsheet.

See: clearValuesRequest smart constructor.

Instances

Eq ClearValuesRequest Source # 
Data ClearValuesRequest Source # 

Methods

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

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

toConstr :: ClearValuesRequest -> Constr #

dataTypeOf :: ClearValuesRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ClearValuesRequest Source # 
Generic ClearValuesRequest Source # 
ToJSON ClearValuesRequest Source # 
FromJSON ClearValuesRequest Source # 
type Rep ClearValuesRequest Source # 
type Rep ClearValuesRequest = D1 (MetaData "ClearValuesRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "ClearValuesRequest'" PrefixI False) U1)

clearValuesRequest :: ClearValuesRequest Source #

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

FindReplaceRequest

data FindReplaceRequest Source #

Finds and replaces data in cells over a range, sheet, or all sheets.

See: findReplaceRequest smart constructor.

Instances

Eq FindReplaceRequest Source # 
Data FindReplaceRequest Source # 

Methods

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

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

toConstr :: FindReplaceRequest -> Constr #

dataTypeOf :: FindReplaceRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FindReplaceRequest Source # 
Generic FindReplaceRequest Source # 
ToJSON FindReplaceRequest Source # 
FromJSON FindReplaceRequest Source # 
type Rep FindReplaceRequest Source # 

findReplaceRequest :: FindReplaceRequest Source #

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

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

frrMatchCase :: Lens' FindReplaceRequest (Maybe Bool) Source #

True if the search is case sensitive.

frrAllSheets :: Lens' FindReplaceRequest (Maybe Bool) Source #

True to find/replace over all sheets.

frrIncludeFormulas :: Lens' FindReplaceRequest (Maybe Bool) Source #

True if the search should include cells with formulas. False to skip cells with formulas.

frrMatchEntireCell :: Lens' FindReplaceRequest (Maybe Bool) Source #

True if the find value should match the entire cell.

frrRange :: Lens' FindReplaceRequest (Maybe GridRange) Source #

The range to find/replace over.

frrSheetId :: Lens' FindReplaceRequest (Maybe Int32) Source #

The sheet to find/replace over.

frrFind :: Lens' FindReplaceRequest (Maybe Text) Source #

The value to search.

frrSearchByRegex :: Lens' FindReplaceRequest (Maybe Bool) Source #

True if the find value is a regex. The regular expression and replacement should follow Java regex rules at https://docs.oracle.com/javase/8/docs/api/java/util/regex/Pattern.html. The replacement string is allowed to refer to capturing groups. For example, if one cell has the contents `"Google Sheets"` and another has `"Google Docs"`, then searching for `"o.* (.*)"` with a replacement of `"$1 Rocks"` would change the contents of the cells to `"GSheets Rocks"` and `"GDocs Rocks"` respectively.

frrReplacement :: Lens' FindReplaceRequest (Maybe Text) Source #

The value to use as the replacement.

MoveDimensionRequest

data MoveDimensionRequest Source #

Moves one or more rows or columns.

See: moveDimensionRequest smart constructor.

Instances

Eq MoveDimensionRequest Source # 
Data MoveDimensionRequest Source # 

Methods

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

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

toConstr :: MoveDimensionRequest -> Constr #

dataTypeOf :: MoveDimensionRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show MoveDimensionRequest Source # 
Generic MoveDimensionRequest Source # 
ToJSON MoveDimensionRequest Source # 
FromJSON MoveDimensionRequest Source # 
type Rep MoveDimensionRequest Source # 
type Rep MoveDimensionRequest = D1 (MetaData "MoveDimensionRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "MoveDimensionRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_mdrDestinationIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_mdrSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionRange)))))

moveDimensionRequest :: MoveDimensionRequest Source #

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

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

mdrDestinationIndex :: Lens' MoveDimensionRequest (Maybe Int32) Source #

The zero-based start index of where to move the source data to, based on the coordinates *before* the source data is removed from the grid. Existing data will be shifted down or right (depending on the dimension) to make room for the moved dimensions. The source dimensions are removed from the grid, so the the data may end up in a different index than specified. For example, given `A1..A5` of `0, 1, 2, 3, 4` and wanting to move `"1"` and `"2"` to between `"3"` and `"4"`, the source would be `ROWS [1..3)`,and the destination index would be `"4"` (the zero-based index of row 5). The end result would be `A1..A5` of `0, 3, 1, 2, 4`.

mdrSource :: Lens' MoveDimensionRequest (Maybe DimensionRange) Source #

The source dimensions to move.

CellFormatVerticalAlignment

data CellFormatVerticalAlignment Source #

The vertical alignment of the value in the cell.

Constructors

VerticalAlignUnspecified

VERTICAL_ALIGN_UNSPECIFIED The vertical alignment is not specified. Do not use this.

Top

TOP The text is explicitly aligned to the top of the cell.

Middle

MIDDLE The text is explicitly aligned to the middle of the cell.

Bottom

BOTTOM The text is explicitly aligned to the bottom of the cell.

Instances

Enum CellFormatVerticalAlignment Source # 
Eq CellFormatVerticalAlignment Source # 
Data CellFormatVerticalAlignment Source # 

Methods

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

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

toConstr :: CellFormatVerticalAlignment -> Constr #

dataTypeOf :: CellFormatVerticalAlignment -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CellFormatVerticalAlignment Source # 
Read CellFormatVerticalAlignment Source # 
Show CellFormatVerticalAlignment Source # 
Generic CellFormatVerticalAlignment Source # 
Hashable CellFormatVerticalAlignment Source # 
ToJSON CellFormatVerticalAlignment Source # 
FromJSON CellFormatVerticalAlignment Source # 
FromHttpApiData CellFormatVerticalAlignment Source # 
ToHttpApiData CellFormatVerticalAlignment Source # 
type Rep CellFormatVerticalAlignment Source # 
type Rep CellFormatVerticalAlignment = D1 (MetaData "CellFormatVerticalAlignment" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "VerticalAlignUnspecified" PrefixI False) U1) (C1 (MetaCons "Top" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Middle" PrefixI False) U1) (C1 (MetaCons "Bottom" PrefixI False) U1)))

NumberFormatType

data NumberFormatType Source #

The type of the number format. When writing, this field must be set.

Constructors

NumberFormatTypeUnspecified

NUMBER_FORMAT_TYPE_UNSPECIFIED The number format is not specified and is based on the contents of the cell. Do not explicitly use this.

Text

TEXT Text formatting, e.g `1000.12`

Number

NUMBER Number formatting, e.g, `1,000.12`

Percent

PERCENT Percent formatting, e.g `10.12%`

Currency

CURRENCY Currency formatting, e.g `$1,000.12`

Date

DATE Date formatting, e.g `9/26/2008`

Time

TIME Time formatting, e.g `3:59:00 PM`

DateTime

DATE_TIME Date+Time formatting, e.g `9/26/08 15:59:00`

Scientific

SCIENTIFIC Scientific number formatting, e.g `1.01E+03`

Instances

Enum NumberFormatType Source # 
Eq NumberFormatType Source # 
Data NumberFormatType Source # 

Methods

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

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

toConstr :: NumberFormatType -> Constr #

dataTypeOf :: NumberFormatType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NumberFormatType Source # 
Read NumberFormatType Source # 
Show NumberFormatType Source # 
Generic NumberFormatType Source # 
Hashable NumberFormatType Source # 
ToJSON NumberFormatType Source # 
FromJSON NumberFormatType Source # 
FromHttpApiData NumberFormatType Source # 
ToHttpApiData NumberFormatType Source # 
type Rep NumberFormatType Source # 
type Rep NumberFormatType = D1 (MetaData "NumberFormatType" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "NumberFormatTypeUnspecified" PrefixI False) U1) (C1 (MetaCons "Text" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Number" PrefixI False) U1) (C1 (MetaCons "Percent" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Currency" PrefixI False) U1) (C1 (MetaCons "Date" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Time" PrefixI False) U1) ((:+:) (C1 (MetaCons "DateTime" PrefixI False) U1) (C1 (MetaCons "Scientific" PrefixI False) U1)))))

GradientRule

data GradientRule Source #

A rule that applies a gradient color scale format, based on the interpolation points listed. The format of a cell will vary based on its contents as compared to the values of the interpolation points.

See: gradientRule smart constructor.

Instances

Eq GradientRule Source # 
Data GradientRule Source # 

Methods

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

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

toConstr :: GradientRule -> Constr #

dataTypeOf :: GradientRule -> DataType #

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

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

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

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

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

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

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

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

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

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

Show GradientRule Source # 
Generic GradientRule Source # 

Associated Types

type Rep GradientRule :: * -> * #

ToJSON GradientRule Source # 
FromJSON GradientRule Source # 
type Rep GradientRule Source # 
type Rep GradientRule = D1 (MetaData "GradientRule" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "GradientRule'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_grMidpoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe InterpolationPoint))) ((:*:) (S1 (MetaSel (Just Symbol "_grMaxpoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe InterpolationPoint))) (S1 (MetaSel (Just Symbol "_grMinpoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe InterpolationPoint))))))

gradientRule :: GradientRule Source #

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

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

grMidpoint :: Lens' GradientRule (Maybe InterpolationPoint) Source #

An optional midway interpolation point.

grMaxpoint :: Lens' GradientRule (Maybe InterpolationPoint) Source #

The final interpolation point.

grMinpoint :: Lens' GradientRule (Maybe InterpolationPoint) Source #

The starting interpolation point.

CutPasteRequest

data CutPasteRequest Source #

Moves data from the source to the destination.

See: cutPasteRequest smart constructor.

Instances

Eq CutPasteRequest Source # 
Data CutPasteRequest Source # 

Methods

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

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

toConstr :: CutPasteRequest -> Constr #

dataTypeOf :: CutPasteRequest -> DataType #

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

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

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

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

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

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

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

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

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

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CutPasteRequest -> m CutPasteRequest #

Show CutPasteRequest Source # 
Generic CutPasteRequest Source # 
ToJSON CutPasteRequest Source # 
FromJSON CutPasteRequest Source # 
type Rep CutPasteRequest Source # 
type Rep CutPasteRequest = D1 (MetaData "CutPasteRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "CutPasteRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cDestination") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridCoordinate))) ((:*:) (S1 (MetaSel (Just Symbol "_cSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange))) (S1 (MetaSel (Just Symbol "_cPasteType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CutPasteRequestPasteType))))))

cutPasteRequest :: CutPasteRequest Source #

Creates a value of CutPasteRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cDestination :: Lens' CutPasteRequest (Maybe GridCoordinate) Source #

The top-left coordinate where the data should be pasted.

cSource :: Lens' CutPasteRequest (Maybe GridRange) Source #

The source data to cut.

cPasteType :: Lens' CutPasteRequest (Maybe CutPasteRequestPasteType) Source #

What kind of data to paste. All the source data will be cut, regardless of what is pasted.

UpdateEmbeddedObjectPositionResponse

data UpdateEmbeddedObjectPositionResponse Source #

The result of updating an embedded object's position.

See: updateEmbeddedObjectPositionResponse smart constructor.

Instances

Eq UpdateEmbeddedObjectPositionResponse Source # 
Data UpdateEmbeddedObjectPositionResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateEmbeddedObjectPositionResponse -> c UpdateEmbeddedObjectPositionResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateEmbeddedObjectPositionResponse #

toConstr :: UpdateEmbeddedObjectPositionResponse -> Constr #

dataTypeOf :: UpdateEmbeddedObjectPositionResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateEmbeddedObjectPositionResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateEmbeddedObjectPositionResponse) #

gmapT :: (forall b. Data b => b -> b) -> UpdateEmbeddedObjectPositionResponse -> UpdateEmbeddedObjectPositionResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateEmbeddedObjectPositionResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateEmbeddedObjectPositionResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateEmbeddedObjectPositionResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateEmbeddedObjectPositionResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateEmbeddedObjectPositionResponse -> m UpdateEmbeddedObjectPositionResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateEmbeddedObjectPositionResponse -> m UpdateEmbeddedObjectPositionResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateEmbeddedObjectPositionResponse -> m UpdateEmbeddedObjectPositionResponse #

Show UpdateEmbeddedObjectPositionResponse Source # 
Generic UpdateEmbeddedObjectPositionResponse Source # 
ToJSON UpdateEmbeddedObjectPositionResponse Source # 
FromJSON UpdateEmbeddedObjectPositionResponse Source # 
type Rep UpdateEmbeddedObjectPositionResponse Source # 
type Rep UpdateEmbeddedObjectPositionResponse = D1 (MetaData "UpdateEmbeddedObjectPositionResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "UpdateEmbeddedObjectPositionResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_ueoprPosition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe EmbeddedObjectPosition))))

updateEmbeddedObjectPositionResponse :: UpdateEmbeddedObjectPositionResponse Source #

Creates a value of UpdateEmbeddedObjectPositionResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ConditionValueRelativeDate

data ConditionValueRelativeDate Source #

A relative date (based on the current date). Valid only if the type is DATE_BEFORE, DATE_AFTER, DATE_ON_OR_BEFORE or DATE_ON_OR_AFTER. Relative dates are not supported in data validation. They are supported only in conditional formatting and conditional filters.

Constructors

RelativeDateUnspecified

RELATIVE_DATE_UNSPECIFIED Default value, do not use.

PastYear

PAST_YEAR The value is one year before today.

PastMonth

PAST_MONTH The value is one month before today.

PastWeek

PAST_WEEK The value is one week before today.

Yesterday

YESTERDAY The value is yesterday.

Today

TODAY The value is today.

Tomorrow

TOMORROW The value is tomorrow.

Instances

Enum ConditionValueRelativeDate Source # 
Eq ConditionValueRelativeDate Source # 
Data ConditionValueRelativeDate Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConditionValueRelativeDate -> c ConditionValueRelativeDate #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConditionValueRelativeDate #

toConstr :: ConditionValueRelativeDate -> Constr #

dataTypeOf :: ConditionValueRelativeDate -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConditionValueRelativeDate) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConditionValueRelativeDate) #

gmapT :: (forall b. Data b => b -> b) -> ConditionValueRelativeDate -> ConditionValueRelativeDate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConditionValueRelativeDate -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConditionValueRelativeDate -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConditionValueRelativeDate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConditionValueRelativeDate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConditionValueRelativeDate -> m ConditionValueRelativeDate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConditionValueRelativeDate -> m ConditionValueRelativeDate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConditionValueRelativeDate -> m ConditionValueRelativeDate #

Ord ConditionValueRelativeDate Source # 
Read ConditionValueRelativeDate Source # 
Show ConditionValueRelativeDate Source # 
Generic ConditionValueRelativeDate Source # 
Hashable ConditionValueRelativeDate Source # 
ToJSON ConditionValueRelativeDate Source # 
FromJSON ConditionValueRelativeDate Source # 
FromHttpApiData ConditionValueRelativeDate Source # 
ToHttpApiData ConditionValueRelativeDate Source # 
type Rep ConditionValueRelativeDate Source # 
type Rep ConditionValueRelativeDate = D1 (MetaData "ConditionValueRelativeDate" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "RelativeDateUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "PastYear" PrefixI False) U1) (C1 (MetaCons "PastMonth" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PastWeek" PrefixI False) U1) (C1 (MetaCons "Yesterday" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Today" PrefixI False) U1) (C1 (MetaCons "Tomorrow" PrefixI False) U1))))

Response

data Response Source #

A single response from an update.

See: response smart constructor.

Instances

Eq Response Source # 
Data Response Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Response -> c Response #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Response #

toConstr :: Response -> Constr #

dataTypeOf :: Response -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Response) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Response) #

gmapT :: (forall b. Data b => b -> b) -> Response -> Response #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Response -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Response -> r #

gmapQ :: (forall d. Data d => d -> u) -> Response -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Response -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Response -> m Response #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Response -> m Response #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Response -> m Response #

Show Response Source # 
Generic Response Source # 

Associated Types

type Rep Response :: * -> * #

Methods

from :: Response -> Rep Response x #

to :: Rep Response x -> Response #

ToJSON Response Source # 
FromJSON Response Source # 
type Rep Response Source # 
type Rep Response = D1 (MetaData "Response" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "Response'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rAddFilterView") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AddFilterViewResponse))) ((:*:) (S1 (MetaSel (Just Symbol "_rDuplicateFilterView") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DuplicateFilterViewResponse))) (S1 (MetaSel (Just Symbol "_rUpdateEmbeddedObjectPosition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateEmbeddedObjectPositionResponse))))) ((:*:) (S1 (MetaSel (Just Symbol "_rAddSheet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AddSheetResponse))) ((:*:) (S1 (MetaSel (Just Symbol "_rFindReplace") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FindReplaceResponse))) (S1 (MetaSel (Just Symbol "_rAddProtectedRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AddProtectedRangeResponse)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rDeleteConditionalFormatRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeleteConditionalFormatRuleResponse))) ((:*:) (S1 (MetaSel (Just Symbol "_rUpdateConditionalFormatRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateConditionalFormatRuleResponse))) (S1 (MetaSel (Just Symbol "_rAddNamedRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AddNamedRangeResponse))))) ((:*:) (S1 (MetaSel (Just Symbol "_rAddChart") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AddChartResponse))) ((:*:) (S1 (MetaSel (Just Symbol "_rAddBanding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AddBandingResponse))) (S1 (MetaSel (Just Symbol "_rDuplicateSheet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DuplicateSheetResponse))))))))

rAddFilterView :: Lens' Response (Maybe AddFilterViewResponse) Source #

A reply from adding a filter view.

rDuplicateFilterView :: Lens' Response (Maybe DuplicateFilterViewResponse) Source #

A reply from duplicating a filter view.

rUpdateEmbeddedObjectPosition :: Lens' Response (Maybe UpdateEmbeddedObjectPositionResponse) Source #

A reply from updating an embedded object's position.

rAddSheet :: Lens' Response (Maybe AddSheetResponse) Source #

A reply from adding a sheet.

rFindReplace :: Lens' Response (Maybe FindReplaceResponse) Source #

A reply from doing a find/replace.

rAddProtectedRange :: Lens' Response (Maybe AddProtectedRangeResponse) Source #

A reply from adding a protected range.

rDeleteConditionalFormatRule :: Lens' Response (Maybe DeleteConditionalFormatRuleResponse) Source #

A reply from deleting a conditional format rule.

rUpdateConditionalFormatRule :: Lens' Response (Maybe UpdateConditionalFormatRuleResponse) Source #

A reply from updating a conditional format rule.

rAddNamedRange :: Lens' Response (Maybe AddNamedRangeResponse) Source #

A reply from adding a named range.

rAddChart :: Lens' Response (Maybe AddChartResponse) Source #

A reply from adding a chart.

rAddBanding :: Lens' Response (Maybe AddBandingResponse) Source #

A reply from adding a banded range.

rDuplicateSheet :: Lens' Response (Maybe DuplicateSheetResponse) Source #

A reply from duplicating a sheet.

FilterCriteria

data FilterCriteria Source #

Criteria for showing/hiding rows in a filter or filter view.

See: filterCriteria smart constructor.

Instances

Eq FilterCriteria Source # 
Data FilterCriteria Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FilterCriteria -> c FilterCriteria #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FilterCriteria #

toConstr :: FilterCriteria -> Constr #

dataTypeOf :: FilterCriteria -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FilterCriteria) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilterCriteria) #

gmapT :: (forall b. Data b => b -> b) -> FilterCriteria -> FilterCriteria #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FilterCriteria -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FilterCriteria -> r #

gmapQ :: (forall d. Data d => d -> u) -> FilterCriteria -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FilterCriteria -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FilterCriteria -> m FilterCriteria #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FilterCriteria -> m FilterCriteria #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FilterCriteria -> m FilterCriteria #

Show FilterCriteria Source # 
Generic FilterCriteria Source # 

Associated Types

type Rep FilterCriteria :: * -> * #

ToJSON FilterCriteria Source # 
FromJSON FilterCriteria Source # 
type Rep FilterCriteria Source # 
type Rep FilterCriteria = D1 (MetaData "FilterCriteria" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "FilterCriteria'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fcHiddenValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_fcCondition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BooleanCondition)))))

filterCriteria :: FilterCriteria Source #

Creates a value of FilterCriteria with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

fcHiddenValues :: Lens' FilterCriteria [Text] Source #

Values that should be hidden.

fcCondition :: Lens' FilterCriteria (Maybe BooleanCondition) Source #

A condition that must be true for values to be shown. (This does not override hiddenValues -- if a value is listed there, it will still be hidden.)

ErrorValue

data ErrorValue Source #

An error in a cell.

See: errorValue smart constructor.

Instances

Eq ErrorValue Source # 
Data ErrorValue Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ErrorValue -> c ErrorValue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ErrorValue #

toConstr :: ErrorValue -> Constr #

dataTypeOf :: ErrorValue -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ErrorValue) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ErrorValue) #

gmapT :: (forall b. Data b => b -> b) -> ErrorValue -> ErrorValue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ErrorValue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ErrorValue -> r #

gmapQ :: (forall d. Data d => d -> u) -> ErrorValue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ErrorValue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ErrorValue -> m ErrorValue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorValue -> m ErrorValue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorValue -> m ErrorValue #

Show ErrorValue Source # 
Generic ErrorValue Source # 

Associated Types

type Rep ErrorValue :: * -> * #

ToJSON ErrorValue Source # 
FromJSON ErrorValue Source # 
type Rep ErrorValue Source # 
type Rep ErrorValue = D1 (MetaData "ErrorValue" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "ErrorValue'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_evType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ErrorValueType))) (S1 (MetaSel (Just Symbol "_evMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

errorValue :: ErrorValue Source #

Creates a value of ErrorValue with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

evMessage :: Lens' ErrorValue (Maybe Text) Source #

A message with more information about the error (in the spreadsheet's locale).

UpdateConditionalFormatRuleRequest

data UpdateConditionalFormatRuleRequest Source #

Updates a conditional format rule at the given index, or moves a conditional format rule to another index.

See: updateConditionalFormatRuleRequest smart constructor.

Instances

Eq UpdateConditionalFormatRuleRequest Source # 
Data UpdateConditionalFormatRuleRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateConditionalFormatRuleRequest -> c UpdateConditionalFormatRuleRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateConditionalFormatRuleRequest #

toConstr :: UpdateConditionalFormatRuleRequest -> Constr #

dataTypeOf :: UpdateConditionalFormatRuleRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateConditionalFormatRuleRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateConditionalFormatRuleRequest) #

gmapT :: (forall b. Data b => b -> b) -> UpdateConditionalFormatRuleRequest -> UpdateConditionalFormatRuleRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateConditionalFormatRuleRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateConditionalFormatRuleRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateConditionalFormatRuleRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateConditionalFormatRuleRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateConditionalFormatRuleRequest -> m UpdateConditionalFormatRuleRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateConditionalFormatRuleRequest -> m UpdateConditionalFormatRuleRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateConditionalFormatRuleRequest -> m UpdateConditionalFormatRuleRequest #

Show UpdateConditionalFormatRuleRequest Source # 
Generic UpdateConditionalFormatRuleRequest Source # 
ToJSON UpdateConditionalFormatRuleRequest Source # 
FromJSON UpdateConditionalFormatRuleRequest Source # 
type Rep UpdateConditionalFormatRuleRequest Source # 
type Rep UpdateConditionalFormatRuleRequest = D1 (MetaData "UpdateConditionalFormatRuleRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "UpdateConditionalFormatRuleRequest'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ucfrrRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ConditionalFormatRule))) (S1 (MetaSel (Just Symbol "_ucfrrNewIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))) ((:*:) (S1 (MetaSel (Just Symbol "_ucfrrSheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_ucfrrIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))))

updateConditionalFormatRuleRequest :: UpdateConditionalFormatRuleRequest Source #

Creates a value of UpdateConditionalFormatRuleRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ucfrrRule :: Lens' UpdateConditionalFormatRuleRequest (Maybe ConditionalFormatRule) Source #

The rule that should replace the rule at the given index.

ucfrrNewIndex :: Lens' UpdateConditionalFormatRuleRequest (Maybe Int32) Source #

The zero-based new index the rule should end up at.

ucfrrSheetId :: Lens' UpdateConditionalFormatRuleRequest (Maybe Int32) Source #

The sheet of the rule to move. Required if new_index is set, unused otherwise.

ucfrrIndex :: Lens' UpdateConditionalFormatRuleRequest (Maybe Int32) Source #

The zero-based index of the rule that should be replaced or moved.

DeleteConditionalFormatRuleRequest

data DeleteConditionalFormatRuleRequest Source #

Deletes a conditional format rule at the given index. All subsequent rules' indexes are decremented.

See: deleteConditionalFormatRuleRequest smart constructor.

Instances

Eq DeleteConditionalFormatRuleRequest Source # 
Data DeleteConditionalFormatRuleRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeleteConditionalFormatRuleRequest -> c DeleteConditionalFormatRuleRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeleteConditionalFormatRuleRequest #

toConstr :: DeleteConditionalFormatRuleRequest -> Constr #

dataTypeOf :: DeleteConditionalFormatRuleRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeleteConditionalFormatRuleRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeleteConditionalFormatRuleRequest) #

gmapT :: (forall b. Data b => b -> b) -> DeleteConditionalFormatRuleRequest -> DeleteConditionalFormatRuleRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeleteConditionalFormatRuleRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeleteConditionalFormatRuleRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeleteConditionalFormatRuleRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeleteConditionalFormatRuleRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeleteConditionalFormatRuleRequest -> m DeleteConditionalFormatRuleRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteConditionalFormatRuleRequest -> m DeleteConditionalFormatRuleRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteConditionalFormatRuleRequest -> m DeleteConditionalFormatRuleRequest #

Show DeleteConditionalFormatRuleRequest Source # 
Generic DeleteConditionalFormatRuleRequest Source # 
ToJSON DeleteConditionalFormatRuleRequest Source # 
FromJSON DeleteConditionalFormatRuleRequest Source # 
type Rep DeleteConditionalFormatRuleRequest Source # 
type Rep DeleteConditionalFormatRuleRequest = D1 (MetaData "DeleteConditionalFormatRuleRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "DeleteConditionalFormatRuleRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dcfrrSheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_dcfrrIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

deleteConditionalFormatRuleRequest :: DeleteConditionalFormatRuleRequest Source #

Creates a value of DeleteConditionalFormatRuleRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dcfrrSheetId :: Lens' DeleteConditionalFormatRuleRequest (Maybe Int32) Source #

The sheet the rule is being deleted from.

dcfrrIndex :: Lens' DeleteConditionalFormatRuleRequest (Maybe Int32) Source #

The zero-based index of the rule to be deleted.

SortSpecSortOrder

data SortSpecSortOrder Source #

The order data should be sorted.

Constructors

SortOrderUnspecified

SORT_ORDER_UNSPECIFIED Default value, do not use this.

Ascending

ASCENDING Sort ascending.

Descending

DESCENDING Sort descending.

Instances

Enum SortSpecSortOrder Source # 
Eq SortSpecSortOrder Source # 
Data SortSpecSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SortSpecSortOrder -> c SortSpecSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SortSpecSortOrder #

toConstr :: SortSpecSortOrder -> Constr #

dataTypeOf :: SortSpecSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SortSpecSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortSpecSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> SortSpecSortOrder -> SortSpecSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SortSpecSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SortSpecSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> SortSpecSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SortSpecSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SortSpecSortOrder -> m SortSpecSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SortSpecSortOrder -> m SortSpecSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SortSpecSortOrder -> m SortSpecSortOrder #

Ord SortSpecSortOrder Source # 
Read SortSpecSortOrder Source # 
Show SortSpecSortOrder Source # 
Generic SortSpecSortOrder Source # 
Hashable SortSpecSortOrder Source # 
ToJSON SortSpecSortOrder Source # 
FromJSON SortSpecSortOrder Source # 
FromHttpApiData SortSpecSortOrder Source # 
ToHttpApiData SortSpecSortOrder Source # 
type Rep SortSpecSortOrder Source # 
type Rep SortSpecSortOrder = D1 (MetaData "SortSpecSortOrder" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "SortOrderUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "Ascending" PrefixI False) U1) (C1 (MetaCons "Descending" PrefixI False) U1)))

OverlayPosition

data OverlayPosition Source #

The location an object is overlaid on top of a grid.

See: overlayPosition smart constructor.

Instances

Eq OverlayPosition Source # 
Data OverlayPosition Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverlayPosition -> c OverlayPosition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverlayPosition #

toConstr :: OverlayPosition -> Constr #

dataTypeOf :: OverlayPosition -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OverlayPosition) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverlayPosition) #

gmapT :: (forall b. Data b => b -> b) -> OverlayPosition -> OverlayPosition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverlayPosition -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverlayPosition -> r #

gmapQ :: (forall d. Data d => d -> u) -> OverlayPosition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlayPosition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverlayPosition -> m OverlayPosition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlayPosition -> m OverlayPosition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlayPosition -> m OverlayPosition #

Show OverlayPosition Source # 
Generic OverlayPosition Source # 
ToJSON OverlayPosition Source # 
FromJSON OverlayPosition Source # 
type Rep OverlayPosition Source # 
type Rep OverlayPosition = D1 (MetaData "OverlayPosition" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "OverlayPosition'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_opHeightPixels") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_opOffSetYPixels") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))) ((:*:) (S1 (MetaSel (Just Symbol "_opAnchorCell") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridCoordinate))) ((:*:) (S1 (MetaSel (Just Symbol "_opWidthPixels") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_opOffSetXPixels") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))))

overlayPosition :: OverlayPosition Source #

Creates a value of OverlayPosition with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

opHeightPixels :: Lens' OverlayPosition (Maybe Int32) Source #

The height of the object, in pixels. Defaults to 371.

opOffSetYPixels :: Lens' OverlayPosition (Maybe Int32) Source #

The vertical offset, in pixels, that the object is offset from the anchor cell.

opAnchorCell :: Lens' OverlayPosition (Maybe GridCoordinate) Source #

The cell the object is anchored to.

opWidthPixels :: Lens' OverlayPosition (Maybe Int32) Source #

The width of the object, in pixels. Defaults to 600.

opOffSetXPixels :: Lens' OverlayPosition (Maybe Int32) Source #

The horizontal offset, in pixels, that the object is offset from the anchor cell.

DeleteEmbeddedObjectRequest

data DeleteEmbeddedObjectRequest Source #

Deletes the embedded object with the given ID.

See: deleteEmbeddedObjectRequest smart constructor.

Instances

Eq DeleteEmbeddedObjectRequest Source # 
Data DeleteEmbeddedObjectRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeleteEmbeddedObjectRequest -> c DeleteEmbeddedObjectRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeleteEmbeddedObjectRequest #

toConstr :: DeleteEmbeddedObjectRequest -> Constr #

dataTypeOf :: DeleteEmbeddedObjectRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeleteEmbeddedObjectRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeleteEmbeddedObjectRequest) #

gmapT :: (forall b. Data b => b -> b) -> DeleteEmbeddedObjectRequest -> DeleteEmbeddedObjectRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeleteEmbeddedObjectRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeleteEmbeddedObjectRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeleteEmbeddedObjectRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeleteEmbeddedObjectRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeleteEmbeddedObjectRequest -> m DeleteEmbeddedObjectRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteEmbeddedObjectRequest -> m DeleteEmbeddedObjectRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteEmbeddedObjectRequest -> m DeleteEmbeddedObjectRequest #

Show DeleteEmbeddedObjectRequest Source # 
Generic DeleteEmbeddedObjectRequest Source # 
ToJSON DeleteEmbeddedObjectRequest Source # 
FromJSON DeleteEmbeddedObjectRequest Source # 
type Rep DeleteEmbeddedObjectRequest Source # 
type Rep DeleteEmbeddedObjectRequest = D1 (MetaData "DeleteEmbeddedObjectRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "DeleteEmbeddedObjectRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_deorObjectId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Textual Int32)))))

deleteEmbeddedObjectRequest :: DeleteEmbeddedObjectRequest Source #

Creates a value of DeleteEmbeddedObjectRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

deorObjectId :: Lens' DeleteEmbeddedObjectRequest (Maybe Int32) Source #

The ID of the embedded object to delete.

SheetProperties

data SheetProperties Source #

Properties of a sheet.

See: sheetProperties smart constructor.

Instances

Eq SheetProperties Source # 
Data SheetProperties Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SheetProperties -> c SheetProperties #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SheetProperties #

toConstr :: SheetProperties -> Constr #

dataTypeOf :: SheetProperties -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SheetProperties) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SheetProperties) #

gmapT :: (forall b. Data b => b -> b) -> SheetProperties -> SheetProperties #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SheetProperties -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SheetProperties -> r #

gmapQ :: (forall d. Data d => d -> u) -> SheetProperties -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SheetProperties -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SheetProperties -> m SheetProperties #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SheetProperties -> m SheetProperties #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SheetProperties -> m SheetProperties #

Show SheetProperties Source # 
Generic SheetProperties Source # 
ToJSON SheetProperties Source # 
FromJSON SheetProperties Source # 
type Rep SheetProperties Source # 

sheetProperties :: SheetProperties Source #

Creates a value of SheetProperties with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sTabColor :: Lens' SheetProperties (Maybe Color) Source #

The color of the tab in the UI.

sGridProperties :: Lens' SheetProperties (Maybe GridProperties) Source #

Additional properties of the sheet if this sheet is a grid. (If the sheet is an object sheet, containing a chart or image, then this field will be absent.) When writing it is an error to set any grid properties on non-grid sheets.

sSheetType :: Lens' SheetProperties (Maybe SheetPropertiesSheetType) Source #

The type of sheet. Defaults to GRID. This field cannot be changed once set.

sHidden :: Lens' SheetProperties (Maybe Bool) Source #

True if the sheet is hidden in the UI, false if it's visible.

sSheetId :: Lens' SheetProperties (Maybe Int32) Source #

The ID of the sheet. Must be non-negative. This field cannot be changed once set.

sTitle :: Lens' SheetProperties (Maybe Text) Source #

The name of the sheet.

sRightToLeft :: Lens' SheetProperties (Maybe Bool) Source #

True if the sheet is an RTL sheet instead of an LTR sheet.

sIndex :: Lens' SheetProperties (Maybe Int32) Source #

The index of the sheet within the spreadsheet. When adding or updating sheet properties, if this field is excluded then the sheet will be added or moved to the end of the sheet list. When updating sheet indices or inserting sheets, movement is considered in "before the move" indexes. For example, if there were 3 sheets (S1, S2, S3) in order to move S1 ahead of S2 the index would have to be set to 2. A sheet index update request will be ignored if the requested index is identical to the sheets current index or if the requested new index is equal to the current sheet index + 1.

FilterViewCriteria

data FilterViewCriteria Source #

The criteria for showing/hiding values per column. The map's key is the column index, and the value is the criteria for that column.

See: filterViewCriteria smart constructor.

Instances

Eq FilterViewCriteria Source # 
Data FilterViewCriteria Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FilterViewCriteria -> c FilterViewCriteria #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FilterViewCriteria #

toConstr :: FilterViewCriteria -> Constr #

dataTypeOf :: FilterViewCriteria -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FilterViewCriteria) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilterViewCriteria) #

gmapT :: (forall b. Data b => b -> b) -> FilterViewCriteria -> FilterViewCriteria #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FilterViewCriteria -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FilterViewCriteria -> r #

gmapQ :: (forall d. Data d => d -> u) -> FilterViewCriteria -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FilterViewCriteria -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FilterViewCriteria -> m FilterViewCriteria #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FilterViewCriteria -> m FilterViewCriteria #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FilterViewCriteria -> m FilterViewCriteria #

Show FilterViewCriteria Source # 
Generic FilterViewCriteria Source # 
ToJSON FilterViewCriteria Source # 
FromJSON FilterViewCriteria Source # 
type Rep FilterViewCriteria Source # 
type Rep FilterViewCriteria = D1 (MetaData "FilterViewCriteria" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "FilterViewCriteria'" PrefixI True) (S1 (MetaSel (Just Symbol "_fvcAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text FilterCriteria))))

filterViewCriteria Source #

Creates a value of FilterViewCriteria with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

BatchUpdateValuesResponse

data BatchUpdateValuesResponse Source #

The response when updating a range of values in a spreadsheet.

See: batchUpdateValuesResponse smart constructor.

Instances

Eq BatchUpdateValuesResponse Source # 
Data BatchUpdateValuesResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BatchUpdateValuesResponse -> c BatchUpdateValuesResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BatchUpdateValuesResponse #

toConstr :: BatchUpdateValuesResponse -> Constr #

dataTypeOf :: BatchUpdateValuesResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BatchUpdateValuesResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BatchUpdateValuesResponse) #

gmapT :: (forall b. Data b => b -> b) -> BatchUpdateValuesResponse -> BatchUpdateValuesResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BatchUpdateValuesResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BatchUpdateValuesResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> BatchUpdateValuesResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BatchUpdateValuesResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BatchUpdateValuesResponse -> m BatchUpdateValuesResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BatchUpdateValuesResponse -> m BatchUpdateValuesResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BatchUpdateValuesResponse -> m BatchUpdateValuesResponse #

Show BatchUpdateValuesResponse Source # 
Generic BatchUpdateValuesResponse Source # 
ToJSON BatchUpdateValuesResponse Source # 
FromJSON BatchUpdateValuesResponse Source # 
type Rep BatchUpdateValuesResponse Source # 
type Rep BatchUpdateValuesResponse = D1 (MetaData "BatchUpdateValuesResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BatchUpdateValuesResponse'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_buvrTotalUpdatedColumns") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) ((:*:) (S1 (MetaSel (Just Symbol "_buvrResponses") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [UpdateValuesResponse]))) (S1 (MetaSel (Just Symbol "_buvrSpreadsheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_buvrTotalUpdatedSheets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) ((:*:) (S1 (MetaSel (Just Symbol "_buvrTotalUpdatedCells") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_buvrTotalUpdatedRows") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))))

batchUpdateValuesResponse :: BatchUpdateValuesResponse Source #

Creates a value of BatchUpdateValuesResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

buvrTotalUpdatedColumns :: Lens' BatchUpdateValuesResponse (Maybe Int32) Source #

The total number of columns where at least one cell in the column was updated.

buvrResponses :: Lens' BatchUpdateValuesResponse [UpdateValuesResponse] Source #

One UpdateValuesResponse per requested range, in the same order as the requests appeared.

buvrSpreadsheetId :: Lens' BatchUpdateValuesResponse (Maybe Text) Source #

The spreadsheet the updates were applied to.

buvrTotalUpdatedSheets :: Lens' BatchUpdateValuesResponse (Maybe Int32) Source #

The total number of sheets where at least one cell in the sheet was updated.

buvrTotalUpdatedRows :: Lens' BatchUpdateValuesResponse (Maybe Int32) Source #

The total number of rows where at least one cell in the row was updated.

UpdateSheetPropertiesRequest

data UpdateSheetPropertiesRequest Source #

Updates properties of the sheet with the specified sheetId.

See: updateSheetPropertiesRequest smart constructor.

Instances

Eq UpdateSheetPropertiesRequest Source # 
Data UpdateSheetPropertiesRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateSheetPropertiesRequest -> c UpdateSheetPropertiesRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateSheetPropertiesRequest #

toConstr :: UpdateSheetPropertiesRequest -> Constr #

dataTypeOf :: UpdateSheetPropertiesRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateSheetPropertiesRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateSheetPropertiesRequest) #

gmapT :: (forall b. Data b => b -> b) -> UpdateSheetPropertiesRequest -> UpdateSheetPropertiesRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateSheetPropertiesRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateSheetPropertiesRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateSheetPropertiesRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateSheetPropertiesRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateSheetPropertiesRequest -> m UpdateSheetPropertiesRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateSheetPropertiesRequest -> m UpdateSheetPropertiesRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateSheetPropertiesRequest -> m UpdateSheetPropertiesRequest #

Show UpdateSheetPropertiesRequest Source # 
Generic UpdateSheetPropertiesRequest Source # 
ToJSON UpdateSheetPropertiesRequest Source # 
FromJSON UpdateSheetPropertiesRequest Source # 
type Rep UpdateSheetPropertiesRequest Source # 
type Rep UpdateSheetPropertiesRequest = D1 (MetaData "UpdateSheetPropertiesRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "UpdateSheetPropertiesRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_usprFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FieldMask))) (S1 (MetaSel (Just Symbol "_usprProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SheetProperties)))))

updateSheetPropertiesRequest :: UpdateSheetPropertiesRequest Source #

Creates a value of UpdateSheetPropertiesRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

usprFields :: Lens' UpdateSheetPropertiesRequest (Maybe FieldMask) Source #

The fields that should be updated. At least one field must be specified. The root `properties` is implied and should not be specified. A single `"*"` can be used as short-hand for listing every field.

Spreadsheet

data Spreadsheet Source #

Resource that represents a spreadsheet.

See: spreadsheet smart constructor.

Instances

Eq Spreadsheet Source # 
Data Spreadsheet Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Spreadsheet -> c Spreadsheet #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Spreadsheet #

toConstr :: Spreadsheet -> Constr #

dataTypeOf :: Spreadsheet -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Spreadsheet) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Spreadsheet) #

gmapT :: (forall b. Data b => b -> b) -> Spreadsheet -> Spreadsheet #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Spreadsheet -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Spreadsheet -> r #

gmapQ :: (forall d. Data d => d -> u) -> Spreadsheet -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Spreadsheet -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Spreadsheet -> m Spreadsheet #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Spreadsheet -> m Spreadsheet #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Spreadsheet -> m Spreadsheet #

Show Spreadsheet Source # 
Generic Spreadsheet Source # 

Associated Types

type Rep Spreadsheet :: * -> * #

ToJSON Spreadsheet Source # 
FromJSON Spreadsheet Source # 
type Rep Spreadsheet Source # 
type Rep Spreadsheet = D1 (MetaData "Spreadsheet" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "Spreadsheet'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sprSheets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Sheet]))) (S1 (MetaSel (Just Symbol "_sprNamedRanges") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [NamedRange])))) ((:*:) (S1 (MetaSel (Just Symbol "_sprSpreadsheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sprSpreadsheetURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_sprProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SpreadsheetProperties)))))))

spreadsheet :: Spreadsheet Source #

Creates a value of Spreadsheet with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sprSheets :: Lens' Spreadsheet [Sheet] Source #

The sheets that are part of a spreadsheet.

sprNamedRanges :: Lens' Spreadsheet [NamedRange] Source #

The named ranges defined in a spreadsheet.

sprSpreadsheetId :: Lens' Spreadsheet (Maybe Text) Source #

The ID of the spreadsheet. This field is read-only.

sprSpreadsheetURL :: Lens' Spreadsheet (Maybe Text) Source #

The url of the spreadsheet. This field is read-only.

sprProperties :: Lens' Spreadsheet (Maybe SpreadsheetProperties) Source #

Overall properties of a spreadsheet.

InsertDimensionRequest

data InsertDimensionRequest Source #

Inserts rows or columns in a sheet at a particular index.

See: insertDimensionRequest smart constructor.

Instances

Eq InsertDimensionRequest Source # 
Data InsertDimensionRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InsertDimensionRequest -> c InsertDimensionRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InsertDimensionRequest #

toConstr :: InsertDimensionRequest -> Constr #

dataTypeOf :: InsertDimensionRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InsertDimensionRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InsertDimensionRequest) #

gmapT :: (forall b. Data b => b -> b) -> InsertDimensionRequest -> InsertDimensionRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InsertDimensionRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InsertDimensionRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> InsertDimensionRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InsertDimensionRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InsertDimensionRequest -> m InsertDimensionRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InsertDimensionRequest -> m InsertDimensionRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InsertDimensionRequest -> m InsertDimensionRequest #

Show InsertDimensionRequest Source # 
Generic InsertDimensionRequest Source # 
ToJSON InsertDimensionRequest Source # 
FromJSON InsertDimensionRequest Source # 
type Rep InsertDimensionRequest Source # 
type Rep InsertDimensionRequest = D1 (MetaData "InsertDimensionRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "InsertDimensionRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_idrRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionRange))) (S1 (MetaSel (Just Symbol "_idrInheritFromBefore") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))

insertDimensionRequest :: InsertDimensionRequest Source #

Creates a value of InsertDimensionRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

idrRange :: Lens' InsertDimensionRequest (Maybe DimensionRange) Source #

The dimensions to insert. Both the start and end indexes must be bounded.

idrInheritFromBefore :: Lens' InsertDimensionRequest (Maybe Bool) Source #

Whether dimension properties should be extended from the dimensions before or after the newly inserted dimensions. True to inherit from the dimensions before (in which case the start index must be greater than 0), and false to inherit from the dimensions after. For example, if row index 0 has red background and row index 1 has a green background, then inserting 2 rows at index 1 can inherit either the green or red background. If `inheritFromBefore` is true, the two new rows will be red (because the row before the insertion point was red), whereas if `inheritFromBefore` is false, the two new rows will be green (because the row after the insertion point was green).

PivotValueSummarizeFunction

data PivotValueSummarizeFunction Source #

A function to summarize the value. If formula is set, the only supported values are SUM and CUSTOM. If sourceColumnOffset is set, then `CUSTOM` is not supported.

Constructors

PivotStandardValueFunctionUnspecified

PIVOT_STANDARD_VALUE_FUNCTION_UNSPECIFIED The default, do not use.

Sum

SUM Corresponds to the `SUM` function.

Counta

COUNTA Corresponds to the `COUNTA` function.

Count

COUNT Corresponds to the `COUNT` function.

Countunique

COUNTUNIQUE Corresponds to the `COUNTUNIQUE` function.

Average

AVERAGE Corresponds to the `AVERAGE` function.

Max

MAX Corresponds to the `MAX` function.

Min

MIN Corresponds to the `MIN` function.

Median

MEDIAN Corresponds to the `MEDIAN` function.

Product

PRODUCT Corresponds to the `PRODUCT` function.

Stdev

STDEV Corresponds to the `STDEV` function.

Stdevp

STDEVP Corresponds to the `STDEVP` function.

Var

VAR Corresponds to the `VAR` function.

Varp

VARP Corresponds to the `VARP` function.

Custom

CUSTOM Indicates the formula should be used as-is. Only valid if PivotValue.formula was set.

Instances

Enum PivotValueSummarizeFunction Source # 
Eq PivotValueSummarizeFunction Source # 
Data PivotValueSummarizeFunction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PivotValueSummarizeFunction -> c PivotValueSummarizeFunction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PivotValueSummarizeFunction #

toConstr :: PivotValueSummarizeFunction -> Constr #

dataTypeOf :: PivotValueSummarizeFunction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PivotValueSummarizeFunction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PivotValueSummarizeFunction) #

gmapT :: (forall b. Data b => b -> b) -> PivotValueSummarizeFunction -> PivotValueSummarizeFunction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PivotValueSummarizeFunction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PivotValueSummarizeFunction -> r #

gmapQ :: (forall d. Data d => d -> u) -> PivotValueSummarizeFunction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PivotValueSummarizeFunction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PivotValueSummarizeFunction -> m PivotValueSummarizeFunction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotValueSummarizeFunction -> m PivotValueSummarizeFunction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotValueSummarizeFunction -> m PivotValueSummarizeFunction #

Ord PivotValueSummarizeFunction Source # 
Read PivotValueSummarizeFunction Source # 
Show PivotValueSummarizeFunction Source # 
Generic PivotValueSummarizeFunction Source # 
Hashable PivotValueSummarizeFunction Source # 
ToJSON PivotValueSummarizeFunction Source # 
FromJSON PivotValueSummarizeFunction Source # 
FromHttpApiData PivotValueSummarizeFunction Source # 
ToHttpApiData PivotValueSummarizeFunction Source # 
type Rep PivotValueSummarizeFunction Source # 
type Rep PivotValueSummarizeFunction = D1 (MetaData "PivotValueSummarizeFunction" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "PivotStandardValueFunctionUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "Sum" PrefixI False) U1) (C1 (MetaCons "Counta" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Count" PrefixI False) U1) (C1 (MetaCons "Countunique" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Average" PrefixI False) U1) (C1 (MetaCons "Max" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Min" PrefixI False) U1) (C1 (MetaCons "Median" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Product" PrefixI False) U1) (C1 (MetaCons "Stdev" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Stdevp" PrefixI False) U1) (C1 (MetaCons "Var" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Varp" PrefixI False) U1) (C1 (MetaCons "Custom" PrefixI False) U1)))))

InterpolationPoint

data InterpolationPoint Source #

A single interpolation point on a gradient conditional format. These pin the gradient color scale according to the color, type and value chosen.

See: interpolationPoint smart constructor.

Instances

Eq InterpolationPoint Source # 
Data InterpolationPoint Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InterpolationPoint -> c InterpolationPoint #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InterpolationPoint #

toConstr :: InterpolationPoint -> Constr #

dataTypeOf :: InterpolationPoint -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InterpolationPoint) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InterpolationPoint) #

gmapT :: (forall b. Data b => b -> b) -> InterpolationPoint -> InterpolationPoint #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InterpolationPoint -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InterpolationPoint -> r #

gmapQ :: (forall d. Data d => d -> u) -> InterpolationPoint -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InterpolationPoint -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InterpolationPoint -> m InterpolationPoint #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InterpolationPoint -> m InterpolationPoint #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InterpolationPoint -> m InterpolationPoint #

Show InterpolationPoint Source # 
Generic InterpolationPoint Source # 
ToJSON InterpolationPoint Source # 
FromJSON InterpolationPoint Source # 
type Rep InterpolationPoint Source # 
type Rep InterpolationPoint = D1 (MetaData "InterpolationPoint" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "InterpolationPoint'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ipColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Color))) ((:*:) (S1 (MetaSel (Just Symbol "_ipValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ipType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe InterpolationPointType))))))

interpolationPoint :: InterpolationPoint Source #

Creates a value of InterpolationPoint with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ipColor :: Lens' InterpolationPoint (Maybe Color) Source #

The color this interpolation point should use.

ipValue :: Lens' InterpolationPoint (Maybe Text) Source #

The value this interpolation point uses. May be a formula. Unused if type is MIN or MAX.

ipType :: Lens' InterpolationPoint (Maybe InterpolationPointType) Source #

How the value should be interpreted.

CellData

data CellData Source #

Data about a specific cell.

See: cellData smart constructor.

Instances

Eq CellData Source # 
Data CellData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CellData -> c CellData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CellData #

toConstr :: CellData -> Constr #

dataTypeOf :: CellData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CellData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CellData) #

gmapT :: (forall b. Data b => b -> b) -> CellData -> CellData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CellData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CellData -> r #

gmapQ :: (forall d. Data d => d -> u) -> CellData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CellData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CellData -> m CellData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CellData -> m CellData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CellData -> m CellData #

Show CellData Source # 
Generic CellData Source # 

Associated Types

type Rep CellData :: * -> * #

Methods

from :: CellData -> Rep CellData x #

to :: Rep CellData x -> CellData #

ToJSON CellData Source # 
FromJSON CellData Source # 
type Rep CellData Source # 

cellData :: CellData Source #

Creates a value of CellData with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cdTextFormatRuns :: Lens' CellData [TextFormatRun] Source #

Runs of rich text applied to subsections of the cell. Runs are only valid on user entered strings, not formulas, bools, or numbers. Runs start at specific indexes in the text and continue until the next run. Properties of a run will continue unless explicitly changed in a subsequent run (and properties of the first run will continue the properties of the cell unless explicitly changed). When writing, the new runs will overwrite any prior runs. When writing a new user_entered_value, previous runs will be erased.

cdNote :: Lens' CellData (Maybe Text) Source #

Any note on the cell.

cdUserEnteredValue :: Lens' CellData (Maybe ExtendedValue) Source #

The value the user entered in the cell. e.g, `1234`, `'Hello'`, or `=NOW()` Note: Dates, Times and DateTimes are represented as doubles in serial number format.

cdUserEnteredFormat :: Lens' CellData (Maybe CellFormat) Source #

The format the user entered for the cell. When writing, the new format will be merged with the existing format.

cdEffectiveFormat :: Lens' CellData (Maybe CellFormat) Source #

The effective format being used by the cell. This includes the results of applying any conditional formatting and, if the cell contains a formula, the computed number format. If the effective format is the default format, effective format will not be written. This field is read-only.

cdPivotTable :: Lens' CellData (Maybe PivotTable) Source #

A pivot table anchored at this cell. The size of pivot table itself is computed dynamically based on its data, grouping, filters, values, etc. Only the top-left cell of the pivot table contains the pivot table definition. The other cells will contain the calculated values of the results of the pivot in their effective_value fields.

cdFormattedValue :: Lens' CellData (Maybe Text) Source #

The formatted value of the cell. This is the value as it's shown to the user. This field is read-only.

cdDataValidation :: Lens' CellData (Maybe DataValidationRule) Source #

A data validation rule on the cell, if any. When writing, the new data validation rule will overwrite any prior rule.

cdHyperlink :: Lens' CellData (Maybe Text) Source #

A hyperlink this cell points to, if any. This field is read-only. (To set it, use a `=HYPERLINK` formula.)

cdEffectiveValue :: Lens' CellData (Maybe ExtendedValue) Source #

The effective value of the cell. For cells with formulas, this will be the calculated value. For cells with literals, this will be the same as the user_entered_value. This field is read-only.

ChartSourceRange

data ChartSourceRange Source #

Source ranges for a chart.

See: chartSourceRange smart constructor.

Instances

Eq ChartSourceRange Source # 
Data ChartSourceRange Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChartSourceRange -> c ChartSourceRange #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChartSourceRange #

toConstr :: ChartSourceRange -> Constr #

dataTypeOf :: ChartSourceRange -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ChartSourceRange) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChartSourceRange) #

gmapT :: (forall b. Data b => b -> b) -> ChartSourceRange -> ChartSourceRange #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChartSourceRange -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChartSourceRange -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChartSourceRange -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChartSourceRange -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChartSourceRange -> m ChartSourceRange #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChartSourceRange -> m ChartSourceRange #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChartSourceRange -> m ChartSourceRange #

Show ChartSourceRange Source # 
Generic ChartSourceRange Source # 
ToJSON ChartSourceRange Source # 
FromJSON ChartSourceRange Source # 
type Rep ChartSourceRange Source # 
type Rep ChartSourceRange = D1 (MetaData "ChartSourceRange" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "ChartSourceRange'" PrefixI True) (S1 (MetaSel (Just Symbol "_csrSources") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [GridRange]))))

chartSourceRange :: ChartSourceRange Source #

Creates a value of ChartSourceRange with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

csrSources :: Lens' ChartSourceRange [GridRange] Source #

The ranges of data for a series or domain. Exactly one dimension must have a length of 1, and all sources in the list must have the same dimension with length 1. The domain (if it exists) & all series must have the same number of source ranges. If using more than one source range, then the source range at a given offset must be contiguous across the domain and series. For example, these are valid configurations: domain sources: A1:A5 series1 sources: B1:B5 series2 sources: D6:D10 domain sources: A1:A5, C10:C12 series1 sources: B1:B5, D10:D12 series2 sources: C1:C5, E10:E12

AddNamedRangeResponse

data AddNamedRangeResponse Source #

The result of adding a named range.

See: addNamedRangeResponse smart constructor.

Instances

Eq AddNamedRangeResponse Source # 
Data AddNamedRangeResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddNamedRangeResponse -> c AddNamedRangeResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddNamedRangeResponse #

toConstr :: AddNamedRangeResponse -> Constr #

dataTypeOf :: AddNamedRangeResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddNamedRangeResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddNamedRangeResponse) #

gmapT :: (forall b. Data b => b -> b) -> AddNamedRangeResponse -> AddNamedRangeResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddNamedRangeResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddNamedRangeResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddNamedRangeResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddNamedRangeResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddNamedRangeResponse -> m AddNamedRangeResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddNamedRangeResponse -> m AddNamedRangeResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddNamedRangeResponse -> m AddNamedRangeResponse #

Show AddNamedRangeResponse Source # 
Generic AddNamedRangeResponse Source # 
ToJSON AddNamedRangeResponse Source # 
FromJSON AddNamedRangeResponse Source # 
type Rep AddNamedRangeResponse Source # 
type Rep AddNamedRangeResponse = D1 (MetaData "AddNamedRangeResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "AddNamedRangeResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_anrrNamedRange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NamedRange))))

addNamedRangeResponse :: AddNamedRangeResponse Source #

Creates a value of AddNamedRangeResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

AddChartResponse

data AddChartResponse Source #

The result of adding a chart to a spreadsheet.

See: addChartResponse smart constructor.

Instances

Eq AddChartResponse Source # 
Data AddChartResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddChartResponse -> c AddChartResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddChartResponse #

toConstr :: AddChartResponse -> Constr #

dataTypeOf :: AddChartResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddChartResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddChartResponse) #

gmapT :: (forall b. Data b => b -> b) -> AddChartResponse -> AddChartResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddChartResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddChartResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddChartResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddChartResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddChartResponse -> m AddChartResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddChartResponse -> m AddChartResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddChartResponse -> m AddChartResponse #

Show AddChartResponse Source # 
Generic AddChartResponse Source # 
ToJSON AddChartResponse Source # 
FromJSON AddChartResponse Source # 
type Rep AddChartResponse Source # 
type Rep AddChartResponse = D1 (MetaData "AddChartResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "AddChartResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_acrChart") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe EmbeddedChart))))

addChartResponse :: AddChartResponse Source #

Creates a value of AddChartResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

UpdateChartSpecRequest

data UpdateChartSpecRequest Source #

Updates a chart's specifications. (This does not move or resize a chart. To move or resize a chart, use UpdateEmbeddedObjectPositionRequest.)

See: updateChartSpecRequest smart constructor.

Instances

Eq UpdateChartSpecRequest Source # 
Data UpdateChartSpecRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateChartSpecRequest -> c UpdateChartSpecRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateChartSpecRequest #

toConstr :: UpdateChartSpecRequest -> Constr #

dataTypeOf :: UpdateChartSpecRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateChartSpecRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateChartSpecRequest) #

gmapT :: (forall b. Data b => b -> b) -> UpdateChartSpecRequest -> UpdateChartSpecRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateChartSpecRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateChartSpecRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateChartSpecRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateChartSpecRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateChartSpecRequest -> m UpdateChartSpecRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateChartSpecRequest -> m UpdateChartSpecRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateChartSpecRequest -> m UpdateChartSpecRequest #

Show UpdateChartSpecRequest Source # 
Generic UpdateChartSpecRequest Source # 
ToJSON UpdateChartSpecRequest Source # 
FromJSON UpdateChartSpecRequest Source # 
type Rep UpdateChartSpecRequest Source # 
type Rep UpdateChartSpecRequest = D1 (MetaData "UpdateChartSpecRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "UpdateChartSpecRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ucsrSpec") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChartSpec))) (S1 (MetaSel (Just Symbol "_ucsrChartId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

updateChartSpecRequest :: UpdateChartSpecRequest Source #

Creates a value of UpdateChartSpecRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ucsrSpec :: Lens' UpdateChartSpecRequest (Maybe ChartSpec) Source #

The specification to apply to the chart.

ucsrChartId :: Lens' UpdateChartSpecRequest (Maybe Int32) Source #

The ID of the chart to update.

SetBasicFilterRequest

data SetBasicFilterRequest Source #

Sets the basic filter associated with a sheet.

See: setBasicFilterRequest smart constructor.

Instances

Eq SetBasicFilterRequest Source # 
Data SetBasicFilterRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SetBasicFilterRequest -> c SetBasicFilterRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SetBasicFilterRequest #

toConstr :: SetBasicFilterRequest -> Constr #

dataTypeOf :: SetBasicFilterRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SetBasicFilterRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SetBasicFilterRequest) #

gmapT :: (forall b. Data b => b -> b) -> SetBasicFilterRequest -> SetBasicFilterRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SetBasicFilterRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SetBasicFilterRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> SetBasicFilterRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SetBasicFilterRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SetBasicFilterRequest -> m SetBasicFilterRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SetBasicFilterRequest -> m SetBasicFilterRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SetBasicFilterRequest -> m SetBasicFilterRequest #

Show SetBasicFilterRequest Source # 
Generic SetBasicFilterRequest Source # 
ToJSON SetBasicFilterRequest Source # 
FromJSON SetBasicFilterRequest Source # 
type Rep SetBasicFilterRequest Source # 
type Rep SetBasicFilterRequest = D1 (MetaData "SetBasicFilterRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "SetBasicFilterRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_sbfrFilter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BasicFilter))))

setBasicFilterRequest :: SetBasicFilterRequest Source #

Creates a value of SetBasicFilterRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

GridProperties

data GridProperties Source #

Properties of a grid.

See: gridProperties smart constructor.

Instances

Eq GridProperties Source # 
Data GridProperties Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GridProperties -> c GridProperties #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GridProperties #

toConstr :: GridProperties -> Constr #

dataTypeOf :: GridProperties -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GridProperties) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GridProperties) #

gmapT :: (forall b. Data b => b -> b) -> GridProperties -> GridProperties #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GridProperties -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GridProperties -> r #

gmapQ :: (forall d. Data d => d -> u) -> GridProperties -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GridProperties -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GridProperties -> m GridProperties #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GridProperties -> m GridProperties #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GridProperties -> m GridProperties #

Show GridProperties Source # 
Generic GridProperties Source # 

Associated Types

type Rep GridProperties :: * -> * #

ToJSON GridProperties Source # 
FromJSON GridProperties Source # 
type Rep GridProperties Source # 
type Rep GridProperties = D1 (MetaData "GridProperties" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "GridProperties'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gpFrozenColumnCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_gpColumnCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))) ((:*:) (S1 (MetaSel (Just Symbol "_gpHideGridlines") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_gpFrozenRowCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_gpRowCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))))

gridProperties :: GridProperties Source #

Creates a value of GridProperties with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

gpFrozenColumnCount :: Lens' GridProperties (Maybe Int32) Source #

The number of columns that are frozen in the grid.

gpColumnCount :: Lens' GridProperties (Maybe Int32) Source #

The number of columns in the grid.

gpHideGridlines :: Lens' GridProperties (Maybe Bool) Source #

True if the grid isn't showing gridlines in the UI.

gpFrozenRowCount :: Lens' GridProperties (Maybe Int32) Source #

The number of rows that are frozen in the grid.

gpRowCount :: Lens' GridProperties (Maybe Int32) Source #

The number of rows in the grid.

CellFormatHyperlinkDisplayType

data CellFormatHyperlinkDisplayType Source #

How a hyperlink, if it exists, should be displayed in the cell.

Constructors

HyperlinkDisplayTypeUnspecified

HYPERLINK_DISPLAY_TYPE_UNSPECIFIED The default value: the hyperlink is rendered. Do not use this.

Linked

LINKED A hyperlink should be explicitly rendered.

PlainText

PLAIN_TEXT A hyperlink should not be rendered.

Instances

Enum CellFormatHyperlinkDisplayType Source # 
Eq CellFormatHyperlinkDisplayType Source # 
Data CellFormatHyperlinkDisplayType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CellFormatHyperlinkDisplayType -> c CellFormatHyperlinkDisplayType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CellFormatHyperlinkDisplayType #

toConstr :: CellFormatHyperlinkDisplayType -> Constr #

dataTypeOf :: CellFormatHyperlinkDisplayType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CellFormatHyperlinkDisplayType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CellFormatHyperlinkDisplayType) #

gmapT :: (forall b. Data b => b -> b) -> CellFormatHyperlinkDisplayType -> CellFormatHyperlinkDisplayType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CellFormatHyperlinkDisplayType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CellFormatHyperlinkDisplayType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CellFormatHyperlinkDisplayType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CellFormatHyperlinkDisplayType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CellFormatHyperlinkDisplayType -> m CellFormatHyperlinkDisplayType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CellFormatHyperlinkDisplayType -> m CellFormatHyperlinkDisplayType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CellFormatHyperlinkDisplayType -> m CellFormatHyperlinkDisplayType #

Ord CellFormatHyperlinkDisplayType Source # 
Read CellFormatHyperlinkDisplayType Source # 
Show CellFormatHyperlinkDisplayType Source # 
Generic CellFormatHyperlinkDisplayType Source # 
Hashable CellFormatHyperlinkDisplayType Source # 
ToJSON CellFormatHyperlinkDisplayType Source # 
FromJSON CellFormatHyperlinkDisplayType Source # 
FromHttpApiData CellFormatHyperlinkDisplayType Source # 
ToHttpApiData CellFormatHyperlinkDisplayType Source # 
type Rep CellFormatHyperlinkDisplayType Source # 
type Rep CellFormatHyperlinkDisplayType = D1 (MetaData "CellFormatHyperlinkDisplayType" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "HyperlinkDisplayTypeUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "Linked" PrefixI False) U1) (C1 (MetaCons "PlainText" PrefixI False) U1)))

BasicFilterCriteria

data BasicFilterCriteria Source #

The criteria for showing/hiding values per column. The map's key is the column index, and the value is the criteria for that column.

See: basicFilterCriteria smart constructor.

Instances

Eq BasicFilterCriteria Source # 
Data BasicFilterCriteria Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BasicFilterCriteria -> c BasicFilterCriteria #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BasicFilterCriteria #

toConstr :: BasicFilterCriteria -> Constr #

dataTypeOf :: BasicFilterCriteria -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BasicFilterCriteria) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BasicFilterCriteria) #

gmapT :: (forall b. Data b => b -> b) -> BasicFilterCriteria -> BasicFilterCriteria #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BasicFilterCriteria -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BasicFilterCriteria -> r #

gmapQ :: (forall d. Data d => d -> u) -> BasicFilterCriteria -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BasicFilterCriteria -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BasicFilterCriteria -> m BasicFilterCriteria #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicFilterCriteria -> m BasicFilterCriteria #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicFilterCriteria -> m BasicFilterCriteria #

Show BasicFilterCriteria Source # 
Generic BasicFilterCriteria Source # 
ToJSON BasicFilterCriteria Source # 
FromJSON BasicFilterCriteria Source # 
type Rep BasicFilterCriteria Source # 
type Rep BasicFilterCriteria = D1 (MetaData "BasicFilterCriteria" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "BasicFilterCriteria'" PrefixI True) (S1 (MetaSel (Just Symbol "_bfcAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text FilterCriteria))))

basicFilterCriteria Source #

Creates a value of BasicFilterCriteria with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

AddBandingRequest

data AddBandingRequest Source #

Adds a new banded range to the spreadsheet.

See: addBandingRequest smart constructor.

Instances

Eq AddBandingRequest Source # 
Data AddBandingRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddBandingRequest -> c AddBandingRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddBandingRequest #

toConstr :: AddBandingRequest -> Constr #

dataTypeOf :: AddBandingRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddBandingRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddBandingRequest) #

gmapT :: (forall b. Data b => b -> b) -> AddBandingRequest -> AddBandingRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddBandingRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddBandingRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddBandingRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddBandingRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddBandingRequest -> m AddBandingRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddBandingRequest -> m AddBandingRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddBandingRequest -> m AddBandingRequest #

Show AddBandingRequest Source # 
Generic AddBandingRequest Source # 
ToJSON AddBandingRequest Source # 
FromJSON AddBandingRequest Source # 
type Rep AddBandingRequest Source # 
type Rep AddBandingRequest = D1 (MetaData "AddBandingRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "AddBandingRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_abrBandedRange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BandedRange))))

addBandingRequest :: AddBandingRequest Source #

Creates a value of AddBandingRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

abrBandedRange :: Lens' AddBandingRequest (Maybe BandedRange) Source #

The banded range to add. The bandedRangeId field is optional; if one is not set, an id will be randomly generated. (It is an error to specify the ID of a range that already exists.)

UpdateDimensionPropertiesRequest

data UpdateDimensionPropertiesRequest Source #

Updates properties of dimensions within the specified range.

See: updateDimensionPropertiesRequest smart constructor.

Instances

Eq UpdateDimensionPropertiesRequest Source # 
Data UpdateDimensionPropertiesRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateDimensionPropertiesRequest -> c UpdateDimensionPropertiesRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateDimensionPropertiesRequest #

toConstr :: UpdateDimensionPropertiesRequest -> Constr #

dataTypeOf :: UpdateDimensionPropertiesRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateDimensionPropertiesRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateDimensionPropertiesRequest) #

gmapT :: (forall b. Data b => b -> b) -> UpdateDimensionPropertiesRequest -> UpdateDimensionPropertiesRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateDimensionPropertiesRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateDimensionPropertiesRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateDimensionPropertiesRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateDimensionPropertiesRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateDimensionPropertiesRequest -> m UpdateDimensionPropertiesRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateDimensionPropertiesRequest -> m UpdateDimensionPropertiesRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateDimensionPropertiesRequest -> m UpdateDimensionPropertiesRequest #

Show UpdateDimensionPropertiesRequest Source # 
Generic UpdateDimensionPropertiesRequest Source # 
ToJSON UpdateDimensionPropertiesRequest Source # 
FromJSON UpdateDimensionPropertiesRequest Source # 
type Rep UpdateDimensionPropertiesRequest Source # 
type Rep UpdateDimensionPropertiesRequest = D1 (MetaData "UpdateDimensionPropertiesRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "UpdateDimensionPropertiesRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_udprRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionRange))) ((:*:) (S1 (MetaSel (Just Symbol "_udprFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FieldMask))) (S1 (MetaSel (Just Symbol "_udprProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionProperties))))))

updateDimensionPropertiesRequest :: UpdateDimensionPropertiesRequest Source #

Creates a value of UpdateDimensionPropertiesRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

udprFields :: Lens' UpdateDimensionPropertiesRequest (Maybe FieldMask) Source #

The fields that should be updated. At least one field must be specified. The root `properties` is implied and should not be specified. A single `"*"` can be used as short-hand for listing every field.

PivotTableCriteria

data PivotTableCriteria Source #

An optional mapping of filters per source column offset. The filters will be applied before aggregating data into the pivot table. The map's key is the column offset of the source range that you want to filter, and the value is the criteria for that column. For example, if the source was `C10:E15`, a key of `0` will have the filter for column `C`, whereas the key `1` is for column `D`.

See: pivotTableCriteria smart constructor.

Instances

Eq PivotTableCriteria Source # 
Data PivotTableCriteria Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PivotTableCriteria -> c PivotTableCriteria #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PivotTableCriteria #

toConstr :: PivotTableCriteria -> Constr #

dataTypeOf :: PivotTableCriteria -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PivotTableCriteria) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PivotTableCriteria) #

gmapT :: (forall b. Data b => b -> b) -> PivotTableCriteria -> PivotTableCriteria #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PivotTableCriteria -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PivotTableCriteria -> r #

gmapQ :: (forall d. Data d => d -> u) -> PivotTableCriteria -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PivotTableCriteria -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PivotTableCriteria -> m PivotTableCriteria #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotTableCriteria -> m PivotTableCriteria #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotTableCriteria -> m PivotTableCriteria #

Show PivotTableCriteria Source # 
Generic PivotTableCriteria Source # 
ToJSON PivotTableCriteria Source # 
FromJSON PivotTableCriteria Source # 
type Rep PivotTableCriteria Source # 
type Rep PivotTableCriteria = D1 (MetaData "PivotTableCriteria" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "PivotTableCriteria'" PrefixI True) (S1 (MetaSel (Just Symbol "_ptcAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text PivotFilterCriteria))))

pivotTableCriteria Source #

Creates a value of PivotTableCriteria with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

AutoFillRequest

data AutoFillRequest Source #

Fills in more data based on existing data.

See: autoFillRequest smart constructor.

Instances

Eq AutoFillRequest Source # 
Data AutoFillRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AutoFillRequest -> c AutoFillRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AutoFillRequest #

toConstr :: AutoFillRequest -> Constr #

dataTypeOf :: AutoFillRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AutoFillRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AutoFillRequest) #

gmapT :: (forall b. Data b => b -> b) -> AutoFillRequest -> AutoFillRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AutoFillRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AutoFillRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> AutoFillRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AutoFillRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AutoFillRequest -> m AutoFillRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AutoFillRequest -> m AutoFillRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AutoFillRequest -> m AutoFillRequest #

Show AutoFillRequest Source # 
Generic AutoFillRequest Source # 
ToJSON AutoFillRequest Source # 
FromJSON AutoFillRequest Source # 
type Rep AutoFillRequest Source # 
type Rep AutoFillRequest = D1 (MetaData "AutoFillRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "AutoFillRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_afrSourceAndDestination") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SourceAndDestination))) ((:*:) (S1 (MetaSel (Just Symbol "_afrUseAlternateSeries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_afrRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange))))))

autoFillRequest :: AutoFillRequest Source #

Creates a value of AutoFillRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

afrSourceAndDestination :: Lens' AutoFillRequest (Maybe SourceAndDestination) Source #

The source and destination areas to autofill. This explicitly lists the source of the autofill and where to extend that data.

afrUseAlternateSeries :: Lens' AutoFillRequest (Maybe Bool) Source #

True if we should generate data with the "alternate" series. This differs based on the type and amount of source data.

afrRange :: Lens' AutoFillRequest (Maybe GridRange) Source #

The range to autofill. This will examine the range and detect the location that has data and automatically fill that data in to the rest of the range.

DuplicateSheetRequest

data DuplicateSheetRequest Source #

Duplicates the contents of a sheet.

See: duplicateSheetRequest smart constructor.

Instances

Eq DuplicateSheetRequest Source # 
Data DuplicateSheetRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DuplicateSheetRequest -> c DuplicateSheetRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DuplicateSheetRequest #

toConstr :: DuplicateSheetRequest -> Constr #

dataTypeOf :: DuplicateSheetRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DuplicateSheetRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DuplicateSheetRequest) #

gmapT :: (forall b. Data b => b -> b) -> DuplicateSheetRequest -> DuplicateSheetRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DuplicateSheetRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DuplicateSheetRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> DuplicateSheetRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DuplicateSheetRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DuplicateSheetRequest -> m DuplicateSheetRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DuplicateSheetRequest -> m DuplicateSheetRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DuplicateSheetRequest -> m DuplicateSheetRequest #

Show DuplicateSheetRequest Source # 
Generic DuplicateSheetRequest Source # 
ToJSON DuplicateSheetRequest Source # 
FromJSON DuplicateSheetRequest Source # 
type Rep DuplicateSheetRequest Source # 
type Rep DuplicateSheetRequest = D1 (MetaData "DuplicateSheetRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "DuplicateSheetRequest'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_dsrNewSheetName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_dsrInsertSheetIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))) ((:*:) (S1 (MetaSel (Just Symbol "_dsrSourceSheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_dsrNewSheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))))

duplicateSheetRequest :: DuplicateSheetRequest Source #

Creates a value of DuplicateSheetRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dsrNewSheetName :: Lens' DuplicateSheetRequest (Maybe Text) Source #

The name of the new sheet. If empty, a new name is chosen for you.

dsrInsertSheetIndex :: Lens' DuplicateSheetRequest (Maybe Int32) Source #

The zero-based index where the new sheet should be inserted. The index of all sheets after this are incremented.

dsrNewSheetId :: Lens' DuplicateSheetRequest (Maybe Int32) Source #

If set, the ID of the new sheet. If not set, an ID is chosen. If set, the ID must not conflict with any existing sheet ID. If set, it must be non-negative.

DuplicateFilterViewResponse

data DuplicateFilterViewResponse Source #

The result of a filter view being duplicated.

See: duplicateFilterViewResponse smart constructor.

Instances

Eq DuplicateFilterViewResponse Source # 
Data DuplicateFilterViewResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DuplicateFilterViewResponse -> c DuplicateFilterViewResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DuplicateFilterViewResponse #

toConstr :: DuplicateFilterViewResponse -> Constr #

dataTypeOf :: DuplicateFilterViewResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DuplicateFilterViewResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DuplicateFilterViewResponse) #

gmapT :: (forall b. Data b => b -> b) -> DuplicateFilterViewResponse -> DuplicateFilterViewResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DuplicateFilterViewResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DuplicateFilterViewResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> DuplicateFilterViewResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DuplicateFilterViewResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DuplicateFilterViewResponse -> m DuplicateFilterViewResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DuplicateFilterViewResponse -> m DuplicateFilterViewResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DuplicateFilterViewResponse -> m DuplicateFilterViewResponse #

Show DuplicateFilterViewResponse Source # 
Generic DuplicateFilterViewResponse Source # 
ToJSON DuplicateFilterViewResponse Source # 
FromJSON DuplicateFilterViewResponse Source # 
type Rep DuplicateFilterViewResponse Source # 
type Rep DuplicateFilterViewResponse = D1 (MetaData "DuplicateFilterViewResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "DuplicateFilterViewResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_dfvrFilter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilterView))))

duplicateFilterViewResponse :: DuplicateFilterViewResponse Source #

Creates a value of DuplicateFilterViewResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

SheetPropertiesSheetType

data SheetPropertiesSheetType Source #

The type of sheet. Defaults to GRID. This field cannot be changed once set.

Constructors

SheetTypeUnspecified

SHEET_TYPE_UNSPECIFIED Default value, do not use.

Grid

GRID The sheet is a grid.

Object

OBJECT The sheet has no grid and instead has an object like a chart or image.

Instances

Enum SheetPropertiesSheetType Source # 
Eq SheetPropertiesSheetType Source # 
Data SheetPropertiesSheetType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SheetPropertiesSheetType -> c SheetPropertiesSheetType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SheetPropertiesSheetType #

toConstr :: SheetPropertiesSheetType -> Constr #

dataTypeOf :: SheetPropertiesSheetType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SheetPropertiesSheetType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SheetPropertiesSheetType) #

gmapT :: (forall b. Data b => b -> b) -> SheetPropertiesSheetType -> SheetPropertiesSheetType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SheetPropertiesSheetType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SheetPropertiesSheetType -> r #

gmapQ :: (forall d. Data d => d -> u) -> SheetPropertiesSheetType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SheetPropertiesSheetType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SheetPropertiesSheetType -> m SheetPropertiesSheetType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SheetPropertiesSheetType -> m SheetPropertiesSheetType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SheetPropertiesSheetType -> m SheetPropertiesSheetType #

Ord SheetPropertiesSheetType Source # 
Read SheetPropertiesSheetType Source # 
Show SheetPropertiesSheetType Source # 
Generic SheetPropertiesSheetType Source # 
Hashable SheetPropertiesSheetType Source # 
ToJSON SheetPropertiesSheetType Source # 
FromJSON SheetPropertiesSheetType Source # 
FromHttpApiData SheetPropertiesSheetType Source # 
ToHttpApiData SheetPropertiesSheetType Source # 
type Rep SheetPropertiesSheetType Source # 
type Rep SheetPropertiesSheetType = D1 (MetaData "SheetPropertiesSheetType" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "SheetTypeUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "Grid" PrefixI False) U1) (C1 (MetaCons "Object" PrefixI False) U1)))

BatchUpdateValuesRequest

data BatchUpdateValuesRequest Source #

The request for updating more than one range of values in a spreadsheet.

See: batchUpdateValuesRequest smart constructor.

Instances

Eq BatchUpdateValuesRequest Source # 
Data BatchUpdateValuesRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BatchUpdateValuesRequest -> c BatchUpdateValuesRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BatchUpdateValuesRequest #

toConstr :: BatchUpdateValuesRequest -> Constr #

dataTypeOf :: BatchUpdateValuesRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BatchUpdateValuesRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BatchUpdateValuesRequest) #

gmapT :: (forall b. Data b => b -> b) -> BatchUpdateValuesRequest -> BatchUpdateValuesRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BatchUpdateValuesRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BatchUpdateValuesRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> BatchUpdateValuesRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BatchUpdateValuesRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BatchUpdateValuesRequest -> m BatchUpdateValuesRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BatchUpdateValuesRequest -> m BatchUpdateValuesRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BatchUpdateValuesRequest -> m BatchUpdateValuesRequest #

Show BatchUpdateValuesRequest Source # 
Generic BatchUpdateValuesRequest Source # 
ToJSON BatchUpdateValuesRequest Source # 
FromJSON BatchUpdateValuesRequest Source # 
type Rep BatchUpdateValuesRequest Source # 
type Rep BatchUpdateValuesRequest = D1 (MetaData "BatchUpdateValuesRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BatchUpdateValuesRequest'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_buvrData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ValueRange]))) (S1 (MetaSel (Just Symbol "_buvrValueInputOption") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BatchUpdateValuesRequestValueInputOption)))) ((:*:) (S1 (MetaSel (Just Symbol "_buvrIncludeValuesInResponse") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_buvrResponseDateTimeRenderOption") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BatchUpdateValuesRequestResponseDateTimeRenderOption))) (S1 (MetaSel (Just Symbol "_buvrResponseValueRenderOption") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BatchUpdateValuesRequestResponseValueRenderOption)))))))

batchUpdateValuesRequest :: BatchUpdateValuesRequest Source #

Creates a value of BatchUpdateValuesRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

buvrData :: Lens' BatchUpdateValuesRequest [ValueRange] Source #

The new values to apply to the spreadsheet.

buvrIncludeValuesInResponse :: Lens' BatchUpdateValuesRequest (Maybe Bool) Source #

Determines if the update response should include the values of the cells that were updated. By default, responses do not include the updated values. The `updatedData` field within each of the BatchUpdateValuesResponse.responses will contain the updated values. If the range to write was larger than than the range actually written, the response will include all values in the requested range (excluding trailing empty rows and columns).

buvrResponseDateTimeRenderOption :: Lens' BatchUpdateValuesRequest (Maybe BatchUpdateValuesRequestResponseDateTimeRenderOption) Source #

Determines how dates, times, and durations in the response should be rendered. This is ignored if response_value_render_option is FORMATTED_VALUE. The default dateTime render option is [DateTimeRenderOption.SERIAL_NUMBER].

buvrResponseValueRenderOption :: Lens' BatchUpdateValuesRequest (Maybe BatchUpdateValuesRequestResponseValueRenderOption) Source #

Determines how values in the response should be rendered. The default render option is ValueRenderOption.FORMATTED_VALUE.

AddChartRequest

data AddChartRequest Source #

Adds a chart to a sheet in the spreadsheet.

See: addChartRequest smart constructor.

Instances

Eq AddChartRequest Source # 
Data AddChartRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddChartRequest -> c AddChartRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddChartRequest #

toConstr :: AddChartRequest -> Constr #

dataTypeOf :: AddChartRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddChartRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddChartRequest) #

gmapT :: (forall b. Data b => b -> b) -> AddChartRequest -> AddChartRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddChartRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddChartRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddChartRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddChartRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddChartRequest -> m AddChartRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddChartRequest -> m AddChartRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddChartRequest -> m AddChartRequest #

Show AddChartRequest Source # 
Generic AddChartRequest Source # 
ToJSON AddChartRequest Source # 
FromJSON AddChartRequest Source # 
type Rep AddChartRequest Source # 
type Rep AddChartRequest = D1 (MetaData "AddChartRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "AddChartRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_aChart") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe EmbeddedChart))))

addChartRequest :: AddChartRequest Source #

Creates a value of AddChartRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

aChart :: Lens' AddChartRequest (Maybe EmbeddedChart) Source #

The chart that should be added to the spreadsheet, including the position where it should be placed. The chartId field is optional; if one is not set, an id will be randomly generated. (It is an error to specify the ID of a chart that already exists.)

NamedRange

data NamedRange Source #

A named range.

See: namedRange smart constructor.

Instances

Eq NamedRange Source # 
Data NamedRange Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NamedRange -> c NamedRange #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NamedRange #

toConstr :: NamedRange -> Constr #

dataTypeOf :: NamedRange -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NamedRange) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NamedRange) #

gmapT :: (forall b. Data b => b -> b) -> NamedRange -> NamedRange #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NamedRange -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NamedRange -> r #

gmapQ :: (forall d. Data d => d -> u) -> NamedRange -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NamedRange -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NamedRange -> m NamedRange #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NamedRange -> m NamedRange #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NamedRange -> m NamedRange #

Show NamedRange Source # 
Generic NamedRange Source # 

Associated Types

type Rep NamedRange :: * -> * #

ToJSON NamedRange Source # 
FromJSON NamedRange Source # 
type Rep NamedRange Source # 
type Rep NamedRange = D1 (MetaData "NamedRange" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "NamedRange'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_nrNamedRangeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_nrName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_nrRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange))))))

namedRange :: NamedRange Source #

Creates a value of NamedRange with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

nrNamedRangeId :: Lens' NamedRange (Maybe Text) Source #

The ID of the named range.

nrName :: Lens' NamedRange (Maybe Text) Source #

The name of the named range.

nrRange :: Lens' NamedRange (Maybe GridRange) Source #

The range this represents.

MergeCellsRequest

data MergeCellsRequest Source #

Merges all cells in the range.

See: mergeCellsRequest smart constructor.

Instances

Eq MergeCellsRequest Source # 
Data MergeCellsRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MergeCellsRequest -> c MergeCellsRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MergeCellsRequest #

toConstr :: MergeCellsRequest -> Constr #

dataTypeOf :: MergeCellsRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MergeCellsRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MergeCellsRequest) #

gmapT :: (forall b. Data b => b -> b) -> MergeCellsRequest -> MergeCellsRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MergeCellsRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MergeCellsRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> MergeCellsRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MergeCellsRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MergeCellsRequest -> m MergeCellsRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MergeCellsRequest -> m MergeCellsRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MergeCellsRequest -> m MergeCellsRequest #

Show MergeCellsRequest Source # 
Generic MergeCellsRequest Source # 
ToJSON MergeCellsRequest Source # 
FromJSON MergeCellsRequest Source # 
type Rep MergeCellsRequest Source # 
type Rep MergeCellsRequest = D1 (MetaData "MergeCellsRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "MergeCellsRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_mcrMergeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MergeCellsRequestMergeType))) (S1 (MetaSel (Just Symbol "_mcrRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange)))))

mergeCellsRequest :: MergeCellsRequest Source #

Creates a value of MergeCellsRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

mcrRange :: Lens' MergeCellsRequest (Maybe GridRange) Source #

The range of cells to merge.

MergeCellsRequestMergeType

data MergeCellsRequestMergeType Source #

How the cells should be merged.

Constructors

MergeAll

MERGE_ALL Create a single merge from the range

MergeColumns

MERGE_COLUMNS Create a merge for each column in the range

MergeRows

MERGE_ROWS Create a merge for each row in the range

Instances

Enum MergeCellsRequestMergeType Source # 
Eq MergeCellsRequestMergeType Source # 
Data MergeCellsRequestMergeType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MergeCellsRequestMergeType -> c MergeCellsRequestMergeType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MergeCellsRequestMergeType #

toConstr :: MergeCellsRequestMergeType -> Constr #

dataTypeOf :: MergeCellsRequestMergeType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MergeCellsRequestMergeType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MergeCellsRequestMergeType) #

gmapT :: (forall b. Data b => b -> b) -> MergeCellsRequestMergeType -> MergeCellsRequestMergeType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MergeCellsRequestMergeType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MergeCellsRequestMergeType -> r #

gmapQ :: (forall d. Data d => d -> u) -> MergeCellsRequestMergeType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MergeCellsRequestMergeType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MergeCellsRequestMergeType -> m MergeCellsRequestMergeType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MergeCellsRequestMergeType -> m MergeCellsRequestMergeType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MergeCellsRequestMergeType -> m MergeCellsRequestMergeType #

Ord MergeCellsRequestMergeType Source # 
Read MergeCellsRequestMergeType Source # 
Show MergeCellsRequestMergeType Source # 
Generic MergeCellsRequestMergeType Source # 
Hashable MergeCellsRequestMergeType Source # 
ToJSON MergeCellsRequestMergeType Source # 
FromJSON MergeCellsRequestMergeType Source # 
FromHttpApiData MergeCellsRequestMergeType Source # 
ToHttpApiData MergeCellsRequestMergeType Source # 
type Rep MergeCellsRequestMergeType Source # 
type Rep MergeCellsRequestMergeType = D1 (MetaData "MergeCellsRequestMergeType" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "MergeAll" PrefixI False) U1) ((:+:) (C1 (MetaCons "MergeColumns" PrefixI False) U1) (C1 (MetaCons "MergeRows" PrefixI False) U1)))

CellFormatHorizontalAlignment

data CellFormatHorizontalAlignment Source #

The horizontal alignment of the value in the cell.

Constructors

HorizontalAlignUnspecified

HORIZONTAL_ALIGN_UNSPECIFIED The horizontal alignment is not specified. Do not use this.

Left'

LEFT The text is explicitly aligned to the left of the cell.

Center

CENTER The text is explicitly aligned to the center of the cell.

Right'

RIGHT The text is explicitly aligned to the right of the cell.

Instances

Enum CellFormatHorizontalAlignment Source # 
Eq CellFormatHorizontalAlignment Source # 
Data CellFormatHorizontalAlignment Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CellFormatHorizontalAlignment -> c CellFormatHorizontalAlignment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CellFormatHorizontalAlignment #

toConstr :: CellFormatHorizontalAlignment -> Constr #

dataTypeOf :: CellFormatHorizontalAlignment -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CellFormatHorizontalAlignment) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CellFormatHorizontalAlignment) #

gmapT :: (forall b. Data b => b -> b) -> CellFormatHorizontalAlignment -> CellFormatHorizontalAlignment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CellFormatHorizontalAlignment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CellFormatHorizontalAlignment -> r #

gmapQ :: (forall d. Data d => d -> u) -> CellFormatHorizontalAlignment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CellFormatHorizontalAlignment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CellFormatHorizontalAlignment -> m CellFormatHorizontalAlignment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CellFormatHorizontalAlignment -> m CellFormatHorizontalAlignment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CellFormatHorizontalAlignment -> m CellFormatHorizontalAlignment #

Ord CellFormatHorizontalAlignment Source # 
Read CellFormatHorizontalAlignment Source # 
Show CellFormatHorizontalAlignment Source # 
Generic CellFormatHorizontalAlignment Source # 
Hashable CellFormatHorizontalAlignment Source # 
ToJSON CellFormatHorizontalAlignment Source # 
FromJSON CellFormatHorizontalAlignment Source # 
FromHttpApiData CellFormatHorizontalAlignment Source # 
ToHttpApiData CellFormatHorizontalAlignment Source # 
type Rep CellFormatHorizontalAlignment Source # 
type Rep CellFormatHorizontalAlignment = D1 (MetaData "CellFormatHorizontalAlignment" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "HorizontalAlignUnspecified" PrefixI False) U1) (C1 (MetaCons "Left'" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Center" PrefixI False) U1) (C1 (MetaCons "Right'" PrefixI False) U1)))

BOrder

data BOrder Source #

A border along a cell.

See: bOrder smart constructor.

Instances

Eq BOrder Source # 

Methods

(==) :: BOrder -> BOrder -> Bool #

(/=) :: BOrder -> BOrder -> Bool #

Data BOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BOrder -> c BOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BOrder #

toConstr :: BOrder -> Constr #

dataTypeOf :: BOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BOrder) #

gmapT :: (forall b. Data b => b -> b) -> BOrder -> BOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> BOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BOrder -> m BOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BOrder -> m BOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BOrder -> m BOrder #

Show BOrder Source # 
Generic BOrder Source # 

Associated Types

type Rep BOrder :: * -> * #

Methods

from :: BOrder -> Rep BOrder x #

to :: Rep BOrder x -> BOrder #

ToJSON BOrder Source # 
FromJSON BOrder Source # 
type Rep BOrder Source # 
type Rep BOrder = D1 (MetaData "BOrder" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BOrder'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_boStyle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BOrderStyle))) ((:*:) (S1 (MetaSel (Just Symbol "_boColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Color))) (S1 (MetaSel (Just Symbol "_boWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))))

bOrder :: BOrder Source #

Creates a value of BOrder with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

boStyle :: Lens' BOrder (Maybe BOrderStyle) Source #

The style of the border.

boColor :: Lens' BOrder (Maybe Color) Source #

The color of the border.

boWidth :: Lens' BOrder (Maybe Int32) Source #

The width of the border, in pixels. Deprecated; the width is determined by the "style" field.

ExtendedValue

data ExtendedValue Source #

The kinds of value that a cell in a spreadsheet can have.

See: extendedValue smart constructor.

Instances

Eq ExtendedValue Source # 
Data ExtendedValue Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExtendedValue -> c ExtendedValue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExtendedValue #

toConstr :: ExtendedValue -> Constr #

dataTypeOf :: ExtendedValue -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ExtendedValue) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExtendedValue) #

gmapT :: (forall b. Data b => b -> b) -> ExtendedValue -> ExtendedValue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExtendedValue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExtendedValue -> r #

gmapQ :: (forall d. Data d => d -> u) -> ExtendedValue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExtendedValue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExtendedValue -> m ExtendedValue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExtendedValue -> m ExtendedValue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExtendedValue -> m ExtendedValue #

Show ExtendedValue Source # 
Generic ExtendedValue Source # 

Associated Types

type Rep ExtendedValue :: * -> * #

ToJSON ExtendedValue Source # 
FromJSON ExtendedValue Source # 
type Rep ExtendedValue Source # 
type Rep ExtendedValue = D1 (MetaData "ExtendedValue" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "ExtendedValue'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_evBoolValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_evNumberValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))) ((:*:) (S1 (MetaSel (Just Symbol "_evErrorValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ErrorValue))) ((:*:) (S1 (MetaSel (Just Symbol "_evStringValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_evFormulaValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

extendedValue :: ExtendedValue Source #

Creates a value of ExtendedValue with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

evBoolValue :: Lens' ExtendedValue (Maybe Bool) Source #

Represents a boolean value.

evNumberValue :: Lens' ExtendedValue (Maybe Double) Source #

Represents a double value. Note: Dates, Times and DateTimes are represented as doubles in "serial number" format.

evErrorValue :: Lens' ExtendedValue (Maybe ErrorValue) Source #

Represents an error. This field is read-only.

evStringValue :: Lens' ExtendedValue (Maybe Text) Source #

Represents a string value. Leading single quotes are not included. For example, if the user typed `'123` into the UI, this would be represented as a `stringValue` of `"123"`.

evFormulaValue :: Lens' ExtendedValue (Maybe Text) Source #

Represents a formula.

AddNamedRangeRequest

data AddNamedRangeRequest Source #

Adds a named range to the spreadsheet.

See: addNamedRangeRequest smart constructor.

Instances

Eq AddNamedRangeRequest Source # 
Data AddNamedRangeRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddNamedRangeRequest -> c AddNamedRangeRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddNamedRangeRequest #

toConstr :: AddNamedRangeRequest -> Constr #

dataTypeOf :: AddNamedRangeRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddNamedRangeRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddNamedRangeRequest) #

gmapT :: (forall b. Data b => b -> b) -> AddNamedRangeRequest -> AddNamedRangeRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddNamedRangeRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddNamedRangeRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddNamedRangeRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddNamedRangeRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddNamedRangeRequest -> m AddNamedRangeRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddNamedRangeRequest -> m AddNamedRangeRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddNamedRangeRequest -> m AddNamedRangeRequest #

Show AddNamedRangeRequest Source # 
Generic AddNamedRangeRequest Source # 
ToJSON AddNamedRangeRequest Source # 
FromJSON AddNamedRangeRequest Source # 
type Rep AddNamedRangeRequest Source # 
type Rep AddNamedRangeRequest = D1 (MetaData "AddNamedRangeRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "AddNamedRangeRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_aNamedRange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe NamedRange))))

addNamedRangeRequest :: AddNamedRangeRequest Source #

Creates a value of AddNamedRangeRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

aNamedRange :: Lens' AddNamedRangeRequest (Maybe NamedRange) Source #

The named range to add. The namedRangeId field is optional; if one is not set, an id will be randomly generated. (It is an error to specify the ID of a range that already exists.)

PivotFilterCriteria

data PivotFilterCriteria Source #

Criteria for showing/hiding rows in a pivot table.

See: pivotFilterCriteria smart constructor.

Instances

Eq PivotFilterCriteria Source # 
Data PivotFilterCriteria Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PivotFilterCriteria -> c PivotFilterCriteria #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PivotFilterCriteria #

toConstr :: PivotFilterCriteria -> Constr #

dataTypeOf :: PivotFilterCriteria -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PivotFilterCriteria) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PivotFilterCriteria) #

gmapT :: (forall b. Data b => b -> b) -> PivotFilterCriteria -> PivotFilterCriteria #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PivotFilterCriteria -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PivotFilterCriteria -> r #

gmapQ :: (forall d. Data d => d -> u) -> PivotFilterCriteria -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PivotFilterCriteria -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PivotFilterCriteria -> m PivotFilterCriteria #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotFilterCriteria -> m PivotFilterCriteria #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotFilterCriteria -> m PivotFilterCriteria #

Show PivotFilterCriteria Source # 
Generic PivotFilterCriteria Source # 
ToJSON PivotFilterCriteria Source # 
FromJSON PivotFilterCriteria Source # 
type Rep PivotFilterCriteria Source # 
type Rep PivotFilterCriteria = D1 (MetaData "PivotFilterCriteria" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "PivotFilterCriteria'" PrefixI True) (S1 (MetaSel (Just Symbol "_pfcVisibleValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Text]))))

pivotFilterCriteria :: PivotFilterCriteria Source #

Creates a value of PivotFilterCriteria with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pfcVisibleValues :: Lens' PivotFilterCriteria [Text] Source #

Values that should be included. Values not listed here are excluded.

DimensionRange

data DimensionRange Source #

A range along a single dimension on a sheet. All indexes are zero-based. Indexes are half open: the start index is inclusive and the end index is exclusive. Missing indexes indicate the range is unbounded on that side.

See: dimensionRange smart constructor.

Instances

Eq DimensionRange Source # 
Data DimensionRange Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DimensionRange -> c DimensionRange #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DimensionRange #

toConstr :: DimensionRange -> Constr #

dataTypeOf :: DimensionRange -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DimensionRange) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DimensionRange) #

gmapT :: (forall b. Data b => b -> b) -> DimensionRange -> DimensionRange #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DimensionRange -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DimensionRange -> r #

gmapQ :: (forall d. Data d => d -> u) -> DimensionRange -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DimensionRange -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DimensionRange -> m DimensionRange #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionRange -> m DimensionRange #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionRange -> m DimensionRange #

Show DimensionRange Source # 
Generic DimensionRange Source # 

Associated Types

type Rep DimensionRange :: * -> * #

ToJSON DimensionRange Source # 
FromJSON DimensionRange Source # 
type Rep DimensionRange Source # 
type Rep DimensionRange = D1 (MetaData "DimensionRange" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "DimensionRange'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_drDimension") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DimensionRangeDimension))) (S1 (MetaSel (Just Symbol "_drEndIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))) ((:*:) (S1 (MetaSel (Just Symbol "_drSheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_drStartIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))))

dimensionRange :: DimensionRange Source #

Creates a value of DimensionRange with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

drEndIndex :: Lens' DimensionRange (Maybe Int32) Source #

The end (exclusive) of the span, or not set if unbounded.

drSheetId :: Lens' DimensionRange (Maybe Int32) Source #

The sheet this span is on.

drStartIndex :: Lens' DimensionRange (Maybe Int32) Source #

The start (inclusive) of the span, or not set if unbounded.

UpdateSpreadsheetPropertiesRequest

data UpdateSpreadsheetPropertiesRequest Source #

Updates properties of a spreadsheet.

See: updateSpreadsheetPropertiesRequest smart constructor.

Instances

Eq UpdateSpreadsheetPropertiesRequest Source # 
Data UpdateSpreadsheetPropertiesRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateSpreadsheetPropertiesRequest -> c UpdateSpreadsheetPropertiesRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateSpreadsheetPropertiesRequest #

toConstr :: UpdateSpreadsheetPropertiesRequest -> Constr #

dataTypeOf :: UpdateSpreadsheetPropertiesRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateSpreadsheetPropertiesRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateSpreadsheetPropertiesRequest) #

gmapT :: (forall b. Data b => b -> b) -> UpdateSpreadsheetPropertiesRequest -> UpdateSpreadsheetPropertiesRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateSpreadsheetPropertiesRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateSpreadsheetPropertiesRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateSpreadsheetPropertiesRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateSpreadsheetPropertiesRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateSpreadsheetPropertiesRequest -> m UpdateSpreadsheetPropertiesRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateSpreadsheetPropertiesRequest -> m UpdateSpreadsheetPropertiesRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateSpreadsheetPropertiesRequest -> m UpdateSpreadsheetPropertiesRequest #

Show UpdateSpreadsheetPropertiesRequest Source # 
Generic UpdateSpreadsheetPropertiesRequest Source # 
ToJSON UpdateSpreadsheetPropertiesRequest Source # 
FromJSON UpdateSpreadsheetPropertiesRequest Source # 
type Rep UpdateSpreadsheetPropertiesRequest Source # 
type Rep UpdateSpreadsheetPropertiesRequest = D1 (MetaData "UpdateSpreadsheetPropertiesRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "UpdateSpreadsheetPropertiesRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_uFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FieldMask))) (S1 (MetaSel (Just Symbol "_uProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SpreadsheetProperties)))))

updateSpreadsheetPropertiesRequest :: UpdateSpreadsheetPropertiesRequest Source #

Creates a value of UpdateSpreadsheetPropertiesRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

uFields :: Lens' UpdateSpreadsheetPropertiesRequest (Maybe FieldMask) Source #

The fields that should be updated. At least one field must be specified. The root 'properties' is implied and should not be specified. A single `"*"` can be used as short-hand for listing every field.

AddProtectedRangeResponse

data AddProtectedRangeResponse Source #

The result of adding a new protected range.

See: addProtectedRangeResponse smart constructor.

Instances

Eq AddProtectedRangeResponse Source # 
Data AddProtectedRangeResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddProtectedRangeResponse -> c AddProtectedRangeResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddProtectedRangeResponse #

toConstr :: AddProtectedRangeResponse -> Constr #

dataTypeOf :: AddProtectedRangeResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddProtectedRangeResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddProtectedRangeResponse) #

gmapT :: (forall b. Data b => b -> b) -> AddProtectedRangeResponse -> AddProtectedRangeResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddProtectedRangeResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddProtectedRangeResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddProtectedRangeResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddProtectedRangeResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddProtectedRangeResponse -> m AddProtectedRangeResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddProtectedRangeResponse -> m AddProtectedRangeResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddProtectedRangeResponse -> m AddProtectedRangeResponse #

Show AddProtectedRangeResponse Source # 
Generic AddProtectedRangeResponse Source # 
ToJSON AddProtectedRangeResponse Source # 
FromJSON AddProtectedRangeResponse Source # 
type Rep AddProtectedRangeResponse Source # 
type Rep AddProtectedRangeResponse = D1 (MetaData "AddProtectedRangeResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "AddProtectedRangeResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_aProtectedRange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ProtectedRange))))

addProtectedRangeResponse :: AddProtectedRangeResponse Source #

Creates a value of AddProtectedRangeResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

AppendDimensionRequest

data AppendDimensionRequest Source #

Appends rows or columns to the end of a sheet.

See: appendDimensionRequest smart constructor.

Instances

Eq AppendDimensionRequest Source # 
Data AppendDimensionRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AppendDimensionRequest -> c AppendDimensionRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AppendDimensionRequest #

toConstr :: AppendDimensionRequest -> Constr #

dataTypeOf :: AppendDimensionRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AppendDimensionRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AppendDimensionRequest) #

gmapT :: (forall b. Data b => b -> b) -> AppendDimensionRequest -> AppendDimensionRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AppendDimensionRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AppendDimensionRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> AppendDimensionRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AppendDimensionRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AppendDimensionRequest -> m AppendDimensionRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AppendDimensionRequest -> m AppendDimensionRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AppendDimensionRequest -> m AppendDimensionRequest #

Show AppendDimensionRequest Source # 
Generic AppendDimensionRequest Source # 
ToJSON AppendDimensionRequest Source # 
FromJSON AppendDimensionRequest Source # 
type Rep AppendDimensionRequest Source # 
type Rep AppendDimensionRequest = D1 (MetaData "AppendDimensionRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "AppendDimensionRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_adrLength") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) ((:*:) (S1 (MetaSel (Just Symbol "_adrDimension") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AppendDimensionRequestDimension))) (S1 (MetaSel (Just Symbol "_adrSheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))))

appendDimensionRequest :: AppendDimensionRequest Source #

Creates a value of AppendDimensionRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

adrLength :: Lens' AppendDimensionRequest (Maybe Int32) Source #

The number of rows or columns to append.

adrSheetId :: Lens' AppendDimensionRequest (Maybe Int32) Source #

The sheet to append rows or columns to.

PivotValue

data PivotValue Source #

The definition of how a value in a pivot table should be calculated.

See: pivotValue smart constructor.

Instances

Eq PivotValue Source # 
Data PivotValue Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PivotValue -> c PivotValue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PivotValue #

toConstr :: PivotValue -> Constr #

dataTypeOf :: PivotValue -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PivotValue) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PivotValue) #

gmapT :: (forall b. Data b => b -> b) -> PivotValue -> PivotValue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PivotValue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PivotValue -> r #

gmapQ :: (forall d. Data d => d -> u) -> PivotValue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PivotValue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PivotValue -> m PivotValue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotValue -> m PivotValue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotValue -> m PivotValue #

Show PivotValue Source # 
Generic PivotValue Source # 

Associated Types

type Rep PivotValue :: * -> * #

ToJSON PivotValue Source # 
FromJSON PivotValue Source # 
type Rep PivotValue Source # 
type Rep PivotValue = D1 (MetaData "PivotValue" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "PivotValue'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_pvSourceColumnOffSet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_pvFormula") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_pvName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_pvSummarizeFunction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PivotValueSummarizeFunction))))))

pivotValue :: PivotValue Source #

Creates a value of PivotValue with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pvSourceColumnOffSet :: Lens' PivotValue (Maybe Int32) Source #

The column offset of the source range that this value reads from. For example, if the source was `C10:E15`, a `sourceColumnOffset` of `0` means this value refers to column `C`, whereas the offset `1` would refer to column `D`.

pvFormula :: Lens' PivotValue (Maybe Text) Source #

A custom formula to calculate the value. The formula must start with an `=` character.

pvName :: Lens' PivotValue (Maybe Text) Source #

A name to use for the value. This is only used if formula was set. Otherwise, the column name is used.

pvSummarizeFunction :: Lens' PivotValue (Maybe PivotValueSummarizeFunction) Source #

A function to summarize the value. If formula is set, the only supported values are SUM and CUSTOM. If sourceColumnOffset is set, then `CUSTOM` is not supported.

UnmergeCellsRequest

data UnmergeCellsRequest Source #

Unmerges cells in the given range.

See: unmergeCellsRequest smart constructor.

Instances

Eq UnmergeCellsRequest Source # 
Data UnmergeCellsRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnmergeCellsRequest -> c UnmergeCellsRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnmergeCellsRequest #

toConstr :: UnmergeCellsRequest -> Constr #

dataTypeOf :: UnmergeCellsRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UnmergeCellsRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnmergeCellsRequest) #

gmapT :: (forall b. Data b => b -> b) -> UnmergeCellsRequest -> UnmergeCellsRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnmergeCellsRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnmergeCellsRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> UnmergeCellsRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UnmergeCellsRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnmergeCellsRequest -> m UnmergeCellsRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnmergeCellsRequest -> m UnmergeCellsRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnmergeCellsRequest -> m UnmergeCellsRequest #

Show UnmergeCellsRequest Source # 
Generic UnmergeCellsRequest Source # 
ToJSON UnmergeCellsRequest Source # 
FromJSON UnmergeCellsRequest Source # 
type Rep UnmergeCellsRequest Source # 
type Rep UnmergeCellsRequest = D1 (MetaData "UnmergeCellsRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "UnmergeCellsRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_ucrRange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe GridRange))))

unmergeCellsRequest :: UnmergeCellsRequest Source #

Creates a value of UnmergeCellsRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ucrRange :: Lens' UnmergeCellsRequest (Maybe GridRange) Source #

The range within which all cells should be unmerged. If the range spans multiple merges, all will be unmerged. The range must not partially span any merge.

DeleteSheetRequest

data DeleteSheetRequest Source #

Deletes the requested sheet.

See: deleteSheetRequest smart constructor.

Instances

Eq DeleteSheetRequest Source # 
Data DeleteSheetRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeleteSheetRequest -> c DeleteSheetRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeleteSheetRequest #

toConstr :: DeleteSheetRequest -> Constr #

dataTypeOf :: DeleteSheetRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeleteSheetRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeleteSheetRequest) #

gmapT :: (forall b. Data b => b -> b) -> DeleteSheetRequest -> DeleteSheetRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeleteSheetRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeleteSheetRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeleteSheetRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeleteSheetRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeleteSheetRequest -> m DeleteSheetRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteSheetRequest -> m DeleteSheetRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteSheetRequest -> m DeleteSheetRequest #

Show DeleteSheetRequest Source # 
Generic DeleteSheetRequest Source # 
ToJSON DeleteSheetRequest Source # 
FromJSON DeleteSheetRequest Source # 
type Rep DeleteSheetRequest Source # 
type Rep DeleteSheetRequest = D1 (MetaData "DeleteSheetRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "DeleteSheetRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_dsrSheetId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Textual Int32)))))

deleteSheetRequest :: DeleteSheetRequest Source #

Creates a value of DeleteSheetRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dsrSheetId :: Lens' DeleteSheetRequest (Maybe Int32) Source #

The ID of the sheet to delete.

BooleanConditionType

data BooleanConditionType Source #

The type of condition.

Constructors

ConditionTypeUnspecified

CONDITION_TYPE_UNSPECIFIED The default value, do not use.

NumberGreater

NUMBER_GREATER The cell's value must be greater than the condition's value. Supported by data validation, conditional formatting and filters. Requires a single ConditionValue.

NumberGreaterThanEQ

NUMBER_GREATER_THAN_EQ The cell's value must be greater than or equal to the condition's value. Supported by data validation, conditional formatting and filters. Requires a single ConditionValue.

NumberLess

NUMBER_LESS The cell's value must be less than the condition's value. Supported by data validation, conditional formatting and filters. Requires a single ConditionValue.

NumberLessThanEQ

NUMBER_LESS_THAN_EQ The cell's value must be less than or equal to the condition's value. Supported by data validation, conditional formatting and filters. Requires a single ConditionValue.

NumberEQ

NUMBER_EQ The cell's value must be equal to the condition's value. Supported by data validation, conditional formatting and filters. Requires a single ConditionValue.

NumberNotEQ

NUMBER_NOT_EQ The cell's value must be not equal to the condition's value. Supported by data validation, conditional formatting and filters. Requires a single ConditionValue.

NumberBetween

NUMBER_BETWEEN The cell's value must be between the two condition values. Supported by data validation, conditional formatting and filters. Requires exactly two ConditionValues.

NumberNotBetween

NUMBER_NOT_BETWEEN The cell's value must not be between the two condition values. Supported by data validation, conditional formatting and filters. Requires exactly two ConditionValues.

TextContains

TEXT_CONTAINS The cell's value must contain the condition's value. Supported by data validation, conditional formatting and filters. Requires a single ConditionValue.

TextNotContains

TEXT_NOT_CONTAINS The cell's value must not contain the condition's value. Supported by data validation, conditional formatting and filters. Requires a single ConditionValue.

TextStartsWith

TEXT_STARTS_WITH The cell's value must start with the condition's value. Supported by conditional formatting and filters. Requires a single ConditionValue.

TextEndsWith

TEXT_ENDS_WITH The cell's value must end with the condition's value. Supported by conditional formatting and filters. Requires a single ConditionValue.

TextEQ

TEXT_EQ The cell's value must be exactly the condition's value. Supported by data validation, conditional formatting and filters. Requires a single ConditionValue.

TextIsEmail

TEXT_IS_EMAIL The cell's value must be a valid email address. Supported by data validation. Requires no ConditionValues.

TextIsURL

TEXT_IS_URL The cell's value must be a valid URL. Supported by data validation. Requires no ConditionValues.

DateEQ

DATE_EQ The cell's value must be the same date as the condition's value. Supported by data validation, conditional formatting and filters. Requires a single ConditionValue.

DateBefore

DATE_BEFORE The cell's value must be before the date of the condition's value. Supported by data validation, conditional formatting and filters. Requires a single ConditionValue that may be a relative date.

DateAfter

DATE_AFTER The cell's value must be after the date of the condition's value. Supported by data validation, conditional formatting and filters. Requires a single ConditionValue that may be a relative date.

DateOnOrBefore

DATE_ON_OR_BEFORE The cell's value must be on or before the date of the condition's value. Supported by data validation. Requires a single ConditionValue that may be a relative date.

DateOnOrAfter

DATE_ON_OR_AFTER The cell's value must be on or after the date of the condition's value. Supported by data validation. Requires a single ConditionValue that may be a relative date.

DateBetween

DATE_BETWEEN The cell's value must be between the dates of the two condition values. Supported by data validation. Requires exactly two ConditionValues.

DateNotBetween

DATE_NOT_BETWEEN The cell's value must be outside the dates of the two condition values. Supported by data validation. Requires exactly two ConditionValues.

DateIsValid

DATE_IS_VALID The cell's value must be a date. Supported by data validation. Requires no ConditionValues.

OneOfRange

ONE_OF_RANGE The cell's value must be listed in the grid in condition value's range. Supported by data validation. Requires a single ConditionValue, and the value must be a valid range in A1 notation.

OneOfList

ONE_OF_LIST The cell's value must in the list of condition values. Supported by data validation. Supports any number of condition values, one per item in the list. Formulas are not supported in the values.

Blank

BLANK The cell's value must be empty. Supported by conditional formatting and filters. Requires no ConditionValues.

NotBlank

NOT_BLANK The cell's value must not be empty. Supported by conditional formatting and filters. Requires no ConditionValues.

CustomFormula

CUSTOM_FORMULA The condition's formula must evaluate to true. Supported by data validation, conditional formatting and filters. Requires a single ConditionValue.

Instances

Enum BooleanConditionType Source # 
Eq BooleanConditionType Source # 
Data BooleanConditionType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BooleanConditionType -> c BooleanConditionType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BooleanConditionType #

toConstr :: BooleanConditionType -> Constr #

dataTypeOf :: BooleanConditionType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BooleanConditionType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BooleanConditionType) #

gmapT :: (forall b. Data b => b -> b) -> BooleanConditionType -> BooleanConditionType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BooleanConditionType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BooleanConditionType -> r #

gmapQ :: (forall d. Data d => d -> u) -> BooleanConditionType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BooleanConditionType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BooleanConditionType -> m BooleanConditionType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BooleanConditionType -> m BooleanConditionType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BooleanConditionType -> m BooleanConditionType #

Ord BooleanConditionType Source # 
Read BooleanConditionType Source # 
Show BooleanConditionType Source # 
Generic BooleanConditionType Source # 
Hashable BooleanConditionType Source # 
ToJSON BooleanConditionType Source # 
FromJSON BooleanConditionType Source # 
FromHttpApiData BooleanConditionType Source # 
ToHttpApiData BooleanConditionType Source # 
type Rep BooleanConditionType Source # 
type Rep BooleanConditionType = D1 (MetaData "BooleanConditionType" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ConditionTypeUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "NumberGreater" PrefixI False) U1) (C1 (MetaCons "NumberGreaterThanEQ" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "NumberLess" PrefixI False) U1) (C1 (MetaCons "NumberLessThanEQ" PrefixI False) U1)) ((:+:) (C1 (MetaCons "NumberEQ" PrefixI False) U1) (C1 (MetaCons "NumberNotEQ" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "NumberBetween" PrefixI False) U1) ((:+:) (C1 (MetaCons "NumberNotBetween" PrefixI False) U1) (C1 (MetaCons "TextContains" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "TextNotContains" PrefixI False) U1) (C1 (MetaCons "TextStartsWith" PrefixI False) U1)) ((:+:) (C1 (MetaCons "TextEndsWith" PrefixI False) U1) (C1 (MetaCons "TextEQ" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TextIsEmail" PrefixI False) U1) ((:+:) (C1 (MetaCons "TextIsURL" PrefixI False) U1) (C1 (MetaCons "DateEQ" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "DateBefore" PrefixI False) U1) (C1 (MetaCons "DateAfter" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DateOnOrBefore" PrefixI False) U1) (C1 (MetaCons "DateOnOrAfter" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DateBetween" PrefixI False) U1) (C1 (MetaCons "DateNotBetween" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DateIsValid" PrefixI False) U1) (C1 (MetaCons "OneOfRange" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "OneOfList" PrefixI False) U1) (C1 (MetaCons "Blank" PrefixI False) U1)) ((:+:) (C1 (MetaCons "NotBlank" PrefixI False) U1) (C1 (MetaCons "CustomFormula" PrefixI False) U1))))))

BandedRange

data BandedRange Source #

A banded (alternating colors) range in a sheet.

See: bandedRange smart constructor.

Instances

Eq BandedRange Source # 
Data BandedRange Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BandedRange -> c BandedRange #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BandedRange #

toConstr :: BandedRange -> Constr #

dataTypeOf :: BandedRange -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BandedRange) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BandedRange) #

gmapT :: (forall b. Data b => b -> b) -> BandedRange -> BandedRange #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BandedRange -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BandedRange -> r #

gmapQ :: (forall d. Data d => d -> u) -> BandedRange -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BandedRange -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BandedRange -> m BandedRange #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BandedRange -> m BandedRange #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BandedRange -> m BandedRange #

Show BandedRange Source # 
Generic BandedRange Source # 

Associated Types

type Rep BandedRange :: * -> * #

ToJSON BandedRange Source # 
FromJSON BandedRange Source # 
type Rep BandedRange Source # 
type Rep BandedRange = D1 (MetaData "BandedRange" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BandedRange'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_brBandedRangeId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_brRowProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BandingProperties)))) ((:*:) (S1 (MetaSel (Just Symbol "_brRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange))) (S1 (MetaSel (Just Symbol "_brColumnProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BandingProperties))))))

bandedRange :: BandedRange Source #

Creates a value of BandedRange with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

brBandedRangeId :: Lens' BandedRange (Maybe Int32) Source #

The id of the banded range.

brRowProperties :: Lens' BandedRange (Maybe BandingProperties) Source #

Properties for row bands. These properties will be applied on a row-by-row basis throughout all the rows in the range. At least one of row_properties or column_properties must be specified.

brRange :: Lens' BandedRange (Maybe GridRange) Source #

The range over which these properties are applied.

brColumnProperties :: Lens' BandedRange (Maybe BandingProperties) Source #

Properties for column bands. These properties will be applied on a column- by-column basis throughout all the columns in the range. At least one of row_properties or column_properties must be specified.

UpdateBOrdersRequest

data UpdateBOrdersRequest Source #

Updates the borders of a range. If a field is not set in the request, that means the border remains as-is. For example, with two subsequent UpdateBordersRequest: 1. range: A1:A5 `{ top: RED, bottom: WHITE }` 2. range: A1:A5 `{ left: BLUE }` That would result in A1:A5 having a borders of `{ top: RED, bottom: WHITE, left: BLUE }`. If you want to clear a border, explicitly set the style to NONE.

See: updateBOrdersRequest smart constructor.

Instances

Eq UpdateBOrdersRequest Source # 
Data UpdateBOrdersRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateBOrdersRequest -> c UpdateBOrdersRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateBOrdersRequest #

toConstr :: UpdateBOrdersRequest -> Constr #

dataTypeOf :: UpdateBOrdersRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateBOrdersRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateBOrdersRequest) #

gmapT :: (forall b. Data b => b -> b) -> UpdateBOrdersRequest -> UpdateBOrdersRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateBOrdersRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateBOrdersRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateBOrdersRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateBOrdersRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateBOrdersRequest -> m UpdateBOrdersRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateBOrdersRequest -> m UpdateBOrdersRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateBOrdersRequest -> m UpdateBOrdersRequest #

Show UpdateBOrdersRequest Source # 
Generic UpdateBOrdersRequest Source # 
ToJSON UpdateBOrdersRequest Source # 
FromJSON UpdateBOrdersRequest Source # 
type Rep UpdateBOrdersRequest Source # 

updateBOrdersRequest :: UpdateBOrdersRequest Source #

Creates a value of UpdateBOrdersRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

uborBottom :: Lens' UpdateBOrdersRequest (Maybe BOrder) Source #

The border to put at the bottom of the range.

uborInnerHorizontal :: Lens' UpdateBOrdersRequest (Maybe BOrder) Source #

The horizontal border to put within the range.

uborLeft :: Lens' UpdateBOrdersRequest (Maybe BOrder) Source #

The border to put at the left of the range.

uborInnerVertical :: Lens' UpdateBOrdersRequest (Maybe BOrder) Source #

The vertical border to put within the range.

uborRange :: Lens' UpdateBOrdersRequest (Maybe GridRange) Source #

The range whose borders should be updated.

uborRight :: Lens' UpdateBOrdersRequest (Maybe BOrder) Source #

The border to put at the right of the range.

uborTop :: Lens' UpdateBOrdersRequest (Maybe BOrder) Source #

The border to put at the top of the range.

ValueRangeMajorDimension

data ValueRangeMajorDimension Source #

The major dimension of the values. For output, if the spreadsheet data is: `A1=1,B1=2,A2=3,B2=4`, then requesting `range=A1:B2,majorDimension=ROWS` will return `[[1,2],[3,4]]`, whereas requesting `range=A1:B2,majorDimension=COLUMNS` will return `[[1,3],[2,4]]`. For input, with `range=A1:B2,majorDimension=ROWS` then `[[1,2],[3,4]]` will set `A1=1,B1=2,A2=3,B2=4`. With `range=A1:B2,majorDimension=COLUMNS` then `[[1,2],[3,4]]` will set `A1=1,B1=3,A2=2,B2=4`. When writing, if this field is not set, it defaults to ROWS.

Constructors

VRMDDimensionUnspecified

DIMENSION_UNSPECIFIED The default value, do not use.

VRMDRows

ROWS Operates on the rows of a sheet.

VRMDColumns

COLUMNS Operates on the columns of a sheet.

Instances

Enum ValueRangeMajorDimension Source # 
Eq ValueRangeMajorDimension Source # 
Data ValueRangeMajorDimension Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ValueRangeMajorDimension -> c ValueRangeMajorDimension #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ValueRangeMajorDimension #

toConstr :: ValueRangeMajorDimension -> Constr #

dataTypeOf :: ValueRangeMajorDimension -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ValueRangeMajorDimension) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ValueRangeMajorDimension) #

gmapT :: (forall b. Data b => b -> b) -> ValueRangeMajorDimension -> ValueRangeMajorDimension #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ValueRangeMajorDimension -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ValueRangeMajorDimension -> r #

gmapQ :: (forall d. Data d => d -> u) -> ValueRangeMajorDimension -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ValueRangeMajorDimension -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ValueRangeMajorDimension -> m ValueRangeMajorDimension #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ValueRangeMajorDimension -> m ValueRangeMajorDimension #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ValueRangeMajorDimension -> m ValueRangeMajorDimension #

Ord ValueRangeMajorDimension Source # 
Read ValueRangeMajorDimension Source # 
Show ValueRangeMajorDimension Source # 
Generic ValueRangeMajorDimension Source # 
Hashable ValueRangeMajorDimension Source # 
ToJSON ValueRangeMajorDimension Source # 
FromJSON ValueRangeMajorDimension Source # 
FromHttpApiData ValueRangeMajorDimension Source # 
ToHttpApiData ValueRangeMajorDimension Source # 
type Rep ValueRangeMajorDimension Source # 
type Rep ValueRangeMajorDimension = D1 (MetaData "ValueRangeMajorDimension" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "VRMDDimensionUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "VRMDRows" PrefixI False) U1) (C1 (MetaCons "VRMDColumns" PrefixI False) U1)))

PivotGroupSortOrder

data PivotGroupSortOrder Source #

The order the values in this group should be sorted.

Constructors

PGSOSortOrderUnspecified

SORT_ORDER_UNSPECIFIED Default value, do not use this.

PGSOAscending

ASCENDING Sort ascending.

PGSODescending

DESCENDING Sort descending.

Instances

Enum PivotGroupSortOrder Source # 
Eq PivotGroupSortOrder Source # 
Data PivotGroupSortOrder Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PivotGroupSortOrder -> c PivotGroupSortOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PivotGroupSortOrder #

toConstr :: PivotGroupSortOrder -> Constr #

dataTypeOf :: PivotGroupSortOrder -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PivotGroupSortOrder) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PivotGroupSortOrder) #

gmapT :: (forall b. Data b => b -> b) -> PivotGroupSortOrder -> PivotGroupSortOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PivotGroupSortOrder -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PivotGroupSortOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> PivotGroupSortOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PivotGroupSortOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PivotGroupSortOrder -> m PivotGroupSortOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotGroupSortOrder -> m PivotGroupSortOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotGroupSortOrder -> m PivotGroupSortOrder #

Ord PivotGroupSortOrder Source # 
Read PivotGroupSortOrder Source # 
Show PivotGroupSortOrder Source # 
Generic PivotGroupSortOrder Source # 
Hashable PivotGroupSortOrder Source # 
ToJSON PivotGroupSortOrder Source # 
FromJSON PivotGroupSortOrder Source # 
FromHttpApiData PivotGroupSortOrder Source # 
ToHttpApiData PivotGroupSortOrder Source # 
type Rep PivotGroupSortOrder Source # 
type Rep PivotGroupSortOrder = D1 (MetaData "PivotGroupSortOrder" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "PGSOSortOrderUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "PGSOAscending" PrefixI False) U1) (C1 (MetaCons "PGSODescending" PrefixI False) U1)))

BasicChartSpecChartType

data BasicChartSpecChartType Source #

The type of the chart.

Constructors

BasicChartTypeUnspecified

BASIC_CHART_TYPE_UNSPECIFIED Default value, do not use.

Bar

BAR A bar chart.

Line

LINE A line chart.

Area

AREA An area chart.

Column

COLUMN A column chart.

Scatter

SCATTER A scatter chart.

Combo

COMBO A combo chart.

Instances

Enum BasicChartSpecChartType Source # 
Eq BasicChartSpecChartType Source # 
Data BasicChartSpecChartType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BasicChartSpecChartType -> c BasicChartSpecChartType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BasicChartSpecChartType #

toConstr :: BasicChartSpecChartType -> Constr #

dataTypeOf :: BasicChartSpecChartType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BasicChartSpecChartType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BasicChartSpecChartType) #

gmapT :: (forall b. Data b => b -> b) -> BasicChartSpecChartType -> BasicChartSpecChartType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BasicChartSpecChartType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BasicChartSpecChartType -> r #

gmapQ :: (forall d. Data d => d -> u) -> BasicChartSpecChartType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BasicChartSpecChartType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BasicChartSpecChartType -> m BasicChartSpecChartType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicChartSpecChartType -> m BasicChartSpecChartType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicChartSpecChartType -> m BasicChartSpecChartType #

Ord BasicChartSpecChartType Source # 
Read BasicChartSpecChartType Source # 
Show BasicChartSpecChartType Source # 
Generic BasicChartSpecChartType Source # 
Hashable BasicChartSpecChartType Source # 
ToJSON BasicChartSpecChartType Source # 
FromJSON BasicChartSpecChartType Source # 
FromHttpApiData BasicChartSpecChartType Source # 
ToHttpApiData BasicChartSpecChartType Source # 
type Rep BasicChartSpecChartType Source # 
type Rep BasicChartSpecChartType = D1 (MetaData "BasicChartSpecChartType" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "BasicChartTypeUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "Bar" PrefixI False) U1) (C1 (MetaCons "Line" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Area" PrefixI False) U1) (C1 (MetaCons "Column" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Scatter" PrefixI False) U1) (C1 (MetaCons "Combo" PrefixI False) U1))))

EmbeddedChart

data EmbeddedChart Source #

A chart embedded in a sheet.

See: embeddedChart smart constructor.

Instances

Eq EmbeddedChart Source # 
Data EmbeddedChart Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EmbeddedChart -> c EmbeddedChart #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EmbeddedChart #

toConstr :: EmbeddedChart -> Constr #

dataTypeOf :: EmbeddedChart -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EmbeddedChart) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EmbeddedChart) #

gmapT :: (forall b. Data b => b -> b) -> EmbeddedChart -> EmbeddedChart #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EmbeddedChart -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EmbeddedChart -> r #

gmapQ :: (forall d. Data d => d -> u) -> EmbeddedChart -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EmbeddedChart -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EmbeddedChart -> m EmbeddedChart #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EmbeddedChart -> m EmbeddedChart #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EmbeddedChart -> m EmbeddedChart #

Show EmbeddedChart Source # 
Generic EmbeddedChart Source # 

Associated Types

type Rep EmbeddedChart :: * -> * #

ToJSON EmbeddedChart Source # 
FromJSON EmbeddedChart Source # 
type Rep EmbeddedChart Source # 
type Rep EmbeddedChart = D1 (MetaData "EmbeddedChart" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "EmbeddedChart'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ecSpec") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChartSpec))) ((:*:) (S1 (MetaSel (Just Symbol "_ecPosition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EmbeddedObjectPosition))) (S1 (MetaSel (Just Symbol "_ecChartId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))))

embeddedChart :: EmbeddedChart Source #

Creates a value of EmbeddedChart with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ecSpec :: Lens' EmbeddedChart (Maybe ChartSpec) Source #

The specification of the chart.

ecChartId :: Lens' EmbeddedChart (Maybe Int32) Source #

The ID of the chart.

RowData

data RowData Source #

Data about each cell in a row.

See: rowData smart constructor.

Instances

Eq RowData Source # 

Methods

(==) :: RowData -> RowData -> Bool #

(/=) :: RowData -> RowData -> Bool #

Data RowData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RowData -> c RowData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RowData #

toConstr :: RowData -> Constr #

dataTypeOf :: RowData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RowData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowData) #

gmapT :: (forall b. Data b => b -> b) -> RowData -> RowData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RowData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RowData -> r #

gmapQ :: (forall d. Data d => d -> u) -> RowData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RowData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RowData -> m RowData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RowData -> m RowData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RowData -> m RowData #

Show RowData Source # 
Generic RowData Source # 

Associated Types

type Rep RowData :: * -> * #

Methods

from :: RowData -> Rep RowData x #

to :: Rep RowData x -> RowData #

ToJSON RowData Source # 
FromJSON RowData Source # 
type Rep RowData Source # 
type Rep RowData = D1 (MetaData "RowData" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "RowData'" PrefixI True) (S1 (MetaSel (Just Symbol "_rdValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [CellData]))))

rowData :: RowData Source #

Creates a value of RowData with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rdValues :: Lens' RowData [CellData] Source #

The values in the row, one per column.

Editors

data Editors Source #

The editors of a protected range.

See: editors smart constructor.

Instances

Eq Editors Source # 

Methods

(==) :: Editors -> Editors -> Bool #

(/=) :: Editors -> Editors -> Bool #

Data Editors Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Editors -> c Editors #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Editors #

toConstr :: Editors -> Constr #

dataTypeOf :: Editors -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Editors) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Editors) #

gmapT :: (forall b. Data b => b -> b) -> Editors -> Editors #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Editors -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Editors -> r #

gmapQ :: (forall d. Data d => d -> u) -> Editors -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Editors -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Editors -> m Editors #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Editors -> m Editors #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Editors -> m Editors #

Show Editors Source # 
Generic Editors Source # 

Associated Types

type Rep Editors :: * -> * #

Methods

from :: Editors -> Rep Editors x #

to :: Rep Editors x -> Editors #

ToJSON Editors Source # 
FromJSON Editors Source # 
type Rep Editors Source # 
type Rep Editors = D1 (MetaData "Editors" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "Editors'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_eGroups") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) ((:*:) (S1 (MetaSel (Just Symbol "_eUsers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_eDomainUsersCanEdit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))

editors :: Editors Source #

Creates a value of Editors with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

eGroups :: Lens' Editors [Text] Source #

The email addresses of groups with edit access to the protected range.

eUsers :: Lens' Editors [Text] Source #

The email addresses of users with edit access to the protected range.

eDomainUsersCanEdit :: Lens' Editors (Maybe Bool) Source #

True if anyone in the document's domain has edit access to the protected range. Domain protection is only supported on documents within a domain.

Xgafv

data Xgafv Source #

V1 error format.

Constructors

X1

1 v1 error format

X2

2 v2 error format

Instances

Enum Xgafv Source # 
Eq Xgafv Source # 

Methods

(==) :: Xgafv -> Xgafv -> Bool #

(/=) :: Xgafv -> Xgafv -> Bool #

Data Xgafv Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Xgafv -> c Xgafv #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Xgafv #

toConstr :: Xgafv -> Constr #

dataTypeOf :: Xgafv -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Xgafv) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Xgafv) #

gmapT :: (forall b. Data b => b -> b) -> Xgafv -> Xgafv #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Xgafv -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Xgafv -> r #

gmapQ :: (forall d. Data d => d -> u) -> Xgafv -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Xgafv -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Xgafv -> m Xgafv #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Xgafv -> m Xgafv #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Xgafv -> m Xgafv #

Ord Xgafv Source # 

Methods

compare :: Xgafv -> Xgafv -> Ordering #

(<) :: Xgafv -> Xgafv -> Bool #

(<=) :: Xgafv -> Xgafv -> Bool #

(>) :: Xgafv -> Xgafv -> Bool #

(>=) :: Xgafv -> Xgafv -> Bool #

max :: Xgafv -> Xgafv -> Xgafv #

min :: Xgafv -> Xgafv -> Xgafv #

Read Xgafv Source # 
Show Xgafv Source # 

Methods

showsPrec :: Int -> Xgafv -> ShowS #

show :: Xgafv -> String #

showList :: [Xgafv] -> ShowS #

Generic Xgafv Source # 

Associated Types

type Rep Xgafv :: * -> * #

Methods

from :: Xgafv -> Rep Xgafv x #

to :: Rep Xgafv x -> Xgafv #

Hashable Xgafv Source # 

Methods

hashWithSalt :: Int -> Xgafv -> Int #

hash :: Xgafv -> Int #

ToJSON Xgafv Source # 
FromJSON Xgafv Source # 
FromHttpApiData Xgafv Source # 
ToHttpApiData Xgafv Source # 
type Rep Xgafv Source # 
type Rep Xgafv = D1 (MetaData "Xgafv" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "X1" PrefixI False) U1) (C1 (MetaCons "X2" PrefixI False) U1))

PivotTable

data PivotTable Source #

A pivot table.

See: pivotTable smart constructor.

Instances

Eq PivotTable Source # 
Data PivotTable Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PivotTable -> c PivotTable #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PivotTable #

toConstr :: PivotTable -> Constr #

dataTypeOf :: PivotTable -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PivotTable) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PivotTable) #

gmapT :: (forall b. Data b => b -> b) -> PivotTable -> PivotTable #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PivotTable -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PivotTable -> r #

gmapQ :: (forall d. Data d => d -> u) -> PivotTable -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PivotTable -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PivotTable -> m PivotTable #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotTable -> m PivotTable #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotTable -> m PivotTable #

Show PivotTable Source # 
Generic PivotTable Source # 

Associated Types

type Rep PivotTable :: * -> * #

ToJSON PivotTable Source # 
FromJSON PivotTable Source # 
type Rep PivotTable Source # 

pivotTable :: PivotTable Source #

Creates a value of PivotTable with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ptValues :: Lens' PivotTable [PivotValue] Source #

A list of values to include in the pivot table.

ptValueLayout :: Lens' PivotTable (Maybe PivotTableValueLayout) Source #

Whether values should be listed horizontally (as columns) or vertically (as rows).

ptRows :: Lens' PivotTable [PivotGroup] Source #

Each row grouping in the pivot table.

ptSource :: Lens' PivotTable (Maybe GridRange) Source #

The range the pivot table is reading data from.

ptColumns :: Lens' PivotTable [PivotGroup] Source #

Each column grouping in the pivot table.

ptCriteria :: Lens' PivotTable (Maybe PivotTableCriteria) Source #

An optional mapping of filters per source column offset. The filters will be applied before aggregating data into the pivot table. The map's key is the column offset of the source range that you want to filter, and the value is the criteria for that column. For example, if the source was `C10:E15`, a key of `0` will have the filter for column `C`, whereas the key `1` is for column `D`.

EmbeddedObjectPosition

data EmbeddedObjectPosition Source #

The position of an embedded object such as a chart.

See: embeddedObjectPosition smart constructor.

Instances

Eq EmbeddedObjectPosition Source # 
Data EmbeddedObjectPosition Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EmbeddedObjectPosition -> c EmbeddedObjectPosition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EmbeddedObjectPosition #

toConstr :: EmbeddedObjectPosition -> Constr #

dataTypeOf :: EmbeddedObjectPosition -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EmbeddedObjectPosition) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EmbeddedObjectPosition) #

gmapT :: (forall b. Data b => b -> b) -> EmbeddedObjectPosition -> EmbeddedObjectPosition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EmbeddedObjectPosition -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EmbeddedObjectPosition -> r #

gmapQ :: (forall d. Data d => d -> u) -> EmbeddedObjectPosition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EmbeddedObjectPosition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EmbeddedObjectPosition -> m EmbeddedObjectPosition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EmbeddedObjectPosition -> m EmbeddedObjectPosition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EmbeddedObjectPosition -> m EmbeddedObjectPosition #

Show EmbeddedObjectPosition Source # 
Generic EmbeddedObjectPosition Source # 
ToJSON EmbeddedObjectPosition Source # 
FromJSON EmbeddedObjectPosition Source # 
type Rep EmbeddedObjectPosition Source # 
type Rep EmbeddedObjectPosition = D1 (MetaData "EmbeddedObjectPosition" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "EmbeddedObjectPosition'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_eopOverlayPosition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe OverlayPosition))) ((:*:) (S1 (MetaSel (Just Symbol "_eopSheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_eopNewSheet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))

embeddedObjectPosition :: EmbeddedObjectPosition Source #

Creates a value of EmbeddedObjectPosition with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

eopOverlayPosition :: Lens' EmbeddedObjectPosition (Maybe OverlayPosition) Source #

The position at which the object is overlaid on top of a grid.

eopSheetId :: Lens' EmbeddedObjectPosition (Maybe Int32) Source #

The sheet this is on. Set only if the embedded object is on its own sheet. Must be non-negative.

eopNewSheet :: Lens' EmbeddedObjectPosition (Maybe Bool) Source #

If true, the embedded object will be put on a new sheet whose ID is chosen for you. Used only when writing.

BasicFilter

data BasicFilter Source #

The default filter associated with a sheet.

See: basicFilter smart constructor.

Instances

Eq BasicFilter Source # 
Data BasicFilter Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BasicFilter -> c BasicFilter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BasicFilter #

toConstr :: BasicFilter -> Constr #

dataTypeOf :: BasicFilter -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BasicFilter) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BasicFilter) #

gmapT :: (forall b. Data b => b -> b) -> BasicFilter -> BasicFilter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BasicFilter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BasicFilter -> r #

gmapQ :: (forall d. Data d => d -> u) -> BasicFilter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BasicFilter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BasicFilter -> m BasicFilter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicFilter -> m BasicFilter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicFilter -> m BasicFilter #

Show BasicFilter Source # 
Generic BasicFilter Source # 

Associated Types

type Rep BasicFilter :: * -> * #

ToJSON BasicFilter Source # 
FromJSON BasicFilter Source # 
type Rep BasicFilter Source # 
type Rep BasicFilter = D1 (MetaData "BasicFilter" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BasicFilter'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bfSortSpecs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [SortSpec]))) ((:*:) (S1 (MetaSel (Just Symbol "_bfRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange))) (S1 (MetaSel (Just Symbol "_bfCriteria") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BasicFilterCriteria))))))

basicFilter :: BasicFilter Source #

Creates a value of BasicFilter with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

bfSortSpecs :: Lens' BasicFilter [SortSpec] Source #

The sort order per column. Later specifications are used when values are equal in the earlier specifications.

bfRange :: Lens' BasicFilter (Maybe GridRange) Source #

The range the filter covers.

bfCriteria :: Lens' BasicFilter (Maybe BasicFilterCriteria) Source #

The criteria for showing/hiding values per column. The map's key is the column index, and the value is the criteria for that column.

TextToColumnsRequest

data TextToColumnsRequest Source #

Splits a column of text into multiple columns, based on a delimiter in each cell.

See: textToColumnsRequest smart constructor.

Instances

Eq TextToColumnsRequest Source # 
Data TextToColumnsRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TextToColumnsRequest -> c TextToColumnsRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TextToColumnsRequest #

toConstr :: TextToColumnsRequest -> Constr #

dataTypeOf :: TextToColumnsRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TextToColumnsRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextToColumnsRequest) #

gmapT :: (forall b. Data b => b -> b) -> TextToColumnsRequest -> TextToColumnsRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TextToColumnsRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TextToColumnsRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> TextToColumnsRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TextToColumnsRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TextToColumnsRequest -> m TextToColumnsRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TextToColumnsRequest -> m TextToColumnsRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TextToColumnsRequest -> m TextToColumnsRequest #

Show TextToColumnsRequest Source # 
Generic TextToColumnsRequest Source # 
ToJSON TextToColumnsRequest Source # 
FromJSON TextToColumnsRequest Source # 
type Rep TextToColumnsRequest Source # 
type Rep TextToColumnsRequest = D1 (MetaData "TextToColumnsRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "TextToColumnsRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ttcrDelimiterType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TextToColumnsRequestDelimiterType))) ((:*:) (S1 (MetaSel (Just Symbol "_ttcrSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange))) (S1 (MetaSel (Just Symbol "_ttcrDelimiter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

textToColumnsRequest :: TextToColumnsRequest Source #

Creates a value of TextToColumnsRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ttcrSource :: Lens' TextToColumnsRequest (Maybe GridRange) Source #

The source data range. This must span exactly one column.

ttcrDelimiter :: Lens' TextToColumnsRequest (Maybe Text) Source #

The delimiter to use. Used only if delimiterType is CUSTOM.

SpreadsheetPropertiesAutoRecalc

data SpreadsheetPropertiesAutoRecalc Source #

The amount of time to wait before volatile functions are recalculated.

Constructors

RecalculationIntervalUnspecified

RECALCULATION_INTERVAL_UNSPECIFIED Default value. This value must not be used.

OnChange

ON_CHANGE Volatile functions are updated on every change.

Minute

MINUTE Volatile functions are updated on every change and every minute.

Hour

HOUR Volatile functions are updated on every change and hourly.

Instances

Enum SpreadsheetPropertiesAutoRecalc Source # 
Eq SpreadsheetPropertiesAutoRecalc Source # 
Data SpreadsheetPropertiesAutoRecalc Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpreadsheetPropertiesAutoRecalc -> c SpreadsheetPropertiesAutoRecalc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SpreadsheetPropertiesAutoRecalc #

toConstr :: SpreadsheetPropertiesAutoRecalc -> Constr #

dataTypeOf :: SpreadsheetPropertiesAutoRecalc -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SpreadsheetPropertiesAutoRecalc) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SpreadsheetPropertiesAutoRecalc) #

gmapT :: (forall b. Data b => b -> b) -> SpreadsheetPropertiesAutoRecalc -> SpreadsheetPropertiesAutoRecalc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpreadsheetPropertiesAutoRecalc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpreadsheetPropertiesAutoRecalc -> r #

gmapQ :: (forall d. Data d => d -> u) -> SpreadsheetPropertiesAutoRecalc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpreadsheetPropertiesAutoRecalc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpreadsheetPropertiesAutoRecalc -> m SpreadsheetPropertiesAutoRecalc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpreadsheetPropertiesAutoRecalc -> m SpreadsheetPropertiesAutoRecalc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpreadsheetPropertiesAutoRecalc -> m SpreadsheetPropertiesAutoRecalc #

Ord SpreadsheetPropertiesAutoRecalc Source # 
Read SpreadsheetPropertiesAutoRecalc Source # 
Show SpreadsheetPropertiesAutoRecalc Source # 
Generic SpreadsheetPropertiesAutoRecalc Source # 
Hashable SpreadsheetPropertiesAutoRecalc Source # 
ToJSON SpreadsheetPropertiesAutoRecalc Source # 
FromJSON SpreadsheetPropertiesAutoRecalc Source # 
FromHttpApiData SpreadsheetPropertiesAutoRecalc Source # 
ToHttpApiData SpreadsheetPropertiesAutoRecalc Source # 
type Rep SpreadsheetPropertiesAutoRecalc Source # 
type Rep SpreadsheetPropertiesAutoRecalc = D1 (MetaData "SpreadsheetPropertiesAutoRecalc" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "RecalculationIntervalUnspecified" PrefixI False) U1) (C1 (MetaCons "OnChange" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Minute" PrefixI False) U1) (C1 (MetaCons "Hour" PrefixI False) U1)))

CopyPasteRequestPasteOrientation

data CopyPasteRequestPasteOrientation Source #

How that data should be oriented when pasting.

Constructors

Normal

NORMAL Paste normally.

Transpose

TRANSPOSE Paste transposed, where all rows become columns and vice versa.

Instances

Enum CopyPasteRequestPasteOrientation Source # 
Eq CopyPasteRequestPasteOrientation Source # 
Data CopyPasteRequestPasteOrientation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CopyPasteRequestPasteOrientation -> c CopyPasteRequestPasteOrientation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CopyPasteRequestPasteOrientation #

toConstr :: CopyPasteRequestPasteOrientation -> Constr #

dataTypeOf :: CopyPasteRequestPasteOrientation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CopyPasteRequestPasteOrientation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CopyPasteRequestPasteOrientation) #

gmapT :: (forall b. Data b => b -> b) -> CopyPasteRequestPasteOrientation -> CopyPasteRequestPasteOrientation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CopyPasteRequestPasteOrientation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CopyPasteRequestPasteOrientation -> r #

gmapQ :: (forall d. Data d => d -> u) -> CopyPasteRequestPasteOrientation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CopyPasteRequestPasteOrientation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CopyPasteRequestPasteOrientation -> m CopyPasteRequestPasteOrientation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CopyPasteRequestPasteOrientation -> m CopyPasteRequestPasteOrientation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CopyPasteRequestPasteOrientation -> m CopyPasteRequestPasteOrientation #

Ord CopyPasteRequestPasteOrientation Source # 
Read CopyPasteRequestPasteOrientation Source # 
Show CopyPasteRequestPasteOrientation Source # 
Generic CopyPasteRequestPasteOrientation Source # 
Hashable CopyPasteRequestPasteOrientation Source # 
ToJSON CopyPasteRequestPasteOrientation Source # 
FromJSON CopyPasteRequestPasteOrientation Source # 
FromHttpApiData CopyPasteRequestPasteOrientation Source # 
ToHttpApiData CopyPasteRequestPasteOrientation Source # 
type Rep CopyPasteRequestPasteOrientation Source # 
type Rep CopyPasteRequestPasteOrientation = D1 (MetaData "CopyPasteRequestPasteOrientation" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "Normal" PrefixI False) U1) (C1 (MetaCons "Transpose" PrefixI False) U1))

BatchUpdateSpreadsheetRequest

data BatchUpdateSpreadsheetRequest Source #

The request for updating any aspect of a spreadsheet.

See: batchUpdateSpreadsheetRequest smart constructor.

Instances

Eq BatchUpdateSpreadsheetRequest Source # 
Data BatchUpdateSpreadsheetRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BatchUpdateSpreadsheetRequest -> c BatchUpdateSpreadsheetRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BatchUpdateSpreadsheetRequest #

toConstr :: BatchUpdateSpreadsheetRequest -> Constr #

dataTypeOf :: BatchUpdateSpreadsheetRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BatchUpdateSpreadsheetRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BatchUpdateSpreadsheetRequest) #

gmapT :: (forall b. Data b => b -> b) -> BatchUpdateSpreadsheetRequest -> BatchUpdateSpreadsheetRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BatchUpdateSpreadsheetRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BatchUpdateSpreadsheetRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> BatchUpdateSpreadsheetRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BatchUpdateSpreadsheetRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BatchUpdateSpreadsheetRequest -> m BatchUpdateSpreadsheetRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BatchUpdateSpreadsheetRequest -> m BatchUpdateSpreadsheetRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BatchUpdateSpreadsheetRequest -> m BatchUpdateSpreadsheetRequest #

Show BatchUpdateSpreadsheetRequest Source # 
Generic BatchUpdateSpreadsheetRequest Source # 
ToJSON BatchUpdateSpreadsheetRequest Source # 
FromJSON BatchUpdateSpreadsheetRequest Source # 
type Rep BatchUpdateSpreadsheetRequest Source # 
type Rep BatchUpdateSpreadsheetRequest = D1 (MetaData "BatchUpdateSpreadsheetRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BatchUpdateSpreadsheetRequest'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_busrResponseIncludeGridData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_busrResponseRanges") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))) ((:*:) (S1 (MetaSel (Just Symbol "_busrRequests") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Request']))) (S1 (MetaSel (Just Symbol "_busrIncludeSpreadsheetInResponse") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))

batchUpdateSpreadsheetRequest :: BatchUpdateSpreadsheetRequest Source #

Creates a value of BatchUpdateSpreadsheetRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

busrResponseIncludeGridData :: Lens' BatchUpdateSpreadsheetRequest (Maybe Bool) Source #

True if grid data should be returned. Meaningful only if if include_spreadsheet_response is 'true'. This parameter is ignored if a field mask was set in the request.

busrResponseRanges :: Lens' BatchUpdateSpreadsheetRequest [Text] Source #

Limits the ranges included in the response spreadsheet. Meaningful only if include_spreadsheet_response is 'true'.

busrRequests :: Lens' BatchUpdateSpreadsheetRequest [Request'] Source #

A list of updates to apply to the spreadsheet.

busrIncludeSpreadsheetInResponse :: Lens' BatchUpdateSpreadsheetRequest (Maybe Bool) Source #

Determines if the update response should include the spreadsheet resource.

PasteDataRequestType

data PasteDataRequestType Source #

How the data should be pasted.

Constructors

PDRTPasteNormal

PASTE_NORMAL Paste values, formulas, formats, and merges.

PDRTPasteValues

PASTE_VALUES Paste the values ONLY without formats, formulas, or merges.

PDRTPasteFormat

PASTE_FORMAT Paste the format and data validation only.

PDRTPasteNoBOrders

PASTE_NO_BORDERS Like PASTE_NORMAL but without borders.

PDRTPasteFormula

PASTE_FORMULA Paste the formulas only.

PDRTPasteDataValidation

PASTE_DATA_VALIDATION Paste the data validation only.

PDRTPasteConditionalFormatting

PASTE_CONDITIONAL_FORMATTING Paste the conditional formatting rules only.

Instances

Enum PasteDataRequestType Source # 
Eq PasteDataRequestType Source # 
Data PasteDataRequestType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PasteDataRequestType -> c PasteDataRequestType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PasteDataRequestType #

toConstr :: PasteDataRequestType -> Constr #

dataTypeOf :: PasteDataRequestType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PasteDataRequestType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PasteDataRequestType) #

gmapT :: (forall b. Data b => b -> b) -> PasteDataRequestType -> PasteDataRequestType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PasteDataRequestType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PasteDataRequestType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PasteDataRequestType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PasteDataRequestType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PasteDataRequestType -> m PasteDataRequestType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PasteDataRequestType -> m PasteDataRequestType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PasteDataRequestType -> m PasteDataRequestType #

Ord PasteDataRequestType Source # 
Read PasteDataRequestType Source # 
Show PasteDataRequestType Source # 
Generic PasteDataRequestType Source # 
Hashable PasteDataRequestType Source # 
ToJSON PasteDataRequestType Source # 
FromJSON PasteDataRequestType Source # 
FromHttpApiData PasteDataRequestType Source # 
ToHttpApiData PasteDataRequestType Source # 
type Rep PasteDataRequestType Source # 
type Rep PasteDataRequestType = D1 (MetaData "PasteDataRequestType" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "PDRTPasteNormal" PrefixI False) U1) ((:+:) (C1 (MetaCons "PDRTPasteValues" PrefixI False) U1) (C1 (MetaCons "PDRTPasteFormat" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PDRTPasteNoBOrders" PrefixI False) U1) (C1 (MetaCons "PDRTPasteFormula" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PDRTPasteDataValidation" PrefixI False) U1) (C1 (MetaCons "PDRTPasteConditionalFormatting" PrefixI False) U1))))

UpdateValuesResponse

data UpdateValuesResponse Source #

The response when updating a range of values in a spreadsheet.

See: updateValuesResponse smart constructor.

Instances

Eq UpdateValuesResponse Source # 
Data UpdateValuesResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateValuesResponse -> c UpdateValuesResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateValuesResponse #

toConstr :: UpdateValuesResponse -> Constr #

dataTypeOf :: UpdateValuesResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateValuesResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateValuesResponse) #

gmapT :: (forall b. Data b => b -> b) -> UpdateValuesResponse -> UpdateValuesResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateValuesResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateValuesResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateValuesResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateValuesResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateValuesResponse -> m UpdateValuesResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateValuesResponse -> m UpdateValuesResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateValuesResponse -> m UpdateValuesResponse #

Show UpdateValuesResponse Source # 
Generic UpdateValuesResponse Source # 
ToJSON UpdateValuesResponse Source # 
FromJSON UpdateValuesResponse Source # 
type Rep UpdateValuesResponse Source # 
type Rep UpdateValuesResponse = D1 (MetaData "UpdateValuesResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "UpdateValuesResponse'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_uvrUpdatedCells") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) ((:*:) (S1 (MetaSel (Just Symbol "_uvrSpreadsheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_uvrUpdatedRows") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))) ((:*:) (S1 (MetaSel (Just Symbol "_uvrUpdatedRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_uvrUpdatedData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ValueRange))) (S1 (MetaSel (Just Symbol "_uvrUpdatedColumns") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))))

updateValuesResponse :: UpdateValuesResponse Source #

Creates a value of UpdateValuesResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

uvrUpdatedCells :: Lens' UpdateValuesResponse (Maybe Int32) Source #

The number of cells updated.

uvrSpreadsheetId :: Lens' UpdateValuesResponse (Maybe Text) Source #

The spreadsheet the updates were applied to.

uvrUpdatedRows :: Lens' UpdateValuesResponse (Maybe Int32) Source #

The number of rows where at least one cell in the row was updated.

uvrUpdatedRange :: Lens' UpdateValuesResponse (Maybe Text) Source #

The range (in A1 notation) that updates were applied to.

uvrUpdatedData :: Lens' UpdateValuesResponse (Maybe ValueRange) Source #

The values of the cells after updates were applied. This is only included if the request's `includeValuesInResponse` field was `true`.

uvrUpdatedColumns :: Lens' UpdateValuesResponse (Maybe Int32) Source #

The number of columns where at least one cell in the column was updated.

CopySheetToAnotherSpreadsheetRequest

data CopySheetToAnotherSpreadsheetRequest Source #

The request to copy a sheet across spreadsheets.

See: copySheetToAnotherSpreadsheetRequest smart constructor.

Instances

Eq CopySheetToAnotherSpreadsheetRequest Source # 
Data CopySheetToAnotherSpreadsheetRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CopySheetToAnotherSpreadsheetRequest -> c CopySheetToAnotherSpreadsheetRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CopySheetToAnotherSpreadsheetRequest #

toConstr :: CopySheetToAnotherSpreadsheetRequest -> Constr #

dataTypeOf :: CopySheetToAnotherSpreadsheetRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CopySheetToAnotherSpreadsheetRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CopySheetToAnotherSpreadsheetRequest) #

gmapT :: (forall b. Data b => b -> b) -> CopySheetToAnotherSpreadsheetRequest -> CopySheetToAnotherSpreadsheetRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CopySheetToAnotherSpreadsheetRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CopySheetToAnotherSpreadsheetRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> CopySheetToAnotherSpreadsheetRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CopySheetToAnotherSpreadsheetRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CopySheetToAnotherSpreadsheetRequest -> m CopySheetToAnotherSpreadsheetRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CopySheetToAnotherSpreadsheetRequest -> m CopySheetToAnotherSpreadsheetRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CopySheetToAnotherSpreadsheetRequest -> m CopySheetToAnotherSpreadsheetRequest #

Show CopySheetToAnotherSpreadsheetRequest Source # 
Generic CopySheetToAnotherSpreadsheetRequest Source # 
ToJSON CopySheetToAnotherSpreadsheetRequest Source # 
FromJSON CopySheetToAnotherSpreadsheetRequest Source # 
type Rep CopySheetToAnotherSpreadsheetRequest Source # 
type Rep CopySheetToAnotherSpreadsheetRequest = D1 (MetaData "CopySheetToAnotherSpreadsheetRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "CopySheetToAnotherSpreadsheetRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_cstasrDestinationSpreadsheetId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

copySheetToAnotherSpreadsheetRequest :: CopySheetToAnotherSpreadsheetRequest Source #

Creates a value of CopySheetToAnotherSpreadsheetRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cstasrDestinationSpreadsheetId :: Lens' CopySheetToAnotherSpreadsheetRequest (Maybe Text) Source #

The ID of the spreadsheet to copy the sheet to.

AddFilterViewRequest

data AddFilterViewRequest Source #

Adds a filter view.

See: addFilterViewRequest smart constructor.

Instances

Eq AddFilterViewRequest Source # 
Data AddFilterViewRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddFilterViewRequest -> c AddFilterViewRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddFilterViewRequest #

toConstr :: AddFilterViewRequest -> Constr #

dataTypeOf :: AddFilterViewRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddFilterViewRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddFilterViewRequest) #

gmapT :: (forall b. Data b => b -> b) -> AddFilterViewRequest -> AddFilterViewRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddFilterViewRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddFilterViewRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddFilterViewRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddFilterViewRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddFilterViewRequest -> m AddFilterViewRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddFilterViewRequest -> m AddFilterViewRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddFilterViewRequest -> m AddFilterViewRequest #

Show AddFilterViewRequest Source # 
Generic AddFilterViewRequest Source # 
ToJSON AddFilterViewRequest Source # 
FromJSON AddFilterViewRequest Source # 
type Rep AddFilterViewRequest Source # 
type Rep AddFilterViewRequest = D1 (MetaData "AddFilterViewRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "AddFilterViewRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_aFilter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilterView))))

addFilterViewRequest :: AddFilterViewRequest Source #

Creates a value of AddFilterViewRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

aFilter :: Lens' AddFilterViewRequest (Maybe FilterView) Source #

The filter to add. The filterViewId field is optional; if one is not set, an id will be randomly generated. (It is an error to specify the ID of a filter that already exists.)

PivotGroupValueMetadata

data PivotGroupValueMetadata Source #

Metadata about a value in a pivot grouping.

See: pivotGroupValueMetadata smart constructor.

Instances

Eq PivotGroupValueMetadata Source # 
Data PivotGroupValueMetadata Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PivotGroupValueMetadata -> c PivotGroupValueMetadata #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PivotGroupValueMetadata #

toConstr :: PivotGroupValueMetadata -> Constr #

dataTypeOf :: PivotGroupValueMetadata -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PivotGroupValueMetadata) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PivotGroupValueMetadata) #

gmapT :: (forall b. Data b => b -> b) -> PivotGroupValueMetadata -> PivotGroupValueMetadata #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PivotGroupValueMetadata -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PivotGroupValueMetadata -> r #

gmapQ :: (forall d. Data d => d -> u) -> PivotGroupValueMetadata -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PivotGroupValueMetadata -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PivotGroupValueMetadata -> m PivotGroupValueMetadata #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotGroupValueMetadata -> m PivotGroupValueMetadata #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotGroupValueMetadata -> m PivotGroupValueMetadata #

Show PivotGroupValueMetadata Source # 
Generic PivotGroupValueMetadata Source # 
ToJSON PivotGroupValueMetadata Source # 
FromJSON PivotGroupValueMetadata Source # 
type Rep PivotGroupValueMetadata Source # 
type Rep PivotGroupValueMetadata = D1 (MetaData "PivotGroupValueMetadata" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "PivotGroupValueMetadata'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pgvmValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ExtendedValue))) (S1 (MetaSel (Just Symbol "_pgvmCollapsed") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))))

pivotGroupValueMetadata :: PivotGroupValueMetadata Source #

Creates a value of PivotGroupValueMetadata with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pgvmValue :: Lens' PivotGroupValueMetadata (Maybe ExtendedValue) Source #

The calculated value the metadata corresponds to. (Note that formulaValue is not valid, because the values will be calculated.)

pgvmCollapsed :: Lens' PivotGroupValueMetadata (Maybe Bool) Source #

True if the data corresponding to the value is collapsed.

CellFormatTextDirection

data CellFormatTextDirection Source #

The direction of the text in the cell.

Constructors

TextDirectionUnspecified

TEXT_DIRECTION_UNSPECIFIED The text direction is not specified. Do not use this.

LeftToRight

LEFT_TO_RIGHT The text direction of left-to-right was set by the user.

RightToLeft

RIGHT_TO_LEFT The text direction of right-to-left was set by the user.

Instances

Enum CellFormatTextDirection Source # 
Eq CellFormatTextDirection Source # 
Data CellFormatTextDirection Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CellFormatTextDirection -> c CellFormatTextDirection #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CellFormatTextDirection #

toConstr :: CellFormatTextDirection -> Constr #

dataTypeOf :: CellFormatTextDirection -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CellFormatTextDirection) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CellFormatTextDirection) #

gmapT :: (forall b. Data b => b -> b) -> CellFormatTextDirection -> CellFormatTextDirection #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CellFormatTextDirection -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CellFormatTextDirection -> r #

gmapQ :: (forall d. Data d => d -> u) -> CellFormatTextDirection -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CellFormatTextDirection -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CellFormatTextDirection -> m CellFormatTextDirection #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CellFormatTextDirection -> m CellFormatTextDirection #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CellFormatTextDirection -> m CellFormatTextDirection #

Ord CellFormatTextDirection Source # 
Read CellFormatTextDirection Source # 
Show CellFormatTextDirection Source # 
Generic CellFormatTextDirection Source # 
Hashable CellFormatTextDirection Source # 
ToJSON CellFormatTextDirection Source # 
FromJSON CellFormatTextDirection Source # 
FromHttpApiData CellFormatTextDirection Source # 
ToHttpApiData CellFormatTextDirection Source # 
type Rep CellFormatTextDirection Source # 
type Rep CellFormatTextDirection = D1 (MetaData "CellFormatTextDirection" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "TextDirectionUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "LeftToRight" PrefixI False) U1) (C1 (MetaCons "RightToLeft" PrefixI False) U1)))

BasicChartSeriesType

data BasicChartSeriesType Source #

The type of this series. Valid only if the chartType is COMBO. Different types will change the way the series is visualized. Only LINE, AREA, and COLUMN are supported.

Constructors

BCSTBasicChartTypeUnspecified

BASIC_CHART_TYPE_UNSPECIFIED Default value, do not use.

BCSTBar

BAR A bar chart.

BCSTLine

LINE A line chart.

BCSTArea

AREA An area chart.

BCSTColumn

COLUMN A column chart.

BCSTScatter

SCATTER A scatter chart.

BCSTCombo

COMBO A combo chart.

Instances

Enum BasicChartSeriesType Source # 
Eq BasicChartSeriesType Source # 
Data BasicChartSeriesType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BasicChartSeriesType -> c BasicChartSeriesType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BasicChartSeriesType #

toConstr :: BasicChartSeriesType -> Constr #

dataTypeOf :: BasicChartSeriesType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BasicChartSeriesType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BasicChartSeriesType) #

gmapT :: (forall b. Data b => b -> b) -> BasicChartSeriesType -> BasicChartSeriesType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BasicChartSeriesType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BasicChartSeriesType -> r #

gmapQ :: (forall d. Data d => d -> u) -> BasicChartSeriesType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BasicChartSeriesType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BasicChartSeriesType -> m BasicChartSeriesType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicChartSeriesType -> m BasicChartSeriesType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicChartSeriesType -> m BasicChartSeriesType #

Ord BasicChartSeriesType Source # 
Read BasicChartSeriesType Source # 
Show BasicChartSeriesType Source # 
Generic BasicChartSeriesType Source # 
Hashable BasicChartSeriesType Source # 
ToJSON BasicChartSeriesType Source # 
FromJSON BasicChartSeriesType Source # 
FromHttpApiData BasicChartSeriesType Source # 
ToHttpApiData BasicChartSeriesType Source # 
type Rep BasicChartSeriesType Source # 
type Rep BasicChartSeriesType = D1 (MetaData "BasicChartSeriesType" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "BCSTBasicChartTypeUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "BCSTBar" PrefixI False) U1) (C1 (MetaCons "BCSTLine" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "BCSTArea" PrefixI False) U1) (C1 (MetaCons "BCSTColumn" PrefixI False) U1)) ((:+:) (C1 (MetaCons "BCSTScatter" PrefixI False) U1) (C1 (MetaCons "BCSTCombo" PrefixI False) U1))))

UpdateCellsRequest

data UpdateCellsRequest Source #

Updates all cells in a range with new data.

See: updateCellsRequest smart constructor.

Instances

Eq UpdateCellsRequest Source # 
Data UpdateCellsRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateCellsRequest -> c UpdateCellsRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateCellsRequest #

toConstr :: UpdateCellsRequest -> Constr #

dataTypeOf :: UpdateCellsRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateCellsRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateCellsRequest) #

gmapT :: (forall b. Data b => b -> b) -> UpdateCellsRequest -> UpdateCellsRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateCellsRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateCellsRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateCellsRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateCellsRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateCellsRequest -> m UpdateCellsRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateCellsRequest -> m UpdateCellsRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateCellsRequest -> m UpdateCellsRequest #

Show UpdateCellsRequest Source # 
Generic UpdateCellsRequest Source # 
ToJSON UpdateCellsRequest Source # 
FromJSON UpdateCellsRequest Source # 
type Rep UpdateCellsRequest Source # 
type Rep UpdateCellsRequest = D1 (MetaData "UpdateCellsRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "UpdateCellsRequest'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_updStart") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridCoordinate))) (S1 (MetaSel (Just Symbol "_updRows") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [RowData])))) ((:*:) (S1 (MetaSel (Just Symbol "_updRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange))) (S1 (MetaSel (Just Symbol "_updFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FieldMask))))))

updateCellsRequest :: UpdateCellsRequest Source #

Creates a value of UpdateCellsRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

updStart :: Lens' UpdateCellsRequest (Maybe GridCoordinate) Source #

The coordinate to start writing data at. Any number of rows and columns (including a different number of columns per row) may be written.

updRange :: Lens' UpdateCellsRequest (Maybe GridRange) Source #

The range to write data to. If the data in rows does not cover the entire requested range, the fields matching those set in fields will be cleared.

updFields :: Lens' UpdateCellsRequest (Maybe FieldMask) Source #

The fields of CellData that should be updated. At least one field must be specified. The root is the CellData; 'row.values.' should not be specified. A single `"*"` can be used as short-hand for listing every field.

CellFormat

data CellFormat Source #

The format of a cell.

See: cellFormat smart constructor.

Instances

Eq CellFormat Source # 
Data CellFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CellFormat -> c CellFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CellFormat #

toConstr :: CellFormat -> Constr #

dataTypeOf :: CellFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CellFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CellFormat) #

gmapT :: (forall b. Data b => b -> b) -> CellFormat -> CellFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CellFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CellFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> CellFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CellFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CellFormat -> m CellFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CellFormat -> m CellFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CellFormat -> m CellFormat #

Show CellFormat Source # 
Generic CellFormat Source # 

Associated Types

type Rep CellFormat :: * -> * #

ToJSON CellFormat Source # 
FromJSON CellFormat Source # 
type Rep CellFormat Source # 
type Rep CellFormat = D1 (MetaData "CellFormat" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "CellFormat'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cfBOrders") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BOrders))) (S1 (MetaSel (Just Symbol "_cfVerticalAlignment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CellFormatVerticalAlignment)))) ((:*:) (S1 (MetaSel (Just Symbol "_cfBackgRoundColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Color))) ((:*:) (S1 (MetaSel (Just Symbol "_cfHyperlinkDisplayType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CellFormatHyperlinkDisplayType))) (S1 (MetaSel (Just Symbol "_cfWrapStrategy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CellFormatWrapStrategy)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cfNumberFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NumberFormat))) (S1 (MetaSel (Just Symbol "_cfTextDirection") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CellFormatTextDirection)))) ((:*:) (S1 (MetaSel (Just Symbol "_cfTextFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TextFormat))) ((:*:) (S1 (MetaSel (Just Symbol "_cfHorizontalAlignment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CellFormatHorizontalAlignment))) (S1 (MetaSel (Just Symbol "_cfPadding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Padding))))))))

cellFormat :: CellFormat Source #

Creates a value of CellFormat with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cfBOrders :: Lens' CellFormat (Maybe BOrders) Source #

The borders of the cell.

cfVerticalAlignment :: Lens' CellFormat (Maybe CellFormatVerticalAlignment) Source #

The vertical alignment of the value in the cell.

cfBackgRoundColor :: Lens' CellFormat (Maybe Color) Source #

The background color of the cell.

cfHyperlinkDisplayType :: Lens' CellFormat (Maybe CellFormatHyperlinkDisplayType) Source #

How a hyperlink, if it exists, should be displayed in the cell.

cfWrapStrategy :: Lens' CellFormat (Maybe CellFormatWrapStrategy) Source #

The wrap strategy for the value in the cell.

cfNumberFormat :: Lens' CellFormat (Maybe NumberFormat) Source #

A format describing how number values should be represented to the user.

cfTextDirection :: Lens' CellFormat (Maybe CellFormatTextDirection) Source #

The direction of the text in the cell.

cfTextFormat :: Lens' CellFormat (Maybe TextFormat) Source #

The format of the text in the cell (unless overridden by a format run).

cfHorizontalAlignment :: Lens' CellFormat (Maybe CellFormatHorizontalAlignment) Source #

The horizontal alignment of the value in the cell.

cfPadding :: Lens' CellFormat (Maybe Padding) Source #

The padding of the cell.

DeleteProtectedRangeRequest

data DeleteProtectedRangeRequest Source #

Deletes the protected range with the given ID.

See: deleteProtectedRangeRequest smart constructor.

Instances

Eq DeleteProtectedRangeRequest Source # 
Data DeleteProtectedRangeRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeleteProtectedRangeRequest -> c DeleteProtectedRangeRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeleteProtectedRangeRequest #

toConstr :: DeleteProtectedRangeRequest -> Constr #

dataTypeOf :: DeleteProtectedRangeRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeleteProtectedRangeRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeleteProtectedRangeRequest) #

gmapT :: (forall b. Data b => b -> b) -> DeleteProtectedRangeRequest -> DeleteProtectedRangeRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeleteProtectedRangeRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeleteProtectedRangeRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeleteProtectedRangeRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeleteProtectedRangeRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeleteProtectedRangeRequest -> m DeleteProtectedRangeRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteProtectedRangeRequest -> m DeleteProtectedRangeRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteProtectedRangeRequest -> m DeleteProtectedRangeRequest #

Show DeleteProtectedRangeRequest Source # 
Generic DeleteProtectedRangeRequest Source # 
ToJSON DeleteProtectedRangeRequest Source # 
FromJSON DeleteProtectedRangeRequest Source # 
type Rep DeleteProtectedRangeRequest Source # 
type Rep DeleteProtectedRangeRequest = D1 (MetaData "DeleteProtectedRangeRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "DeleteProtectedRangeRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_dprrProtectedRangeId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Textual Int32)))))

deleteProtectedRangeRequest :: DeleteProtectedRangeRequest Source #

Creates a value of DeleteProtectedRangeRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dprrProtectedRangeId :: Lens' DeleteProtectedRangeRequest (Maybe Int32) Source #

The ID of the protected range to delete.

UpdateProtectedRangeRequest

data UpdateProtectedRangeRequest Source #

Updates an existing protected range with the specified protectedRangeId.

See: updateProtectedRangeRequest smart constructor.

Instances

Eq UpdateProtectedRangeRequest Source # 
Data UpdateProtectedRangeRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateProtectedRangeRequest -> c UpdateProtectedRangeRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateProtectedRangeRequest #

toConstr :: UpdateProtectedRangeRequest -> Constr #

dataTypeOf :: UpdateProtectedRangeRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateProtectedRangeRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateProtectedRangeRequest) #

gmapT :: (forall b. Data b => b -> b) -> UpdateProtectedRangeRequest -> UpdateProtectedRangeRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateProtectedRangeRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateProtectedRangeRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateProtectedRangeRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateProtectedRangeRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateProtectedRangeRequest -> m UpdateProtectedRangeRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateProtectedRangeRequest -> m UpdateProtectedRangeRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateProtectedRangeRequest -> m UpdateProtectedRangeRequest #

Show UpdateProtectedRangeRequest Source # 
Generic UpdateProtectedRangeRequest Source # 
ToJSON UpdateProtectedRangeRequest Source # 
FromJSON UpdateProtectedRangeRequest Source # 
type Rep UpdateProtectedRangeRequest Source # 
type Rep UpdateProtectedRangeRequest = D1 (MetaData "UpdateProtectedRangeRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "UpdateProtectedRangeRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_uprrProtectedRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ProtectedRange))) (S1 (MetaSel (Just Symbol "_uprrFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FieldMask)))))

updateProtectedRangeRequest :: UpdateProtectedRangeRequest Source #

Creates a value of UpdateProtectedRangeRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

uprrProtectedRange :: Lens' UpdateProtectedRangeRequest (Maybe ProtectedRange) Source #

The protected range to update with the new properties.

uprrFields :: Lens' UpdateProtectedRangeRequest (Maybe FieldMask) Source #

The fields that should be updated. At least one field must be specified. The root `protectedRange` is implied and should not be specified. A single `"*"` can be used as short-hand for listing every field.

AddSheetResponse

data AddSheetResponse Source #

The result of adding a sheet.

See: addSheetResponse smart constructor.

Instances

Eq AddSheetResponse Source # 
Data AddSheetResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddSheetResponse -> c AddSheetResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddSheetResponse #

toConstr :: AddSheetResponse -> Constr #

dataTypeOf :: AddSheetResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddSheetResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddSheetResponse) #

gmapT :: (forall b. Data b => b -> b) -> AddSheetResponse -> AddSheetResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddSheetResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddSheetResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddSheetResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddSheetResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddSheetResponse -> m AddSheetResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddSheetResponse -> m AddSheetResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddSheetResponse -> m AddSheetResponse #

Show AddSheetResponse Source # 
Generic AddSheetResponse Source # 
ToJSON AddSheetResponse Source # 
FromJSON AddSheetResponse Source # 
type Rep AddSheetResponse Source # 
type Rep AddSheetResponse = D1 (MetaData "AddSheetResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "AddSheetResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_aProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SheetProperties))))

addSheetResponse :: AddSheetResponse Source #

Creates a value of AddSheetResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

aProperties :: Lens' AddSheetResponse (Maybe SheetProperties) Source #

The properties of the newly added sheet.

ProtectedRange

data ProtectedRange Source #

A protected range.

See: protectedRange smart constructor.

Instances

Eq ProtectedRange Source # 
Data ProtectedRange Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProtectedRange -> c ProtectedRange #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProtectedRange #

toConstr :: ProtectedRange -> Constr #

dataTypeOf :: ProtectedRange -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ProtectedRange) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProtectedRange) #

gmapT :: (forall b. Data b => b -> b) -> ProtectedRange -> ProtectedRange #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProtectedRange -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProtectedRange -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProtectedRange -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProtectedRange -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProtectedRange -> m ProtectedRange #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProtectedRange -> m ProtectedRange #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProtectedRange -> m ProtectedRange #

Show ProtectedRange Source # 
Generic ProtectedRange Source # 

Associated Types

type Rep ProtectedRange :: * -> * #

ToJSON ProtectedRange Source # 
FromJSON ProtectedRange Source # 
type Rep ProtectedRange Source # 

protectedRange :: ProtectedRange Source #

Creates a value of ProtectedRange with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

prProtectedRangeId :: Lens' ProtectedRange (Maybe Int32) Source #

The ID of the protected range. This field is read-only.

prWarningOnly :: Lens' ProtectedRange (Maybe Bool) Source #

True if this protected range will show a warning when editing. Warning-based protection means that every user can edit data in the protected range, except editing will prompt a warning asking the user to confirm the edit. When writing: if this field is true, then editors is ignored. Additionally, if this field is changed from true to false and the `editors` field is not set (nor included in the field mask), then the editors will be set to all the editors in the document.

prNamedRangeId :: Lens' ProtectedRange (Maybe Text) Source #

The named range this protected range is backed by, if any. When writing, only one of range or named_range_id may be set.

prRange :: Lens' ProtectedRange (Maybe GridRange) Source #

The range that is being protected. The range may be fully unbounded, in which case this is considered a protected sheet. When writing, only one of range or named_range_id may be set.

prEditors :: Lens' ProtectedRange (Maybe Editors) Source #

The users and groups with edit access to the protected range. This field is only visible to users with edit access to the protected range and the document. Editors are not supported with warning_only protection.

prUnprotectedRanges :: Lens' ProtectedRange [GridRange] Source #

The list of unprotected ranges within a protected sheet. Unprotected ranges are only supported on protected sheets.

prRequestingUserCanEdit :: Lens' ProtectedRange (Maybe Bool) Source #

True if the user who requested this protected range can edit the protected area. This field is read-only.

prDescription :: Lens' ProtectedRange (Maybe Text) Source #

The description of this protected range.

BasicChartAxis

data BasicChartAxis Source #

An axis of the chart. A chart may not have more than one axis per axis position.

See: basicChartAxis smart constructor.

Instances

Eq BasicChartAxis Source # 
Data BasicChartAxis Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BasicChartAxis -> c BasicChartAxis #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BasicChartAxis #

toConstr :: BasicChartAxis -> Constr #

dataTypeOf :: BasicChartAxis -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BasicChartAxis) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BasicChartAxis) #

gmapT :: (forall b. Data b => b -> b) -> BasicChartAxis -> BasicChartAxis #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BasicChartAxis -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BasicChartAxis -> r #

gmapQ :: (forall d. Data d => d -> u) -> BasicChartAxis -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BasicChartAxis -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BasicChartAxis -> m BasicChartAxis #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicChartAxis -> m BasicChartAxis #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicChartAxis -> m BasicChartAxis #

Show BasicChartAxis Source # 
Generic BasicChartAxis Source # 

Associated Types

type Rep BasicChartAxis :: * -> * #

ToJSON BasicChartAxis Source # 
FromJSON BasicChartAxis Source # 
type Rep BasicChartAxis Source # 
type Rep BasicChartAxis = D1 (MetaData "BasicChartAxis" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BasicChartAxis'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bcaFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TextFormat))) ((:*:) (S1 (MetaSel (Just Symbol "_bcaTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bcaPosition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BasicChartAxisPosition))))))

basicChartAxis :: BasicChartAxis Source #

Creates a value of BasicChartAxis with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

bcaFormat :: Lens' BasicChartAxis (Maybe TextFormat) Source #

The format of the title. Only valid if the axis is not associated with the domain.

bcaTitle :: Lens' BasicChartAxis (Maybe Text) Source #

The title of this axis. If set, this overrides any title inferred from headers of the data.

GridData

data GridData Source #

Data in the grid, as well as metadata about the dimensions.

See: gridData smart constructor.

Instances

Eq GridData Source # 
Data GridData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GridData -> c GridData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GridData #

toConstr :: GridData -> Constr #

dataTypeOf :: GridData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GridData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GridData) #

gmapT :: (forall b. Data b => b -> b) -> GridData -> GridData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GridData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GridData -> r #

gmapQ :: (forall d. Data d => d -> u) -> GridData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GridData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GridData -> m GridData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GridData -> m GridData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GridData -> m GridData #

Show GridData Source # 
Generic GridData Source # 

Associated Types

type Rep GridData :: * -> * #

Methods

from :: GridData -> Rep GridData x #

to :: Rep GridData x -> GridData #

ToJSON GridData Source # 
FromJSON GridData Source # 
type Rep GridData Source # 

gridData :: GridData Source #

Creates a value of GridData with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

gdRowMetadata :: Lens' GridData [DimensionProperties] Source #

Metadata about the requested rows in the grid, starting with the row in start_row.

gdStartRow :: Lens' GridData (Maybe Int32) Source #

The first row this GridData refers to, zero-based.

gdRowData :: Lens' GridData [RowData] Source #

The data in the grid, one entry per row, starting with the row in startRow. The values in RowData will correspond to columns starting at start_column.

gdColumnMetadata :: Lens' GridData [DimensionProperties] Source #

Metadata about the requested columns in the grid, starting with the column in start_column.

gdStartColumn :: Lens' GridData (Maybe Int32) Source #

The first column this GridData refers to, zero-based.

NumberFormat

data NumberFormat Source #

The number format of a cell.

See: numberFormat smart constructor.

Instances

Eq NumberFormat Source # 
Data NumberFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NumberFormat -> c NumberFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NumberFormat #

toConstr :: NumberFormat -> Constr #

dataTypeOf :: NumberFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NumberFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NumberFormat) #

gmapT :: (forall b. Data b => b -> b) -> NumberFormat -> NumberFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NumberFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NumberFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> NumberFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NumberFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NumberFormat -> m NumberFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NumberFormat -> m NumberFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NumberFormat -> m NumberFormat #

Show NumberFormat Source # 
Generic NumberFormat Source # 

Associated Types

type Rep NumberFormat :: * -> * #

ToJSON NumberFormat Source # 
FromJSON NumberFormat Source # 
type Rep NumberFormat Source # 
type Rep NumberFormat = D1 (MetaData "NumberFormat" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "NumberFormat'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_nfPattern") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_nfType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe NumberFormatType)))))

numberFormat :: NumberFormat Source #

Creates a value of NumberFormat with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

nfPattern :: Lens' NumberFormat (Maybe Text) Source #

Pattern string used for formatting. If not set, a default pattern based on the user's locale will be used if necessary for the given type. See the Date and Number Formats guide for more information about the supported patterns.

nfType :: Lens' NumberFormat (Maybe NumberFormatType) Source #

The type of the number format. When writing, this field must be set.

BatchUpdateSpreadsheetResponse

data BatchUpdateSpreadsheetResponse Source #

The reply for batch updating a spreadsheet.

See: batchUpdateSpreadsheetResponse smart constructor.

Instances

Eq BatchUpdateSpreadsheetResponse Source # 
Data BatchUpdateSpreadsheetResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BatchUpdateSpreadsheetResponse -> c BatchUpdateSpreadsheetResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BatchUpdateSpreadsheetResponse #

toConstr :: BatchUpdateSpreadsheetResponse -> Constr #

dataTypeOf :: BatchUpdateSpreadsheetResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BatchUpdateSpreadsheetResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BatchUpdateSpreadsheetResponse) #

gmapT :: (forall b. Data b => b -> b) -> BatchUpdateSpreadsheetResponse -> BatchUpdateSpreadsheetResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BatchUpdateSpreadsheetResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BatchUpdateSpreadsheetResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> BatchUpdateSpreadsheetResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BatchUpdateSpreadsheetResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BatchUpdateSpreadsheetResponse -> m BatchUpdateSpreadsheetResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BatchUpdateSpreadsheetResponse -> m BatchUpdateSpreadsheetResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BatchUpdateSpreadsheetResponse -> m BatchUpdateSpreadsheetResponse #

Show BatchUpdateSpreadsheetResponse Source # 
Generic BatchUpdateSpreadsheetResponse Source # 
ToJSON BatchUpdateSpreadsheetResponse Source # 
FromJSON BatchUpdateSpreadsheetResponse Source # 
type Rep BatchUpdateSpreadsheetResponse Source # 
type Rep BatchUpdateSpreadsheetResponse = D1 (MetaData "BatchUpdateSpreadsheetResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BatchUpdateSpreadsheetResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_busrSpreadsheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_busrReplies") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Response]))) (S1 (MetaSel (Just Symbol "_busrUpdatedSpreadsheet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Spreadsheet))))))

batchUpdateSpreadsheetResponse :: BatchUpdateSpreadsheetResponse Source #

Creates a value of BatchUpdateSpreadsheetResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

busrSpreadsheetId :: Lens' BatchUpdateSpreadsheetResponse (Maybe Text) Source #

The spreadsheet the updates were applied to.

busrReplies :: Lens' BatchUpdateSpreadsheetResponse [Response] Source #

The reply of the updates. This maps 1:1 with the updates, although replies to some requests may be empty.

busrUpdatedSpreadsheet :: Lens' BatchUpdateSpreadsheetResponse (Maybe Spreadsheet) Source #

The spreadsheet after updates were applied. This is only set if [BatchUpdateSpreadsheetRequest.include_spreadsheet_in_response] is `true`.

SetDataValidationRequest

data SetDataValidationRequest Source #

Sets a data validation rule to every cell in the range. To clear validation in a range, call this with no rule specified.

See: setDataValidationRequest smart constructor.

Instances

Eq SetDataValidationRequest Source # 
Data SetDataValidationRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SetDataValidationRequest -> c SetDataValidationRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SetDataValidationRequest #

toConstr :: SetDataValidationRequest -> Constr #

dataTypeOf :: SetDataValidationRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SetDataValidationRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SetDataValidationRequest) #

gmapT :: (forall b. Data b => b -> b) -> SetDataValidationRequest -> SetDataValidationRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SetDataValidationRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SetDataValidationRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> SetDataValidationRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SetDataValidationRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SetDataValidationRequest -> m SetDataValidationRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SetDataValidationRequest -> m SetDataValidationRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SetDataValidationRequest -> m SetDataValidationRequest #

Show SetDataValidationRequest Source # 
Generic SetDataValidationRequest Source # 
ToJSON SetDataValidationRequest Source # 
FromJSON SetDataValidationRequest Source # 
type Rep SetDataValidationRequest Source # 
type Rep SetDataValidationRequest = D1 (MetaData "SetDataValidationRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "SetDataValidationRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sdvrRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DataValidationRule))) (S1 (MetaSel (Just Symbol "_sdvrRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange)))))

setDataValidationRequest :: SetDataValidationRequest Source #

Creates a value of SetDataValidationRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sdvrRule :: Lens' SetDataValidationRequest (Maybe DataValidationRule) Source #

The data validation rule to set on each cell in the range, or empty to clear the data validation in the range.

sdvrRange :: Lens' SetDataValidationRequest (Maybe GridRange) Source #

The range the data validation rule should apply to.

BandingProperties

data BandingProperties Source #

Properties referring a single dimension (either row or column). If both BandedRange.row_properties and BandedRange.column_properties are set, the fill colors are applied to cells according to the following rules: * header_color and footer_color take priority over band colors. * first_band_color takes priority over second_band_color. * row_properties takes priority over column_properties. For example, the first row color takes priority over the first column color, but the first column color takes priority over the second row color. Similarly, the row header takes priority over the column header in the top left cell, but the column header takes priority over the first row color if the row header is not set.

See: bandingProperties smart constructor.

Instances

Eq BandingProperties Source # 
Data BandingProperties Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BandingProperties -> c BandingProperties #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BandingProperties #

toConstr :: BandingProperties -> Constr #

dataTypeOf :: BandingProperties -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BandingProperties) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BandingProperties) #

gmapT :: (forall b. Data b => b -> b) -> BandingProperties -> BandingProperties #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BandingProperties -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BandingProperties -> r #

gmapQ :: (forall d. Data d => d -> u) -> BandingProperties -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BandingProperties -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BandingProperties -> m BandingProperties #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BandingProperties -> m BandingProperties #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BandingProperties -> m BandingProperties #

Show BandingProperties Source # 
Generic BandingProperties Source # 
ToJSON BandingProperties Source # 
FromJSON BandingProperties Source # 
type Rep BandingProperties Source # 
type Rep BandingProperties = D1 (MetaData "BandingProperties" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BandingProperties'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_bpSecondBandColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Color))) (S1 (MetaSel (Just Symbol "_bpHeaderColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Color)))) ((:*:) (S1 (MetaSel (Just Symbol "_bpFooterColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Color))) (S1 (MetaSel (Just Symbol "_bpFirstBandColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Color))))))

bandingProperties :: BandingProperties Source #

Creates a value of BandingProperties with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

bpSecondBandColor :: Lens' BandingProperties (Maybe Color) Source #

The second color that is alternating. (Required)

bpHeaderColor :: Lens' BandingProperties (Maybe Color) Source #

The color of the first row or column. If this field is set, the first row or column will be filled with this color and the colors will alternate between first_band_color and second_band_color starting from the second row or column. Otherwise, the first row or column will be filled with first_band_color and the colors will proceed to alternate as they normally would.

bpFooterColor :: Lens' BandingProperties (Maybe Color) Source #

The color of the last row or column. If this field is not set, the last row or column will be filled with either first_band_color or second_band_color, depending on the color of the previous row or column.

bpFirstBandColor :: Lens' BandingProperties (Maybe Color) Source #

The first color that is alternating. (Required)

ChartSpecHiddenDimensionStrategy

data ChartSpecHiddenDimensionStrategy Source #

Determines how the charts will use hidden rows or columns.

Constructors

ChartHiddenDimensionStrategyUnspecified

CHART_HIDDEN_DIMENSION_STRATEGY_UNSPECIFIED Default value, do not use.

SkipHiddenRowsAndColumns

SKIP_HIDDEN_ROWS_AND_COLUMNS Charts will skip hidden rows and columns.

SkipHiddenRows

SKIP_HIDDEN_ROWS Charts will skip hidden rows only.

SkipHiddenColumns

SKIP_HIDDEN_COLUMNS Charts will skip hidden columns only.

ShowAll

SHOW_ALL Charts will not skip any hidden rows or columns.

Instances

Enum ChartSpecHiddenDimensionStrategy Source # 
Eq ChartSpecHiddenDimensionStrategy Source # 
Data ChartSpecHiddenDimensionStrategy Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChartSpecHiddenDimensionStrategy -> c ChartSpecHiddenDimensionStrategy #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChartSpecHiddenDimensionStrategy #

toConstr :: ChartSpecHiddenDimensionStrategy -> Constr #

dataTypeOf :: ChartSpecHiddenDimensionStrategy -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ChartSpecHiddenDimensionStrategy) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChartSpecHiddenDimensionStrategy) #

gmapT :: (forall b. Data b => b -> b) -> ChartSpecHiddenDimensionStrategy -> ChartSpecHiddenDimensionStrategy #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChartSpecHiddenDimensionStrategy -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChartSpecHiddenDimensionStrategy -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChartSpecHiddenDimensionStrategy -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChartSpecHiddenDimensionStrategy -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChartSpecHiddenDimensionStrategy -> m ChartSpecHiddenDimensionStrategy #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChartSpecHiddenDimensionStrategy -> m ChartSpecHiddenDimensionStrategy #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChartSpecHiddenDimensionStrategy -> m ChartSpecHiddenDimensionStrategy #

Ord ChartSpecHiddenDimensionStrategy Source # 
Read ChartSpecHiddenDimensionStrategy Source # 
Show ChartSpecHiddenDimensionStrategy Source # 
Generic ChartSpecHiddenDimensionStrategy Source # 
Hashable ChartSpecHiddenDimensionStrategy Source # 
ToJSON ChartSpecHiddenDimensionStrategy Source # 
FromJSON ChartSpecHiddenDimensionStrategy Source # 
FromHttpApiData ChartSpecHiddenDimensionStrategy Source # 
ToHttpApiData ChartSpecHiddenDimensionStrategy Source # 
type Rep ChartSpecHiddenDimensionStrategy Source # 
type Rep ChartSpecHiddenDimensionStrategy = D1 (MetaData "ChartSpecHiddenDimensionStrategy" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "ChartHiddenDimensionStrategyUnspecified" PrefixI False) U1) (C1 (MetaCons "SkipHiddenRowsAndColumns" PrefixI False) U1)) ((:+:) (C1 (MetaCons "SkipHiddenRows" PrefixI False) U1) ((:+:) (C1 (MetaCons "SkipHiddenColumns" PrefixI False) U1) (C1 (MetaCons "ShowAll" PrefixI False) U1))))

DuplicateFilterViewRequest

data DuplicateFilterViewRequest Source #

Duplicates a particular filter view.

See: duplicateFilterViewRequest smart constructor.

Instances

Eq DuplicateFilterViewRequest Source # 
Data DuplicateFilterViewRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DuplicateFilterViewRequest -> c DuplicateFilterViewRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DuplicateFilterViewRequest #

toConstr :: DuplicateFilterViewRequest -> Constr #

dataTypeOf :: DuplicateFilterViewRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DuplicateFilterViewRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DuplicateFilterViewRequest) #

gmapT :: (forall b. Data b => b -> b) -> DuplicateFilterViewRequest -> DuplicateFilterViewRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DuplicateFilterViewRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DuplicateFilterViewRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> DuplicateFilterViewRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DuplicateFilterViewRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DuplicateFilterViewRequest -> m DuplicateFilterViewRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DuplicateFilterViewRequest -> m DuplicateFilterViewRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DuplicateFilterViewRequest -> m DuplicateFilterViewRequest #

Show DuplicateFilterViewRequest Source # 
Generic DuplicateFilterViewRequest Source # 
ToJSON DuplicateFilterViewRequest Source # 
FromJSON DuplicateFilterViewRequest Source # 
type Rep DuplicateFilterViewRequest Source # 
type Rep DuplicateFilterViewRequest = D1 (MetaData "DuplicateFilterViewRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "DuplicateFilterViewRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_dFilterId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Textual Int32)))))

duplicateFilterViewRequest :: DuplicateFilterViewRequest Source #

Creates a value of DuplicateFilterViewRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dFilterId :: Lens' DuplicateFilterViewRequest (Maybe Int32) Source #

The ID of the filter being duplicated.

BOrderStyle

data BOrderStyle Source #

The style of the border.

Constructors

StyleUnspecified

STYLE_UNSPECIFIED The style is not specified. Do not use this.

Dotted

DOTTED The border is dotted.

Dashed

DASHED The border is dashed.

Solid

SOLID The border is a thin solid line.

SolidMedium

SOLID_MEDIUM The border is a medium solid line.

SolidThick

SOLID_THICK The border is a thick solid line.

None

NONE No border. Used only when updating a border in order to erase it.

Double

DOUBLE The border is two solid lines.

Instances

Enum BOrderStyle Source # 
Eq BOrderStyle Source # 
Data BOrderStyle Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BOrderStyle -> c BOrderStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BOrderStyle #

toConstr :: BOrderStyle -> Constr #

dataTypeOf :: BOrderStyle -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BOrderStyle) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BOrderStyle) #

gmapT :: (forall b. Data b => b -> b) -> BOrderStyle -> BOrderStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BOrderStyle -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BOrderStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> BOrderStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BOrderStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BOrderStyle -> m BOrderStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BOrderStyle -> m BOrderStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BOrderStyle -> m BOrderStyle #

Ord BOrderStyle Source # 
Read BOrderStyle Source # 
Show BOrderStyle Source # 
Generic BOrderStyle Source # 

Associated Types

type Rep BOrderStyle :: * -> * #

Hashable BOrderStyle Source # 
ToJSON BOrderStyle Source # 
FromJSON BOrderStyle Source # 
FromHttpApiData BOrderStyle Source # 
ToHttpApiData BOrderStyle Source # 
type Rep BOrderStyle Source # 
type Rep BOrderStyle = D1 (MetaData "BOrderStyle" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "StyleUnspecified" PrefixI False) U1) (C1 (MetaCons "Dotted" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Dashed" PrefixI False) U1) (C1 (MetaCons "Solid" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "SolidMedium" PrefixI False) U1) (C1 (MetaCons "SolidThick" PrefixI False) U1)) ((:+:) (C1 (MetaCons "None" PrefixI False) U1) (C1 (MetaCons "Double" PrefixI False) U1))))

PivotGroup

data PivotGroup Source #

A single grouping (either row or column) in a pivot table.

See: pivotGroup smart constructor.

Instances

Eq PivotGroup Source # 
Data PivotGroup Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PivotGroup -> c PivotGroup #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PivotGroup #

toConstr :: PivotGroup -> Constr #

dataTypeOf :: PivotGroup -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PivotGroup) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PivotGroup) #

gmapT :: (forall b. Data b => b -> b) -> PivotGroup -> PivotGroup #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PivotGroup -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PivotGroup -> r #

gmapQ :: (forall d. Data d => d -> u) -> PivotGroup -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PivotGroup -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PivotGroup -> m PivotGroup #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotGroup -> m PivotGroup #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotGroup -> m PivotGroup #

Show PivotGroup Source # 
Generic PivotGroup Source # 

Associated Types

type Rep PivotGroup :: * -> * #

ToJSON PivotGroup Source # 
FromJSON PivotGroup Source # 
type Rep PivotGroup Source # 

pivotGroup :: PivotGroup Source #

Creates a value of PivotGroup with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pgValueMetadata :: Lens' PivotGroup [PivotGroupValueMetadata] Source #

Metadata about values in the grouping.

pgSourceColumnOffSet :: Lens' PivotGroup (Maybe Int32) Source #

The column offset of the source range that this grouping is based on. For example, if the source was `C10:E15`, a `sourceColumnOffset` of `0` means this group refers to column `C`, whereas the offset `1` would refer to column `D`.

pgSortOrder :: Lens' PivotGroup (Maybe PivotGroupSortOrder) Source #

The order the values in this group should be sorted.

pgShowTotals :: Lens' PivotGroup (Maybe Bool) Source #

True if the pivot table should include the totals for this grouping.

pgValueBucket :: Lens' PivotGroup (Maybe PivotGroupSortValueBucket) Source #

The bucket of the opposite pivot group to sort by. If not specified, sorting is alphabetical by this group's values.

AddBandingResponse

data AddBandingResponse Source #

The result of adding a banded range.

See: addBandingResponse smart constructor.

Instances

Eq AddBandingResponse Source # 
Data AddBandingResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddBandingResponse -> c AddBandingResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddBandingResponse #

toConstr :: AddBandingResponse -> Constr #

dataTypeOf :: AddBandingResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddBandingResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddBandingResponse) #

gmapT :: (forall b. Data b => b -> b) -> AddBandingResponse -> AddBandingResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddBandingResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddBandingResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddBandingResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddBandingResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddBandingResponse -> m AddBandingResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddBandingResponse -> m AddBandingResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddBandingResponse -> m AddBandingResponse #

Show AddBandingResponse Source # 
Generic AddBandingResponse Source # 
ToJSON AddBandingResponse Source # 
FromJSON AddBandingResponse Source # 
type Rep AddBandingResponse Source # 
type Rep AddBandingResponse = D1 (MetaData "AddBandingResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "AddBandingResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_aBandedRange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BandedRange))))

addBandingResponse :: AddBandingResponse Source #

Creates a value of AddBandingResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

aBandedRange :: Lens' AddBandingResponse (Maybe BandedRange) Source #

The banded range that was added.

CutPasteRequestPasteType

data CutPasteRequestPasteType Source #

What kind of data to paste. All the source data will be cut, regardless of what is pasted.

Constructors

CPRPTPasteNormal

PASTE_NORMAL Paste values, formulas, formats, and merges.

CPRPTPasteValues

PASTE_VALUES Paste the values ONLY without formats, formulas, or merges.

CPRPTPasteFormat

PASTE_FORMAT Paste the format and data validation only.

CPRPTPasteNoBOrders

PASTE_NO_BORDERS Like PASTE_NORMAL but without borders.

CPRPTPasteFormula

PASTE_FORMULA Paste the formulas only.

CPRPTPasteDataValidation

PASTE_DATA_VALIDATION Paste the data validation only.

CPRPTPasteConditionalFormatting

PASTE_CONDITIONAL_FORMATTING Paste the conditional formatting rules only.

Instances

Enum CutPasteRequestPasteType Source # 
Eq CutPasteRequestPasteType Source # 
Data CutPasteRequestPasteType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CutPasteRequestPasteType -> c CutPasteRequestPasteType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CutPasteRequestPasteType #

toConstr :: CutPasteRequestPasteType -> Constr #

dataTypeOf :: CutPasteRequestPasteType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CutPasteRequestPasteType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CutPasteRequestPasteType) #

gmapT :: (forall b. Data b => b -> b) -> CutPasteRequestPasteType -> CutPasteRequestPasteType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CutPasteRequestPasteType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CutPasteRequestPasteType -> r #

gmapQ :: (forall d. Data d => d -> u) -> CutPasteRequestPasteType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CutPasteRequestPasteType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CutPasteRequestPasteType -> m CutPasteRequestPasteType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CutPasteRequestPasteType -> m CutPasteRequestPasteType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CutPasteRequestPasteType -> m CutPasteRequestPasteType #

Ord CutPasteRequestPasteType Source # 
Read CutPasteRequestPasteType Source # 
Show CutPasteRequestPasteType Source # 
Generic CutPasteRequestPasteType Source # 
Hashable CutPasteRequestPasteType Source # 
ToJSON CutPasteRequestPasteType Source # 
FromJSON CutPasteRequestPasteType Source # 
FromHttpApiData CutPasteRequestPasteType Source # 
ToHttpApiData CutPasteRequestPasteType Source # 
type Rep CutPasteRequestPasteType Source # 
type Rep CutPasteRequestPasteType = D1 (MetaData "CutPasteRequestPasteType" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "CPRPTPasteNormal" PrefixI False) U1) ((:+:) (C1 (MetaCons "CPRPTPasteValues" PrefixI False) U1) (C1 (MetaCons "CPRPTPasteFormat" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CPRPTPasteNoBOrders" PrefixI False) U1) (C1 (MetaCons "CPRPTPasteFormula" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CPRPTPasteDataValidation" PrefixI False) U1) (C1 (MetaCons "CPRPTPasteConditionalFormatting" PrefixI False) U1))))

BasicChartSpecLegendPosition

data BasicChartSpecLegendPosition Source #

The position of the chart legend.

Constructors

BCSLPBasicChartLegendPositionUnspecified

BASIC_CHART_LEGEND_POSITION_UNSPECIFIED Default value, do not use.

BCSLPBottomLegend

BOTTOM_LEGEND The legend is rendered on the bottom of the chart.

BCSLPLeftLegend

LEFT_LEGEND The legend is rendered on the left of the chart.

BCSLPRightLegend

RIGHT_LEGEND The legend is rendered on the right of the chart.

BCSLPTopLegend

TOP_LEGEND The legend is rendered on the top of the chart.

BCSLPNoLegend

NO_LEGEND No legend is rendered.

Instances

Enum BasicChartSpecLegendPosition Source # 
Eq BasicChartSpecLegendPosition Source # 
Data BasicChartSpecLegendPosition Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BasicChartSpecLegendPosition -> c BasicChartSpecLegendPosition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BasicChartSpecLegendPosition #

toConstr :: BasicChartSpecLegendPosition -> Constr #

dataTypeOf :: BasicChartSpecLegendPosition -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BasicChartSpecLegendPosition) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BasicChartSpecLegendPosition) #

gmapT :: (forall b. Data b => b -> b) -> BasicChartSpecLegendPosition -> BasicChartSpecLegendPosition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BasicChartSpecLegendPosition -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BasicChartSpecLegendPosition -> r #

gmapQ :: (forall d. Data d => d -> u) -> BasicChartSpecLegendPosition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BasicChartSpecLegendPosition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BasicChartSpecLegendPosition -> m BasicChartSpecLegendPosition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicChartSpecLegendPosition -> m BasicChartSpecLegendPosition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicChartSpecLegendPosition -> m BasicChartSpecLegendPosition #

Ord BasicChartSpecLegendPosition Source # 
Read BasicChartSpecLegendPosition Source # 
Show BasicChartSpecLegendPosition Source # 
Generic BasicChartSpecLegendPosition Source # 
Hashable BasicChartSpecLegendPosition Source # 
ToJSON BasicChartSpecLegendPosition Source # 
FromJSON BasicChartSpecLegendPosition Source # 
FromHttpApiData BasicChartSpecLegendPosition Source # 
ToHttpApiData BasicChartSpecLegendPosition Source # 
type Rep BasicChartSpecLegendPosition Source # 
type Rep BasicChartSpecLegendPosition = D1 (MetaData "BasicChartSpecLegendPosition" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "BCSLPBasicChartLegendPositionUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "BCSLPBottomLegend" PrefixI False) U1) (C1 (MetaCons "BCSLPLeftLegend" PrefixI False) U1))) ((:+:) (C1 (MetaCons "BCSLPRightLegend" PrefixI False) U1) ((:+:) (C1 (MetaCons "BCSLPTopLegend" PrefixI False) U1) (C1 (MetaCons "BCSLPNoLegend" PrefixI False) U1))))

ErrorValueType

data ErrorValueType Source #

The type of error.

Constructors

ErrorTypeUnspecified

ERROR_TYPE_UNSPECIFIED The default error type, do not use this.

Error'

ERROR Corresponds to the `#ERROR!` error.

NullValue

NULL_VALUE Corresponds to the `#NULL!` error.

DivideByZero

DIVIDE_BY_ZERO Corresponds to the `#DIV/0` error.

Value

VALUE Corresponds to the `#VALUE!` error.

Ref

REF Corresponds to the `#REF!` error.

Name

NAME Corresponds to the `#NAME?` error.

Num

NUM Corresponds to the `#NUM`! error.

NA

N_A Corresponds to the `#N/A` error.

Loading

LOADING Corresponds to the `Loading...` state.

Instances

Enum ErrorValueType Source # 
Eq ErrorValueType Source # 
Data ErrorValueType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ErrorValueType -> c ErrorValueType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ErrorValueType #

toConstr :: ErrorValueType -> Constr #

dataTypeOf :: ErrorValueType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ErrorValueType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ErrorValueType) #

gmapT :: (forall b. Data b => b -> b) -> ErrorValueType -> ErrorValueType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ErrorValueType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ErrorValueType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ErrorValueType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ErrorValueType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ErrorValueType -> m ErrorValueType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorValueType -> m ErrorValueType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorValueType -> m ErrorValueType #

Ord ErrorValueType Source # 
Read ErrorValueType Source # 
Show ErrorValueType Source # 
Generic ErrorValueType Source # 

Associated Types

type Rep ErrorValueType :: * -> * #

Hashable ErrorValueType Source # 
ToJSON ErrorValueType Source # 
FromJSON ErrorValueType Source # 
FromHttpApiData ErrorValueType Source # 
ToHttpApiData ErrorValueType Source # 
type Rep ErrorValueType Source # 
type Rep ErrorValueType = D1 (MetaData "ErrorValueType" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ErrorTypeUnspecified" PrefixI False) U1) (C1 (MetaCons "Error'" PrefixI False) U1)) ((:+:) (C1 (MetaCons "NullValue" PrefixI False) U1) ((:+:) (C1 (MetaCons "DivideByZero" PrefixI False) U1) (C1 (MetaCons "Value" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Ref" PrefixI False) U1) (C1 (MetaCons "Name" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Num" PrefixI False) U1) ((:+:) (C1 (MetaCons "NA" PrefixI False) U1) (C1 (MetaCons "Loading" PrefixI False) U1)))))

ConditionalFormatRule

data ConditionalFormatRule Source #

A rule describing a conditional format.

See: conditionalFormatRule smart constructor.

Instances

Eq ConditionalFormatRule Source # 
Data ConditionalFormatRule Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConditionalFormatRule -> c ConditionalFormatRule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConditionalFormatRule #

toConstr :: ConditionalFormatRule -> Constr #

dataTypeOf :: ConditionalFormatRule -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConditionalFormatRule) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConditionalFormatRule) #

gmapT :: (forall b. Data b => b -> b) -> ConditionalFormatRule -> ConditionalFormatRule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConditionalFormatRule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConditionalFormatRule -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConditionalFormatRule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConditionalFormatRule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConditionalFormatRule -> m ConditionalFormatRule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConditionalFormatRule -> m ConditionalFormatRule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConditionalFormatRule -> m ConditionalFormatRule #

Show ConditionalFormatRule Source # 
Generic ConditionalFormatRule Source # 
ToJSON ConditionalFormatRule Source # 
FromJSON ConditionalFormatRule Source # 
type Rep ConditionalFormatRule Source # 
type Rep ConditionalFormatRule = D1 (MetaData "ConditionalFormatRule" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "ConditionalFormatRule'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cfrBooleanRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BooleanRule))) ((:*:) (S1 (MetaSel (Just Symbol "_cfrGradientRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GradientRule))) (S1 (MetaSel (Just Symbol "_cfrRanges") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [GridRange]))))))

conditionalFormatRule :: ConditionalFormatRule Source #

Creates a value of ConditionalFormatRule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cfrBooleanRule :: Lens' ConditionalFormatRule (Maybe BooleanRule) Source #

The formatting is either "on" or "off" according to the rule.

cfrGradientRule :: Lens' ConditionalFormatRule (Maybe GradientRule) Source #

The formatting will vary based on the gradients in the rule.

cfrRanges :: Lens' ConditionalFormatRule [GridRange] Source #

The ranges that will be formatted if the condition is true. All the ranges must be on the same grid.

BasicChartSpec

data BasicChartSpec Source #

The specification for a basic chart. See BasicChartType for the list of charts this supports.

See: basicChartSpec smart constructor.

Instances

Eq BasicChartSpec Source # 
Data BasicChartSpec Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BasicChartSpec -> c BasicChartSpec #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BasicChartSpec #

toConstr :: BasicChartSpec -> Constr #

dataTypeOf :: BasicChartSpec -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BasicChartSpec) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BasicChartSpec) #

gmapT :: (forall b. Data b => b -> b) -> BasicChartSpec -> BasicChartSpec #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BasicChartSpec -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BasicChartSpec -> r #

gmapQ :: (forall d. Data d => d -> u) -> BasicChartSpec -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BasicChartSpec -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BasicChartSpec -> m BasicChartSpec #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicChartSpec -> m BasicChartSpec #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicChartSpec -> m BasicChartSpec #

Show BasicChartSpec Source # 
Generic BasicChartSpec Source # 

Associated Types

type Rep BasicChartSpec :: * -> * #

ToJSON BasicChartSpec Source # 
FromJSON BasicChartSpec Source # 
type Rep BasicChartSpec Source # 

basicChartSpec :: BasicChartSpec Source #

Creates a value of BasicChartSpec with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

bHeaderCount :: Lens' BasicChartSpec (Maybe Int32) Source #

The number of rows or columns in the data that are "headers". If not set, Google Sheets will guess how many rows are headers based on the data. (Note that BasicChartAxis.title may override the axis title inferred from the header values.)

bSeries :: Lens' BasicChartSpec [BasicChartSeries] Source #

The data this chart is visualizing.

bDomains :: Lens' BasicChartSpec [BasicChartDomain] Source #

The domain of data this is charting. Only a single domain is currently supported.

bAxis :: Lens' BasicChartSpec [BasicChartAxis] Source #

The axis on the chart.

AddConditionalFormatRuleRequest

data AddConditionalFormatRuleRequest Source #

Adds a new conditional format rule at the given index. All subsequent rules' indexes are incremented.

See: addConditionalFormatRuleRequest smart constructor.

Instances

Eq AddConditionalFormatRuleRequest Source # 
Data AddConditionalFormatRuleRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AddConditionalFormatRuleRequest -> c AddConditionalFormatRuleRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AddConditionalFormatRuleRequest #

toConstr :: AddConditionalFormatRuleRequest -> Constr #

dataTypeOf :: AddConditionalFormatRuleRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AddConditionalFormatRuleRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AddConditionalFormatRuleRequest) #

gmapT :: (forall b. Data b => b -> b) -> AddConditionalFormatRuleRequest -> AddConditionalFormatRuleRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AddConditionalFormatRuleRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AddConditionalFormatRuleRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> AddConditionalFormatRuleRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AddConditionalFormatRuleRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AddConditionalFormatRuleRequest -> m AddConditionalFormatRuleRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AddConditionalFormatRuleRequest -> m AddConditionalFormatRuleRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AddConditionalFormatRuleRequest -> m AddConditionalFormatRuleRequest #

Show AddConditionalFormatRuleRequest Source # 
Generic AddConditionalFormatRuleRequest Source # 
ToJSON AddConditionalFormatRuleRequest Source # 
FromJSON AddConditionalFormatRuleRequest Source # 
type Rep AddConditionalFormatRuleRequest Source # 
type Rep AddConditionalFormatRuleRequest = D1 (MetaData "AddConditionalFormatRuleRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "AddConditionalFormatRuleRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_acfrrRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ConditionalFormatRule))) (S1 (MetaSel (Just Symbol "_acfrrIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

addConditionalFormatRuleRequest :: AddConditionalFormatRuleRequest Source #

Creates a value of AddConditionalFormatRuleRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

acfrrIndex :: Lens' AddConditionalFormatRuleRequest (Maybe Int32) Source #

The zero-based index where the rule should be inserted.

PivotTableValueLayout

data PivotTableValueLayout Source #

Whether values should be listed horizontally (as columns) or vertically (as rows).

Constructors

Horizontal

HORIZONTAL Values are laid out horizontally (as columns).

Vertical

VERTICAL Values are laid out vertically (as rows).

Instances

Enum PivotTableValueLayout Source # 
Eq PivotTableValueLayout Source # 
Data PivotTableValueLayout Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PivotTableValueLayout -> c PivotTableValueLayout #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PivotTableValueLayout #

toConstr :: PivotTableValueLayout -> Constr #

dataTypeOf :: PivotTableValueLayout -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PivotTableValueLayout) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PivotTableValueLayout) #

gmapT :: (forall b. Data b => b -> b) -> PivotTableValueLayout -> PivotTableValueLayout #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PivotTableValueLayout -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PivotTableValueLayout -> r #

gmapQ :: (forall d. Data d => d -> u) -> PivotTableValueLayout -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PivotTableValueLayout -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PivotTableValueLayout -> m PivotTableValueLayout #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotTableValueLayout -> m PivotTableValueLayout #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PivotTableValueLayout -> m PivotTableValueLayout #

Ord PivotTableValueLayout Source # 
Read PivotTableValueLayout Source # 
Show PivotTableValueLayout Source # 
Generic PivotTableValueLayout Source # 
Hashable PivotTableValueLayout Source # 
ToJSON PivotTableValueLayout Source # 
FromJSON PivotTableValueLayout Source # 
FromHttpApiData PivotTableValueLayout Source # 
ToHttpApiData PivotTableValueLayout Source # 
type Rep PivotTableValueLayout Source # 
type Rep PivotTableValueLayout = D1 (MetaData "PivotTableValueLayout" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "Horizontal" PrefixI False) U1) (C1 (MetaCons "Vertical" PrefixI False) U1))

DuplicateSheetResponse

data DuplicateSheetResponse Source #

The result of duplicating a sheet.

See: duplicateSheetResponse smart constructor.

Instances

Eq DuplicateSheetResponse Source # 
Data DuplicateSheetResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DuplicateSheetResponse -> c DuplicateSheetResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DuplicateSheetResponse #

toConstr :: DuplicateSheetResponse -> Constr #

dataTypeOf :: DuplicateSheetResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DuplicateSheetResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DuplicateSheetResponse) #

gmapT :: (forall b. Data b => b -> b) -> DuplicateSheetResponse -> DuplicateSheetResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DuplicateSheetResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DuplicateSheetResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> DuplicateSheetResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DuplicateSheetResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DuplicateSheetResponse -> m DuplicateSheetResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DuplicateSheetResponse -> m DuplicateSheetResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DuplicateSheetResponse -> m DuplicateSheetResponse #

Show DuplicateSheetResponse Source # 
Generic DuplicateSheetResponse Source # 
ToJSON DuplicateSheetResponse Source # 
FromJSON DuplicateSheetResponse Source # 
type Rep DuplicateSheetResponse Source # 
type Rep DuplicateSheetResponse = D1 (MetaData "DuplicateSheetResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "DuplicateSheetResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_dsrProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SheetProperties))))

duplicateSheetResponse :: DuplicateSheetResponse Source #

Creates a value of DuplicateSheetResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dsrProperties :: Lens' DuplicateSheetResponse (Maybe SheetProperties) Source #

The properties of the duplicate sheet.

TextFormat

data TextFormat Source #

The format of a run of text in a cell. Absent values indicate that the field isn't specified.

See: textFormat smart constructor.

Instances

Eq TextFormat Source # 
Data TextFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TextFormat -> c TextFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TextFormat #

toConstr :: TextFormat -> Constr #

dataTypeOf :: TextFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TextFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextFormat) #

gmapT :: (forall b. Data b => b -> b) -> TextFormat -> TextFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TextFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TextFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> TextFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TextFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TextFormat -> m TextFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TextFormat -> m TextFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TextFormat -> m TextFormat #

Show TextFormat Source # 
Generic TextFormat Source # 

Associated Types

type Rep TextFormat :: * -> * #

ToJSON TextFormat Source # 
FromJSON TextFormat Source # 
type Rep TextFormat Source # 

textFormat :: TextFormat Source #

Creates a value of TextFormat with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tfForegRoundColor :: Lens' TextFormat (Maybe Color) Source #

The foreground color of the text.

tfFontSize :: Lens' TextFormat (Maybe Int32) Source #

The size of the font.

tfUnderline :: Lens' TextFormat (Maybe Bool) Source #

True if the text is underlined.

tfItalic :: Lens' TextFormat (Maybe Bool) Source #

True if the text is italicized.

tfBold :: Lens' TextFormat (Maybe Bool) Source #

True if the text is bold.

tfStrikethrough :: Lens' TextFormat (Maybe Bool) Source #

True if the text has a strikethrough.

BatchClearValuesResponse

data BatchClearValuesResponse Source #

The response when updating a range of values in a spreadsheet.

See: batchClearValuesResponse smart constructor.

Instances

Eq BatchClearValuesResponse Source # 
Data BatchClearValuesResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BatchClearValuesResponse -> c BatchClearValuesResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BatchClearValuesResponse #

toConstr :: BatchClearValuesResponse -> Constr #

dataTypeOf :: BatchClearValuesResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BatchClearValuesResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BatchClearValuesResponse) #

gmapT :: (forall b. Data b => b -> b) -> BatchClearValuesResponse -> BatchClearValuesResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BatchClearValuesResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BatchClearValuesResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> BatchClearValuesResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BatchClearValuesResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BatchClearValuesResponse -> m BatchClearValuesResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BatchClearValuesResponse -> m BatchClearValuesResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BatchClearValuesResponse -> m BatchClearValuesResponse #

Show BatchClearValuesResponse Source # 
Generic BatchClearValuesResponse Source # 
ToJSON BatchClearValuesResponse Source # 
FromJSON BatchClearValuesResponse Source # 
type Rep BatchClearValuesResponse Source # 
type Rep BatchClearValuesResponse = D1 (MetaData "BatchClearValuesResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BatchClearValuesResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bcvrClearedRanges") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_bcvrSpreadsheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

batchClearValuesResponse :: BatchClearValuesResponse Source #

Creates a value of BatchClearValuesResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

bcvrClearedRanges :: Lens' BatchClearValuesResponse [Text] Source #

The ranges that were cleared, in A1 notation. (If the requests were for an unbounded range or a ranger larger than the bounds of the sheet, this will be the actual ranges that were cleared, bounded to the sheet's limits.)

bcvrSpreadsheetId :: Lens' BatchClearValuesResponse (Maybe Text) Source #

The spreadsheet the updates were applied to.

BasicChartDomain

data BasicChartDomain Source #

The domain of a chart. For example, if charting stock prices over time, this would be the date.

See: basicChartDomain smart constructor.

Instances

Eq BasicChartDomain Source # 
Data BasicChartDomain Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BasicChartDomain -> c BasicChartDomain #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BasicChartDomain #

toConstr :: BasicChartDomain -> Constr #

dataTypeOf :: BasicChartDomain -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BasicChartDomain) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BasicChartDomain) #

gmapT :: (forall b. Data b => b -> b) -> BasicChartDomain -> BasicChartDomain #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BasicChartDomain -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BasicChartDomain -> r #

gmapQ :: (forall d. Data d => d -> u) -> BasicChartDomain -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BasicChartDomain -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BasicChartDomain -> m BasicChartDomain #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicChartDomain -> m BasicChartDomain #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BasicChartDomain -> m BasicChartDomain #

Show BasicChartDomain Source # 
Generic BasicChartDomain Source # 
ToJSON BasicChartDomain Source # 
FromJSON BasicChartDomain Source # 
type Rep BasicChartDomain Source # 
type Rep BasicChartDomain = D1 (MetaData "BasicChartDomain" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "BasicChartDomain'" PrefixI True) (S1 (MetaSel (Just Symbol "_bcdDomain") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ChartData))))

basicChartDomain :: BasicChartDomain Source #

Creates a value of BasicChartDomain with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

bcdDomain :: Lens' BasicChartDomain (Maybe ChartData) Source #

The data of the domain. For example, if charting stock prices over time, this is the data representing the dates.

InterpolationPointType

data InterpolationPointType Source #

How the value should be interpreted.

Constructors

IPTInterpolationPointTypeUnspecified

INTERPOLATION_POINT_TYPE_UNSPECIFIED The default value, do not use.

IPTMin

MIN The interpolation point will use the minimum value in the cells over the range of the conditional format.

IPTMax

MAX The interpolation point will use the maximum value in the cells over the range of the conditional format.

IPTNumber

NUMBER The interpolation point will use exactly the value in InterpolationPoint.value.

IPTPercent

PERCENT The interpolation point will be the given percentage over all the cells in the range of the conditional format. This is equivalent to NUMBER if the value was: `=(MAX(FLATTEN(range)) * (value / 100)) + (MIN(FLATTEN(range)) * (1 - (value / 100)))` (where errors in the range are ignored when flattening).

IPTPercentile

PERCENTILE The interpolation point will be the given percentile over all the cells in the range of the conditional format. This is equivalent to NUMBER if the value was: `=PERCENTILE(FLATTEN(range), value / 100)` (where errors in the range are ignored when flattening).

Instances

Enum InterpolationPointType Source # 
Eq InterpolationPointType Source # 
Data InterpolationPointType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InterpolationPointType -> c InterpolationPointType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InterpolationPointType #

toConstr :: InterpolationPointType -> Constr #

dataTypeOf :: InterpolationPointType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InterpolationPointType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InterpolationPointType) #

gmapT :: (forall b. Data b => b -> b) -> InterpolationPointType -> InterpolationPointType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InterpolationPointType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InterpolationPointType -> r #

gmapQ :: (forall d. Data d => d -> u) -> InterpolationPointType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InterpolationPointType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InterpolationPointType -> m InterpolationPointType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InterpolationPointType -> m InterpolationPointType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InterpolationPointType -> m InterpolationPointType #

Ord InterpolationPointType Source # 
Read InterpolationPointType Source # 
Show InterpolationPointType Source # 
Generic InterpolationPointType Source # 
Hashable InterpolationPointType Source # 
ToJSON InterpolationPointType Source # 
FromJSON InterpolationPointType Source # 
FromHttpApiData InterpolationPointType Source # 
ToHttpApiData InterpolationPointType Source # 
type Rep InterpolationPointType Source # 
type Rep InterpolationPointType = D1 (MetaData "InterpolationPointType" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "IPTInterpolationPointTypeUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "IPTMin" PrefixI False) U1) (C1 (MetaCons "IPTMax" PrefixI False) U1))) ((:+:) (C1 (MetaCons "IPTNumber" PrefixI False) U1) ((:+:) (C1 (MetaCons "IPTPercent" PrefixI False) U1) (C1 (MetaCons "IPTPercentile" PrefixI False) U1))))

TextToColumnsRequestDelimiterType

data TextToColumnsRequestDelimiterType Source #

The delimiter type to use.

Constructors

TTCRDTDelimiterTypeUnspecified

DELIMITER_TYPE_UNSPECIFIED Default value. This value must not be used.

TTCRDTComma

COMMA ","

TTCRDTSemicolon

SEMICOLON ";"

TTCRDTPeriod

PERIOD "."

TTCRDTSpace

SPACE " "

TTCRDTCustom

CUSTOM A custom value as defined in delimiter.

Instances

Enum TextToColumnsRequestDelimiterType Source # 
Eq TextToColumnsRequestDelimiterType Source # 
Data TextToColumnsRequestDelimiterType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TextToColumnsRequestDelimiterType -> c TextToColumnsRequestDelimiterType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TextToColumnsRequestDelimiterType #

toConstr :: TextToColumnsRequestDelimiterType -> Constr #

dataTypeOf :: TextToColumnsRequestDelimiterType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TextToColumnsRequestDelimiterType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextToColumnsRequestDelimiterType) #

gmapT :: (forall b. Data b => b -> b) -> TextToColumnsRequestDelimiterType -> TextToColumnsRequestDelimiterType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TextToColumnsRequestDelimiterType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TextToColumnsRequestDelimiterType -> r #

gmapQ :: (forall d. Data d => d -> u) -> TextToColumnsRequestDelimiterType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TextToColumnsRequestDelimiterType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TextToColumnsRequestDelimiterType -> m TextToColumnsRequestDelimiterType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TextToColumnsRequestDelimiterType -> m TextToColumnsRequestDelimiterType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TextToColumnsRequestDelimiterType -> m TextToColumnsRequestDelimiterType #

Ord TextToColumnsRequestDelimiterType Source # 
Read TextToColumnsRequestDelimiterType Source # 
Show TextToColumnsRequestDelimiterType Source # 
Generic TextToColumnsRequestDelimiterType Source # 
Hashable TextToColumnsRequestDelimiterType Source # 
ToJSON TextToColumnsRequestDelimiterType Source # 
FromJSON TextToColumnsRequestDelimiterType Source # 
FromHttpApiData TextToColumnsRequestDelimiterType Source # 
ToHttpApiData TextToColumnsRequestDelimiterType Source # 
type Rep TextToColumnsRequestDelimiterType Source # 
type Rep TextToColumnsRequestDelimiterType = D1 (MetaData "TextToColumnsRequestDelimiterType" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) ((:+:) (C1 (MetaCons "TTCRDTDelimiterTypeUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "TTCRDTComma" PrefixI False) U1) (C1 (MetaCons "TTCRDTSemicolon" PrefixI False) U1))) ((:+:) (C1 (MetaCons "TTCRDTPeriod" PrefixI False) U1) ((:+:) (C1 (MetaCons "TTCRDTSpace" PrefixI False) U1) (C1 (MetaCons "TTCRDTCustom" PrefixI False) U1))))

InsertRangeRequest

data InsertRangeRequest Source #

Inserts cells into a range, shifting the existing cells over or down.

See: insertRangeRequest smart constructor.

Instances

Eq InsertRangeRequest Source # 
Data InsertRangeRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InsertRangeRequest -> c InsertRangeRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InsertRangeRequest #

toConstr :: InsertRangeRequest -> Constr #

dataTypeOf :: InsertRangeRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InsertRangeRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InsertRangeRequest) #

gmapT :: (forall b. Data b => b -> b) -> InsertRangeRequest -> InsertRangeRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InsertRangeRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InsertRangeRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> InsertRangeRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InsertRangeRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InsertRangeRequest -> m InsertRangeRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InsertRangeRequest -> m InsertRangeRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InsertRangeRequest -> m InsertRangeRequest #

Show InsertRangeRequest Source # 
Generic InsertRangeRequest Source # 
ToJSON InsertRangeRequest Source # 
FromJSON InsertRangeRequest Source # 
type Rep InsertRangeRequest Source # 
type Rep InsertRangeRequest = D1 (MetaData "InsertRangeRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "InsertRangeRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_irrShiftDimension") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe InsertRangeRequestShiftDimension))) (S1 (MetaSel (Just Symbol "_irrRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GridRange)))))

insertRangeRequest :: InsertRangeRequest Source #

Creates a value of InsertRangeRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

irrShiftDimension :: Lens' InsertRangeRequest (Maybe InsertRangeRequestShiftDimension) Source #

The dimension which will be shifted when inserting cells. If ROWS, existing cells will be shifted down. If COLUMNS, existing cells will be shifted right.

irrRange :: Lens' InsertRangeRequest (Maybe GridRange) Source #

The range to insert new cells into.

InsertRangeRequestShiftDimension

data InsertRangeRequestShiftDimension Source #

The dimension which will be shifted when inserting cells. If ROWS, existing cells will be shifted down. If COLUMNS, existing cells will be shifted right.

Constructors

IRRSDDimensionUnspecified

DIMENSION_UNSPECIFIED The default value, do not use.

IRRSDRows

ROWS Operates on the rows of a sheet.

IRRSDColumns

COLUMNS Operates on the columns of a sheet.

Instances

Enum InsertRangeRequestShiftDimension Source # 
Eq InsertRangeRequestShiftDimension Source # 
Data InsertRangeRequestShiftDimension Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InsertRangeRequestShiftDimension -> c InsertRangeRequestShiftDimension #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InsertRangeRequestShiftDimension #

toConstr :: InsertRangeRequestShiftDimension -> Constr #

dataTypeOf :: InsertRangeRequestShiftDimension -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InsertRangeRequestShiftDimension) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InsertRangeRequestShiftDimension) #

gmapT :: (forall b. Data b => b -> b) -> InsertRangeRequestShiftDimension -> InsertRangeRequestShiftDimension #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InsertRangeRequestShiftDimension -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InsertRangeRequestShiftDimension -> r #

gmapQ :: (forall d. Data d => d -> u) -> InsertRangeRequestShiftDimension -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InsertRangeRequestShiftDimension -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InsertRangeRequestShiftDimension -> m InsertRangeRequestShiftDimension #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InsertRangeRequestShiftDimension -> m InsertRangeRequestShiftDimension #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InsertRangeRequestShiftDimension -> m InsertRangeRequestShiftDimension #

Ord InsertRangeRequestShiftDimension Source # 
Read InsertRangeRequestShiftDimension Source # 
Show InsertRangeRequestShiftDimension Source # 
Generic InsertRangeRequestShiftDimension Source # 
Hashable InsertRangeRequestShiftDimension Source # 
ToJSON InsertRangeRequestShiftDimension Source # 
FromJSON InsertRangeRequestShiftDimension Source # 
FromHttpApiData InsertRangeRequestShiftDimension Source # 
ToHttpApiData InsertRangeRequestShiftDimension Source # 
type Rep InsertRangeRequestShiftDimension Source # 
type Rep InsertRangeRequestShiftDimension = D1 (MetaData "InsertRangeRequestShiftDimension" "Network.Google.Sheets.Types.Sum" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) ((:+:) (C1 (MetaCons "IRRSDDimensionUnspecified" PrefixI False) U1) ((:+:) (C1 (MetaCons "IRRSDRows" PrefixI False) U1) (C1 (MetaCons "IRRSDColumns" PrefixI False) U1)))

Padding

data Padding Source #

The amount of padding around the cell, in pixels. When updating padding, every field must be specified.

See: padding smart constructor.

Instances

Eq Padding Source # 

Methods

(==) :: Padding -> Padding -> Bool #

(/=) :: Padding -> Padding -> Bool #

Data Padding Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Padding -> c Padding #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Padding #

toConstr :: Padding -> Constr #

dataTypeOf :: Padding -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Padding) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Padding) #

gmapT :: (forall b. Data b => b -> b) -> Padding -> Padding #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Padding -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Padding -> r #

gmapQ :: (forall d. Data d => d -> u) -> Padding -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Padding -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Padding -> m Padding #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Padding -> m Padding #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Padding -> m Padding #

Show Padding Source # 
Generic Padding Source # 

Associated Types

type Rep Padding :: * -> * #

Methods

from :: Padding -> Rep Padding x #

to :: Rep Padding x -> Padding #

ToJSON Padding Source # 
FromJSON Padding Source # 
type Rep Padding Source # 

padding :: Padding Source #

Creates a value of Padding with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pBottom :: Lens' Padding (Maybe Int32) Source #

The bottom padding of the cell.

pLeft :: Lens' Padding (Maybe Int32) Source #

The left padding of the cell.

pRight :: Lens' Padding (Maybe Int32) Source #

The right padding of the cell.

pTop :: Lens' Padding (Maybe Int32) Source #

The top padding of the cell.

ChartSpec

data ChartSpec Source #

The specifications of a chart.

See: chartSpec smart constructor.

Instances

Eq ChartSpec Source # 
Data ChartSpec Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChartSpec -> c ChartSpec #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChartSpec #

toConstr :: ChartSpec -> Constr #

dataTypeOf :: ChartSpec -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ChartSpec) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChartSpec) #

gmapT :: (forall b. Data b => b -> b) -> ChartSpec -> ChartSpec #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChartSpec -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChartSpec -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChartSpec -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChartSpec -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChartSpec -> m ChartSpec #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChartSpec -> m ChartSpec #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChartSpec -> m ChartSpec #

Show ChartSpec Source # 
Generic ChartSpec Source # 

Associated Types

type Rep ChartSpec :: * -> * #

ToJSON ChartSpec Source # 
FromJSON ChartSpec Source # 
type Rep ChartSpec Source # 
type Rep ChartSpec = D1 (MetaData "ChartSpec" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "ChartSpec'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_csTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_csPieChart") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PieChartSpec)))) ((:*:) (S1 (MetaSel (Just Symbol "_csBasicChart") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BasicChartSpec))) (S1 (MetaSel (Just Symbol "_csHiddenDimensionStrategy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChartSpecHiddenDimensionStrategy))))))

chartSpec :: ChartSpec Source #

Creates a value of ChartSpec with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

csTitle :: Lens' ChartSpec (Maybe Text) Source #

The title of the chart.

csPieChart :: Lens' ChartSpec (Maybe PieChartSpec) Source #

A pie chart specification.

csBasicChart :: Lens' ChartSpec (Maybe BasicChartSpec) Source #

A basic chart specification, can be one of many kinds of charts. See BasicChartType for the list of all charts this supports.

csHiddenDimensionStrategy :: Lens' ChartSpec (Maybe ChartSpecHiddenDimensionStrategy) Source #

Determines how the charts will use hidden rows or columns.

DimensionProperties

data DimensionProperties Source #

Properties about a dimension.

See: dimensionProperties smart constructor.

Instances

Eq DimensionProperties Source # 
Data DimensionProperties Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DimensionProperties -> c DimensionProperties #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DimensionProperties #

toConstr :: DimensionProperties -> Constr #

dataTypeOf :: DimensionProperties -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DimensionProperties) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DimensionProperties) #

gmapT :: (forall b. Data b => b -> b) -> DimensionProperties -> DimensionProperties #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DimensionProperties -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DimensionProperties -> r #

gmapQ :: (forall d. Data d => d -> u) -> DimensionProperties -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DimensionProperties -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DimensionProperties -> m DimensionProperties #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionProperties -> m DimensionProperties #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionProperties -> m DimensionProperties #

Show DimensionProperties Source # 
Generic DimensionProperties Source # 
ToJSON DimensionProperties Source # 
FromJSON DimensionProperties Source # 
type Rep DimensionProperties Source # 
type Rep DimensionProperties = D1 (MetaData "DimensionProperties" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "DimensionProperties'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dpHiddenByFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_dpPixelSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_dpHiddenByUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))

dimensionProperties :: DimensionProperties Source #

Creates a value of DimensionProperties with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dpHiddenByFilter :: Lens' DimensionProperties (Maybe Bool) Source #

True if this dimension is being filtered. This field is read-only.

dpPixelSize :: Lens' DimensionProperties (Maybe Int32) Source #

The height (if a row) or width (if a column) of the dimension in pixels.

dpHiddenByUser :: Lens' DimensionProperties (Maybe Bool) Source #

True if this dimension is explicitly hidden.

UpdateBandingRequest

data UpdateBandingRequest Source #

Updates properties of the supplied banded range.

See: updateBandingRequest smart constructor.

Instances

Eq UpdateBandingRequest Source # 
Data UpdateBandingRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateBandingRequest -> c UpdateBandingRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateBandingRequest #

toConstr :: UpdateBandingRequest -> Constr #

dataTypeOf :: UpdateBandingRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateBandingRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateBandingRequest) #

gmapT :: (forall b. Data b => b -> b) -> UpdateBandingRequest -> UpdateBandingRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateBandingRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateBandingRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateBandingRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateBandingRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateBandingRequest -> m UpdateBandingRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateBandingRequest -> m UpdateBandingRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateBandingRequest -> m UpdateBandingRequest #

Show UpdateBandingRequest Source # 
Generic UpdateBandingRequest Source # 
ToJSON UpdateBandingRequest Source # 
FromJSON UpdateBandingRequest Source # 
type Rep UpdateBandingRequest Source # 
type Rep UpdateBandingRequest = D1 (MetaData "UpdateBandingRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "UpdateBandingRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ubrBandedRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BandedRange))) (S1 (MetaSel (Just Symbol "_ubrFields") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FieldMask)))))

updateBandingRequest :: UpdateBandingRequest Source #

Creates a value of UpdateBandingRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ubrBandedRange :: Lens' UpdateBandingRequest (Maybe BandedRange) Source #

The banded range to update with the new properties.

ubrFields :: Lens' UpdateBandingRequest (Maybe FieldMask) Source #

The fields that should be updated. At least one field must be specified. The root `bandedRange` is implied and should not be specified. A single `"*"` can be used as short-hand for listing every field.

BatchGetValuesResponse

data BatchGetValuesResponse Source #

The response when retrieving more than one range of values in a spreadsheet.

See: batchGetValuesResponse smart constructor.

Instances

Eq BatchGetValuesResponse Source # 
Data BatchGetValuesResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BatchGetValuesResponse -> c BatchGetValuesResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BatchGetValuesResponse #

toConstr :: BatchGetValuesResponse -> Constr #

dataTypeOf :: BatchGetValuesResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BatchGetValuesResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BatchGetValuesResponse) #

gmapT :: (forall b. Data b => b -> b) -> BatchGetValuesResponse -> BatchGetValuesResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BatchGetValuesResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BatchGetValuesResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> BatchGetValuesResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BatchGetValuesResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BatchGetValuesResponse -> m BatchGetValuesResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BatchGetValuesResponse -> m BatchGetValuesResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BatchGetValuesResponse -> m BatchGetValuesResponse #

Show BatchGetValuesResponse Source # 
Generic BatchGetValuesResponse Source # 
ToJSON BatchGetValuesResponse Source # 
FromJSON BatchGetValuesResponse Source # 
type Rep BatchGetValuesResponse Source # 
type Rep BatchGetValuesResponse = D1 (MetaData "BatchGetValuesResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "BatchGetValuesResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bgvrSpreadsheetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_bgvrValueRanges") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ValueRange])))))

batchGetValuesResponse :: BatchGetValuesResponse Source #

Creates a value of BatchGetValuesResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

bgvrSpreadsheetId :: Lens' BatchGetValuesResponse (Maybe Text) Source #

The ID of the spreadsheet the data was retrieved from.

bgvrValueRanges :: Lens' BatchGetValuesResponse [ValueRange] Source #

The requested values. The order of the ValueRanges is the same as the order of the requested ranges.

DeleteBandingRequest

data DeleteBandingRequest Source #

Removes the banded range with the given ID from the spreadsheet.

See: deleteBandingRequest smart constructor.

Instances

Eq DeleteBandingRequest Source # 
Data DeleteBandingRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeleteBandingRequest -> c DeleteBandingRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeleteBandingRequest #

toConstr :: DeleteBandingRequest -> Constr #

dataTypeOf :: DeleteBandingRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeleteBandingRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeleteBandingRequest) #

gmapT :: (forall b. Data b => b -> b) -> DeleteBandingRequest -> DeleteBandingRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeleteBandingRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeleteBandingRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeleteBandingRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeleteBandingRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeleteBandingRequest -> m DeleteBandingRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteBandingRequest -> m DeleteBandingRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteBandingRequest -> m DeleteBandingRequest #

Show DeleteBandingRequest Source # 
Generic DeleteBandingRequest Source # 
ToJSON DeleteBandingRequest Source # 
FromJSON DeleteBandingRequest Source # 
type Rep DeleteBandingRequest Source # 
type Rep DeleteBandingRequest = D1 (MetaData "DeleteBandingRequest" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "DeleteBandingRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_dbrBandedRangeId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Textual Int32)))))

deleteBandingRequest :: DeleteBandingRequest Source #

Creates a value of DeleteBandingRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dbrBandedRangeId :: Lens' DeleteBandingRequest (Maybe Int32) Source #

The ID of the banded range to delete.

Request'

data Request' Source #

A single kind of update to apply to a spreadsheet.

See: request' smart constructor.

Instances

Eq Request' Source # 
Data Request' Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Request' -> c Request' #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Request' #

toConstr :: Request' -> Constr #

dataTypeOf :: Request' -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Request') #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Request') #

gmapT :: (forall b. Data b => b -> b) -> Request' -> Request' #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Request' -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Request' -> r #

gmapQ :: (forall d. Data d => d -> u) -> Request' -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Request' -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Request' -> m Request' #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Request' -> m Request' #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Request' -> m Request' #

Show Request' Source # 
Generic Request' Source # 

Associated Types

type Rep Request' :: * -> * #

Methods

from :: Request' -> Rep Request' x #

to :: Rep Request' x -> Request' #

ToJSON Request' Source # 
FromJSON Request' Source # 
type Rep Request' Source # 
type Rep Request' = D1 (MetaData "Request'" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "Request''" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_reqAddFilterView") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AddFilterViewRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqDeleteProtectedRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeleteProtectedRangeRequest))) (S1 (MetaSel (Just Symbol "_reqUpdateProtectedRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateProtectedRangeRequest))))) ((:*:) (S1 (MetaSel (Just Symbol "_reqUpdateCells") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateCellsRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqDuplicateFilterView") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DuplicateFilterViewRequest))) (S1 (MetaSel (Just Symbol "_reqAddConditionalFormatRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AddConditionalFormatRuleRequest)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_reqSortRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SortRangeRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqUpdateNamedRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateNamedRangeRequest))) (S1 (MetaSel (Just Symbol "_reqDeleteNamedRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeleteNamedRangeRequest))))) ((:*:) (S1 (MetaSel (Just Symbol "_reqInsertRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe InsertRangeRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqDeleteBanding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeleteBandingRequest))) (S1 (MetaSel (Just Symbol "_reqUpdateBanding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateBandingRequest))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_reqClearBasicFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ClearBasicFilterRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqAppendCells") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AppendCellsRequest))) (S1 (MetaSel (Just Symbol "_reqPasteData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PasteDataRequest))))) ((:*:) (S1 (MetaSel (Just Symbol "_reqUpdateEmbeddedObjectPosition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateEmbeddedObjectPositionRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqDeleteRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeleteRangeRequest))) (S1 (MetaSel (Just Symbol "_reqCopyPaste") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CopyPasteRequest)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_reqAutoResizeDimensions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AutoResizeDimensionsRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqAddSheet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AddSheetRequest))) (S1 (MetaSel (Just Symbol "_reqFindReplace") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FindReplaceRequest))))) ((:*:) (S1 (MetaSel (Just Symbol "_reqDeleteDimension") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeleteDimensionRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqCutPaste") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CutPasteRequest))) (S1 (MetaSel (Just Symbol "_reqMoveDimension") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MoveDimensionRequest)))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_reqRepeatCell") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RepeatCellRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqAddProtectedRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AddProtectedRangeRequest))) (S1 (MetaSel (Just Symbol "_reqUpdateFilterView") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateFilterViewRequest))))) ((:*:) (S1 (MetaSel (Just Symbol "_reqDeleteFilterView") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeleteFilterViewRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqInsertDimension") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe InsertDimensionRequest))) (S1 (MetaSel (Just Symbol "_reqUpdateSheetProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateSheetPropertiesRequest)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_reqDeleteConditionalFormatRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeleteConditionalFormatRuleRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqUpdateConditionalFormatRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateConditionalFormatRuleRequest))) (S1 (MetaSel (Just Symbol "_reqDeleteEmbeddedObject") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeleteEmbeddedObjectRequest))))) ((:*:) (S1 (MetaSel (Just Symbol "_reqMergeCells") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MergeCellsRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqAddNamedRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AddNamedRangeRequest))) (S1 (MetaSel (Just Symbol "_reqAddChart") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AddChartRequest))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_reqAddBanding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AddBandingRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqDuplicateSheet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DuplicateSheetRequest))) (S1 (MetaSel (Just Symbol "_reqAutoFill") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AutoFillRequest))))) ((:*:) (S1 (MetaSel (Just Symbol "_reqUpdateDimensionProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateDimensionPropertiesRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqUpdateChartSpec") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateChartSpecRequest))) (S1 (MetaSel (Just Symbol "_reqSetBasicFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SetBasicFilterRequest)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_reqTextToColumns") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TextToColumnsRequest))) ((:*:) (S1 (MetaSel (Just Symbol "_reqUpdateSpreadsheetProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateSpreadsheetPropertiesRequest))) (S1 (MetaSel (Just Symbol "_reqDeleteSheet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DeleteSheetRequest))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_reqUnmergeCells") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UnmergeCellsRequest))) (S1 (MetaSel (Just Symbol "_reqUpdateBOrders") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UpdateBOrdersRequest)))) ((:*:) (S1 (MetaSel (Just Symbol "_reqAppendDimension") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AppendDimensionRequest))) (S1 (MetaSel (Just Symbol "_reqSetDataValidation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SetDataValidationRequest))))))))))

reqUpdateCells :: Lens' Request' (Maybe UpdateCellsRequest) Source #

Updates many cells at once.

reqInsertRange :: Lens' Request' (Maybe InsertRangeRequest) Source #

Inserts new cells in a sheet, shifting the existing cells.

reqClearBasicFilter :: Lens' Request' (Maybe ClearBasicFilterRequest) Source #

Clears the basic filter on a sheet.

reqAppendCells :: Lens' Request' (Maybe AppendCellsRequest) Source #

Appends cells after the last row with data in a sheet.

reqPasteData :: Lens' Request' (Maybe PasteDataRequest) Source #

Pastes data (HTML or delimited) into a sheet.

reqUpdateEmbeddedObjectPosition :: Lens' Request' (Maybe UpdateEmbeddedObjectPositionRequest) Source #

Updates an embedded object's (e.g. chart, image) position.

reqDeleteRange :: Lens' Request' (Maybe DeleteRangeRequest) Source #

Deletes a range of cells from a sheet, shifting the remaining cells.

reqCopyPaste :: Lens' Request' (Maybe CopyPasteRequest) Source #

Copies data from one area and pastes it to another.

reqAutoResizeDimensions :: Lens' Request' (Maybe AutoResizeDimensionsRequest) Source #

Automatically resizes one or more dimensions based on the contents of the cells in that dimension.

reqFindReplace :: Lens' Request' (Maybe FindReplaceRequest) Source #

Finds and replaces occurrences of some text with other text.

reqDeleteDimension :: Lens' Request' (Maybe DeleteDimensionRequest) Source #

Deletes rows or columns in a sheet.

reqCutPaste :: Lens' Request' (Maybe CutPasteRequest) Source #

Cuts data from one area and pastes it to another.

reqMoveDimension :: Lens' Request' (Maybe MoveDimensionRequest) Source #

Moves rows or columns to another location in a sheet.

reqRepeatCell :: Lens' Request' (Maybe RepeatCellRequest) Source #

Repeats a single cell across a range.

reqUpdateFilterView :: Lens' Request' (Maybe UpdateFilterViewRequest) Source #

Updates the properties of a filter view.

reqDeleteFilterView :: Lens' Request' (Maybe DeleteFilterViewRequest) Source #

Deletes a filter view from a sheet.

reqInsertDimension :: Lens' Request' (Maybe InsertDimensionRequest) Source #

Inserts new rows or columns in a sheet.

reqDeleteEmbeddedObject :: Lens' Request' (Maybe DeleteEmbeddedObjectRequest) Source #

Deletes an embedded object (e.g, chart, image) in a sheet.

reqAutoFill :: Lens' Request' (Maybe AutoFillRequest) Source #

Automatically fills in more data based on existing data.

reqUpdateChartSpec :: Lens' Request' (Maybe UpdateChartSpecRequest) Source #

Updates a chart's specifications.

reqSetBasicFilter :: Lens' Request' (Maybe SetBasicFilterRequest) Source #

Sets the basic filter on a sheet.

reqTextToColumns :: Lens' Request' (Maybe TextToColumnsRequest) Source #

Converts a column of text into many columns of text.

reqUpdateBOrders :: Lens' Request' (Maybe UpdateBOrdersRequest) Source #

Updates the borders in a range of cells.

reqAppendDimension :: Lens' Request' (Maybe AppendDimensionRequest) Source #

Appends dimensions to the end of a sheet.

reqSetDataValidation :: Lens' Request' (Maybe SetDataValidationRequest) Source #

Sets data validation for one or more cells.

DeleteConditionalFormatRuleResponse

data DeleteConditionalFormatRuleResponse Source #

The result of deleting a conditional format rule.

See: deleteConditionalFormatRuleResponse smart constructor.

Instances

Eq DeleteConditionalFormatRuleResponse Source # 
Data DeleteConditionalFormatRuleResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeleteConditionalFormatRuleResponse -> c DeleteConditionalFormatRuleResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeleteConditionalFormatRuleResponse #

toConstr :: DeleteConditionalFormatRuleResponse -> Constr #

dataTypeOf :: DeleteConditionalFormatRuleResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeleteConditionalFormatRuleResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeleteConditionalFormatRuleResponse) #

gmapT :: (forall b. Data b => b -> b) -> DeleteConditionalFormatRuleResponse -> DeleteConditionalFormatRuleResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeleteConditionalFormatRuleResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeleteConditionalFormatRuleResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeleteConditionalFormatRuleResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeleteConditionalFormatRuleResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeleteConditionalFormatRuleResponse -> m DeleteConditionalFormatRuleResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteConditionalFormatRuleResponse -> m DeleteConditionalFormatRuleResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteConditionalFormatRuleResponse -> m DeleteConditionalFormatRuleResponse #

Show DeleteConditionalFormatRuleResponse Source # 
Generic DeleteConditionalFormatRuleResponse Source # 
ToJSON DeleteConditionalFormatRuleResponse Source # 
FromJSON DeleteConditionalFormatRuleResponse Source # 
type Rep DeleteConditionalFormatRuleResponse Source # 
type Rep DeleteConditionalFormatRuleResponse = D1 (MetaData "DeleteConditionalFormatRuleResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" True) (C1 (MetaCons "DeleteConditionalFormatRuleResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_dcfrrRule") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ConditionalFormatRule))))

deleteConditionalFormatRuleResponse :: DeleteConditionalFormatRuleResponse Source #

Creates a value of DeleteConditionalFormatRuleResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

UpdateConditionalFormatRuleResponse

data UpdateConditionalFormatRuleResponse Source #

The result of updating a conditional format rule.

See: updateConditionalFormatRuleResponse smart constructor.

Instances

Eq UpdateConditionalFormatRuleResponse Source # 
Data UpdateConditionalFormatRuleResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateConditionalFormatRuleResponse -> c UpdateConditionalFormatRuleResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateConditionalFormatRuleResponse #

toConstr :: UpdateConditionalFormatRuleResponse -> Constr #

dataTypeOf :: UpdateConditionalFormatRuleResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateConditionalFormatRuleResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateConditionalFormatRuleResponse) #

gmapT :: (forall b. Data b => b -> b) -> UpdateConditionalFormatRuleResponse -> UpdateConditionalFormatRuleResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateConditionalFormatRuleResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateConditionalFormatRuleResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateConditionalFormatRuleResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateConditionalFormatRuleResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateConditionalFormatRuleResponse -> m UpdateConditionalFormatRuleResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateConditionalFormatRuleResponse -> m UpdateConditionalFormatRuleResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateConditionalFormatRuleResponse -> m UpdateConditionalFormatRuleResponse #

Show UpdateConditionalFormatRuleResponse Source # 
Generic UpdateConditionalFormatRuleResponse Source # 
ToJSON UpdateConditionalFormatRuleResponse Source # 
FromJSON UpdateConditionalFormatRuleResponse Source # 
type Rep UpdateConditionalFormatRuleResponse Source # 
type Rep UpdateConditionalFormatRuleResponse = D1 (MetaData "UpdateConditionalFormatRuleResponse" "Network.Google.Sheets.Types.Product" "gogol-sheets-0.2.0-IDNtMXZzsIH4a3bq6iKPtn" False) (C1 (MetaCons "UpdateConditionalFormatRuleResponse'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_uNewRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ConditionalFormatRule))) (S1 (MetaSel (Just Symbol "_uNewIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))) ((:*:) (S1 (MetaSel (Just Symbol "_uOldIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_uOldRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ConditionalFormatRule))))))

updateConditionalFormatRuleResponse :: UpdateConditionalFormatRuleResponse Source #

Creates a value of UpdateConditionalFormatRuleResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

uNewRule :: Lens' UpdateConditionalFormatRuleResponse (Maybe ConditionalFormatRule) Source #

The new rule that replaced the old rule (if replacing), or the rule that was moved (if moved)

uOldIndex :: Lens' UpdateConditionalFormatRuleResponse (Maybe Int32) Source #

The old index of the rule. Not set if a rule was replaced (because it is the same as new_index).

uOldRule :: Lens' UpdateConditionalFormatRuleResponse (Maybe ConditionalFormatRule) Source #

The old (deleted) rule. Not set if a rule was moved (because it is the same as new_rule).